{-# LINE 1 "src/Text/Regex/Posix/Wrap.hsc" #-}
{-# OPTIONS_GHC -Wall -fno-warn-unused-imports #-}
module Text.Regex.Posix.Wrap(
Regex,
RegOffset,
RegOffsetT,
(=~),
(=~~),
WrapError,
wrapCompile,
wrapTest,
wrapMatch,
wrapMatchAll,
wrapCount,
unusedRegOffset,
CompOption(CompOption),
compBlank,
compExtended,
compIgnoreCase,
compNoSub,
compNewline,
ExecOption(ExecOption),
execBlank,
execNotBOL,
execNotEOL,
ReturnCode(ReturnCode),
retBadbr,
retBadpat,
retBadrpt,
retEcollate,
retEctype,
retEescape,
retEsubreg,
retEbrack,
retEparen,
retEbrace,
retErange,
retEspace
) where
{-# LINE 95 "src/Text/Regex/Posix/Wrap.hsc" #-}
import Prelude hiding (fail)
import Control.Monad.Fail (MonadFail)
import Control.Monad(liftM)
import Data.Array(Array,listArray)
import Data.Bits(Bits(..))
import Data.Int(Int32,Int64)
import Data.Word(Word32,Word64)
import Foreign(Ptr, FunPtr, nullPtr, newForeignPtr,
addForeignPtrFinalizer, Storable(peekByteOff), allocaArray,
allocaBytes, withForeignPtr,ForeignPtr,plusPtr,peekElemOff)
import Foreign.Marshal.Alloc(mallocBytes)
import Foreign.C(CChar)
{-# LINE 114 "src/Text/Regex/Posix/Wrap.hsc" #-}
import Foreign.C(CSize(CSize),CInt(CInt))
{-# LINE 118 "src/Text/Regex/Posix/Wrap.hsc" #-}
import Foreign.C.String(peekCAString, CString)
import Text.Regex.Base.RegexLike(RegexOptions(..),RegexMaker(..),RegexContext(..),MatchArray)
import qualified Control.Exception(try,IOException)
try :: IO a -> IO (Either Control.Exception.IOException a)
try :: forall a. IO a -> IO (Either IOException a)
try = IO a -> IO (Either IOException a)
forall e a. Exception e => IO a -> IO (Either e a)
Control.Exception.try
data CRegex
type RegOffset = Int64
type RegOffsetT = (Int64)
{-# LINE 145 "src/Text/Regex/Posix/Wrap.hsc" #-}
newtype CompOption = CompOption CInt deriving (CompOption -> CompOption -> Bool
(CompOption -> CompOption -> Bool)
-> (CompOption -> CompOption -> Bool) -> Eq CompOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompOption -> CompOption -> Bool
$c/= :: CompOption -> CompOption -> Bool
== :: CompOption -> CompOption -> Bool
$c== :: CompOption -> CompOption -> Bool
Eq,Int -> CompOption -> ShowS
[CompOption] -> ShowS
CompOption -> String
(Int -> CompOption -> ShowS)
-> (CompOption -> String)
-> ([CompOption] -> ShowS)
-> Show CompOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompOption] -> ShowS
$cshowList :: [CompOption] -> ShowS
show :: CompOption -> String
$cshow :: CompOption -> String
showsPrec :: Int -> CompOption -> ShowS
$cshowsPrec :: Int -> CompOption -> ShowS
Show,Integer -> CompOption
CompOption -> CompOption
CompOption -> CompOption -> CompOption
(CompOption -> CompOption -> CompOption)
-> (CompOption -> CompOption -> CompOption)
-> (CompOption -> CompOption -> CompOption)
-> (CompOption -> CompOption)
-> (CompOption -> CompOption)
-> (CompOption -> CompOption)
-> (Integer -> CompOption)
-> Num CompOption
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> CompOption
$cfromInteger :: Integer -> CompOption
signum :: CompOption -> CompOption
$csignum :: CompOption -> CompOption
abs :: CompOption -> CompOption
$cabs :: CompOption -> CompOption
negate :: CompOption -> CompOption
$cnegate :: CompOption -> CompOption
* :: CompOption -> CompOption -> CompOption
$c* :: CompOption -> CompOption -> CompOption
- :: CompOption -> CompOption -> CompOption
$c- :: CompOption -> CompOption -> CompOption
+ :: CompOption -> CompOption -> CompOption
$c+ :: CompOption -> CompOption -> CompOption
Num,Eq CompOption
CompOption
Eq CompOption
-> (CompOption -> CompOption -> CompOption)
-> (CompOption -> CompOption -> CompOption)
-> (CompOption -> CompOption -> CompOption)
-> (CompOption -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> CompOption
-> (Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> Bool)
-> (CompOption -> Maybe Int)
-> (CompOption -> Int)
-> (CompOption -> Bool)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int -> CompOption)
-> (CompOption -> Int)
-> Bits CompOption
Int -> CompOption
CompOption -> Bool
CompOption -> Int
CompOption -> Maybe Int
CompOption -> CompOption
CompOption -> Int -> Bool
CompOption -> Int -> CompOption
CompOption -> CompOption -> CompOption
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: CompOption -> Int
$cpopCount :: CompOption -> Int
rotateR :: CompOption -> Int -> CompOption
$crotateR :: CompOption -> Int -> CompOption
rotateL :: CompOption -> Int -> CompOption
$crotateL :: CompOption -> Int -> CompOption
unsafeShiftR :: CompOption -> Int -> CompOption
$cunsafeShiftR :: CompOption -> Int -> CompOption
shiftR :: CompOption -> Int -> CompOption
$cshiftR :: CompOption -> Int -> CompOption
unsafeShiftL :: CompOption -> Int -> CompOption
$cunsafeShiftL :: CompOption -> Int -> CompOption
shiftL :: CompOption -> Int -> CompOption
$cshiftL :: CompOption -> Int -> CompOption
isSigned :: CompOption -> Bool
$cisSigned :: CompOption -> Bool
bitSize :: CompOption -> Int
$cbitSize :: CompOption -> Int
bitSizeMaybe :: CompOption -> Maybe Int
$cbitSizeMaybe :: CompOption -> Maybe Int
testBit :: CompOption -> Int -> Bool
$ctestBit :: CompOption -> Int -> Bool
complementBit :: CompOption -> Int -> CompOption
$ccomplementBit :: CompOption -> Int -> CompOption
clearBit :: CompOption -> Int -> CompOption
$cclearBit :: CompOption -> Int -> CompOption
setBit :: CompOption -> Int -> CompOption
$csetBit :: CompOption -> Int -> CompOption
bit :: Int -> CompOption
$cbit :: Int -> CompOption
zeroBits :: CompOption
$czeroBits :: CompOption
rotate :: CompOption -> Int -> CompOption
$crotate :: CompOption -> Int -> CompOption
shift :: CompOption -> Int -> CompOption
$cshift :: CompOption -> Int -> CompOption
complement :: CompOption -> CompOption
$ccomplement :: CompOption -> CompOption
xor :: CompOption -> CompOption -> CompOption
$cxor :: CompOption -> CompOption -> CompOption
.|. :: CompOption -> CompOption -> CompOption
$c.|. :: CompOption -> CompOption -> CompOption
.&. :: CompOption -> CompOption -> CompOption
$c.&. :: CompOption -> CompOption -> CompOption
Bits)
newtype ExecOption = ExecOption CInt deriving (ExecOption -> ExecOption -> Bool
(ExecOption -> ExecOption -> Bool)
-> (ExecOption -> ExecOption -> Bool) -> Eq ExecOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecOption -> ExecOption -> Bool
$c/= :: ExecOption -> ExecOption -> Bool
== :: ExecOption -> ExecOption -> Bool
$c== :: ExecOption -> ExecOption -> Bool
Eq,Int -> ExecOption -> ShowS
[ExecOption] -> ShowS
ExecOption -> String
(Int -> ExecOption -> ShowS)
-> (ExecOption -> String)
-> ([ExecOption] -> ShowS)
-> Show ExecOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecOption] -> ShowS
$cshowList :: [ExecOption] -> ShowS
show :: ExecOption -> String
$cshow :: ExecOption -> String
showsPrec :: Int -> ExecOption -> ShowS
$cshowsPrec :: Int -> ExecOption -> ShowS
Show,Integer -> ExecOption
ExecOption -> ExecOption
ExecOption -> ExecOption -> ExecOption
(ExecOption -> ExecOption -> ExecOption)
-> (ExecOption -> ExecOption -> ExecOption)
-> (ExecOption -> ExecOption -> ExecOption)
-> (ExecOption -> ExecOption)
-> (ExecOption -> ExecOption)
-> (ExecOption -> ExecOption)
-> (Integer -> ExecOption)
-> Num ExecOption
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ExecOption
$cfromInteger :: Integer -> ExecOption
signum :: ExecOption -> ExecOption
$csignum :: ExecOption -> ExecOption
abs :: ExecOption -> ExecOption
$cabs :: ExecOption -> ExecOption
negate :: ExecOption -> ExecOption
$cnegate :: ExecOption -> ExecOption
* :: ExecOption -> ExecOption -> ExecOption
$c* :: ExecOption -> ExecOption -> ExecOption
- :: ExecOption -> ExecOption -> ExecOption
$c- :: ExecOption -> ExecOption -> ExecOption
+ :: ExecOption -> ExecOption -> ExecOption
$c+ :: ExecOption -> ExecOption -> ExecOption
Num,Eq ExecOption
ExecOption
Eq ExecOption
-> (ExecOption -> ExecOption -> ExecOption)
-> (ExecOption -> ExecOption -> ExecOption)
-> (ExecOption -> ExecOption -> ExecOption)
-> (ExecOption -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> ExecOption
-> (Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> Bool)
-> (ExecOption -> Maybe Int)
-> (ExecOption -> Int)
-> (ExecOption -> Bool)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int -> ExecOption)
-> (ExecOption -> Int)
-> Bits ExecOption
Int -> ExecOption
ExecOption -> Bool
ExecOption -> Int
ExecOption -> Maybe Int
ExecOption -> ExecOption
ExecOption -> Int -> Bool
ExecOption -> Int -> ExecOption
ExecOption -> ExecOption -> ExecOption
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: ExecOption -> Int
$cpopCount :: ExecOption -> Int
rotateR :: ExecOption -> Int -> ExecOption
$crotateR :: ExecOption -> Int -> ExecOption
rotateL :: ExecOption -> Int -> ExecOption
$crotateL :: ExecOption -> Int -> ExecOption
unsafeShiftR :: ExecOption -> Int -> ExecOption
$cunsafeShiftR :: ExecOption -> Int -> ExecOption
shiftR :: ExecOption -> Int -> ExecOption
$cshiftR :: ExecOption -> Int -> ExecOption
unsafeShiftL :: ExecOption -> Int -> ExecOption
$cunsafeShiftL :: ExecOption -> Int -> ExecOption
shiftL :: ExecOption -> Int -> ExecOption
$cshiftL :: ExecOption -> Int -> ExecOption
isSigned :: ExecOption -> Bool
$cisSigned :: ExecOption -> Bool
bitSize :: ExecOption -> Int
$cbitSize :: ExecOption -> Int
bitSizeMaybe :: ExecOption -> Maybe Int
$cbitSizeMaybe :: ExecOption -> Maybe Int
testBit :: ExecOption -> Int -> Bool
$ctestBit :: ExecOption -> Int -> Bool
complementBit :: ExecOption -> Int -> ExecOption
$ccomplementBit :: ExecOption -> Int -> ExecOption
clearBit :: ExecOption -> Int -> ExecOption
$cclearBit :: ExecOption -> Int -> ExecOption
setBit :: ExecOption -> Int -> ExecOption
$csetBit :: ExecOption -> Int -> ExecOption
bit :: Int -> ExecOption
$cbit :: Int -> ExecOption
zeroBits :: ExecOption
$czeroBits :: ExecOption
rotate :: ExecOption -> Int -> ExecOption
$crotate :: ExecOption -> Int -> ExecOption
shift :: ExecOption -> Int -> ExecOption
$cshift :: ExecOption -> Int -> ExecOption
complement :: ExecOption -> ExecOption
$ccomplement :: ExecOption -> ExecOption
xor :: ExecOption -> ExecOption -> ExecOption
$cxor :: ExecOption -> ExecOption -> ExecOption
.|. :: ExecOption -> ExecOption -> ExecOption
$c.|. :: ExecOption -> ExecOption -> ExecOption
.&. :: ExecOption -> ExecOption -> ExecOption
$c.&. :: ExecOption -> ExecOption -> ExecOption
Bits)
newtype ReturnCode = ReturnCode CInt deriving (ReturnCode -> ReturnCode -> Bool
(ReturnCode -> ReturnCode -> Bool)
-> (ReturnCode -> ReturnCode -> Bool) -> Eq ReturnCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReturnCode -> ReturnCode -> Bool
$c/= :: ReturnCode -> ReturnCode -> Bool
== :: ReturnCode -> ReturnCode -> Bool
$c== :: ReturnCode -> ReturnCode -> Bool
Eq,Int -> ReturnCode -> ShowS
[ReturnCode] -> ShowS
ReturnCode -> String
(Int -> ReturnCode -> ShowS)
-> (ReturnCode -> String)
-> ([ReturnCode] -> ShowS)
-> Show ReturnCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReturnCode] -> ShowS
$cshowList :: [ReturnCode] -> ShowS
show :: ReturnCode -> String
$cshow :: ReturnCode -> String
showsPrec :: Int -> ReturnCode -> ShowS
$cshowsPrec :: Int -> ReturnCode -> ShowS
Show)
data Regex = Regex (ForeignPtr CRegex) CompOption ExecOption
compBlank :: CompOption
compBlank :: CompOption
compBlank = CInt -> CompOption
CompOption CInt
0
execBlank :: ExecOption
execBlank :: ExecOption
execBlank = CInt -> ExecOption
ExecOption CInt
0
unusedRegOffset :: RegOffset
unusedRegOffset :: Int64
unusedRegOffset = (-Int64
1)
type WrapError = (ReturnCode,String)
wrapCompile :: CompOption
-> ExecOption
-> CString
-> IO (Either WrapError Regex)
wrapTest :: Regex -> CString
-> IO (Either WrapError Bool)
wrapMatch :: Regex -> CString
-> IO (Either WrapError (Maybe [(RegOffset,RegOffset)]))
wrapMatchAll :: Regex -> CString
-> IO (Either WrapError [MatchArray])
wrapCount :: Regex -> CString
-> IO (Either WrapError Int)
(=~) :: (RegexMaker Regex CompOption ExecOption source,RegexContext Regex source1 target)
=> source1 -> source -> target
(=~~) :: (RegexMaker Regex CompOption ExecOption source,RegexContext Regex source1 target,MonadFail m)
=> source1 -> source -> m target
instance RegexOptions Regex CompOption ExecOption where
blankCompOpt :: CompOption
blankCompOpt = CompOption
compBlank
blankExecOpt :: ExecOption
blankExecOpt = ExecOption
execBlank
defaultCompOpt :: CompOption
defaultCompOpt = CompOption
compExtended CompOption -> CompOption -> CompOption
forall a. Bits a => a -> a -> a
.|. CompOption
compNewline
defaultExecOpt :: ExecOption
defaultExecOpt = ExecOption
execBlank
setExecOpts :: ExecOption -> Regex -> Regex
setExecOpts ExecOption
e' (Regex ForeignPtr CRegex
r CompOption
c ExecOption
_) = ForeignPtr CRegex -> CompOption -> ExecOption -> Regex
Regex ForeignPtr CRegex
r CompOption
c ExecOption
e'
getExecOpts :: Regex -> ExecOption
getExecOpts (Regex ForeignPtr CRegex
_ CompOption
_ ExecOption
e) = ExecOption
e
=~ :: forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
(=~) source1
x source
r = let make :: RegexMaker Regex CompOption ExecOption a => a -> Regex
make :: forall a. RegexMaker Regex CompOption ExecOption a => a -> Regex
make = a -> Regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
source -> regex
makeRegex
in Regex -> source1 -> target
forall regex source target.
RegexContext regex source target =>
regex -> source -> target
match (source -> Regex
forall a. RegexMaker Regex CompOption ExecOption a => a -> Regex
make source
r) source1
x
=~~ :: forall source source1 target (m :: * -> *).
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target, MonadFail m) =>
source1 -> source -> m target
(=~~) source1
x source
r = let make :: RegexMaker Regex CompOption ExecOption a => a -> Regex
make :: forall a. RegexMaker Regex CompOption ExecOption a => a -> Regex
make = a -> Regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
source -> regex
makeRegex
in Regex -> source1 -> m target
forall regex source target (m :: * -> *).
(RegexContext regex source target, MonadFail m) =>
regex -> source -> m target
matchM (source -> Regex
forall a. RegexMaker Regex CompOption ExecOption a => a -> Regex
make source
r) source1
x
type CRegMatch = ()
foreign import ccall unsafe "memset"
c_memset :: Ptr CRegex -> CInt -> CSize -> IO (Ptr CRegex)
foreign import ccall unsafe "&hs_regex_regfree"
c_myregfree :: FunPtr (Ptr CRegex -> IO ())
foreign import ccall unsafe "regex.h regcomp"
c_regcomp :: Ptr CRegex -> CString -> CompOption -> IO ReturnCode
foreign import ccall unsafe "regex.h regexec"
c_regexec :: Ptr CRegex -> CString -> CSize
-> Ptr CRegMatch -> ExecOption -> IO ReturnCode
foreign import ccall unsafe "regex.h regerror"
c_regerror :: ReturnCode -> Ptr CRegex
-> CString -> CSize -> IO CSize
retOk :: ReturnCode
retOk :: ReturnCode
retOk = CInt -> ReturnCode
ReturnCode CInt
0
execNotBOL :: ExecOption
execNotBOL :: ExecOption
execNotBOL = CInt -> ExecOption
ExecOption CInt
1
execNotEOL :: ExecOption
execNotEOL :: ExecOption
execNotEOL = CInt -> ExecOption
ExecOption CInt
2
{-# LINE 314 "src/Text/Regex/Posix/Wrap.hsc" #-}
compExtended :: CompOption
compExtended :: CompOption
compExtended = CInt -> CompOption
CompOption CInt
1
compIgnoreCase :: CompOption
compIgnoreCase :: CompOption
compIgnoreCase = CInt -> CompOption
CompOption CInt
2
compNoSub :: CompOption
compNoSub :: CompOption
compNoSub = CInt -> CompOption
CompOption CInt
4
compNewline :: CompOption
compNewline :: CompOption
compNewline = CInt -> CompOption
CompOption CInt
8
{-# LINE 321 "src/Text/Regex/Posix/Wrap.hsc" #-}
retNoMatch :: ReturnCode
retNoMatch :: ReturnCode
retNoMatch = CInt -> ReturnCode
ReturnCode CInt
1
retBadbr :: ReturnCode
retBadbr :: ReturnCode
retBadbr = CInt -> ReturnCode
ReturnCode CInt
10
retBadpat :: ReturnCode
retBadpat :: ReturnCode
retBadpat = CInt -> ReturnCode
ReturnCode CInt
2
retBadrpt :: ReturnCode
retBadrpt :: ReturnCode
retBadrpt = CInt -> ReturnCode
ReturnCode CInt
13
retEcollate :: ReturnCode
retEcollate :: ReturnCode
retEcollate = CInt -> ReturnCode
ReturnCode CInt
3
retEctype :: ReturnCode
retEctype :: ReturnCode
retEctype = CInt -> ReturnCode
ReturnCode CInt
4
retEescape :: ReturnCode
retEescape :: ReturnCode
retEescape = CInt -> ReturnCode
ReturnCode CInt
5
retEsubreg :: ReturnCode
retEsubreg :: ReturnCode
retEsubreg = CInt -> ReturnCode
ReturnCode CInt
6
retEbrack :: ReturnCode
retEbrack :: ReturnCode
retEbrack = CInt -> ReturnCode
ReturnCode CInt
7
retEparen :: ReturnCode
retEparen :: ReturnCode
retEparen = CInt -> ReturnCode
ReturnCode CInt
8
retEbrace :: ReturnCode
retEbrace :: ReturnCode
retEbrace = CInt -> ReturnCode
ReturnCode CInt
9
retErange :: ReturnCode
retErange :: ReturnCode
retErange = CInt -> ReturnCode
ReturnCode CInt
11
retEspace :: ReturnCode
isNewline :: Ptr CChar -> Int -> IO Bool
retEspace :: ReturnCode
retEspace = CInt -> ReturnCode
ReturnCode CInt
12
{-# LINE 339 "src/Text/Regex/Posix/Wrap.hsc" #-}
nullTest :: Ptr a -> String -> IO (Either WrapError b) -> IO (Either WrapError b)
{-# INLINE nullTest #-}
nullTest ptr msg io = do
if nullPtr == ptr
then return (Left (retOk,"Ptr parameter was nullPtr in Text.Regex.TRE.Wrap."++msg))
else io
isNewline,isNull :: Ptr CChar -> Int -> IO Bool
isNewline cstr pos = liftM (newline ==) (peekElemOff cstr pos)
where newline = toEnum 10
isNull cstr pos = liftM (nullChar ==) (peekElemOff cstr pos)
where nullChar = toEnum 0
wrapError :: ReturnCode -> Ptr CRegex -> IO (Either WrapError b)
wrapError :: forall b. ReturnCode -> Ptr CRegex -> IO (Either WrapError b)
wrapError ReturnCode
errCode Ptr CRegex
regex_ptr = do
CSize
errBufSize <- ReturnCode -> Ptr CRegex -> Ptr CChar -> CSize -> IO CSize
c_regerror ReturnCode
errCode Ptr CRegex
regex_ptr Ptr CChar
forall a. Ptr a
nullPtr CSize
0
Int
-> (Ptr CChar -> IO (Either WrapError b))
-> IO (Either WrapError b)
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
errBufSize) ((Ptr CChar -> IO (Either WrapError b)) -> IO (Either WrapError b))
-> (Ptr CChar -> IO (Either WrapError b))
-> IO (Either WrapError b)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
errBuf -> do
Ptr CChar
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CChar
errBuf String
"wrapError errBuf" (IO (Either WrapError b) -> IO (Either WrapError b))
-> IO (Either WrapError b) -> IO (Either WrapError b)
forall a b. (a -> b) -> a -> b
$ do
CSize
_ <- ReturnCode -> Ptr CRegex -> Ptr CChar -> CSize -> IO CSize
c_regerror ReturnCode
errCode Ptr CRegex
regex_ptr Ptr CChar
errBuf CSize
errBufSize
String
msg <- Ptr CChar -> IO String
peekCAString Ptr CChar
errBuf :: IO String
Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError b
forall a b. a -> Either a b
Left (ReturnCode
errCode, String
msg))
wrapCompile :: CompOption
-> ExecOption -> Ptr CChar -> IO (Either WrapError Regex)
wrapCompile CompOption
flags ExecOption
e Ptr CChar
pattern = do
Ptr CChar
-> String
-> IO (Either WrapError Regex)
-> IO (Either WrapError Regex)
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CChar
pattern String
"wrapCompile pattern" (IO (Either WrapError Regex) -> IO (Either WrapError Regex))
-> IO (Either WrapError Regex) -> IO (Either WrapError Regex)
forall a b. (a -> b) -> a -> b
$ do
Either IOException (Ptr CRegex)
e_regex_ptr <- IO (Ptr CRegex) -> IO (Either IOException (Ptr CRegex))
forall a. IO a -> IO (Either IOException a)
try (IO (Ptr CRegex) -> IO (Either IOException (Ptr CRegex)))
-> IO (Ptr CRegex) -> IO (Either IOException (Ptr CRegex))
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr CRegex)
forall a. Int -> IO (Ptr a)
mallocBytes (Int
32)
{-# LINE 375 "src/Text/Regex/Posix/Wrap.hsc" #-}
case e_regex_ptr of
Left ioerror -> return (Left (retOk,"Text.Regex.Posix.Wrap.wrapCompile: IOError from mallocBytes(regex_t) : "++show ioerror))
Right raw_regex_ptr -> do
zero_regex_ptr <- c_memset raw_regex_ptr 0 (32)
{-# LINE 379 "src/Text/Regex/Posix/Wrap.hsc" #-}
regex_fptr <- newForeignPtr c_myregfree zero_regex_ptr
withForeignPtr regex_fptr $ \regex_ptr -> do
errCode <- c_regcomp regex_ptr pattern flags
if (errCode == retOk)
then return . Right $ Regex regex_fptr flags e
else wrapError errCode regex_ptr
wrapTest :: Regex -> Ptr CChar -> IO (Either WrapError Bool)
wrapTest (Regex ForeignPtr CRegex
regex_fptr CompOption
_ ExecOption
flags) Ptr CChar
cstr = do
Ptr CChar
-> String
-> IO (Either WrapError Bool)
-> IO (Either WrapError Bool)
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CChar
cstr String
"wrapTest" (IO (Either WrapError Bool) -> IO (Either WrapError Bool))
-> IO (Either WrapError Bool) -> IO (Either WrapError Bool)
forall a b. (a -> b) -> a -> b
$ do
ForeignPtr CRegex
-> (Ptr CRegex -> IO (Either WrapError Bool))
-> IO (Either WrapError Bool)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CRegex
regex_fptr ((Ptr CRegex -> IO (Either WrapError Bool))
-> IO (Either WrapError Bool))
-> (Ptr CRegex -> IO (Either WrapError Bool))
-> IO (Either WrapError Bool)
forall a b. (a -> b) -> a -> b
$ \Ptr CRegex
regex_ptr -> do
ReturnCode
r <- Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO ReturnCode
c_regexec Ptr CRegex
regex_ptr Ptr CChar
cstr CSize
0 Ptr CRegMatch
forall a. Ptr a
nullPtr ExecOption
flags
if ReturnCode
r ReturnCode -> ReturnCode -> Bool
forall a. Eq a => a -> a -> Bool
== ReturnCode
retOk
then Either WrapError Bool -> IO (Either WrapError Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Either WrapError Bool
forall a b. b -> Either a b
Right Bool
True)
else if ReturnCode
r ReturnCode -> ReturnCode -> Bool
forall a. Eq a => a -> a -> Bool
== ReturnCode
retNoMatch
then Either WrapError Bool -> IO (Either WrapError Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Either WrapError Bool
forall a b. b -> Either a b
Right Bool
False)
else ReturnCode -> Ptr CRegex -> IO (Either WrapError Bool)
forall b. ReturnCode -> Ptr CRegex -> IO (Either WrapError b)
wrapError ReturnCode
r Ptr CRegex
regex_ptr
wrapMatch :: Regex
-> Ptr CChar -> IO (Either WrapError (Maybe [(Int64, Int64)]))
wrapMatch regex :: Regex
regex@(Regex ForeignPtr CRegex
regex_fptr CompOption
compileOptions ExecOption
flags) Ptr CChar
cstr = do
Ptr CChar
-> String
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CChar
cstr String
"wrapMatch cstr" (IO (Either WrapError (Maybe [(Int64, Int64)]))
-> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b. (a -> b) -> a -> b
$ do
if (CompOption
0 CompOption -> CompOption -> Bool
forall a. Eq a => a -> a -> Bool
/= CompOption
compNoSub CompOption -> CompOption -> CompOption
forall a. Bits a => a -> a -> a
.&. CompOption
compileOptions)
then do
Either WrapError Bool
r <- Regex -> Ptr CChar -> IO (Either WrapError Bool)
wrapTest Regex
regex Ptr CChar
cstr
case Either WrapError Bool
r of
Right Bool
True -> Either WrapError (Maybe [(Int64, Int64)])
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [(Int64, Int64)] -> Either WrapError (Maybe [(Int64, Int64)])
forall a b. b -> Either a b
Right ([(Int64, Int64)] -> Maybe [(Int64, Int64)]
forall a. a -> Maybe a
Just []))
Right Bool
False -> Either WrapError (Maybe [(Int64, Int64)])
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [(Int64, Int64)] -> Either WrapError (Maybe [(Int64, Int64)])
forall a b. b -> Either a b
Right Maybe [(Int64, Int64)]
forall a. Maybe a
Nothing)
Left WrapError
err -> Either WrapError (Maybe [(Int64, Int64)])
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError (Maybe [(Int64, Int64)])
forall a b. a -> Either a b
Left WrapError
err)
else do
ForeignPtr CRegex
-> (Ptr CRegex -> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CRegex
regex_fptr ((Ptr CRegex -> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> (Ptr CRegex -> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b. (a -> b) -> a -> b
$ \Ptr CRegex
regex_ptr -> do
CSize
nsub <- ((\Ptr CRegex
hsc_ptr -> Ptr CRegex -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CRegex
hsc_ptr Int
8)) Ptr CRegex
regex_ptr :: IO CSize
{-# LINE 410 "src/Text/Regex/Posix/Wrap.hsc" #-}
let nsub_int,nsub_bytes :: Int
nsub_int :: Int
nsub_int = CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nsub
nsub_bytes :: Int
nsub_bytes = ((Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
nsub_int) Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
16))
{-# LINE 413 "src/Text/Regex/Posix/Wrap.hsc" #-}
Int
-> (Ptr CRegMatch
-> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nsub_bytes ((Ptr CRegMatch -> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> (Ptr CRegMatch
-> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b. (a -> b) -> a -> b
$ \Ptr CRegMatch
p_match -> do
Ptr CRegMatch
-> String
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CRegMatch
p_match String
"wrapMatch allocaBytes" (IO (Either WrapError (Maybe [(Int64, Int64)]))
-> IO (Either WrapError (Maybe [(Int64, Int64)])))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall a b. (a -> b) -> a -> b
$ do
Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr Ptr CChar
cstr CSize
nsub Ptr CRegMatch
p_match ExecOption
flags
doMatch :: Ptr CRegex -> CString -> CSize -> Ptr CRegMatch -> ExecOption
-> IO (Either WrapError (Maybe [(RegOffset,RegOffset)]))
{-# INLINE doMatch #-}
doMatch :: Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr Ptr CChar
cstr CSize
nsub Ptr CRegMatch
p_match ExecOption
flags = do
ReturnCode
r <- Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO ReturnCode
c_regexec Ptr CRegex
regex_ptr Ptr CChar
cstr (CSize
1 CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
+ CSize
nsub) Ptr CRegMatch
p_match ExecOption
flags
if ReturnCode
r ReturnCode -> ReturnCode -> Bool
forall a. Eq a => a -> a -> Bool
== ReturnCode
retOk
then do
[(Int64, Int64)]
regions <- (Ptr CRegMatch -> IO (Int64, Int64))
-> [Ptr CRegMatch] -> IO [(Int64, Int64)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Ptr CRegMatch -> IO (Int64, Int64)
getOffsets ([Ptr CRegMatch] -> IO [(Int64, Int64)])
-> (Ptr CRegMatch -> [Ptr CRegMatch])
-> Ptr CRegMatch
-> IO [(Int64, Int64)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Ptr CRegMatch] -> [Ptr CRegMatch]
forall a. Int -> [a] -> [a]
take (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nsub)
([Ptr CRegMatch] -> [Ptr CRegMatch])
-> (Ptr CRegMatch -> [Ptr CRegMatch])
-> Ptr CRegMatch
-> [Ptr CRegMatch]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ptr CRegMatch -> Ptr CRegMatch)
-> Ptr CRegMatch -> [Ptr CRegMatch]
forall a. (a -> a) -> a -> [a]
iterate (Ptr CRegMatch -> Int -> Ptr CRegMatch
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
16)) (Ptr CRegMatch -> IO [(Int64, Int64)])
-> Ptr CRegMatch -> IO [(Int64, Int64)]
forall a b. (a -> b) -> a -> b
$ Ptr CRegMatch
p_match
{-# LINE 430 "src/Text/Regex/Posix/Wrap.hsc" #-}
return (Right (Just regions))
else if ReturnCode
r ReturnCode -> ReturnCode -> Bool
forall a. Eq a => a -> a -> Bool
== ReturnCode
retNoMatch
then Either WrapError (Maybe [(Int64, Int64)])
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [(Int64, Int64)] -> Either WrapError (Maybe [(Int64, Int64)])
forall a b. b -> Either a b
Right Maybe [(Int64, Int64)]
forall a. Maybe a
Nothing)
else ReturnCode
-> Ptr CRegex -> IO (Either WrapError (Maybe [(Int64, Int64)]))
forall b. ReturnCode -> Ptr CRegex -> IO (Either WrapError b)
wrapError ReturnCode
r Ptr CRegex
regex_ptr
where
getOffsets :: Ptr CRegMatch -> IO (RegOffset,RegOffset)
{-# INLINE getOffsets #-}
getOffsets :: Ptr CRegMatch -> IO (Int64, Int64)
getOffsets Ptr CRegMatch
pmatch' = do
Int64
start <- ((\Ptr CRegMatch
hsc_ptr -> Ptr CRegMatch -> Int -> IO Int64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CRegMatch
hsc_ptr Int
0)) Ptr CRegMatch
pmatch' :: IO (Int64)
{-# LINE 439 "src/Text/Regex/Posix/Wrap.hsc" #-}
end <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) pmatch' :: IO (Int64)
{-# LINE 440 "src/Text/Regex/Posix/Wrap.hsc" #-}
return (fromIntegral start,fromIntegral end)
wrapMatchAll :: Regex -> Ptr CChar -> IO (Either WrapError [MatchArray])
wrapMatchAll regex :: Regex
regex@(Regex ForeignPtr CRegex
regex_fptr CompOption
compileOptions ExecOption
flags) Ptr CChar
cstr = do
Ptr CChar
-> String
-> IO (Either WrapError [MatchArray])
-> IO (Either WrapError [MatchArray])
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CChar
cstr String
"wrapMatchAll cstr" (IO (Either WrapError [MatchArray])
-> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray])
-> IO (Either WrapError [MatchArray])
forall a b. (a -> b) -> a -> b
$ do
if (CompOption
0 CompOption -> CompOption -> Bool
forall a. Eq a => a -> a -> Bool
/= CompOption
compNoSub CompOption -> CompOption -> CompOption
forall a. Bits a => a -> a -> a
.&. CompOption
compileOptions)
then do
Either WrapError Bool
r <- Regex -> Ptr CChar -> IO (Either WrapError Bool)
wrapTest Regex
regex Ptr CChar
cstr
case Either WrapError Bool
r of
Right Bool
True -> Either WrapError [MatchArray] -> IO (Either WrapError [MatchArray])
forall (m :: * -> *) a. Monad m => a -> m a
return ([MatchArray] -> Either WrapError [MatchArray]
forall a b. b -> Either a b
Right [(Int -> [(Int64, Int64)] -> MatchArray
toMA Int
0 [])])
Right Bool
False -> Either WrapError [MatchArray] -> IO (Either WrapError [MatchArray])
forall (m :: * -> *) a. Monad m => a -> m a
return ([MatchArray] -> Either WrapError [MatchArray]
forall a b. b -> Either a b
Right [])
Left WrapError
err -> Either WrapError [MatchArray] -> IO (Either WrapError [MatchArray])
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError [MatchArray]
forall a b. a -> Either a b
Left WrapError
err)
else do
ForeignPtr CRegex
-> (Ptr CRegex -> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray])
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CRegex
regex_fptr ((Ptr CRegex -> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray]))
-> (Ptr CRegex -> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray])
forall a b. (a -> b) -> a -> b
$ \Ptr CRegex
regex_ptr -> do
CSize
nsub <- ((\Ptr CRegex
hsc_ptr -> Ptr CRegex -> Int -> IO CSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CRegex
hsc_ptr Int
8)) Ptr CRegex
regex_ptr :: IO CSize
{-# LINE 454 "src/Text/Regex/Posix/Wrap.hsc" #-}
let nsub_int,nsub_bytes :: Int
nsub_int :: Int
nsub_int = CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
nsub
nsub_bytes :: Int
nsub_bytes = ((Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
nsub_int) Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
16))
{-# LINE 457 "src/Text/Regex/Posix/Wrap.hsc" #-}
Int
-> (Ptr CRegMatch -> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray])
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nsub_bytes ((Ptr CRegMatch -> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray]))
-> (Ptr CRegMatch -> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray])
forall a b. (a -> b) -> a -> b
$ \Ptr CRegMatch
p_match -> do
Ptr CRegMatch
-> String
-> IO (Either WrapError [MatchArray])
-> IO (Either WrapError [MatchArray])
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CRegMatch
p_match String
"wrapMatchAll p_match" (IO (Either WrapError [MatchArray])
-> IO (Either WrapError [MatchArray]))
-> IO (Either WrapError [MatchArray])
-> IO (Either WrapError [MatchArray])
forall a b. (a -> b) -> a -> b
$ do
let flagsBOL :: ExecOption
flagsBOL = (ExecOption -> ExecOption
forall a. Bits a => a -> a
complement ExecOption
execNotBOL) ExecOption -> ExecOption -> ExecOption
forall a. Bits a => a -> a -> a
.&. ExecOption
flags
flagsMIDDLE :: ExecOption
flagsMIDDLE = ExecOption
execNotBOL ExecOption -> ExecOption -> ExecOption
forall a. Bits a => a -> a -> a
.|. ExecOption
flags
atBOL :: Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atBOL Int
pos = Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr (Ptr CChar -> Int -> Ptr CChar
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr CChar
cstr Int
pos) CSize
nsub Ptr CRegMatch
p_match ExecOption
flagsBOL
atMIDDLE :: Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atMIDDLE Int
pos = Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr (Ptr CChar -> Int -> Ptr CChar
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr CChar
cstr Int
pos) CSize
nsub Ptr CRegMatch
p_match ExecOption
flagsMIDDLE
loop :: ([MatchArray] -> b)
-> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop [MatchArray] -> b
acc Int
old (Int64
s,Int64
e) | [MatchArray] -> b
acc ([MatchArray] -> b) -> Bool -> Bool
`seq` Int
old Int -> Bool -> Bool
`seq` Bool
False = IO (Either WrapError b)
forall a. HasCallStack => a
undefined
| Int64
s Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
e = do
let pos :: Int
pos = Int
old Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
e
Bool
atEnd <- Ptr CChar -> Int -> IO Bool
isNull Ptr CChar
cstr Int
pos
if Bool
atEnd then Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either WrapError b
forall a b. b -> Either a b
Right ([MatchArray] -> b
acc []))
else ([MatchArray] -> b)
-> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop [MatchArray] -> b
acc Int
old (Int64
s,Int64 -> Int64
forall a. Enum a => a -> a
succ Int64
e)
| Bool
otherwise = do
let pos :: Int
pos = Int
old Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
e
Bool
prev'newline <- Ptr CChar -> Int -> IO Bool
isNewline Ptr CChar
cstr (Int -> Int
forall a. Enum a => a -> a
pred Int
pos)
Either WrapError (Maybe [(Int64, Int64)])
result <- if Bool
prev'newline then Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atBOL Int
pos else Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atMIDDLE Int
pos
case Either WrapError (Maybe [(Int64, Int64)])
result of
Right Maybe [(Int64, Int64)]
Nothing -> Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either WrapError b
forall a b. b -> Either a b
Right ([MatchArray] -> b
acc []))
Right (Just parts :: [(Int64, Int64)]
parts@((Int64, Int64)
whole:[(Int64, Int64)]
_)) -> let ma :: MatchArray
ma = Int -> [(Int64, Int64)] -> MatchArray
toMA Int
pos [(Int64, Int64)]
parts
in ([MatchArray] -> b)
-> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop ([MatchArray] -> b
acc([MatchArray] -> b)
-> ([MatchArray] -> [MatchArray]) -> [MatchArray] -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(MatchArray
maMatchArray -> [MatchArray] -> [MatchArray]
forall a. a -> [a] -> [a]
:)) Int
pos (Int64, Int64)
whole
Left WrapError
err -> Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError b
forall a b. a -> Either a b
Left WrapError
err)
Right (Just []) -> Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either WrapError b
forall a b. b -> Either a b
Right ([MatchArray] -> b
acc [(Int -> [(Int64, Int64)] -> MatchArray
toMA Int
pos [])]))
Either WrapError (Maybe [(Int64, Int64)])
result <- Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr Ptr CChar
cstr CSize
nsub Ptr CRegMatch
p_match ExecOption
flags
case Either WrapError (Maybe [(Int64, Int64)])
result of
Right Maybe [(Int64, Int64)]
Nothing -> Either WrapError [MatchArray] -> IO (Either WrapError [MatchArray])
forall (m :: * -> *) a. Monad m => a -> m a
return ([MatchArray] -> Either WrapError [MatchArray]
forall a b. b -> Either a b
Right [])
Right (Just parts :: [(Int64, Int64)]
parts@((Int64, Int64)
whole:[(Int64, Int64)]
_)) -> let ma :: MatchArray
ma = Int -> [(Int64, Int64)] -> MatchArray
toMA Int
0 [(Int64, Int64)]
parts
in ([MatchArray] -> [MatchArray])
-> Int -> (Int64, Int64) -> IO (Either WrapError [MatchArray])
forall {b}.
([MatchArray] -> b)
-> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop (MatchArray
maMatchArray -> [MatchArray] -> [MatchArray]
forall a. a -> [a] -> [a]
:) Int
0 (Int64, Int64)
whole
Left WrapError
err -> Either WrapError [MatchArray] -> IO (Either WrapError [MatchArray])
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError [MatchArray]
forall a b. a -> Either a b
Left WrapError
err)
Right (Just []) -> Either WrapError [MatchArray] -> IO (Either WrapError [MatchArray])
forall (m :: * -> *) a. Monad m => a -> m a
return ([MatchArray] -> Either WrapError [MatchArray]
forall a b. b -> Either a b
Right [(Int -> [(Int64, Int64)] -> MatchArray
toMA Int
0 [])])
where
toMA :: Int -> [(RegOffset,RegOffset)] -> Array Int (Int,Int)
toMA :: Int -> [(Int64, Int64)] -> MatchArray
toMA Int
pos [] = (Int, Int) -> [(Int, Int)] -> MatchArray
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
0) [(Int
pos,Int
0)]
toMA Int
pos [(Int64, Int64)]
parts = (Int, Int) -> [(Int, Int)] -> MatchArray
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int -> Int
forall a. Enum a => a -> a
pred ([(Int64, Int64)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Int64, Int64)]
parts))
([(Int, Int)] -> MatchArray)
-> ([(Int64, Int64)] -> [(Int, Int)])
-> [(Int64, Int64)]
-> MatchArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int64, Int64) -> (Int, Int)) -> [(Int64, Int64)] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int64
s,Int64
e)-> if Int64
sInt64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>=Int64
0 then (Int
posInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
s, Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64
eInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
s)) else (-Int
1,Int
0))
([(Int64, Int64)] -> MatchArray) -> [(Int64, Int64)] -> MatchArray
forall a b. (a -> b) -> a -> b
$ [(Int64, Int64)]
parts
wrapCount :: Regex -> Ptr CChar -> IO (Either WrapError Int)
wrapCount regex :: Regex
regex@(Regex ForeignPtr CRegex
regex_fptr CompOption
compileOptions ExecOption
flags) Ptr CChar
cstr = do
Ptr CChar
-> String -> IO (Either WrapError Int) -> IO (Either WrapError Int)
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CChar
cstr String
"wrapCount cstr" (IO (Either WrapError Int) -> IO (Either WrapError Int))
-> IO (Either WrapError Int) -> IO (Either WrapError Int)
forall a b. (a -> b) -> a -> b
$ do
if (CompOption
0 CompOption -> CompOption -> Bool
forall a. Eq a => a -> a -> Bool
/= CompOption
compNoSub CompOption -> CompOption -> CompOption
forall a. Bits a => a -> a -> a
.&. CompOption
compileOptions)
then do
Either WrapError Bool
r <- Regex -> Ptr CChar -> IO (Either WrapError Bool)
wrapTest Regex
regex Ptr CChar
cstr
case Either WrapError Bool
r of
Right Bool
True -> Either WrapError Int -> IO (Either WrapError Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either WrapError Int
forall a b. b -> Either a b
Right Int
1)
Right Bool
False -> Either WrapError Int -> IO (Either WrapError Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either WrapError Int
forall a b. b -> Either a b
Right Int
0)
Left WrapError
err -> Either WrapError Int -> IO (Either WrapError Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError Int
forall a b. a -> Either a b
Left WrapError
err)
else do
ForeignPtr CRegex
-> (Ptr CRegex -> IO (Either WrapError Int))
-> IO (Either WrapError Int)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CRegex
regex_fptr ((Ptr CRegex -> IO (Either WrapError Int))
-> IO (Either WrapError Int))
-> (Ptr CRegex -> IO (Either WrapError Int))
-> IO (Either WrapError Int)
forall a b. (a -> b) -> a -> b
$ \Ptr CRegex
regex_ptr -> do
let nsub_bytes :: Int
nsub_bytes = ((Int
16))
{-# LINE 507 "src/Text/Regex/Posix/Wrap.hsc" #-}
Int
-> (Ptr CRegMatch -> IO (Either WrapError Int))
-> IO (Either WrapError Int)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
nsub_bytes ((Ptr CRegMatch -> IO (Either WrapError Int))
-> IO (Either WrapError Int))
-> (Ptr CRegMatch -> IO (Either WrapError Int))
-> IO (Either WrapError Int)
forall a b. (a -> b) -> a -> b
$ \Ptr CRegMatch
p_match -> do
Ptr CRegMatch
-> String -> IO (Either WrapError Int) -> IO (Either WrapError Int)
forall a b.
Ptr a
-> String -> IO (Either WrapError b) -> IO (Either WrapError b)
nullTest Ptr CRegMatch
p_match String
"wrapCount p_match" (IO (Either WrapError Int) -> IO (Either WrapError Int))
-> IO (Either WrapError Int) -> IO (Either WrapError Int)
forall a b. (a -> b) -> a -> b
$ do
let flagsBOL :: ExecOption
flagsBOL = (ExecOption -> ExecOption
forall a. Bits a => a -> a
complement ExecOption
execNotBOL) ExecOption -> ExecOption -> ExecOption
forall a. Bits a => a -> a -> a
.&. ExecOption
flags
flagsMIDDLE :: ExecOption
flagsMIDDLE = ExecOption
execNotBOL ExecOption -> ExecOption -> ExecOption
forall a. Bits a => a -> a -> a
.|. ExecOption
flags
atBOL :: Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atBOL Int
pos = Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr (Ptr CChar -> Int -> Ptr CChar
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr CChar
cstr Int
pos) CSize
0 Ptr CRegMatch
p_match ExecOption
flagsBOL
atMIDDLE :: Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atMIDDLE Int
pos = Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr (Ptr CChar -> Int -> Ptr CChar
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr CChar
cstr Int
pos) CSize
0 Ptr CRegMatch
p_match ExecOption
flagsMIDDLE
loop :: b -> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop b
acc Int
old (Int64
s,Int64
e) | b
acc b -> Bool -> Bool
`seq` Int
old Int -> Bool -> Bool
`seq` Bool
False = IO (Either WrapError b)
forall a. HasCallStack => a
undefined
| Int64
s Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
e = do
let pos :: Int
pos = Int
old Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
e
Bool
atEnd <- Ptr CChar -> Int -> IO Bool
isNull Ptr CChar
cstr Int
pos
if Bool
atEnd then Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either WrapError b
forall a b. b -> Either a b
Right b
acc)
else b -> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop b
acc Int
old (Int64
s,Int64 -> Int64
forall a. Enum a => a -> a
succ Int64
e)
| Bool
otherwise = do
let pos :: Int
pos = Int
old Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
e
Bool
prev'newline <- Ptr CChar -> Int -> IO Bool
isNewline Ptr CChar
cstr (Int -> Int
forall a. Enum a => a -> a
pred Int
pos)
Either WrapError (Maybe [(Int64, Int64)])
result <- if Bool
prev'newline then Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atBOL Int
pos else Int -> IO (Either WrapError (Maybe [(Int64, Int64)]))
atMIDDLE Int
pos
case Either WrapError (Maybe [(Int64, Int64)])
result of
Right Maybe [(Int64, Int64)]
Nothing -> Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either WrapError b
forall a b. b -> Either a b
Right b
acc)
Right (Just ((Int64, Int64)
whole:[(Int64, Int64)]
_)) -> b -> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop (b -> b
forall a. Enum a => a -> a
succ b
acc) Int
pos (Int64, Int64)
whole
Left WrapError
err -> Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError b
forall a b. a -> Either a b
Left WrapError
err)
Right (Just []) -> Either WrapError b -> IO (Either WrapError b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either WrapError b
forall a b. b -> Either a b
Right b
acc)
Either WrapError (Maybe [(Int64, Int64)])
result <- Ptr CRegex
-> Ptr CChar
-> CSize
-> Ptr CRegMatch
-> ExecOption
-> IO (Either WrapError (Maybe [(Int64, Int64)]))
doMatch Ptr CRegex
regex_ptr Ptr CChar
cstr CSize
0 Ptr CRegMatch
p_match ExecOption
flags
case Either WrapError (Maybe [(Int64, Int64)])
result of
Right Maybe [(Int64, Int64)]
Nothing -> Either WrapError Int -> IO (Either WrapError Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either WrapError Int
forall a b. b -> Either a b
Right Int
0)
Right (Just ((Int64, Int64)
whole:[(Int64, Int64)]
_)) -> Int -> Int -> (Int64, Int64) -> IO (Either WrapError Int)
forall {b}.
Enum b =>
b -> Int -> (Int64, Int64) -> IO (Either WrapError b)
loop Int
1 Int
0 (Int64, Int64)
whole
Left WrapError
err -> Either WrapError Int -> IO (Either WrapError Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapError -> Either WrapError Int
forall a b. a -> Either a b
Left WrapError
err)
Right (Just []) -> Either WrapError Int -> IO (Either WrapError Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Either WrapError Int
forall a b. b -> Either a b
Right Int
0)