dhall-1.0.1: A configuration language guaranteed to terminate

Safe HaskellNone
LanguageHaskell98

Dhall

Contents

Description

Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library

Synopsis

Input

input Source

Arguments

:: Type a

The type of value to decode from Dhall to Haskell

-> Text

The Dhall program

-> IO a

The decoded value in Haskell

Type-check and evaluate a Dhall program, decoding the result into Haskell

The first argument determines the type of value that you decode:

>>> input integer "2"
2
>>> input (vector double) "[ 1.0, 2.0 ] : List Bool"
[1.0,2.0]

Use auto to automatically select which type to decode based on the inferred return type:

>>> input auto "True" :: IO Bool
True

detailed :: IO a -> IO a Source

Use this to provide more detailed error messages

> input auto "True" :: IO Integer
 *** Exception: Error: Expression doesn't match annotation
 
 True : Integer
 
 (input):1:1
> detailed (input auto "True") :: IO Integer
 *** Exception: Error: Expression doesn't match annotation
 
 Explanation: You can annotate an expression with its type or kind using the
 ❰:❱ symbol, like this:
 
 
     ┌───────┐
     │ x : t │  ❰x❱ is an expression and ❰t❱ is the annotated type or kind of ❰x❱
     └───────┘
 
 The type checker verifies that the expression's type or kind matches the
 provided annotation
 
 For example, all of the following are valid annotations that the type checker
 accepts:
 
 
     ┌─────────────┐
     │ 1 : Integer │  ❰1❱ is an expression that has type ❰Integer❱, so the type
     └─────────────┘  checker accepts the annotation
 
 
     ┌────────────────────────┐
     │ Natural/even +2 : Bool │  ❰Natural/even +2❱ has type ❰Bool❱, so the type
     └────────────────────────┘  checker accepts the annotation
 
 
     ┌────────────────────┐
     │ List : Type → Type │  ❰List❱ is an expression that has kind ❰Type → Type❱,
     └────────────────────┘  so the type checker accepts the annotation
 
 
     ┌──────────────────┐
     │ List Text : Type │  ❰List Text❱ is an expression that has kind ❰Type❱, so
     └──────────────────┘  the type checker accepts the annotation
 
 
 However, the following annotations are not valid and the type checker will
 reject them:
 
 
     ┌──────────┐
     │ 1 : Text │  The type checker rejects this because ❰1❱ does not have type
     └──────────┘  ❰Text❱
 
 
     ┌─────────────┐
     │ List : Type │  ❰List❱ does not have kind ❰Type❱
     └─────────────┘
 
 
 You or the interpreter annotated this expression:
 
 ↳ True
 
 ... with this type or kind:
 
 ↳ Integer
 
 ... but the inferred type or kind of the expression is actually:
 
 ↳ Bool
 
 Some common reasons why you might get this error:
 
 ● The Haskell Dhall interpreter implicitly inserts a top-level annotation
   matching the expected type
 
   For example, if you run the following Haskell code:
 
 
     ┌───────────────────────────────┐
     │ >>> input auto "1" :: IO Text │
     └───────────────────────────────┘
 
 
   ... then the interpreter will actually type check the following annotated
   expression:
 
 
     ┌──────────┐
     │ 1 : Text │
     └──────────┘
 
 
   ... and then type-checking will fail
 
 ────────────────────────────────────────────────────────────────────────────────
 
 True : Integer
 
 (input):1:1

Types

data Type a Source

A (Type a) represents a way to marshal a value of type 'a' from Dhall into Haskell

You can produce Types either explicitly:

example :: Type (Vector Text)
example = vector text

... or implicitly using auto:

example :: Type (Vector Text)
example = auto

You can consume Types using the input function:

input :: Type a -> Text -> IO a

Instances

class Interpret a where Source

Any value that implements Interpret can be automatically decoded based on the inferred return type of input

>>> input auto "[1, 2, 3 ] : List Integer" :: IO (Vector Integer)
[1,2,3]

This class auto-generates a default implementation for records that implement Generic. This does not auto-generate an instance for sum types nor recursive types.

Minimal complete definition

Nothing

Methods

auto :: Type a Source

