regex-0.10.0.3: Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.Types.Match

Synopsis

Documentation

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

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 #

noMatch :: a -> Match a Source #

Construct a Match that does not match anything.

emptyMatchArray :: Array CaptureOrdinal (Capture a) Source #

an empty array of Capture

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

(!$$) :: Match a -> CaptureID -> a infixl 9 Source #

an alternative for captureText

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

(!$$?) :: Match a -> CaptureID -> Maybe a Source #

an alternative for captureTextMaybe

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

(!$) :: Match a -> CaptureID -> Capture a infixl 9 Source #

an alternative for 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

(!$?) :: Match a -> CaptureID -> Maybe (Capture a) Source #

an alternative for capture captureMaybe

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)

convertMatchText :: source -> MatchText source -> Match source Source #

convert a regex-base native MatchText into a regex Match type