Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Text.Regex.PCRE2.ByteString.Lazy
Description
Synopsis
- data Regex
- type MatchOffset = Int
- type MatchLength = Int
- newtype CompOption = CompOption Word32
- newtype MatchOption = MatchOption Word32
- data ReturnCode
- type WrapError = (ReturnCode, String)
- unusedOffset :: MatchOffset
- getVersion :: Maybe String
- compile :: CompOption -> MatchOption -> ByteString -> IO (Either (MatchOffset, String) Regex)
- execute :: Regex -> ByteString -> IO (Either WrapError (Maybe (Array Int (MatchOffset, MatchLength))))
- regexec :: Regex -> ByteString -> IO (Either WrapError (Maybe (ByteString, ByteString, ByteString, [ByteString])))
- 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
Types
A compiled regular expression
Instances
type MatchOffset = Int #
0 based index from start of source, or (-1) for unused
type MatchLength = Int #
non-negative length of a match
newtype CompOption Source #
Constructors
CompOption Word32 |
Instances
newtype MatchOption Source #
Constructors
MatchOption Word32 |
Instances
data ReturnCode Source #
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 #
Miscellaneous
getVersion :: Maybe String Source #
Version string of PCRE2 library
Medium level API functions
Arguments
:: CompOption | (summed together) |
-> MatchOption | (summed together) |
-> ByteString | The regular expression to compile |
-> IO (Either (MatchOffset, String) Regex) | Returns: the compiled regular expression |
Compiles a regular expression
Arguments
:: Regex | Compiled regular expression |
-> ByteString | String to match against |
-> IO (Either WrapError (Maybe (Array Int (MatchOffset, MatchLength)))) | Returns: |
Matches a regular expression against a buffer, returning the buffer indicies of the match, and any submatches
| Matches a regular expression against a string
Arguments
:: Regex | Compiled regular expression |
-> ByteString | String to match against |
-> IO (Either WrapError (Maybe (ByteString, ByteString, ByteString, [ByteString]))) |
CompOption flags
compUTF :: CompOption Source #
MatchOption flags, new to v1.0.0.0 (pcre2), replacing the obsolete ExecOptions
Orphan instances
RegexLike Regex ByteString Source # | |
Methods matchOnce :: Regex -> ByteString -> Maybe MatchArray # matchAll :: Regex -> ByteString -> [MatchArray] # matchCount :: Regex -> ByteString -> Int # matchTest :: Regex -> ByteString -> Bool # matchAllText :: Regex -> ByteString -> [MatchText ByteString] # matchOnceText :: Regex -> ByteString -> Maybe (ByteString, MatchText ByteString, ByteString) # | |
RegexContext Regex ByteString ByteString Source # | |
Methods match :: Regex -> ByteString -> ByteString # matchM :: MonadFail m => Regex -> ByteString -> m ByteString # | |
RegexMaker Regex CompOption MatchOption ByteString Source # | |
Methods makeRegex :: ByteString -> Regex # makeRegexOpts :: CompOption -> MatchOption -> ByteString -> Regex # makeRegexM :: MonadFail m => ByteString -> m Regex # makeRegexOptsM :: MonadFail m => CompOption -> MatchOption -> ByteString -> m Regex # |