{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Core(
hydraCore,
hydraCoreModule,
module Hydra.Kernel,
) where
import Hydra.Kernel
import Hydra.Dsl.Bootstrap
import Hydra.Dsl.Types as Types
hydraCore :: Graph
hydraCore :: Graph
hydraCore = Graph -> Maybe Graph -> [Element] -> Graph
elementsToGraph Graph
bootstrapGraph Maybe Graph
forall a. Maybe a
Nothing (Module -> [Element]
moduleElements Module
hydraCoreModule)
hydraCoreModule :: Module
hydraCoreModule :: Module
hydraCoreModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module Namespace
ns [Element]
elements [] [] (Maybe String -> Module) -> Maybe String -> Module
forall a b. (a -> b) -> a -> b
$
String -> Maybe String
forall a. a -> Maybe a
Just String
"Hydra's core data model, defining types, terms, and their dependencies"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/core"
core :: String -> Type
core = Namespace -> String -> Type
typeref Namespace
ns
def :: String -> Type -> Element
def = Namespace -> String -> Type -> Element
datatype Namespace
ns
doc :: String -> Type -> Type
doc String
s = Maybe String -> Type -> Type
setTypeDescription (String -> Maybe String
forall a. a -> Maybe a
Just String
s)
elements :: [Element]
elements = [
String -> Type -> Element
def String
"AnnotatedTerm" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A term together with an annotation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"subject"String -> Type -> FieldType
>: String -> Type
core String
"Term",
String
"annotation"String -> Type -> FieldType
>: Type -> Type -> Type
Types.map (String -> Type
core String
"Name") (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Term"],
String -> Type -> Element
def String
"AnnotatedType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A type together with an annotation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"subject"String -> Type -> FieldType
>: String -> Type
core String
"Type",
String
"annotation"String -> Type -> FieldType
>: Type -> Type -> Type
Types.map (String -> Type
core String
"Name") (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Term"],
String -> Type -> Element
def String
"Application" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A term which applies a function to an argument" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"function"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The left-hand side of the application" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term",
String
"argument"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The right-hand side of the application" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term"],
String -> Type -> Element
def String
"ApplicationType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The type-level analog of an application term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"function"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The left-hand side of the application" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Type",
String
"argument"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The right-hand side of the application" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Type"],
String -> Type -> Element
def String
"CaseStatement" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A union elimination; a case statement" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeName"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"default"String -> Type -> FieldType
>: Type -> Type
optional (String -> Type
core String
"Term"),
String
"cases"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Field"],
String -> Type -> Element
def String
"Elimination" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A corresponding elimination for an introduction term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"list"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"Eliminates a list using a fold function; this function has the signature b -> [a] -> b" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term",
String
"optional"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"Eliminates an optional term by matching over the two possible cases" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"OptionalCases",
String
"product"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"Eliminates a tuple by projecting the component at a given 0-indexed offset" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"TupleProjection",
String
"record"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"Eliminates a record by projecting a given field" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Projection",
String
"union"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"Eliminates a union term by matching over the fields of the union. This is a case statement." (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"CaseStatement",
String
"wrap"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"Unwrap a wrapped term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name"],
String -> Type -> Element
def String
"Field" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A name/term pair" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"term"String -> Type -> FieldType
>: String -> Type
core String
"Term"],
String -> Type -> Element
def String
"FieldType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A name/type pair" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"type"String -> Type -> FieldType
>: String -> Type
core String
"Type"],
String -> Type -> Element
def String
"FloatType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A floating-point type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [
String
"bigfloat",
String
"float32",
String
"float64"],
String -> Type -> Element
def String
"FloatValue" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A floating-point literal value" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"bigfloat"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An arbitrary-precision floating-point value" Type
bigfloat,
String
"float32"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 32-bit floating-point value" Type
float32,
String
"float64"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 64-bit floating-point value" Type
float64],
String -> Type -> Element
def String
"Function" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A function" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"elimination"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An elimination for any of a few term variants" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Elimination",
String
"lambda"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A function abstraction (lambda)" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Lambda",
String
"primitive"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A reference to a built-in (primitive) function" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name"],
String -> Type -> Element
def String
"FunctionType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A function type, also known as an arrow type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"domain"String -> Type -> FieldType
>: String -> Type
core String
"Type",
String
"codomain"String -> Type -> FieldType
>: String -> Type
core String
"Type"],
String -> Type -> Element
def String
"Injection" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An instance of a union type; i.e. a string-indexed generalization of inl() or inr()" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeName"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"field"String -> Type -> FieldType
>: String -> Type
core String
"Field"],
String -> Type -> Element
def String
"IntegerType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An integer type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [
String
"bigint",
String
"int8",
String
"int16",
String
"int32",
String
"int64",
String
"uint8",
String
"uint16",
String
"uint32",
String
"uint64"],
String -> Type -> Element
def String
"IntegerValue" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An integer literal value" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"bigint"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An arbitrary-precision integer value" Type
bigint,
String
"int8"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An 8-bit signed integer value" Type
int8,
String
"int16"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 16-bit signed integer value (short value)" Type
int16,
String
"int32"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 32-bit signed integer value (int value)" Type
int32,
String
"int64"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 64-bit signed integer value (long value)" Type
int64,
String
"uint8"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An 8-bit unsigned integer value (byte)" Type
uint8,
String
"uint16"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 16-bit unsigned integer value" Type
uint16,
String
"uint32"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 32-bit unsigned integer value (unsigned int)" Type
uint32,
String
"uint64"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A 64-bit unsigned integer value (unsigned long)" Type
uint64],
String -> Type -> Element
def String
"Lambda" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A function abstraction (lambda)" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"parameter"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The parameter of the lambda" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"domain"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An optional domain type for the lambda" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Type",
String
"body"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The body of the lambda" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term"],
String -> Type -> Element
def String
"LambdaType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A type abstraction; the type-level analog of a lambda term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"parameter"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The variable which is bound by the lambda" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"body"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The body of the lambda" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Type"],
String -> Type -> Element
def String
"Let" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A set of (possibly recursive) 'let' bindings together with an environment in which they are bound" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"bindings"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"LetBinding",
String
"environment"String -> Type -> FieldType
>: String -> Type
core String
"Term"],
String -> Type -> Element
def String
"LetBinding" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A field with an optional type scheme, used to bind variables to terms in a 'let' expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"term"String -> Type -> FieldType
>: String -> Type
core String
"Term",
String
"type"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"TypeScheme"],
String -> Type -> Element
def String
"Literal" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A term constant; an instance of a literal type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"binary"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A binary literal" Type
binary,
String
"boolean"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A boolean literal" Type
boolean,
String
"float"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A floating-point literal" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"FloatValue",
String
"integer"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An integer literal" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"IntegerValue",
String
"string"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A string literal" Type
string],
String -> Type -> Element
def String
"LiteralType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"Any of a fixed set of literal types, also called atomic types, base types, primitive types, or type constants" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"binary"String -> Type -> FieldType
>: Type
unit,
String
"boolean"String -> Type -> FieldType
>: Type
unit,
String
"float"String -> Type -> FieldType
>: String -> Type
core String
"FloatType",
String
"integer"String -> Type -> FieldType
>: String -> Type
core String
"IntegerType",
String
"string"String -> Type -> FieldType
>: Type
unit],
String -> Type -> Element
def String
"MapType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A map type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"keys"String -> Type -> FieldType
>: String -> Type
core String
"Type",
String
"values"String -> Type -> FieldType
>: String -> Type
core String
"Type"],
String -> Type -> Element
def String
"Name" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A unique identifier in some context; a string-valued key"
(Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
wrap Type
string,
String -> Type -> Element
def String
"WrappedTerm" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A term wrapped in a type name" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeName"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"object"String -> Type -> FieldType
>: String -> Type
core String
"Term"],
String -> Type -> Element
def String
"WrappedType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A type wrapped in a type name" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeName"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"object"String -> Type -> FieldType
>: String -> Type
core String
"Type"],
String -> Type -> Element
def String
"OptionalCases" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A case statement for matching optional terms" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"nothing"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A term provided if the optional value is nothing" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term",
String
"just"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A function which is applied if the optional value is non-nothing" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term"],
String -> Type -> Element
def String
"Projection" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A record elimination; a projection" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeName"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The name of the record type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"field"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The name of the projected field" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name"],
String -> Type -> Element
def String
"Record" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A record, or labeled tuple; a map of field names to terms" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeName"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"fields"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Field"],
String -> Type -> Element
def String
"RowType" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A labeled record or union type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeName"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The name of the row type, which must correspond to the name of a Type element" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"fields"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The fields of this row type, excluding any inherited fields" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"FieldType"],
String -> Type -> Element
def String
"Sum" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The unlabeled equivalent of an Injection term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"index"String -> Type -> FieldType
>: Type
int32,
String
"size"String -> Type -> FieldType
>: Type
int32,
String
"term"String -> Type -> FieldType
>: String -> Type
core String
"Term"],
String -> Type -> Element
def String
"Term" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"annotated"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A term annotated with metadata" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"AnnotatedTerm",
String
"application"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A function application" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Application",
String
"function"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A function term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Function",
String
"let"String -> Type -> FieldType
>:
String -> Type
core String
"Let",
String
"list"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A list" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Term",
String
"literal"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A literal value" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Literal",
String
"map"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A map of keys to values" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type -> Type
Types.map (String -> Type
core String
"Term") (String -> Type
core String
"Term"),
String
"optional"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An optional value" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Term",
String
"product"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A tuple" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (String -> Type
core String
"Term"),
String
"record"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A record term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Record",
String
"set"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A set of values" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
set (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Term",
String
"sum"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A variant tuple" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Sum",
String
"typeAbstraction"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A System F type abstraction term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"TypeAbstraction",
String
"typeApplication"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A System F type application term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"TypedTerm",
String
"typed"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A term annotated with its type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"TypedTerm",
String
"union"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An injection; an instance of a union type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Injection",
String
"variable"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A variable reference" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"wrap"String -> Type -> FieldType
>:
String -> Type
core String
"WrappedTerm"],
String -> Type -> Element
def String
"TupleProjection" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A tuple elimination; a projection from an integer-indexed product" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"arity"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The arity of the tuple"
Type
int32,
String
"index"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The 0-indexed offset from the beginning of the tuple"
Type
int32],
String -> Type -> Element
def String
"Type" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"annotated"String -> Type -> FieldType
>: String -> Type
core String
"AnnotatedType",
String
"application"String -> Type -> FieldType
>: String -> Type
core String
"ApplicationType",
String
"function"String -> Type -> FieldType
>: String -> Type
core String
"FunctionType",
String
"lambda"String -> Type -> FieldType
>: String -> Type
core String
"LambdaType",
String
"list"String -> Type -> FieldType
>: String -> Type
core String
"Type",
String
"literal"String -> Type -> FieldType
>: String -> Type
core String
"LiteralType",
String
"map"String -> Type -> FieldType
>: String -> Type
core String
"MapType",
String
"optional"String -> Type -> FieldType
>: String -> Type
core String
"Type",
String
"product"String -> Type -> FieldType
>: Type -> Type
list (String -> Type
core String
"Type"),
String
"record"String -> Type -> FieldType
>: String -> Type
core String
"RowType",
String
"set"String -> Type -> FieldType
>: String -> Type
core String
"Type",
String
"sum"String -> Type -> FieldType
>: Type -> Type
list (String -> Type
core String
"Type"),
String
"union"String -> Type -> FieldType
>: String -> Type
core String
"RowType",
String
"variable"String -> Type -> FieldType
>: String -> Type
core String
"Name",
String
"wrap"String -> Type -> FieldType
>: String -> Type
core String
"WrappedType"],
String -> Type -> Element
def String
"TypeAbstraction" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A System F type abstraction term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"parameter"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The type variable introduced by the abstraction" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"body"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The body of the abstraction" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term"],
String -> Type -> Element
def String
"TypeScheme" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A type expression together with free type variables occurring in the expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"variables"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Name",
String
"type"String -> Type -> FieldType
>: String -> Type
core String
"Type"],
String -> Type -> Element
def String
"TypedTerm" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A term together with its type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"term"String -> Type -> FieldType
>: String -> Type
core String
"Term",
String
"type"String -> Type -> FieldType
>: String -> Type
core String
"Type"],
String -> Type -> Element
def String
"Unit" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An empty record as a canonical unit value" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record []]