regex-0.10.0.2: Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.TDFA

Contents

Synopsis

Tutorial

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

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

find all matches in text

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

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

Instances

Functor Matches Source # 

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

Methods

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

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

Show a => Show (Matches a) Source # 

Methods

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

show :: Matches a -> String #

showList :: [Matches a] -> ShowS #

matchesSource :: Matches a -> a Source #

the source text being matched

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

all Match instances found, left to right

anyMatches :: Matches a -> Bool Source #

tests whether the RE matched the source text at all

countMatches :: Matches a -> Int Source #

count the matches

matches :: Matches a -> [a] Source #

list the Matches

Match

data Match a Source #

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

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

Methods

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

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

Show a => Show (Match a) Source # 

Methods

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

show :: Match a -> String #

showList :: [Match a] -> ShowS #

matchSource :: Match a -> a Source #

the whole source text

matched :: Match a -> Bool Source #

tests whether the RE matched the source text at all

matchedText :: Match a -> Maybe a Source #

tests whether the RE matched the source text at all

The RE Type and Functions

data SimpleREOptions Source #

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

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

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.