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

Dhall.Parser

Description

This module contains Dhall's parsing logic

Synopsis

Utilities

exprFromText Source #

Arguments

:: String

User-friendly name describing the input expression, used in parsing error messages

-> Text

Input expression to parse

-> Either ParseError (Expr Src Import) 

Parse an expression from Text containing a Dhall program

exprAndHeaderFromText Source #

Arguments

:: String

User-friendly name describing the input expression, used in parsing error messages

-> Text

Input expression to parse

-> Either ParseError (Header, Expr Src Import) 

Like exprFromText but also returns the leading comments and whitespace (i.e. header) up to the last newline before the code begins

In other words, if you have a Dhall file of the form:

-- Comment 1
{- Comment -} 2

Then this will preserve Comment 1, but not Comment 2

This is used by dhall-format to preserve leading comments and whitespace

censor :: ParseError -> ParseError Source #

Replace the source code with spaces when rendering error messages

This utility is used to implement the --censor flag

createHeader :: Text -> Header Source #

Create a header with stripped leading spaces and trailing newlines

Parsers

expr :: Parser (Expr Src Import) Source #

Parser for a top-level Dhall expression

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

Deprecated: Support for parsing custom imports will be dropped in a future release

Parser for a top-level Dhall expression. The expression is parameterized over any parseable type, allowing the language to be extended as needed.

Types

newtype Header Source #

A header corresponds to the leading comment at the top of a Dhall file.

The header includes comment characters but is stripped of leading spaces and trailing newlines

Constructors

Header Text 

Instances

Instances details
Show Header Source # 
Instance details

Defined in Dhall.Parser

data Src Source #

Source code extract

Constructors

Src 

Instances

Instances details
Eq Src Source # 
Instance details

Defined in Dhall.Src

Methods

(==) :: Src -> Src -> Bool #

(/=) :: Src -> Src -> Bool #

Data Src Source # 
Instance details

Defined in Dhall.Src

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Src -> c Src #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Src #

toConstr :: Src -> Constr #

dataTypeOf :: Src -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Src) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Src) #

gmapT :: (forall b. Data b => b -> b) -> Src -> Src #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Src -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Src -> r #

gmapQ :: (forall d. Data d => d -> u) -> Src -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Src -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Src -> m Src #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Src -> m Src #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Src -> m Src #

Ord Src Source # 
Instance details

Defined in Dhall.Src

Methods

compare :: Src -> Src -> Ordering #

(<) :: Src -> Src -> Bool #

(<=) :: Src -> Src -> Bool #

(>) :: Src -> Src -> Bool #

(>=) :: Src -> Src -> Bool #

max :: Src -> Src -> Src #

min :: Src -> Src -> Src #

Show Src Source # 
Instance details

Defined in Dhall.Src

Methods

showsPrec :: Int -> Src -> ShowS #

show :: Src -> String #

showList :: [Src] -> ShowS #

Generic Src Source # 
Instance details

Defined in Dhall.Src

Associated Types

type Rep Src :: Type -> Type #

Methods

from :: Src -> Rep Src x #

to :: Rep Src x -> Src #

NFData Src Source # 
Instance details

Defined in Dhall.Src

Methods

rnf :: Src -> () #

Pretty Src Source # 
Instance details

Defined in Dhall.Src

Methods

pretty :: Src -> Doc ann #

prettyList :: [Src] -> Doc ann #

Lift Src Source # 
Instance details

Defined in Dhall.Src

Methods

lift :: Src -> Q Exp #

liftTyped :: Src -> Q (TExp Src) #

type Rep Src Source # 
Instance details

Defined in Dhall.Src

type Rep Src = D1 ('MetaData "Src" "Dhall.Src" "dhall-1.38.0-DqkKc1wi0jW9R5LnT6BXmA" 'False) (C1 ('MetaCons "Src" 'PrefixI 'True) (S1 ('MetaSel ('Just "srcStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "srcEnd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "srcText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data SourcedException e Source #

An exception annotated with a Src span

Constructors

SourcedException Src e 

data ParseError Source #

A parsing error

Constructors

ParseError 

newtype Parser a Source #

A Parser that is almost identical to Text.Megaparsec.Parsec except treating Haskell-style comments as whitespace

Constructors

Parser 

Fields

Instances

Instances details
Monad Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

Functor Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

MonadFail Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

fail :: String -> Parser a #

Applicative Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

TokenParsing Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

CharParsing Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Parsing Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

try :: Parser a -> Parser a #

(<?>) :: Parser a -> String -> Parser a #

skipMany :: Parser a -> Parser () #

skipSome :: Parser a -> Parser () #

unexpected :: String -> Parser a #

eof :: Parser () #

notFollowedBy :: Show a => Parser a -> Parser () #

MonadParsec Void Text Parser Source # 
Instance details

Defined in Dhall.Parser.Combinators

IsString a => IsString (Parser a) Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

fromString :: String -> Parser a #

Semigroup a => Semigroup (Parser a) Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

(<>) :: Parser a -> Parser a -> Parser a #

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

(Semigroup a, Monoid a) => Monoid (Parser a) Source # 
Instance details

Defined in Dhall.Parser.Combinators

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #