{-# LINE 1 "src/Regex/Rure.chs" #-}
module Regex.Rure (
hsMatches
, hsIsMatch
, hsSetIsMatch
, hsFind
, hsSetMatches
, compile
, compileSet
, isMatch
, setIsMatch
, setMatches
, find
, matches
, matches'
, mkIter
, findCaptures
, captures
, RureMatch (..)
, RurePtr
, RureIterPtr
, RureSetPtr
, RureFlags
, rureFlagCaseI
, rureFlagMulti
, rureFlagDotNL
, rureFlagSwapGreed
, rureFlagSpace
, rureFlagUnicode
, rureDefaultFlags
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Data.Coerce (coerce)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Unsafe as BS
import Data.Foldable (traverse_)
import Foreign.C.Types (CSize)
import Foreign.ForeignPtr (castForeignPtr, newForeignPtr, touchForeignPtr)
import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import Foreign.Ptr (castPtr, nullPtr, Ptr)
import Foreign.Storable (sizeOf)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Array (peekArray, pokeArray)
import Regex.Rure.FFI
import System.IO.Unsafe (unsafePerformIO)
capturesAt :: RureCapturesPtr -> CSize -> IO (Maybe RureMatch)
capturesAt :: RureCapturesPtr -> CSize -> IO (Maybe RureMatch)
capturesAt RureCapturesPtr
rcp CSize
sz =
Int
-> (Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
16 ((Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch))
-> (Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch)
forall a b. (a -> b) -> a -> b
$ \Ptr RureMatch
matchPtr -> do
res <- RureCapturesPtr -> CSize -> Ptr RureMatch -> IO Bool
rureCapturesAt RureCapturesPtr
rcp CSize
sz Ptr RureMatch
matchPtr
if res
then Just <$> rureMatchFromPtr matchPtr
else pure Nothing
{-# DEPRECATED mkIter "This creates a stateful pointer in an otherwise pure API" #-}
mkIter :: RurePtr -> IO RureIterPtr
mkIter :: RurePtr -> IO RureIterPtr
mkIter RurePtr
rePtr =
ForeignPtr () -> RureIterPtr
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr (ForeignPtr () -> RureIterPtr)
-> IO (ForeignPtr ()) -> IO RureIterPtr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FinalizerPtr () -> Ptr () -> IO (ForeignPtr ())
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr ()
rureIterFree (Ptr () -> IO (ForeignPtr ()))
-> (Ptr RureIter -> Ptr ()) -> Ptr RureIter -> IO (ForeignPtr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr RureIter -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr RureIter -> IO (ForeignPtr ()))
-> IO (Ptr RureIter) -> IO (ForeignPtr ())
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< RurePtr -> IO (Ptr RureIter)
rureIterNew RurePtr
rePtr)
compileSet :: RureFlags -> [BS.ByteString] -> IO (Either String RureSetPtr)
compileSet :: RureFlags -> [ByteString] -> IO (Either String RureSetPtr)
compileSet RureFlags
flags [ByteString]
bss = do
preErr <- IO (Ptr RureError)
rureErrorNew
err <- castForeignPtr <$> newForeignPtr rureErrorFree (castPtr preErr)
preOpt <- rureOptionsNew
opt <- castForeignPtr <$> newForeignPtr rureOptionsFree (castPtr preOpt)
allocaBytes lBytes $ \Ptr (Ptr Word8)
bPtrs ->
Int
-> (Ptr CSize -> IO (Either String RureSetPtr))
-> IO (Either String RureSetPtr)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
lBytes ((Ptr CSize -> IO (Either String RureSetPtr))
-> IO (Either String RureSetPtr))
-> (Ptr CSize -> IO (Either String RureSetPtr))
-> IO (Either String RureSetPtr)
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
szs -> do
Ptr (Ptr Word8) -> [Ptr Word8] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeArray Ptr (Ptr Word8)
bPtrs ((ForeignPtr Word8 -> Ptr Word8)
-> [ForeignPtr Word8] -> [Ptr Word8]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr [ForeignPtr Word8]
ps)
Ptr CSize -> [CSize] -> IO ()
forall a. Storable a => Ptr a -> [a] -> IO ()
pokeArray Ptr CSize
szs (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> [Int] -> [CSize]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int]
ss)
res <- Ptr (Ptr UInt8)
-> Ptr CSize
-> CSize
-> RureFlags
-> ForeignPtr RureOptions
-> ForeignPtr RureError
-> IO (Ptr RureSet)
rureCompileSet (Ptr (Ptr Word8) -> Ptr (Ptr UInt8)
forall a b. Ptr a -> Ptr b
castPtr Ptr (Ptr Word8)
bPtrs) Ptr CSize
szs (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l) RureFlags
flags ForeignPtr RureOptions
opt ForeignPtr RureError
err
traverse_ touchForeignPtr ps
if res == nullPtr
then Left <$> rureErrorMessage err
else Right . castForeignPtr <$> newForeignPtr rureSetFree (castPtr res)
where l :: Int
l = [ByteString] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ByteString]
bss
lBytes :: Int
lBytes = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
* Ptr Any -> Int
forall a. Storable a => a -> Int
sizeOf (Ptr a
forall a. Ptr a
forall a. HasCallStack => a
undefined :: Ptr a)
rip :: ByteString -> (ForeignPtr Word8, Int)
rip (BS.BS ForeignPtr Word8
psϵ Int
lϵ) = (ForeignPtr Word8
psϵ, Int
lϵ)
([ForeignPtr Word8]
ps, [Int]
ss) = [(ForeignPtr Word8, Int)] -> ([ForeignPtr Word8], [Int])
forall a b. [(a, b)] -> ([a], [b])
unzip ((ByteString -> (ForeignPtr Word8, Int))
-> [ByteString] -> [(ForeignPtr Word8, Int)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> (ForeignPtr Word8, Int)
rip [ByteString]
bss)
compile :: RureFlags -> BS.ByteString -> IO (Either String RurePtr)
compile :: RureFlags -> ByteString -> IO (Either String RurePtr)
compile RureFlags
flags ByteString
re = do
preErr <- IO (Ptr RureError)
rureErrorNew
err <- castForeignPtr <$> newForeignPtr rureErrorFree (castPtr preErr)
preOpt <- rureOptionsNew
opt <- castForeignPtr <$> newForeignPtr rureOptionsFree (castPtr preOpt)
BS.unsafeUseAsCStringLen re $ \(Ptr CChar
p, Int
sz) -> do
res <- Ptr UInt8
-> CSize
-> RureFlags
-> ForeignPtr RureOptions
-> ForeignPtr RureError
-> IO (Ptr Rure)
rureCompile (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) RureFlags
flags ForeignPtr RureOptions
opt ForeignPtr RureError
err
if res == nullPtr
then Left <$> rureErrorMessage err
else Right . castForeignPtr <$> newForeignPtr rureFree (castPtr res)
{-# NOINLINE hsMatches #-}
hsMatches :: RureFlags
-> BS.ByteString
-> BS.ByteString
-> Either String [RureMatch]
hsMatches :: RureFlags -> ByteString -> ByteString -> Either String [RureMatch]
hsMatches RureFlags
flags ByteString
re ByteString
haystack = IO (Either String [RureMatch]) -> Either String [RureMatch]
forall a. IO a -> a
unsafePerformIO (IO (Either String [RureMatch]) -> Either String [RureMatch])
-> IO (Either String [RureMatch]) -> Either String [RureMatch]
forall a b. (a -> b) -> a -> b
$ do
rePtr <- RureFlags -> ByteString -> IO (Either String RurePtr)
compile RureFlags
flags ByteString
re
case rePtr of
Left String
err -> Either String [RureMatch] -> IO (Either String [RureMatch])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Either String [RureMatch]
forall a b. a -> Either a b
Left String
err)
Right RurePtr
rp -> [RureMatch] -> Either String [RureMatch]
forall a b. b -> Either a b
Right ([RureMatch] -> Either String [RureMatch])
-> IO [RureMatch] -> IO (Either String [RureMatch])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((\RureIterPtr
riPtr -> RureIterPtr -> ByteString -> IO [RureMatch]
matches RureIterPtr
riPtr ByteString
haystack) (RureIterPtr -> IO [RureMatch]) -> IO RureIterPtr -> IO [RureMatch]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< RurePtr -> IO RureIterPtr
mkIter RurePtr
rp)
matches' :: RurePtr
-> BS.ByteString
-> IO [RureMatch]
matches' :: RurePtr -> ByteString -> IO [RureMatch]
matches' RurePtr
rp ByteString
haystack = do
ri <- RurePtr -> IO RureIterPtr
mkIter RurePtr
rp
matches ri haystack
{-# DEPRECATED matches "Use matches', which is not stateful" #-}
matches :: RureIterPtr
-> BS.ByteString
-> IO [RureMatch]
matches :: RureIterPtr -> ByteString -> IO [RureMatch]
matches RureIterPtr
reIPtr ByteString
haystack = do
res <- RureIterPtr -> ByteString -> IO (Maybe RureMatch)
iterNext RureIterPtr
reIPtr ByteString
haystack
case res of
Maybe RureMatch
Nothing -> [RureMatch] -> IO [RureMatch]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
Just RureMatch
m -> (RureMatch
m RureMatch -> [RureMatch] -> [RureMatch]
forall a. a -> [a] -> [a]
:) ([RureMatch] -> [RureMatch]) -> IO [RureMatch] -> IO [RureMatch]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RureIterPtr -> ByteString -> IO [RureMatch]
matches RureIterPtr
reIPtr ByteString
haystack
iterNext :: RureIterPtr
-> BS.ByteString
-> IO (Maybe RureMatch)
iterNext :: RureIterPtr -> ByteString -> IO (Maybe RureMatch)
iterNext RureIterPtr
reIPtr ByteString
haystack =
Int
-> (Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
16 ((Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch))
-> (Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch)
forall a b. (a -> b) -> a -> b
$ \Ptr RureMatch
matchPtr -> do
res <- ByteString -> (CStringLen -> IO Bool) -> IO Bool
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
haystack ((CStringLen -> IO Bool) -> IO Bool)
-> (CStringLen -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
p, Int
sz) ->
RureIterPtr -> Ptr UInt8 -> CSize -> Ptr RureMatch -> IO Bool
rureIterNext RureIterPtr
reIPtr (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) Ptr RureMatch
matchPtr
if res
then Just <$> rureMatchFromPtr matchPtr
else pure Nothing
rureMatchFromPtr :: Ptr RureMatch -> IO RureMatch
rureMatchFromPtr :: Ptr RureMatch -> IO RureMatch
rureMatchFromPtr Ptr RureMatch
matchPtr =
CSize -> CSize -> RureMatch
RureMatch
(CSize -> CSize -> RureMatch)
-> IO CSize -> IO (CSize -> RureMatch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CULong -> CSize) -> IO CULong -> IO CSize
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CULong -> CSize
forall a b. Coercible a b => a -> b
coerce ((\Ptr RureMatch
ptr -> do {Ptr RureMatch -> Int -> IO CULong
forall b. Ptr b -> Int -> IO CULong
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr RureMatch
ptr Int
0 :: IO C2HSImp.CULong}) Ptr RureMatch
matchPtr)
IO (CSize -> RureMatch) -> IO CSize -> IO RureMatch
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CULong -> CSize) -> IO CULong -> IO CSize
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CULong -> CSize
forall a b. Coercible a b => a -> b
coerce ((\Ptr RureMatch
ptr -> do {Ptr RureMatch -> Int -> IO CULong
forall b. Ptr b -> Int -> IO CULong
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr RureMatch
ptr Int
8 :: IO C2HSImp.CULong}) Ptr RureMatch
matchPtr)
{-# NOINLINE hsFind #-}
hsFind :: RureFlags
-> BS.ByteString
-> BS.ByteString
-> Either String (Maybe (RureMatch))
hsFind :: RureFlags
-> ByteString -> ByteString -> Either String (Maybe RureMatch)
hsFind RureFlags
flags ByteString
re ByteString
haystack = IO (Either String (Maybe RureMatch))
-> Either String (Maybe RureMatch)
forall a. IO a -> a
unsafePerformIO (IO (Either String (Maybe RureMatch))
-> Either String (Maybe RureMatch))
-> IO (Either String (Maybe RureMatch))
-> Either String (Maybe RureMatch)
forall a b. (a -> b) -> a -> b
$ do
rePtr <- RureFlags -> ByteString -> IO (Either String RurePtr)
compile RureFlags
flags ByteString
re
case rePtr of
Left String
err -> Either String (Maybe RureMatch)
-> IO (Either String (Maybe RureMatch))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Either String (Maybe RureMatch)
forall a b. a -> Either a b
Left String
err)
Right RurePtr
rp -> Maybe RureMatch -> Either String (Maybe RureMatch)
forall a b. b -> Either a b
Right (Maybe RureMatch -> Either String (Maybe RureMatch))
-> IO (Maybe RureMatch) -> IO (Either String (Maybe RureMatch))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RurePtr -> ByteString -> CSize -> IO (Maybe RureMatch)
find RurePtr
rp ByteString
haystack CSize
0
allocCapPtr :: RurePtr -> IO RureCapturesPtr
allocCapPtr :: RurePtr -> IO RureCapturesPtr
allocCapPtr RurePtr
rp = do
capPtr <- RurePtr -> IO (Ptr RureCaptures)
rureCapturesNew RurePtr
rp
castForeignPtr <$> newForeignPtr rureCapturesFree (castPtr capPtr)
captures :: RurePtr
-> BS.ByteString
-> CSize
-> IO [RureMatch]
captures :: RurePtr -> ByteString -> CSize -> IO [RureMatch]
captures RurePtr
re ByteString
haystack CSize
ix = do
capPtr <- RurePtr -> IO RureCapturesPtr
allocCapPtr RurePtr
re
reIPtr <- mkIter re
capturesLoop capPtr reIPtr haystack ix
capturesLoop :: RureCapturesPtr
-> RureIterPtr
-> BS.ByteString
-> CSize
-> IO [RureMatch]
capturesLoop :: RureCapturesPtr
-> RureIterPtr -> ByteString -> CSize -> IO [RureMatch]
capturesLoop RureCapturesPtr
capPtr RureIterPtr
reIPtr ByteString
haystack CSize
ix = do
res <- RureCapturesPtr
-> RureIterPtr -> ByteString -> CSize -> IO (Maybe RureMatch)
iterNextCaptures RureCapturesPtr
capPtr RureIterPtr
reIPtr ByteString
haystack CSize
ix
case res of
Maybe RureMatch
Nothing -> [RureMatch] -> IO [RureMatch]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
Just RureMatch
m -> (RureMatch
m RureMatch -> [RureMatch] -> [RureMatch]
forall a. a -> [a] -> [a]
:) ([RureMatch] -> [RureMatch]) -> IO [RureMatch] -> IO [RureMatch]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RureCapturesPtr
-> RureIterPtr -> ByteString -> CSize -> IO [RureMatch]
capturesLoop RureCapturesPtr
capPtr RureIterPtr
reIPtr ByteString
haystack CSize
ix
iterNextCaptures :: RureCapturesPtr
-> RureIterPtr
-> BS.ByteString
-> CSize
-> IO (Maybe RureMatch)
iterNextCaptures :: RureCapturesPtr
-> RureIterPtr -> ByteString -> CSize -> IO (Maybe RureMatch)
iterNextCaptures RureCapturesPtr
capPtr RureIterPtr
reIPtr ByteString
haystack CSize
ix = do
res <- ByteString -> (CStringLen -> IO Bool) -> IO Bool
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
haystack ((CStringLen -> IO Bool) -> IO Bool)
-> (CStringLen -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
p, Int
sz) ->
RureIterPtr -> Ptr UInt8 -> CSize -> RureCapturesPtr -> IO Bool
rureIterNextCaptures RureIterPtr
reIPtr (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) RureCapturesPtr
capPtr
if res
then capturesAt capPtr ix
else pure Nothing
findCaptures :: RurePtr
-> BS.ByteString
-> CSize
-> CSize
-> IO (Maybe RureMatch)
findCaptures :: RurePtr -> ByteString -> CSize -> CSize -> IO (Maybe RureMatch)
findCaptures RurePtr
rp ByteString
haystack CSize
ix CSize
start' = do
capFp <- RurePtr -> IO RureCapturesPtr
allocCapPtr RurePtr
rp
res <- BS.unsafeUseAsCStringLen haystack $ \(Ptr CChar
p, Int
sz) ->
RurePtr
-> Ptr UInt8 -> CSize -> CSize -> RureCapturesPtr -> IO Bool
rureFindCaptures RurePtr
rp (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) CSize
start' RureCapturesPtr
capFp
if res
then capturesAt capFp ix
else pure Nothing
find :: RurePtr
-> BS.ByteString
-> CSize
-> IO (Maybe RureMatch)
find :: RurePtr -> ByteString -> CSize -> IO (Maybe RureMatch)
find RurePtr
rePtr ByteString
haystack CSize
start' =
Int
-> (Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
16 ((Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch))
-> (Ptr RureMatch -> IO (Maybe RureMatch)) -> IO (Maybe RureMatch)
forall a b. (a -> b) -> a -> b
$ \Ptr RureMatch
matchPtr -> do
res <- ByteString -> (CStringLen -> IO Bool) -> IO Bool
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
haystack ((CStringLen -> IO Bool) -> IO Bool)
-> (CStringLen -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
p, Int
sz) ->
RurePtr -> Ptr UInt8 -> CSize -> CSize -> Ptr RureMatch -> IO Bool
rureFind RurePtr
rePtr (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) CSize
start' Ptr RureMatch
matchPtr
if res
then Just <$> rureMatchFromPtr matchPtr
else pure Nothing
{-# NOINLINE hsSetMatches #-}
hsSetMatches :: RureFlags
-> [BS.ByteString]
-> BS.ByteString
-> Either String [Bool]
hsSetMatches :: RureFlags -> [ByteString] -> ByteString -> Either String [Bool]
hsSetMatches RureFlags
flags [ByteString]
res ByteString
haystack = IO (Either String [Bool]) -> Either String [Bool]
forall a. IO a -> a
unsafePerformIO (IO (Either String [Bool]) -> Either String [Bool])
-> IO (Either String [Bool]) -> Either String [Bool]
forall a b. (a -> b) -> a -> b
$ do
resPtr <- RureFlags -> [ByteString] -> IO (Either String RureSetPtr)
compileSet RureFlags
flags [ByteString]
res
case resPtr of
Left String
err -> Either String [Bool] -> IO (Either String [Bool])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Either String [Bool]
forall a b. a -> Either a b
Left String
err)
Right RureSetPtr
rsp -> [Bool] -> Either String [Bool]
forall a b. b -> Either a b
Right ([Bool] -> Either String [Bool])
-> IO [Bool] -> IO (Either String [Bool])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RureSetPtr -> ByteString -> CSize -> IO [Bool]
setMatches RureSetPtr
rsp ByteString
haystack CSize
0
{-# NOINLINE hsSetIsMatch #-}
hsSetIsMatch :: RureFlags
-> [BS.ByteString]
-> BS.ByteString
-> Either String Bool
hsSetIsMatch :: RureFlags -> [ByteString] -> ByteString -> Either String Bool
hsSetIsMatch RureFlags
flags [ByteString]
res ByteString
haystack = IO (Either String Bool) -> Either String Bool
forall a. IO a -> a
unsafePerformIO (IO (Either String Bool) -> Either String Bool)
-> IO (Either String Bool) -> Either String Bool
forall a b. (a -> b) -> a -> b
$ do
resPtr <- RureFlags -> [ByteString] -> IO (Either String RureSetPtr)
compileSet RureFlags
flags [ByteString]
res
case resPtr of
Left String
err -> Either String Bool -> IO (Either String Bool)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Either String Bool
forall a b. a -> Either a b
Left String
err)
Right RureSetPtr
rsp -> Bool -> Either String Bool
forall a b. b -> Either a b
Right (Bool -> Either String Bool) -> IO Bool -> IO (Either String Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RureSetPtr -> ByteString -> CSize -> IO Bool
setIsMatch RureSetPtr
rsp ByteString
haystack CSize
0
{-# NOINLINE hsIsMatch #-}
hsIsMatch :: RureFlags
-> BS.ByteString
-> BS.ByteString
-> Either String Bool
hsIsMatch :: RureFlags -> ByteString -> ByteString -> Either String Bool
hsIsMatch RureFlags
flags ByteString
re ByteString
haystack = IO (Either String Bool) -> Either String Bool
forall a. IO a -> a
unsafePerformIO (IO (Either String Bool) -> Either String Bool)
-> IO (Either String Bool) -> Either String Bool
forall a b. (a -> b) -> a -> b
$ do
rePtr <- RureFlags -> ByteString -> IO (Either String RurePtr)
compile RureFlags
flags ByteString
re
case rePtr of
Left String
err -> Either String Bool -> IO (Either String Bool)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Either String Bool
forall a b. a -> Either a b
Left String
err)
Right RurePtr
rp -> Bool -> Either String Bool
forall a b. b -> Either a b
Right (Bool -> Either String Bool) -> IO Bool -> IO (Either String Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RurePtr -> ByteString -> CSize -> IO Bool
isMatch RurePtr
rp ByteString
haystack CSize
0
setIsMatch :: RureSetPtr
-> BS.ByteString
-> CSize
-> IO Bool
setIsMatch :: RureSetPtr -> ByteString -> CSize -> IO Bool
setIsMatch RureSetPtr
rsPtr ByteString
haystack CSize
startϵ =
ByteString -> (CStringLen -> IO Bool) -> IO Bool
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
haystack ((CStringLen -> IO Bool) -> IO Bool)
-> (CStringLen -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
p, Int
sz) ->
RureSetPtr -> Ptr UInt8 -> CSize -> CSize -> IO Bool
rureSetIsMatch RureSetPtr
rsPtr (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) CSize
startϵ
setMatches :: RureSetPtr
-> BS.ByteString
-> CSize
-> IO [Bool]
setMatches :: RureSetPtr -> ByteString -> CSize -> IO [Bool]
setMatches RureSetPtr
rsPtr ByteString
haystack CSize
startϵ =
ByteString -> (CStringLen -> IO [Bool]) -> IO [Bool]
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
haystack ((CStringLen -> IO [Bool]) -> IO [Bool])
-> (CStringLen -> IO [Bool]) -> IO [Bool]
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
p, Int
sz) -> do
l <- CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CSize -> Int) -> IO CSize -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RureSetPtr -> IO CSize
rureSetLen RureSetPtr
rsPtr
allocaBytes l $ \Ptr CBool
boolPtr -> do
RureSetPtr -> Ptr UInt8 -> CSize -> CSize -> Ptr CBool -> IO Bool
rureSetMatches RureSetPtr
rsPtr (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) CSize
startϵ Ptr CBool
boolPtr
(CBool -> Bool) -> [CBool] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall {a}. (Eq a, Num a) => a -> Bool
cBoolToBool ([CBool] -> [Bool]) -> IO [CBool] -> IO [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr CBool -> IO [CBool]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
l Ptr CBool
boolPtr
where cBoolToBool :: a -> Bool
cBoolToBool a
0 = Bool
False
cBoolToBool a
_ = Bool
True
isMatch :: RurePtr
-> BS.ByteString
-> CSize
-> IO Bool
isMatch :: RurePtr -> ByteString -> CSize -> IO Bool
isMatch RurePtr
rePtr ByteString
haystack CSize
start' =
ByteString -> (CStringLen -> IO Bool) -> IO Bool
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
haystack ((CStringLen -> IO Bool) -> IO Bool)
-> (CStringLen -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
p, Int
sz) ->
RurePtr -> Ptr UInt8 -> CSize -> CSize -> IO Bool
rureIsMatch RurePtr
rePtr (Ptr CChar -> Ptr UInt8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
p) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sz) CSize
start'