regex-pcre-builtin-0.94.2.0.7.7: Replaces/Enhances Text.RegexSource codeContentsIndex
Text.Regex.PCRE.Wrap
Contents
High-level interface
Low-level interface
Miscellaneous
CompOption values
ExecOption values
ReturnCode values
Description
This will fail or error only if allocation fails or a nullPtr is passed in.
Synopsis
data Regex
newtype CompOption = CompOption CInt
newtype ExecOption = ExecOption CInt
(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target
(=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, Monad m) => source1 -> source -> m target
type StartOffset = MatchOffset
type EndOffset = MatchOffset
newtype ReturnCode = ReturnCode CInt
type WrapError = (ReturnCode, String)
wrapCompile :: CompOption -> ExecOption -> CString -> IO (Either (MatchOffset, String) Regex)
wrapTest :: StartOffset -> Regex -> CStringLen -> IO (Either WrapError Bool)
wrapMatch :: StartOffset -> Regex -> CStringLen -> IO (Either WrapError (Maybe [(StartOffset, EndOffset)]))
wrapMatchAll :: Regex -> CStringLen -> IO (Either WrapError [MatchArray])
wrapCount :: Regex -> CStringLen -> IO (Either WrapError Int)
getVersion :: Maybe String
configUTF8 :: Bool
getNumSubs :: Regex -> Int
unusedOffset :: MatchOffset
compBlank :: CompOption
compAnchored :: CompOption
compAutoCallout :: CompOption
compCaseless :: CompOption
compDollarEndOnly :: CompOption
compDotAll :: CompOption
compExtended :: CompOption
compExtra :: CompOption
compFirstLine :: CompOption
compMultiline :: CompOption
compNoAutoCapture :: CompOption
compUngreedy :: CompOption
compUTF8 :: CompOption
compNoUTF8Check :: CompOption
execBlank :: ExecOption
execAnchored :: ExecOption
execNotBOL :: ExecOption
execNotEOL :: ExecOption
execNotEmpty :: ExecOption
execNoUTF8Check :: ExecOption
execPartial :: ExecOption
retOk :: ReturnCode
retNoMatch :: ReturnCode
retNull :: ReturnCode
retBadOption :: ReturnCode
retBadMagic :: ReturnCode
retUnknownNode :: ReturnCode
retNoMemory :: ReturnCode
retNoSubstring :: ReturnCode
High-level interface
data Regex Source
A compiled regular expression
show/hide Instances
newtype CompOption Source
Constructors
CompOption CInt
show/hide Instances
newtype ExecOption Source
Constructors
ExecOption CInt
show/hide Instances
(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> targetSource
(=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, Monad m) => source1 -> source -> m targetSource
Low-level interface
type StartOffset = MatchOffsetSource
type EndOffset = MatchOffsetSource
newtype ReturnCode Source
Constructors
ReturnCode CInt
show/hide Instances
type WrapError = (ReturnCode, String)Source
wrapCompileSource
:: CompOptionFlags (summed together)
-> ExecOptionFlags (summed together)
-> CStringThe regular expression to compile
-> IO (Either (MatchOffset, String) Regex)Returns: an error offset and string or the compiled regular expression
wrapTestSource
:: StartOffsetStarting index in CStringLen
-> RegexCompiled regular expression
-> CStringLenString to match against and length in bytes
-> IO (Either WrapError Bool)
wrapMatchSource
:: StartOffsetStarting index in CStringLen
-> RegexCompiled regular expression
-> CStringLenString to match against and length in bytes
-> IO (Either WrapError (Maybe [(StartOffset, EndOffset)]))Returns: 'Right Nothing' if the regex did not match the string, or: 'Right Just' an array of (offset,length) pairs where index 0 is whole match, and the rest are the captured subexpressions, or: 'Left ReturnCode' if there is some strange error
wrapMatchAll :: Regex -> CStringLen -> IO (Either WrapError [MatchArray])Source
wrapCount :: Regex -> CStringLen -> IO (Either WrapError Int)Source
Miscellaneous
getVersion :: Maybe StringSource
return version of pcre used or Nothing if pcre is not available.
configUTF8 :: BoolSource
getNumSubs :: Regex -> IntSource
unusedOffset :: MatchOffsetSource
CompOption values
compBlank :: CompOptionSource
compAnchored :: CompOptionSource
compAutoCallout :: CompOptionSource
compCaseless :: CompOptionSource
compDollarEndOnly :: CompOptionSource
compDotAll :: CompOptionSource
compExtended :: CompOptionSource
compExtra :: CompOptionSource
compFirstLine :: CompOptionSource
compMultiline :: CompOptionSource
compNoAutoCapture :: CompOptionSource
compUngreedy :: CompOptionSource
compUTF8 :: CompOptionSource
compNoUTF8Check :: CompOptionSource
ExecOption values
execBlank :: ExecOptionSource
execAnchored :: ExecOptionSource
execNotBOL :: ExecOptionSource
execNotEOL :: ExecOptionSource
execNotEmpty :: ExecOptionSource
execNoUTF8Check :: ExecOptionSource
execPartial :: ExecOptionSource
ReturnCode values
retOk :: ReturnCodeSource
retNoMatch :: ReturnCodeSource
retNull :: ReturnCodeSource
retBadOption :: ReturnCodeSource
retBadMagic :: ReturnCodeSource
retUnknownNode :: ReturnCodeSource
retNoMemory :: ReturnCodeSource
retNoSubstring :: ReturnCodeSource
Produced by Haddock version 2.4.2