regex-0.6.0.0: Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.Replace

Synopsis

Documentation

class (Extract a, Monoid a) => Replace a where Source

Replace provides the missing methods needed to replace the matched text; lengthE is the minimum implementation

Minimal complete definition

lengthE, packE, unpackE, parseTemplateE

Methods

lengthE :: a -> Int Source

length function for a

packE :: String -> a Source

inject String into a

unpackE :: a -> String Source

project a onto a String

textifyE :: a -> Text Source

inject into Text

detextifyE :: Text -> a Source

project Text onto a

appendNewlineE :: a -> a Source

append a newline

substE :: (a -> a) -> Capture a -> a Source

apply a substitution function to a Capture

parseTemplateE :: a -> Match a -> Location -> 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 
Replace ByteString 
Replace Text 
Replace Text 
Replace [Char] 
Replace (Seq Char) 

data ReplaceMethods a Source

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

Constructors

ReplaceMethods 

Fields

methodLength :: a -> Int
 
methodSubst :: (a -> a) -> Capture a -> a
 

replaceMethods :: Replace a => ReplaceMethods a Source

replaceMethods encapsulates ReplaceMethods a from a Replace a context

data Context Source

Context 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

Instances

data Location Source

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

Constructors

Location 

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.

Instances

isTopLocation :: Location -> Bool Source

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

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

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

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 => Context -> (Match a -> Location -> 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 -> Context -> (Match a -> Location -> 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 -> Context -> (Match a -> Location -> Capture a -> m (Maybe a)) -> Matches a -> m a Source

replaceAllCapturesM is just a monadically generalised version of replaceAllCaptures_

replaceCaptures :: Replace a => Context -> (Match a -> Location -> 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 -> Context -> (Match a -> Location -> 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 -> Context -> (Match a -> Location -> Capture a -> m (Maybe a)) -> Match a -> m a Source

replaceCapturesM is just a monadically generalised version of replaceCaptures_

expandMacros :: (r -> String) -> Macros r -> String -> String Source

expand all of the @{..} macros in the RE in the argument String according to the Macros argument, preprocessing the RE String according to the Mode argument (used internally)

expandMacros' :: (MacroID -> Maybe String) -> String -> String Source

expand the @{..} macos in the argument string using the given function