trifecta-0.50.1: A modern parser combinator library with convenient diagnostics

Portabilitynon-portable
Stabilityprovisional
Maintainerekmett@gmail.com
Safe HaskellNone

Text.Trifecta.Parser.Token.Combinators

Description

 

Synopsis

Documentation

lexeme :: MonadParser m => m a -> m aSource

lexeme p first applies parser p and then the whiteSpace parser, returning the value of p. Every lexical token (lexeme) is defined using lexeme, this way every parse starts at a point without white space. Parsers that use lexeme are called lexeme parsers in this document.

The only point where the whiteSpace parser should be called explicitly is the start of the main parser in order to skip any leading white space.

    mainParser  = do { whiteSpace
                     ; ds <- many (lexeme digit)
                     ; eof
                     ; return (sum ds)
                     }

charLiteral :: MonadParser m => m CharSource

This lexeme parser parses a single literal character. Returns the literal character value. This parsers deals correctly with escape sequences. The literal character is parsed according to the grammar rules defined in the Haskell report (which matches most programming languages quite closely).

stringLiteral :: MonadParser m => m StringSource

This lexeme parser parses a literal string. Returns the literal string value. This parsers deals correctly with escape sequences and gaps. The literal string is parsed according to the grammar rules defined in the Haskell report (which matches most programming languages quite closely).

natural :: MonadParser m => m IntegerSource

This lexeme parser parses a natural number (a positive whole number). Returns the value of the number. The number can be specified in decimal, hexadecimal or octal. The number is parsed according to the grammar rules in the Haskell report.

integer :: MonadParser m => m IntegerSource

This lexeme parser parses an integer (a whole number). This parser is like natural except that it can be prefixed with sign (i.e. '-' or '+'). Returns the value of the number. The number can be specified in decimal, hexadecimal or octal. The number is parsed according to the grammar rules in the Haskell report.

double :: MonadParser m => m DoubleSource

This lexeme parser parses a floating point value. Returns the value of the number. The number is parsed according to the grammar rules defined in the Haskell report.

naturalOrDouble :: MonadParser m => m (Either Integer Double)Source

This lexeme parser parses either natural or a float. Returns the value of the number. This parsers deals with any overlap in the grammar rules for naturals and floats. The number is parsed according to the grammar rules defined in the Haskell report.

symbol :: MonadParser m => ByteString -> m ByteStringSource

Lexeme parser symbol s parses string s and skips trailing white space.

symbolic :: MonadParser m => Char -> m CharSource

Lexeme parser symbolic s parses char s and skips trailing white space.

parens :: MonadParser m => m a -> m aSource

Lexeme parser parens p parses p enclosed in parenthesis, returning the value of p.

braces :: MonadParser m => m a -> m aSource

Lexeme parser braces p parses p enclosed in braces ('{' and '}'), returning the value of p.

angles :: MonadParser m => m a -> m aSource

Lexeme parser angles p parses p enclosed in angle brackets ('<' and '>'), returning the value of p.

brackets :: MonadParser m => m a -> m aSource

Lexeme parser brackets p parses p enclosed in brackets ('[' and ']'), returning the value of p.

comma :: MonadParser m => m CharSource

Lexeme parser comma parses the character ',' and skips any trailing white space. Returns the string ",".

colon :: MonadParser m => m CharSource

Lexeme parser colon parses the character ':' and skips any trailing white space. Returns the string ":".

dot :: MonadParser m => m CharSource

Lexeme parser dot parses the character '.' and skips any trailing white space. Returns the string ".".

semiSep :: MonadParser m => m a -> m [a]Source

Lexeme parser semiSep p parses zero or more occurrences of p separated by semi. Returns a list of values returned by p.

semiSep1 :: MonadParser m => m a -> m [a]Source

Lexeme parser semiSep1 p parses one or more occurrences of p separated by semi. Returns a list of values returned by p.

commaSep :: MonadParser m => m a -> m [a]Source

Lexeme parser commaSep p parses zero or more occurrences of p separated by comma. Returns a list of values returned by p.

commaSep1 :: MonadParser m => m a -> m [a]Source

Lexeme parser commaSep1 p parses one or more occurrences of p separated by comma. Returns a list of values returned by p.