hledger-iadd-1.3.6: A terminal UI as drop-in replacement for hledger add

Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Compat

Contents

Description

Compatibility module to bridge the gap between megaparsec-5 and megaparsec-6

Import this instead of Text.Megaparsec, Text.Megaparsec.Char and Text.Megaparsec.Text

Synopsis

Re-exports

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

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

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

satisfy #

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)

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

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.

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

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 "'\""

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

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

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

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

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

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

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

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

char c parses a single character c.

semicolon = char ';'

categoryName :: GeneralCategory -> String #

Return the human-readable name of Unicode General Category.

charCategory :: (MonadParsec e s m, Token s ~ Char) => GeneralCategory -> m (Token s) #

charCategory cat parses character in Unicode General Category cat, see GeneralCategory.

latin1Char :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #

Parse a character from the first 256 characters of the Unicode character set, corresponding to the ISO 8859-1 (Latin-1) character set.

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

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

separatorChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #

Parse a Unicode space and separator characters.

symbolChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #

Parse a Unicode symbol characters, including mathematical and currency symbols.

punctuationChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #

Parse a Unicode punctuation character, including various kinds of connectors, brackets and quotes.

numberChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #

Parse a Unicode numeric character, including digits from various scripts, Roman numerals, etc.

markChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) #

Parse a Unicode mark character (accents and the like), which combines with preceding characters.

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

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

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

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

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

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

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

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

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

Parse an alphabetic or numeric digit Unicode characters.

Note that the numeric digits outside the ASCII range are parsed by this parser but not by digitChar. Such digits may be part of identifiers but are not used by the printer and reader to represent numbers.

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

Parse an alphabetic Unicode character: lower-case, upper-case, or title-case letter, or a letter of case-less scripts/modifier letter.

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

Parse a lower-case alphabetic Unicode character.

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

Parse an upper-case or title-case alphabetic Unicode character. Title case is used by a small number of letter ligatures like the single-character form of Lj.

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

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

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

Parse a control character (a non-printing character of the Latin-1 subset of Unicode).

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

Skip one or more white space characters.

See also: skipSome and spaceChar.

Since: megaparsec-6.0.0

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

Skip zero or more white space characters.

See also: skipMany and spaceChar.

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

Parse a tab character.

eol :: (MonadParsec e s m, Token s ~ Char) => m (Tokens s) #

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

crlf :: (MonadParsec e s m, Token s ~ Char) => m (Tokens s) #

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

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

Parse a newline character.

Compatibility reimplementations

type Parser = Parsec Dec Text Source #

Same as the type in Text.Megaparsec.Text from megaparsec-5

type Dec = Void Source #

Custom error type for when no custom errors are needed

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

Reimplementation of string, but specialized to Text.

Custom error handling

data CustomError e Source #

Custom error type that mimics FancyError of megaparsec-6 but retains information about unexpected and expected tokens.

Instances
Eq e => Eq (CustomError e) Source # 
Instance details

Defined in Text.Megaparsec.Compat

Ord e => Ord (CustomError e) Source # 
Instance details

Defined in Text.Megaparsec.Compat

Show e => Show (CustomError e) Source # 
Instance details

Defined in Text.Megaparsec.Compat

ShowErrorComponent e => ShowErrorComponent (CustomError e) Source # 
Instance details

Defined in Text.Megaparsec.Compat

mkCustomError :: SourcePos -> e -> ParseError t (CustomError e) Source #

Wrap a custom error type into a ParseError.

addCustomError :: Ord e => ParseError Char (CustomError e) -> e -> ParseError Char (CustomError e) Source #

Add a custom error to an already existing error.

This retains the original information such as expected and unexpected tokens as well as the source position.

Additional helpers

parseWithStart :: (Stream s, Ord e) => Parsec e s a -> SourcePos -> s -> Either (ParseError (Token s) e) a Source #

Like parse, but start at a specific source position instead of 0.