module Hydra.Sources.Tier4.Langs.Haskell.Ast where
import Hydra.Sources.Tier3.All
import Hydra.Dsl.Annotations
import Hydra.Dsl.Bootstrap
import Hydra.Dsl.Types as Types
haskellAstModule :: Module
haskellAstModule :: Module
haskellAstModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module Namespace
ns [Element]
elements [Module
hydraCoreModule] [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 Haskell syntax model, loosely based on Language.Haskell.Tools.AST"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/langs/haskell/ast"
def :: String -> Type -> Element
def = Namespace -> String -> Type -> Element
datatype Namespace
ns
ast :: String -> Type
ast = Namespace -> String -> Type
typeref Namespace
ns
elements :: [Element]
elements = [
String -> Type -> Element
def String
"Alternative" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A pattern-matching alternative" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"pattern"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern",
String
"rhs"String -> Type -> FieldType
>: String -> Type
ast String
"CaseRhs",
String
"binds"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"LocalBindings"],
String -> Type -> Element
def String
"Assertion" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A type assertion" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"class"String -> Type -> FieldType
>: String -> Type
ast String
"Assertion.Class",
String
"tuple"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Assertion"],
String -> Type -> Element
def String
"Assertion.Class" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"types"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"CaseRhs" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The right-hand side of a pattern-matching alternative" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
ast String
"Expression",
String -> Type -> Element
def String
"Constructor" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"ordinary"String -> Type -> FieldType
>: String -> Type
ast String
"Constructor.Ordinary",
String
"record"String -> Type -> FieldType
>: String -> Type
ast String
"Constructor.Record"],
String -> Type -> Element
def String
"Constructor.Ordinary" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An ordinary (positional) data constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"fields"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"Constructor.Record" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A record-style data constructor" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"fields"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"FieldWithComments"],
String -> Type -> Element
def String
"ConstructorWithComments" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data constructor together with any comments" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"body"String -> Type -> FieldType
>: String -> Type
ast String
"Constructor",
String
"comments"String -> Type -> FieldType
>: Type -> Type
optional Type
string],
String -> Type -> Element
def String
"DataDeclaration" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data type declaration" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"keyword"String -> Type -> FieldType
>: String -> Type
ast String
"DataDeclaration.Keyword",
String
"context"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Assertion",
String
"head"String -> Type -> FieldType
>: String -> Type
ast String
"DeclarationHead",
String
"constructors"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"ConstructorWithComments",
String
"deriving"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Deriving"],
String -> Type -> Element
def String
"DataDeclaration.Keyword" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The 'data' versus 'newtype keyword" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [String
"data", String
"newtype"],
String -> Type -> Element
def String
"DeclarationWithComments" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data declaration together with any comments" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"body"String -> Type -> FieldType
>: String -> Type
ast String
"Declaration",
String
"comments"String -> Type -> FieldType
>: Type -> Type
optional Type
string],
String -> Type -> Element
def String
"Declaration" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data or value declaration" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"data"String -> Type -> FieldType
>: String -> Type
ast String
"DataDeclaration",
String
"type"String -> Type -> FieldType
>: String -> Type
ast String
"TypeDeclaration",
String
"valueBinding"String -> Type -> FieldType
>: String -> Type
ast String
"ValueBinding",
String
"typedBinding"String -> Type -> FieldType
>: String -> Type
ast String
"TypedBinding"],
String -> Type -> Element
def String
"DeclarationHead" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"The left-hand side of a declaration" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"application"String -> Type -> FieldType
>: String -> Type
ast String
"DeclarationHead.Application",
String
"parens"String -> Type -> FieldType
>: String -> Type
ast String
"DeclarationHead",
String
"simple"String -> Type -> FieldType
>: String -> Type
ast String
"Name"],
String -> Type -> Element
def String
"DeclarationHead.Application" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An application-style declaration head" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"function"String -> Type -> FieldType
>: String -> Type
ast String
"DeclarationHead",
String
"operand"String -> Type -> FieldType
>: String -> Type
ast String
"Variable"],
String -> Type -> Element
def String
"Deriving" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A 'deriving' statement" (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
ast String
"Name",
String -> Type -> Element
def String
"Export" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An export statement" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"declaration"String -> Type -> FieldType
>: String -> Type
ast String
"ImportExportSpec",
String
"module"String -> Type -> FieldType
>: String -> Type
ast String
"ModuleName"],
String -> Type -> Element
def String
"Expression" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A data expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"application"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.Application",
String
"case"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.Case",
String
"constructRecord"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.ConstructRecord",
String
"do"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Statement",
String
"if"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.If",
String
"infixApplication"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.InfixApplication",
String
"literal"String -> Type -> FieldType
>: String -> Type
ast String
"Literal",
String
"lambda"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.Lambda",
String
"leftSection"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.Section",
String
"let"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.Let",
String
"list"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Expression",
String
"parens"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"prefixApplication"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.PrefixApplication",
String
"rightSection"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.Section",
String
"tuple"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Expression",
String
"typeSignature"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.TypeSignature",
String
"updateRecord"String -> Type -> FieldType
>: String -> Type
ast String
"Expression.UpdateRecord",
String
"variable"String -> Type -> FieldType
>: String -> Type
ast String
"Name"],
String -> Type -> Element
def String
"Expression.Application" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An application expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"function"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"argument"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Expression.Case" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A case expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"case"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"alternatives"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Alternative"],
String -> Type -> Element
def String
"Expression.ConstructRecord" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A record constructor expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"fields"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"FieldUpdate"],
String -> Type -> Element
def String
"Expression.If" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An 'if' expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"condition"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"then"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"else"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Expression.InfixApplication" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An infix application expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"lhs"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"operator"String -> Type -> FieldType
>: String -> Type
ast String
"Operator",
String
"rhs"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Expression.Lambda" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A lambda expression" (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
ast String
"Pattern",
String
"inner"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Expression.Let" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A 'let' expression" (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
ast String
"LocalBinding",
String
"inner"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Expression.PrefixApplication" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A prefix expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"operator"String -> Type -> FieldType
>: String -> Type
ast String
"Operator",
String
"rhs"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Expression.Section" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A section expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"operator"String -> Type -> FieldType
>: String -> Type
ast String
"Operator",
String
"expression"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Expression.TypeSignature" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A type signature expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"inner"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"type"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"Expression.UpdateRecord" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An update record expression" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"inner"String -> Type -> FieldType
>: String -> Type
ast String
"Expression",
String
"fields"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"FieldUpdate"],
String -> Type -> Element
def String
"Field" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A field (name/type pair)" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"type"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"FieldWithComments" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A field together with any comments" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"field"String -> Type -> FieldType
>: String -> Type
ast String
"Field",
String
"comments"String -> Type -> FieldType
>: Type -> Type
optional Type
string],
String -> Type -> Element
def String
"FieldUpdate" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A field name and value" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"value"String -> Type -> FieldType
>: String -> Type
ast String
"Expression"],
String -> Type -> Element
def String
"Import" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An import statement" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"qualified"String -> Type -> FieldType
>: Type
boolean,
String
"module"String -> Type -> FieldType
>: String -> Type
ast String
"ModuleName",
String
"as"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"ModuleName",
String
"spec"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Import.Spec"],
String -> Type -> Element
def String
"Import.Spec" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An import specification" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"list"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"ImportExportSpec",
String
"hiding"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"ImportExportSpec"],
String -> Type -> Element
def String
"ImportModifier" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An import modifier ('pattern' or 'type')" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [String
"pattern", String
"type"],
String -> Type -> Element
def String
"ImportExportSpec" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An import or export specification" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"modifier"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"ImportModifier",
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"subspec"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"ImportExportSpec.Subspec"],
String -> Type -> Element
def String
"ImportExportSpec.Subspec" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"all"String -> Type -> FieldType
>: Type
unit,
String
"list"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Name"],
String -> Type -> Element
def String
"Literal" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A literal value" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"char"String -> Type -> FieldType
>: Type
uint16,
String
"double"String -> Type -> FieldType
>: Type
float64,
String
"float"String -> Type -> FieldType
>: Type
float32,
String
"int"String -> Type -> FieldType
>: Type
int32,
String
"integer"String -> Type -> FieldType
>: Type
bigint,
String
"string"String -> Type -> FieldType
>: Type
string],
String -> Type -> Element
def String
"LocalBinding" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"signature"String -> Type -> FieldType
>: String -> Type
ast String
"TypeSignature",
String
"value"String -> Type -> FieldType
>: String -> Type
ast String
"ValueBinding"],
String -> Type -> Element
def String
"LocalBindings" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"LocalBinding",
String -> Type -> Element
def String
"Module" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"head"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"ModuleHead",
String
"imports"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Import",
String
"declarations"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"DeclarationWithComments"],
String -> Type -> Element
def String
"ModuleHead" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"comments"String -> Type -> FieldType
>: Type -> Type
optional Type
string,
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"ModuleName",
String
"exports"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Export"],
String -> Type -> Element
def String
"ModuleName"
Type
string,
String -> Type -> Element
def String
"Name" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"implicit"String -> Type -> FieldType
>: String -> Type
ast String
"QualifiedName",
String
"normal"String -> Type -> FieldType
>: String -> Type
ast String
"QualifiedName",
String
"parens"String -> Type -> FieldType
>: String -> Type
ast String
"QualifiedName"],
String -> Type -> Element
def String
"NamePart"
Type
string,
String -> Type -> Element
def String
"Operator" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"backtick"String -> Type -> FieldType
>: String -> Type
ast String
"QualifiedName",
String
"normal"String -> Type -> FieldType
>: String -> Type
ast String
"QualifiedName"],
String -> Type -> Element
def String
"Pattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"application"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern.Application",
String
"as"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern.As",
String
"list"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Pattern",
String
"literal"String -> Type -> FieldType
>: String -> Type
ast String
"Literal",
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"parens"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern",
String
"record"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern.Record",
String
"tuple"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Pattern",
String
"typed"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern.Typed",
String
"wildcard"String -> Type -> FieldType
>: Type
unit],
String -> Type -> Element
def String
"Pattern.Application" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"args"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Pattern"],
String -> Type -> Element
def String
"Pattern.As" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"inner"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern"],
String -> Type -> Element
def String
"Pattern.Record" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"fields"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"PatternField"],
String -> Type -> Element
def String
"Pattern.Typed" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"inner"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern",
String
"type"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"PatternField" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"pattern"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern"],
String -> Type -> Element
def String
"QualifiedName" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"qualifiers"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"NamePart",
String
"unqualified"String -> Type -> FieldType
>: String -> Type
ast String
"NamePart"],
String -> Type -> Element
def String
"RightHandSide" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type
ast String
"Expression",
String -> Type -> Element
def String
"Statement" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type
ast String
"Expression",
String -> Type -> Element
def String
"Type" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"application"String -> Type -> FieldType
>: String -> Type
ast String
"Type.Application",
String
"ctx"String -> Type -> FieldType
>: String -> Type
ast String
"Type.Context",
String
"function"String -> Type -> FieldType
>: String -> Type
ast String
"Type.Function",
String
"infix"String -> Type -> FieldType
>: String -> Type
ast String
"Type.Infix",
String
"list"String -> Type -> FieldType
>: String -> Type
ast String
"Type",
String
"parens"String -> Type -> FieldType
>: String -> Type
ast String
"Type",
String
"tuple"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"Type",
String
"variable"String -> Type -> FieldType
>: String -> Type
ast String
"Name"],
String -> Type -> Element
def String
"Type.Application" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"context"String -> Type -> FieldType
>: String -> Type
ast String
"Type",
String
"argument"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"Type.Context" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"ctx"String -> Type -> FieldType
>: String -> Type
ast String
"Assertion",
String
"type"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"Type.Function" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"domain"String -> Type -> FieldType
>: String -> Type
ast String
"Type",
String
"codomain"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"Type.Infix" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"lhs"String -> Type -> FieldType
>: String -> Type
ast String
"Type",
String
"operator"String -> Type -> FieldType
>: String -> Type
ast String
"Operator",
String
"rhs"String -> Type -> FieldType
>: String -> Type
ast String
"Operator"],
String -> Type -> Element
def String
"TypeDeclaration" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"DeclarationHead",
String
"type"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"TypeSignature" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"name"String -> Type -> FieldType
>: String -> Type
ast String
"Name",
String
"type"String -> Type -> FieldType
>: String -> Type
ast String
"Type"],
String -> Type -> Element
def String
"TypedBinding" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"typeSignature"String -> Type -> FieldType
>: String -> Type
ast String
"TypeSignature",
String
"valueBinding"String -> Type -> FieldType
>: String -> Type
ast String
"ValueBinding"],
String -> Type -> Element
def String
"ValueBinding" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"simple"String -> Type -> FieldType
>: String -> Type
ast String
"ValueBinding.Simple"],
String -> Type -> Element
def String
"ValueBinding.Simple" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"pattern"String -> Type -> FieldType
>: String -> Type
ast String
"Pattern",
String
"rhs"String -> Type -> FieldType
>: String -> Type
ast String
"RightHandSide",
String
"localBindings"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
ast String
"LocalBindings"],
String -> Type -> Element
def String
"Variable" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type
ast String
"Name"]