dhall-1.38.0: A configuration language guaranteed to terminate
Safe HaskellNone
LanguageHaskell2010

Dhall.Parser.Token

Description

Parse Dhall tokens. Even though we don't have a tokenizer per-se this

Synopsis

Documentation

validCodepoint :: Int -> Bool Source #

Returns True if the given Int is a valid Unicode codepoint

whitespace :: Parser () Source #

Parse 0 or more whitespace characters (including comments)

This corresponds to the whsp rule in the official grammar

lineComment :: Parser Text Source #

Parse a Dhall's single-line comment, starting from `--` and until the last character of the line before the end-of-line character

blockComment :: Parser Text Source #

Parsed text doesn't include opening braces

nonemptyWhitespace :: Parser () Source #

Parse 1 or more whitespace characters (including comments)

This corresponds to the whsp1 rule in the official grammar

bashEnvironmentVariable :: Parser Text Source #

Parse a valid Bash environment variable name

This corresponds to the bash-environment-variable rule in the official grammar

posixEnvironmentVariable :: Parser Text Source #

Parse a valid POSIX environment variable name, which permits a wider range of characters than a Bash environment variable name

This corresponds to the posix-environment-variable rule in the official grammar

data ComponentType Source #

The pathComponent function uses this type to distinguish whether to parse a URL path component or a file path component

text :: Text -> Parser Text Source #

A variation on text that doesn't quote the expected in error messages

char :: Char -> Parser Char Source #

A variation on char that doesn't quote the expected token in error messages

label :: Parser Text Source #

Parse a label (e.g. a variable/field/alternative name)

Rejects labels that match built-in names (e.g. Natural/even)

This corresponds to the nonreserved-label rule in the official grammar

anyLabelOrSome :: Parser Text Source #

Same as anyLabel except that Some is allowed

This corresponds to the any-label-or-some rule in the official grammar

anyLabel :: Parser Text Source #

Same as label except that built-in names are allowed

This corresponds to the any-label rule in the official grammar

labels :: Parser [Text] Source #

Parse a braced sequence of comma-separated labels

For example, this is used to parse the record projection syntax

This corresponds to the labels rule in the official grammar

httpRaw :: Parser URL Source #

Parse an HTTP(S) URL without trailing whitespace

This corresponds to the http-raw rule in the official grammar

hexdig :: Char -> Bool Source #

Parse a hex digit (uppercase or lowercase)

This corresponds to the HEXDIG rule in the official grammar

identifier :: Parser Var Source #

Parse an identifier (i.e. a variable or built-in)

Variables can have an optional index to disambiguate shadowed variables

This corresponds to the identifier rule from the official grammar

hexNumber :: Parser Int Source #

Parse a hexademical number and convert to the corresponding Int

doubleLiteral :: Parser Double Source #

Parse a Double literal

This corresponds to the double-literal rule from the official grammar

doubleInfinity :: Parser Double Source #

Parse a signed Infinity

This corresponds to the minus-infinity-literal and plus-infinity-literal rules from the official grammar

naturalLiteral :: Parser Natural Source #

Parse a Natural literal

This corresponds to the natural-literal rule from the official grammar

integerLiteral :: Parser Integer Source #

Parse an Integer literal

This corresponds to the integer-literal rule from the official grammar

_Optional :: Parser () Source #

Parse the Optional built-in

This corresponds to the Optional rule from the official grammar

_if :: Parser () Source #

Parse the if keyword

This corresponds to the if rule from the official grammar

_then :: Parser () Source #

Parse the then keyword

This corresponds to the then rule from the official grammar

_else :: Parser () Source #

Parse the else keyword

This corresponds to the else rule from the official grammar

_let :: Parser () Source #

Parse the let keyword

This corresponds to the let rule from the official grammar

_in :: Parser () Source #

Parse the in keyword

This corresponds to the in rule from the official grammar

_as :: Parser () Source #

Parse the as keyword

This corresponds to the as rule from the official grammar

_using :: Parser () Source #

Parse the using keyword

This corresponds to the using rule from the official grammar

_merge :: Parser () Source #

Parse the merge keyword

This corresponds to the merge rule from the official grammar

_toMap :: Parser () Source #

Parse the toMap keyword

This corresponds to the toMap rule from the official grammar

_assert :: Parser () Source #

Parse the assert keyword

This corresponds to the assert rule from the official grammar

_Some :: Parser () Source #

Parse the Some built-in

This corresponds to the Some rule from the official grammar

_None :: Parser () Source #

Parse the None built-in

This corresponds to the None rule from the official grammar

_NaturalFold :: Parser () Source #

Parse the Natural/fold built-in

This corresponds to the Natural-fold rule from the official grammar

_NaturalBuild :: Parser () Source #

Parse the Natural/build built-in

This corresponds to the Natural-build rule from the official grammar

_NaturalIsZero :: Parser () Source #

Parse the Natural/isZero built-in

This corresponds to the Natural-isZero rule from the official grammar

_NaturalEven :: Parser () Source #

Parse the Natural/even built-in

This corresponds to the Natural-even rule from the official grammar

_NaturalOdd :: Parser () Source #

Parse the Natural/odd built-in

This corresponds to the Natural-odd rule from the official grammar

_NaturalToInteger :: Parser () Source #

Parse the Natural/toInteger built-in

This corresponds to the Natural-toInteger rule from the official grammar

_NaturalShow :: Parser () Source #

Parse the Natural/show built-in

