trifecta-0.37: A modern parser combinator library with convenient diagnostics

Portabilitynon-portable (mptcs, fundeps)
Stabilityexperimental
Maintainerekmett@gmail.com

Text.Trifecta.Parser.Char8

Description

This provides a thin backwards compatibility layer for folks who want to write parsers for languages where characters are bytes and don't need to deal with unicode issues. Diagnostics will still report the correct column number in the absence of high ascii characters but if you have those in your source file, you probably aren't going to want to draw those to the screen anyways.

Synopsis

Documentation

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

Using this instead of Text.Trifecta.Parser.Class.satisfy you too can time travel back to when men were men and characters fit into 8 bits like God intended. It might also be useful when writing lots of fiddly protocol code, where the UTF8 decoding is probably a very bad idea.

oneOf :: MonadParser 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 :: MonadParser 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 :: MonadParser m => ByteSet -> 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 :: MonadParser m => ByteSet -> 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 :: MonadParser m => m ()Source

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

space :: MonadParser m => m CharSource

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

newline :: MonadParser m => m CharSource

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

tab :: MonadParser m => m CharSource

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

upper :: MonadParser m => m CharSource

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

lower :: MonadParser m => m CharSource

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

alphaNum :: MonadParser m => m CharSource

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

letter :: MonadParser m => m CharSource

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

digit :: MonadParser m => m CharSource

Parses a digit. Returns the parsed character.

hexDigit :: MonadParser 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 :: MonadParser m => m CharSource

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

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

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

  semiColon  = char ';'

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

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

  semiColon  = char ';'

anyChar :: MonadParser m => m CharSource

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

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

byteString :: MonadParser m => ByteString -> m ByteStringSource

byteString s parses a sequence of bytes given by s. Returns the parsed byteString (i.e. s).

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