regex-0.0.0.1: A Regular Expression Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.Capture

Synopsis

Documentation

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

Constructors

Matches 

Fields

matchesSource :: !a

the source text being matched

allMatches :: [Match a]

all captures found, left to right

Instances

Functor Matches 
RegexContext regex source [MatchText source] => RegexContext regex source (Matches source)

for matching all REs against the source text

Eq a => Eq (Matches a) 
Show a => Show (Matches a) 

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

Constructors

Match 

Fields

matchSource :: !a

the whole source text

captureNames :: CaptureNames

the RE's capture names

matchArray :: !(Array CaptureOrdinal (Capture a))
  1. .n-1 captures, starting with the text matched by the whole RE

Instances

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

for matching just the first RE against the source text

Eq a => Eq (Match a) 
Show a => Show (Match a) 

data Capture a Source

the matching of a single sub-expression against part of the source text

Constructors

Capture 

Fields

captureSource :: !a

the whole text that was searched

capturedText :: !a

the text that was matched

captureOffset :: !Int

the number of characters preceding the match with -1 used if no text was captured by the RE (not even the empty string)

captureLength :: !Int

the number of chacter in the captured sub-string

Instances

Functor Capture 
Eq a => Eq (Capture a) 
Show a => Show (Capture a) 

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

mainCaptures :: Matches a -> [Capture a] Source

extract the main capture from each match

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

matchCapture :: Match a -> Maybe (Capture a) Source

the top-level capture if the source text matched the RE, Nothing otherwise

matchCaptures :: Match a -> Maybe (Capture a, [Capture a]) Source

the top-level capture and the sub captures if the text matched the RE, Nothing otherwise

captureText :: CaptureID -> Match a -> a Source

look up the text of the nth capture, 0 being the match of the whole RE against the source text, 1, the first bracketed sub-expression to be matched and so on

captureTextMaybe :: CaptureID -> Match a -> Maybe a Source

look up the text of the nth capture (0 being the match of the whole), returning Nothing if the Match doesn't contain the capture

capture :: CaptureID -> Match a -> Capture a Source

look up the nth capture, 0 being the match of the whole RE against the source text, 1, the first bracketed sub-expression to be matched and so on

captureMaybe :: CaptureID -> Match a -> Maybe (Capture a) Source

look up the nth capture, 0 being the match of the whole RE against the source text, 1, the first bracketed sub-expression to be matched and so on, returning Nothing if there is no such capture, or if the capture failed to capture anything (being in a failed alternate)

hasCaptured :: Capture a -> Bool Source

test if the capture has matched any text

capturePrefix :: Extract a => Capture a -> a Source

returns the text preceding the match

captureSuffix :: Extract a => Capture a -> a Source

returns the text after the match