| Copyright | (c) Edward Kmett 2011 | 
|---|---|
| License | BSD3 | 
| Maintainer | ekmett@gmail.com | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Distribution.Compat.CharParsing
Contents
Description
Parsers for character streams
Originally in parsers package.
Synopsis
- oneOf :: CharParsing m => [Char] -> m Char
- noneOf :: CharParsing m => [Char] -> m Char
- spaces :: CharParsing m => m ()
- space :: CharParsing m => m Char
- newline :: CharParsing m => m Char
- tab :: CharParsing m => m Char
- upper :: CharParsing m => m Char
- lower :: CharParsing m => m Char
- alphaNum :: CharParsing m => m Char
- letter :: CharParsing m => m Char
- digit :: CharParsing m => m Char
- hexDigit :: CharParsing m => m Char
- octDigit :: CharParsing m => m Char
- satisfyRange :: CharParsing m => Char -> Char -> m Char
- class Parsing m => CharParsing m where
- integral :: (CharParsing m, Integral a) => m a
- signedIntegral :: (CharParsing m, Integral a) => m a
- munch1 :: CharParsing m => (Char -> Bool) -> m String
- munch :: CharParsing m => (Char -> Bool) -> m String
- skipSpaces1 :: CharParsing m => m ()
- module Distribution.Compat.Parsing
Combinators
oneOf :: CharParsing m => [Char] -> m 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 :: CharParsing m => [Char] -> m Char Source #
As the dual of oneOf, noneOf cs succeeds if the current
 character is 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 Char Source #
Parses a white space character (any character which satisfies isSpace)
 Returns the parsed character.
newline :: CharParsing m => m Char Source #
Parses a newline character ('\n'). Returns a newline character.
tab :: CharParsing m => m Char Source #
Parses a tab character ('\t'). Returns a tab character.
upper :: CharParsing m => m Char Source #
Parses an upper case letter. Returns the parsed character.
lower :: CharParsing m => m Char Source #
Parses a lower case character. Returns the parsed character.
alphaNum :: CharParsing m => m Char Source #
Parses a letter or digit. Returns the parsed character.
letter :: CharParsing m => m Char Source #
Parses a letter (an upper case or lower case character). Returns the parsed character.
digit :: CharParsing m => m Char Source #
Parses a digit. Returns the parsed character.
hexDigit :: CharParsing m => m Char Source #
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 Char Source #
Parses an octal digit (a character between '0' and '7'). Returns the parsed character.
satisfyRange :: CharParsing m => Char -> Char -> m Char Source #
Class
class Parsing m => CharParsing m where Source #
Additional functionality needed to parse character streams.
Minimal complete definition
Methods
satisfy :: (Char -> Bool) -> m Char Source #
Parse a single character of the input, with UTF-8 decoding
char :: Char -> m Char Source #
notChar :: Char -> m Char Source #
notChar c parses any single character other than c. Returns the parsed
 character.
This parser succeeds for any character. Returns the parsed character.
string :: String -> m String Source #
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 Text Source #
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"Instances
Cabal additions
integral :: (CharParsing m, Integral a) => m a Source #
signedIntegral :: (CharParsing m, Integral a) => m a Source #
Accepts negative (starting with -) and positive (without sign) integral
 numbers.
Since: 3.4.0.0
munch1 :: CharParsing m => (Char -> Bool) -> m String Source #
Greedily munch characters while predicate holds. Require at least one character.
munch :: CharParsing m => (Char -> Bool) -> m String Source #
Greedely munch characters while predicate holds. Always succeeds.
skipSpaces1 :: CharParsing m => m () Source #
module Distribution.Compat.Parsing