{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier0.Workflow 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
import Hydra.Sources.Tier0.Compute
import Hydra.Sources.Tier0.Graph
import Hydra.Sources.Tier0.Module
hydraWorkflowModule :: Module
hydraWorkflowModule :: Module
hydraWorkflowModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module Namespace
ns [Element]
elements [Module
hydraModuleModule, Module
hydraComputeModule, Module
hydraGraphModule] [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 model for Hydra transformation workflows"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/workflow"
mod :: String -> Type
mod = Namespace -> String -> Type
typeref (Namespace -> String -> Type) -> Namespace -> String -> Type
forall a b. (a -> b) -> a -> b
$ Module -> Namespace
moduleNamespace Module
hydraModuleModule
compute :: String -> Type
compute = Namespace -> String -> Type
typeref (Namespace -> String -> Type) -> Namespace -> String -> Type
forall a b. (a -> b) -> a -> b
$ Module -> Namespace
moduleNamespace Module
hydraComputeModule
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
graph :: String -> Type
graph = Namespace -> String -> Type
typeref (Namespace -> String -> Type) -> Namespace -> String -> Type
forall a b. (a -> b) -> a -> b
$ Module -> Namespace
moduleNamespace Module
hydraGraphModule
wf :: String -> Type
wf = 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
"HydraSchemaSpec" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The specification of a Hydra schema, provided as a set of modules and a distinguished type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"modules"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The modules to include in the schema graph" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
mod String
"Module",
String
"typeName"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The name of the top-level type; all data which passes through the workflow will be instances of this type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name"],
String -> Type -> Element
def String
"LastMile" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The last mile of a transformation, which encodes and serializes terms to a file" (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
"a" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
record [
String
"encoder"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An encoder for terms to a list of output objects" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Type" Type -> Type -> Type
--> String -> Type
compute String
"Flow" Type -> Type -> Type
@@ Type
"s"
Type -> Type -> Type
@@ (String -> Type
core String
"Term" Type -> Type -> Type
--> String -> Type
graph String
"Graph" Type -> Type -> Type
--> String -> Type
compute String
"Flow" Type -> Type -> Type
@@ Type
"s" Type -> Type -> Type
@@ Type -> Type
list Type
"a"),
String
"serializer"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A function which serializes a list of output objects to a string representation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list Type
"a" Type -> Type -> Type
--> String -> Type
compute String
"Flow" Type -> Type -> Type
@@ Type
"s" Type -> Type -> Type
@@ Type
string,
String
"fileExtension"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A file extension for the generated file(s)"
Type
string],
String -> Type -> Element
def String
"SchemaSpec" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The specification of a schema at the source end of a workflow" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"hydra"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A native Hydra schema" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
wf String
"HydraSchemaSpec",
String
"file"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A schema provided as a file, available at the given file path" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type
string,
String
"provided"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A schema which will be provided within the workflow" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type
unit],
String -> Type -> Element
def String
"TransformWorkflow" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The specification of a workflow which takes a schema specification, reads data from a directory, and writes data to another directory" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A descriptive name for the workflow"
Type
string,
String
"schemaSpec"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The schema specification" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
wf String
"SchemaSpec",
String
"srcDir"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The source directory"
Type
string,
String
"destDir"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The destination directory"
Type
string]]