module Text.Regex.PCRE.Precompile where
import Control.Monad (liftM)
import Data.ByteString.Char8 (ByteString, packCStringLen)
import Data.ByteString.Internal (toForeignPtr)
import Foreign.C.Types (CSize)
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (nullPtr, castPtr)
import Foreign.Marshal (alloca)
import Foreign.Storable (peek)
import GHC.Exts (Int(..), plusAddr#)
import GHC.ForeignPtr (ForeignPtr(..))
import Text.Regex.PCRE.Light
import Text.Regex.PCRE.Light.Base
type CompiledBytes = ByteString
precompile :: ByteString -> [PCREOption] -> IO (Maybe CompiledBytes)
precompile pat opts = regexToTable $ compile pat opts
regexToTable :: Regex -> IO (Maybe CompiledBytes)
regexToTable (Regex p _) =
withForeignPtr p $ \pcre -> alloca $ \res -> do
success <- c_pcre_fullinfo pcre nullPtr info_size res
len <- return . fromIntegral =<< (peek res :: IO CSize)
if success >= 0
then liftM Just $ packCStringLen (castPtr pcre, len)
else return Nothing
regexFromTable :: CompiledBytes -> IO Regex
regexFromTable bytes =
return $ Regex (ForeignPtr (plusAddr# addr offset) content) bytes
where
!(ForeignPtr addr content, I# offset, _) = toForeignPtr bytes