{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier0.Compute 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
hydraComputeModule :: Module
hydraComputeModule :: Module
hydraComputeModule = 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
"Abstractions for single- and bidirectional transformations"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/compute"
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
compute :: String -> Type
compute = 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
"Adapter" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A two-level bidirectional encoder which adapts types to types and terms to terms" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
lambda String
"s1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"s2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"t1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"t2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"v1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"v2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
record [
String
"isLossy"String -> Type -> FieldType
>: Type
boolean,
String
"source"String -> Type -> FieldType
>: String -> Type
var String
"t1",
String
"target"String -> Type -> FieldType
>: String -> Type
var String
"t2",
String
"coder"String -> Type -> FieldType
>: String -> Type
compute String
"Coder" Type -> Type -> Type
@@ Type
"s1" Type -> Type -> Type
@@ Type
"s2" Type -> Type -> Type
@@ Type
"v1" Type -> Type -> Type
@@ Type
"v2"],
String -> Type -> Element
def String
"Bicoder" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A two-level encoder and decoder, operating both at a type level and an instance (data) level" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
lambda String
"s1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"s2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"t1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"t2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"v1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"v2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
record [
String
"encode"String -> Type -> FieldType
>: Type
"t1" Type -> Type -> Type
--> String -> Type
compute String
"Adapter" Type -> Type -> Type
@@ Type
"s1" Type -> Type -> Type
@@ Type
"s2" Type -> Type -> Type
@@ Type
"t1" Type -> Type -> Type
@@ Type
"t2" Type -> Type -> Type
@@ Type
"v1" Type -> Type -> Type
@@ Type
"v2",
String
"decode"String -> Type -> FieldType
>: Type
"t2" Type -> Type -> Type
--> String -> Type
compute String
"Adapter" Type -> Type -> Type
@@ Type
"s2" Type -> Type -> Type
@@ Type
"s1" Type -> Type -> Type
@@ Type
"t2" Type -> Type -> Type
@@ Type
"t1" Type -> Type -> Type
@@ Type
"v2" Type -> Type -> Type
@@ Type
"v1"],
String -> Type -> Element
def String
"Coder" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An encoder and decoder; a bidirectional flow between two types" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
lambda String
"s1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"s2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"v1" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"v2" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
record [
String
"encode"String -> Type -> FieldType
>: (Type
"v1" Type -> Type -> Type
--> String -> Type
compute String
"Flow" Type -> Type -> Type
@@ Type
"s1" Type -> Type -> Type
@@ Type
"v2"),
String
"decode"String -> Type -> FieldType
>: (Type
"v2" Type -> Type -> Type
--> String -> Type
compute String
"Flow" Type -> Type -> Type
@@ Type
"s2" Type -> Type -> Type
@@ Type
"v1")],
String -> Type -> Element
def String
"Flow" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A variant of the State monad with built-in logging and error handling" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
lambda String
"s" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"x" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Type
function Type
"s" (String -> Type
compute String
"Trace" Type -> Type -> Type
--> String -> Type
compute String
"FlowState" Type -> Type -> Type
@@ Type
"s" Type -> Type -> Type
@@ Type
"x"),
String -> Type -> Element
def String
"FlowState" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The result of evaluating a Flow" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
lambda String
"s" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type -> Type
lambda String
"x" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
record [
String
"value"String -> Type -> FieldType
>: Type -> Type
optional Type
"x",
String
"state"String -> Type -> FieldType
>: Type
"s",
String
"trace"String -> Type -> FieldType
>: String -> Type
compute String
"Trace"],
String -> Type -> Element
def String
"Trace" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A container for logging and error information" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"stack"String -> Type -> FieldType
>: Type -> Type
list Type
string,
String
"messages"String -> Type -> FieldType
>: Type -> Type
list Type
string,
String
"other"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A map of string keys to arbitrary terms as values, for application-specific use" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Type
Types.map (String -> Type
core String
"Name") (String -> Type
core String
"Term")]]