megaparsec-6.5.0: Monadic parser combinators

Copyright© 2015–2018 Megaparsec contributors
LicenseFreeBSD
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Byte

Contents

Description

Commonly used binary parsers.

Since: megaparsec-6.0.0

Synopsis

Simple parsers

newline :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a newline byte.

crlf :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m (Tokens s) Source #

Parse a carriage return character followed by a newline character. Return the sequence of characters parsed.

eol :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m (Tokens s) Source #

Parse a CRLF (see crlf) or LF (see newline) end of line. Return the sequence of characters parsed.

tab :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a tab character.

space :: (MonadParsec e s m, Token s ~ Word8) => m () Source #

Skip zero or more white space characters.

See also: skipMany and spaceChar.

space1 :: (MonadParsec e s m, Token s ~ Word8) => m () Source #

Skip one or more white space characters.

See also: skipSome and spaceChar.

Categories of characters

controlChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a control character.

spaceChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a space character, and the control characters: tab, newline, carriage return, form feed, and vertical tab.

upperChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse an upper-case character.

lowerChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a lower-case alphabetic character.

letterChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse an alphabetic character: lower-case or upper-case.

alphaNumChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse an alphabetic or digit characters.

printChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a printable character: letter, number, mark, punctuation, symbol or space.

digitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse an ASCII digit, i.e between “0” and “9”.

octDigitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse an octal digit, i.e. between “0” and “7”.

hexDigitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a hexadecimal digit, i.e. between “0” and “9”, or “a” and “f”, or “A” and “F”.

asciiChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) Source #

Parse a character from the first 128 characters of the Unicode character set, corresponding to the ASCII character set.

More general parsers

char :: MonadParsec e s m => Token s -> m (Token s) Source #

char c parses a single character c.

semicolon = char ';'

char' :: (MonadParsec e s m, Token s ~ Word8) => Token s -> m (Token s) Source #

The same as char but case-insensitive. This parser returns the actually parsed character preserving its case.

>>> parseTest (char' 101) "E"
69 -- 'E'
>>> parseTest (char' 101) "G"
1:1:
unexpected 'G'
expecting 'E' or 'e'

anyChar :: MonadParsec e s m => m (Token s) Source #

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

notChar :: MonadParsec e s m => Token s -> m (Token s) Source #

Match any character but the given one. It's a good idea to attach a label to this parser manually.

Since: megaparsec-6.0.0

oneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s) Source #

oneOf cs succeeds if the current character is in the supplied collection of characters cs. Returns the parsed character. Note that this parser cannot automatically generate the “expected” component of error message, so usually you should label it manually with label or (<?>).

See also: satisfy.

digit = oneOf ['0'..'9'] <?> "digit"

Performance note: prefer satisfy when you can because it's faster when you have only a couple of tokens to compare to:

quoteFast = satisfy (\x -> x == '\'' || x == '\"')
quoteSlow = oneOf "'\""

noneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s) 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. Note that this parser cannot automatically generate the “expected” component of error message, so usually you should label it manually with label or (<?>).

See also: satisfy.

Performance note: prefer satisfy and notChar when you can because it's faster.

satisfy Source #

Arguments

:: MonadParsec e s m 
=> (Token s -> Bool)

Predicate to apply

-> m (Token s) 

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

digitChar = satisfy isDigit <?> "digit"
oneOf cs  = satisfy (`elem` cs)

Sequence of bytes

string :: MonadParsec e s m => Tokens s -> m (Tokens s) Source #

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

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

string' :: (MonadParsec e s m, FoldCase (Tokens s)) => Tokens s -> m (Tokens s) Source #

The same as string, but case-insensitive. On success returns string cased as actually parsed input.

>>> parseTest (string' "foobar") "foObAr"
"foObAr"