| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Text.Megaparsec.Compat
Synopsis
- class (Stream s, MonadPlus m) => MonadParsec e s (m :: Type -> Type) | m -> e s where
- parseError :: ParseError s e -> m a
- label :: String -> m a -> m a
- hidden :: m a -> m a
- try :: m a -> m a
- lookAhead :: m a -> m a
- notFollowedBy :: m a -> m ()
- withRecovery :: (ParseError s e -> m a) -> m a -> m a
- observing :: m a -> m (Either (ParseError s e) a)
- eof :: m ()
- token :: (Token s -> Maybe a) -> Set (ErrorItem (Token s)) -> m a
- tokens :: (Tokens s -> Tokens s -> Bool) -> Tokens s -> m (Tokens s)
- takeWhileP :: Maybe String -> (Token s -> Bool) -> m (Tokens s)
- takeWhile1P :: Maybe String -> (Token s -> Bool) -> m (Tokens s)
- takeP :: Maybe String -> Int -> m (Tokens s)
- getParserState :: m (State s e)
- updateParserState :: (State s e -> State s e) -> m ()
- mkParsec :: (State s e -> Reply e s a) -> m a
- empty :: Alternative f => f a
- (<|>) :: Alternative f => f a -> f a -> f a
- some :: MonadPlus m => m a -> m [a]
- many :: MonadPlus m => m a -> m [a]
- satisfy :: MonadParsec e s m => (Token s -> Bool) -> m (Token s)
- choice :: (Foldable f, Alternative m) => f (m a) -> m a
- count :: Monad m => Int -> m a -> m [a]
- between :: Applicative m => m open -> m close -> m a -> m a
- option :: Alternative m => a -> m a -> m a
- optional :: Alternative f => f a -> f (Maybe a)
- skipMany :: MonadPlus m => m a -> m ()
- sepBy :: MonadPlus m => m a -> m sep -> m [a]
- sepBy1 :: MonadPlus m => m a -> m sep -> m [a]
- endBy :: MonadPlus m => m a -> m sep -> m [a]
- endBy1 :: MonadPlus m => m a -> m sep -> m [a]
- manyTill :: MonadPlus m => m a -> m end -> m [a]
- class (Ord (Token s), Ord (Tokens s)) => Stream s where
- type Token s
- type Tokens s
- tokenToChunk :: Proxy s -> Token s -> Tokens s
- tokensToChunk :: Proxy s -> [Token s] -> Tokens s
- chunkToTokens :: Proxy s -> Tokens s -> [Token s]
- chunkLength :: Proxy s -> Tokens s -> Int
- chunkEmpty :: Proxy s -> Tokens s -> Bool
- take1_ :: s -> Maybe (Token s, s)
- takeN_ :: Int -> s -> Maybe (Tokens s, s)
- takeWhile_ :: (Token s -> Bool) -> s -> (Tokens s, s)
- data SourcePos = SourcePos {
- sourceName :: FilePath
- sourceLine :: !Pos
- sourceColumn :: !Pos
- chunk :: MonadParsec e s m => Tokens s -> m (Tokens s)
- data State s e = State {
- stateInput :: s
- stateOffset :: !Int
- statePosState :: PosState s
- stateParseErrors :: [ParseError s e]
- match :: MonadParsec e s m => m a -> m (Tokens s, a)
- customFailure :: MonadParsec e s m => e -> m a
- newtype InvalidPosException = InvalidPosException Int
- data Pos
- mkPos :: Int -> Pos
- unPos :: Pos -> Int
- pos1 :: Pos
- defaultTabWidth :: Pos
- initialPos :: FilePath -> SourcePos
- sourcePosPretty :: SourcePos -> String
- data ParseError s e
- = TrivialError Int (Maybe (ErrorItem (Token s))) (Set (ErrorItem (Token s)))
- | FancyError Int (Set (ErrorFancy e))
- data PosState s = PosState {
- pstateInput :: s
- pstateOffset :: !Int
- pstateSourcePos :: !SourcePos
- pstateTabWidth :: Pos
- pstateLinePrefix :: String
- class Stream s => TraversableStream s where
- reachOffset :: Int -> PosState s -> (Maybe String, PosState s)
- reachOffsetNoLine :: Int -> PosState s -> PosState s
- class Stream s => VisualStream s where
- showTokens :: Proxy s -> NonEmpty (Token s) -> String
- tokensLength :: Proxy s -> NonEmpty (Token s) -> Int
- newtype NoShareInput a = NoShareInput {
- unNoShareInput :: a
- newtype ShareInput a = ShareInput {
- unShareInput :: a
- type family Token s
- type family Tokens s
- data ErrorItem t
- class Ord a => ShowErrorComponent a where
- showErrorComponent :: a -> String
- errorComponentLen :: a -> Int
- data ParseErrorBundle s e = ParseErrorBundle {
- bundleErrors :: NonEmpty (ParseError s e)
- bundlePosState :: PosState s
- data ErrorFancy e
- mapParseError :: Ord e' => (e -> e') -> ParseError s e -> ParseError s e'
- errorOffset :: ParseError s e -> Int
- setErrorOffset :: Int -> ParseError s e -> ParseError s e
- attachSourcePos :: (Traversable t, TraversableStream s) => (a -> Int) -> t a -> PosState s -> (t (a, SourcePos), PosState s)
- errorBundlePrettyWith :: (VisualStream s, TraversableStream s) => (Maybe String -> SourcePos -> ParseError s e -> String) -> ParseErrorBundle s e -> String
- errorBundlePrettyForGhcPreProcessors :: (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- parseErrorPretty :: (VisualStream s, ShowErrorComponent e) => ParseError s e -> String
- parseErrorTextPretty :: (VisualStream s, ShowErrorComponent e) => ParseError s e -> String
- showErrorItem :: VisualStream s => Proxy s -> ErrorItem (Token s) -> String
- data ParsecT e s (m :: Type -> Type) a
- type Parsec e s = ParsecT e s Identity
- parse :: Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
- parseMaybe :: (Ord e, Stream s) => Parsec e s a -> s -> Maybe a
- parseTest :: (ShowErrorComponent e, Show a, VisualStream s, TraversableStream s) => Parsec e s a -> s -> IO ()
- runParser :: Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
- runParser' :: Parsec e s a -> State s e -> (State s e, Either (ParseErrorBundle s e) a)
- runParserT :: Monad m => ParsecT e s m a -> String -> s -> m (Either (ParseErrorBundle s e) a)
- runParserT' :: Monad m => ParsecT e s m a -> State s e -> m (State s e, Either (ParseErrorBundle s e) a)
- failure :: MonadParsec e s m => Maybe (ErrorItem (Token s)) -> Set (ErrorItem (Token s)) -> m a
- fancyFailure :: MonadParsec e s m => Set (ErrorFancy e) -> m a
- unexpected :: MonadParsec e s m => ErrorItem (Token s) -> m a
- region :: MonadParsec e s m => (ParseError s e -> ParseError s e) -> m a -> m a
- registerParseError :: MonadParsec e s m => ParseError s e -> m ()
- registerFailure :: MonadParsec e s m => Maybe (ErrorItem (Token s)) -> Set (ErrorItem (Token s)) -> m ()
- registerFancyFailure :: MonadParsec e s m => Set (ErrorFancy e) -> m ()
- single :: MonadParsec e s m => Token s -> m (Token s)
- anySingle :: MonadParsec e s m => m (Token s)
- anySingleBut :: MonadParsec e s m => Token s -> m (Token s)
- oneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s)
- noneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s)
- (<?>) :: MonadParsec e s m => m a -> String -> m a
- takeRest :: MonadParsec e s m => m (Tokens s)
- atEnd :: MonadParsec e s m => m Bool
- getInput :: MonadParsec e s m => m s
- setInput :: MonadParsec e s m => s -> m ()
- getSourcePos :: (TraversableStream s, MonadParsec e s m) => m SourcePos
- getOffset :: MonadParsec e s m => m Int
- setOffset :: MonadParsec e s m => Int -> m ()
- setParserState :: MonadParsec e s m => State s e -> m ()
- eitherP :: Alternative m => m a -> m b -> m (Either a b)
- count' :: MonadPlus m => Int -> Int -> m a -> m [a]
- manyTill_ :: MonadPlus m => m a -> m end -> m ([a], end)
- sepEndBy :: MonadPlus m => m a -> m sep -> m [a]
- sepEndBy1 :: MonadPlus m => m a -> m sep -> m [a]
- skipCount :: Monad m => Int -> m a -> m ()
- skipManyTill :: MonadPlus m => m a -> m end -> m end
- skipSome :: MonadPlus m => m a -> m ()
- skipSomeTill :: MonadPlus m => m a -> m end -> m end
- someTill :: MonadPlus m => m a -> m end -> m [a]
- someTill_ :: MonadPlus m => m a -> m end -> m ([a], end)
- errorBundlePretty :: (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
Documentation
class (Stream s, MonadPlus m) => MonadParsec e s (m :: Type -> Type) | m -> e s where #
Type class describing monads that implement the full set of primitive parsers.
Note that the following primitives are “fast” and should be taken
advantage of as much as possible if your aim is a fast parser: tokens,
takeWhileP, takeWhile1P, and takeP.
Minimal complete definition
parseError, label, try, lookAhead, notFollowedBy, withRecovery, observing, eof, token, tokens, takeWhileP, takeWhile1P, takeP, getParserState, updateParserState, mkParsec
Methods
parseError :: ParseError s e -> m a #
Stop parsing and report the ParseError. This is the only way to
control position of the error without manipulating the parser state
manually.
Since: megaparsec-8.0.0
label :: String -> m a -> m a #
The parser behaves as parser label name pp, but whenever the
parser p fails without consuming any input, it replaces names of
“expected” tokens with the name name.
:: m a -> m a #
behaves just like parser hidden pp, but it doesn't show any
“expected” tokens in error message when p fails.
The parser behaves like the parser try pp, except that it
backtracks the parser state when p fails (either consuming input or
not).
This combinator is used whenever arbitrary look ahead is needed. Since
it pretends that it hasn't consumed any input when p fails, the
(<|>) combinator will try its second alternative even if the first
parser failed while consuming input.
For example, here is a parser that is supposed to parse the word “let” or the word “lexical”:
>>>parseTest (string "let" <|> string "lexical") "lexical"1:1: unexpected "lex" expecting "let"
What happens here? The first parser consumes “le” and fails (because it
doesn't see a “t”). The second parser, however, isn't tried, since the
first parser has already consumed some input! try fixes this behavior
and allows backtracking to work:
>>>parseTest (try (string "let") <|> string "lexical") "lexical""lexical"
try also improves error messages in case of overlapping alternatives,
because Megaparsec's hint system can be used:
>>>parseTest (try (string "let") <|> string "lexical") "le"1:1: unexpected "le" expecting "let" or "lexical"
Note that as of Megaparsec 4.4.0, string
backtracks automatically (see tokens), so it does not need try.
However, the examples above demonstrate the idea behind try so well
that it was decided to keep them. You still need to use try when your
alternatives are complex, composite parsers.
If p in succeeds (either consuming input or not)
the whole parser behaves like lookAhead pp succeeded without consuming anything
(parser state is not updated as well). If p fails, lookAhead has no
effect, i.e. it will fail consuming input if p fails consuming input.
Combine with try if this is undesirable.
notFollowedBy :: m a -> m () #
only succeeds when the parser notFollowedBy pp fails. This
parser never consumes any input and never modifies parser state. It
can be used to implement the “longest match” rule.
Arguments
| :: (ParseError s e -> m a) | How to recover from failure |
| -> m a | Original parser |
| -> m a | Parser that can recover from failures |
allows us to continue parsing even if the parser
withRecovery r pp fails. In this case r is called with the actual ParseError as
its argument. Typical usage is to return a value signifying failure to
parse this particular object and to consume some part of the input up
to the point where the next object starts.
Note that if r fails, the original error message is reported as if
without withRecovery. In no way recovering parser r can influence
error messages.
Since: megaparsec-4.4.0
Arguments
| :: m a | The parser to run |
| -> m (Either (ParseError s e) a) |
allows us to “observe” failure of the observing pp parser,
should it happen, without actually ending parsing but instead getting
the ParseError in Left. On success parsed value is returned in
Right as usual. Note that this primitive just allows you to observe
parse errors as they happen, it does not backtrack or change how the
p parser works in any way.
Since: megaparsec-5.1.0
This parser only succeeds at the end of input.
Arguments
| :: (Token s -> Maybe a) | Matching function for the token to parse |
| -> Set (ErrorItem (Token s)) | Used in the error message to mention the items that were expected |
| -> m a |
The parser accepts tokens for which the
matching function token test expectedtest returns Just results. If Nothing is
returned the expected set is used to report the items that were
expected.
For example, the satisfy parser is implemented as:
satisfy f = token testToken Set.empty
where
testToken x = if f x then Just x else NothingNote: type signature of this primitive was changed in the version 7.0.0.
Arguments
| :: (Tokens s -> Tokens s -> Bool) | Predicate to check equality of chunks |
| -> Tokens s | Chunk of input to match against |
| -> m (Tokens s) |
The parser parses a chunk of input tokens test chkchk and
returns it. The supplied predicate test is used to check equality of
given and parsed chunks after a candidate chunk of correct length is
fetched from the stream.
This can be used for example to write chunk:
chunk = tokens (==)
Note that beginning from Megaparsec 4.4.0, this is an auto-backtracking
primitive, which means that if it fails, it never consumes any input.
This is done to make its consumption model match how error messages for
this primitive are reported (which becomes an important thing as user
gets more control with primitives like withRecovery):
>>>parseTest (string "abc") "abd"1:1: unexpected "abd" expecting "abc"
This means, in particular, that it's no longer necessary to use try
with tokens-based parsers, such as string and
string'. This feature does not affect
performance in any way.
Arguments
| :: Maybe String | Name for a single token in the row |
| -> (Token s -> Bool) | Predicate to use to test tokens |
| -> m (Tokens s) | A chunk of matching tokens |
Parse zero or more tokens for which the supplied predicate holds.
Try to use this as much as possible because for many streams this
combinator is much faster than parsers built with
many and satisfy.
takeWhileP (Just "foo") f = many (satisfy f <?> "foo") takeWhileP Nothing f = many (satisfy f)
The combinator never fails, although it may parse the empty chunk.
Since: megaparsec-6.0.0
Arguments
| :: Maybe String | Name for a single token in the row |
| -> (Token s -> Bool) | Predicate to use to test tokens |
| -> m (Tokens s) | A chunk of matching tokens |
Similar to takeWhileP, but fails if it can't parse at least one
token. Try to use this as much as possible because for many streams
this combinator is much faster than parsers built with
some and satisfy.
takeWhile1P (Just "foo") f = some (satisfy f <?> "foo") takeWhile1P Nothing f = some (satisfy f)
Note that the combinator either succeeds or fails without consuming any
input, so try is not necessary with it.
Since: megaparsec-6.0.0
Arguments
| :: Maybe String | Name for a single token in the row |
| -> Int | How many tokens to extract |
| -> m (Tokens s) | A chunk of matching tokens |
Extract the specified number of tokens from the input stream and return them packed as a chunk of stream. If there is not enough tokens in the stream, a parse error will be signaled. It's guaranteed that if the parser succeeds, the requested number of tokens will be returned.
The parser is roughly equivalent to:
takeP (Just "foo") n = count n (anySingle <?> "foo") takeP Nothing n = count n anySingle
Note that if the combinator fails due to insufficient number of tokens
in the input stream, it backtracks automatically. No try is necessary
with takeP.
Since: megaparsec-6.0.0
getParserState :: m (State s e) #
Return the full parser state as a State record.
updateParserState :: (State s e -> State s e) -> m () #
applies the function updateParserState ff to the parser state.
mkParsec :: (State s e -> Reply e s a) -> m a #
An escape hatch for defining custom MonadParsec primitives. You
will need to import Text.Megaparsec.Internal in order to construct
Reply.
Since: megaparsec-9.4.0
Instances
empty :: Alternative f => f a #
The identity of <|>
(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #
An associative binary operation
some :: MonadPlus m => m a -> m [a] #
applies the parser some pp one or more times and returns a
list of the values returned by p.
word = some letter
many :: MonadPlus m => m a -> m [a] #
applies the parser many pp zero or more times and returns a
list of the values returned by p.
identifier = (:) <$> letter <*> many (alphaNumChar <|> char '_')
Arguments
| :: MonadParsec e s m | |
| => (Token s -> Bool) | Predicate to apply |
| -> m (Token s) |
The parser succeeds for any token for which the supplied
function satisfy ff returns True.
digitChar = satisfy isDigit <?> "digit" oneOf cs = satisfy (`elem` cs)
Performance note: when you need to parse a single token, it is often
a good idea to use satisfy with the right predicate function instead of
creating a complex parser using the combinators.
See also: anySingle, anySingleBut, oneOf, noneOf.
Since: megaparsec-7.0.0
choice :: (Foldable f, Alternative m) => f (m a) -> m a #
tries to apply the parsers in the list choice psps in order,
until one of them succeeds. Returns the value of the succeeding parser.
choice = asum
between :: Applicative m => m open -> m close -> m a -> m a #
parses between open close popen, followed by p and close.
Returns the value returned by p.
braces = between (symbol "{") (symbol "}")option :: Alternative m => a -> m a -> m a #
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
It is useful for modelling any computation that is allowed to fail.
Examples
Using the Alternative instance of Control.Monad.Except, the following functions:
>>>import Control.Monad.Except
>>>canFail = throwError "it failed" :: Except String Int>>>final = return 42 :: Except String Int
Can be combined by allowing the first function to fail:
>>>runExcept $ canFail *> finalLeft "it failed">>>runExcept $ optional canFail *> finalRight 42
skipMany :: MonadPlus m => m a -> m () #
applies the parser skipMany pp zero or more times, skipping
its result.
See also: manyTill, skipManyTill.
sepBy :: MonadPlus m => m a -> m sep -> m [a] #
parses zero or more occurrences of sepBy p sepp, separated by
sep. Returns a list of values returned by p.
commaSep p = p `sepBy` comma
sepBy1 :: MonadPlus m => m a -> m sep -> m [a] #
parses one or more occurrences of sepBy1 p sepp, separated by
sep. Returns a list of values returned by p.
endBy :: MonadPlus m => m a -> m sep -> m [a] #
parses zero or more occurrences of endBy p sepp, separated and
ended by sep. Returns a list of values returned by p.
cStatements = cStatement `endBy` semicolon
endBy1 :: MonadPlus m => m a -> m sep -> m [a] #
parses one or more occurrences of endBy1 p sepp, separated and
ended by sep. Returns a list of values returned by p.
manyTill :: MonadPlus m => m a -> m end -> m [a] #
applies parser manyTill p endp zero or more times until parser
end succeeds. Returns the list of values returned by p. Note that
end result is consumed and lost. Use manyTill_ if you wish to keep
it.
See also: skipMany, skipManyTill.
class (Ord (Token s), Ord (Tokens s)) => Stream s where #
Type class for inputs that can be consumed by the library.
Note that the Stream instances for Text and ByteString (strict and
lazy) default to "input sharing" (see ShareInput, NoShareInput). We plan
to move away from input sharing in a future major release; if you want to
retain the current behaviour and are concerned with maximum performance you
should consider using the ShareInput wrapper explicitly.
Note: before the version 9.0.0 the class included the methods from
VisualStream and TraversableStream.
Minimal complete definition
tokensToChunk, chunkToTokens, chunkLength, take1_, takeN_, takeWhile_
Associated Types
Type of token in the stream.
Type of “chunk” of the stream.
Methods
tokenToChunk :: Proxy s -> Token s -> Tokens s #
Lift a single token to chunk of the stream. The default implementation is:
tokenToChunk pxy = tokensToChunk pxy . pure
However for some types of stream there may be a more efficient way to lift.
tokensToChunk :: Proxy s -> [Token s] -> Tokens s #
The first method that establishes isomorphism between list of tokens and chunk of the stream. Valid implementation should satisfy:
chunkToTokens pxy (tokensToChunk pxy ts) == ts
chunkToTokens :: Proxy s -> Tokens s -> [Token s] #
The second method that establishes isomorphism between list of tokens and chunk of the stream. Valid implementation should satisfy:
tokensToChunk pxy (chunkToTokens pxy chunk) == chunk
chunkLength :: Proxy s -> Tokens s -> Int #
Return length of a chunk of the stream.
chunkEmpty :: Proxy s -> Tokens s -> Bool #
Check if a chunk of the stream is empty. The default implementation
is in terms of the more general chunkLength:
chunkEmpty pxy ts = chunkLength pxy ts <= 0
However for many streams there may be a more efficient implementation.
take1_ :: s -> Maybe (Token s, s) #
Extract a single token form the stream. Return Nothing if the
stream is empty.
takeN_ :: Int -> s -> Maybe (Tokens s, s) #
should try to extract a chunk of length takeN_ n sn, or if the
stream is too short, the rest of the stream. Valid implementation
should follow the rules:
- If the requested length
nis 0 (or less),Nothingshould never be returned, insteadshould be returned, whereJust("", s)""stands for the empty chunk, andsis the original stream (second argument). - If the requested length is greater than 0 and the stream is
empty,
Nothingshould be returned indicating end of input. - In other cases, take chunk of length
n(or shorter if the stream is not long enough) from the input stream and return the chunk along with the rest of the stream.
takeWhile_ :: (Token s -> Bool) -> s -> (Tokens s, s) #
Extract chunk of the stream taking tokens while the supplied
predicate returns True. Return the chunk and the rest of the stream.
For many types of streams, the method allows for significant performance improvements, although it is not strictly necessary from conceptual point of view.
Instances
The data type SourcePos represents source positions. It contains the
name of the source file, a line number, and a column number. Source line
and column positions change intensively during parsing, so we need to
make them strict to avoid memory leaks.
Constructors
| SourcePos | |
Fields
| |
Instances
| Data SourcePos | |||||
Defined in Text.Megaparsec.Pos Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourcePos -> c SourcePos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourcePos # toConstr :: SourcePos -> Constr # dataTypeOf :: SourcePos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourcePos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos) # gmapT :: (forall b. Data b => b -> b) -> SourcePos -> SourcePos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r # gmapQ :: (forall d. Data d => d -> u) -> SourcePos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourcePos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # | |||||
| Generic SourcePos | |||||
Defined in Text.Megaparsec.Pos Associated Types
| |||||
| Read SourcePos | |||||
| Show SourcePos | |||||
| NFData SourcePos | |||||
Defined in Text.Megaparsec.Pos | |||||
| Eq SourcePos | |||||
| Ord SourcePos | |||||
| type Rep SourcePos | |||||
Defined in Text.Megaparsec.Pos type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos)))) | |||||
Arguments
| :: MonadParsec e s m | |
| => Tokens s | Chunk to match |
| -> m (Tokens s) |
This is the Megaparsec's state parametrized over stream type s and
custom error component type e.
Constructors
| State | |
Fields
| |
Instances
| (Data e, Data (ParseError s e), Data s) => Data (State s e) | |||||
Defined in Text.Megaparsec.State Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> State s e -> c (State s e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (State s e) # toConstr :: State s e -> Constr # dataTypeOf :: State s e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (State s e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (State s e)) # gmapT :: (forall b. Data b => b -> b) -> State s e -> State s e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> State s e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> State s e -> r # gmapQ :: (forall d. Data d => d -> u) -> State s e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> State s e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> State s e -> m (State s e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> State s e -> m (State s e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> State s e -> m (State s e) # | |||||
| Generic (State s e) | |||||
Defined in Text.Megaparsec.State Associated Types
| |||||
| (Show (ParseError s e), Show s) => Show (State s e) | |||||
| (NFData s, NFData (ParseError s e)) => NFData (State s e) | |||||
Defined in Text.Megaparsec.State | |||||
| (Eq (ParseError s e), Eq s) => Eq (State s e) | |||||
| type Rep (State s e) | |||||
Defined in Text.Megaparsec.State type Rep (State s e) = D1 ('MetaData "State" "Text.Megaparsec.State" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'False) (C1 ('MetaCons "State" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stateInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s) :*: S1 ('MetaSel ('Just "stateOffset") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "statePosState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PosState s)) :*: S1 ('MetaSel ('Just "stateParseErrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ParseError s e])))) | |||||
match :: MonadParsec e s m => m a -> m (Tokens s, a) #
Return both the result of a parse and a chunk of input that was
consumed during parsing. This relies on the change of the stateOffset
value to evaluate how many tokens were consumed. If you mess with it
manually in the argument parser, prepare for troubles.
Since: megaparsec-5.3.0
customFailure :: MonadParsec e s m => e -> m a #
Report a custom parse error. For a more general version, see
fancyFailure.
customFailure = fancyFailure . Set.singleton . ErrorCustom
Since: megaparsec-6.3.0
newtype InvalidPosException #
The exception is thrown by mkPos when its argument is not a positive
number.
Since: megaparsec-5.0.0
Constructors
| InvalidPosException Int | Contains the actual value that was passed to |
Instances
| Data InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InvalidPosException -> c InvalidPosException # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InvalidPosException # toConstr :: InvalidPosException -> Constr # dataTypeOf :: InvalidPosException -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InvalidPosException) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InvalidPosException) # gmapT :: (forall b. Data b => b -> b) -> InvalidPosException -> InvalidPosException # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InvalidPosException -> r # gmapQ :: (forall d. Data d => d -> u) -> InvalidPosException -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InvalidPosException -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InvalidPosException -> m InvalidPosException # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InvalidPosException -> m InvalidPosException # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InvalidPosException -> m InvalidPosException # | |||||
| Exception InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Methods toException :: InvalidPosException -> SomeException # fromException :: SomeException -> Maybe InvalidPosException # | |||||
| Generic InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Associated Types
Methods from :: InvalidPosException -> Rep InvalidPosException x # to :: Rep InvalidPosException x -> InvalidPosException # | |||||
| Show InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Methods showsPrec :: Int -> InvalidPosException -> ShowS # show :: InvalidPosException -> String # showList :: [InvalidPosException] -> ShowS # | |||||
| NFData InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Methods rnf :: InvalidPosException -> () # | |||||
| Eq InvalidPosException | |||||
Defined in Text.Megaparsec.Pos Methods (==) :: InvalidPosException -> InvalidPosException -> Bool # (/=) :: InvalidPosException -> InvalidPosException -> Bool # | |||||
| type Rep InvalidPosException | |||||
Defined in Text.Megaparsec.Pos type Rep InvalidPosException = D1 ('MetaData "InvalidPosException" "Text.Megaparsec.Pos" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'True) (C1 ('MetaCons "InvalidPosException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) | |||||
Pos is the type for positive integers. This is used to represent line
number, column number, and similar things like indentation level.
Semigroup instance can be used to safely and efficiently add Poses
together.
Since: megaparsec-5.0.0
Instances
| Data Pos | |||||
Defined in Text.Megaparsec.Pos Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pos -> c Pos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pos # dataTypeOf :: Pos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos) # gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r # gmapQ :: (forall d. Data d => d -> u) -> Pos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pos -> m Pos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos # | |||||
| Semigroup Pos | |||||
| Generic Pos | |||||
Defined in Text.Megaparsec.Pos Associated Types
| |||||
| Read Pos | |||||
| Show Pos | |||||
| NFData Pos | |||||
Defined in Text.Megaparsec.Pos | |||||
| Eq Pos | |||||
| Ord Pos | |||||
| type Rep Pos | |||||
Defined in Text.Megaparsec.Pos | |||||
Construction of Pos from Int. The function throws
InvalidPosException when given a non-positive argument.
Since: megaparsec-6.0.0
defaultTabWidth :: Pos #
Value of tab width used by default. Always prefer this constant when you want to refer to the default tab width because actual value may change in future.
Currently:
defaultTabWidth = mkPos 8
Since: megaparsec-5.0.0
initialPos :: FilePath -> SourcePos #
Construct initial position (line 1, column 1) given name of source file.
sourcePosPretty :: SourcePos -> String #
Pretty-print a SourcePos.
Since: megaparsec-5.0.0
data ParseError s e #
represents a parse error parametrized over the
stream type ParseError s es and the custom data e.
Semigroup and Monoid instances of the data type allow us to merge
parse errors from different branches of parsing. When merging two
ParseErrors, the longest match is preferred; if positions are the same,
custom data sets and collections of message items are combined. Note that
fancy errors take precedence over trivial errors in merging.
Since: megaparsec-7.0.0
Constructors
| TrivialError Int (Maybe (ErrorItem (Token s))) (Set (ErrorItem (Token s))) | Trivial errors, generated by the Megaparsec's machinery. The data constructor includes the offset of error, unexpected token (if any), and expected tokens. Type of the first argument was changed in the version 7.0.0. |
| FancyError Int (Set (ErrorFancy e)) | Fancy, custom errors. Type of the first argument was changed in the version 7.0.0. |
Instances
| (Data s, Data (Token s), Ord (Token s), Data e, Ord e) => Data (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseError s e -> c (ParseError s e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParseError s e) # toConstr :: ParseError s e -> Constr # dataTypeOf :: ParseError s e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParseError s e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (ParseError s e)) # gmapT :: (forall b. Data b => b -> b) -> ParseError s e -> ParseError s e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseError s e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseError s e -> r # gmapQ :: (forall d. Data d => d -> u) -> ParseError s e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseError s e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseError s e -> m (ParseError s e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseError s e -> m (ParseError s e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseError s e -> m (ParseError s e) # | |||||
| (Stream s, Ord e) => Monoid (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Methods mempty :: ParseError s e # mappend :: ParseError s e -> ParseError s e -> ParseError s e # mconcat :: [ParseError s e] -> ParseError s e # | |||||
| (Stream s, Ord e) => Semigroup (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Methods (<>) :: ParseError s e -> ParseError s e -> ParseError s e # sconcat :: NonEmpty (ParseError s e) -> ParseError s e # stimes :: Integral b => b -> ParseError s e -> ParseError s e # | |||||
| (Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, Typeable s, Typeable e) => Exception (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Methods toException :: ParseError s e -> SomeException # fromException :: SomeException -> Maybe (ParseError s e) # displayException :: ParseError s e -> String # | |||||
| Generic (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Associated Types
Methods from :: ParseError s e -> Rep (ParseError s e) x # to :: Rep (ParseError s e) x -> ParseError s e # | |||||
| (Show (Token s), Show e) => Show (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Methods showsPrec :: Int -> ParseError s e -> ShowS # show :: ParseError s e -> String # showList :: [ParseError s e] -> ShowS # | |||||
| (NFData (Token s), NFData e) => NFData (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Methods rnf :: ParseError s e -> () # | |||||
| (Eq (Token s), Eq e) => Eq (ParseError s e) | |||||
Defined in Text.Megaparsec.Error Methods (==) :: ParseError s e -> ParseError s e -> Bool # (/=) :: ParseError s e -> ParseError s e -> Bool # | |||||
| type Rep (ParseError s e) | |||||
Defined in Text.Megaparsec.Error type Rep (ParseError s e) = D1 ('MetaData "ParseError" "Text.Megaparsec.Error" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'False) (C1 ('MetaCons "TrivialError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ErrorItem (Token s)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (ErrorItem (Token s)))))) :+: C1 ('MetaCons "FancyError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (ErrorFancy e))))) | |||||
A special kind of state that is used to calculate line/column positions on demand.
Since: megaparsec-7.0.0
Constructors
| PosState | |
Fields
| |
Instances
| Data s => Data (PosState s) | |||||
Defined in Text.Megaparsec.State Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosState s -> c (PosState s) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PosState s) # toConstr :: PosState s -> Constr # dataTypeOf :: PosState s -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PosState s)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PosState s)) # gmapT :: (forall b. Data b => b -> b) -> PosState s -> PosState s # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosState s -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosState s -> r # gmapQ :: (forall d. Data d => d -> u) -> PosState s -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PosState s -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosState s -> m (PosState s) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosState s -> m (PosState s) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosState s -> m (PosState s) # | |||||
| Generic (PosState s) | |||||
Defined in Text.Megaparsec.State Associated Types
| |||||
| Show s => Show (PosState s) | |||||
| NFData s => NFData (PosState s) | |||||
Defined in Text.Megaparsec.State | |||||
| Eq s => Eq (PosState s) | |||||
| type Rep (PosState s) | |||||
Defined in Text.Megaparsec.State type Rep (PosState s) = D1 ('MetaData "PosState" "Text.Megaparsec.State" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'False) (C1 ('MetaCons "PosState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pstateInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s) :*: S1 ('MetaSel ('Just "pstateOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "pstateSourcePos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "pstateTabWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pos) :*: S1 ('MetaSel ('Just "pstateLinePrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) | |||||
class Stream s => TraversableStream s where #
Type class for inputs that can also be used for error reporting.
Since: megaparsec-9.0.0
Minimal complete definition
Methods
Arguments
| :: Int | Offset to reach |
| -> PosState s | Initial |
| -> (Maybe String, PosState s) | See the description of the function |
Given an offset o and initial PosState, adjust the state in such
a way that it starts at the offset.
Return two values (in order):
MaybeStringrepresenting the line on which the given offsetois located. It can be omitted (i.e.Nothing); in that case error reporting functions will not show offending lines. If returned, the line should satisfy a number of conditions that are described below.- The updated
PosStatewhich can be in turn used to locate another offseto'given thato' >= o.
The String representing the offending line in input stream should
satisfy the following:
- It should adequately represent location of token at the offset of
interest, that is, character at
sourceColumnof the returnedSourcePosshould correspond to the token at the offseto. - It should not include the newline at the end.
- It should not be empty, if the line happens to be empty, it
should be replaced with the string
"<empty line>". - Tab characters should be replaced by appropriate number of
spaces, which is determined by the
pstateTabWidthfield ofPosState.
Note: type signature of the function was changed in the version 9.0.0.
Since: megaparsec-7.0.0
Arguments
| :: Int | Offset to reach |
| -> PosState s | Initial |
| -> PosState s | Reached source position and updated state |
A version of reachOffset that may be faster because it doesn't need
to fetch the line at which the given offset in located.
The default implementation is this:
reachOffsetNoLine o pst = snd (reachOffset o pst)
Note: type signature of the function was changed in the version 8.0.0.
Since: megaparsec-7.0.0
Instances
| TraversableStream ByteString | |
Defined in Text.Megaparsec.Stream Methods reachOffset :: Int -> PosState ByteString -> (Maybe String, PosState ByteString) # reachOffsetNoLine :: Int -> PosState ByteString -> PosState ByteString # | |
| TraversableStream ByteString | |
Defined in Text.Megaparsec.Stream Methods reachOffset :: Int -> PosState ByteString -> (Maybe String, PosState ByteString) # reachOffsetNoLine :: Int -> PosState ByteString -> PosState ByteString # | |
| TraversableStream Text | |
| TraversableStream Text | |
| TraversableStream String | |
class Stream s => VisualStream s where #
Type class for inputs that can also be used for debugging.
Since: megaparsec-9.0.0
Minimal complete definition
Methods
showTokens :: Proxy s -> NonEmpty (Token s) -> String #
Pretty-print non-empty stream of tokens. This function is also used to print single tokens (represented as singleton lists).
Since: megaparsec-7.0.0
tokensLength :: Proxy s -> NonEmpty (Token s) -> Int #
Return the number of characters that a non-empty stream of tokens spans. The default implementation is sufficient if every token spans exactly 1 character.
Since: megaparsec-8.0.0
Instances
| VisualStream ByteString | |
Defined in Text.Megaparsec.Stream Methods showTokens :: Proxy ByteString -> NonEmpty (Token ByteString) -> String # tokensLength :: Proxy ByteString -> NonEmpty (Token ByteString) -> Int # | |
| VisualStream ByteString | |
Defined in Text.Megaparsec.Stream Methods showTokens :: Proxy ByteString -> NonEmpty (Token ByteString) -> String # tokensLength :: Proxy ByteString -> NonEmpty (Token ByteString) -> Int # | |
| VisualStream Text | |
| VisualStream Text | |
| VisualStream String | |
newtype NoShareInput a #
This wrapper selects the no-input-sharing Stream implementation for
Text (Text) and ByteString (ByteString). This means
that our parsers will create independent copies rather than using slices
of the input. See also the documentation of copy.
More importantly, any parser output will be independent of the input, and holding on to parts of the output will never prevent the input from being garbage collected.
For maximum performance you might consider using ShareInput instead,
but beware of its pitfalls!
Since: megaparsec-9.3.0
Constructors
| NoShareInput | |
Fields
| |
Instances
newtype ShareInput a #
This wrapper selects the input-sharing Stream implementation for
Text (Text) and ByteString (ByteString). By input
sharing we mean that our parsers will use slices whenever possible to
avoid having to copy parts of the input. See also the documentation of
split.
Note that using slices is in general faster than copying; on the other
hand it also has the potential for causing surprising memory leaks: if
any slice of the input survives in the output, holding on to the output
will force the entire input Text/ByteString to stay in memory!
Even when using lazy Text/ByteString we will hold on to whole
chunks at a time leading to to significantly worse memory residency in
some cases.
See NoShareInput for a somewhat slower implementation that avoids this
memory leak scenario.
Since: megaparsec-9.3.0
Constructors
| ShareInput | |
Fields
| |
Instances
Type of token in the stream.
Instances
| type Token ByteString | |
Defined in Text.Megaparsec.Stream | |
| type Token ByteString | |
Defined in Text.Megaparsec.Stream | |
| type Token Text | |
Defined in Text.Megaparsec.Stream | |
| type Token Text | |
Defined in Text.Megaparsec.Stream | |
| type Token (Seq a) | |
Defined in Text.Megaparsec.Stream | |
| type Token (NoShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Token (NoShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Token (NoShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Token (NoShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Token (ShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Token (ShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Token (ShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Token (ShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Token [a] | |
Defined in Text.Megaparsec.Stream type Token [a] = a | |
Type of “chunk” of the stream.
Instances
| type Tokens ByteString | |
Defined in Text.Megaparsec.Stream | |
| type Tokens ByteString | |
Defined in Text.Megaparsec.Stream | |
| type Tokens Text | |
Defined in Text.Megaparsec.Stream | |
| type Tokens Text | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (Seq a) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (NoShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (NoShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (NoShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (NoShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (ShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (ShareInput ByteString) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (ShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens (ShareInput Text) | |
Defined in Text.Megaparsec.Stream | |
| type Tokens [a] | |
Defined in Text.Megaparsec.Stream type Tokens [a] = [a] | |
A data type that is used to represent “unexpected/expected” items in
ParseError. It is parametrized over the token type t.
Since: megaparsec-5.0.0
Constructors
| Tokens (NonEmpty t) | Non-empty stream of tokens |
| Label (NonEmpty Char) | Label (cannot be empty) |
| EndOfInput | End of input |
Instances
| Functor ErrorItem | |||||
| Data t => Data (ErrorItem t) | |||||
Defined in Text.Megaparsec.Error Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorItem t -> c (ErrorItem t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ErrorItem t) # toConstr :: ErrorItem t -> Constr # dataTypeOf :: ErrorItem t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (ErrorItem t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (ErrorItem t)) # gmapT :: (forall b. Data b => b -> b) -> ErrorItem t -> ErrorItem t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorItem t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorItem t -> r # gmapQ :: (forall d. Data d => d -> u) -> ErrorItem t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorItem t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # | |||||
| Generic (ErrorItem t) | |||||
Defined in Text.Megaparsec.Error Associated Types
| |||||
| Read t => Read (ErrorItem t) | |||||
| Show t => Show (ErrorItem t) | |||||
| NFData t => NFData (ErrorItem t) | |||||
Defined in Text.Megaparsec.Error | |||||
| Eq t => Eq (ErrorItem t) | |||||
| Ord t => Ord (ErrorItem t) | |||||
Defined in Text.Megaparsec.Error | |||||
| type Rep (ErrorItem t) | |||||
Defined in Text.Megaparsec.Error type Rep (ErrorItem t) = D1 ('MetaData "ErrorItem" "Text.Megaparsec.Error" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'False) (C1 ('MetaCons "Tokens" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty t))) :+: (C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Char))) :+: C1 ('MetaCons "EndOfInput" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
class Ord a => ShowErrorComponent a where #
The type class defines how to print a custom component of ParseError.
Since: megaparsec-5.0.0
Minimal complete definition
Methods
showErrorComponent :: a -> String #
Pretty-print a component of ParseError.
errorComponentLen :: a -> Int #
Length of the error component in characters, used for highlighting of parse errors in input string.
Since: megaparsec-7.0.0
Instances
| ShowErrorComponent Void | |
Defined in Text.Megaparsec.Error | |
data ParseErrorBundle s e #
A non-empty collection of ParseErrors equipped with PosState that
allows us to pretty-print the errors efficiently and correctly.
Since: megaparsec-7.0.0
Constructors
| ParseErrorBundle | |
Fields
| |
Instances
| (Data s, Data (Token s), Ord (Token s), Data e, Ord e) => Data (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseErrorBundle s e -> c (ParseErrorBundle s e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParseErrorBundle s e) # toConstr :: ParseErrorBundle s e -> Constr # dataTypeOf :: ParseErrorBundle s e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParseErrorBundle s e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (ParseErrorBundle s e)) # gmapT :: (forall b. Data b => b -> b) -> ParseErrorBundle s e -> ParseErrorBundle s e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r # gmapQ :: (forall d. Data d => d -> u) -> ParseErrorBundle s e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseErrorBundle s e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) # | |||||
| (Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, TraversableStream s, Typeable s, Typeable e) => Exception (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Methods toException :: ParseErrorBundle s e -> SomeException # fromException :: SomeException -> Maybe (ParseErrorBundle s e) # displayException :: ParseErrorBundle s e -> String # | |||||
| Generic (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Associated Types
Methods from :: ParseErrorBundle s e -> Rep (ParseErrorBundle s e) x # to :: Rep (ParseErrorBundle s e) x -> ParseErrorBundle s e # | |||||
| (Show s, Show (Token s), Show e) => Show (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Methods showsPrec :: Int -> ParseErrorBundle s e -> ShowS # show :: ParseErrorBundle s e -> String # showList :: [ParseErrorBundle s e] -> ShowS # | |||||
| (NFData s, NFData (Token s), NFData e) => NFData (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Methods rnf :: ParseErrorBundle s e -> () # | |||||
| (Eq s, Eq (Token s), Eq e) => Eq (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error Methods (==) :: ParseErrorBundle s e -> ParseErrorBundle s e -> Bool # (/=) :: ParseErrorBundle s e -> ParseErrorBundle s e -> Bool # | |||||
| type Rep (ParseErrorBundle s e) | |||||
Defined in Text.Megaparsec.Error type Rep (ParseErrorBundle s e) = D1 ('MetaData "ParseErrorBundle" "Text.Megaparsec.Error" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'False) (C1 ('MetaCons "ParseErrorBundle" 'PrefixI 'True) (S1 ('MetaSel ('Just "bundleErrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (ParseError s e))) :*: S1 ('MetaSel ('Just "bundlePosState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PosState s)))) | |||||
data ErrorFancy e #
Additional error data, extendable by user. When no custom data is
necessary, the type is typically indexed by Void to “cancel” the
ErrorCustom constructor.
Since: megaparsec-6.0.0
Constructors
| ErrorFail String |
|
| ErrorIndentation Ordering Pos Pos | Incorrect indentation error: desired ordering between reference level and actual level, reference indentation level, actual indentation level |
| ErrorCustom e | Custom error data |
Instances
| Functor ErrorFancy | |||||
Defined in Text.Megaparsec.Error Methods fmap :: (a -> b) -> ErrorFancy a -> ErrorFancy b # (<$) :: a -> ErrorFancy b -> ErrorFancy a # | |||||
| Data e => Data (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorFancy e -> c (ErrorFancy e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ErrorFancy e) # toConstr :: ErrorFancy e -> Constr # dataTypeOf :: ErrorFancy e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ErrorFancy e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (ErrorFancy e)) # gmapT :: (forall b. Data b => b -> b) -> ErrorFancy e -> ErrorFancy e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorFancy e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorFancy e -> r # gmapQ :: (forall d. Data d => d -> u) -> ErrorFancy e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorFancy e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorFancy e -> m (ErrorFancy e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorFancy e -> m (ErrorFancy e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorFancy e -> m (ErrorFancy e) # | |||||
| Generic (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error Associated Types
| |||||
| Read e => Read (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error Methods readsPrec :: Int -> ReadS (ErrorFancy e) # readList :: ReadS [ErrorFancy e] # readPrec :: ReadPrec (ErrorFancy e) # readListPrec :: ReadPrec [ErrorFancy e] # | |||||
| Show e => Show (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error Methods showsPrec :: Int -> ErrorFancy e -> ShowS # show :: ErrorFancy e -> String # showList :: [ErrorFancy e] -> ShowS # | |||||
| NFData a => NFData (ErrorFancy a) | |||||
Defined in Text.Megaparsec.Error Methods rnf :: ErrorFancy a -> () # | |||||
| Eq e => Eq (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error | |||||
| Ord e => Ord (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error Methods compare :: ErrorFancy e -> ErrorFancy e -> Ordering # (<) :: ErrorFancy e -> ErrorFancy e -> Bool # (<=) :: ErrorFancy e -> ErrorFancy e -> Bool # (>) :: ErrorFancy e -> ErrorFancy e -> Bool # (>=) :: ErrorFancy e -> ErrorFancy e -> Bool # max :: ErrorFancy e -> ErrorFancy e -> ErrorFancy e # min :: ErrorFancy e -> ErrorFancy e -> ErrorFancy e # | |||||
| type Rep (ErrorFancy e) | |||||
Defined in Text.Megaparsec.Error type Rep (ErrorFancy e) = D1 ('MetaData "ErrorFancy" "Text.Megaparsec.Error" "megaparsec-9.7.0-AZVb3OSPdl4TChiinRysA" 'False) (C1 ('MetaCons "ErrorFail" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "ErrorIndentation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ordering) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pos) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pos))) :+: C1 ('MetaCons "ErrorCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) | |||||
mapParseError :: Ord e' => (e -> e') -> ParseError s e -> ParseError s e' #
errorOffset :: ParseError s e -> Int #
Get the offset of a ParseError.
Since: megaparsec-7.0.0
setErrorOffset :: Int -> ParseError s e -> ParseError s e #
Set the offset of a ParseError.
Since: megaparsec-8.0.0
Arguments
| :: (Traversable t, TraversableStream s) | |
| => (a -> Int) | How to project offset from an item (e.g. |
| -> t a | The collection of items |
| -> PosState s | Initial |
| -> (t (a, SourcePos), PosState s) | The collection with |
Attach SourcePoses to items in a Traversable container given that
there is a projection allowing us to get an offset per item.
Items must be in ascending order with respect to their offsets.
Since: megaparsec-7.0.0
Arguments
| :: (VisualStream s, TraversableStream s) | |
| => (Maybe String -> SourcePos -> ParseError s e -> String) | Format function for a single |
| -> ParseErrorBundle s e | Parse error bundle to display |
| -> String | Textual rendition of the bundle |
Pretty-print a ParseErrorBundle. All ParseErrors in the bundle will
be pretty-printed in order, by applying a provided format function, with
a single pass over the input stream.
Since: megaparsec-9.7.0
errorBundlePrettyForGhcPreProcessors #
Arguments
| :: (VisualStream s, TraversableStream s, ShowErrorComponent e) | |
| => ParseErrorBundle s e | Parse error bundle to display |
| -> String | Textual rendition of the bundle |
Pretty-print a ParseErrorBundle. All ParseErrors in the bundle will
be pretty-printed in order by doing a single pass over the input stream.
The rendered format is suitable for custom GHC pre-processors (as can be specified with -F -pgmF).
Since: megaparsec-9.7.0
Arguments
| :: (VisualStream s, ShowErrorComponent e) | |
| => ParseError s e | Parse error to render |
| -> String | Result of rendering |
Pretty-print a ParseError. The rendered String always ends with a
newline.
Since: megaparsec-5.0.0
Arguments
| :: (VisualStream s, ShowErrorComponent e) | |
| => ParseError s e | Parse error to render |
| -> String | Result of rendering |
Pretty-print a textual part of a ParseError, that is, everything
except for its position. The rendered String always ends with a
newline.
Since: megaparsec-5.1.0
showErrorItem :: VisualStream s => Proxy s -> ErrorItem (Token s) -> String #
Pretty-print an ErrorItem.
Since: megaparsec-9.4.0
data ParsecT e s (m :: Type -> Type) a #
is a parser with custom data component of error
ParsecT e s m ae, stream type s, underlying monad m and return type a.
Instances
| (Ord e, Stream s) => MonadParsec e s (ParsecT e s m) | |
Defined in Text.Megaparsec.Internal Methods parseError :: ParseError s e -> ParsecT e s m a # label :: String -> ParsecT e s m a -> ParsecT e s m a # hidden :: ParsecT e s m a -> ParsecT e s m a # try :: ParsecT e s m a -> ParsecT e s m a # lookAhead :: ParsecT e s m a -> ParsecT e s m a # notFollowedBy :: ParsecT e s m a -> ParsecT e s m () # withRecovery :: (ParseError s e -> ParsecT e s m a) -> ParsecT e s m a -> ParsecT e s m a # observing :: ParsecT e s m a -> ParsecT e s m (Either (ParseError s e) a) # token :: (Token s -> Maybe a) -> Set (ErrorItem (Token s)) -> ParsecT e s m a # tokens :: (Tokens s -> Tokens s -> Bool) -> Tokens s -> ParsecT e s m (Tokens s) # takeWhileP :: Maybe String -> (Token s -> Bool) -> ParsecT e s m (Tokens s) # takeWhile1P :: Maybe String -> (Token s -> Bool) -> ParsecT e s m (Tokens s) # takeP :: Maybe String -> Int -> ParsecT e s m (Tokens s) # getParserState :: ParsecT e s m (State s e) # updateParserState :: (State s e -> State s e) -> ParsecT e s m () # | |
| (VisualStream s, ShowErrorComponent e) => MonadParsecDbg e s (ParsecT e s m) | |
| (Stream s, MonadError e' m) => MonadError e' (ParsecT e s m) | |
Defined in Text.Megaparsec.Internal Methods throwError :: e' -> ParsecT e s m a # catchError :: ParsecT e s m a -> (e' -> ParsecT e s m a) -> ParsecT e s m a # | |
| (Stream s, MonadReader r m) => MonadReader r (ParsecT e s m) | |
| (Stream s, MonadState st m) => MonadState st (ParsecT e s m) | |
| (Stream s, MonadWriter w m) => MonadWriter w (ParsecT e s m) | Since: megaparsec-9.5.0 |
| Stream s => MonadTrans (ParsecT e s) | |
Defined in Text.Megaparsec.Internal | |
| Stream s => MonadFail (ParsecT e s m) | |
Defined in Text.Megaparsec.Internal | |
| (Stream s, MonadFix m) => MonadFix (ParsecT e s m) | Since: megaparsec-6.0.0 |
Defined in Text.Megaparsec.Internal | |
| (Stream s, MonadIO m) => MonadIO (ParsecT e s m) | |
Defined in Text.Megaparsec.Internal | |
| (Ord e, Stream s) => Alternative (ParsecT e s m) |
|
| Stream s => Applicative (ParsecT e s m) |
|
Defined in Text.Megaparsec.Internal Methods pure :: a -> ParsecT e s m a # (<*>) :: ParsecT e s m (a -> b) -> ParsecT e s m a -> ParsecT e s m b # liftA2 :: (a -> b -> c) -> ParsecT e s m a -> ParsecT e s m b -> ParsecT e s m c # (*>) :: ParsecT e s m a -> ParsecT e s m b -> ParsecT e s m b # (<*) :: ParsecT e s m a -> ParsecT e s m b -> ParsecT e s m a # | |
| Functor (ParsecT e s m) | |
| Stream s => Monad (ParsecT e s m) |
|
| (Ord e, Stream s) => MonadPlus (ParsecT e s m) |
Note: strictly speaking, this instance is unlawful. The right identity law does not hold, e.g. in general this is not true: v >> mzero = mzero However the following holds: try v >> mzero = mzero |
| (Stream s, MonadCont m) => MonadCont (ParsecT e s m) | |
| (a ~ Tokens s, IsString a, Eq a, Stream s, Ord e) => IsString (ParsecT e s m a) | Since: megaparsec-6.3.0 |
Defined in Text.Megaparsec.Internal Methods fromString :: String -> ParsecT e s m a # | |
| (Stream s, Monoid a) => Monoid (ParsecT e s m a) | Since: megaparsec-5.3.0 |
| (Stream s, Semigroup a) => Semigroup (ParsecT e s m a) | Since: megaparsec-5.3.0 |
Arguments
| :: Parsec e s a | Parser to run |
| -> String | Name of source file |
| -> s | Input for parser |
| -> Either (ParseErrorBundle s e) a |
runs parser parse p file inputp over Identity (see
runParserT if you're using the ParsecT monad transformer; parse
itself is just a synonym for runParser). It returns either a
ParseErrorBundle (Left) or a value of type a (Right).
errorBundlePretty can be used to turn ParseErrorBundle into the
string representation of the error message. See Text.Megaparsec.Error
if you need to do more advanced error analysis.
main = case parse numbers "" "11,2,43" of
Left bundle -> putStr (errorBundlePretty bundle)
Right xs -> print (sum xs)
numbers = decimal `sepBy` char ','parseMaybe :: (Ord e, Stream s) => Parsec e s a -> s -> Maybe a #
runs the parser parseMaybe p inputp on input and returns the
result inside Just on success and Nothing on failure. This function
also parses eof, so if the parser doesn't consume all of its input, it
will fail.
The function is supposed to be useful for lightweight parsing, where error messages (and thus file names) are not important and entire input should be consumed. For example, it can be used for parsing of a single number according to a specification of its format.
Arguments
| :: (ShowErrorComponent e, Show a, VisualStream s, TraversableStream s) | |
| => Parsec e s a | Parser to run |
| -> s | Input for parser |
| -> IO () |
The expression applies the parser parseTest p inputp on the
input input and prints the result to stdout. Useful for testing.
Arguments
| :: Parsec e s a | Parser to run |
| -> String | Name of source file |
| -> s | Input for parser |
| -> Either (ParseErrorBundle s e) a |
runs parser runParser p file inputp on the input stream of
tokens input, obtained from source file. The file is only used in
error messages and may be the empty string. Returns either a
ParseErrorBundle (Left) or a value of type a (Right).
parseFromFile p file = runParser p file <$> readFile file
Arguments
| :: Parsec e s a | Parser to run |
| -> State s e | Initial state |
| -> (State s e, Either (ParseErrorBundle s e) a) |
Arguments
| :: Monad m | |
| => ParsecT e s m a | Parser to run |
| -> String | Name of source file |
| -> s | Input for parser |
| -> m (Either (ParseErrorBundle s e) a) |
runs parser runParserT p file inputp on the input list of tokens
input, obtained from source file. The file is only used in error
messages and may be the empty string. Returns a computation in the
underlying monad m that returns either a ParseErrorBundle (Left) or
a value of type a (Right).
Arguments
| :: Monad m | |
| => ParsecT e s m a | Parser to run |
| -> State s e | Initial state |
| -> m (State s e, Either (ParseErrorBundle s e) a) |
This function is similar to runParserT, but like runParser' it
accepts and returns parser state. This is thus the most general way to
run a parser.
Since: megaparsec-4.2.0
Arguments
| :: MonadParsec e s m | |
| => Maybe (ErrorItem (Token s)) | Unexpected item (if any) |
| -> Set (ErrorItem (Token s)) | Expected items |
| -> m a |
Stop parsing and report a trivial ParseError.
Since: megaparsec-6.0.0
Arguments
| :: MonadParsec e s m | |
| => Set (ErrorFancy e) | Fancy error components |
| -> m a |
Stop parsing and report a fancy ParseError. To report a single custom
parse error, see customFailure.
Since: megaparsec-6.0.0
unexpected :: MonadParsec e s m => ErrorItem (Token s) -> m a #
The parser fails with an error message telling
about unexpected item unexpected itemitem without consuming any input.
unexpected item = failure (Just item) Set.empty
Arguments
| :: MonadParsec e s m | |
| => (ParseError s e -> ParseError s e) | How to process |
| -> m a | The “region” that the processing applies to |
| -> m a |
Specify how to process ParseErrors that happen inside of this
wrapper. This applies to both normal and delayed ParseErrors.
As a side-effect of the implementation the inner computation will start
with an empty collection of delayed errors and they will be updated and
“restored” on the way out of region.
Since: megaparsec-5.3.0
registerParseError :: MonadParsec e s m => ParseError s e -> m () #
Register a ParseError for later reporting. This action does not end
parsing and has no effect except for adding the given ParseError to the
collection of “delayed” ParseErrors which will be taken into
consideration at the end of parsing. Only if this collection is empty the
parser will succeed. This is the main way to report several parse errors
at once.
Since: megaparsec-8.0.0
Arguments
| :: MonadParsec e s m | |
| => Maybe (ErrorItem (Token s)) | Unexpected item (if any) |
| -> Set (ErrorItem (Token s)) | Expected items |
| -> m () |
Like failure, but for delayed ParseErrors.
Since: megaparsec-8.0.0
Arguments
| :: MonadParsec e s m | |
| => Set (ErrorFancy e) | Fancy error components |
| -> m () |
Like fancyFailure, but for delayed ParseErrors.
Since: megaparsec-8.0.0
Arguments
| :: MonadParsec e s m | |
| => Token s | Token to match |
| -> m (Token s) |
anySingle :: MonadParsec e s m => m (Token s) #
Parse and return a single token. It's a good idea to attach a label
to this parser.
anySingle = satisfy (const True)
See also: satisfy, anySingleBut.
Since: megaparsec-7.0.0
Arguments
| :: MonadParsec e s m | |
| => Token s | Token we should not match |
| -> m (Token s) |
Arguments
| :: (Foldable f, MonadParsec e s m) | |
| => f (Token s) | Collection of matching tokens |
| -> m (Token s) |
succeeds if the current token is in the supplied
collection of tokens oneOf tsts. Returns the parsed token. Note that this
parser cannot automatically generate the “expected” component of error
message, so usually you should label it manually with label or (<?>).
oneOf cs = satisfy (`elem` cs)
See also: satisfy.
digit = oneOf ['0'..'9'] <?> "digit"
Performance note: prefer satisfy when you can because it's faster
when you have only a couple of tokens to compare to:
quoteFast = satisfy (\x -> x == '\'' || x == '\"') quoteSlow = oneOf "'\""
Since: megaparsec-7.0.0
Arguments
| :: (Foldable f, MonadParsec e s m) | |
| => f (Token s) | Collection of taken we should not match |
| -> m (Token s) |
As the dual of oneOf, succeeds if the current token
not in the supplied list of tokens noneOf tsts. Returns the parsed character.
Note that this parser cannot automatically generate the “expected”
component of error message, so usually you should label it manually with
label or (<?>).
noneOf cs = satisfy (`notElem` cs)
See also: satisfy.
Performance note: prefer satisfy and anySingleBut when you can
because it's faster.
Since: megaparsec-7.0.0
(<?>) :: MonadParsec e s m => m a -> String -> m a infix 0 #
A synonym for label in the form of an operator.
takeRest :: MonadParsec e s m => m (Tokens s) #
Consume the rest of the input and return it as a chunk. This parser never fails, but may return the empty chunk.
takeRest = takeWhileP Nothing (const True)
Since: megaparsec-6.0.0
atEnd :: MonadParsec e s m => m Bool #
Return True when end of input has been reached.
atEnd = option False (True <$ hidden eof)
Since: megaparsec-6.0.0
getInput :: MonadParsec e s m => m s #
Return the current input.
setInput :: MonadParsec e s m => s -> m () #
continues parsing with setInput inputinput.
getSourcePos :: (TraversableStream s, MonadParsec e s m) => m SourcePos #
Return the current source position. This function is not cheap, do
not call it e.g. on matching of every token, that's a bad idea. Still you
can use it to get SourcePos to attach to things that you parse.
The function works under the assumption that we move in the input stream only forwards and never backwards, which is always true unless the user abuses the library.
Since: megaparsec-7.0.0
getOffset :: MonadParsec e s m => m Int #
setOffset :: MonadParsec e s m => Int -> m () #
setParserState :: MonadParsec e s m => State s e -> m () #
sets the parser state to setParserState stst.
See also: getParserState, updateParserState.
eitherP :: Alternative m => m a -> m b -> m (Either a b) #
Combine two alternatives.
eitherP a b = (Left <$> a) <|> (Right <$> b)
manyTill_ :: MonadPlus m => m a -> m end -> m ([a], end) #
applies parser manyTill_ p endp zero or more times until
parser end succeeds. Returns the list of values returned by p and the
end result. Use manyTill if you have no need in the result of the
end.
See also: skipMany, skipManyTill.
Since: parser-combinators-1.2.0
sepEndBy :: MonadPlus m => m a -> m sep -> m [a] #
parses zero or more occurrences of sepEndBy p sepp, separated
and optionally ended by sep. Returns a list of values returned by p.
sepEndBy1 :: MonadPlus m => m a -> m sep -> m [a] #
parses one or more occurrences of sepEndBy1 p sepp, separated
and optionally ended by sep. Returns a list of values returned by p.
skipManyTill :: MonadPlus m => m a -> m end -> m end #
applies the parser skipManyTill p endp zero or more times
skipping results until parser end succeeds. Result parsed by end is
then returned.
skipSome :: MonadPlus m => m a -> m () #
applies the parser skipSome pp one or more times, skipping its
result.
See also: someTill, skipSomeTill.
skipSomeTill :: MonadPlus m => m a -> m end -> m end #
applies the parser skipSomeTill p endp one or more times
skipping results until parser end succeeds. Result parsed by end is
then returned.
someTill :: MonadPlus m => m a -> m end -> m [a] #
works similarly to someTill p end, but manyTill p endp
should succeed at least once. Note that end result is consumed and
lost. Use someTill_ if you wish to keep it.
someTill p end = liftM2 (:) p (manyTill p end)
See also: skipSome, skipSomeTill.
someTill_ :: MonadPlus m => m a -> m end -> m ([a], end) #
works similarly to someTill_ p end, but manyTill_ p endp
should succeed at least once. Use someTill if you have no need in the
result of the end.
See also: skipSome, skipSomeTill.
Since: parser-combinators-1.2.0
Arguments
| :: (VisualStream s, TraversableStream s, ShowErrorComponent e) | |
| => ParseErrorBundle s e | Parse error bundle to display |
| -> String | Textual rendition of the bundle |
Pretty-print a ParseErrorBundle. All ParseErrors in the bundle will
be pretty-printed in order together with the corresponding offending
lines by doing a single pass over the input stream. The rendered String
always ends with a newline.
Since: megaparsec-7.0.0