parsers-0.1: Simple parsing combinators

Portabilitynon-portable
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellSafe-Infered

Text.Parser.Char

Contents

Description

Parsers for character streams

Synopsis

Documentation

class Parsing m => CharParsing m whereSource

Methods

satisfy :: (Char -> Bool) -> m CharSource

Parse a single character of the input, with UTF-8 decoding

char :: CharParsing m => Char -> m CharSource

char c parses a single character c. Returns the parsed character (i.e. c).

  semiColon  = char ';'

notChar :: CharParsing m => Char -> m CharSource

notChar c parses any single character other than c. Returns the parsed character.

  semiColon  = char ';'

anyChar :: CharParsing m => m CharSource

This parser succeeds for any character. Returns the parsed character.

string :: CharParsing m => String -> m StringSource

string s parses a sequence of characters given by s. Returns the parsed string (i.e. s).

  divOrMod    =   string "div"
              <|> string "mod"

Character parsers

oneOf :: CharParsing m => [Char] -> m CharSource

oneOf cs succeeds if the current character is in the supplied list of characters cs. Returns the parsed character. See also satisfy.

   vowel  = oneOf "aeiou"

noneOf :: CharParsing m => [Char] -> m CharSource

As the dual of oneOf, noneOf cs succeeds if the current character not in the supplied list of characters cs. Returns the parsed character.

  consonant = noneOf "aeiou"

oneOfSet :: CharParsing m => CharSet -> m CharSource

oneOfSet cs succeeds if the current character is in the supplied set of characters cs. Returns the parsed character. See also satisfy.

   vowel  = oneOf "aeiou"

noneOfSet :: CharParsing m => CharSet -> m CharSource

As the dual of oneOf, noneOf cs succeeds if the current character not in the supplied list of characters cs. Returns the parsed character.

  consonant = noneOf "aeiou"

spaces :: CharParsing m => m ()Source

Skips zero or more white space characters. See also skipMany and whiteSpace.

space :: CharParsing m => m CharSource

Parses a white space character (any character which satisfies isSpace) Returns the parsed character.

newline :: CharParsing m => m CharSource

Parses a newline character ('\n'). Returns a newline character.

tab :: CharParsing m => m CharSource

Parses a tab character ('\t'). Returns a tab character.

upper :: CharParsing m => m CharSource

Parses an upper case letter (a character between 'A' and 'Z'). Returns the parsed character.

lower :: CharParsing m => m CharSource

Parses a lower case character (a character between 'a' and 'z'). Returns the parsed character.

alphaNum :: CharParsing m => m CharSource

Parses a letter or digit (a character between '0' and '9'). Returns the parsed character.

letter :: CharParsing m => m CharSource

Parses a letter (an upper case or lower case character). Returns the parsed character.

digit :: CharParsing m => m CharSource

Parses a digit. Returns the parsed character.

hexDigit :: CharParsing m => m CharSource

Parses a hexadecimal digit (a digit or a letter between 'a' and 'f' or 'A' and 'F'). Returns the parsed character.

octDigit :: CharParsing m => m CharSource

Parses an octal digit (a character between '0' and '7'). Returns the parsed character.

decimal :: CharParsing m => m IntegerSource

Parses a positive whole number in the decimal system. Returns the value of the number.

hexadecimal :: CharParsing m => m IntegerSource

Parses a positive whole number in the hexadecimal system. The number should be prefixed with "x" or "X". Returns the value of the number.

octal :: CharParsing m => m IntegerSource

Parses a positive whole number in the octal system. The number should be prefixed with "o" or "O". Returns the value of the number.

Internal parsers

charLiteral' :: CharParsing m => m CharSource

This 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).

This parser does NOT swallow trailing whitespace.

stringLiteral' :: CharParsing m => m StringSource

This 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).

This parser does NOT swallow trailing whitespace

natural' :: CharParsing m => m IntegerSource

This 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.

This parser does NOT swallow trailing whitespace.

integer' :: CharParsing m => m IntegerSource

This 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.

This parser does NOT swallow trailing whitespace.

Also, unlike the integer parser, this parser does not admit spaces between the sign and the number.

double' :: CharParsing m => m DoubleSource

This 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.

This parser does NOT swallow trailing whitespace.

naturalOrDouble' :: CharParsing m => m (Either Integer Double)Source

This parser parses either natural or a double. 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.

This parser does NOT swallow trailing whitespace.