module Text.Regex.TDFA.Sequence(
Regex
,CompOption
,ExecOption
,compile
,execute
,regexec
) where
import Data.Sequence(Seq)
import Data.Foldable as F(toList)
import Text.Regex.Base(MatchArray,RegexContext(..),RegexMaker(..),RegexLike(..),Extract(..))
import Text.Regex.Base.Impl(polymatch,polymatchM)
import Text.Regex.TDFA.Common(Regex(..),CompOption,ExecOption(captureGroups))
import Text.Regex.TDFA.String()
import Text.Regex.TDFA.TDFA(patternToRegex)
import Text.Regex.TDFA.ReadRegex(parseRegex)
import Data.Array.IArray((!),elems)
import Data.Maybe(listToMaybe)
import Text.Regex.TDFA.NewDFA.Engine(execMatch)
import Text.Regex.TDFA.NewDFA.Tester as Tester(matchTest)
instance RegexContext Regex (Seq Char) (Seq Char) where
match = polymatch
matchM = polymatchM
instance RegexMaker Regex CompOption ExecOption (Seq Char) where
makeRegexOptsM c e source =
case parseRegex (F.toList source) of
Left err -> fail $ "parseRegex for Text.Regex.TDFA.Sequence failed:"++show err
Right pattern -> return $ patternToRegex pattern c e
instance RegexLike Regex (Seq Char) where
matchOnce r s = listToMaybe (matchAll r s)
matchAll r s = execMatch r 0 '\n' s
matchCount r s = length (matchAll r' s)
where r' = r { regex_execOptions = (regex_execOptions r) {captureGroups = False} }
matchTest = Tester.matchTest
matchOnceText regex source =
fmap (\ma -> let (o,l) = ma!0
in (before o source
,fmap (\ol -> (extract ol source,ol)) ma
,after (o+l) source))
(matchOnce regex source)
matchAllText regex source =
map (fmap (\ol -> (extract ol source,ol)))
(matchAll regex source)
compile :: CompOption
-> ExecOption
-> (Seq Char)
-> Either String Regex
compile compOpt execOpt bs =
case parseRegex (F.toList bs) of
Left err -> Left ("parseRegex for Text.Regex.TDFA.Sequence failed:"++show err)
Right pattern -> Right (patternToRegex pattern compOpt execOpt)
execute :: Regex
-> (Seq Char)
-> Either String (Maybe MatchArray)
execute r bs = Right (matchOnce r bs)
regexec :: Regex
-> (Seq Char)
-> Either String (Maybe ((Seq Char), (Seq Char), (Seq Char), [(Seq Char)]))
regexec r bs =
case matchOnceText r bs of
Nothing -> Right (Nothing)
Just (pre,mt,post) ->
let main = fst (mt!0)
rest = map fst (tail (elems mt))
in Right (Just (pre,main,post,rest))