Copyright | (c) Edward Kmett 2011 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Parsers for character streams
Synopsis
- oneOf :: CharParsing m => [Char] -> m Char
- noneOf :: CharParsing m => [Char] -> m Char
- oneOfSet :: CharParsing m => CharSet -> m Char
- noneOfSet :: CharParsing m => CharSet -> 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
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"
oneOfSet :: CharParsing m => CharSet -> m Char Source #
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 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.
Nothing
satisfy :: (Char -> Bool) -> m Char Source #
Parse a single character of the input, with UTF-8 decoding
default satisfy :: (MonadTrans t, CharParsing n, Monad n, m ~ t n) => (Char -> Bool) -> m Char Source #
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
CharParsing ReadP Source # | |
Chunk t => CharParsing (Parser t) Source # | |
CharParsing m => CharParsing (Unlined m) Source # | |
CharParsing m => CharParsing (Unspaced m) Source # | |
CharParsing m => CharParsing (Unhighlighted m) Source # | |
Defined in Text.Parser.Token | |
(CharParsing m, MonadPlus m) => CharParsing (IdentityT m) Source # | |
(CharParsing m, MonadPlus m) => CharParsing (ReaderT e m) Source # | |
(CharParsing m, MonadPlus m) => CharParsing (StateT s m) Source # | |
(CharParsing m, MonadPlus m) => CharParsing (StateT s m) Source # | |
(CharParsing m, MonadPlus m, Monoid w) => CharParsing (WriterT w m) Source # | |
(CharParsing m, MonadPlus m, Monoid w) => CharParsing (WriterT w m) Source # | |
Stream s m Char => CharParsing (ParsecT s u m) Source # | |
Defined in Text.Parser.Char | |
(CharParsing m, MonadPlus m, Monoid w) => CharParsing (RWST r w s m) Source # | |
(CharParsing m, MonadPlus m, Monoid w) => CharParsing (RWST r w s m) Source # | |