{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier2.Basics where
import Prelude hiding ((++))
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.Base as Base
import qualified Hydra.Dsl.Core as Core
import qualified Hydra.Dsl.Graph as Graph
import qualified Hydra.Dsl.Lib.Equality as Equality
import qualified Hydra.Dsl.Lib.Flows as Flows
import qualified Hydra.Dsl.Lib.Io as Io
import qualified Hydra.Dsl.Lib.Lists as Lists
import qualified Hydra.Dsl.Lib.Literals as Literals
import qualified Hydra.Dsl.Lib.Logic as Logic
import qualified Hydra.Dsl.Lib.Maps as Maps
import qualified Hydra.Dsl.Lib.Math as Math
import qualified Hydra.Dsl.Lib.Optionals as Optionals
import qualified Hydra.Dsl.Lib.Sets as Sets
import Hydra.Dsl.Lib.Strings as Strings
import qualified Hydra.Dsl.Module as Module
import qualified Hydra.Dsl.Terms as Terms
import qualified Hydra.Dsl.Types as Types
import Hydra.Sources.Tier1.All
basicsDefinition :: String -> Datum a -> Definition a
basicsDefinition :: forall a. String -> Datum a -> Definition a
basicsDefinition = Module -> String -> Datum a -> Definition a
forall a. Module -> String -> Datum a -> Definition a
definitionInModule Module
hydraBasicsModule
hydraBasicsModule :: Module
hydraBasicsModule :: Module
hydraBasicsModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module (String -> Namespace
Namespace String
"hydra/basics") [Element]
elements
[Module
hydraTier1Module]
[Module]
tier0Modules (Maybe String -> Module) -> Maybe String -> Module
forall a b. (a -> b) -> a -> b
$
String -> Maybe String
forall a. a -> Maybe a
Just String
"A tier-2 module of basic functions for working with types and terms."
where
elements :: [Element]
elements = [
Definition (Elimination -> EliminationVariant) -> Element
forall a. Definition a -> Element
el Definition (Elimination -> EliminationVariant)
eliminationVariantDef,
Definition [EliminationVariant] -> Element
forall a. Definition a -> Element
el Definition [EliminationVariant]
eliminationVariantsDef,
Definition (FloatType -> Precision) -> Element
forall a. Definition a -> Element
el Definition (FloatType -> Precision)
floatTypePrecisionDef,
Definition [FloatType] -> Element
forall a. Definition a -> Element
el Definition [FloatType]
floatTypesDef,
Definition (FloatValue -> FloatType) -> Element
forall a. Definition a -> Element
el Definition (FloatValue -> FloatType)
floatValueTypeDef,
Definition (Function -> FunctionVariant) -> Element
forall a. Definition a -> Element
el Definition (Function -> FunctionVariant)
functionVariantDef,
Definition [FunctionVariant] -> Element
forall a. Definition a -> Element
el Definition [FunctionVariant]
functionVariantsDef,
Definition (Any -> Any) -> Element
forall a. Definition a -> Element
el Definition (Any -> Any)
forall a. Definition (a -> a)
idDef,
Definition (IntegerType -> Bool) -> Element
forall a. Definition a -> Element
el Definition (IntegerType -> Bool)
integerTypeIsSignedDef,
Definition (IntegerType -> Precision) -> Element
forall a. Definition a -> Element
el Definition (IntegerType -> Precision)
integerTypePrecisionDef,
Definition [IntegerType] -> Element
forall a. Definition a -> Element
el Definition [IntegerType]
integerTypesDef,
Definition (IntegerValue -> IntegerType) -> Element
forall a. Definition a -> Element
el Definition (IntegerValue -> IntegerType)
integerValueTypeDef,
Definition (Literal -> LiteralType) -> Element
forall a. Definition a -> Element
el Definition (Literal -> LiteralType)
literalTypeDef,
Definition (LiteralType -> LiteralVariant) -> Element
forall a. Definition a -> Element
el Definition (LiteralType -> LiteralVariant)
literalTypeVariantDef,
Definition (Literal -> LiteralVariant) -> Element
forall a. Definition a -> Element
el Definition (Literal -> LiteralVariant)
literalVariantDef,
Definition [LiteralVariant] -> Element
forall a. Definition a -> Element
el Definition [LiteralVariant]
literalVariantsDef,
Definition (Term -> TermVariant) -> Element
forall a. Definition a -> Element
el Definition (Term -> TermVariant)
termVariantDef,
Definition [TermVariant] -> Element
forall a. Definition a -> Element
el Definition [TermVariant]
termVariantsDef,
Definition (Type -> TypeVariant) -> Element
forall a. Definition a -> Element
el Definition (Type -> TypeVariant)
typeVariantDef,
Definition [TypeVariant] -> Element
forall a. Definition a -> Element
el Definition [TypeVariant]
typeVariantsDef,
Definition (String -> String) -> Element
forall a. Definition a -> Element
el Definition (String -> String)
capitalizeDef,
Definition (String -> String) -> Element
forall a. Definition a -> Element
el Definition (String -> String)
decapitalizeDef,
Definition ((String -> String) -> String -> String) -> Element
forall a. Definition a -> Element
el Definition ((String -> String) -> String -> String)
mapFirstLetterDef,
Definition ([Field] -> Map Name Term) -> Element
forall a. Definition a -> Element
el Definition ([Field] -> Map Name Term)
fieldMapDef,
Definition ([FieldType] -> Map Name Type) -> Element
forall a. Definition a -> Element
el Definition ([FieldType] -> Map Name Type)
fieldTypeMapDef,
Definition (Term -> Bool) -> Element
forall a. Definition a -> Element
el Definition (Term -> Bool)
isEncodedTypeDef,
Definition (Type -> Bool) -> Element
forall a. Definition a -> Element
el Definition (Type -> Bool)
isTypeDef,
Definition (Term -> Bool) -> Element
forall a. Definition a -> Element
el Definition (Term -> Bool)
isUnitTermDef,
Definition (Term -> Bool) -> Element
forall a. Definition a -> Element
el Definition (Term -> Bool)
isUnitTypeDef,
Definition (Graph -> Maybe Graph -> [Element] -> Graph) -> Element
forall a. Definition a -> Element
el Definition (Graph -> Maybe Graph -> [Element] -> Graph)
elementsToGraphDef,
Definition (Name -> String) -> Element
forall a. Definition a -> Element
el Definition (Name -> String)
localNameOfEagerDef,
Definition (Name -> String) -> Element
forall a. Definition a -> Element
el Definition (Name -> String)
localNameOfLazyDef,
Definition (Name -> Maybe Namespace) -> Element
forall a. Definition a -> Element
el Definition (Name -> Maybe Namespace)
namespaceOfEagerDef,
Definition (Name -> Maybe Namespace) -> Element
forall a. Definition a -> Element
el Definition (Name -> Maybe Namespace)
namespaceOfLazyDef,
Definition (Bool -> FileExtension -> Namespace -> String)
-> Element
forall a. Definition a -> Element
el Definition (Bool -> FileExtension -> Namespace -> String)
namespaceToFilePathDef,
Definition (Name -> QualifiedName) -> Element
forall a. Definition a -> Element
el Definition (Name -> QualifiedName)
qualifyNameEagerDef,
Definition (Name -> QualifiedName) -> Element
forall a. Definition a -> Element
el Definition (Name -> QualifiedName)
qualifyNameLazyDef
]
eliminationVariantDef :: Definition (Elimination -> EliminationVariant)
eliminationVariantDef :: Definition (Elimination -> EliminationVariant)
eliminationVariantDef = String
-> Datum (Elimination -> EliminationVariant)
-> Definition (Elimination -> EliminationVariant)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"eliminationVariant" (Datum (Elimination -> EliminationVariant)
-> Definition (Elimination -> EliminationVariant))
-> Datum (Elimination -> EliminationVariant)
-> Definition (Elimination -> EliminationVariant)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Elimination -> EliminationVariant)
-> Datum (Elimination -> EliminationVariant)
forall a. String -> Datum a -> Datum a
doc String
"Find the elimination variant (constructor) for a given elimination term" (Datum (Elimination -> EliminationVariant)
-> Datum (Elimination -> EliminationVariant))
-> Datum (Elimination -> EliminationVariant)
-> Datum (Elimination -> EliminationVariant)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Elimination -> EliminationVariant)
-> Datum (Elimination -> EliminationVariant)
forall a. Type -> Type -> Datum a -> Datum a
function Type
eliminationT Type
eliminationVariantT (Datum (Elimination -> EliminationVariant)
-> Datum (Elimination -> EliminationVariant))
-> Datum (Elimination -> EliminationVariant)
-> Datum (Elimination -> EliminationVariant)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum EliminationVariant)
-> [(Name, Name)]
-> Datum (Elimination -> EliminationVariant)
forall b a.
Name -> Name -> Maybe (Datum b) -> [(Name, Name)] -> Datum (a -> b)
matchToEnum Name
_Elimination Name
_EliminationVariant Maybe (Datum EliminationVariant)
forall a. Maybe a
Nothing [
Name
_Elimination_list Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_EliminationVariant_list,
Name
_Elimination_optional Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_EliminationVariant_optional,
Name
_Elimination_product Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_EliminationVariant_product,
Name
_Elimination_record Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_EliminationVariant_record,
Name
_Elimination_union Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_EliminationVariant_union,
Name
_Elimination_wrap Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_EliminationVariant_wrap]
eliminationVariantsDef :: Definition [EliminationVariant]
eliminationVariantsDef :: Definition [EliminationVariant]
eliminationVariantsDef = String
-> Datum [EliminationVariant] -> Definition [EliminationVariant]
forall a. String -> Datum a -> Definition a
basicsDefinition String
"eliminationVariants" (Datum [EliminationVariant] -> Definition [EliminationVariant])
-> Datum [EliminationVariant] -> Definition [EliminationVariant]
forall a b. (a -> b) -> a -> b
$
String -> Datum [EliminationVariant] -> Datum [EliminationVariant]
forall a. String -> Datum a -> Datum a
doc String
"All elimination variants (constructors), in a canonical order" (Datum [EliminationVariant] -> Datum [EliminationVariant])
-> Datum [EliminationVariant] -> Datum [EliminationVariant]
forall a b. (a -> b) -> a -> b
$
Type -> Datum [EliminationVariant] -> Datum [EliminationVariant]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
eliminationVariantT) (Datum [EliminationVariant] -> Datum [EliminationVariant])
-> Datum [EliminationVariant] -> Datum [EliminationVariant]
forall a b. (a -> b) -> a -> b
$
[Datum EliminationVariant] -> Datum [EliminationVariant]
forall a. [Datum a] -> Datum [a]
list ([Datum EliminationVariant] -> Datum [EliminationVariant])
-> [Datum EliminationVariant] -> Datum [EliminationVariant]
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum EliminationVariant
forall a. Name -> Name -> Datum a
unitVariant Name
_EliminationVariant (Name -> Datum EliminationVariant)
-> [Name] -> [Datum EliminationVariant]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [
Name
_EliminationVariant_list,
Name
_EliminationVariant_wrap,
Name
_EliminationVariant_optional,
Name
_EliminationVariant_product,
Name
_EliminationVariant_record,
Name
_EliminationVariant_union]
floatTypePrecisionDef :: Definition (FloatType -> Precision)
floatTypePrecisionDef :: Definition (FloatType -> Precision)
floatTypePrecisionDef = String
-> Datum (FloatType -> Precision)
-> Definition (FloatType -> Precision)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"floatTypePrecision" (Datum (FloatType -> Precision)
-> Definition (FloatType -> Precision))
-> Datum (FloatType -> Precision)
-> Definition (FloatType -> Precision)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (FloatType -> Precision) -> Datum (FloatType -> Precision)
forall a. String -> Datum a -> Datum a
doc String
"Find the precision of a given floating-point type" (Datum (FloatType -> Precision) -> Datum (FloatType -> Precision))
-> Datum (FloatType -> Precision) -> Datum (FloatType -> Precision)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (FloatType -> Precision)
-> Datum (FloatType -> Precision)
forall a. Type -> Type -> Datum a -> Datum a
function Type
floatTypeT Type
precisionT (Datum (FloatType -> Precision) -> Datum (FloatType -> Precision))
-> Datum (FloatType -> Precision) -> Datum (FloatType -> Precision)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum Precision)
-> [(Name, Field)]
-> Datum (FloatType -> Precision)
forall b a.
Name
-> Name -> Maybe (Datum b) -> [(Name, Field)] -> Datum (a -> b)
matchToUnion Name
_FloatType Name
_Precision Maybe (Datum Precision)
forall a. Maybe a
Nothing [
Name
_FloatType_bigfloat Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Any -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_arbitrary Datum Any
forall a. Datum a
unit,
Name
_FloatType_float32 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
32,
Name
_FloatType_float64 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
64]
floatTypesDef :: Definition [FloatType]
floatTypesDef :: Definition [FloatType]
floatTypesDef = String -> Datum [FloatType] -> Definition [FloatType]
forall a. String -> Datum a -> Definition a
basicsDefinition String
"floatTypes" (Datum [FloatType] -> Definition [FloatType])
-> Datum [FloatType] -> Definition [FloatType]
forall a b. (a -> b) -> a -> b
$
String -> Datum [FloatType] -> Datum [FloatType]
forall a. String -> Datum a -> Datum a
doc String
"All floating-point types in a canonical order" (Datum [FloatType] -> Datum [FloatType])
-> Datum [FloatType] -> Datum [FloatType]
forall a b. (a -> b) -> a -> b
$
Type -> Datum [FloatType] -> Datum [FloatType]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
floatTypeT) (Datum [FloatType] -> Datum [FloatType])
-> Datum [FloatType] -> Datum [FloatType]
forall a b. (a -> b) -> a -> b
$
[Datum FloatType] -> Datum [FloatType]
forall a. [Datum a] -> Datum [a]
list ([Datum FloatType] -> Datum [FloatType])
-> [Datum FloatType] -> Datum [FloatType]
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum FloatType
forall a. Name -> Name -> Datum a
unitVariant Name
_FloatType (Name -> Datum FloatType) -> [Name] -> [Datum FloatType]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [
Name
_FloatType_bigfloat,
Name
_FloatType_float32,
Name
_FloatType_float64]
floatValueTypeDef :: Definition (FloatValue -> FloatType)
floatValueTypeDef :: Definition (FloatValue -> FloatType)
floatValueTypeDef = String
-> Datum (FloatValue -> FloatType)
-> Definition (FloatValue -> FloatType)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"floatValueType" (Datum (FloatValue -> FloatType)
-> Definition (FloatValue -> FloatType))
-> Datum (FloatValue -> FloatType)
-> Definition (FloatValue -> FloatType)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (FloatValue -> FloatType)
-> Datum (FloatValue -> FloatType)
forall a. String -> Datum a -> Datum a
doc String
"Find the float type for a given floating-point value" (Datum (FloatValue -> FloatType)
-> Datum (FloatValue -> FloatType))
-> Datum (FloatValue -> FloatType)
-> Datum (FloatValue -> FloatType)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (FloatValue -> FloatType)
-> Datum (FloatValue -> FloatType)
forall a. Type -> Type -> Datum a -> Datum a
function Type
floatValueT Type
floatTypeT (Datum (FloatValue -> FloatType)
-> Datum (FloatValue -> FloatType))
-> Datum (FloatValue -> FloatType)
-> Datum (FloatValue -> FloatType)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum FloatType)
-> [(Name, Name)]
-> Datum (FloatValue -> FloatType)
forall b a.
Name -> Name -> Maybe (Datum b) -> [(Name, Name)] -> Datum (a -> b)
matchToEnum Name
_FloatValue Name
_FloatType Maybe (Datum FloatType)
forall a. Maybe a
Nothing [
Name
_FloatValue_bigfloat Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_FloatType_bigfloat,
Name
_FloatValue_float32 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_FloatType_float32,
Name
_FloatValue_float64 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_FloatType_float64]
functionVariantDef :: Definition (Function -> FunctionVariant)
functionVariantDef :: Definition (Function -> FunctionVariant)
functionVariantDef = String
-> Datum (Function -> FunctionVariant)
-> Definition (Function -> FunctionVariant)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"functionVariant" (Datum (Function -> FunctionVariant)
-> Definition (Function -> FunctionVariant))
-> Datum (Function -> FunctionVariant)
-> Definition (Function -> FunctionVariant)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Function -> FunctionVariant)
-> Datum (Function -> FunctionVariant)
forall a. String -> Datum a -> Datum a
doc String
"Find the function variant (constructor) for a given function" (Datum (Function -> FunctionVariant)
-> Datum (Function -> FunctionVariant))
-> Datum (Function -> FunctionVariant)
-> Datum (Function -> FunctionVariant)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Function -> FunctionVariant)
-> Datum (Function -> FunctionVariant)
forall a. Type -> Type -> Datum a -> Datum a
function Type
functionT Type
functionVariantT (Datum (Function -> FunctionVariant)
-> Datum (Function -> FunctionVariant))
-> Datum (Function -> FunctionVariant)
-> Datum (Function -> FunctionVariant)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum FunctionVariant)
-> [(Name, Name)]
-> Datum (Function -> FunctionVariant)
forall b a.
Name -> Name -> Maybe (Datum b) -> [(Name, Name)] -> Datum (a -> b)
matchToEnum Name
_Function Name
_FunctionVariant Maybe (Datum FunctionVariant)
forall a. Maybe a
Nothing [
Name
_Function_elimination Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_FunctionVariant_elimination,
Name
_Function_lambda Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_FunctionVariant_lambda,
Name
_Function_primitive Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_FunctionVariant_primitive]
functionVariantsDef :: Definition [FunctionVariant]
functionVariantsDef :: Definition [FunctionVariant]
functionVariantsDef = String -> Datum [FunctionVariant] -> Definition [FunctionVariant]
forall a. String -> Datum a -> Definition a
basicsDefinition String
"functionVariants" (Datum [FunctionVariant] -> Definition [FunctionVariant])
-> Datum [FunctionVariant] -> Definition [FunctionVariant]
forall a b. (a -> b) -> a -> b
$
String -> Datum [FunctionVariant] -> Datum [FunctionVariant]
forall a. String -> Datum a -> Datum a
doc String
"All function variants (constructors), in a canonical order" (Datum [FunctionVariant] -> Datum [FunctionVariant])
-> Datum [FunctionVariant] -> Datum [FunctionVariant]
forall a b. (a -> b) -> a -> b
$
Type -> Datum [FunctionVariant] -> Datum [FunctionVariant]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
functionVariantT) (Datum [FunctionVariant] -> Datum [FunctionVariant])
-> Datum [FunctionVariant] -> Datum [FunctionVariant]
forall a b. (a -> b) -> a -> b
$
[Datum FunctionVariant] -> Datum [FunctionVariant]
forall a. [Datum a] -> Datum [a]
list ([Datum FunctionVariant] -> Datum [FunctionVariant])
-> [Datum FunctionVariant] -> Datum [FunctionVariant]
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum FunctionVariant
forall a. Name -> Name -> Datum a
unitVariant Name
_FunctionVariant (Name -> Datum FunctionVariant)
-> [Name] -> [Datum FunctionVariant]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [
Name
_FunctionVariant_elimination,
Name
_FunctionVariant_lambda,
Name
_FunctionVariant_primitive]
idDef :: Definition (a -> a)
idDef :: forall a. Definition (a -> a)
idDef = String -> Datum (a -> a) -> Definition (a -> a)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"id" (Datum (a -> a) -> Definition (a -> a))
-> Datum (a -> a) -> Definition (a -> a)
forall a b. (a -> b) -> a -> b
$
String -> Datum (a -> a) -> Datum (a -> a)
forall a. String -> Datum a -> Datum a
doc String
"The identity function" (Datum (a -> a) -> Datum (a -> a))
-> Datum (a -> a) -> Datum (a -> a)
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Datum (a -> a) -> Datum (a -> a)
forall a. Type -> Type -> Datum a -> Datum a
function Type
aT Type
aT (Datum (a -> a) -> Datum (a -> a))
-> Datum (a -> a) -> Datum (a -> a)
forall a b. (a -> b) -> a -> b
$
String -> Datum Any -> Datum (a -> a)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"x" (Datum Any -> Datum (a -> a)) -> Datum Any -> Datum (a -> a)
forall a b. (a -> b) -> a -> b
$ String -> Datum Any
forall a. String -> Datum a
var String
"x"
integerTypeIsSignedDef :: Definition (IntegerType -> Bool)
integerTypeIsSignedDef :: Definition (IntegerType -> Bool)
integerTypeIsSignedDef = String
-> Datum (IntegerType -> Bool) -> Definition (IntegerType -> Bool)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"integerTypeIsSigned" (Datum (IntegerType -> Bool) -> Definition (IntegerType -> Bool))
-> Datum (IntegerType -> Bool) -> Definition (IntegerType -> Bool)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (IntegerType -> Bool) -> Datum (IntegerType -> Bool)
forall a. String -> Datum a -> Datum a
doc String
"Find whether a given integer type is signed (true) or unsigned (false)" (Datum (IntegerType -> Bool) -> Datum (IntegerType -> Bool))
-> Datum (IntegerType -> Bool) -> Datum (IntegerType -> Bool)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (IntegerType -> Bool)
-> Datum (IntegerType -> Bool)
forall a. Type -> Type -> Datum a -> Datum a
function Type
integerTypeT Type
booleanT (Datum (IntegerType -> Bool) -> Datum (IntegerType -> Bool))
-> Datum (IntegerType -> Bool) -> Datum (IntegerType -> Bool)
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe (Datum Bool)
-> [(Name, Datum (Any -> Bool))]
-> Datum (IntegerType -> Bool)
forall b x a.
Name
-> Maybe (Datum b) -> [(Name, Datum (x -> b))] -> Datum (a -> b)
matchData Name
_IntegerType Maybe (Datum Bool)
forall a. Maybe a
Nothing [
Name
_IntegerType_bigint Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
true,
Name
_IntegerType_int8 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
true,
Name
_IntegerType_int16 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
true,
Name
_IntegerType_int32 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
true,
Name
_IntegerType_int64 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
true,
Name
_IntegerType_uint8 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
false,
Name
_IntegerType_uint16 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
false,
Name
_IntegerType_uint32 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
false,
Name
_IntegerType_uint64 Name -> Datum (Any -> Bool) -> (Name, Datum (Any -> Bool))
forall a b. a -> b -> (a, b)
@-> Datum Bool -> Datum (Any -> Bool)
forall a b. Datum a -> Datum (b -> a)
constant Datum Bool
false]
integerTypePrecisionDef :: Definition (IntegerType -> Precision)
integerTypePrecisionDef :: Definition (IntegerType -> Precision)
integerTypePrecisionDef = String
-> Datum (IntegerType -> Precision)
-> Definition (IntegerType -> Precision)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"integerTypePrecision" (Datum (IntegerType -> Precision)
-> Definition (IntegerType -> Precision))
-> Datum (IntegerType -> Precision)
-> Definition (IntegerType -> Precision)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (IntegerType -> Precision)
-> Datum (IntegerType -> Precision)
forall a. String -> Datum a -> Datum a
doc String
"Find the precision of a given integer type" (Datum (IntegerType -> Precision)
-> Datum (IntegerType -> Precision))
-> Datum (IntegerType -> Precision)
-> Datum (IntegerType -> Precision)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (IntegerType -> Precision)
-> Datum (IntegerType -> Precision)
forall a. Type -> Type -> Datum a -> Datum a
function Type
integerTypeT Type
precisionT (Datum (IntegerType -> Precision)
-> Datum (IntegerType -> Precision))
-> Datum (IntegerType -> Precision)
-> Datum (IntegerType -> Precision)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum Precision)
-> [(Name, Field)]
-> Datum (IntegerType -> Precision)
forall b a.
Name
-> Name -> Maybe (Datum b) -> [(Name, Field)] -> Datum (a -> b)
matchToUnion Name
_IntegerType Name
_Precision Maybe (Datum Precision)
forall a. Maybe a
Nothing [
Name
_IntegerType_bigint Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Any -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_arbitrary Datum Any
forall a. Datum a
unit,
Name
_IntegerType_int8 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
8,
Name
_IntegerType_int16 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
16,
Name
_IntegerType_int32 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
32,
Name
_IntegerType_int64 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
64,
Name
_IntegerType_uint8 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
8,
Name
_IntegerType_uint16 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
16,
Name
_IntegerType_uint32 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
32,
Name
_IntegerType_uint64 Name -> Field -> (Name, Field)
forall a b. a -> b -> (a, b)
@-> Name -> Datum Int -> Field
forall a. Name -> Datum a -> Field
field Name
_Precision_bits (Datum Int -> Field) -> Datum Int -> Field
forall a b. (a -> b) -> a -> b
$ Int -> Datum Int
int Int
64]
integerTypesDef :: Definition [IntegerType]
integerTypesDef :: Definition [IntegerType]
integerTypesDef = String -> Datum [IntegerType] -> Definition [IntegerType]
forall a. String -> Datum a -> Definition a
basicsDefinition String
"integerTypes" (Datum [IntegerType] -> Definition [IntegerType])
-> Datum [IntegerType] -> Definition [IntegerType]
forall a b. (a -> b) -> a -> b
$
String -> Datum [IntegerType] -> Datum [IntegerType]
forall a. String -> Datum a -> Datum a
doc String
"All integer types, in a canonical order" (Datum [IntegerType] -> Datum [IntegerType])
-> Datum [IntegerType] -> Datum [IntegerType]
forall a b. (a -> b) -> a -> b
$
Type -> Datum [IntegerType] -> Datum [IntegerType]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
integerTypeT) (Datum [IntegerType] -> Datum [IntegerType])
-> Datum [IntegerType] -> Datum [IntegerType]
forall a b. (a -> b) -> a -> b
$
[Datum IntegerType] -> Datum [IntegerType]
forall a. [Datum a] -> Datum [a]
list ([Datum IntegerType] -> Datum [IntegerType])
-> [Datum IntegerType] -> Datum [IntegerType]
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum IntegerType
forall a. Name -> Name -> Datum a
unitVariant Name
_IntegerType (Name -> Datum IntegerType) -> [Name] -> [Datum IntegerType]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [
Name
_IntegerType_bigint,
Name
_IntegerType_int8,
Name
_IntegerType_int16,
Name
_IntegerType_int32,
Name
_IntegerType_int64,
Name
_IntegerType_uint8,
Name
_IntegerType_uint16,
Name
_IntegerType_uint32,
Name
_IntegerType_uint64]
integerValueTypeDef :: Definition (IntegerValue -> IntegerType)
integerValueTypeDef :: Definition (IntegerValue -> IntegerType)
integerValueTypeDef = String
-> Datum (IntegerValue -> IntegerType)
-> Definition (IntegerValue -> IntegerType)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"integerValueType" (Datum (IntegerValue -> IntegerType)
-> Definition (IntegerValue -> IntegerType))
-> Datum (IntegerValue -> IntegerType)
-> Definition (IntegerValue -> IntegerType)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> IntegerType)
forall a. String -> Datum a -> Datum a
doc String
"Find the integer type for a given integer value" (Datum (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> IntegerType))
-> Datum (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> IntegerType)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> IntegerType)
forall a. Type -> Type -> Datum a -> Datum a
function Type
integerValueT Type
integerTypeT (Datum (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> IntegerType))
-> Datum (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> IntegerType)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum IntegerType)
-> [(Name, Name)]
-> Datum (IntegerValue -> IntegerType)
forall b a.
Name -> Name -> Maybe (Datum b) -> [(Name, Name)] -> Datum (a -> b)
matchToEnum Name
_IntegerValue Name
_IntegerType Maybe (Datum IntegerType)
forall a. Maybe a
Nothing [
Name
_IntegerValue_bigint Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_bigint,
Name
_IntegerValue_int8 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_int8,
Name
_IntegerValue_int16 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_int16,
Name
_IntegerValue_int32 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_int32,
Name
_IntegerValue_int64 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_int64,
Name
_IntegerValue_uint8 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_uint8,
Name
_IntegerValue_uint16 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_uint16,
Name
_IntegerValue_uint32 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_uint32,
Name
_IntegerValue_uint64 Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_IntegerType_uint64]
literalTypeDef :: Definition (Literal -> LiteralType)
literalTypeDef :: Definition (Literal -> LiteralType)
literalTypeDef = String
-> Datum (Literal -> LiteralType)
-> Definition (Literal -> LiteralType)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"literalType" (Datum (Literal -> LiteralType)
-> Definition (Literal -> LiteralType))
-> Datum (Literal -> LiteralType)
-> Definition (Literal -> LiteralType)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Literal -> LiteralType) -> Datum (Literal -> LiteralType)
forall a. String -> Datum a -> Datum a
doc String
"Find the literal type for a given literal value" (Datum (Literal -> LiteralType) -> Datum (Literal -> LiteralType))
-> Datum (Literal -> LiteralType) -> Datum (Literal -> LiteralType)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Literal -> LiteralType)
-> Datum (Literal -> LiteralType)
forall a. Type -> Type -> Datum a -> Datum a
function Type
literalT Type
literalTypeT (Datum (Literal -> LiteralType) -> Datum (Literal -> LiteralType))
-> Datum (Literal -> LiteralType) -> Datum (Literal -> LiteralType)
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe (Datum LiteralType)
-> [Field]
-> Datum (Literal -> LiteralType)
forall b u. Name -> Maybe (Datum b) -> [Field] -> Datum (u -> b)
match Name
_Literal Maybe (Datum LiteralType)
forall a. Maybe a
Nothing [
Name -> Case Any
forall a. Name -> Case a
Case Name
_Literal_binary Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> Datum Any -> Datum (Any -> Any)
forall a b. Datum a -> Datum (b -> a)
constant (Datum Any -> Datum (Any -> Any))
-> Datum Any -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum Any -> Datum Any
forall a b. Name -> Name -> Datum a -> Datum b
variant Name
_LiteralType Name
_LiteralType_binary Datum Any
forall a. Datum a
unit,
Name -> Case Any
forall a. Name -> Case a
Case Name
_Literal_boolean Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> Datum Any -> Datum (Any -> Any)
forall a b. Datum a -> Datum (b -> a)
constant (Datum Any -> Datum (Any -> Any))
-> Datum Any -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum Any -> Datum Any
forall a b. Name -> Name -> Datum a -> Datum b
variant Name
_LiteralType Name
_LiteralType_boolean Datum Any
forall a. Datum a
unit,
Name -> Case FloatValue
forall a. Name -> Case a
Case Name
_Literal_float Case FloatValue -> Datum (FloatValue -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> Name -> Name -> Datum (FloatType -> Any)
forall a b. Name -> Name -> Datum (a -> b)
inject2 Name
_LiteralType Name
_LiteralType_float Datum (FloatType -> Any)
-> Datum (FloatValue -> FloatType) -> Datum (FloatValue -> Any)
forall b c a. Datum (b -> c) -> Datum (a -> b) -> Datum (a -> c)
<.> Definition (FloatValue -> FloatType)
-> Datum (FloatValue -> FloatType)
forall a. Definition a -> Datum a
ref Definition (FloatValue -> FloatType)
floatValueTypeDef,
Name -> Case IntegerValue
forall a. Name -> Case a
Case Name
_Literal_integer Case IntegerValue -> Datum (IntegerValue -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> Name -> Name -> Datum (IntegerType -> Any)
forall a b. Name -> Name -> Datum (a -> b)
inject2 Name
_LiteralType Name
_LiteralType_integer Datum (IntegerType -> Any)
-> Datum (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> Any)
forall b c a. Datum (b -> c) -> Datum (a -> b) -> Datum (a -> c)
<.> Definition (IntegerValue -> IntegerType)
-> Datum (IntegerValue -> IntegerType)
forall a. Definition a -> Datum a
ref Definition (IntegerValue -> IntegerType)
integerValueTypeDef,
Name -> Case Any
forall a. Name -> Case a
Case Name
_Literal_string Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> Datum Any -> Datum (Any -> Any)
forall a b. Datum a -> Datum (b -> a)
constant (Datum Any -> Datum (Any -> Any))
-> Datum Any -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum Any -> Datum Any
forall a b. Name -> Name -> Datum a -> Datum b
variant Name
_LiteralType Name
_LiteralType_string Datum Any
forall a. Datum a
unit]
literalTypeVariantDef :: Definition (LiteralType -> LiteralVariant)
literalTypeVariantDef :: Definition (LiteralType -> LiteralVariant)
literalTypeVariantDef = String
-> Datum (LiteralType -> LiteralVariant)
-> Definition (LiteralType -> LiteralVariant)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"literalTypeVariant" (Datum (LiteralType -> LiteralVariant)
-> Definition (LiteralType -> LiteralVariant))
-> Datum (LiteralType -> LiteralVariant)
-> Definition (LiteralType -> LiteralVariant)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (LiteralType -> LiteralVariant)
-> Datum (LiteralType -> LiteralVariant)
forall a. String -> Datum a -> Datum a
doc String
"Find the literal type variant (constructor) for a given literal value" (Datum (LiteralType -> LiteralVariant)
-> Datum (LiteralType -> LiteralVariant))
-> Datum (LiteralType -> LiteralVariant)
-> Datum (LiteralType -> LiteralVariant)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (LiteralType -> LiteralVariant)
-> Datum (LiteralType -> LiteralVariant)
forall a. Type -> Type -> Datum a -> Datum a
function Type
literalTypeT Type
literalVariantT (Datum (LiteralType -> LiteralVariant)
-> Datum (LiteralType -> LiteralVariant))
-> Datum (LiteralType -> LiteralVariant)
-> Datum (LiteralType -> LiteralVariant)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum LiteralVariant)
-> [(Name, Name)]
-> Datum (LiteralType -> LiteralVariant)
forall b a.
Name -> Name -> Maybe (Datum b) -> [(Name, Name)] -> Datum (a -> b)
matchToEnum Name
_LiteralType Name
_LiteralVariant Maybe (Datum LiteralVariant)
forall a. Maybe a
Nothing [
Name
_LiteralType_binary Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_LiteralVariant_binary,
Name
_LiteralType_boolean Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_LiteralVariant_boolean,
Name
_LiteralType_float Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_LiteralVariant_float,
Name
_LiteralType_integer Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_LiteralVariant_integer,
Name
_LiteralType_string Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_LiteralVariant_string]
literalVariantDef :: Definition (Literal -> LiteralVariant)
literalVariantDef :: Definition (Literal -> LiteralVariant)
literalVariantDef = String
-> Datum (Literal -> LiteralVariant)
-> Definition (Literal -> LiteralVariant)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"literalVariant" (Datum (Literal -> LiteralVariant)
-> Definition (Literal -> LiteralVariant))
-> Datum (Literal -> LiteralVariant)
-> Definition (Literal -> LiteralVariant)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Literal -> LiteralVariant)
-> Datum (Literal -> LiteralVariant)
forall a. String -> Datum a -> Datum a
doc String
"Find the literal variant (constructor) for a given literal value" (Datum (Literal -> LiteralVariant)
-> Datum (Literal -> LiteralVariant))
-> Datum (Literal -> LiteralVariant)
-> Datum (Literal -> LiteralVariant)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Literal -> LiteralVariant)
-> Datum (Literal -> LiteralVariant)
forall a. Type -> Type -> Datum a -> Datum a
function Type
literalT Type
literalVariantT (Datum (Literal -> LiteralVariant)
-> Datum (Literal -> LiteralVariant))
-> Datum (Literal -> LiteralVariant)
-> Datum (Literal -> LiteralVariant)
forall a b. (a -> b) -> a -> b
$
Definition (LiteralType -> LiteralVariant)
-> Datum (LiteralType -> LiteralVariant)
forall a. Definition a -> Datum a
ref Definition (LiteralType -> LiteralVariant)
literalTypeVariantDef Datum (LiteralType -> LiteralVariant)
-> Datum (Literal -> LiteralType)
-> Datum (Literal -> LiteralVariant)
forall b c a. Datum (b -> c) -> Datum (a -> b) -> Datum (a -> c)
<.> Definition (Literal -> LiteralType)
-> Datum (Literal -> LiteralType)
forall a. Definition a -> Datum a
ref Definition (Literal -> LiteralType)
literalTypeDef
literalVariantsDef :: Definition [LiteralVariant]
literalVariantsDef :: Definition [LiteralVariant]
literalVariantsDef = String -> Datum [LiteralVariant] -> Definition [LiteralVariant]
forall a. String -> Datum a -> Definition a
basicsDefinition String
"literalVariants" (Datum [LiteralVariant] -> Definition [LiteralVariant])
-> Datum [LiteralVariant] -> Definition [LiteralVariant]
forall a b. (a -> b) -> a -> b
$
String -> Datum [LiteralVariant] -> Datum [LiteralVariant]
forall a. String -> Datum a -> Datum a
doc String
"All literal variants, in a canonical order" (Datum [LiteralVariant] -> Datum [LiteralVariant])
-> Datum [LiteralVariant] -> Datum [LiteralVariant]
forall a b. (a -> b) -> a -> b
$
Type -> Datum [LiteralVariant] -> Datum [LiteralVariant]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
literalVariantT) (Datum [LiteralVariant] -> Datum [LiteralVariant])
-> Datum [LiteralVariant] -> Datum [LiteralVariant]
forall a b. (a -> b) -> a -> b
$
[Datum LiteralVariant] -> Datum [LiteralVariant]
forall a. [Datum a] -> Datum [a]
list ([Datum LiteralVariant] -> Datum [LiteralVariant])
-> [Datum LiteralVariant] -> Datum [LiteralVariant]
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum LiteralVariant
forall a. Name -> Name -> Datum a
unitVariant Name
_LiteralVariant (Name -> Datum LiteralVariant) -> [Name] -> [Datum LiteralVariant]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [
Name
_LiteralVariant_binary,
Name
_LiteralVariant_boolean,
Name
_LiteralVariant_float,
Name
_LiteralVariant_integer,
Name
_LiteralVariant_string]
termVariantDef :: Definition (Term -> TermVariant)
termVariantDef :: Definition (Term -> TermVariant)
termVariantDef = String
-> Datum (Term -> TermVariant) -> Definition (Term -> TermVariant)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"termVariant" (Datum (Term -> TermVariant) -> Definition (Term -> TermVariant))
-> Datum (Term -> TermVariant) -> Definition (Term -> TermVariant)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Term -> TermVariant) -> Datum (Term -> TermVariant)
forall a. String -> Datum a -> Datum a
doc String
"Find the term variant (constructor) for a given term" (Datum (Term -> TermVariant) -> Datum (Term -> TermVariant))
-> Datum (Term -> TermVariant) -> Datum (Term -> TermVariant)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Term -> TermVariant)
-> Datum (Term -> TermVariant)
forall a. Type -> Type -> Datum a -> Datum a
function Type
termT Type
termVariantT (Datum (Term -> TermVariant) -> Datum (Term -> TermVariant))
-> Datum (Term -> TermVariant) -> Datum (Term -> TermVariant)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum TermVariant)
-> [(Name, Name)]
-> Datum (Term -> TermVariant)
forall b a.
Name -> Name -> Maybe (Datum b) -> [(Name, Name)] -> Datum (a -> b)
matchToEnum Name
_Term Name
_TermVariant Maybe (Datum TermVariant)
forall a. Maybe a
Nothing [
Name
_Term_annotated Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_annotated,
Name
_Term_application Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_application,
Name
_Term_function Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_function,
Name
_Term_let Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_let,
Name
_Term_list Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_list,
Name
_Term_literal Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_literal,
Name
_Term_map Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_map,
Name
_Term_optional Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_optional,
Name
_Term_product Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_product,
Name
_Term_record Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_record,
Name
_Term_set Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_set,
Name
_Term_sum Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_sum,
Name
_Term_typed Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_typed,
Name
_Term_union Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_union,
Name
_Term_variable Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_variable,
Name
_Term_wrap Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TermVariant_wrap]
termVariantsDef :: Definition [TermVariant]
termVariantsDef :: Definition [TermVariant]
termVariantsDef = String -> Datum [TermVariant] -> Definition [TermVariant]
forall a. String -> Datum a -> Definition a
basicsDefinition String
"termVariants" (Datum [TermVariant] -> Definition [TermVariant])
-> Datum [TermVariant] -> Definition [TermVariant]
forall a b. (a -> b) -> a -> b
$
String -> Datum [TermVariant] -> Datum [TermVariant]
forall a. String -> Datum a -> Datum a
doc String
"All term (expression) variants, in a canonical order" (Datum [TermVariant] -> Datum [TermVariant])
-> Datum [TermVariant] -> Datum [TermVariant]
forall a b. (a -> b) -> a -> b
$
Type -> Datum [TermVariant] -> Datum [TermVariant]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
termVariantT) (Datum [TermVariant] -> Datum [TermVariant])
-> Datum [TermVariant] -> Datum [TermVariant]
forall a b. (a -> b) -> a -> b
$
[Datum TermVariant] -> Datum [TermVariant]
forall a. [Datum a] -> Datum [a]
list ([Datum TermVariant] -> Datum [TermVariant])
-> [Datum TermVariant] -> Datum [TermVariant]
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum TermVariant
forall a. Name -> Name -> Datum a
unitVariant Name
_TermVariant (Name -> Datum TermVariant) -> [Name] -> [Datum TermVariant]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [
Name
_TermVariant_annotated,
Name
_TermVariant_application,
Name
_TermVariant_literal,
Name
_TermVariant_function,
Name
_TermVariant_list,
Name
_TermVariant_map,
Name
_TermVariant_optional,
Name
_TermVariant_product,
Name
_TermVariant_record,
Name
_TermVariant_set,
Name
_TermVariant_sum,
Name
_TermVariant_typed,
Name
_TermVariant_union,
Name
_TermVariant_variable,
Name
_TermVariant_wrap]
typeVariantDef :: Definition (Type -> TypeVariant)
typeVariantDef :: Definition (Type -> TypeVariant)
typeVariantDef = String
-> Datum (Type -> TypeVariant) -> Definition (Type -> TypeVariant)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"typeVariant" (Datum (Type -> TypeVariant) -> Definition (Type -> TypeVariant))
-> Datum (Type -> TypeVariant) -> Definition (Type -> TypeVariant)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Type -> TypeVariant) -> Datum (Type -> TypeVariant)
forall a. String -> Datum a -> Datum a
doc String
"Find the type variant (constructor) for a given type" (Datum (Type -> TypeVariant) -> Datum (Type -> TypeVariant))
-> Datum (Type -> TypeVariant) -> Datum (Type -> TypeVariant)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Type -> TypeVariant)
-> Datum (Type -> TypeVariant)
forall a. Type -> Type -> Datum a -> Datum a
function Type
typeT Type
typeVariantT (Datum (Type -> TypeVariant) -> Datum (Type -> TypeVariant))
-> Datum (Type -> TypeVariant) -> Datum (Type -> TypeVariant)
forall a b. (a -> b) -> a -> b
$
Name
-> Name
-> Maybe (Datum TypeVariant)
-> [(Name, Name)]
-> Datum (Type -> TypeVariant)
forall b a.
Name -> Name -> Maybe (Datum b) -> [(Name, Name)] -> Datum (a -> b)
matchToEnum Name
_Type Name
_TypeVariant Maybe (Datum TypeVariant)
forall a. Maybe a
Nothing [
Name
_Type_annotated Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_annotated,
Name
_Type_application Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_application,
Name
_Type_function Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_function,
Name
_Type_lambda Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_lambda,
Name
_Type_list Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_list,
Name
_Type_literal Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_literal,
Name
_Type_map Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_map,
Name
_Type_optional Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_optional,
Name
_Type_product Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_product,
Name
_Type_record Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_record,
Name
_Type_set Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_set,
Name
_Type_sum Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_sum,
Name
_Type_union Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_union,
Name
_Type_variable Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_variable,
Name
_Type_wrap Name -> Name -> (Name, Name)
forall a b. a -> b -> (a, b)
@-> Name
_TypeVariant_wrap]
typeVariantsDef :: Definition [TypeVariant]
typeVariantsDef :: Definition [TypeVariant]
typeVariantsDef = String -> Datum [TypeVariant] -> Definition [TypeVariant]
forall a. String -> Datum a -> Definition a
basicsDefinition String
"typeVariants" (Datum [TypeVariant] -> Definition [TypeVariant])
-> Datum [TypeVariant] -> Definition [TypeVariant]
forall a b. (a -> b) -> a -> b
$
String -> Datum [TypeVariant] -> Datum [TypeVariant]
forall a. String -> Datum a -> Datum a
doc String
"All type variants, in a canonical order" (Datum [TypeVariant] -> Datum [TypeVariant])
-> Datum [TypeVariant] -> Datum [TypeVariant]
forall a b. (a -> b) -> a -> b
$
Type -> Datum [TypeVariant] -> Datum [TypeVariant]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
typeVariantT) (Datum [TypeVariant] -> Datum [TypeVariant])
-> Datum [TypeVariant] -> Datum [TypeVariant]
forall a b. (a -> b) -> a -> b
$
[Datum TypeVariant] -> Datum [TypeVariant]
forall a. [Datum a] -> Datum [a]
list ([Datum TypeVariant] -> Datum [TypeVariant])
-> [Datum TypeVariant] -> Datum [TypeVariant]
forall a b. (a -> b) -> a -> b
$ Name -> Name -> Datum TypeVariant
forall a. Name -> Name -> Datum a
unitVariant Name
_TypeVariant (Name -> Datum TypeVariant) -> [Name] -> [Datum TypeVariant]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [
Name
_TypeVariant_annotated,
Name
_TypeVariant_application,
Name
_TypeVariant_function,
Name
_TypeVariant_lambda,
Name
_TypeVariant_list,
Name
_TypeVariant_literal,
Name
_TypeVariant_map,
Name
_TypeVariant_wrap,
Name
_TypeVariant_optional,
Name
_TypeVariant_product,
Name
_TypeVariant_record,
Name
_TypeVariant_set,
Name
_TypeVariant_sum,
Name
_TypeVariant_union,
Name
_TypeVariant_variable]
capitalizeDef :: Definition (String -> String)
capitalizeDef :: Definition (String -> String)
capitalizeDef = String -> Datum (String -> String) -> Definition (String -> String)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"capitalize" (Datum (String -> String) -> Definition (String -> String))
-> Datum (String -> String) -> Definition (String -> String)
forall a b. (a -> b) -> a -> b
$
String -> Datum (String -> String) -> Datum (String -> String)
forall a. String -> Datum a -> Datum a
doc String
"Capitalize the first letter of a string" (Datum (String -> String) -> Datum (String -> String))
-> Datum (String -> String) -> Datum (String -> String)
forall a b. (a -> b) -> a -> b
$
Type
-> Type -> Datum (String -> String) -> Datum (String -> String)
forall a. Type -> Type -> Datum a -> Datum a
function Type
stringT Type
stringT (Datum (String -> String) -> Datum (String -> String))
-> Datum (String -> String) -> Datum (String -> String)
forall a b. (a -> b) -> a -> b
$
Definition ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String)
forall a. Definition a -> Datum a
ref Definition ((String -> String) -> String -> String)
mapFirstLetterDef Datum ((String -> String) -> String -> String)
-> Datum (String -> String) -> Datum (String -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum (String -> String)
Strings.toUpper
decapitalizeDef :: Definition (String -> String)
decapitalizeDef :: Definition (String -> String)
decapitalizeDef = String -> Datum (String -> String) -> Definition (String -> String)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"decapitalize" (Datum (String -> String) -> Definition (String -> String))
-> Datum (String -> String) -> Definition (String -> String)
forall a b. (a -> b) -> a -> b
$
String -> Datum (String -> String) -> Datum (String -> String)
forall a. String -> Datum a -> Datum a
doc String
"Decapitalize the first letter of a string" (Datum (String -> String) -> Datum (String -> String))
-> Datum (String -> String) -> Datum (String -> String)
forall a b. (a -> b) -> a -> b
$
Type
-> Type -> Datum (String -> String) -> Datum (String -> String)
forall a. Type -> Type -> Datum a -> Datum a
function Type
stringT Type
stringT (Datum (String -> String) -> Datum (String -> String))
-> Datum (String -> String) -> Datum (String -> String)
forall a b. (a -> b) -> a -> b
$
Definition ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String)
forall a. Definition a -> Datum a
ref Definition ((String -> String) -> String -> String)
mapFirstLetterDef Datum ((String -> String) -> String -> String)
-> Datum (String -> String) -> Datum (String -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum (String -> String)
Strings.toLower
mapFirstLetterDef :: Definition ((String -> String) -> String -> String)
mapFirstLetterDef :: Definition ((String -> String) -> String -> String)
mapFirstLetterDef = String
-> Datum ((String -> String) -> String -> String)
-> Definition ((String -> String) -> String -> String)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"mapFirstLetter" (Datum ((String -> String) -> String -> String)
-> Definition ((String -> String) -> String -> String))
-> Datum ((String -> String) -> String -> String)
-> Definition ((String -> String) -> String -> String)
forall a b. (a -> b) -> a -> b
$
String
-> Datum ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String)
forall a. String -> Datum a -> Datum a
doc String
"A helper which maps the first letter of a string to another string" (Datum ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String))
-> Datum ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String)
forall a. Type -> Type -> Datum a -> Datum a
function (Type -> Type -> Type
funT Type
stringT Type
stringT) (Type -> Type -> Type
funT Type
stringT Type
stringT) (Datum ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String))
-> Datum ((String -> String) -> String -> String)
-> Datum ((String -> String) -> String -> String)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Any -> Any)
-> Datum ((String -> String) -> String -> String)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"mapping" (Datum (Any -> Any)
-> Datum ((String -> String) -> String -> String))
-> Datum (Any -> Any)
-> Datum ((String -> String) -> String -> String)
forall a b. (a -> b) -> a -> b
$ String -> Datum String -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"s" ((Datum (String -> String -> Bool -> String)
forall a. Datum (a -> a -> Bool -> a)
Logic.ifElse
Datum (String -> String -> Bool -> String)
-> Datum String -> Datum (String -> Bool -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum String
forall a. String -> Datum a
var String
"s"
Datum (String -> Bool -> String)
-> Datum String -> Datum (Bool -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum (String -> String -> String)
Strings.cat2 Datum (String -> String -> String)
-> Datum String -> Datum (String -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum String
forall a. String -> Datum a
var String
"firstLetter" Datum (String -> String) -> Datum String -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([Int] -> String)
Strings.fromList Datum ([Int] -> String) -> Datum [Int] -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([Int] -> [Int])
forall a. Datum ([a] -> [a])
Lists.tail Datum ([Int] -> [Int]) -> Datum [Int] -> Datum [Int]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Int]
forall a. String -> Datum a
var String
"list")))
Datum (Bool -> String) -> Datum Bool -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum (String -> Bool)
Strings.isEmpty Datum (String -> Bool) -> Datum String -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum String
forall a. String -> Datum a
var String
"s"))
Datum String -> [Field] -> Datum String
forall a. Datum a -> [Field] -> Datum a
`with` [
String
"firstLetter"String -> Datum Any -> Field
forall a. String -> Datum a -> Field
>: String -> Datum (String -> Any)
forall a. String -> Datum a
var String
"mapping" Datum (String -> Any) -> Datum String -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([Int] -> String)
Strings.fromList Datum ([Int] -> String) -> Datum [Int] -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum (Int -> [Int])
forall a. Datum (a -> [a])
Lists.pure Datum (Int -> [Int]) -> Datum Int -> Datum [Int]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([Int] -> Int)
forall a. Datum ([a] -> a)
Lists.head Datum ([Int] -> Int) -> Datum [Int] -> Datum Int
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Int]
forall a. String -> Datum a
var String
"list"))),
String
"list"String -> Datum [Int] -> Field
forall a. String -> Datum a -> Field
>: Type -> Datum [Int] -> Datum [Int]
forall a. Type -> Datum a -> Datum a
typed (Type -> Type
listT Type
int32T) (Datum [Int] -> Datum [Int]) -> Datum [Int] -> Datum [Int]
forall a b. (a -> b) -> a -> b
$ Datum (String -> [Int])
Strings.toList Datum (String -> [Int]) -> Datum String -> Datum [Int]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum String
forall a. String -> Datum a
var String
"s"])
fieldMapDef :: Definition ([Field] -> M.Map Name Term)
fieldMapDef :: Definition ([Field] -> Map Name Term)
fieldMapDef = String
-> Datum ([Field] -> Map Name Term)
-> Definition ([Field] -> Map Name Term)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"fieldMap" (Datum ([Field] -> Map Name Term)
-> Definition ([Field] -> Map Name Term))
-> Datum ([Field] -> Map Name Term)
-> Definition ([Field] -> Map Name Term)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum ([Field] -> Map Name Term)
-> Datum ([Field] -> Map Name Term)
forall a. Type -> Type -> Datum a -> Datum a
function (Type -> Type
TypeList Type
fieldT) (Type -> Type -> Type
mapT Type
fieldNameT Type
termT) (Datum ([Field] -> Map Name Term)
-> Datum ([Field] -> Map Name Term))
-> Datum ([Field] -> Map Name Term)
-> Datum ([Field] -> Map Name Term)
forall a b. (a -> b) -> a -> b
$
(String -> Datum (Map Any Any) -> Datum ([Field] -> Map Name Term)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"fields" (Datum (Map Any Any) -> Datum ([Field] -> Map Name Term))
-> Datum (Map Any Any) -> Datum ([Field] -> Map Name Term)
forall a b. (a -> b) -> a -> b
$ Datum ([(Any, Any)] -> Map Any Any)
forall k v. Datum ([(k, v)] -> Map k v)
Maps.fromList Datum ([(Any, Any)] -> Map Any Any)
-> Datum [(Any, Any)] -> Datum (Map Any Any)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ((Any -> (Any, Any)) -> [Any] -> [(Any, Any)])
forall a b. Datum ((a -> b) -> [a] -> [b])
Lists.map Datum ((Any -> (Any, Any)) -> [Any] -> [(Any, Any)])
-> Datum (Any -> (Any, Any)) -> Datum ([Any] -> [(Any, Any)])
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum (Any -> (Any, Any))
forall a. String -> Datum a
var String
"toPair" Datum ([Any] -> [(Any, Any)]) -> Datum [Any] -> Datum [(Any, Any)]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Any]
forall a. String -> Datum a
var String
"fields"))
Datum ([Field] -> Map Name Term)
-> [Field] -> Datum ([Field] -> Map Name Term)
forall a. Datum a -> [Field] -> Datum a
`with` [
String
"toPair"String -> Datum (Any -> Any) -> Field
forall a. String -> Datum a -> Field
>: String -> Datum (Any, Any) -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"f" (Datum (Any, Any) -> Datum (Any -> Any))
-> Datum (Any, Any) -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ (Datum Any, Datum Any) -> Datum (Any, Any)
forall a b. (Datum a, Datum b) -> Datum (a, b)
pair (Name -> Name -> Datum (Any -> Any)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_Field Name
_Field_name Datum (Any -> Any) -> Datum Any -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"f", Name -> Name -> Datum (Any -> Any)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_Field Name
_Field_term Datum (Any -> Any) -> Datum Any -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"f")]
fieldTypeMapDef :: Definition ([FieldType] -> M.Map Name Type)
fieldTypeMapDef :: Definition ([FieldType] -> Map Name Type)
fieldTypeMapDef = String
-> Datum ([FieldType] -> Map Name Type)
-> Definition ([FieldType] -> Map Name Type)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"fieldTypeMap" (Datum ([FieldType] -> Map Name Type)
-> Definition ([FieldType] -> Map Name Type))
-> Datum ([FieldType] -> Map Name Type)
-> Definition ([FieldType] -> Map Name Type)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum ([FieldType] -> Map Name Type)
-> Datum ([FieldType] -> Map Name Type)
forall a. Type -> Type -> Datum a -> Datum a
function (Type -> Type
TypeList Type
fieldTypeT) (Type -> Type -> Type
mapT Type
fieldNameT Type
typeT) (Datum ([FieldType] -> Map Name Type)
-> Datum ([FieldType] -> Map Name Type))
-> Datum ([FieldType] -> Map Name Type)
-> Datum ([FieldType] -> Map Name Type)
forall a b. (a -> b) -> a -> b
$
(String
-> Datum (Map Any Any) -> Datum ([FieldType] -> Map Name Type)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"fields" (Datum (Map Any Any) -> Datum ([FieldType] -> Map Name Type))
-> Datum (Map Any Any) -> Datum ([FieldType] -> Map Name Type)
forall a b. (a -> b) -> a -> b
$ Datum ([(Any, Any)] -> Map Any Any)
forall k v. Datum ([(k, v)] -> Map k v)
Maps.fromList Datum ([(Any, Any)] -> Map Any Any)
-> Datum [(Any, Any)] -> Datum (Map Any Any)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ((Any -> (Any, Any)) -> [Any] -> [(Any, Any)])
forall a b. Datum ((a -> b) -> [a] -> [b])
Lists.map Datum ((Any -> (Any, Any)) -> [Any] -> [(Any, Any)])
-> Datum (Any -> (Any, Any)) -> Datum ([Any] -> [(Any, Any)])
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum (Any -> (Any, Any))
forall a. String -> Datum a
var String
"toPair" Datum ([Any] -> [(Any, Any)]) -> Datum [Any] -> Datum [(Any, Any)]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Any]
forall a. String -> Datum a
var String
"fields"))
Datum ([FieldType] -> Map Name Type)
-> [Field] -> Datum ([FieldType] -> Map Name Type)
forall a. Datum a -> [Field] -> Datum a
`with` [
String
"toPair"String -> Datum (Any -> Any) -> Field
forall a. String -> Datum a -> Field
>: String -> Datum (Any, Any) -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"f" (Datum (Any, Any) -> Datum (Any -> Any))
-> Datum (Any, Any) -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ (Datum Any, Datum Any) -> Datum (Any, Any)
forall a b. (Datum a, Datum b) -> Datum (a, b)
pair (Name -> Name -> Datum (Any -> Any)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_FieldType Name
_FieldType_name Datum (Any -> Any) -> Datum Any -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"f", Name -> Name -> Datum (Any -> Any)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_FieldType Name
_FieldType_type Datum (Any -> Any) -> Datum Any -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"f")]
isEncodedTypeDef :: Definition (Term -> Bool)
isEncodedTypeDef :: Definition (Term -> Bool)
isEncodedTypeDef = String -> Datum (Term -> Bool) -> Definition (Term -> Bool)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"isEncodedType" (Datum (Term -> Bool) -> Definition (Term -> Bool))
-> Datum (Term -> Bool) -> Definition (Term -> Bool)
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Datum (Term -> Bool) -> Datum (Term -> Bool)
forall a. Type -> Type -> Datum a -> Datum a
function Type
termT Type
booleanT (Datum (Term -> Bool) -> Datum (Term -> Bool))
-> Datum (Term -> Bool) -> Datum (Term -> Bool)
forall a b. (a -> b) -> a -> b
$
String -> Datum Bool -> Datum (Term -> Bool)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"t" (Datum Bool -> Datum (Term -> Bool))
-> Datum Bool -> Datum (Term -> Bool)
forall a b. (a -> b) -> a -> b
$ (Name -> Maybe (Datum Bool) -> [Field] -> Datum (Term -> Bool)
forall b u. Name -> Maybe (Datum b) -> [Field] -> Datum (u -> b)
match Name
_Term (Datum Bool -> Maybe (Datum Bool)
forall a. a -> Maybe a
Just Datum Bool
false) [
Name -> Case Any
forall a. Name -> Case a
Case Name
_Term_application Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> String -> Datum Bool -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"a" (Datum Bool -> Datum (Any -> Any))
-> Datum Bool -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$
Definition (Term -> Bool) -> Datum (Term -> Bool)
forall a. Definition a -> Datum a
ref Definition (Term -> Bool)
isEncodedTypeDef Datum (Term -> Bool) -> Datum Term -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Name -> Datum (Any -> Term)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_Application Name
_Application_function Datum (Any -> Term) -> Datum Any -> Datum Term
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"a"),
Name -> Case Any
forall a. Name -> Case a
Case Name
_Term_union Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> String -> Datum Bool -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"i" (Datum Bool -> Datum (Any -> Any))
-> Datum Bool -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$
Datum (String -> String -> Bool)
Equality.equalString Datum (String -> String -> Bool)
-> Datum String -> Datum (String -> Bool)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (String -> Datum String
string (String -> Datum String) -> String -> Datum String
forall a b. (a -> b) -> a -> b
$ Name -> String
unName Name
_Type) Datum (String -> Bool) -> Datum String -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_Name Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Name -> Datum (Any -> Any)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_Injection Name
_Injection_typeName Datum (Any -> Any) -> Datum Any -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"i"))
]) Datum (Term -> Bool) -> Datum Term -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Definition (Term -> Term) -> Datum (Term -> Term)
forall a. Definition a -> Datum a
ref Definition (Term -> Term)
stripTermDef Datum (Term -> Term) -> Datum Term -> Datum Term
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Term
forall a. String -> Datum a
var String
"t")
isTypeDef :: Definition (Type -> Bool)
isTypeDef :: Definition (Type -> Bool)
isTypeDef = String -> Datum (Type -> Bool) -> Definition (Type -> Bool)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"isType" (Datum (Type -> Bool) -> Definition (Type -> Bool))
-> Datum (Type -> Bool) -> Definition (Type -> Bool)
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Datum (Type -> Bool) -> Datum (Type -> Bool)
forall a. Type -> Type -> Datum a -> Datum a
function Type
typeT Type
booleanT (Datum (Type -> Bool) -> Datum (Type -> Bool))
-> Datum (Type -> Bool) -> Datum (Type -> Bool)
forall a b. (a -> b) -> a -> b
$
String -> Datum Bool -> Datum (Type -> Bool)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"t" (Datum Bool -> Datum (Type -> Bool))
-> Datum Bool -> Datum (Type -> Bool)
forall a b. (a -> b) -> a -> b
$ (Name -> Maybe (Datum Bool) -> [Field] -> Datum (Type -> Bool)
forall b u. Name -> Maybe (Datum b) -> [Field] -> Datum (u -> b)
match Name
_Type (Datum Bool -> Maybe (Datum Bool)
forall a. a -> Maybe a
Just Datum Bool
false) [
Name -> Case Any
forall a. Name -> Case a
Case Name
_Type_application Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> String -> Datum Bool -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"a" (Datum Bool -> Datum (Any -> Any))
-> Datum Bool -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$
Definition (Type -> Bool) -> Datum (Type -> Bool)
forall a. Definition a -> Datum a
ref Definition (Type -> Bool)
isTypeDef Datum (Type -> Bool) -> Datum Type -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Name -> Datum (Any -> Type)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_ApplicationType Name
_ApplicationType_function Datum (Any -> Type) -> Datum Any -> Datum Type
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"a"),
Name -> Case Any
forall a. Name -> Case a
Case Name
_Type_lambda Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> String -> Datum Bool -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"l" (Datum Bool -> Datum (Any -> Any))
-> Datum Bool -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$
Definition (Type -> Bool) -> Datum (Type -> Bool)
forall a. Definition a -> Datum a
ref Definition (Type -> Bool)
isTypeDef Datum (Type -> Bool) -> Datum Type -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Name -> Datum (Any -> Type)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_LambdaType Name
_LambdaType_body Datum (Any -> Type) -> Datum Any -> Datum Type
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"l"),
Name -> Case Any
forall a. Name -> Case a
Case Name
_Type_union Case Any -> Datum (Any -> Any) -> Field
forall a b. Case a -> Datum (a -> b) -> Field
--> String -> Datum Bool -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"rt" (Datum Bool -> Datum (Any -> Any))
-> Datum Bool -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$
Datum (String -> String -> Bool)
Equality.equalString Datum (String -> String -> Bool)
-> Datum String -> Datum (String -> Bool)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (String -> Datum String
string (String -> Datum String) -> String -> Datum String
forall a b. (a -> b) -> a -> b
$ Name -> String
unName Name
_Type) Datum (String -> Bool) -> Datum String -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_Name Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Name -> Datum (Any -> Any)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_RowType Name
_RowType_typeName Datum (Any -> Any) -> Datum Any -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"rt"))
]) Datum (Type -> Bool) -> Datum Type -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Definition (Type -> Type) -> Datum (Type -> Type)
forall a. Definition a -> Datum a
ref Definition (Type -> Type)
stripTypeDef Datum (Type -> Type) -> Datum Type -> Datum Type
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Type
forall a. String -> Datum a
var String
"t")
isUnitTermDef :: Definition (Term -> Bool)
isUnitTermDef :: Definition (Term -> Bool)
isUnitTermDef = String -> Datum (Term -> Bool) -> Definition (Term -> Bool)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"isUnitTerm" (Datum (Term -> Bool) -> Definition (Term -> Bool))
-> Datum (Term -> Bool) -> Definition (Term -> Bool)
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Datum (Term -> Bool) -> Datum (Term -> Bool)
forall a. Type -> Type -> Datum a -> Datum a
function Type
termT Type
booleanT (Datum (Term -> Bool) -> Datum (Term -> Bool))
-> Datum (Term -> Bool) -> Datum (Term -> Bool)
forall a b. (a -> b) -> a -> b
$
String -> Datum Bool -> Datum (Term -> Bool)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"t" (Datum Bool -> Datum (Term -> Bool))
-> Datum Bool -> Datum (Term -> Bool)
forall a b. (a -> b) -> a -> b
$ Datum (Term -> Term -> Bool)
Equality.equalTerm Datum (Term -> Term -> Bool) -> Datum Term -> Datum (Term -> Bool)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Definition (Term -> Term) -> Datum (Term -> Term)
forall a. Definition a -> Datum a
ref Definition (Term -> Term)
fullyStripTermDef Datum (Term -> Term) -> Datum Term -> Datum Term
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Term
forall a. String -> Datum a
var String
"t") Datum (Term -> Bool) -> Datum Term -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Term -> Datum Term
forall a. Term -> Datum a
Datum (Term -> Term
coreEncodeTerm Term
Terms.unit)
isUnitTypeDef :: Definition (Term -> Bool)
isUnitTypeDef :: Definition (Term -> Bool)
isUnitTypeDef = String -> Datum (Term -> Bool) -> Definition (Term -> Bool)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"isUnitType" (Datum (Term -> Bool) -> Definition (Term -> Bool))
-> Datum (Term -> Bool) -> Definition (Term -> Bool)
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Datum (Term -> Bool) -> Datum (Term -> Bool)
forall a. Type -> Type -> Datum a -> Datum a
function Type
typeT Type
booleanT (Datum (Term -> Bool) -> Datum (Term -> Bool))
-> Datum (Term -> Bool) -> Datum (Term -> Bool)
forall a b. (a -> b) -> a -> b
$
String -> Datum Bool -> Datum (Term -> Bool)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"t" (Datum Bool -> Datum (Term -> Bool))
-> Datum Bool -> Datum (Term -> Bool)
forall a b. (a -> b) -> a -> b
$ Datum (Type -> Type -> Bool)
Equality.equalType Datum (Type -> Type -> Bool) -> Datum Type -> Datum (Type -> Bool)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Definition (Type -> Type) -> Datum (Type -> Type)
forall a. Definition a -> Datum a
ref Definition (Type -> Type)
stripTypeDef Datum (Type -> Type) -> Datum Type -> Datum Type
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Type
forall a. String -> Datum a
var String
"t") Datum (Type -> Bool) -> Datum Type -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Term -> Datum Type
forall a. Term -> Datum a
Datum (Type -> Term
coreEncodeType Type
unitT)
elementsToGraphDef :: Definition (Graph -> Maybe Graph -> [Element] -> Graph)
elementsToGraphDef :: Definition (Graph -> Maybe Graph -> [Element] -> Graph)
elementsToGraphDef = String
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
-> Definition (Graph -> Maybe Graph -> [Element] -> Graph)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"elementsToGraph" (Datum (Graph -> Maybe Graph -> [Element] -> Graph)
-> Definition (Graph -> Maybe Graph -> [Element] -> Graph))
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
-> Definition (Graph -> Maybe Graph -> [Element] -> Graph)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
forall a. Type -> Type -> Datum a -> Datum a
function Type
graphT (Type -> Type -> Type
funT (Type -> Type
optionalT Type
graphT) (Type -> Type -> Type
funT (Type -> Type
TypeList Type
elementT) Type
graphT)) (Datum (Graph -> Maybe Graph -> [Element] -> Graph)
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph))
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Any -> Any)
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"parent" (Datum (Any -> Any)
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph))
-> Datum (Any -> Any)
-> Datum (Graph -> Maybe Graph -> [Element] -> Graph)
forall a b. (a -> b) -> a -> b
$ String -> Datum (Any -> Any) -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"schema" (Datum (Any -> Any) -> Datum (Any -> Any))
-> Datum (Any -> Any) -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ String -> Datum Graph -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"elements" (Datum Graph -> Datum (Any -> Any))
-> Datum Graph -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$
Datum (Map Name Element)
-> Datum (Map Name (Maybe Term))
-> Datum (Map Name Type)
-> Datum Term
-> Datum (Map Name Primitive)
-> Datum (Maybe Graph)
-> Datum Graph
Graph.graph
(Datum ([(Name, Element)] -> Map Name Element)
forall k v. Datum ([(k, v)] -> Map k v)
Maps.fromList Datum ([(Name, Element)] -> Map Name Element)
-> Datum [(Name, Element)] -> Datum (Map Name Element)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ((Any -> (Name, Element)) -> [Any] -> [(Name, Element)])
forall a b. Datum ((a -> b) -> [a] -> [b])
Lists.map Datum ((Any -> (Name, Element)) -> [Any] -> [(Name, Element)])
-> Datum (Any -> (Name, Element))
-> Datum ([Any] -> [(Name, Element)])
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum (Any -> (Name, Element))
forall a. String -> Datum a
var String
"toPair" Datum ([Any] -> [(Name, Element)])
-> Datum [Any] -> Datum [(Name, Element)]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Any]
forall a. String -> Datum a
var String
"elements"))
(Datum (Graph -> Map Name (Maybe Term))
Graph.graphEnvironment Datum (Graph -> Map Name (Maybe Term))
-> Datum Graph -> Datum (Map Name (Maybe Term))
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Graph
forall a. String -> Datum a
var String
"parent")
(Datum (Graph -> Map Name Type)
Graph.graphTypes Datum (Graph -> Map Name Type)
-> Datum Graph -> Datum (Map Name Type)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Graph
forall a. String -> Datum a
var String
"parent")
(Datum (Graph -> Term)
Graph.graphBody Datum (Graph -> Term) -> Datum Graph -> Datum Term
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Graph
forall a. String -> Datum a
var String
"parent")
(Datum (Graph -> Map Name Primitive)
Graph.graphPrimitives Datum (Graph -> Map Name Primitive)
-> Datum Graph -> Datum (Map Name Primitive)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Graph
forall a. String -> Datum a
var String
"parent")
(String -> Datum (Maybe Graph)
forall a. String -> Datum a
var String
"schema")
Datum Graph -> [Field] -> Datum Graph
forall a. Datum a -> [Field] -> Datum a
`with` [
String
"toPair" String -> Datum (Any -> Any) -> Field
forall a. String -> Datum a -> Field
>: String -> Datum (Any, Any) -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"el" (Datum (Any, Any) -> Datum (Any -> Any))
-> Datum (Any, Any) -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ (Datum Any, Datum Any) -> Datum (Any, Any)
forall a b. (Datum a, Datum b) -> Datum (a, b)
pair (Name -> Name -> Datum (Any -> Any)
forall a b. Name -> Name -> Datum (a -> b)
project Name
_Element Name
_Element_name Datum (Any -> Any) -> Datum Any -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"el", String -> Datum Any
forall a. String -> Datum a
var String
"el")]
localNameOfEagerDef :: Definition (Name -> String)
localNameOfEagerDef :: Definition (Name -> String)
localNameOfEagerDef = String -> Datum (Name -> String) -> Definition (Name -> String)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"localNameOfEager" (Datum (Name -> String) -> Definition (Name -> String))
-> Datum (Name -> String) -> Definition (Name -> String)
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Datum (Name -> String) -> Datum (Name -> String)
forall a. Type -> Type -> Datum a -> Datum a
function Type
nameT Type
stringT (Datum (Name -> String) -> Datum (Name -> String))
-> Datum (Name -> String) -> Datum (Name -> String)
forall a b. (a -> b) -> a -> b
$
Datum (QualifiedName -> String)
Module.qualifiedNameLocal Datum (QualifiedName -> String)
-> Datum (Name -> QualifiedName) -> Datum (Name -> String)
forall b c a. Datum (b -> c) -> Datum (a -> b) -> Datum (a -> c)
<.> Definition (Name -> QualifiedName) -> Datum (Name -> QualifiedName)
forall a. Definition a -> Datum a
ref Definition (Name -> QualifiedName)
qualifyNameEagerDef
localNameOfLazyDef :: Definition (Name -> String)
localNameOfLazyDef :: Definition (Name -> String)
localNameOfLazyDef = String -> Datum (Name -> String) -> Definition (Name -> String)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"localNameOfLazy" (Datum (Name -> String) -> Definition (Name -> String))
-> Datum (Name -> String) -> Definition (Name -> String)
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Datum (Name -> String) -> Datum (Name -> String)
forall a. Type -> Type -> Datum a -> Datum a
function Type
nameT Type
stringT (Datum (Name -> String) -> Datum (Name -> String))
-> Datum (Name -> String) -> Datum (Name -> String)
forall a b. (a -> b) -> a -> b
$
Datum (QualifiedName -> String)
Module.qualifiedNameLocal Datum (QualifiedName -> String)
-> Datum (Name -> QualifiedName) -> Datum (Name -> String)
forall b c a. Datum (b -> c) -> Datum (a -> b) -> Datum (a -> c)
<.> Definition (Name -> QualifiedName) -> Datum (Name -> QualifiedName)
forall a. Definition a -> Datum a
ref Definition (Name -> QualifiedName)
qualifyNameLazyDef
namespaceOfEagerDef :: Definition (Name -> Maybe Namespace)
namespaceOfEagerDef :: Definition (Name -> Maybe Namespace)
namespaceOfEagerDef = String
-> Datum (Name -> Maybe Namespace)
-> Definition (Name -> Maybe Namespace)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"namespaceOfEager" (Datum (Name -> Maybe Namespace)
-> Definition (Name -> Maybe Namespace))
-> Datum (Name -> Maybe Namespace)
-> Definition (Name -> Maybe Namespace)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Name -> Maybe Namespace)
-> Datum (Name -> Maybe Namespace)
forall a. Type -> Type -> Datum a -> Datum a
function Type
nameT (Type -> Type
optionalT Type
namespaceT) (Datum (Name -> Maybe Namespace)
-> Datum (Name -> Maybe Namespace))
-> Datum (Name -> Maybe Namespace)
-> Datum (Name -> Maybe Namespace)
forall a b. (a -> b) -> a -> b
$
Datum (QualifiedName -> Maybe Namespace)
Module.qualifiedNameNamespace Datum (QualifiedName -> Maybe Namespace)
-> Datum (Name -> QualifiedName) -> Datum (Name -> Maybe Namespace)
forall b c a. Datum (b -> c) -> Datum (a -> b) -> Datum (a -> c)
<.> Definition (Name -> QualifiedName) -> Datum (Name -> QualifiedName)
forall a. Definition a -> Datum a
ref Definition (Name -> QualifiedName)
qualifyNameEagerDef
namespaceOfLazyDef :: Definition (Name -> Maybe Namespace)
namespaceOfLazyDef :: Definition (Name -> Maybe Namespace)
namespaceOfLazyDef = String
-> Datum (Name -> Maybe Namespace)
-> Definition (Name -> Maybe Namespace)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"namespaceOfLazy" (Datum (Name -> Maybe Namespace)
-> Definition (Name -> Maybe Namespace))
-> Datum (Name -> Maybe Namespace)
-> Definition (Name -> Maybe Namespace)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Name -> Maybe Namespace)
-> Datum (Name -> Maybe Namespace)
forall a. Type -> Type -> Datum a -> Datum a
function Type
nameT (Type -> Type
optionalT Type
namespaceT) (Datum (Name -> Maybe Namespace)
-> Datum (Name -> Maybe Namespace))
-> Datum (Name -> Maybe Namespace)
-> Datum (Name -> Maybe Namespace)
forall a b. (a -> b) -> a -> b
$
Datum (QualifiedName -> Maybe Namespace)
Module.qualifiedNameNamespace Datum (QualifiedName -> Maybe Namespace)
-> Datum (Name -> QualifiedName) -> Datum (Name -> Maybe Namespace)
forall b c a. Datum (b -> c) -> Datum (a -> b) -> Datum (a -> c)
<.> Definition (Name -> QualifiedName) -> Datum (Name -> QualifiedName)
forall a. Definition a -> Datum a
ref Definition (Name -> QualifiedName)
qualifyNameLazyDef
namespaceToFilePathDef :: Definition (Bool -> FileExtension -> Namespace -> String)
namespaceToFilePathDef :: Definition (Bool -> FileExtension -> Namespace -> String)
namespaceToFilePathDef = String
-> Datum (Bool -> FileExtension -> Namespace -> String)
-> Definition (Bool -> FileExtension -> Namespace -> String)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"namespaceToFilePath" (Datum (Bool -> FileExtension -> Namespace -> String)
-> Definition (Bool -> FileExtension -> Namespace -> String))
-> Datum (Bool -> FileExtension -> Namespace -> String)
-> Definition (Bool -> FileExtension -> Namespace -> String)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Bool -> FileExtension -> Namespace -> String)
-> Datum (Bool -> FileExtension -> Namespace -> String)
forall a. Type -> Type -> Datum a -> Datum a
function Type
booleanT (Type -> Type -> Type
funT Type
fileExtensionT (Type -> Type -> Type
funT Type
namespaceT Type
stringT)) (Datum (Bool -> FileExtension -> Namespace -> String)
-> Datum (Bool -> FileExtension -> Namespace -> String))
-> Datum (Bool -> FileExtension -> Namespace -> String)
-> Datum (Bool -> FileExtension -> Namespace -> String)
forall a b. (a -> b) -> a -> b
$
String
-> Datum (Any -> Any)
-> Datum (Bool -> FileExtension -> Namespace -> String)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"caps" (Datum (Any -> Any)
-> Datum (Bool -> FileExtension -> Namespace -> String))
-> Datum (Any -> Any)
-> Datum (Bool -> FileExtension -> Namespace -> String)
forall a b. (a -> b) -> a -> b
$ String -> Datum (Any -> Any) -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"ext" (Datum (Any -> Any) -> Datum (Any -> Any))
-> Datum (Any -> Any) -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$ String -> Datum String -> Datum (Any -> Any)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"ns" (Datum String -> Datum (Any -> Any))
-> Datum String -> Datum (Any -> Any)
forall a b. (a -> b) -> a -> b
$
(((Datum (String -> [String] -> String)
Strings.intercalate Datum (String -> [String] -> String)
-> Datum String -> Datum ([String] -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum String
"/" Datum ([String] -> String) -> Datum [String] -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [String]
forall a. String -> Datum a
var String
"parts") Datum String -> Datum String -> Datum String
++ Datum String
"." Datum String -> Datum String -> Datum String
++ (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_FileExtension Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"ext"))
Datum String -> [Field] -> Datum String
forall a. Datum a -> [Field] -> Datum a
`with` [
String
"parts"String -> Datum [String] -> Field
forall a. String -> Datum a -> Field
>: Datum ((String -> String) -> [String] -> [String])
forall a b. Datum ((a -> b) -> [a] -> [b])
Lists.map Datum ((String -> String) -> [String] -> [String])
-> Datum (String -> String) -> Datum ([String] -> [String])
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum
((String -> String)
-> (String -> String) -> Bool -> String -> String)
forall a. Datum (a -> a -> Bool -> a)
Logic.ifElse Datum
((String -> String)
-> (String -> String) -> Bool -> String -> String)
-> Datum (String -> String)
-> Datum ((String -> String) -> Bool -> String -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Definition (String -> String) -> Datum (String -> String)
forall a. Definition a -> Datum a
ref Definition (String -> String)
capitalizeDef Datum ((String -> String) -> Bool -> String -> String)
-> Datum (String -> String) -> Datum (Bool -> String -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Definition (String -> String) -> Datum (String -> String)
forall a. Definition a -> Datum a
ref Definition (String -> String)
forall a. Definition (a -> a)
idDef Datum (Bool -> String -> String)
-> Datum Bool -> Datum (String -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Bool
forall a. String -> Datum a
var String
"caps") Datum ([String] -> [String]) -> Datum [String] -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum (String -> String -> [String])
Strings.splitOn Datum (String -> String -> [String])
-> Datum String -> Datum (String -> [String])
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum String
"/" Datum (String -> [String]) -> Datum String -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_Namespace Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"ns"))])
qualifyNameEagerDef :: Definition (Name -> QualifiedName)
qualifyNameEagerDef :: Definition (Name -> QualifiedName)
qualifyNameEagerDef = String
-> Datum (Name -> QualifiedName)
-> Definition (Name -> QualifiedName)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"qualifyNameEager" (Datum (Name -> QualifiedName)
-> Definition (Name -> QualifiedName))
-> Datum (Name -> QualifiedName)
-> Definition (Name -> QualifiedName)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Name -> QualifiedName)
-> Datum (Name -> QualifiedName)
forall a. Type -> Type -> Datum a -> Datum a
function Type
nameT Type
qualifiedNameT (Datum (Name -> QualifiedName) -> Datum (Name -> QualifiedName))
-> Datum (Name -> QualifiedName) -> Datum (Name -> QualifiedName)
forall a b. (a -> b) -> a -> b
$
String -> Datum QualifiedName -> Datum (Name -> QualifiedName)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"name" (Datum QualifiedName -> Datum (Name -> QualifiedName))
-> Datum QualifiedName -> Datum (Name -> QualifiedName)
forall a b. (a -> b) -> a -> b
$ ((Datum (QualifiedName -> QualifiedName -> Bool -> QualifiedName)
forall a. Datum (a -> a -> Bool -> a)
Logic.ifElse
Datum (QualifiedName -> QualifiedName -> Bool -> QualifiedName)
-> Datum QualifiedName
-> Datum (QualifiedName -> Bool -> QualifiedName)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum (Maybe Namespace) -> Datum String -> Datum QualifiedName
Module.qualifiedName Datum (Maybe Namespace)
forall a. Datum a
nothing (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_Name Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"name")
Datum (QualifiedName -> Bool -> QualifiedName)
-> Datum QualifiedName -> Datum (Bool -> QualifiedName)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum (Maybe Namespace) -> Datum String -> Datum QualifiedName
Module.qualifiedName
(Datum Namespace -> Datum (Maybe Namespace)
forall x. Datum x -> Datum (Maybe x)
just (Datum Namespace -> Datum (Maybe Namespace))
-> Datum Namespace -> Datum (Maybe Namespace)
forall a b. (a -> b) -> a -> b
$ Name -> Datum Any -> Datum Namespace
forall a b. Name -> Datum a -> Datum b
wrap Name
_Namespace (Datum ([Any] -> Any)
forall a. Datum ([a] -> a)
Lists.head Datum ([Any] -> Any) -> Datum [Any] -> Datum Any
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Any]
forall a. String -> Datum a
var String
"parts"))
(Datum (String -> [String] -> String)
Strings.intercalate Datum (String -> [String] -> String)
-> Datum String -> Datum ([String] -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum String
"." Datum ([String] -> String) -> Datum [String] -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([String] -> [String])
forall a. Datum ([a] -> [a])
Lists.tail Datum ([String] -> [String]) -> Datum [String] -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [String]
forall a. String -> Datum a
var String
"parts"))
Datum (Bool -> QualifiedName) -> Datum Bool -> Datum QualifiedName
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum (Int -> Int -> Bool)
Equality.equalInt32 Datum (Int -> Int -> Bool) -> Datum Int -> Datum (Int -> Bool)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Int -> Datum Int
int32 Int
1 Datum (Int -> Bool) -> Datum Int -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([Any] -> Int)
forall a. Datum ([a] -> Int)
Lists.length Datum ([Any] -> Int) -> Datum [Any] -> Datum Int
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Any]
forall a. String -> Datum a
var String
"parts")))
Datum QualifiedName -> [Field] -> Datum QualifiedName
forall a. Datum a -> [Field] -> Datum a
`with` [
String
"parts"String -> Datum [String] -> Field
forall a. String -> Datum a -> Field
>: Datum (String -> String -> [String])
Strings.splitOn Datum (String -> String -> [String])
-> Datum String -> Datum (String -> [String])
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum String
"." Datum (String -> [String]) -> Datum String -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_Name Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"name")])
qualifyNameLazyDef :: Definition (Name -> QualifiedName)
qualifyNameLazyDef :: Definition (Name -> QualifiedName)
qualifyNameLazyDef = String
-> Datum (Name -> QualifiedName)
-> Definition (Name -> QualifiedName)
forall a. String -> Datum a -> Definition a
basicsDefinition String
"qualifyNameLazy" (Datum (Name -> QualifiedName)
-> Definition (Name -> QualifiedName))
-> Datum (Name -> QualifiedName)
-> Definition (Name -> QualifiedName)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> Datum (Name -> QualifiedName)
-> Datum (Name -> QualifiedName)
forall a. Type -> Type -> Datum a -> Datum a
function Type
nameT Type
qualifiedNameT (Datum (Name -> QualifiedName) -> Datum (Name -> QualifiedName))
-> Datum (Name -> QualifiedName) -> Datum (Name -> QualifiedName)
forall a b. (a -> b) -> a -> b
$
String -> Datum QualifiedName -> Datum (Name -> QualifiedName)
forall x a b. String -> Datum x -> Datum (a -> b)
lambda String
"name" (Datum QualifiedName -> Datum (Name -> QualifiedName))
-> Datum QualifiedName -> Datum (Name -> QualifiedName)
forall a b. (a -> b) -> a -> b
$ (Datum (QualifiedName -> QualifiedName -> Bool -> QualifiedName)
forall a. Datum (a -> a -> Bool -> a)
Logic.ifElse
Datum (QualifiedName -> QualifiedName -> Bool -> QualifiedName)
-> Datum QualifiedName
-> Datum (QualifiedName -> Bool -> QualifiedName)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum (Maybe Namespace) -> Datum String -> Datum QualifiedName
Module.qualifiedName Datum (Maybe Namespace)
forall a. Datum a
nothing (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_Name Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"name")
Datum (QualifiedName -> Bool -> QualifiedName)
-> Datum QualifiedName -> Datum (Bool -> QualifiedName)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum (Maybe Namespace) -> Datum String -> Datum QualifiedName
Module.qualifiedName
(Datum Namespace -> Datum (Maybe Namespace)
forall x. Datum x -> Datum (Maybe x)
just (Datum Namespace -> Datum (Maybe Namespace))
-> Datum Namespace -> Datum (Maybe Namespace)
forall a b. (a -> b) -> a -> b
$ Name -> Datum String -> Datum Namespace
forall a b. Name -> Datum a -> Datum b
wrap Name
_Namespace (Datum (String -> [String] -> String)
Strings.intercalate Datum (String -> [String] -> String)
-> Datum String -> Datum ([String] -> String)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum String
"." Datum ([String] -> String) -> Datum [String] -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([String] -> [String])
forall a. Datum ([a] -> [a])
Lists.reverse Datum ([String] -> [String]) -> Datum [String] -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([String] -> [String])
forall a. Datum ([a] -> [a])
Lists.tail Datum ([String] -> [String]) -> Datum [String] -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [String]
forall a. String -> Datum a
var String
"parts"))))
(Datum ([String] -> String)
forall a. Datum ([a] -> a)
Lists.head Datum ([String] -> String) -> Datum [String] -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [String]
forall a. String -> Datum a
var String
"parts")
Datum (Bool -> QualifiedName) -> Datum Bool -> Datum QualifiedName
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum (Int -> Int -> Bool)
Equality.equalInt32 Datum (Int -> Int -> Bool) -> Datum Int -> Datum (Int -> Bool)
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Int -> Datum Int
int32 Int
1 Datum (Int -> Bool) -> Datum Int -> Datum Bool
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum ([Any] -> Int)
forall a. Datum ([a] -> Int)
Lists.length Datum ([Any] -> Int) -> Datum [Any] -> Datum Int
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum [Any]
forall a. String -> Datum a
var String
"parts")))
Datum QualifiedName -> [Field] -> Datum QualifiedName
forall a. Datum a -> [Field] -> Datum a
`with` [
String
"parts"String -> Datum [String] -> Field
forall a. String -> Datum a -> Field
>: Datum ([String] -> [String])
forall a. Datum ([a] -> [a])
Lists.reverse Datum ([String] -> [String]) -> Datum [String] -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Datum (String -> String -> [String])
Strings.splitOn Datum (String -> String -> [String])
-> Datum String -> Datum (String -> [String])
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ Datum String
"." Datum (String -> [String]) -> Datum String -> Datum [String]
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ (Name -> Datum (Any -> String)
forall a b. Name -> Datum (a -> b)
unwrap Name
_Name Datum (Any -> String) -> Datum Any -> Datum String
forall a b. Datum (a -> b) -> Datum a -> Datum b
@@ String -> Datum Any
forall a. String -> Datum a
var String
"name"))]