regex-with-pcre-0.11.0.0: Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.PCRE

Contents

Synopsis

Tutorial

We have a regex tutorial at http://tutorial.regex.uk.

About this Module

This module provides access to the back end through polymorphic functions that operate over all of the StringTextByteString types supported by the PCRE back end. If you don't need this generality you might find it easier to work with one of the modules that have been specialised for each of these types:

The Match Operators

(*=~) :: IsRegex RE s => s -> RE -> Matches s Source #

find all matches in text; e.g., to count the number of naturals in s:

countMatches $ s *=~ [re|[0-9]+|]

(?=~) :: IsRegex RE s => s -> RE -> Match s Source #

find first match in text

The SearchReplace Operators

(*=~/) :: IsRegex RE s => s -> SearchReplace RE s -> s Source #

search and replace, all occurrences

(?=~/) :: IsRegex RE s => s -> SearchReplace RE s -> s Source #

search and replace once

The Classic rexex-base Match Operators

(=~) :: (RegexContext Regex s a, RegexMaker Regex CompOption ExecOption s) => s -> RE -> a Source #

the regex-base polymorphic match operator

(=~~) :: (Monad m, RegexContext Regex s a, RegexMaker Regex CompOption ExecOption s) => s -> RE -> m a Source #

the regex-base monadic, polymorphic match operator

Matches

data Matches a :: * -> * #

the result type to use when every match is needed, not just the first match of the RE against the source

Instances

Functor Matches 

Methods

fmap :: (a -> b) -> Matches a -> Matches b #

(<$) :: a -> Matches b -> Matches a #

(RegexContext regex source [MatchText source], RegexLike regex source) => RegexContext regex source (Matches source)

this instance hooks Matches into regex-base: regex consumers need not worry about any of this

Methods

match :: regex -> source -> Matches source #

matchM :: Monad m => regex -> source -> m (Matches source) #

Eq a => Eq (Matches a) 

Methods

(==) :: Matches a -> Matches a -> Bool #

(/=) :: Matches a -> Matches a -> Bool #

Show a => Show (Matches a) 

Methods

showsPrec :: Int -> Matches a -> ShowS #

show :: Matches a -> String #

showList :: [Matches a] -> ShowS #

matchesSource :: Matches a -> a #

the source text being matched

allMatches :: Matches a -> [Match a] #

all Match instances found, left to right

anyMatches :: Matches a -> Bool #

tests whether the RE matched the source text at all

countMatches :: Matches a -> Int #

count the matches

matches :: Matches a -> [a] #

list the Matches

Match

data Match a :: * -> * #

the result of matching a RE to a text once, listing the text that was matched and the named captures in the RE and all of the substrings matched, with the text captured by the whole RE; a complete failure to match will be represented with an empty array (with bounds (0,-1))

Instances

Functor Match 

Methods

fmap :: (a -> b) -> Match a -> Match b #

(<$) :: a -> Match b -> Match a #

(RegexContext regex source (AllTextSubmatches (Array Int) (source, (Int, Int))), RegexLike regex source) => RegexContext regex source (Match source)

this instance hooks Match into regex-base: regex consumers need not worry about any of this

Methods

match :: regex -> source -> Match source #

matchM :: Monad m => regex -> source -> m (Match source) #

Eq a => Eq (Match a) 

Methods

(==) :: Match a -> Match a -> Bool #

(/=) :: Match a -> Match a -> Bool #

Show a => Show (Match a) 

Methods

showsPrec :: Int -> Match a -> ShowS #

show :: Match a -> String #

showList :: [Match a] -> ShowS #

matchSource :: Match a -> a #

the whole source text

matched :: Match a -> Bool #

tests whether the RE matched the source text at all

matchedText :: Match a -> Maybe a #

tests whether the RE matched the source text at all

The RE Type and Functions

data RE Source #

the RE type for this back end representing a well-formed, compiled RE

data SimpleREOptions :: * #

the default API uses these simple, universal RE options, which get auto-converted into the apropriate back-end REOptions_

Constructors

MultilineSensitive

case-sensitive with ^ and $ matching the start and end of a line

MultilineInsensitive

case-insensitive with ^ and $ matsh the start and end of a line

BlockSensitive

case-sensitive with ^ and $ matching the start and end of the input text

BlockInsensitive

case-insensitive with ^ and $ matching the start and end of the input text

reSource :: RE -> String Source #

extract the RE source string from the RE

compileRegex :: (Functor m, Monad m) => String -> m RE Source #

compile a String into a RE with the default options, generating an error if the RE is not well formed

compileRegexWith :: (Functor m, Monad m) => SimpleREOptions -> String -> m RE Source #

compile a String into a RE using the given SimpleREOptions, generating an error if the RE is not well formed

escape :: (Functor m, Monad m) => (String -> String) -> String -> m RE Source #

convert a string into a RE that matches that string, and apply it to an argument continuation function to make up the RE string to be compiled

escapeWith :: (Functor m, Monad m) => SimpleREOptions -> (String -> String) -> String -> m RE Source #

convert a string into a RE that matches that string, and apply it to an argument continuation function to make up the RE string to be compiled with the default options

escapeREString :: String -> String #

Convert a string into a regular expression that will amtch that string

The [ed| ... |] quasi quoters

ed :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edMS :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edMI :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edBS :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edBI :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edMultilineSensitive :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edMultilineInsensitive :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edBlockSensitive :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

edBlockInsensitive :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

ed_ :: QuasiQuoter Source #

the [ed| ... /// ... |] quasi quoters

The Operator Instances

These modules merely provide the IsRegex instances.