Safe Haskell | None |
---|---|
Language | Haskell2010 |
Please read the Dhall.Tutorial module, which contains a tutorial explaining how to use the language, the compiler, and this library
Synopsis
- input :: Decoder a -> Text -> IO a
- inputWithSettings :: InputSettings -> Decoder a -> Text -> IO a
- inputFile :: Decoder a -> FilePath -> IO a
- inputFileWithSettings :: EvaluateSettings -> Decoder a -> FilePath -> IO a
- inputExpr :: Text -> IO (Expr Src Void)
- inputExprWithSettings :: InputSettings -> Text -> IO (Expr Src Void)
- rootDirectory :: Functor f => LensLike' f InputSettings FilePath
- sourceName :: Functor f => LensLike' f InputSettings FilePath
- startingContext :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Context (Expr Src Void))
- substitutions :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Substitutions Src Void)
- normalizer :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Maybe (ReifiedNormalizer Void))
- newManager :: (Functor f, HasEvaluateSettings s) => LensLike' f s (IO Manager)
- defaultInputSettings :: InputSettings
- data InputSettings
- defaultEvaluateSettings :: EvaluateSettings
- data EvaluateSettings
- class HasEvaluateSettings s where
- evaluateSettings :: Functor f => LensLike' f s EvaluateSettings
- detailed :: IO a -> IO a
- module Dhall.Marshal.Decode
- module Dhall.Marshal.Encode
- rawInput :: Alternative f => Decoder a -> Expr s Void -> f a
Input
:: Decoder a | The decoder for the Dhall value |
-> 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
This uses the settings from defaultInputSettings
.
:: InputSettings | |
-> Decoder a | The decoder for the Dhall value |
-> Text | The Dhall program |
-> IO a | The decoded value in Haskell |
Extend input
with a root directory to resolve imports relative
to, a file to mention in errors as the source, a custom typing
context, and a custom normalization process.
Since: 1.16
:: Decoder a | The decoder for the Dhall value |
-> FilePath | The path to the Dhall program. |
-> IO a | The decoded value in Haskell. |
Type-check and evaluate a Dhall program that is read from the file-system.
This uses the settings from defaultEvaluateSettings
.
Since: 1.16
inputFileWithSettings Source #
:: EvaluateSettings | |
-> Decoder a | The decoder for the Dhall value |
-> FilePath | The path to the Dhall program. |
-> IO a | The decoded value in Haskell. |
Extend inputFile
with a custom typing context and a custom
normalization process.
Since: 1.16
Similar to input
, but without interpreting the Dhall Expr
into a Haskell
type.
Uses the settings from defaultInputSettings
.
inputExprWithSettings Source #
Extend inputExpr
with a root directory to resolve imports relative
to, a file to mention in errors as the source, a custom typing
context, and a custom normalization process.
Since: 1.16
rootDirectory :: Functor f => LensLike' f InputSettings FilePath Source #
Access the directory to resolve imports relative to.
Since: 1.16
sourceName :: Functor f => LensLike' f InputSettings FilePath Source #
Access the name of the source to report locations from; this is only used in error messages, so it's okay if this is a best guess or something symbolic.
Since: 1.16
startingContext :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Context (Expr Src Void)) Source #
Access the starting context used for evaluation and type-checking.
Since: 1.16
substitutions :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Substitutions Src Void) Source #
Access the custom substitutions.
Since: 1.30
normalizer :: (Functor f, HasEvaluateSettings s) => LensLike' f s (Maybe (ReifiedNormalizer Void)) Source #
Access the custom normalizer.
Since: 1.16
newManager :: (Functor f, HasEvaluateSettings s) => LensLike' f s (IO Manager) Source #
Access the HTTP manager initializer.
Since: 1.36
defaultInputSettings :: InputSettings Source #
Default input settings: resolves imports relative to .
(the
current working directory), report errors as coming from (input)
,
and default evaluation settings from defaultEvaluateSettings
.
Since: 1.16
data InputSettings Source #
Since: 1.16
Instances
HasEvaluateSettings InputSettings Source # | |
Defined in Dhall |
defaultEvaluateSettings :: EvaluateSettings Source #
Default evaluation settings: no extra entries in the initial context, and no special normalizer behaviour.
Since: 1.16
data EvaluateSettings Source #
Since: 1.16
Instances
HasEvaluateSettings EvaluateSettings Source # | |
Defined in Dhall |
class HasEvaluateSettings s where Source #
Since: 1.16
evaluateSettings :: Functor f => LensLike' f s EvaluateSettings Source #
Instances
HasEvaluateSettings EvaluateSettings Source # | |
Defined in Dhall | |
HasEvaluateSettings InputSettings Source # | |
Defined in Dhall |
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 : Natural │ ❰1❱ is an expression that has type ❰Natural❱, 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
Decoders
module Dhall.Marshal.Decode
Encoders
module Dhall.Marshal.Encode
Miscellaneous
:: Alternative f | |
=> Decoder a | The decoder for the Dhall value |
-> Expr s Void | a closed form Dhall program, which evaluates to the expected type |
-> f a | The decoded value in Haskell |
Use this function to extract Haskell values directly from Dhall AST.
The intended use case is to allow easy extraction of Dhall values for
making the function normalizeWith
easier to use.
For other use cases, use input
from Dhall module. It will give you
a much better user experience.