module Text.Regex.Posix.ByteString.Lazy(
Regex,
MatchOffset,
MatchLength,
ReturnCode,
WrapError,
unusedOffset,
compile,
execute,
regexec,
CompOption(CompOption),
compBlank,
compExtended,
compIgnoreCase,
compNoSub,
compNewline,
ExecOption(ExecOption),
execBlank,
execNotBOL,
execNotEOL
) where
import Data.Array(Array)
import qualified Data.ByteString.Lazy as L (ByteString,null,toChunks,fromChunks,last,snoc)
import qualified Data.ByteString as B(ByteString,concat)
#ifdef SPLIT_BASE
import qualified Data.ByteString.Unsafe as B(unsafeUseAsCString)
#else
import qualified Data.ByteString.Base as B(unsafeUseAsCString)
#endif
import System.IO.Unsafe(unsafePerformIO)
import Text.Regex.Base.RegexLike(RegexMaker(..),RegexContext(..),RegexLike(..),MatchOffset,MatchLength)
import Text.Regex.Posix.Wrap
import qualified Text.Regex.Posix.ByteString as BS(execute,regexec)
import Text.Regex.Base.Impl(polymatch,polymatchM)
import Foreign.C.String(CString)
instance RegexContext Regex L.ByteString L.ByteString where
match = polymatch
matchM = polymatchM
fromLazy :: L.ByteString -> B.ByteString
fromLazy = B.concat . L.toChunks
toLazy :: B.ByteString -> L.ByteString
toLazy = L.fromChunks . return
unwrap :: (Show e) => Either e v -> IO v
unwrap x = case x of Left err -> fail ("Text.Regex.Posix.ByteString.Lazy died: "++ show err)
Right v -> return v
asCString :: L.ByteString -> (CString -> IO a) -> IO a
asCString s = if (not (L.null s)) && (0==L.last s)
then B.unsafeUseAsCString (fromLazy s)
else B.unsafeUseAsCString (fromLazy (L.snoc s 0))
instance RegexMaker Regex CompOption ExecOption L.ByteString where
makeRegexOpts c e pattern = unsafePerformIO $ compile c e pattern >>= unwrap
makeRegexOptsM c e pattern = either (fail.show) return $ unsafePerformIO $ compile c e pattern
instance RegexLike Regex L.ByteString where
matchTest regex bs = unsafePerformIO $
asCString bs (wrapTest regex) >>= unwrap
matchOnce regex bs = unsafePerformIO $
execute regex bs >>= unwrap
matchAll regex bs = unsafePerformIO $
asCString bs (wrapMatchAll regex) >>= unwrap
matchCount regex bs = unsafePerformIO $
asCString bs (wrapCount regex) >>= unwrap
compile :: CompOption
-> ExecOption
-> L.ByteString
-> IO (Either WrapError Regex)
compile c e pattern = asCString pattern (wrapCompile c e)
execute :: Regex
-> L.ByteString
-> IO (Either WrapError (Maybe (Array Int (MatchOffset,MatchLength))))
execute regex bs = if (not (L.null bs)) && (0==L.last bs)
then BS.execute regex (fromLazy bs)
else BS.execute regex (fromLazy (L.snoc bs 0))
regexec :: Regex
-> L.ByteString
-> IO (Either WrapError (Maybe (L.ByteString, L.ByteString, L.ByteString, [L.ByteString])))
regexec regex bs = do
x <- if (not (L.null bs)) && (0==L.last bs)
then BS.regexec regex (fromLazy bs)
else BS.regexec regex (fromLazy (L.snoc bs 0))
return $ case x of
Left e -> Left e
Right Nothing -> Right Nothing
Right (Just (a,b,c,ds)) -> Right (Just (toLazy a,toLazy b,toLazy c,map toLazy ds))
unusedOffset :: Int
unusedOffset = fromIntegral unusedRegOffset