parsers-0.12: Parsing combinators

Portabilitynon-portable
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Text.Parser.Char

Contents

Description

Parsers for character streams

Synopsis

Combinators

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.

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. Returns the parsed character.

lower :: CharParsing m => m CharSource

Parses a lower case character. Returns the parsed character.

alphaNum :: CharParsing m => m CharSource

Parses a letter or digit. 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.

Class

class Parsing m => CharParsing m whereSource

Additional functionality needed to parse character streams.

Methods

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

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

char :: Char -> m CharSource

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

e.g.

semiColon = char ';'

notChar :: Char -> m CharSource

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

anyChar :: m CharSource

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

string :: 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"

text :: Text -> m TextSource

text t parses a sequence of characters determined by the text t Returns the parsed text fragment (i.e. t).

Using OverloadedStrings:

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