regex-pcre-0.95.0.1: PCRE Backend for "Text.Regex" (regex-base)
Safe HaskellNone
LanguageHaskell2010

Text.Regex.PCRE

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

class Extract source where #

Minimal complete definition

before, after, empty

Methods

before :: Int -> source -> source #

after :: Int -> source -> source #

empty :: source #

extract :: (Int, Int) -> source -> source #

Instances

Instances details
Extract ByteString 
Instance details

Defined in Text.Regex.Base.RegexLike

Methods

before :: Int -> ByteString -> ByteString #

after :: Int -> ByteString -> ByteString #

empty :: ByteString #

extract :: (Int, Int) -> ByteString -> ByteString #

Extract ByteString 
Instance details

Defined in Text.Regex.Base.RegexLike

Methods

before :: Int -> ByteString -> ByteString #

after :: Int -> ByteString -> ByteString #

empty :: ByteString #

extract :: (Int, Int) -> ByteString -> ByteString #

Extract Text 
Instance details

Defined in Text.Regex.Base.RegexLike

Methods

before :: Int -> Text -> Text #

after :: Int -> Text -> Text #

empty :: Text #

extract :: (Int, Int) -> Text -> Text #

Extract Text 
Instance details

Defined in Text.Regex.Base.RegexLike

Methods

before :: Int -> Text -> Text #

after :: Int -> Text -> Text #

empty :: Text #

extract :: (Int, Int) -> Text -> Text #

Extract String 
Instance details

Defined in Text.Regex.Base.RegexLike

Methods

before :: Int -> String -> String #

after :: Int -> String -> String #

empty :: String #

extract :: (Int, Int) -> String -> String #

Extract (Seq a) 
Instance details

Defined in Text.Regex.Base.RegexLike

Methods

before :: Int -> Seq a -> Seq a #

after :: Int -> Seq a -> Seq a #

empty :: Seq a #

extract :: (Int, Int) -> Seq a -> Seq a #

class Extract source => RegexLike regex source where #

Minimal complete definition

Nothing

Methods

matchOnce :: regex -> source -> Maybe MatchArray #

matchAll :: regex -> source -> [MatchArray] #

matchCount :: regex -> source -> Int #

matchTest :: regex -> source -> Bool #

matchAllText :: regex -> source -> [MatchText source] #

matchOnceText :: regex -> source -> Maybe (source, MatchText source, source) #

Instances

Instances details
RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

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) #

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

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) #

RegexLike Regex String Source # 
Instance details

Defined in Text.Regex.PCRE.String

Methods

matchOnce :: Regex -> String -> Maybe MatchArray #

matchAll :: Regex -> String -> [MatchArray] #

matchCount :: Regex -> String -> Int #

matchTest :: Regex -> String -> Bool #

matchAllText :: Regex -> String -> [MatchText String] #

matchOnceText :: Regex -> String -> Maybe (String, MatchText String, String) #

