module Hydra.Impl.Haskell.Sources.Ext.Json.Model where
import Hydra.Impl.Haskell.Sources.Core
import Hydra.All
import Hydra.Impl.Haskell.Dsl.Types as Types
import Hydra.Impl.Haskell.Dsl.Standard
jsonModelModule :: Module Meta
jsonModelModule :: Module Meta
jsonModelModule = forall m.
Namespace -> [Element m] -> [Module m] -> Maybe String -> Module m
Module Namespace
ns [Element Meta]
elements [] forall a b. (a -> b) -> a -> b
$
forall a. a -> Maybe a
Just String
"A JSON syntax model. See the BNF at https://www.json.org"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/ext/json/model"
def :: String -> Type m -> Element m
def = forall m. Namespace -> String -> Type m -> Element m
datatype Namespace
ns
json :: String -> Type m
json = forall m. Namespace -> String -> Type m
nsref Namespace
ns
elements :: [Element Meta]
elements = [
forall {m}. String -> Type m -> Element m
def String
"Value" forall a b. (a -> b) -> a -> b
$
String -> Type Meta -> Type Meta
doc String
"A JSON value" forall a b. (a -> b) -> a -> b
$
forall m. [FieldType m] -> Type m
union [
String
"array"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
json String
"Value",
String
"boolean"forall m. String -> Type m -> FieldType m
>: forall m. Type m
boolean,
String
"null"forall m. String -> Type m -> FieldType m
>: forall m. Type m
unit,
String
"number"forall m. String -> Type m -> FieldType m
>: forall m. Type m
bigfloat,
String
"object"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m -> Type m
Types.map forall m. Type m
string (forall {m}. String -> Type m
json String
"Value"),
String
"string"forall m. String -> Type m -> FieldType m
>: forall m. Type m
string]]