Bulat Ziganshin wrote:
Hello Chris,

Wednesday, August 2, 2006, 3:16:58 PM, you wrote:

Announcing: TextRegexLazy version 0.56

your feature list is really strong! it will be great now to make it
a part of GHC standard distribution

afaiu, selection of regex engine implemented via import statements?


You can actually choose which backend (=~) uses at runtime:

{-# OPTIONS_GHC -fglasgow-exts #-}
import Text.Regex.Lazy

import qualified Text.Regex.PCRE as R
import qualified Text.Regex.PosixRE as S
import qualified Text.Regex.Full as F

-- Choose which library to use depending on presence of PCRE library

(=~) :: (RegexMaker R.Regex R.CompOption R.ExecOption a,RegexContext R.Regex b t
        ,RegexMaker F.Regex F.CompOption F.ExecOption a,RegexContext F.Regex b t
        ,RegexMaker S.Regex S.CompOption S.ExecOption a,RegexContext S.Regex b 
t)
>      => b -> a -> t
(=~) = case R.getVersion of
         Just _ -> (R.=~)
         Nothing -> case S.getVersion of
                      Just _ -> (S.=~)
                      Nothing -> (F.=~)

main = print (("ba" =~ "(.)a") :: (String,String,String,[String]))

The R.getVersion and S.getVersion detect whether it was compiled against PCRE or PosixRE. The (=~) is then chosen at run time.


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to