regex-0.13.0.0: Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.Replace

Contents

Synopsis

REContext and RELocation

data REContext Source #

REContext specifies which contexts the substitutions should be applied

Constructors

TOP

substitutions should be applied to the top-level only, the text that matched the whole RE

SUB

substitutions should only be applied to the text captured by bracketed sub-REs

ALL

the substitution function should be applied to all captures, the top level and the sub-expression captures

data RELocation Source #

the RELocation information passed into the substitution function specifies which sub-expression is being substituted

Constructors

RELocation 

Fields

  • locationMatch :: Int

    the zero-based, i-th string to be matched, when matching all strings, zero when only the first string is being matched

  • locationCapture :: CaptureOrdinal

    0, when matching the top-level string matched by the whole RE, 1 for the top-most, left-most redex captured by bracketed sub-REs, etc.

isTopLocation :: RELocation -> Bool Source #

True iff the location references a complete match (i.e., not a bracketed capture)

replaceAll

replaceAll :: Replace a => a -> Matches a -> a Source #

replace all with a template, $0 for whole text, $1 for first capture, etc.

replaceAllCaptures :: Replace a => REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Matches a -> a Source #

substitutes using a function that takes the full Match context and returns the same replacement text as the _phi_phi context.

replaceAllCaptures_ :: Extract a => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Matches a -> a Source #

replaceAllCaptures_ is like like replaceAllCaptures but takes the Replace methods through the ReplaceMethods argument

replaceAllCapturesM :: (Extract a, Monad m) => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> m (Maybe a)) -> Matches a -> m a Source #

replaceAllCapturesM is just a monadically generalised version of replaceAllCaptures_

replace

replace :: Replace a => a -> Match a -> a Source #

replaceCaptures :: Replace a => REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Match a -> a Source #

substitutes using a function that takes the full Match context and returns the same replacement text as the _phi_phi context.

replaceCaptures_ :: Extract a => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Match a -> a Source #

replaceCaptures_ is like replaceCaptures but takes the Replace methods through the ReplaceMethods argument

replaceCapturesM :: (Monad m, Extract a) => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> m (Maybe a)) -> Match a -> m a Source #

replaceCapturesM is just a monadically generalised version of replaceCaptures_

Replace and ReplaceMethods

class (Show a, Eq a, Ord a, Extract a, Monoid a) => Replace a where Source #

Replace provides the missing needed to replace the matched text in a Replace a => Match a.

Minimal complete definition

lengthR, packR, unpackR, linesR, unlinesR, parseTemplateR

Methods

lengthR :: a -> Int Source #

length function for a

packR :: String -> a Source #

inject String into a

unpackR :: a -> String Source #

project a onto a String

textifyR :: a -> Text Source #

inject into Text

detextifyR :: Text -> a Source #

project Text onto a

linesR :: a -> [a] Source #

split into lines

unlinesR :: [a] -> a Source #

concatenate a list of lines

appendNewlineR :: a -> a Source #

append a newline

substR :: (a -> a) -> Capture a -> a Source #

apply a substitution function to a Capture

parseTemplateR :: a -> Match a -> RELocation -> Capture a -> Maybe a Source #

convert a template containing $0, $1, etc., in the first argument, into a phi replacement function for use with replaceAllCaptures and replaceCaptures

Instances

Replace ByteString Source # 
Replace ByteString Source # 
Replace Text Source # 
Replace Text Source # 
Replace [Char] Source # 
Replace (Seq Char) Source # 

data ReplaceMethods a Source #

a selction of the Replace methods can be encapsulated with ReplaceMethods for the higher-order replacement functions

Constructors

ReplaceMethods 

Fields

replaceMethods :: Replace a => ReplaceMethods a Source #

replaceMethods encapsulates ReplaceMethods a from a Replace a context

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

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 #

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 #

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

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

extract the main capture from each match

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

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

Capture

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 #

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

CaptureID

data CaptureID Source #

CaptureID identifies captures, either by number (e.g., [cp|1|]) or name (e.g., [cp|foo|]).

type CaptureNames = HashMap CaptureName CaptureOrdinal Source #

the dictionary for named captures stored in compiled regular expressions associates

newtype CaptureOrdinal Source #

a CaptureOrdinal is just the number of the capture, starting with 0 for the whole of the text matched, then in leftmost, outermost

Constructors

CaptureOrdinal 

Instances

Enum CaptureOrdinal Source # 
Eq CaptureOrdinal Source # 
Num CaptureOrdinal Source # 
Ord CaptureOrdinal Source # 
Show CaptureOrdinal Source # 
Ix CaptureOrdinal Source #