{-# LANGUAGE OverloadedStrings #-}

module Hydra.Impl.Haskell.Sources.Mantle where

import Hydra.Kernel
import Hydra.Impl.Haskell.Dsl.Types as Types
import Hydra.Impl.Haskell.Dsl.Standard
import Hydra.Impl.Haskell.Sources.Core


hydraMantleModule :: Module Meta
hydraMantleModule :: Module Meta
hydraMantleModule = 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 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 m
core = forall m. Namespace -> String -> Type m
nsref forall a b. (a -> b) -> a -> b
$ forall m. Module m -> Namespace
moduleNamespace Module Meta
hydraCoreModule
    mantle :: String -> Type m
mantle = forall m. Namespace -> String -> Type m
nsref Namespace
ns
    def :: String -> Type m -> Element m
def = forall m. Namespace -> String -> Type m -> Element m
datatype Namespace
ns

    elements :: [Element Meta]
elements = [

      forall {m}. String -> Type m -> Element m
def String
"Comparison" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"An equality judgement: less than, equal to, or greater than" forall a b. (a -> b) -> a -> b
$
        forall m. [String] -> Type m
enum [
          String
"lessThan",
          String
"equalTo",
          String
"greaterThan"],

      forall {m}. String -> Type m -> Element m
def String
"Element" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"A graph element, having a name, data term (value), and schema term (type)" forall a b. (a -> b) -> a -> b
$
        forall m. String -> Type m -> Type m
lambda String
"m" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
          String
"name"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
core String
"Name",
          String
"schema"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
core String
"Term" forall m. Type m -> Type m -> Type m
@@ Type Meta
"m",
          String
"data"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
core String
"Term" forall m. Type m -> Type m -> Type m
@@ Type Meta
"m"],

      forall {m}. String -> Type m -> Element m
def String
"EliminationVariant" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"The identifier of an elimination constructor" forall a b. (a -> b) -> a -> b
$
        forall m. [String] -> Type m
enum [
          String
"element",
          String
"list",
          String
"nominal",
          String
"optional",
          String
"record",
          String
"union"],

      forall {m}. String -> Type m -> Element m
def String
"FunctionVariant" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"The identifier of a function constructor" forall a b. (a -> b) -> a -> b
$
        forall m. [String] -> Type m
enum [
          String
"compareTo",
          String
"elimination",
          String
"lambda",
          String
"primitive"],

      forall {m}. String -> Type m -> Element m
def String
"Graph" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc (String
"A graph, or set of named terms, together with its schema graph") forall a b. (a -> b) -> a -> b
$
        forall m. String -> Type m -> Type m
lambda String
"m" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
          String
"elements"forall m. String -> Type m -> FieldType m
>:
            String -> Type Meta -> Type Meta
doc String
"All of the elements in the graph" forall a b. (a -> b) -> a -> b
$
            forall m. Type m -> Type m -> Type m
Types.map (forall {m}. String -> Type m
core String
"Name") (forall {m}. String -> Type m
mantle String
"Element" forall m. Type m -> Type m -> Type m
@@ Type Meta
"m"),
          String
"schema"forall m. String -> Type m -> FieldType m
>:
            String -> Type Meta -> Type Meta
doc String
"The schema graph to this graph. If omitted, the graph is its own schema graph." forall a b. (a -> b) -> a -> b
$
            forall m. Type m -> Type m
optional forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
mantle String
"Graph" forall m. Type m -> Type m -> Type m
@@ Type Meta
"m"],

      forall {m}. String -> Type m -> Element m
def String
"LiteralVariant" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"The identifier of a literal constructor" forall a b. (a -> b) -> a -> b
$
        forall m. [String] -> Type m
enum [
          String
"binary",
          String
"boolean",
          String
"float",
          String
"integer",
          String
"string"],

      forall {m}. String -> Type m -> Element m
def String
"Precision" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"Numeric precision: arbitrary precision, or precision to a specified number of bits" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
union [
          String
"arbitrary"forall m. String -> Type m -> FieldType m
>: forall m. Type m
unit,
          String
"bits"forall m. String -> Type m -> FieldType m
>: forall m. Type m
int32],

      forall {m}. String -> Type m -> Element m
def String
"TermVariant" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"The identifier of a term expression constructor" forall a b. (a -> b) -> a -> b
$
        forall m. [String] -> Type m
enum [
          String
"annotated",
          String
"application",
          String
"element",
          String
"function",
          String
"let",
          String
"list",
          String
"literal",
          String
"map",
          String
"nominal",
          String
"optional",
          String
"product",
          String
"record",
          String
"set",
          String
"stream",
          String
"sum",
          String
"union",
          String
"variable"],

      forall {m}. String -> Type m -> Element m
def String
"TypeScheme" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"A type expression together with free type variables occurring in the expression" forall a b. (a -> b) -> a -> b
$
        forall m. String -> Type m -> Type m
lambda String
"m" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
          String
"variables"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
core String
"VariableType",
          String
"type"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
core String
"Type" forall m. Type m -> Type m -> Type m
@@ Type Meta
"m"],

      forall {m}. String -> Type m -> Element m
def String
"TypeVariant" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"The identifier of a type constructor" forall a b. (a -> b) -> a -> b
$
        forall m. [String] -> Type m
enum [
          String
"annotated",
          String
"application",
          String
"element",
          String
"function",
          String
"lambda",
          String
"list",
          String
"literal",
          String
"map",
          String
"nominal",
          String
"optional",
          String
"product",
          String
"record",
          String
"set",
          String
"stream",
          String
"sum",
          String
"union",
          String
"variable"],

      forall {m}. String -> Type m -> Element m
def String
"TypedTerm" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
doc String
"A type together with an instance of the type" forall a b. (a -> b) -> a -> b
$
        forall m. String -> Type m -> Type m
lambda String
"m" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
          String
"type"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
core String
"Type" forall m. Type m -> Type m -> Type m
@@ Type Meta
"m",
          String
"term"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
core String
"Term" forall m. Type m -> Type m -> Type m
@@ Type Meta
"m"]]