This corresponds to the Natural-show rule from the official grammar

_NaturalSubtract :: Parser () Source #

Parse the Natural/subtract built-in

This corresponds to the Natural-subtract rule from the official grammar

_IntegerClamp :: Parser () Source #

Parse the Integer/clamp built-in

This corresponds to the Integer-clamp rule from the official grammar

_IntegerNegate :: Parser () Source #

Parse the Integer/negate built-in

This corresponds to the Integer-negate rule from the official grammar

_IntegerShow :: Parser () Source #

Parse the Integer/show built-in

This corresponds to the Integer-show rule from the official grammar

_IntegerToDouble :: Parser () Source #

Parse the Integer/toDouble built-in

This corresponds to the Integer-toDouble rule from the official grammar

_DoubleShow :: Parser () Source #

Parse the Double/show built-in

This corresponds to the Double-show rule from the official grammar

_ListBuild :: Parser () Source #

Parse the List/build built-in

This corresponds to the List-build rule from the official grammar

_ListFold :: Parser () Source #

Parse the List/fold built-in

This corresponds to the List-fold rule from the official grammar

_ListLength :: Parser () Source #

Parse the List/length built-in

This corresponds to the List-length rule from the official grammar

_ListHead :: Parser () Source #

Parse the List/head built-in

This corresponds to the List-head rule from the official grammar

_ListLast :: Parser () Source #

Parse the List/last built-in

This corresponds to the List-last rule from the official grammar

_ListIndexed :: Parser () Source #

Parse the List/indexed built-in

This corresponds to the List-indexed rule from the official grammar

_ListReverse :: Parser () Source #

Parse the List/reverse built-in

This corresponds to the List-reverse rule from the official grammar

_Bool :: Parser () Source #

Parse the Bool built-in

This corresponds to the Bool rule from the official grammar

_Natural :: Parser () Source #

Parse the Natural built-in

This corresponds to the Natural rule from the official grammar

_Integer :: Parser () Source #

Parse the Integer built-in

This corresponds to the Integer rule from the official grammar

_Double :: Parser () Source #

Parse the Double built-in

This corresponds to the Double rule from the official grammar

_Text :: Parser () Source #

Parse the Text built-in

This corresponds to the Text rule from the official grammar

_TextReplace :: Parser () Source #

Parse the Text/replace built-in

This corresponds to the Text-replace rule from the official grammar

_TextShow :: Parser () Source #

Parse the Text/show built-in

This corresponds to the Text-show rule from the official grammar

_List :: Parser () Source #

Parse the List built-in

This corresponds to the List rule from the official grammar

_True :: Parser () Source #

Parse the True built-in

This corresponds to the True rule from the official grammar

_False :: Parser () Source #

Parse the False built-in

This corresponds to the False rule from the official grammar

_NaN :: Parser () Source #

Parse a NaN literal

This corresponds to the NaN rule from the official grammar

_Type :: Parser () Source #

Parse the Type built-in

This corresponds to the Type rule from the official grammar

_Kind :: Parser () Source #

Parse the Kind built-in

This corresponds to the Kind rule from the official grammar

_Sort :: Parser () Source #

Parse the Sort built-in

This corresponds to the Sort rule from the official grammar

_Location :: Parser () Source #

Parse the Location keyword

This corresponds to the Location rule from the official grammar

_equal :: Parser () Source #

Parse the = symbol

_or :: Parser () Source #

Parse the || symbol

_plus :: Parser () Source #

Parse the + symbol

_textAppend :: Parser () Source #

Parse the ++ symbol

_listAppend :: Parser () Source #

Parse the # symbol

_and :: Parser () Source #

Parse the && symbol

_times :: Parser () Source #

Parse the * symbol

_doubleEqual :: Parser () Source #

Parse the == symbol

_notEqual :: Parser () Source #

Parse the != symbol

_dot :: Parser () Source #

Parse the . symbol

_openBrace :: Parser () Source #

Parse the { symbol

_closeBrace :: Parser () Source #

Parse the } symbol

_openBracket :: Parser () Source #

Parse the [] symbol

_closeBracket :: Parser () Source #

Parse the ] symbol

_openAngle :: Parser () Source #

Parse the < symbol

_closeAngle :: Parser () Source #

Parse the > symbol

_bar :: Parser () Source #

Parse the | symbol

_comma :: Parser () Source #

Parse the , symbol

_openParens :: Parser () Source #

Parse the ( symbol

_closeParens :: Parser () Source #

Parse the ) symbol

_colon :: Parser () Source #

Parse the : symbol

_at :: Parser () Source #

Parse the @ symbol

_equivalent :: Parser () Source #

Parse the equivalence symbol (=== or )

_missing :: Parser () Source #

Parse the missing keyword

_importAlt :: Parser () Source #

Parse the ? symbol

_combine :: Parser CharacterSet Source #

Parse the record combine operator (/\ or )

_combineTypes :: Parser CharacterSet Source #

Parse the record type combine operator (//\\ or )

_prefer :: Parser CharacterSet Source #

Parse the record "prefer" operator (// or )

_lambda :: Parser CharacterSet Source #

Parse a lambda (\ or λ)

_forall :: Parser CharacterSet Source #

Parse a forall (forall or )

_arrow :: Parser CharacterSet Source #

Parse a right arrow (-> or )

_doubleColon :: Parser () Source #

Parse a double colon (::)

_with :: Parser () Source #

Parse the with keyword