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

Text.Regex.PCRE2

Description

The Text.Regex.PCRE2 module provides a backend for regular expressions. If you import this along with other backends, then you should do so with qualified imports, perhaps renamed for convenience.

This library uses the newer libpcre2, which supports UTF8-encoded strings by default.

The regular expression can be provided as a ByteString. The regular expression and search string are passed as CStringLens and may contain NUL bytes and do not need to end in a NUL byte. ByteStrings are searched in place (via unsafeUseAsCStringLen).

A String will be converted into a CStringLen for processing. Doing this repeatedly will be very inefficient.

The Text.Regex.PCRE2.String, Text.Regex.PCRE2.ByteString, and Text.Regex.PCRE2.Wrap modules provide both the high-level interface exported by this module and medium- and low-level interfaces that return errors using Either structures.

Synopsis

Documentation

Wrap, for =~ and =~~, types and constants

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 #

getVersion :: Maybe String Source #

Version string of PCRE2 library