regex-pcre2-1.0.0.0: PCRE2 Backend for "Text.Regex" (regex-base)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Regex.PCRE2.Wrap

Description

This will fail or error only if allocation fails or a nullPtr is passed in.

Synopsis

High-level interface

data Regex Source #

A compiled regular expression

Instances

Instances details
RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString.Lazy

RegexLike Regex String Source # 
Instance details

Defined in Text.Regex.PCRE2.String

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString.Lazy

RegexContext Regex String String Source # 
Instance details

Defined in Text.Regex.PCRE2.String

Methods

match :: Regex -> String -> String #

matchM :: MonadFail m => Regex -> String -> m String #

RegexOptions Regex CompOption MatchOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

RegexMaker Regex CompOption MatchOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString

RegexMaker Regex CompOption MatchOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString.Lazy

RegexMaker Regex CompOption MatchOption String Source # 
Instance details

Defined in Text.Regex.PCRE2.String

RegexMaker Regex CompOption MatchOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE2.Sequence

RegexLike Regex (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE2.Sequence

RegexContext Regex (Seq Char) (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE2.Sequence

Methods

match :: Regex -> Seq Char -> Seq Char #

matchM :: MonadFail m => Regex -> Seq Char -> m (Seq Char) #

newtype CompOption Source #

Constructors

CompOption Word32 

Instances

Instances details
Bits CompOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

Num CompOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

Show CompOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

Eq CompOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

RegexOptions Regex CompOption MatchOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

RegexMaker Regex CompOption MatchOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString

RegexMaker Regex CompOption MatchOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString.Lazy

RegexMaker Regex CompOption MatchOption String Source # 
Instance details

Defined in Text.Regex.PCRE2.String

RegexMaker Regex CompOption MatchOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE2.Sequence

newtype MatchOption Source #

Constructors

MatchOption Word32 

Instances

Instances details
Bits MatchOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

Num MatchOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

Show MatchOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

Eq MatchOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

RegexOptions Regex CompOption MatchOption Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

RegexMaker Regex CompOption MatchOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString

RegexMaker Regex CompOption MatchOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE2.ByteString.Lazy

RegexMaker Regex CompOption MatchOption String Source # 
Instance details

Defined in Text.Regex.PCRE2.String

RegexMaker Regex CompOption MatchOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE2.Sequence

(=~) :: (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

newtype ReturnCode Source #

Constructors

ReturnCode CInt 

Instances

Instances details
Show ReturnCode Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

Eq ReturnCode Source # 
Instance details

Defined in Text.Regex.PCRE2.Wrap

wrapCompile 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

wrapTest Source #

Arguments

:: StartOffset

Starting index in CStringLen

-> Regex

Compiled regular expression

-> CStringLen

String to match against and length in bytes

-> IO (Either WrapError Bool) 

wrapMatch Source #

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

CompOption values

ReturnCode values