regex-0.0.0.2: A Regular Expression 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; length_ is the minimum implementation

Minimal complete definition

length_, pack_, unpack_, parse_tpl

Methods

length_ :: a -> Int Source

length function for a

pack_ :: String -> a Source

inject String into a

unpack_ :: a -> String Source

project a onto a String

textify :: a -> Text Source

inject into Text

detextify :: Text -> a Source

project Text onto a

appendNewline :: a -> a Source

append a newline

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

apply a substitution function to a Capture

parse_tpl :: 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 Replace_ a Source

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

Constructors

Replace_ 

Fields

_r_length :: a -> Int
 
_r_subst :: (a -> a) -> Capture a -> a
 

replace_ :: Replace a => Replace_ a Source

replace_ encapsulates Replace_ a from a Replace a context

data Phi a Source

Phi specifies the substitution function for procesing the substrings captured by the regular expression.

Constructors

Phi 

Fields

_phi_context :: Context

the context for applying the substitution

_phi_phi :: Location -> a -> a

the substitution function takes the location and the text to be replaced and returns the replacement text to be substituted

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

_loc_match :: Int

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

_loc_capture :: 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 => Phi a -> Matches a -> a Source

substitutes the PHI substitutions through the Matches

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 => Replace_ 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 Replace_ argument

replaceAllCapturesM :: (Extract a, Monad m) => Replace_ 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 => Phi a -> Match a -> a Source

substitutes the PHI substitutions through the Match

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

replaceCaptures_ is like replaceCaptures' but takes the Replace methods through the Replace_ argument

replaceCapturesM :: (Monad m, Extract a) => Replace_ 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) -> Mode -> 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