module Hydra.Impl.Haskell.Sources.Ext.Yaml.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
yamlModelModule :: Module Meta
yamlModelModule :: Module Meta
yamlModelModule = 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 basic YAML representation model. Based on:\n" forall a. [a] -> [a] -> [a]
++
String
" https://yaml.org/spec/1.2/spec.html\n" forall a. [a] -> [a] -> [a]
++
String
"The Serialization and Presentation properties of YAML,\n" forall a. [a] -> [a] -> [a]
++
String
"including directives, comments, anchors, style, formatting, and aliases, are not supported by this model.\n" forall a. [a] -> [a] -> [a]
++
String
"In addition, tags are omitted from this model, and non-standard scalars are unsupported.")
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/ext/yaml/model"
def :: String -> Type m -> Element m
def = forall m. Namespace -> String -> Type m -> Element m
datatype Namespace
ns
model :: String -> Type m
model = forall m. Namespace -> String -> Type m
nsref Namespace
ns
elements :: [Element Meta]
elements = [
forall {m}. String -> Type m -> Element m
def String
"Node" forall a b. (a -> b) -> a -> b
$
String -> Type Meta -> Type Meta
doc String
"A YAML node (value)" forall a b. (a -> b) -> a -> b
$
forall m. [FieldType m] -> Type m
union [
String
"mapping"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m -> Type m
Types.map (forall {m}. String -> Type m
model String
"Node") (forall {m}. String -> Type m
model String
"Node"),
String
"scalar"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
model String
"Scalar",
String
"sequence"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
model String
"Node"],
forall {m}. String -> Type m -> Element m
def String
"Scalar" forall a b. (a -> b) -> a -> b
$
String -> Type Meta -> Type Meta
doc String
"A union of scalars supported in the YAML failsafe and JSON schemas. Other scalars are not supported here" forall a b. (a -> b) -> a -> b
$
forall m. [FieldType m] -> Type m
union [
String
"bool"forall m. String -> Type m -> FieldType m
>:
String -> Type Meta -> Type Meta
doc String
"Represents a true/false value"
forall m. Type m
boolean,
String
"float"forall m. String -> Type m -> FieldType m
>:
String -> Type Meta -> Type Meta
doc String
"Represents an approximation to real numbers"
forall m. Type m
bigfloat,
String
"int"forall m. String -> Type m -> FieldType m
>:
String -> Type Meta -> Type Meta
doc String
"Represents arbitrary sized finite mathematical integers"
forall m. Type m
bigint,
String
"null"forall m. String -> Type m -> FieldType m
>:
String -> Type Meta -> Type Meta
doc String
"Represents the lack of a value"
forall m. Type m
unit,
String
"str"forall m. String -> Type m -> FieldType m
>:
String -> Type Meta -> Type Meta
doc String
"A string value"
forall m. Type m
string]]