Safe Haskell | None |
---|---|
Language | Haskell2010 |
Parse Dhall tokens. Even though we don't have a tokenizer per-se this
Synopsis
- validCodepoint :: Int -> Bool
- whitespace :: Parser ()
- nonemptyWhitespace :: Parser ()
- bashEnvironmentVariable :: Parser Text
- posixEnvironmentVariable :: Parser Text
- data ComponentType
- text :: Text -> Parser Text
- char :: Char -> Parser Char
- file_ :: ComponentType -> Parser File
- label :: Parser Text
- anyLabel :: Parser Text
- labels :: Parser (Set Text)
- httpRaw :: Parser URL
- hexdig :: Char -> Bool
- identifier :: Parser Var
- hexNumber :: Parser Int
- doubleLiteral :: Parser Double
- doubleInfinity :: Parser Double
- naturalLiteral :: Parser Natural
- integerLiteral :: Parser Integer
- _Optional :: Parser ()
- _if :: Parser ()
- _then :: Parser ()
- _else :: Parser ()
- _let :: Parser ()
- _in :: Parser ()
- _as :: Parser ()
- _using :: Parser ()
- _merge :: Parser ()
- _toMap :: Parser ()
- _assert :: Parser ()
- _Some :: Parser ()
- _None :: Parser ()
- _NaturalFold :: Parser ()
- _NaturalBuild :: Parser ()
- _NaturalIsZero :: Parser ()
- _NaturalEven :: Parser ()
- _NaturalOdd :: Parser ()
- _NaturalToInteger :: Parser ()
- _NaturalShow :: Parser ()
- _NaturalSubtract :: Parser ()
- _IntegerClamp :: Parser ()
- _IntegerNegate :: Parser ()
- _IntegerShow :: Parser ()
- _IntegerToDouble :: Parser ()
- _DoubleShow :: Parser ()
- _ListBuild :: Parser ()
- _ListFold :: Parser ()
- _ListLength :: Parser ()
- _ListHead :: Parser ()
- _ListLast :: Parser ()
- _ListIndexed :: Parser ()
- _ListReverse :: Parser ()
- _OptionalFold :: Parser ()
- _OptionalBuild :: Parser ()
- _Bool :: Parser ()
- _Natural :: Parser ()
- _Integer :: Parser ()
- _Double :: Parser ()
- _Text :: Parser ()
- _TextShow :: Parser ()
- _List :: Parser ()
- _True :: Parser ()
- _False :: Parser ()
- _NaN :: Parser ()
- _Type :: Parser ()
- _Kind :: Parser ()
- _Sort :: Parser ()
- _Location :: Parser ()
- _equal :: Parser ()
- _or :: Parser ()
- _plus :: Parser ()
- _textAppend :: Parser ()
- _listAppend :: Parser ()
- _and :: Parser ()
- _times :: Parser ()
- _doubleEqual :: Parser ()
- _notEqual :: Parser ()
- _dot :: Parser ()
- _openBrace :: Parser ()
- _closeBrace :: Parser ()
- _openBracket :: Parser ()
- _closeBracket :: Parser ()
- _openAngle :: Parser ()
- _closeAngle :: Parser ()
- _bar :: Parser ()
- _comma :: Parser ()
- _openParens :: Parser ()
- _closeParens :: Parser ()
- _colon :: Parser ()
- _at :: Parser ()
- _equivalent :: Parser ()
- _missing :: Parser ()
- _importAlt :: Parser ()
- _combine :: Parser ()
- _combineTypes :: Parser ()
- _prefer :: Parser ()
- _lambda :: Parser ()
- _forall :: Parser ()
- _arrow :: Parser ()
- _doubleColon :: Parser ()
- _with :: Parser ()
Documentation
whitespace :: Parser () Source #
Parse 0 or more whitespace characters (including comments)
This corresponds to the whsp
rule in the official grammar
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
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
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 (Set 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
doubleLiteral :: Parser Double Source #
Parse a Expr
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 Expr
literal
This corresponds to the natural-literal
rule from the official grammar
integerLiteral :: Parser Integer Source #
Parse an Expr
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
Parse the if
keyword
This corresponds to the if
rule from the official grammar
Parse the then
keyword
This corresponds to the then
rule from the official grammar
Parse the else
keyword
This corresponds to the else
rule from the official grammar
Parse the let
keyword
This corresponds to the let
rule from the official grammar
Parse the in
keyword
This corresponds to the in
rule from the official grammar
Parse the as
keyword
This corresponds to the as
rule from the official grammar
Parse the using
keyword
This corresponds to the using
rule from the official grammar
Parse the merge
keyword
This corresponds to the merge
rule from the official grammar
Parse the toMap
keyword
This corresponds to the toMap
rule from the official grammar
Parse the assert
keyword
This corresponds to the assert
rule from the official grammar
Parse the Some
built-in
This corresponds to the Some
rule from the official grammar
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
_OptionalFold :: Parser () Source #
Parse the Optional/fold
built-in
This corresponds to the Optional-fold
rule from the official grammar
_OptionalBuild :: Parser () Source #
Parse the Optional/build
built-in
This corresponds to the Optional-build
rule from the official grammar
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
Parse the Double
built-in
This corresponds to the Double
rule from the official grammar
Parse the Text
built-in
This corresponds to the Text
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
Parse the List
built-in
This corresponds to the List
rule from the official grammar
Parse the True
built-in
This corresponds to the True
rule from the official grammar
Parse the False
built-in
This corresponds to the False
rule from the official grammar
Parse a NaN
literal
This corresponds to the NaN
rule from the official grammar
Parse the Type
built-in
This corresponds to the Type
rule from the official grammar
Parse the Kind
built-in
This corresponds to the Kind
rule from the official grammar
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
_textAppend :: Parser () Source #
Parse the ++
symbol
_listAppend :: Parser () Source #
Parse the #
symbol
_doubleEqual :: 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
_openParens :: Parser () Source #
Parse the (
symbol
_closeParens :: Parser () Source #
Parse the )
symbol
_equivalent :: Parser () Source #
Parse the equivalence symbol (===
or ≡
)
_importAlt :: Parser () Source #
Parse the ?
symbol
_combineTypes :: Parser () Source #
Parse the record type combine operator (//\\
or ⩓
)
_doubleColon :: Parser () Source #
Parse a double colon (::
)