regex-pcre-builtin-0.95.1.1.8.43: PCRE Backend for "Text.Regex" (regex-base)

Safe HaskellNone
LanguageHaskell2010

Text.Regex.PCRE

Contents

Description

The Text.Regex.PCRE 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.

Using the provided CompOption and ExecOption values and if configUTF8 is True, then you might be able to send UTF8 encoded ByteStrings to PCRE and get sensible results. This is currently untested.

The regular expression can be provided as a ByteString, but it will be copied and a NUL byte appended to make a CString unless such a byte is already present. Thus the regular expression cannot contain an explicit NUL byte. The search string is passed as a CStringLen and may contain NUL bytes and does not need to end in a NUL byte. ByteStrings are searched in place (via unsafeUseAsCStringLen).

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

The Text.Regex.PCRE.String, Text.Regex.PCRE.ByteString, and Text.Regex.PCRE.Wrap modules provides both the high level interface exported by this module and medium- and low-level interfaces that returns error using Either structures.

Synopsis

Documentation

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

data Regex Source #

A compiled regular expression

Instances
RegexLike Regex String Source # 
Instance details

Defined in Text.Regex.PCRE.String

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

RegexLike Regex Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text.Lazy

RegexLike Regex Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexContext Regex String String Source # 
Instance details

Defined in Text.Regex.PCRE.String

Methods

match :: Regex -> String -> String #

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

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

RegexContext Regex Text Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text.Lazy

Methods

match :: Regex -> Text -> Text #

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

RegexContext Regex Text Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text

Methods

match :: Regex -> Text -> Text #

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

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.PCRE.String

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

RegexMaker Regex CompOption ExecOption Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text.Lazy

RegexMaker Regex CompOption ExecOption Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text

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

Defined in Text.Regex.PCRE.Sequence

RegexLike Regex (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE.Sequence

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

Defined in Text.Regex.PCRE.Sequence

Methods

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

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

newtype ExecOption Source #

Constructors

ExecOption CInt 
Instances
Eq ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Num ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Show ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Bits ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.PCRE.String

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

RegexMaker Regex CompOption ExecOption Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text.Lazy

RegexMaker Regex CompOption ExecOption Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text

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

Defined in Text.Regex.PCRE.Sequence

newtype CompOption Source #

Constructors

CompOption CInt 
Instances
Eq CompOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Num CompOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Show CompOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Bits CompOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.PCRE.String

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

RegexMaker Regex CompOption ExecOption Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text.Lazy

RegexMaker Regex CompOption ExecOption Text Source # 
Instance details

Defined in Text.Regex.PCRE.Text

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

Defined in Text.Regex.PCRE.Sequence

(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target Source #

(=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, MonadFail m) => source1 -> source -> m target Source #

getVersion :: Maybe String Source #

Version string of PCRE library

NOTE: The Maybe type is used for historic reasons; practically, getVersion is never Nothing.