regex-0.11.1.0: Toolkit for regex-base

Safe HaskellNone
LanguageHaskell2010

Text.RE.ZeInternals.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_

expandMacros

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

templateCaptures

templateCaptures :: (Replace a, RegexContext Regex a (Matches a), RegexMaker Regex CompOption ExecOption String) => (a -> String) -> a -> [CaptureID] Source #

list all of the CaptureID references in the replace template in the second argument

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