parsec2-1.0.1: Monadic parser combinators

Copyright(c) Daan Leijen 1999-2001
LicenseBSD-style (see the file libraries/parsec/LICENSE)
MaintainerAntoine Latter <aslatter@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Text.ParserCombinators.Parsec.Char

Description

Commonly used character parsers.

Synopsis

Documentation

type CharParser st a = GenParser Char st a Source

spaces :: CharParser st () Source

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

space :: CharParser st Char Source

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

newline :: CharParser st Char Source

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

tab :: CharParser st Char Source

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

upper :: CharParser st Char Source

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

lower :: CharParser st Char Source

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

alphaNum :: CharParser st Char Source

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

letter :: CharParser st Char Source

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

digit :: CharParser st Char Source

Parses a digit. Returns the parsed character.

hexDigit :: CharParser st Char Source

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

octDigit :: CharParser st Char Source

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

char :: Char -> CharParser st Char Source

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

 semiColon  = char ';'

string :: String -> CharParser st String Source

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

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

anyChar :: CharParser st Char Source

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

oneOf :: [Char] -> CharParser st Char Source

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 :: [Char] -> CharParser st Char Source

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"

satisfy :: (Char -> Bool) -> CharParser st Char Source

The parser satisfy f succeeds for any character for which the supplied function f returns True. Returns the character that is actually parsed.

 digit     = satisfy isDigit
 oneOf cs  = satisfy (\c -> c `elem` cs)