| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Core
Description
Hydra's core data model, defining types, terms, and their dependencies
Synopsis
- data AnnotatedTerm = AnnotatedTerm {}
- _AnnotatedTerm :: Name
- _AnnotatedTerm_subject :: Name
- _AnnotatedTerm_annotation :: Name
- data AnnotatedType = AnnotatedType {}
- _AnnotatedType :: Name
- _AnnotatedType_subject :: Name
- _AnnotatedType_annotation :: Name
- data Application = Application {}
- _Application :: Name
- _Application_function :: Name
- _Application_argument :: Name
- data ApplicationType = ApplicationType {}
- _ApplicationType :: Name
- _ApplicationType_function :: Name
- _ApplicationType_argument :: Name
- data CaseStatement = CaseStatement {}
- _CaseStatement :: Name
- _CaseStatement_typeName :: Name
- _CaseStatement_default :: Name
- _CaseStatement_cases :: Name
- data Elimination
- _Elimination :: Name
- _Elimination_list :: Name
- _Elimination_optional :: Name
- _Elimination_product :: Name
- _Elimination_record :: Name
- _Elimination_union :: Name
- _Elimination_wrap :: Name
- data Field = Field {}
- _Field :: Name
- _Field_name :: Name
- _Field_term :: Name
- data FieldType = FieldType {}
- _FieldType :: Name
- _FieldType_name :: Name
- _FieldType_type :: Name
- data FloatType
- _FloatType :: Name
- _FloatType_bigfloat :: Name
- _FloatType_float32 :: Name
- _FloatType_float64 :: Name
- data FloatValue
- _FloatValue :: Name
- _FloatValue_bigfloat :: Name
- _FloatValue_float32 :: Name
- _FloatValue_float64 :: Name
- data Function
- _Function :: Name
- _Function_elimination :: Name
- _Function_lambda :: Name
- _Function_primitive :: Name
- data FunctionType = FunctionType {}
- _FunctionType :: Name
- _FunctionType_domain :: Name
- _FunctionType_codomain :: Name
- data Injection = Injection {}
- _Injection :: Name
- _Injection_typeName :: Name
- _Injection_field :: Name
- data IntegerType
- _IntegerType :: 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 :: Name
- data IntegerValue
- _IntegerValue :: Name
- _IntegerValue_bigint :: Name
- _IntegerValue_int8 :: Name
- _IntegerValue_int16 :: Name
- _IntegerValue_int32 :: Name
- _IntegerValue_int64 :: Name
- _IntegerValue_uint8 :: Name
- _IntegerValue_uint16 :: Name
- _IntegerValue_uint32 :: Name
- _IntegerValue_uint64 :: Name
- data Lambda = Lambda {}
- _Lambda :: Name
- _Lambda_parameter :: Name
- _Lambda_domain :: Name
- _Lambda_body :: Name
- data LambdaType = LambdaType {}
- _LambdaType :: Name
- _LambdaType_parameter :: Name
- _LambdaType_body :: Name
- data Let = Let {
- letBindings :: [LetBinding]
- letEnvironment :: Term
- _Let :: Name
- _Let_bindings :: Name
- _Let_environment :: Name
- data LetBinding = LetBinding {}
- _LetBinding :: Name
- _LetBinding_name :: Name
- _LetBinding_term :: Name
- _LetBinding_type :: Name
- data Literal
- _Literal :: Name
- _Literal_binary :: Name
- _Literal_boolean :: Name
- _Literal_float :: Name
- _Literal_integer :: Name
- _Literal_string :: Name
- data LiteralType
- _LiteralType :: Name
- _LiteralType_binary :: Name
- _LiteralType_boolean :: Name
- _LiteralType_float :: Name
- _LiteralType_integer :: Name
- _LiteralType_string :: Name
- data MapType = MapType {
- mapTypeKeys :: Type
- mapTypeValues :: Type
- _MapType :: Name
- _MapType_keys :: Name
- _MapType_values :: Name
- newtype Name = Name {}
- _Name :: Name
- data WrappedTerm = WrappedTerm {}
- _WrappedTerm :: Name
- _WrappedTerm_typeName :: Name
- _WrappedTerm_object :: Name
- data WrappedType = WrappedType {}
- _WrappedType :: Name
- _WrappedType_typeName :: Name
- _WrappedType_object :: Name
- data OptionalCases = OptionalCases {}
- _OptionalCases :: Name
- _OptionalCases_nothing :: Name
- _OptionalCases_just :: Name
- data Projection = Projection {}
- _Projection :: Name
- _Projection_typeName :: Name
- _Projection_field :: Name
- data Record = Record {
- recordTypeName :: Name
- recordFields :: [Field]
- _Record :: Name
- _Record_typeName :: Name
- _Record_fields :: Name
- data RowType = RowType {}
- _RowType :: Name
- _RowType_typeName :: Name
- _RowType_fields :: Name
- data Sum = Sum {}
- _Sum :: Name
- _Sum_index :: Name
- _Sum_size :: Name
- _Sum_term :: Name
- data Term
- = TermAnnotated AnnotatedTerm
- | TermApplication Application
- | TermFunction Function
- | TermLet Let
- | TermList [Term]
- | TermLiteral Literal
- | TermMap (Map Term Term)
- | TermOptional (Maybe Term)
- | TermProduct [Term]
- | TermRecord Record
- | TermSet (Set Term)
- | TermSum Sum
- | TermTypeAbstraction TypeAbstraction
- | TermTypeApplication TypedTerm
- | TermTyped TypedTerm
- | TermUnion Injection
- | TermVariable Name
- | TermWrap WrappedTerm
- _Term :: Name
- _Term_annotated :: Name
- _Term_application :: Name
- _Term_function :: Name
- _Term_let :: Name
- _Term_list :: Name
- _Term_literal :: Name
- _Term_map :: Name
- _Term_optional :: Name
- _Term_product :: Name
- _Term_record :: Name
- _Term_set :: Name
- _Term_sum :: Name
- _Term_typeAbstraction :: Name
- _Term_typeApplication :: Name
- _Term_typed :: Name
- _Term_union :: Name
- _Term_variable :: Name
- _Term_wrap :: Name
- data TupleProjection = TupleProjection {}
- _TupleProjection :: Name
- _TupleProjection_arity :: Name
- _TupleProjection_index :: Name
- data Type
- = TypeAnnotated AnnotatedType
- | TypeApplication ApplicationType
- | TypeFunction FunctionType
- | TypeLambda LambdaType
- | TypeList Type
- | TypeLiteral LiteralType
- | TypeMap MapType
- | TypeOptional Type
- | TypeProduct [Type]
- | TypeRecord RowType
- | TypeSet Type
- | TypeSum [Type]
- | TypeUnion RowType
- | TypeVariable Name
- | TypeWrap WrappedType
- _Type :: Name
- _Type_annotated :: Name
- _Type_application :: Name
- _Type_function :: Name
- _Type_lambda :: Name
- _Type_list :: Name
- _Type_literal :: Name
- _Type_map :: Name
- _Type_optional :: Name
- _Type_product :: Name
- _Type_record :: Name
- _Type_set :: Name
- _Type_sum :: Name
- _Type_union :: Name
- _Type_variable :: Name
- _Type_wrap :: Name
- data TypeAbstraction = TypeAbstraction {}
- _TypeAbstraction :: Name
- _TypeAbstraction_parameter :: Name
- _TypeAbstraction_body :: Name
- data TypeScheme = TypeScheme {}
- _TypeScheme :: Name
- _TypeScheme_variables :: Name
- _TypeScheme_type :: Name
- data TypedTerm = TypedTerm {}
- _TypedTerm :: Name
- _TypedTerm_term :: Name
- _TypedTerm_type :: Name
- data Unit = Unit {
- _Unit :: Name
Documentation
data AnnotatedTerm Source #
A term together with an annotation
Constructors
| AnnotatedTerm | |
Fields | |
Instances
| Read AnnotatedTerm Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS AnnotatedTerm # readList :: ReadS [AnnotatedTerm] # | |
| Show AnnotatedTerm Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> AnnotatedTerm -> ShowS # show :: AnnotatedTerm -> String # showList :: [AnnotatedTerm] -> ShowS # | |
| Eq AnnotatedTerm Source # | |
Defined in Hydra.Core Methods (==) :: AnnotatedTerm -> AnnotatedTerm -> Bool # (/=) :: AnnotatedTerm -> AnnotatedTerm -> Bool # | |
| Ord AnnotatedTerm Source # | |
Defined in Hydra.Core Methods compare :: AnnotatedTerm -> AnnotatedTerm -> Ordering # (<) :: AnnotatedTerm -> AnnotatedTerm -> Bool # (<=) :: AnnotatedTerm -> AnnotatedTerm -> Bool # (>) :: AnnotatedTerm -> AnnotatedTerm -> Bool # (>=) :: AnnotatedTerm -> AnnotatedTerm -> Bool # max :: AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm # min :: AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm # | |
data AnnotatedType Source #
A type together with an annotation
Constructors
| AnnotatedType | |
Fields | |
Instances
| Read AnnotatedType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS AnnotatedType # readList :: ReadS [AnnotatedType] # | |
| Show AnnotatedType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> AnnotatedType -> ShowS # show :: AnnotatedType -> String # showList :: [AnnotatedType] -> ShowS # | |
| Eq AnnotatedType Source # | |
Defined in Hydra.Core Methods (==) :: AnnotatedType -> AnnotatedType -> Bool # (/=) :: AnnotatedType -> AnnotatedType -> Bool # | |
| Ord AnnotatedType Source # | |
Defined in Hydra.Core Methods compare :: AnnotatedType -> AnnotatedType -> Ordering # (<) :: AnnotatedType -> AnnotatedType -> Bool # (<=) :: AnnotatedType -> AnnotatedType -> Bool # (>) :: AnnotatedType -> AnnotatedType -> Bool # (>=) :: AnnotatedType -> AnnotatedType -> Bool # max :: AnnotatedType -> AnnotatedType -> AnnotatedType # min :: AnnotatedType -> AnnotatedType -> AnnotatedType # | |
data Application Source #
A term which applies a function to an argument
Constructors
| Application | |
Fields
| |
Instances
| Read Application Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS Application # readList :: ReadS [Application] # readPrec :: ReadPrec Application # readListPrec :: ReadPrec [Application] # | |
| Show Application Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> Application -> ShowS # show :: Application -> String # showList :: [Application] -> ShowS # | |
| Eq Application Source # | |
Defined in Hydra.Core | |
| Ord Application Source # | |
Defined in Hydra.Core Methods compare :: Application -> Application -> Ordering # (<) :: Application -> Application -> Bool # (<=) :: Application -> Application -> Bool # (>) :: Application -> Application -> Bool # (>=) :: Application -> Application -> Bool # max :: Application -> Application -> Application # min :: Application -> Application -> Application # | |
_Application :: Name Source #
data ApplicationType Source #
The type-level analog of an application term
Constructors
| ApplicationType | |
Fields
| |
Instances
| Read ApplicationType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS ApplicationType # readList :: ReadS [ApplicationType] # | |
| Show ApplicationType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> ApplicationType -> ShowS # show :: ApplicationType -> String # showList :: [ApplicationType] -> ShowS # | |
| Eq ApplicationType Source # | |
Defined in Hydra.Core Methods (==) :: ApplicationType -> ApplicationType -> Bool # (/=) :: ApplicationType -> ApplicationType -> Bool # | |
| Ord ApplicationType Source # | |
Defined in Hydra.Core Methods compare :: ApplicationType -> ApplicationType -> Ordering # (<) :: ApplicationType -> ApplicationType -> Bool # (<=) :: ApplicationType -> ApplicationType -> Bool # (>) :: ApplicationType -> ApplicationType -> Bool # (>=) :: ApplicationType -> ApplicationType -> Bool # max :: ApplicationType -> ApplicationType -> ApplicationType # min :: ApplicationType -> ApplicationType -> ApplicationType # | |
data CaseStatement Source #
A union elimination; a case statement
Constructors
| CaseStatement | |
Fields | |
Instances
| Read CaseStatement Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS CaseStatement # readList :: ReadS [CaseStatement] # | |
| Show CaseStatement Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> CaseStatement -> ShowS # show :: CaseStatement -> String # showList :: [CaseStatement] -> ShowS # | |
| Eq CaseStatement Source # | |
Defined in Hydra.Core Methods (==) :: CaseStatement -> CaseStatement -> Bool # (/=) :: CaseStatement -> CaseStatement -> Bool # | |
| Ord CaseStatement Source # | |
Defined in Hydra.Core Methods compare :: CaseStatement -> CaseStatement -> Ordering # (<) :: CaseStatement -> CaseStatement -> Bool # (<=) :: CaseStatement -> CaseStatement -> Bool # (>) :: CaseStatement -> CaseStatement -> Bool # (>=) :: CaseStatement -> CaseStatement -> Bool # max :: CaseStatement -> CaseStatement -> CaseStatement # min :: CaseStatement -> CaseStatement -> CaseStatement # | |
data Elimination Source #
A corresponding elimination for an introduction term
Constructors
| EliminationList Term | Eliminates a list using a fold function; this function has the signature b -> [a] -> b |
| EliminationOptional OptionalCases | Eliminates an optional term by matching over the two possible cases |
| EliminationProduct TupleProjection | Eliminates a tuple by projecting the component at a given 0-indexed offset |
| EliminationRecord Projection | Eliminates a record by projecting a given field |
| EliminationUnion CaseStatement | Eliminates a union term by matching over the fields of the union. This is a case statement. |
| EliminationWrap Name | Unwrap a wrapped term |
Instances
| Read Elimination Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS Elimination # readList :: ReadS [Elimination] # readPrec :: ReadPrec Elimination # readListPrec :: ReadPrec [Elimination] # | |
| Show Elimination Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> Elimination -> ShowS # show :: Elimination -> String # showList :: [Elimination] -> ShowS # | |
| Eq Elimination Source # | |
Defined in Hydra.Core | |
| Ord Elimination Source # | |
Defined in Hydra.Core Methods compare :: Elimination -> Elimination -> Ordering # (<) :: Elimination -> Elimination -> Bool # (<=) :: Elimination -> Elimination -> Bool # (>) :: Elimination -> Elimination -> Bool # (>=) :: Elimination -> Elimination -> Bool # max :: Elimination -> Elimination -> Elimination # min :: Elimination -> Elimination -> Elimination # | |
_Elimination :: Name Source #
A name/term pair
_Field_name :: Name Source #
_Field_term :: Name Source #
A name/type pair
Constructors
| FieldType | |
Fields
| |
Instances
| Read FieldType Source # | |
| Show FieldType Source # | |
| Eq FieldType Source # | |
| Ord FieldType Source # | |
_FieldType :: Name Source #
A floating-point type
Constructors
| FloatTypeBigfloat | |
| FloatTypeFloat32 | |
| FloatTypeFloat64 |
Instances
| Read FloatType Source # | |
| Show FloatType Source # | |
| Eq FloatType Source # | |
| Ord FloatType Source # | |
_FloatType :: Name Source #
data FloatValue Source #
A floating-point literal value
Constructors
| 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 Methods readsPrec :: Int -> ReadS FloatValue # readList :: ReadS [FloatValue] # readPrec :: ReadPrec FloatValue # readListPrec :: ReadPrec [FloatValue] # | |
| Show FloatValue Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> FloatValue -> ShowS # show :: FloatValue -> String # showList :: [FloatValue] -> ShowS # | |
| Eq FloatValue Source # | |
Defined in Hydra.Core | |
| Ord FloatValue Source # | |
Defined in Hydra.Core Methods 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
Constructors
| FunctionElimination Elimination | An elimination for any of a few term variants |
| FunctionLambda Lambda | A function abstraction (lambda) |
| FunctionPrimitive Name | A reference to a built-in (primitive) function |
data FunctionType Source #
A function type, also known as an arrow type
Constructors
| FunctionType | |
Fields | |
Instances
| Read FunctionType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS FunctionType # readList :: ReadS [FunctionType] # | |
| Show FunctionType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> FunctionType -> ShowS # show :: FunctionType -> String # showList :: [FunctionType] -> ShowS # | |
| Eq FunctionType Source # | |
Defined in Hydra.Core | |
| Ord FunctionType Source # | |
Defined in Hydra.Core Methods compare :: FunctionType -> FunctionType -> Ordering # (<) :: FunctionType -> FunctionType -> Bool # (<=) :: FunctionType -> FunctionType -> Bool # (>) :: FunctionType -> FunctionType -> Bool # (>=) :: FunctionType -> FunctionType -> Bool # max :: FunctionType -> FunctionType -> FunctionType # min :: FunctionType -> FunctionType -> FunctionType # | |
_FunctionType :: Name Source #
An instance of a union type; i.e. a string-indexed generalization of inl() or inr()
Constructors
| Injection | |
Fields | |
Instances
| Read Injection Source # | |
| Show Injection Source # | |
| Eq Injection Source # | |
| Ord Injection Source # | |
_Injection :: Name Source #
data IntegerType Source #
An integer type
Constructors
| IntegerTypeBigint | |
| IntegerTypeInt8 | |
| IntegerTypeInt16 | |
| IntegerTypeInt32 | |
| IntegerTypeInt64 | |
| IntegerTypeUint8 | |
| IntegerTypeUint16 | |
| IntegerTypeUint32 | |
| IntegerTypeUint64 |
Instances
| Read IntegerType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS IntegerType # readList :: ReadS [IntegerType] # readPrec :: ReadPrec IntegerType # readListPrec :: ReadPrec [IntegerType] # | |
| Show IntegerType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> IntegerType -> ShowS # show :: IntegerType -> String # showList :: [IntegerType] -> ShowS # | |
| Eq IntegerType Source # | |
Defined in Hydra.Core | |
| Ord IntegerType Source # | |
Defined in Hydra.Core Methods 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
Constructors
| IntegerValueBigint Integer | An arbitrary-precision integer value |
| IntegerValueInt8 Int8 | An 8-bit signed integer value |
| IntegerValueInt16 Int16 | A 16-bit signed integer value (short value) |
| IntegerValueInt32 Int | A 32-bit signed integer value (int value) |
| IntegerValueInt64 Int64 | A 64-bit signed integer value (long value) |
| IntegerValueUint8 Int16 | An 8-bit unsigned integer value (byte) |
| IntegerValueUint16 Int | A 16-bit unsigned integer value |
| IntegerValueUint32 Int64 | 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 Methods readsPrec :: Int -> ReadS IntegerValue # readList :: ReadS [IntegerValue] # | |
| Show IntegerValue Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> IntegerValue -> ShowS # show :: IntegerValue -> String # showList :: [IntegerValue] -> ShowS # | |
| Eq IntegerValue Source # | |
Defined in Hydra.Core | |
| Ord IntegerValue Source # | |
Defined in Hydra.Core Methods 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)
Constructors
| Lambda | |
Fields
| |
_Lambda_body :: Name Source #
data LambdaType Source #
A type abstraction; the type-level analog of a lambda term
Constructors
| LambdaType | |
Fields
| |
Instances
| Read LambdaType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS LambdaType # readList :: ReadS [LambdaType] # readPrec :: ReadPrec LambdaType # readListPrec :: ReadPrec [LambdaType] # | |
| Show LambdaType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> LambdaType -> ShowS # show :: LambdaType -> String # showList :: [LambdaType] -> ShowS # | |
| Eq LambdaType Source # | |
Defined in Hydra.Core | |
| Ord LambdaType Source # | |
Defined in Hydra.Core Methods compare :: LambdaType -> LambdaType -> Ordering # (<) :: LambdaType -> LambdaType -> Bool # (<=) :: LambdaType -> LambdaType -> Bool # (>) :: LambdaType -> LambdaType -> Bool # (>=) :: LambdaType -> LambdaType -> Bool # max :: LambdaType -> LambdaType -> LambdaType # min :: LambdaType -> LambdaType -> LambdaType # | |
_LambdaType :: Name Source #
A set of (possibly recursive) 'let' bindings together with an environment in which they are bound
Constructors
| Let | |
Fields
| |
_Let_bindings :: Name Source #
data LetBinding Source #
A field with an optional type scheme, used to bind variables to terms in a 'let' expression
Constructors
| LetBinding | |
Fields | |
Instances
| Read LetBinding Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS LetBinding # readList :: ReadS [LetBinding] # readPrec :: ReadPrec LetBinding # readListPrec :: ReadPrec [LetBinding] # | |
| Show LetBinding Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> LetBinding -> ShowS # show :: LetBinding -> String # showList :: [LetBinding] -> ShowS # | |
| Eq LetBinding Source # | |
Defined in Hydra.Core | |
| Ord LetBinding Source # | |
Defined in Hydra.Core Methods compare :: LetBinding -> LetBinding -> Ordering # (<) :: LetBinding -> LetBinding -> Bool # (<=) :: LetBinding -> LetBinding -> Bool # (>) :: LetBinding -> LetBinding -> Bool # (>=) :: LetBinding -> LetBinding -> Bool # max :: LetBinding -> LetBinding -> LetBinding # min :: LetBinding -> LetBinding -> LetBinding # | |
_LetBinding :: Name Source #
A term constant; an instance of a literal type
Constructors
| 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
Constructors
| LiteralTypeBinary | |
| LiteralTypeBoolean | |
| LiteralTypeFloat FloatType | |
| LiteralTypeInteger IntegerType | |
| LiteralTypeString |
Instances
| Read LiteralType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS LiteralType # readList :: ReadS [LiteralType] # readPrec :: ReadPrec LiteralType # readListPrec :: ReadPrec [LiteralType] # | |
| Show LiteralType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> LiteralType -> ShowS # show :: LiteralType -> String # showList :: [LiteralType] -> ShowS # | |
| Eq LiteralType Source # | |
Defined in Hydra.Core | |
| Ord LiteralType Source # | |
Defined in Hydra.Core Methods 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
Constructors
| MapType | |
Fields
| |
_MapType_keys :: Name Source #
A unique identifier in some context; a string-valued key
data WrappedTerm Source #
A term wrapped in a type name
Constructors
| WrappedTerm | |
Fields | |
Instances
| Read WrappedTerm Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS WrappedTerm # readList :: ReadS [WrappedTerm] # readPrec :: ReadPrec WrappedTerm # readListPrec :: ReadPrec [WrappedTerm] # | |
| Show WrappedTerm Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> WrappedTerm -> ShowS # show :: WrappedTerm -> String # showList :: [WrappedTerm] -> ShowS # | |
| Eq WrappedTerm Source # | |
Defined in Hydra.Core | |
| Ord WrappedTerm Source # | |
Defined in Hydra.Core Methods compare :: WrappedTerm -> WrappedTerm -> Ordering # (<) :: WrappedTerm -> WrappedTerm -> Bool # (<=) :: WrappedTerm -> WrappedTerm -> Bool # (>) :: WrappedTerm -> WrappedTerm -> Bool # (>=) :: WrappedTerm -> WrappedTerm -> Bool # max :: WrappedTerm -> WrappedTerm -> WrappedTerm # min :: WrappedTerm -> WrappedTerm -> WrappedTerm # | |
_WrappedTerm :: Name Source #
data WrappedType Source #
A type wrapped in a type name
Constructors
| WrappedType | |
Fields | |
Instances
| Read WrappedType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS WrappedType # readList :: ReadS [WrappedType] # readPrec :: ReadPrec WrappedType # readListPrec :: ReadPrec [WrappedType] # | |
| Show WrappedType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> WrappedType -> ShowS # show :: WrappedType -> String # showList :: [WrappedType] -> ShowS # | |
| Eq WrappedType Source # | |
Defined in Hydra.Core | |
| Ord WrappedType Source # | |
Defined in Hydra.Core Methods compare :: WrappedType -> WrappedType -> Ordering # (<) :: WrappedType -> WrappedType -> Bool # (<=) :: WrappedType -> WrappedType -> Bool # (>) :: WrappedType -> WrappedType -> Bool # (>=) :: WrappedType -> WrappedType -> Bool # max :: WrappedType -> WrappedType -> WrappedType # min :: WrappedType -> WrappedType -> WrappedType # | |
_WrappedType :: Name Source #
data OptionalCases Source #
A case statement for matching optional terms
Constructors
| OptionalCases | |
Fields
| |
Instances
| Read OptionalCases Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS OptionalCases # readList :: ReadS [OptionalCases] # | |
| Show OptionalCases Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> OptionalCases -> ShowS # show :: OptionalCases -> String # showList :: [OptionalCases] -> ShowS # | |
| Eq OptionalCases Source # | |
Defined in Hydra.Core Methods (==) :: OptionalCases -> OptionalCases -> Bool # (/=) :: OptionalCases -> OptionalCases -> Bool # | |
| Ord OptionalCases Source # | |
Defined in Hydra.Core Methods compare :: OptionalCases -> OptionalCases -> Ordering # (<) :: OptionalCases -> OptionalCases -> Bool # (<=) :: OptionalCases -> OptionalCases -> Bool # (>) :: OptionalCases -> OptionalCases -> Bool # (>=) :: OptionalCases -> OptionalCases -> Bool # max :: OptionalCases -> OptionalCases -> OptionalCases # min :: OptionalCases -> OptionalCases -> OptionalCases # | |
data Projection Source #
A record elimination; a projection
Constructors
| Projection | |
Fields
| |
Instances
| Read Projection Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS Projection # readList :: ReadS [Projection] # readPrec :: ReadPrec Projection # readListPrec :: ReadPrec [Projection] # | |
| Show Projection Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> Projection -> ShowS # show :: Projection -> String # showList :: [Projection] -> ShowS # | |
| Eq Projection Source # | |
Defined in Hydra.Core | |
| Ord Projection Source # | |
Defined in Hydra.Core Methods 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
Constructors
| Record | |
Fields
| |
A labeled record or union type
Constructors
| RowType | |
Fields
| |
The unlabeled equivalent of an Injection term
_Sum_index :: Name Source #
A data term
Constructors
| TermAnnotated AnnotatedTerm | A term annotated with metadata |
| TermApplication Application | A function application |
| TermFunction Function | A function term |
| TermLet Let | |
| TermList [Term] | A list |
| TermLiteral Literal | A literal value |
| TermMap (Map Term Term) | A map of keys to values |
| TermOptional (Maybe Term) | An optional value |
| TermProduct [Term] | A tuple |
| TermRecord Record | A record term |
| TermSet (Set Term) | A set of values |
| TermSum Sum | A variant tuple |
| TermTypeAbstraction TypeAbstraction | A System F type abstraction term |
| TermTypeApplication TypedTerm | A System F type application term |
| TermTyped TypedTerm | A term annotated with its type |
| TermUnion Injection | An injection; an instance of a union type |
| TermVariable Name | A variable reference |
| TermWrap WrappedTerm |
_Term_list :: Name Source #
_Term_literal :: Name Source #
_Term_product :: Name Source #
_Term_record :: Name Source #
_Term_typed :: Name Source #
_Term_union :: Name Source #
_Term_wrap :: Name Source #
data TupleProjection Source #
A tuple elimination; a projection from an integer-indexed product
Constructors
| TupleProjection | |
Fields
| |
Instances
| Read TupleProjection Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS TupleProjection # readList :: ReadS [TupleProjection] # | |
| Show TupleProjection Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> TupleProjection -> ShowS # show :: TupleProjection -> String # showList :: [TupleProjection] -> ShowS # | |
| Eq TupleProjection Source # | |
Defined in Hydra.Core Methods (==) :: TupleProjection -> TupleProjection -> Bool # (/=) :: TupleProjection -> TupleProjection -> Bool # | |
| Ord TupleProjection Source # | |
Defined in Hydra.Core Methods compare :: TupleProjection -> TupleProjection -> Ordering # (<) :: TupleProjection -> TupleProjection -> Bool # (<=) :: TupleProjection -> TupleProjection -> Bool # (>) :: TupleProjection -> TupleProjection -> Bool # (>=) :: TupleProjection -> TupleProjection -> Bool # max :: TupleProjection -> TupleProjection -> TupleProjection # min :: TupleProjection -> TupleProjection -> TupleProjection # | |
A data type
Constructors
_Type_lambda :: Name Source #
_Type_list :: Name Source #
_Type_literal :: Name Source #
_Type_product :: Name Source #
_Type_record :: Name Source #
_Type_union :: Name Source #
_Type_wrap :: Name Source #
data TypeAbstraction Source #
A System F type abstraction term
Constructors
| TypeAbstraction | |
Fields
| |
Instances
| Read TypeAbstraction Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS TypeAbstraction # readList :: ReadS [TypeAbstraction] # | |
| Show TypeAbstraction Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> TypeAbstraction -> ShowS # show :: TypeAbstraction -> String # showList :: [TypeAbstraction] -> ShowS # | |
| Eq TypeAbstraction Source # | |
Defined in Hydra.Core Methods (==) :: TypeAbstraction -> TypeAbstraction -> Bool # (/=) :: TypeAbstraction -> TypeAbstraction -> Bool # | |
| Ord TypeAbstraction Source # | |
Defined in Hydra.Core Methods compare :: TypeAbstraction -> TypeAbstraction -> Ordering # (<) :: TypeAbstraction -> TypeAbstraction -> Bool # (<=) :: TypeAbstraction -> TypeAbstraction -> Bool # (>) :: TypeAbstraction -> TypeAbstraction -> Bool # (>=) :: TypeAbstraction -> TypeAbstraction -> Bool # max :: TypeAbstraction -> TypeAbstraction -> TypeAbstraction # min :: TypeAbstraction -> TypeAbstraction -> TypeAbstraction # | |
data TypeScheme Source #
A type expression together with free type variables occurring in the expression
Constructors
| TypeScheme | |
Fields
| |
Instances
| Read TypeScheme Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS TypeScheme # readList :: ReadS [TypeScheme] # readPrec :: ReadPrec TypeScheme # readListPrec :: ReadPrec [TypeScheme] # | |
| Show TypeScheme Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> TypeScheme -> ShowS # show :: TypeScheme -> String # showList :: [TypeScheme] -> ShowS # | |
| Eq TypeScheme Source # | |
Defined in Hydra.Core | |
| Ord TypeScheme Source # | |
Defined in Hydra.Core Methods compare :: TypeScheme -> TypeScheme -> Ordering # (<) :: TypeScheme -> TypeScheme -> Bool # (<=) :: TypeScheme -> TypeScheme -> Bool # (>) :: TypeScheme -> TypeScheme -> Bool # (>=) :: TypeScheme -> TypeScheme -> Bool # max :: TypeScheme -> TypeScheme -> TypeScheme # min :: TypeScheme -> TypeScheme -> TypeScheme # | |
_TypeScheme :: Name Source #
A term together with its type
Constructors
| TypedTerm | |
Fields
| |
Instances
| Read TypedTerm Source # | |
| Show TypedTerm Source # | |
| Eq TypedTerm Source # | |
| Ord TypedTerm Source # | |
_TypedTerm :: Name Source #