Safe Haskell | None |
---|---|
Language | Haskell98 |
This library only exports a single dhallToJSON
function for translating a
Dhall syntax tree to a JSON syntax tree (i.e. a Value
) for the aeson
library
NOTE: The yaml
library uses the same Value
type to represent YAML
files, so you can use this to convert Dhall expressions to YAML, too
See the dhall
package if you would like to transform Dhall source code
into a Dhall syntax tree. Similarly, see the aeson
package if you would
like to translate a JSON syntax tree into JSON.
This package also provides dhall-to-json
and dhall-to-yaml
executables
which you can use to compile Dhall source code directly to JSON or YAML for
your convenience
Not all Dhall expressions can be converted to JSON since JSON is not a programming language. The only things you can convert are:
Bool
sNatural
sInteger
sDouble
sText
List
sOptional
values- unions
- records
Dhall Bool
s translate to JSON bools:
$ dhall-to-json <<< 'True' true $ dhall-to-json <<< 'False' false
Dhall numbers translate to JSON numbers:
$ dhall-to-json <<< '+2' 2 $ dhall-to-json <<< '2' 2 $ dhall-to-json <<< '2.3' 2.3
Dhall Text
translates to JSON text:
$ dhall-to-json <<< '"ABC"' "ABC"
Dhall List
s translate to JSON lists:
$ dhall-to-json <<< '[1, 2, 3] : List Integer' [1,2,3]
Dhall Optional
values translate to null
if absent and the unwrapped
value otherwise:
$ dhall-to-json <<< '[] : Optional Integer' null $ dhall-to-json <<< '[1] : Optional Integer' 1
Dhall records translate to JSON records:
$ dhall-to-json <<< '{ foo = 1, bar = True }' {"foo":1,"bar":true}
Dhall unions translate to the wrapped value:
$ dhall-to-json <<< "< Left = +2 | Right : Natural>" 2 $ cat config [ < Person = { age = +47, name = "John" } | Place : { location : Text } > , < Place = { location = "North Pole" } | Person : { age : Natural, name : Text } > , < Place = { location = "Sahara Desert" } | Person : { age : Natural, name : Text } > , < Person = { age = +35, name = "Alice" } | Place : { location : Text } > ] $ dhall-to-json <<< "./config" [{"age":47,"name":"John"},{"location":"North Pole"},{"location":"Sahara Desert"},{"age":35,"name":"Alice"}]
You can preserve the name of the alternative if you wrap the value in a record with three fields:
contents
: The union literal that you want to preserve the tag offield
: the name of the field that will store the name of the alternativenesting
: A value of type< Inline : {} | Nested : Text >
.
If nesting
is set to Inline
and the union literal stored in contents
contains a record then the name of the alternative is stored inline within
the same record. For example, this code:
let Example = < Left : { foo : Natural } | Right : { bar : Bool } > in let example = constructors Example in let Nesting = < Inline : {} | Nested : Text > in let nesting = constructors Nesting in { field = "name" , nesting = nesting.Inline {=} , contents = example.Left { foo = 2 } }
... produces this JSON:
{ "foo": 2, "name": "Left" }
If nesting
is set to Nested nestedField
then the union is store
underneath a field named nestedField
. For example, this code:
let Example = < Left : { foo : Natural } | Right : { bar : Bool } > in let example = constructors Example in let Nesting = < Inline : {} | Nested : Text > in let nesting = constructors Nesting in { field = "name" , nesting = nesting.Nested "value" , contents = example.Left { foo = 2 } }
... produces this JSON:
{ "name": "Left", "value": { "foo": 2 } }
Also, all Dhall expressions are normalized before translation to JSON:
$ dhall-to-json <<< "True == False" false
Synopsis
- dhallToJSON :: Expr s X -> Either CompileError Value
- omitNull :: Value -> Value
- data Conversion
- = NoConversion
- | Conversion { }
- convertToHomogeneousMaps :: Conversion -> Expr s X -> Expr s X
- parseConversion :: Parser Conversion
- codeToValue :: Conversion -> Text -> Text -> IO Value
- data CompileError = Unsupported (Expr X X)
Dhall to JSON
dhallToJSON :: Expr s X -> Either CompileError Value Source #
Convert a Dhall expression to the equivalent JSON expression
>>>
:set -XOverloadedStrings
>>>
:set -XOverloadedLists
>>>
import Dhall.Core
>>>
dhallToJSON (RecordLit [("foo", IntegerLit 1), ("bar", TextLit "ABC")])
Right (Object (fromList [("foo",Number 1.0),("bar",String "ABC")]))>>>
fmap Data.Aeson.encode it
Right "{\"foo\":1,\"bar\":\"ABC\"}"
data Conversion Source #
Specify whether or not to convert association lists of type
List { mapKey: Text, mapValue : v }
to records
convertToHomogeneousMaps :: Conversion -> Expr s X -> Expr s X Source #
Convert association lists to homogeneous maps
This converts an association list of the form:
[ { mapKey = k0, mapValue = v0 }, { mapKey = k1, mapValue = v1 } ]
... to a record of the form:
{ k0 = v0, k1 = v1 }
:: Conversion | |
-> Text | Describe the input for the sake of error location. |
-> Text | Input text. |
-> IO Value |
Convert a piece of Text carrying a Dhall inscription to an equivalent JSON Value
>>>
:set -XOverloadedStrings
>>>
import Dhall.Core
>>>
Dhall.JSON.codeToValue "(stdin)" "{ a = 1 }"
>>>
Object (fromList [("a",Number 1.0)])
Exceptions
data CompileError Source #
This is the exception type for errors that might arise when translating Dhall to JSON
Because the majority of Dhall language features do not translate to JSON this just returns the expression that failed
Unsupported (Expr X X) |
Instances
Show CompileError Source # | |
Defined in Dhall.JSON showsPrec :: Int -> CompileError -> ShowS # show :: CompileError -> String # showList :: [CompileError] -> ShowS # | |
Exception CompileError Source # | |
Defined in Dhall.JSON |