Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.RE.Replace
Contents
- data REContext
- data RELocation = RELocation {}
- isTopLocation :: RELocation -> Bool
- replaceAll :: Replace a => a -> Matches a -> a
- replaceAllCaptures :: Replace a => REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Matches a -> a
- replaceAllCaptures_ :: Extract a => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Matches a -> a
- replaceAllCapturesM :: (Extract a, Monad m) => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> m (Maybe a)) -> Matches a -> m a
- replace :: Replace a => a -> Match a -> a
- replaceCaptures :: Replace a => REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Match a -> a
- replaceCaptures_ :: Extract a => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> Maybe a) -> Match a -> a
- replaceCapturesM :: (Monad m, Extract a) => ReplaceMethods a -> REContext -> (Match a -> RELocation -> Capture a -> m (Maybe a)) -> Match a -> m a
- class (Show a, Eq a, Ord a, Extract a, Monoid a) => Replace a where
- data ReplaceMethods a = ReplaceMethods {
- methodLength :: a -> Int
- methodSubst :: (a -> a) -> Capture a -> a
- replaceMethods :: Replace a => ReplaceMethods a
- data Matches a = Matches {
- matchesSource :: !a
- allMatches :: ![Match a]
- anyMatches :: Matches a -> Bool
- countMatches :: Matches a -> Int
- matches :: Matches a -> [a]
- mainCaptures :: Matches a -> [Capture a]
- data Match a = Match {
- matchSource :: !a
- captureNames :: !CaptureNames
- matchArray :: !(Array CaptureOrdinal (Capture a))
- noMatch :: a -> Match a
- emptyMatchArray :: Array CaptureOrdinal (Capture a)
- matched :: Match a -> Bool
- matchedText :: Match a -> Maybe a
- matchCapture :: Match a -> Maybe (Capture a)
- matchCaptures :: Match a -> Maybe (Capture a, [Capture a])
- (!$$) :: Match a -> CaptureID -> a
- captureText :: CaptureID -> Match a -> a
- (!$$?) :: Match a -> CaptureID -> Maybe a
- captureTextMaybe :: CaptureID -> Match a -> Maybe a
- (!$) :: Match a -> CaptureID -> Capture a
- capture :: CaptureID -> Match a -> Capture a
- (!$?) :: Match a -> CaptureID -> Maybe (Capture a)
- captureMaybe :: CaptureID -> Match a -> Maybe (Capture a)
- convertMatchText :: source -> MatchText source -> Match source
- data Capture a = Capture {
- captureSource :: !a
- capturedText :: !a
- captureOffset :: !Int
- captureLength :: !Int
- hasCaptured :: Capture a -> Bool
- capturePrefix :: Extract a => Capture a -> a
- captureSuffix :: Extract a => Capture a -> a
- data CaptureID
- type CaptureNames = HashMap CaptureName CaptureOrdinal
- noCaptureNames :: CaptureNames
- newtype CaptureName = CaptureName {}
- newtype CaptureOrdinal = CaptureOrdinal {}
- findCaptureID :: CaptureID -> CaptureNames -> Int
REContext and RELocation
REContext
specifies which contexts the substitutions should be applied
data RELocation Source #
the RELocation
information passed into the substitution function
specifies which sub-expression is being substituted
Constructors
RELocation | |
Fields
|
Instances
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
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
.
Methods
length function for a
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
split into lines
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
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
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 # | |
(RegexContext regex source [MatchText source], RegexLike regex source) => RegexContext regex source (Matches source) Source # | this instance hooks |
Eq a => Eq (Matches a) Source # | |
Show a => Show (Matches a) Source # | |
anyMatches :: Matches a -> Bool Source #
tests whether the RE matched the source text at all
countMatches :: Matches a -> Int Source #
count the matches
mainCaptures :: Matches a -> [Capture a] Source #
extract the main capture from each match
Match
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 # | |
(RegexContext regex source (AllTextSubmatches (Array Int) (source, (Int, Int))), RegexLike regex source) => RegexContext regex source (Match source) Source # | this instance hooks |
Eq a => Eq (Match a) Source # | |
Show a => Show (Match a) Source # | |
emptyMatchArray :: Array CaptureOrdinal (Capture a) Source #
an empty array of Capture
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
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
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
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
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
the matching of a single sub-expression against part of the source text
Constructors
Capture | |
Fields
|
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
CaptureID identifies captures, either by number (e.g., [cp|1|]) or name (e.g., [cp|foo|]).
Constructors
IsCaptureOrdinal CaptureOrdinal | |
IsCaptureName CaptureName |
type CaptureNames = HashMap CaptureName CaptureOrdinal Source #
the dictionary for named captures stored in compiled regular expressions associates
noCaptureNames :: CaptureNames Source #
an empty CaptureNames
dictionary
newtype CaptureName Source #
a CaptureName
is just the text of the name
Constructors
CaptureName | |
Fields |
Instances
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 | |
Fields |
findCaptureID :: CaptureID -> CaptureNames -> Int Source #
look up a CaptureID
in the CaptureNames
dictionary