lens-regex-0.1.1: Lens powered regular expression

Safe HaskellNone
LanguageHaskell2010

Text.Regex.Lens

Synopsis

Documentation

data MatchPart text Source #

Constructors

MatchPart 

Fields

Instances
Show text => Show (MatchPart text) Source # 
Instance details

Defined in Text.Regex.Lens

Methods

showsPrec :: Int -> MatchPart text -> ShowS #

show :: MatchPart text -> String #

showList :: [MatchPart text] -> ShowS #

matchedString :: forall text. Lens' (MatchPart text) text Source #

captures :: forall text. Getter (MatchPart text) [text] Source #

regex Source #

Arguments

:: (RegexLike regex text, Monoid text) 
=> regex

compiled regular expression

-> IndexedTraversal' Int text (MatchPart text) 

An indexed Traversal for matched part with regexp.

>>> "foo bar baz" ^? regex [r|b.*r|]
Just (MatchPart {_matchedString = "bar", _captures = []})
>>> "foo bar baz" ^? regex [r|hoge|]
Nothing

You can access to the matched string by using matchedString:

>>> "foo bar baz" ^? regex [r|b.*r|] . matchedString
Just "bar"

Multiple result:

>>> "foo bar baz" ^.. regex [r|b[^ ]+|] . matchedString
["bar","baz"]

Replace:

>>> "foo bar baz" & regex [r|b[^ ]+|] . matchedString .~ "nya"
"foo nya nya"

Indexing:

>>> "foo bar baz" ^.. regex [r|b[^ ]+|] . index 1 . matchedString
["baz"]
>>> "foo bar baz" & regex [r|b[^ ]+|] . index 1 . matchedString .~ "nya"
"foo bar nya"

Captures:

>>> "foo00 bar01 baz02" ^.. regex [r|([a-z]+)([0-9]+)|] . captures
[["foo","00"],["bar","01"],["baz","02"]]
>>> "foo00 bar01 baz02" ^.. regex [r|([a-z]+)([0-9]+)|] . captures . traversed . index 1
["00","01","02"]

Note: This is not a legal Traversal, unless you are very careful not to invalidate the predicate on the target. For example, if you replace the matched part with a string which is not match with the regex, the second Traversal law is violated.

let l = regex [r|t.*t|] . matchedString
over l (++ "peta") . over l (++ "nya") /= over l ((++ "peta") . (++ "nya"))
over l (++ "put") . over l (++ "hot") == over l ((++ "put") . (++ "hot"))

regex' :: (RegexLike regex text, Monoid text) => regex -> Lens' text (RegexResult text) Source #

matched :: (Indexable Int p, Applicative f) => p (MatchPart text) (f (MatchPart text)) -> RegexResult text -> f (RegexResult text) Source #

matched' :: Traversal' (RegexResult text) (MatchPart text) Source #