Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Text.Regex.PCRE2.Wrap
Description
This will fail or error only if allocation fails or a nullPtr is passed in.
Synopsis
- data Regex
- newtype CompOption = CompOption Word32
- newtype MatchOption = MatchOption Word32
- (=~) :: (RegexMaker Regex CompOption MatchOption source, RegexContext Regex source1 target) => source1 -> source -> target
- (=~~) :: (RegexMaker Regex CompOption MatchOption source, RegexContext Regex source1 target, MonadFail m) => source1 -> source -> m target
- type StartOffset = MatchOffset
- type EndOffset = MatchOffset
- newtype ReturnCode = ReturnCode CInt
- type WrapError = (ReturnCode, String)
- wrapCompile :: CompOption -> MatchOption -> CStringLen -> 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
- getNumSubs :: Regex -> Int
- unusedOffset :: MatchOffset
- compBlank :: CompOption
- compAnchored :: CompOption
- compEndAnchored :: CompOption
- compAllowEmptyClass :: CompOption
- compAltBSUX :: CompOption
- compAltExtendedClass :: CompOption
- compAltVerbnames :: CompOption
- compAutoCallout :: CompOption
- compCaseless :: CompOption
- compDollarEndOnly :: CompOption
- compDotAll :: CompOption
- compDupNames :: CompOption
- compExtended :: CompOption
- compExtendedMore :: CompOption
- compFirstLine :: CompOption
- compLiteral :: CompOption
- compMatchUnsetBackref :: CompOption
- compMultiline :: CompOption
- compNeverBackslashC :: CompOption
- compNoAutoCapture :: CompOption
- compNoAutoPossess :: CompOption
- compNoDotstarAnchor :: CompOption
- compNoUTFCheck :: CompOption
- compUngreedy :: CompOption
- compUTF :: CompOption
- matchBlank :: MatchOption
- matchAnchored :: MatchOption
- matchCopyMatchedSubject :: MatchOption
- matchDisableRecurseLoopCheck :: MatchOption
- matchEndAnchored :: MatchOption
- matchNotBOL :: MatchOption
- matchNotEOL :: MatchOption
- matchNotEmpty :: MatchOption
- matchNotEmptyAtStart :: MatchOption
- matchNoUTFCheck :: MatchOption
- matchPartialHard :: MatchOption
- matchPartialSoft :: MatchOption
- retOk :: ReturnCode
- retNoMatch :: ReturnCode
- retPartial :: ReturnCode
- retNull :: ReturnCode
- retBadOption :: ReturnCode
- retBadMagic :: ReturnCode
- retNoMemory :: ReturnCode
- retNoSubstring :: ReturnCode
High-level interface
A compiled regular expression
Instances
newtype CompOption Source #
Constructors
CompOption Word32 |
Instances
newtype MatchOption Source #
Constructors
MatchOption Word32 |
Instances
(=~) :: (RegexMaker Regex CompOption MatchOption source, RegexContext Regex source1 target) => source1 -> source -> target Source #
(=~~) :: (RegexMaker Regex CompOption MatchOption source, RegexContext Regex source1 target, MonadFail m) => source1 -> source -> m target Source #
Low-level interface
type StartOffset = MatchOffset Source #
type EndOffset = MatchOffset Source #
newtype ReturnCode Source #
Constructors
ReturnCode CInt |
Instances
Show ReturnCode Source # | |
Defined in Text.Regex.PCRE2.Wrap Methods showsPrec :: Int -> ReturnCode -> ShowS # show :: ReturnCode -> String # showList :: [ReturnCode] -> ShowS # | |
Eq ReturnCode Source # | |
Defined in Text.Regex.PCRE2.Wrap |
type WrapError = (ReturnCode, String) Source #
Arguments
:: CompOption | Flags (summed together) |
-> MatchOption | Flags (summed together) |
-> CStringLen | The regular expression to compile |
-> IO (Either (MatchOffset, String) Regex) | Returns: an error offset and string or the compiled regular expression |
Compiles a regular expression
Arguments
:: StartOffset | Starting index in CStringLen |
-> Regex | Compiled regular expression |
-> CStringLen | String to match against and length in bytes |
-> IO (Either WrapError Bool) |
Arguments
:: StartOffset | Starting index in CStringLen |
-> Regex | Compiled regular expression |
-> CStringLen | String 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 |
Matches a regular expression against a string
Should never return (Right (Just []))
wrapMatchAll :: Regex -> CStringLen -> IO (Either WrapError [MatchArray]) Source #
wrapMatchAll is an improvement over wrapMatch since it only allocates memory with allocaBytes once at the start.
Miscellaneous
getVersion :: Maybe String Source #
Version string of PCRE2 library
getNumSubs :: Regex -> Int Source #
CompOption values
compUTF :: CompOption Source #
ReturnCode values
retOk :: ReturnCode Source #
retNull :: ReturnCode Source #