regex-0.2.0.1: 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

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 #

for matching all REs against the source text

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 #

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 #

for matching just the first RE against the source text

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 #

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

Methods

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

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

Eq a => Eq (Capture a) Source # 

Methods

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

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

Show a => Show (Capture a) Source # 

Methods

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

show :: Capture a -> String #

showList :: [Capture 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

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

(!$$) :: 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)

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