| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Dhall.Parser.Expression
Description
Parsing Dhall expressions.
Synopsis
- getOffset :: MonadParsec e s m => m Int
- setOffset :: MonadParsec e s m => Int -> m ()
- src :: Parser a -> Parser Src
- srcAnd :: Parser a -> Parser (Src, a)
- noted :: Parser (Expr Src a) -> Parser (Expr Src a)
- completeExpression :: Parser a -> Parser (Expr Src a)
- importExpression :: Parser a -> Parser (Expr Src a)
- data Parsers a = Parsers {- completeExpression_ :: Parser (Expr Src a)
- importExpression_ :: Parser (Expr Src a)
- letBinding :: Parser (Binding Src a)
 
- timeNumOffset :: Parser (Expr s a)
- timeOffset :: Parser (Expr s a)
- partialTime :: Parser (Expr s a)
- fullDate :: Parser (Expr s a)
- temporalLiteral :: Parser (Expr s a)
- shebang :: Parser ()
- parsers :: forall a. Parser a -> Parsers a
- env :: Parser ImportType
- localOnly :: Parser ImportType
- local :: Parser ImportType
- http :: Parser ImportType
- missing :: Parser ImportType
- importType_ :: Parser ImportType
- importHash_ :: Parser SHA256Digest
- importHashed_ :: Parser ImportHashed
- import_ :: Parser Import
- data ApplicationExprInfo
Documentation
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
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
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
Constructors
| Parsers | |
| Fields 
 | |
timeNumOffset :: Parser (Expr s a) Source #
Parse a numeric TimeZone
This corresponds to the time-numoffset rule from the official grammar
timeOffset :: Parser (Expr s a) Source #
Parse a numeric TimeZone or a Z
This corresponds to the time-offset rule from the official grammar
partialTime :: Parser (Expr s a) Source #
Parse a Time
This corresponds to the partial-time rule from the official grammar
fullDate :: Parser (Expr s a) Source #
Parse a Date
This corresponds to the full-date rule from the official grammar
temporalLiteral :: Parser (Expr s a) Source #
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
data ApplicationExprInfo Source #
ApplicationExprInfo distinguishes certain subtypes of application
 expressions.
Constructors
| NakedMergeOrSomeOrToMap | 
 | 
| ImportExpr | An import expression. | 
| ApplicationExpr | Any other application expression. |