Safe Haskell | None |
---|---|
Language | Haskell98 |
Dhall
Contents
Description
Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library
- input :: Type a -> Text -> IO a
- detailed :: IO a -> IO a
- data Type a
- class Interpret a where
- data InvalidType = InvalidType
- auto :: Interpret a => Type a
- data InterpretOptions = InterpretOptions {
- fieldModifier :: Text -> Text
- constructorModifier :: Text -> Text
- defaultInterpretOptions :: InterpretOptions
- bool :: Type Bool
- natural :: Type Natural
- integer :: Type Integer
- double :: Type Double
- text :: Type Text
- maybe :: Type a -> Type (Maybe a)
- vector :: Type a -> Type (Vector a)
- class GenericInterpret f where
- data Natural :: *
- data Text :: *
- data Vector a :: * -> *
- class Generic a
Input
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]"
[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
A (Type a)
represents a way to marshal a value of type 'a'
from Dhall
into Haskell
You can produce Type
s either explicitly:
example :: Type (Vector Text) example = vector text
... or implicitly using auto
:
example :: Type (Vector Text) example = auto
You can consume Type
s using the input
function:
input :: Type a -> Text -> IO a
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]" :: 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 recursive
types.
Methods
autoWith :: InterpretOptions -> Type a Source #
autoWith :: (Generic a, GenericInterpret (Rep a)) => InterpretOptions -> Type a Source #
data InvalidType Source #
Every Type
must obey the contract that if an expression's type matches the
the expected
type then the extract
function must succeed. If not, then
this exception is thrown
This exception indicates that an invalid Type
was provided to the input
function
Constructors
InvalidType |
Instances
auto :: Interpret a => Type a Source #
Use the default options for interpreting a configuration file
auto = autoWith defaultInterpretOptions
data InterpretOptions Source #
Use these options to tweak how Dhall derives a generic implementation of
Interpret
Constructors
InterpretOptions | |
Fields
|
defaultInterpretOptions :: InterpretOptions Source #
Default interpret options, which you can tweak or override, like this:
autoWith (defaultInterpretOptions { fieldModifier = Data.Text.Lazy.dropWhile (== '_') })
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]"
[1,2,3]
class GenericInterpret f where Source #
This is the underlying class that powers the Interpret
class's support
for automatically deriving a generic implementation
Minimal complete definition
Methods
genericAutoWith :: InterpretOptions -> Type (f a) Source #
Instances
GenericInterpret V1 Source # | |
GenericInterpret U1 Source # | |
(Constructor Meta c, GenericInterpret f, GenericInterpret ((:+:) g h)) => GenericInterpret ((:+:) (M1 C c f) ((:+:) g h)) Source # | |
(Constructor Meta c1, Constructor Meta c2, GenericInterpret f1, GenericInterpret f2) => GenericInterpret ((:+:) (M1 C c1 f1) (M1 C c2 f2)) Source # | |
(GenericInterpret ((:+:) f g), GenericInterpret ((:+:) h i)) => GenericInterpret ((:+:) ((:+:) f g) ((:+:) h i)) Source # | |
(Constructor Meta c, GenericInterpret ((:+:) f g), GenericInterpret h) => GenericInterpret ((:+:) ((:+:) f g) (M1 C c h)) Source # | |
(GenericInterpret f, GenericInterpret g) => GenericInterpret ((:*:) f g) Source # | |
GenericInterpret f => GenericInterpret (M1 D d f) Source # | |
GenericInterpret f => GenericInterpret (M1 C c f) Source # | |
(Selector Meta s, Interpret a) => GenericInterpret (M1 S s (K1 i a)) Source # | |
Re-exports
Type representing arbitrary-precision non-negative integers.
Operations whose result would be negative
.throw
(Underflow
:: ArithException
)
Since: 4.8.0.0
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 | |
type Item (Vector a) | |
type Index (Vector a) | |
type IxValue (Vector a) | |
type Unwrapped (Vector a) | |
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Instances