hexpr-0.0.0.0: A framework for symbolic, homoiconic languages.

Safe HaskellSafe-Inferred

Language.Parse

Contents

Description

Utility library that provides parsers for commonly-occuring programming constructs such as identifiers, numbers and characters.

Synopsis

Combinators

Composable

string :: (Monad m, Stream s m Char) => String -> ParsecT s u m StringSource

Parse a string, but don't consume input on failure.

lookAhead :: (Monad m, Stream s m t) => ParsecT s u m a -> ParsecT s u m aSource

Lookahead without consuming any input.

manyTill :: (Monad m, Stream s m t) => ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m [a]Source

Use manyTill p e to apply parser p many times, stopping as soon as e is next to parse. Note that e is not consumed.

manyThru :: (Monad m, Stream s m t) => ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m [a]Source

Use manyThru p e to apply parser p many times, stopping as soon as e is consumed. Unlike Parsec's manyTill, if e fails, it does not consume input.

(<|>) :: (Monad m, Stream s m t) => ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m aSource

Use a | b to parse a or b. If a fails, no input is consumed.

choice :: (Monad m, Stream s m t) => [ParsecT s u m a] -> ParsecT s u m aSource

Parse the first of the passed combinators that succeeds. If any parser fails, it does not consume input.

Extra

many2 :: (Monad m, Stream s m t) => ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m [a]Source

Use many2 a b to parse an a followed by zero or more bs.

between2 :: (Monad m, Stream s m t) => ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m bSource

Use between2 a p to parse an a, then a p, then an a. Return the results of the p parser.

isEof :: (Show t, Monad m, Stream s m t) => ParsecT s u m BoolSource

Detect end of file as a boolean.

spaces1 :: (Monad m, Stream s m Char) => ParsecT s u m ()Source

One or more spaces.

charICase :: (Monad m, Stream s m Char) => Char -> ParsecT s u m CharSource

Parse one character, case-insensitive.

stringICase :: (Monad m, Stream s m Char) => String -> ParsecT s u m StringSource

Parse a string, case-insensitive. If this parser fails, it consumes no input.

Identifiers

blacklistChar :: (Monad m, Stream s m Char) => (Char -> Bool) -> ParsecT s u m CharSource

Parses a wide variety of characters, excepting those which meet the passed predicate. Specifically, we accept all of Unicode except:

  • Space
  • LineSeparator
  • ParagraphSeparator
  • Control
  • Format
  • Surrogate
  • PrivateUse
  • NotAssigned

Numbers

Prepackaged Parsers

anyNumber :: (Monad m, Stream s m Char) => ParsecT s u m RationalSource

Optional sign, then an integer number in scientific notation or ratio, in base 2, 8, 10 or 16. If in scientific notation, the exponent may be in base 10 or 16

Number Parts

signLiteral :: (Monad m, Stream s m Char) => ParsecT s u m IntegerSource

Parse a minus or plus sign and return the appropriate multiplier.

baseLiteral :: (Monad m, Stream s m Char) => ParsecT s u m IntSource

Parse "0x", "0o", or "0b" case-insensitive and return the appropriate base. If none of these parse, return base 10.

naturalLiteral :: (Monad m, Stream s m Char) => Int -> ParsecT s u m IntegerSource

Parse many digits in the passed base and return the corresponding integer.

mantissaLiteral :: (Monad m, Stream s m Char) => Int -> ParsecT s u m RationalSource

Parse a dot followed by many digits in the passed base and return the corresponding ratio.

exponentLiteral :: (Monad m, Stream s m Char) => Int -> ParsecT s u m IntegerSource

In base 10, parse an e and a decimal integer. In base 16, parse an h and a hexadecimal integer.

denominatorLiteral :: (Monad m, Stream s m Char) => Int -> ParsecT s u m RationalSource

Parse a / and a natural in the passed base. Return the reciprocal of that number.

xDigit :: (Monad m, Stream s m Char) => Int -> ParsecT s u m CharSource

Parse a digit in the passed base: 2, 8, 10 or 16.

Convert Strings to Numbers

stringToInteger :: Int -> String -> IntegerSource

Interpret a string as an integer in the passed base.

stringToMantissa :: Int -> String -> Ratio IntegerSource

Interpret a string as a mantissa in the passed base.

Characters

literalChar :: (Monad m, Stream s m Char) => ParsecT s u m CharSource

Parse a single character as if in a string literal. This should be applicable to both character and string literals.

Here's the list of what characters are accepted:

  • Any single unicode character that is not an ASCII control character, backslash, or double-quote.
  • Line continuation: backslash, then advance over whitespace (including newlines and comments) through the next backslash.
  • Octal or hexadecimal ASCII escapes: a sequence in /\\(x[0-9a-fA-F]{2}|o[0-7]{3})/.
  • Unicode escapes: a sequence in /\\(u|U0[0-9a-fA-F]|U10)[0-9a-fA-F]{4}/.
  • Special escape: a sequence in /\\[0abefnrtv'"]/. For reference, the meanings of special escapes are:
\0: nul             (ASCII 0,  0x00)
\a: bell            (ASCII 7,  0x07)
\b: backspace       (ASCII 8,  0x08)
\e: escape          (ASCII 27, 0x1B)
\f: form feed       (ASCII 12, 0x0C)
\n: line feed       (ASCII 10, 0x0A)
\r: carriage return (ASCII 13, 0x0D)
\t: horizontal tab  (ASCII 9,  0x09)
\v: vertical tab    (ASCII 11, 0x0B)
\': single quote    (ASCII 39, 0x27)
\": double quote    (ASCII 34, 0x22)

maybeLiteralChar :: (Monad m, Stream s m Char) => ParsecT s u m (Maybe Char)Source

Parse any character accepted by literalChar, but also accept two empty characters:

  • \& The eplicit empty character.
  • Backslash-whitespace-backslash.