Safe Haskell | None |
---|---|
Language | Haskell2010 |
Replace.Megaparsec is for finding text patterns, and also editing and replacing the found patterns. This activity is traditionally done with regular expressions, but Replace.Megaparsec uses Text.Megaparsec parsers instead for the pattern matching.
Replace.Megaparsec can be used in the same sort of “pattern capture” or “find all” situations in which one would use Python re.findall, or Perl m//, or Unix grep.
Replace.Megaparsec can be used in the same sort of “stream editing” or “search-and-replace” situations in which one would use Python re.sub, or Perl s///, or Unix sed, or awk.
See the replace-megaparsec package README for usage examples.
Synopsis
- sepCap :: forall e s m a. MonadParsec e s m => m a -> m [Either (Tokens s) a]
- findAll :: MonadParsec e s m => m a -> m [Either (Tokens s) (Tokens s)]
- findAllCap :: MonadParsec e s m => m a -> m [Either (Tokens s) (Tokens s, a)]
- streamEditT :: forall s m a. (Stream s, Monad m, Monoid s, Tokens s ~ s, Show s, Show (Token s), Typeable s) => ParsecT Void s m a -> (a -> m s) -> s -> m s
- streamEdit :: forall s a. (Stream s, Monoid s, Tokens s ~ s, Show s, Show (Token s), Typeable s) => Parsec Void s a -> (a -> s) -> s -> s
Parser combinator
:: MonadParsec e s m | |
=> m a | The pattern matching parser |
-> m [Either (Tokens s) a] |
Separate and capture
Parser combinator to find all of the non-overlapping ocurrences
of the pattern sep
in a text stream. Separate the stream into sections:
- sections which can parsed by the pattern
sep
will be captured as matching sections inRight
- non-matching sections of the stream will be captured in
Left
.
This parser will always consume its entire input and can never fail.
If there are no pattern matches, then the entire input stream will be
returned as a non-matching Left
section.
The pattern matching parser sep
will not be allowed to succeed without
consuming any input. If we allow the parser to match a zero-width pattern,
then it can match the same zero-width pattern again at the same position
on the next iteration, which would result in an infinite number of
overlapping pattern matches. So, for example, the
pattern many digitChar
, which can match zero occurences of a digit,
will be treated by sepCap
as some digitChar
, and required to match
at least one digit.
This sepCap
parser combinator is the basis for all of the other
features of this module. It is similar to the sep*
family of functions
found in
parser-combinators
and
parsers
but, importantly, it returns the parsed result of the sep
parser instead
of throwing it away.
:: MonadParsec e s m | |
=> m a | The pattern matching parser |
-> m [Either (Tokens s) (Tokens s)] |
:: MonadParsec e s m | |
=> m a | The pattern matching parser |
-> m [Either (Tokens s) (Tokens s, a)] |
Find all occurences, parse and capture pattern matches
Parser combinator for finding all occurences of a pattern in a stream.
Will call sepCap
with the match
combinator so that
the text which matched the pattern parser sep
will be returned in
the Right
sections, along with the result of the parse of sep
.
findAllCap sep =sepCap
(match
sep)
Running parser
:: (Stream s, Monad m, Monoid s, Tokens s ~ s, Show s, Show (Token s), Typeable s) | |
=> ParsecT Void s m a | The parser |
-> (a -> m s) | The |
-> s | The input stream of text to be edited. |
-> m s |
Stream editor
Also can be considered “find-and-replace”. Finds all
of the sections of the stream which match the pattern sep
, and replaces
them with the result of the editor
function.
This function is not a “parser combinator,” it is
a “way to run a parser”, like parse
or runParserT
.
Access the matched section of text in the editor
If you want access to the matched string in the editor
function,
then combine the pattern parser sep
with match
.
This will effectively change the type of the editor
to `(s,a) -> m s`, and then we can write editor
like:
let editor (matchString,parseResult) = return matchString
streamEditT (match
sep) editor inputString
Type constraints
The type of the stream of text that is input must
be Stream s
such that Tokens s ~ s
, because we want
to output the same type of stream that was input. That requirement is
satisfied for all the Stream
instances included
with Text.Megaparsec:
Data.Text,
Data.Text.Lazy,
Data.Bytestring,
Data.Bytestring.Lazy,
and Data.String.
We need the Monoid s
instance so that we can mappend
the output
stream.
We need Typeable s
and Show s
for throw
. In theory
this function should never throw an exception, because it only throws
when the sepCap
parser fails, and the sepCap
parser
can never fail. If this function ever throws, please report that as a bug.
Underlying monad context
Both the parser sep
and the editor
function are run in the underlying
monad context.
If you want to do IO
operations in the editor
function or the
parser sep
, then run this in IO
.
If you want the editor
function or the parser sep
to remember some state,
then run this in a stateful monad.
:: (Stream s, Monoid s, Tokens s ~ s, Show s, Show (Token s), Typeable s) | |
=> Parsec Void s a | The parser |
-> (a -> s) | The |
-> s | The input stream of text to be edited. |
-> s |
Pure stream editor
Pure version of streamEditT
.