{-# OPTIONS_GHC -fglasgow-exts -fno-warn-orphans #-} {-| This modules provides 'RegexMaker' and 'RegexLike' instances for using 'ByteString' with the DFA backend. This module is usually used via import "Text.Regex.DFA". This exports instances of the high level API and the medium level API of 'compile','execute', and 'regexec'. -} module Text.Regex.DFA.ByteString( Regex ,CompOption ,ExecOption ,compile ,execute ,regexec ) where import Data.Array(listArray,Array,elems,(!)) import Text.Regex.DFA.ReadRegex(parseRegex) import Data.ByteString.Char8(ByteString) import qualified Data.ByteString.Char8 as B(unpack,drop) import Text.Regex.Base.RegexLike(RegexContext(..),RegexMaker(..),RegexLike(..)) import Text.Regex.DFA.EngineFPS(findRegex,matchesRegex,countRegex,accept) import Text.Regex.DFA.String() -- piggyback on RegexMaker for String import Text.Regex.DFA.Wrap(Regex(..),CompOption,ExecOption,makeCompat) import Text.Regex.DFA.Transitions(noLoop) import Text.Regex.Base.Impl(polymatch,polymatchM) unwrap :: Either String v -> v unwrap x = case x of Left err -> error ("Text.Regex.Parsec.ByteString died: "++ err) Right v -> v instance RegexContext Regex ByteString ByteString where match = polymatch matchM = polymatchM instance RegexMaker Regex CompOption ExecOption ByteString where makeRegexOpts c e source = unwrap $ compile c e source makeRegexOptsM c e source = either fail return $ compile c e source instance RegexLike Regex ByteString where matchOnce r source = case findRegex regex source of (_,Nothing) -> Nothing (lenBefore,Just (lenOf,_)) -> Just $ listArray (0,0) [(lenBefore,lenOf)] where regex = asLexer r matchAll r source = let loop n | n `seq` False = undefined | otherwise = case findRegex regex (B.drop n source) of (_,Nothing) -> [] (lenBefore,Just (0,_)) -> listArray (0,0) [(n+lenBefore,0)] : [] (lenBefore,Just (lenOf,posAfter)) -> listArray (0,0) [(n+lenBefore,lenOf)] : loop (n+posAfter) in loop 0 where regex = asLexer r matchTest r source = matchesRegex regex source where regex = asLexer r matchCount r source = countRegex regex source where regex = asLexer r compile :: CompOption -- ^ Flags (summed together) -> ExecOption -- ^ Flags (summed together) -> ByteString -- ^ The regular expression to compile -> Either String Regex -- ^ Returns: the compiled regular expression compile compOpt execOpt bs = case parseRegex (B.unpack bs) of Left err -> Left ("parseRegex for DFA failed:"++show err) Right (patternRead,_) -> let pattern = noLoop patternRead lexer = accept (makeCompat compOpt pattern) in Right (Regex pattern lexer compOpt execOpt) execute :: Regex -- ^ Compiled regular expression -> ByteString -- ^ ByteString to match against -> Either String (Maybe (Array Int (Int,Int))) execute r bs = Right (matchOnce r bs) regexec :: Regex -- ^ Compiled regular expression -> ByteString -- ^ ByteString to match against -> Either String (Maybe (ByteString, ByteString, ByteString, [ByteString])) 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)) -- will be [] in Right (Just (pre,main,post,rest))