| Copyright | (c) 2018-2021 Kowainik | 
|---|---|
| License | MPL-2.0 | 
| Maintainer | Kowainik <xrom.xkov@gmail.com> | 
| Stability | Stable | 
| Portability | Portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Toml.Parser.Core
Description
Core functions for TOML parser.
Synopsis
- match :: MonadParsec e s m => m a -> m (Tokens s, a)
- (<?>) :: MonadParsec e s m => m a -> String -> m a
- anySingle :: MonadParsec e s m => m (Token s)
- satisfy :: MonadParsec e s m => (Token s -> Bool) -> m (Token s)
- parse :: Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
- type Parsec e s = ParsecT e s Identity
- try :: MonadParsec e s m => m a -> m a
- eof :: MonadParsec e s m => m ()
- errorBundlePretty :: (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- char :: (MonadParsec e s m, Token s ~ Char) => Token s -> m (Token s)
- hexDigitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s)
- octDigitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s)
- binDigitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s)
- digitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s)
- alphaNumChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s)
- space1 :: (MonadParsec e s m, Token s ~ Char) => m ()
- space :: (MonadParsec e s m, Token s ~ Char) => m ()
- tab :: (MonadParsec e s m, Token s ~ Char) => m (Token s)
- eol :: (MonadParsec e s m, Token s ~ Char) => m (Tokens s)
- string :: MonadParsec e s m => Tokens s -> m (Tokens s)
- signed :: (MonadParsec e s m, Token s ~ Char, Num a) => m () -> m a -> m a
- float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a
- hexadecimal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
- octal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
- binary :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
- skipLineComment :: (MonadParsec e s m, Token s ~ Char) => Tokens s -> m ()
- symbol :: MonadParsec e s m => m () -> Tokens s -> m (Tokens s)
- type Parser = Parsec Void Text
- lexeme :: Parser a -> Parser a
- sc :: Parser ()
- text :: Text -> Parser Text
Reexports from megaparsec
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
(<?>) :: MonadParsec e s m => m a -> String -> m a infix 0 #
A synonym for label in the form of an operator.
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 -> Bool) | Predicate to apply | 
| -> m (Token s) | 
Arguments
| :: Parsec e s a | Parser to run | 
| -> String | Name of source file | 
| -> s | Input for parser | 
| -> Either (ParseErrorBundle s e) a | 
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 ','try :: MonadParsec e s m => m a -> m a #
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.
eof :: MonadParsec e s m => m () #
This parser only succeeds at the end of input.
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 efficient pass over the input stream. The
 rendered String always ends with a newline.
Since: megaparsec-7.0.0
char :: (MonadParsec e s m, Token s ~ Char) => Token s -> m (Token s) #
A type-constrained version of single.
semicolon = char ';'
hexDigitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #
Parse a hexadecimal digit, i.e. between “0” and “9”, or “a” and “f”, or “A” and “F”.
octDigitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #
Parse an octal digit, i.e. between “0” and “7”.
binDigitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #
Parse a binary digit, i.e. "0" or "1".
Since: megaparsec-7.0.0
digitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #
Parse an ASCII digit, i.e between “0” and “9”.
alphaNumChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #
Parse an alphabetic or numeric digit Unicode characters.
Note that the numeric digits outside the ASCII range are parsed by this
 parser but not by digitChar. Such digits may be part of identifiers but
 are not used by the printer and reader to represent numbers.
space1 :: (MonadParsec e s m, Token s ~ Char) => m () #
space :: (MonadParsec e s m, Token s ~ Char) => m () #
Arguments
| :: (MonadParsec e s m, Token s ~ Char, Num a) | |
| => m () | How to consume white space after the sign | 
| -> m a | How to parse the number itself | 
| -> m a | Parser for signed numbers | 
signed space pspace parser), then it runs parser p which should return a number.
 Sign of the number is changed according to the previously parsed sign
 character.
For example, to parse signed integer you can write:
lexeme = L.lexeme spaceConsumer integer = lexeme L.decimal signedInteger = L.signed spaceConsumer integer
float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a #
Parse a floating point number according to the syntax for floating point literals described in the Haskell report.
This function does not parse sign, if you need to parse signed numbers,
 see signed.
Note: before version 6.0.0 the function returned Double, i.e. it
 wasn't polymorphic in its return type.
Note: in versions 6.0.0–6.1.1 this function accepted plain integers.
hexadecimal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a #
Parse an integer in hexadecimal representation. Representation of hexadecimal number is expected to be according to the Haskell report except for the fact that this parser doesn't parse “0x” or “0X” prefix. It is a responsibility of the programmer to parse correct prefix before parsing the number itself.
For example you can make it conform to the Haskell report like this:
hexadecimal = char '0' >> char' 'x' >> L.hexadecimal
Note: before version 6.0.0 the function returned Integer, i.e. it
 wasn't polymorphic in its return type.
octal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a #
Parse an integer in octal representation. Representation of octal number is expected to be according to the Haskell report except for the fact that this parser doesn't parse “0o” or “0O” prefix. It is a responsibility of the programmer to parse correct prefix before parsing the number itself.
For example you can make it conform to the Haskell report like this:
octal = char '0' >> char' 'o' >> L.octal
Note: before version 6.0.0 the function returned Integer, i.e. it
 wasn't polymorphic in its return type.
binary :: (MonadParsec e s m, Token s ~ Char, Num a) => m a #
Parse an integer in binary representation. Binary number is expected to be a non-empty sequence of zeroes “0” and ones “1”.
You could of course parse some prefix before the actual number:
binary = char '0' >> char' 'b' >> L.binary
Since: megaparsec-7.0.0
Arguments
| :: (MonadParsec e s m, Token s ~ Char) | |
| => Tokens s | Line comment prefix | 
| -> m () | 
Given comment prefix this function returns a parser that skips line
 comments. Note that it stops just before the newline character but
 doesn't consume the newline. Newline is either supposed to be consumed by
 space parser or picked up manually.
Arguments
| :: MonadParsec e s m | |
| => m () | How to consume white space after lexeme | 
| -> Tokens s | Symbol to parse | 
| -> m (Tokens s) | 
This is a helper to parse symbols, i.e. verbatim strings. You pass the
 first argument (parser that consumes white space, probably defined via
 space) and then you can use the resulting function to parse strings:
symbol    = L.symbol spaceConsumer
parens    = between (symbol "(") (symbol ")")
braces    = between (symbol "{") (symbol "}")
angles    = between (symbol "<") (symbol ">")
brackets  = between (symbol "[") (symbol "]")
semicolon = symbol ";"
comma     = symbol ","
colon     = symbol ":"
dot       = symbol "."