module Text.Regex.Posix.Sequence(
Regex,
MatchOffset,
MatchLength,
ReturnCode,
WrapError,
unusedOffset,
compile,
regexec,
execute,
CompOption(CompOption),
compBlank,
compExtended,
compIgnoreCase,
compNoSub,
compNewline,
ExecOption(ExecOption),
execBlank,
execNotBOL,
execNotEOL
) where
import Data.Array(listArray, Array)
import System.IO.Unsafe(unsafePerformIO)
import Text.Regex.Base.RegexLike(RegexContext(..),RegexMaker(..),RegexLike(..),MatchOffset,MatchLength,Extract(..))
import Text.Regex.Posix.Wrap
import Text.Regex.Base.Impl(polymatch,polymatchM)
import Data.Sequence as S hiding (length)
import qualified Data.Sequence as S (length)
import Foreign.C.String
import Foreign.Marshal.Array
import Foreign.Marshal.Alloc
import Foreign.Storable
instance RegexContext Regex (Seq Char) (Seq Char) where
match = polymatch
matchM = polymatchM
unusedOffset :: Int
unusedOffset = fromIntegral unusedRegOffset
unwrap :: (Show e) => Either e v -> IO v
unwrap x = case x of Left err -> fail ("Text.Regex.Posix.Sequence died: "++ show err)
Right v -> return v
instance RegexMaker Regex CompOption ExecOption (Seq Char) 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 (Seq Char) where
matchTest regex str = unsafePerformIO $ do
withSeq str (wrapTest regex) >>= unwrap
matchOnce regex str = unsafePerformIO $
execute regex str >>= unwrap
matchAll regex str = unsafePerformIO $
withSeq str (wrapMatchAll regex) >>= unwrap
matchCount regex str = unsafePerformIO $
withSeq str (wrapCount regex) >>= unwrap
compile :: CompOption
-> ExecOption
-> (Seq Char)
-> IO (Either WrapError Regex)
compile flags e pattern = withSeq pattern (wrapCompile flags e)
execute :: Regex
-> (Seq Char)
-> IO (Either WrapError (Maybe (Array Int (MatchOffset,MatchLength))))
execute regex str = do
maybeStartEnd <- withSeq str (wrapMatch regex)
case maybeStartEnd of
Right Nothing -> return (Right Nothing)
Right (Just parts) ->
return . Right . Just . listArray (0,pred (length parts))
. map (\(s,e)->(fromIntegral s, fromIntegral (es)))
$ parts
Left err -> return (Left err)
regexec :: Regex
-> (Seq Char)
-> IO (Either WrapError (Maybe ((Seq Char), (Seq Char), (Seq Char), [(Seq Char)])))
regexec regex str = do
let getSub :: (RegOffset,RegOffset) -> (Seq Char)
getSub (start,stop) | start == unusedRegOffset = S.empty
| otherwise =
extract (fromEnum start,fromEnum $ stopstart) $ str
matchedParts :: [(RegOffset,RegOffset)] -> ((Seq Char), (Seq Char), (Seq Char), [(Seq Char)])
matchedParts [] = (str,S.empty,S.empty,[])
matchedParts (matchedStartStop@(start,stop):subStartStop) =
(before (fromEnum start) str
,getSub matchedStartStop
,after (fromEnum stop) str
,map getSub subStartStop)
maybeStartEnd <- withSeq str (wrapMatch regex)
case maybeStartEnd of
Right Nothing -> return (Right Nothing)
Right (Just parts) -> return . Right . Just . matchedParts $ parts
Left err -> return (Left err)
withSeq :: Seq Char -> (CString -> IO a) -> IO a
withSeq s f =
let
s' = case viewr s of
EmptyR -> singleton '\0'
_ :> '\0' -> s
_ -> s |> '\0'
pokes p a = case viewl a of
EmptyL -> return ()
c :< a' -> poke p (castCharToCChar c) >> pokes (advancePtr p 1) a'
in allocaBytes (S.length s') (\ptr -> pokes ptr s' >> f ptr)