dhall-1.30.0: A configuration language guaranteed to terminate

Safe HaskellNone
LanguageHaskell2010

Dhall.Parser.Expression

Description

Parsing Dhall expressions.

Synopsis

Documentation

getSourcePos :: MonadParsec e s m => m SourcePos Source #

Get the current source position

getOffset :: MonadParsec e s m => m Int Source #

Get the current source offset (in tokens)

setOffset :: MonadParsec e s m => Int -> m () Source #

Set the current source offset

src :: Parser a -> Parser Src Source #

Wrap a Parser to still match the same text but return only the Src span

noted :: Parser (Expr Src a) -> Parser (Expr Src a) Source #

Wrap a Parser to still match the same text, but to wrap the resulting Expr in a Note constructor containing the Src span

completeExpression :: Parser a -> Parser (Expr Src a) Source #

Parse a complete expression (with leading and trailing whitespace)

This corresponds to the complete-expression rule from the official grammar

importExpression :: Parser a -> Parser (Expr Src a) Source #

Parse an "import expression"

This is not the same thing as fmap Embed. This parses any expression of the same or higher precedence as an import expression (such as a selector expression). For example, this parses (1)

This corresponds to the import-expression rule from the official grammar

data Parsers a Source #

For efficiency (and simplicity) we only expose two parsers from the result of the parsers function, since these are the only parsers needed outside of this module

parsers :: Parser a -> Parsers a Source #

Given a parser for imports,

env :: Parser ImportType Source #

Parse an environment variable import

This corresponds to the env rule from the official grammar

localOnly :: Parser ImportType Source #

Parse a local import without trailing whitespace

local :: Parser ImportType Source #

Parse a local import

This corresponds to the local rule from the official grammar

http :: Parser ImportType Source #

Parse an HTTP(S) import

This corresponds to the http rule from the official grammar

missing :: Parser ImportType Source #

Parse a Missing import

This corresponds to the missing rule from the official grammar

importType_ :: Parser ImportType Source #

Parse an ImportType

This corresponds to the import-type rule from the official grammar

importHash_ :: Parser SHA256Digest Source #

Parse a SHA256Digest

This corresponds to the hash rule from the official grammar

importHashed_ :: Parser ImportHashed Source #

Parse an ImportHashed

This corresponds to the import-hashed rule from the official grammar

import_ :: Parser Import Source #

Parse an Import

This corresponds to the import rule from the official grammar