bool :: Type Bool Source

Decode a Bool

>>> input bool "True"
True

natural :: Type Natural Source

Decode a Natural

>>> input natural "+42"
42

integer :: Type Integer Source

Decode an Integer

>>> input integer "42"
42

double :: Type Double Source

Decode a Double

>>> input double "42.0"
42.0

text :: Type Text Source

Decode Text

>>> input text "\"Test\""
"Test"

maybe :: Type a -> Type (Maybe a) Source

Decode a Maybe

>>> input (maybe integer) "[1] : Optional Integer"
Just 1

vector :: Type a -> Type (Vector a) Source

Decode a Vector

>>> input (vector integer) "[ 1, 2, 3 ] : List Integer"
[1,2,3]

Re-exports

data Natural :: *

Type representing arbitrary-precision non-negative integers.

Operations whose result would be negative throw (Underflow :: ArithException).

Since: 4.8.0.0

data Vector a :: * -> *

Boxed vectors, supporting efficient slicing.

Instances

Monad Vector 
Functor Vector 
Applicative Vector 
Foldable Vector 
Traversable Vector 
Alternative Vector 
MonadPlus Vector 
Vector Vector a 
IsList (Vector a) 
Eq a => Eq (Vector a) 
Data a => Data (Vector a) 
Ord a => Ord (Vector a) 
Read a => Read (Vector a) 
Show a => Show (Vector a) 
Monoid (Vector a) 
NFData a => NFData (Vector a) 
Ixed (Vector a) 
Wrapped (Vector a) 
Interpret a => Interpret (Vector a) Source 
(~) * t (Vector a') => Rewrapped (Vector a) t 
type Mutable Vector = MVector 
type Item (Vector a) = a 
type Index (Vector a) = Int 
type IxValue (Vector a) = a 
type Unwrapped (Vector a) = [a] 

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic Exp 
Generic Match 
Generic Clause 
Generic Pat 
Generic Type 
Generic Dec 
Generic Name 
Generic FunDep 
Generic TyVarBndr 
Generic () 
Generic Void 
Generic All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic URI 
Generic Con 
Generic Doc 
Generic TextDetails 
Generic Style 
Generic Mode 
Generic WindowBits 
Generic ModName 
Generic PkgName 
Generic Module 
Generic OccName 
Generic NameFlavour 
Generic NameSpace 
Generic Loc 
Generic Info 
Generic ModuleInfo 
Generic Fixity 
Generic FixityDirection 
Generic Lit 
Generic Body 
Generic Guard 
Generic Stmt 
Generic Range 
Generic TySynEqn 
Generic FamFlavour 
Generic Foreign 
Generic Callconv 
Generic Safety 
Generic Pragma 
Generic Inline 
Generic RuleMatch 
Generic Phases 
Generic RuleBndr 
Generic AnnTarget 
Generic Strict 
Generic TyLit 
Generic Role 
Generic AnnLookup 
Generic Caret 
Generic Span 
Generic Fixit 
Generic Strand 
Generic Delta 
Generic Format 
Generic Method 
Generic CompressionLevel 
Generic MemoryLevel 
Generic CompressionStrategy 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (Maybe a) 
Generic (Identity a) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (HistoriedResponse body) 
Generic (WrappedMonoid m) 
Generic (Min a) 
Generic (Max a) 
Generic (First a) 
Generic (Last a) 
Generic (Option a) 
Generic (NonEmpty a) 
Generic (Careted a) 
Generic (Spanned a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (Arg a b) 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (WrappedArrow a b c) 
Generic (Alt k f a) 
Generic (Join k p a) 
Generic (Tagged k s b) 
Generic (M1 i c f p) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (WrappedBifunctor k k1 p a b) 
Generic (Joker k k1 g a b) 
Generic (Flip k k1 p a b) 
Generic (Clown k k1 f a b) 
Generic (a, b, c, d, e, f) 
Generic (Product k k1 f g a b) 
Generic (Sum k k1 p q a b) 
Generic (a, b, c, d, e, f, g) 
Generic (Tannen k k1 k2 f p a b) 
Generic (Biff k k1 k2 k3 p f g a b)