Safe Haskell | None |
---|---|
Language | Haskell2010 |
See rure.h
for documentation + how to use.
Synopsis
- data Rure
- data RureOptions
- data RureError
- data RureCaptures
- data RureSet
- data RureIter
- data RureIterCaptureNames
- type UInt8 = CUChar
- type UInt32 = CUInt
- data RureMatch = RureMatch {}
- data RureFlags
- type RurePtr = ForeignPtr Rure
- type RureErrorPtr = ForeignPtr RureError
- type RureOptionsPtr = ForeignPtr RureOptions
- type RureIterPtr = ForeignPtr RureIter
- type RureCapturesPtr = ForeignPtr RureCaptures
- type RureSetPtr = ForeignPtr RureSet
- type RureIterCaptureNamesPtr = ForeignPtr RureIterCaptureNames
- rureOptionsNew :: IO (Ptr RureOptions)
- rureOptionsFree :: FinalizerPtr ()
- rureErrorNew :: IO (Ptr RureError)
- rureErrorFree :: FinalizerPtr ()
- rureIterNew :: RurePtr -> IO (Ptr RureIter)
- rureFree :: FinalizerPtr ()
- rureIterFree :: FinalizerPtr ()
- rureCapturesNew :: RurePtr -> IO (Ptr RureCaptures)
- rureCapturesFree :: FinalizerPtr ()
- rureSetFree :: FinalizerPtr ()
- rureIterCaptureNamesNew :: RurePtr -> IO (Ptr RureIterCaptureNames)
- rureIterCaptureNamesFree :: FinalizerPtr ()
- rureOptionsSizeLimit :: RureOptionsPtr -> CSize -> IO ()
- rureOptionsDfaSizeLimit :: RureOptionsPtr -> CSize -> IO ()
- rureErrorMessage :: RureErrorPtr -> IO String
- rureCompile :: Ptr UInt8 -> CSize -> RureFlags -> RureOptionsPtr -> RureErrorPtr -> IO (Ptr Rure)
- rureCompileMust :: CString -> IO (Ptr Rure)
- rureCompileSet :: Ptr (Ptr UInt8) -> Ptr CSize -> CSize -> RureFlags -> RureOptionsPtr -> RureErrorPtr -> IO (Ptr RureSet)
- rureIsMatch :: RurePtr -> Ptr UInt8 -> CSize -> CSize -> IO Bool
- rureFind :: RurePtr -> Ptr UInt8 -> CSize -> CSize -> Ptr RureMatch -> IO Bool
- rureIterNext :: RureIterPtr -> Ptr UInt8 -> CSize -> Ptr RureMatch -> IO Bool
- rureIterNextCaptures :: RureIterPtr -> Ptr UInt8 -> CSize -> RureCapturesPtr -> IO Bool
- rureCapturesAt :: RureCapturesPtr -> CSize -> Ptr RureMatch -> IO Bool
- rureCapturesLen :: RureCapturesPtr -> IO CSize
- rureFindCaptures :: RurePtr -> Ptr UInt8 -> CSize -> CSize -> RureCapturesPtr -> IO Bool
- rureShortestMatch :: RurePtr -> Ptr UInt8 -> CSize -> CSize -> Ptr CSize -> IO Bool
- rureCaptureNameIndex :: RurePtr -> CString -> IO Int32
- rureSetIsMatch :: RureSetPtr -> Ptr UInt8 -> CSize -> CSize -> IO Bool
- rureSetMatches :: RureSetPtr -> Ptr UInt8 -> CSize -> CSize -> Ptr CBool -> IO Bool
- rureSetLen :: RureSetPtr -> IO CSize
- rureIterCaptureNamesNext :: RureIterCaptureNamesPtr -> Ptr CString -> IO Bool
- rureFlagCaseI :: RureFlags
- rureFlagMulti :: RureFlags
- rureFlagDotNL :: RureFlags
- rureFlagSwapGreed :: RureFlags
- rureFlagSpace :: RureFlags
- rureFlagUnicode :: RureFlags
- rureDefaultFlags :: RureFlags
- rureEscapeMust :: CString -> IO CString
- rureCstringFree :: CString -> IO ()
Types
Abstract types
data RureOptions Source #
data RureCaptures Source #
data RureIterCaptureNames Source #
Integer types
Types
Pointer types (c2hs)
type RurePtr = ForeignPtr Rure Source #
type RureErrorPtr = ForeignPtr RureError Source #
type RureOptionsPtr = ForeignPtr RureOptions Source #
type RureIterPtr = ForeignPtr RureIter Source #
type RureCapturesPtr = ForeignPtr RureCaptures Source #
type RureSetPtr = ForeignPtr RureSet Source #
Functions
Allocation
rureOptionsNew :: IO (Ptr RureOptions) Source #
rureOptionsFree :: FinalizerPtr () Source #
rureErrorFree :: FinalizerPtr () Source #
rureFree :: FinalizerPtr () Source #
rureIterFree :: FinalizerPtr () Source #
rureCapturesNew :: RurePtr -> IO (Ptr RureCaptures) Source #
rureCapturesFree :: FinalizerPtr () Source #
rureSetFree :: FinalizerPtr () Source #
Options
rureOptionsSizeLimit :: RureOptionsPtr -> CSize -> IO () Source #
rureOptionsDfaSizeLimit :: RureOptionsPtr -> CSize -> IO () Source #
rureErrorMessage :: RureErrorPtr -> IO String Source #
Compilation
rureCompile :: Ptr UInt8 -> CSize -> RureFlags -> RureOptionsPtr -> RureErrorPtr -> IO (Ptr Rure) Source #
rureCompileSet :: Ptr (Ptr UInt8) -> Ptr CSize -> CSize -> RureFlags -> RureOptionsPtr -> RureErrorPtr -> IO (Ptr RureSet) Source #
Matching
rureIterNextCaptures :: RureIterPtr -> Ptr UInt8 -> CSize -> RureCapturesPtr -> IO Bool Source #
rureCapturesAt :: RureCapturesPtr -> CSize -> Ptr RureMatch -> IO Bool Source #
rureCapturesLen :: RureCapturesPtr -> IO CSize Source #
rureSetIsMatch :: RureSetPtr -> Ptr UInt8 -> CSize -> CSize -> IO Bool Source #
rureSetLen :: RureSetPtr -> IO CSize Source #
Flags
String utilities
rureCstringFree :: CString -> IO () Source #