Safe Haskell | None |
---|---|
Language | Haskell2010 |
Parsing Dhall expressions.
Synopsis
- getSourcePos :: MonadParsec e s m => m SourcePos
- getOffset :: MonadParsec e s m => m Int
- setOffset :: MonadParsec e s m => Int -> m ()
- src :: Parser a -> Parser Src
- 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)
- parsers :: 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
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
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
Parsers | |
|
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