Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hydra's core data model, defining types, terms, and their dependencies
Synopsis
- data Annotated a m = Annotated {
- annotatedSubject :: a
- annotatedAnnotation :: m
- _Annotated :: Name
- _Annotated_subject :: FieldName
- _Annotated_annotation :: FieldName
- data Application m = Application {
- applicationFunction :: Term m
- applicationArgument :: Term m
- _Application :: Name
- _Application_function :: FieldName
- _Application_argument :: FieldName
- data ApplicationType m = ApplicationType {}
- _ApplicationType :: Name
- _ApplicationType_function :: FieldName
- _ApplicationType_argument :: FieldName
- data CaseStatement m = CaseStatement {
- caseStatementTypeName :: Name
- caseStatementCases :: [Field m]
- _CaseStatement :: Name
- _CaseStatement_typeName :: FieldName
- _CaseStatement_cases :: FieldName
- data Elimination m
- _Elimination :: Name
- _Elimination_element :: FieldName
- _Elimination_list :: FieldName
- _Elimination_nominal :: FieldName
- _Elimination_optional :: FieldName
- _Elimination_record :: FieldName
- _Elimination_union :: FieldName
- data Field m = Field {}
- _Field :: Name
- _Field_name :: FieldName
- _Field_term :: FieldName
- newtype FieldName = FieldName {}
- _FieldName :: Name
- data FieldType m = FieldType {
- fieldTypeName :: FieldName
- fieldTypeType :: Type m
- _FieldType :: Name
- _FieldType_name :: FieldName
- _FieldType_type :: FieldName
- data FloatType
- _FloatType :: Name
- _FloatType_bigfloat :: FieldName
- _FloatType_float32 :: FieldName
- _FloatType_float64 :: FieldName
- data FloatValue
- _FloatValue :: Name
- _FloatValue_bigfloat :: FieldName
- _FloatValue_float32 :: FieldName
- _FloatValue_float64 :: FieldName
- data Function m
- = FunctionCompareTo (Term m)
- | FunctionElimination (Elimination m)
- | FunctionLambda (Lambda m)
- | FunctionPrimitive Name
- _Function :: Name
- _Function_compareTo :: FieldName
- _Function_elimination :: FieldName
- _Function_lambda :: FieldName
- _Function_primitive :: FieldName
- data FunctionType m = FunctionType {
- functionTypeDomain :: Type m
- functionTypeCodomain :: Type m
- _FunctionType :: Name
- _FunctionType_domain :: FieldName
- _FunctionType_codomain :: FieldName
- data IntegerType
- _IntegerType :: Name
- _IntegerType_bigint :: FieldName
- _IntegerType_int8 :: FieldName
- _IntegerType_int16 :: FieldName
- _IntegerType_int32 :: FieldName
- _IntegerType_int64 :: FieldName
- _IntegerType_uint8 :: FieldName
- _IntegerType_uint16 :: FieldName
- _IntegerType_uint32 :: FieldName
- _IntegerType_uint64 :: FieldName
- data IntegerValue
- _IntegerValue :: Name
- _IntegerValue_bigint :: FieldName
- _IntegerValue_int8 :: FieldName
- _IntegerValue_int16 :: FieldName
- _IntegerValue_int32 :: FieldName
- _IntegerValue_int64 :: FieldName
- _IntegerValue_uint8 :: FieldName
- _IntegerValue_uint16 :: FieldName
- _IntegerValue_uint32 :: FieldName
- _IntegerValue_uint64 :: FieldName
- data Lambda m = Lambda {
- lambdaParameter :: Variable
- lambdaBody :: Term m
- _Lambda :: Name
- _Lambda_parameter :: FieldName
- _Lambda_body :: FieldName
- data LambdaType m = LambdaType {}
- _LambdaType :: Name
- _LambdaType_parameter :: FieldName
- _LambdaType_body :: FieldName
- data Let m = Let {}
- _Let :: Name
- _Let_key :: FieldName
- _Let_value :: FieldName
- _Let_environment :: FieldName
- data Literal
- _Literal :: Name
- _Literal_binary :: FieldName
- _Literal_boolean :: FieldName
- _Literal_float :: FieldName
- _Literal_integer :: FieldName
- _Literal_string :: FieldName
- data LiteralType
- _LiteralType :: Name
- _LiteralType_binary :: FieldName
- _LiteralType_boolean :: FieldName
- _LiteralType_float :: FieldName
- _LiteralType_integer :: FieldName
- _LiteralType_string :: FieldName
- data MapType m = MapType {
- mapTypeKeys :: Type m
- mapTypeValues :: Type m
- _MapType :: Name
- _MapType_keys :: FieldName
- _MapType_values :: FieldName
- newtype Name = Name {}
- _Name :: Name
- data Named m = Named {
- namedTypeName :: Name
- namedTerm :: Term m
- _Named :: Name
- _Named_typeName :: FieldName
- _Named_term :: FieldName
- data OptionalCases m = OptionalCases {
- optionalCasesNothing :: Term m
- optionalCasesJust :: Term m
- _OptionalCases :: Name
- _OptionalCases_nothing :: FieldName
- _OptionalCases_just :: FieldName
- data Projection = Projection {}
- _Projection :: Name
- _Projection_typeName :: FieldName
- _Projection_field :: FieldName
- data Record m = Record {
- recordTypeName :: Name
- recordFields :: [Field m]
- _Record :: Name
- _Record_typeName :: FieldName
- _Record_fields :: FieldName
- data RowType m = RowType {
- rowTypeTypeName :: Name
- rowTypeExtends :: Maybe Name
- rowTypeFields :: [FieldType m]
- _RowType :: Name
- _RowType_typeName :: FieldName
- _RowType_extends :: FieldName
- _RowType_fields :: FieldName
- data Stream m = Stream {
- streamFirst :: Term m
- streamRest :: Stream m
- _Stream :: Name
- _Stream_first :: FieldName
- _Stream_rest :: FieldName
- data Sum m = Sum {}
- _Sum :: Name
- _Sum_index :: FieldName
- _Sum_size :: FieldName
- _Sum_term :: FieldName
- data Term m
- = TermAnnotated (Annotated (Term m) m)
- | TermApplication (Application m)
- | TermElement Name
- | TermFunction (Function m)
- | TermLet (Let m)
- | TermList [Term m]
- | TermLiteral Literal
- | TermMap (Map (Term m) (Term m))
- | TermNominal (Named m)
- | TermOptional (Maybe (Term m))
- | TermProduct [Term m]
- | TermRecord (Record m)
- | TermSet (Set (Term m))
- | TermStream (Stream m)
- | TermSum (Sum m)
- | TermUnion (Union m)
- | TermVariable Variable
- _Term :: Name
- _Term_annotated :: FieldName
- _Term_application :: FieldName
- _Term_element :: FieldName
- _Term_function :: FieldName
- _Term_let :: FieldName
- _Term_list :: FieldName
- _Term_literal :: FieldName
- _Term_map :: FieldName
- _Term_nominal :: FieldName
- _Term_optional :: FieldName
- _Term_product :: FieldName
- _Term_record :: FieldName
- _Term_set :: FieldName
- _Term_stream :: FieldName
- _Term_sum :: FieldName
- _Term_union :: FieldName
- _Term_variable :: FieldName
- data Type m
- = TypeAnnotated (Annotated (Type m) m)
- | TypeApplication (ApplicationType m)
- | TypeElement (Type m)
- | TypeFunction (FunctionType m)
- | TypeLambda (LambdaType m)
- | TypeList (Type m)
- | TypeLiteral LiteralType
- | TypeMap (MapType m)
- | TypeNominal Name
- | TypeOptional (Type m)
- | TypeProduct [Type m]
- | TypeRecord (RowType m)
- | TypeSet (Type m)
- | TypeStream (Type m)
- | TypeSum [Type m]
- | TypeUnion (RowType m)
- | TypeVariable VariableType
- _Type :: Name
- _Type_annotated :: FieldName
- _Type_application :: FieldName
- _Type_element :: FieldName
- _Type_function :: FieldName
- _Type_lambda :: FieldName
- _Type_list :: FieldName
- _Type_literal :: FieldName
- _Type_map :: FieldName
- _Type_nominal :: FieldName
- _Type_optional :: FieldName
- _Type_product :: FieldName
- _Type_record :: FieldName
- _Type_set :: FieldName
- _Type_stream :: FieldName
- _Type_sum :: FieldName
- _Type_union :: FieldName
- _Type_variable :: FieldName
- newtype Variable = Variable {
- unVariable :: String
- _Variable :: Name
- newtype VariableType = VariableType {}
- _VariableType :: Name
- data Union m = Union {
- unionTypeName :: Name
- unionField :: Field m
- _Union :: Name
- _Union_typeName :: FieldName
- _Union_field :: FieldName
- data UnitType = UnitType {
- _UnitType :: Name
Documentation
Annotated | |
|
Instances
(Read a, Read m) => Read (Annotated a m) Source # | |
(Show a, Show m) => Show (Annotated a m) Source # | |
(Eq a, Eq m) => Eq (Annotated a m) Source # | |
(Ord a, Ord m) => Ord (Annotated a m) Source # | |
Defined in Hydra.Core compare :: Annotated a m -> Annotated a m -> Ordering # (<) :: Annotated a m -> Annotated a m -> Bool # (<=) :: Annotated a m -> Annotated a m -> Bool # (>) :: Annotated a m -> Annotated a m -> Bool # (>=) :: Annotated a m -> Annotated a m -> Bool # |
_Annotated :: Name Source #
data Application m Source #
A term which applies a function to an argument
Application | |
|
Instances
(Read m, Ord m) => Read (Application m) Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS (Application m) # readList :: ReadS [Application m] # readPrec :: ReadPrec (Application m) # readListPrec :: ReadPrec [Application m] # | |
Show m => Show (Application m) Source # | |
Defined in Hydra.Core showsPrec :: Int -> Application m -> ShowS # show :: Application m -> String # showList :: [Application m] -> ShowS # | |
Eq m => Eq (Application m) Source # | |
Defined in Hydra.Core (==) :: Application m -> Application m -> Bool # (/=) :: Application m -> Application m -> Bool # | |
Ord m => Ord (Application m) Source # | |
Defined in Hydra.Core compare :: Application m -> Application m -> Ordering # (<) :: Application m -> Application m -> Bool # (<=) :: Application m -> Application m -> Bool # (>) :: Application m -> Application m -> Bool # (>=) :: Application m -> Application m -> Bool # max :: Application m -> Application m -> Application m # min :: Application m -> Application m -> Application m # |
_Application :: Name Source #
data ApplicationType m Source #
The type-level analog of an application term
ApplicationType | |
|
Instances
data CaseStatement m Source #
Instances
data Elimination m Source #
A corresponding elimination for an introduction term
EliminationElement | Eliminates an element by mapping it to its data term. This is Hydra's delta function. |
EliminationList (Term m) | Eliminates a list using a fold function; this function has the signature b -> [a] -> b |
EliminationNominal Name | Eliminates a nominal term by extracting the wrapped term |
EliminationOptional (OptionalCases m) | Eliminates an optional term by matching over the two possible cases |
EliminationRecord Projection | Eliminates a record by projecting a given field |
EliminationUnion (CaseStatement m) | Eliminates a union term by matching over the fields of the union. This is a case statement. |
Instances
(Read m, Ord m) => Read (Elimination m) Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS (Elimination m) # readList :: ReadS [Elimination m] # readPrec :: ReadPrec (Elimination m) # readListPrec :: ReadPrec [Elimination m] # | |
Show m => Show (Elimination m) Source # | |
Defined in Hydra.Core showsPrec :: Int -> Elimination m -> ShowS # show :: Elimination m -> String # showList :: [Elimination m] -> ShowS # | |
Eq m => Eq (Elimination m) Source # | |
Defined in Hydra.Core (==) :: Elimination m -> Elimination m -> Bool # (/=) :: Elimination m -> Elimination m -> Bool # | |
Ord m => Ord (Elimination m) Source # | |
Defined in Hydra.Core compare :: Elimination m -> Elimination m -> Ordering # (<) :: Elimination m -> Elimination m -> Bool # (<=) :: Elimination m -> Elimination m -> Bool # (>) :: Elimination m -> Elimination m -> Bool # (>=) :: Elimination m -> Elimination m -> Bool # max :: Elimination m -> Elimination m -> Elimination m # min :: Elimination m -> Elimination m -> Elimination m # |
_Elimination :: Name Source #
A labeled term
The name of a field
FieldName | |
|
_FieldName :: Name Source #
The name and type of a field
FieldType | |
|
Instances
Read m => Read (FieldType m) Source # | |
Show m => Show (FieldType m) Source # | |
Eq m => Eq (FieldType m) Source # | |
Ord m => Ord (FieldType m) Source # | |
_FieldType :: Name Source #
A floating-point type
_FloatType :: Name Source #
data FloatValue Source #
A floating-point literal value
FloatValueBigfloat Double | An arbitrary-precision floating-point value |
FloatValueFloat32 Float | A 32-bit floating-point value |
FloatValueFloat64 Double | A 64-bit floating-point value |
Instances
Read FloatValue Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS FloatValue # readList :: ReadS [FloatValue] # readPrec :: ReadPrec FloatValue # readListPrec :: ReadPrec [FloatValue] # | |
Show FloatValue Source # | |
Defined in Hydra.Core showsPrec :: Int -> FloatValue -> ShowS # show :: FloatValue -> String # showList :: [FloatValue] -> ShowS # | |
Eq FloatValue Source # | |
Defined in Hydra.Core (==) :: FloatValue -> FloatValue -> Bool # (/=) :: FloatValue -> FloatValue -> Bool # | |
Ord FloatValue Source # | |
Defined in Hydra.Core compare :: FloatValue -> FloatValue -> Ordering # (<) :: FloatValue -> FloatValue -> Bool # (<=) :: FloatValue -> FloatValue -> Bool # (>) :: FloatValue -> FloatValue -> Bool # (>=) :: FloatValue -> FloatValue -> Bool # max :: FloatValue -> FloatValue -> FloatValue # min :: FloatValue -> FloatValue -> FloatValue # |
_FloatValue :: Name Source #
A function
FunctionCompareTo (Term m) | Compares a term with a given term of the same type, producing a Comparison |
FunctionElimination (Elimination m) | An elimination for any of a few term variants |
FunctionLambda (Lambda m) | A function abstraction (lambda) |
FunctionPrimitive Name | A reference to a built-in (primitive) function |
Instances
(Read m, Ord m) => Read (Function m) Source # | |
Show m => Show (Function m) Source # | |
Eq m => Eq (Function m) Source # | |
Ord m => Ord (Function m) Source # | |
data FunctionType m Source #
A function type, also known as an arrow type
Instances
_FunctionType :: Name Source #
data IntegerType Source #
An integer type
IntegerTypeBigint | |
IntegerTypeInt8 | |
IntegerTypeInt16 | |
IntegerTypeInt32 | |
IntegerTypeInt64 | |
IntegerTypeUint8 | |
IntegerTypeUint16 | |
IntegerTypeUint32 | |
IntegerTypeUint64 |
Instances
Read IntegerType Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS IntegerType # readList :: ReadS [IntegerType] # readPrec :: ReadPrec IntegerType # readListPrec :: ReadPrec [IntegerType] # | |
Show IntegerType Source # | |
Defined in Hydra.Core showsPrec :: Int -> IntegerType -> ShowS # show :: IntegerType -> String # showList :: [IntegerType] -> ShowS # | |
Eq IntegerType Source # | |
Defined in Hydra.Core (==) :: IntegerType -> IntegerType -> Bool # (/=) :: IntegerType -> IntegerType -> Bool # | |
Ord IntegerType Source # | |
Defined in Hydra.Core compare :: IntegerType -> IntegerType -> Ordering # (<) :: IntegerType -> IntegerType -> Bool # (<=) :: IntegerType -> IntegerType -> Bool # (>) :: IntegerType -> IntegerType -> Bool # (>=) :: IntegerType -> IntegerType -> Bool # max :: IntegerType -> IntegerType -> IntegerType # min :: IntegerType -> IntegerType -> IntegerType # |
_IntegerType :: Name Source #
data IntegerValue Source #
An integer literal value
IntegerValueBigint Integer | An arbitrary-precision integer value |
IntegerValueInt8 Int | An 8-bit signed integer value |
IntegerValueInt16 Int | A 16-bit signed integer value (short value) |
IntegerValueInt32 Int | A 32-bit signed integer value (int value) |
IntegerValueInt64 Integer | A 64-bit signed integer value (long value) |
IntegerValueUint8 Int | An 8-bit unsigned integer value (byte) |
IntegerValueUint16 Int | A 16-bit unsigned integer value |
IntegerValueUint32 Integer | A 32-bit unsigned integer value (unsigned int) |
IntegerValueUint64 Integer | A 64-bit unsigned integer value (unsigned long) |
Instances
Read IntegerValue Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS IntegerValue # readList :: ReadS [IntegerValue] # | |
Show IntegerValue Source # | |
Defined in Hydra.Core showsPrec :: Int -> IntegerValue -> ShowS # show :: IntegerValue -> String # showList :: [IntegerValue] -> ShowS # | |
Eq IntegerValue Source # | |
Defined in Hydra.Core (==) :: IntegerValue -> IntegerValue -> Bool # (/=) :: IntegerValue -> IntegerValue -> Bool # | |
Ord IntegerValue Source # | |
Defined in Hydra.Core compare :: IntegerValue -> IntegerValue -> Ordering # (<) :: IntegerValue -> IntegerValue -> Bool # (<=) :: IntegerValue -> IntegerValue -> Bool # (>) :: IntegerValue -> IntegerValue -> Bool # (>=) :: IntegerValue -> IntegerValue -> Bool # max :: IntegerValue -> IntegerValue -> IntegerValue # min :: IntegerValue -> IntegerValue -> IntegerValue # |
_IntegerValue :: Name Source #
A function abstraction (lambda)
Lambda | |
|
data LambdaType m Source #
A type abstraction; the type-level analog of a lambda term
LambdaType | |
|
Instances
Read m => Read (LambdaType m) Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS (LambdaType m) # readList :: ReadS [LambdaType m] # readPrec :: ReadPrec (LambdaType m) # readListPrec :: ReadPrec [LambdaType m] # | |
Show m => Show (LambdaType m) Source # | |
Defined in Hydra.Core showsPrec :: Int -> LambdaType m -> ShowS # show :: LambdaType m -> String # showList :: [LambdaType m] -> ShowS # | |
Eq m => Eq (LambdaType m) Source # | |
Defined in Hydra.Core (==) :: LambdaType m -> LambdaType m -> Bool # (/=) :: LambdaType m -> LambdaType m -> Bool # | |
Ord m => Ord (LambdaType m) Source # | |
Defined in Hydra.Core compare :: LambdaType m -> LambdaType m -> Ordering # (<) :: LambdaType m -> LambdaType m -> Bool # (<=) :: LambdaType m -> LambdaType m -> Bool # (>) :: LambdaType m -> LambdaType m -> Bool # (>=) :: LambdaType m -> LambdaType m -> Bool # max :: LambdaType m -> LambdaType m -> LambdaType m # min :: LambdaType m -> LambdaType m -> LambdaType m # |
_LambdaType :: Name Source #
A 'let' binding
A term constant; an instance of a literal type
LiteralBinary String | A binary literal |
LiteralBoolean Bool | A boolean literal |
LiteralFloat FloatValue | A floating-point literal |
LiteralInteger IntegerValue | An integer literal |
LiteralString String | A string literal |
data LiteralType Source #
Any of a fixed set of literal types, also called atomic types, base types, primitive types, or type constants
LiteralTypeBinary | |
LiteralTypeBoolean | |
LiteralTypeFloat FloatType | |
LiteralTypeInteger IntegerType | |
LiteralTypeString |
Instances
Read LiteralType Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS LiteralType # readList :: ReadS [LiteralType] # readPrec :: ReadPrec LiteralType # readListPrec :: ReadPrec [LiteralType] # | |
Show LiteralType Source # | |
Defined in Hydra.Core showsPrec :: Int -> LiteralType -> ShowS # show :: LiteralType -> String # showList :: [LiteralType] -> ShowS # | |
Eq LiteralType Source # | |
Defined in Hydra.Core (==) :: LiteralType -> LiteralType -> Bool # (/=) :: LiteralType -> LiteralType -> Bool # | |
Ord LiteralType Source # | |
Defined in Hydra.Core compare :: LiteralType -> LiteralType -> Ordering # (<) :: LiteralType -> LiteralType -> Bool # (<=) :: LiteralType -> LiteralType -> Bool # (>) :: LiteralType -> LiteralType -> Bool # (>=) :: LiteralType -> LiteralType -> Bool # max :: LiteralType -> LiteralType -> LiteralType # min :: LiteralType -> LiteralType -> LiteralType # |
_LiteralType :: Name Source #
A map type
MapType | |
|
A unique element name
A term annotated with a fixed, named type; an instance of a newtype
Named | |
|
data OptionalCases m Source #
A case statement for matching optional terms
OptionalCases | |
|
Instances
data Projection Source #
Instances
Read Projection Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS Projection # readList :: ReadS [Projection] # readPrec :: ReadPrec Projection # readListPrec :: ReadPrec [Projection] # | |
Show Projection Source # | |
Defined in Hydra.Core showsPrec :: Int -> Projection -> ShowS # show :: Projection -> String # showList :: [Projection] -> ShowS # | |
Eq Projection Source # | |
Defined in Hydra.Core (==) :: Projection -> Projection -> Bool # (/=) :: Projection -> Projection -> Bool # | |
Ord Projection Source # | |
Defined in Hydra.Core compare :: Projection -> Projection -> Ordering # (<) :: Projection -> Projection -> Bool # (<=) :: Projection -> Projection -> Bool # (>) :: Projection -> Projection -> Bool # (>=) :: Projection -> Projection -> Bool # max :: Projection -> Projection -> Projection # min :: Projection -> Projection -> Projection # |
_Projection :: Name Source #
A record, or labeled tuple; a map of field names to terms
Record | |
|
A labeled record or union type
RowType | |
|
An infinite stream of terms
Stream | |
|
The unlabeled equivalent of a Union term
A data term
TermAnnotated (Annotated (Term m) m) | A term annotated with metadata |
TermApplication (Application m) | A function application |
TermElement Name | An element reference |
TermFunction (Function m) | A function term |
TermLet (Let m) | |
TermList [Term m] | A list |
TermLiteral Literal | A literal value |
TermMap (Map (Term m) (Term m)) | A map of keys to values |
TermNominal (Named m) | |
TermOptional (Maybe (Term m)) | An optional value |
TermProduct [Term m] | A tuple |
TermRecord (Record m) | A record term |
TermSet (Set (Term m)) | A set of values |
TermStream (Stream m) | An infinite stream of terms |
TermSum (Sum m) | A variant tuple |
TermUnion (Union m) | A union term |
TermVariable Variable | A variable reference |
A data type
TypeAnnotated (Annotated (Type m) m) | A type annotated with metadata |
TypeApplication (ApplicationType m) | |
TypeElement (Type m) | |
TypeFunction (FunctionType m) | |
TypeLambda (LambdaType m) | |
TypeList (Type m) | |
TypeLiteral LiteralType | |
TypeMap (MapType m) | |
TypeNominal Name | |
TypeOptional (Type m) | |
TypeProduct [Type m] | |
TypeRecord (RowType m) | |
TypeSet (Type m) | |
TypeStream (Type m) | |
TypeSum [Type m] | |
TypeUnion (RowType m) | |
TypeVariable VariableType |
A symbol which stands in for a term
Variable | |
|
newtype VariableType Source #
A symbol which stands in for a type
VariableType | |
|
Instances
Read VariableType Source # | |
Defined in Hydra.Core readsPrec :: Int -> ReadS VariableType # readList :: ReadS [VariableType] # | |
Show VariableType Source # | |
Defined in Hydra.Core showsPrec :: Int -> VariableType -> ShowS # show :: VariableType -> String # showList :: [VariableType] -> ShowS # | |
Eq VariableType Source # | |
Defined in Hydra.Core (==) :: VariableType -> VariableType -> Bool # (/=) :: VariableType -> VariableType -> Bool # | |
Ord VariableType Source # | |
Defined in Hydra.Core compare :: VariableType -> VariableType -> Ordering # (<) :: VariableType -> VariableType -> Bool # (<=) :: VariableType -> VariableType -> Bool # (>) :: VariableType -> VariableType -> Bool # (>=) :: VariableType -> VariableType -> Bool # max :: VariableType -> VariableType -> VariableType # min :: VariableType -> VariableType -> VariableType # |
_VariableType :: Name Source #
An instance of a union type; i.e. a string-indexed generalization of inl() or inr()
Union | |
|