RegexLike Regex (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE.Sequence

Methods

matchOnce :: Regex -> Seq Char -> Maybe MatchArray #

matchAll :: Regex -> Seq Char -> [MatchArray] #

matchCount :: Regex -> Seq Char -> Int #

matchTest :: Regex -> Seq Char -> Bool #

matchAllText :: Regex -> Seq Char -> [MatchText (Seq Char)] #

matchOnceText :: Regex -> Seq Char -> Maybe (Seq Char, MatchText (Seq Char), Seq Char) #

class RegexOptions regex compOpt execOpt | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where #

Methods

blankCompOpt :: compOpt #

blankExecOpt :: execOpt #

defaultCompOpt :: compOpt #

defaultExecOpt :: execOpt #

setExecOpts :: execOpt -> regex -> regex #

getExecOpts :: regex -> execOpt #

class RegexOptions regex compOpt execOpt => RegexMaker regex compOpt execOpt source | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where #

Minimal complete definition

Nothing

Methods

makeRegex :: source -> regex #

makeRegexOpts :: compOpt -> execOpt -> source -> regex #

makeRegexM :: MonadFail m => source -> m regex #

makeRegexOptsM :: MonadFail m => compOpt -> execOpt -> source -> m regex #

Instances

Instances details
RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.PCRE.String

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

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

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #

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

Defined in Text.Regex.PCRE.Sequence

Methods

makeRegex :: Seq Char -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex #

makeRegexM :: MonadFail m => Seq Char -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex #

class RegexLike regex source => RegexContext regex source target where #

Methods

match :: regex -> source -> target #

matchM :: MonadFail m => regex -> source -> m target #

Instances

Instances details
RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

Methods

match :: Regex -> ByteString -> ByteString #

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

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

Methods

match :: Regex -> ByteString -> ByteString #

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

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 (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) #

type MatchArray = Array Int (MatchOffset, MatchLength) #

type MatchOffset = Int #

type MatchLength = Int #

newtype AllMatches (f :: Type -> Type) b #

Constructors

AllMatches 

Fields

newtype AllSubmatches (f :: Type -> Type) b #

Constructors

AllSubmatches 

Fields

newtype AllTextMatches (f :: Type -> Type) b #

Constructors

AllTextMatches 

Fields

newtype AllTextSubmatches (f :: Type -> Type) b #

Constructors

AllTextSubmatches 

Fields

data MatchResult a #

Constructors

MR 

Fields

type MatchText source = Array Int (source, (MatchOffset, MatchLength)) #

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.PCRE.ByteString

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) #

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

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) #

RegexLike Regex String Source # 
Instance details

Defined in Text.Regex.PCRE.String

Methods

matchOnce :: Regex -> String -> Maybe MatchArray #

matchAll :: Regex -> String -> [MatchArray] #

matchCount :: Regex -> String -> Int #

matchTest :: Regex -> String -> Bool #

matchAllText :: Regex -> String -> [MatchText String] #

matchOnceText :: Regex -> String -> Maybe (String, MatchText String, String) #

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

Methods

match :: Regex -> ByteString -> ByteString #

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

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

Methods

match :: Regex -> ByteString -> ByteString #

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

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 #

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.PCRE.String

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

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

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #

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

Defined in Text.Regex.PCRE.Sequence

Methods

makeRegex :: Seq Char -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex #

makeRegexM :: MonadFail m => Seq Char -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex #

RegexLike Regex (Seq Char) Source # 
Instance details

Defined in Text.Regex.PCRE.Sequence

Methods

matchOnce :: Regex -> Seq Char -> Maybe MatchArray #

matchAll :: Regex -> Seq Char -> [MatchArray] #

matchCount :: Regex -> Seq Char -> Int #

matchTest :: Regex -> Seq Char -> Bool #

matchAllText :: Regex -> Seq Char -> [MatchText (Seq Char)] #

matchOnceText :: Regex -> Seq Char -> Maybe (Seq Char, MatchText (Seq Char), Seq Char) #

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 CompOption Source #

Constructors

CompOption CInt 

Instances

Instances details
Bits 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

Methods

showsPrec :: Int -> CompOption -> ShowS

show :: CompOption -> String

showList :: [CompOption] -> ShowS

Eq CompOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Methods

(==) :: CompOption -> CompOption -> Bool

(/=) :: CompOption -> CompOption -> Bool

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.PCRE.String

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

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

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #

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

Defined in Text.Regex.PCRE.Sequence

Methods

makeRegex :: Seq Char -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex #

makeRegexM :: MonadFail m => Seq Char -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex #

newtype ExecOption Source #

Constructors

ExecOption CInt 

Instances

Instances details
Bits 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

Methods

showsPrec :: Int -> ExecOption -> ShowS

show :: ExecOption -> String

showList :: [ExecOption] -> ShowS

Eq ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

Methods

(==) :: ExecOption -> ExecOption -> Bool

(/=) :: ExecOption -> ExecOption -> Bool

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.PCRE.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.PCRE.String

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

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

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #

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

Defined in Text.Regex.PCRE.Sequence

Methods

makeRegex :: Seq Char -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex #

makeRegexM :: MonadFail m => Seq Char -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex #

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