{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier0.Mantle where
import qualified Data.List as L
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Maybe as Y
import Hydra.Dsl.Annotations
import Hydra.Dsl.Bootstrap
import qualified Hydra.Dsl.Terms as Terms
import Hydra.Dsl.Types as Types
import Hydra.Sources.Core
hydraMantleModule :: Module
hydraMantleModule :: Module
hydraMantleModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module Namespace
ns [Element]
elements [Module
hydraCoreModule] [Module
hydraCoreModule] (Maybe String -> Module) -> Maybe String -> Module
forall a b. (a -> b) -> a -> b
$
String -> Maybe String
forall a. a -> Maybe a
Just String
"A set of types which supplement hydra/core with type variants, graphs, and elements"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/mantle"
core :: String -> Type
core = Namespace -> String -> Type
typeref (Namespace -> String -> Type) -> Namespace -> String -> Type
forall a b. (a -> b) -> a -> b
$ Module -> Namespace
moduleNamespace Module
hydraCoreModule
mantle :: String -> Type
mantle = Namespace -> String -> Type
typeref Namespace
ns
def :: String -> Type -> Element
def = Namespace -> String -> Type -> Element
datatype Namespace
ns
elements :: [Element]
elements = [
String -> Type -> Element
def String
"Either" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A disjoint union between a 'left' type and a 'right' type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
lambda String
"a" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"b" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
union [
String
"left"String -> Type -> FieldType
>: Type
"a",
String
"right"String -> Type -> FieldType
>: Type
"b"],
String -> Type -> Element
def String
"EliminationVariant" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The identifier of an elimination constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [
String
"list",
String
"optional",
String
"product",
String
"record",
String
"union",
String
"wrap"],
String -> Type -> Element
def String
"FunctionVariant" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The identifier of a function constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [
String
"elimination",
String
"lambda",
String
"primitive"],
String -> Type -> Element
def String
"LiteralVariant" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The identifier of a literal constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [
String
"binary",
String
"boolean",
String
"float",
String
"integer",
String
"string"],
String -> Type -> Element
def String
"Precision" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Numeric precision: arbitrary precision, or precision to a specified number of bits" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"arbitrary"String -> Type -> FieldType
>: Type
unit,
String
"bits"String -> Type -> FieldType
>: Type
int32],
String -> Type -> Element
def String
"TermVariant" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The identifier of a term expression constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [
String
"annotated",
String
"application",
String
"function",
String
"let",
String
"list",
String
"literal",
String
"map",
String
"optional",
String
"product",
String
"record",
String
"set",
String
"sum",
String
"typed",
String
"union",
String
"variable",
String
"wrap"],
String -> Type -> Element
def String
"TypeVariant" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The identifier of a type constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [
String
"annotated",
String
"application",
String
"function",
String
"lambda",
String
"list",
String
"literal",
String
"map",
String
"optional",
String
"product",
String
"record",
String
"set",
String
"sum",
String
"union",
String
"variable",
String
"wrap"]]