Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A set of types which supplement hydra/core with type variants, graphs, and elements
Synopsis
- data Comparison
- _Comparison :: Name
- _Comparison_lessThan :: FieldName
- _Comparison_equalTo :: FieldName
- _Comparison_greaterThan :: FieldName
- data Element m = Element {
- elementName :: Name
- elementSchema :: Term m
- elementData :: Term m
- _Element :: Name
- _Element_name :: FieldName
- _Element_schema :: FieldName
- _Element_data :: FieldName
- data EliminationVariant
- _EliminationVariant :: Name
- _EliminationVariant_element :: FieldName
- _EliminationVariant_list :: FieldName
- _EliminationVariant_nominal :: FieldName
- _EliminationVariant_optional :: FieldName
- _EliminationVariant_record :: FieldName
- _EliminationVariant_union :: FieldName
- data FunctionVariant
- _FunctionVariant :: Name
- _FunctionVariant_compareTo :: FieldName
- _FunctionVariant_elimination :: FieldName
- _FunctionVariant_lambda :: FieldName
- _FunctionVariant_primitive :: FieldName
- data Graph m = Graph {
- graphElements :: Map Name (Element m)
- graphSchema :: Maybe (Graph m)
- _Graph :: Name
- _Graph_elements :: FieldName
- _Graph_schema :: FieldName
- data LiteralVariant
- _LiteralVariant :: Name
- _LiteralVariant_binary :: FieldName
- _LiteralVariant_boolean :: FieldName
- _LiteralVariant_float :: FieldName
- _LiteralVariant_integer :: FieldName
- _LiteralVariant_string :: FieldName
- data Precision
- _Precision :: Name
- _Precision_arbitrary :: FieldName
- _Precision_bits :: FieldName
- data TermVariant
- = TermVariantAnnotated
- | TermVariantApplication
- | TermVariantElement
- | TermVariantFunction
- | TermVariantLet
- | TermVariantList
- | TermVariantLiteral
- | TermVariantMap
- | TermVariantNominal
- | TermVariantOptional
- | TermVariantProduct
- | TermVariantRecord
- | TermVariantSet
- | TermVariantStream
- | TermVariantSum
- | TermVariantUnion
- | TermVariantVariable
- _TermVariant :: Name
- _TermVariant_annotated :: FieldName
- _TermVariant_application :: FieldName
- _TermVariant_element :: FieldName
- _TermVariant_function :: FieldName
- _TermVariant_let :: FieldName
- _TermVariant_list :: FieldName
- _TermVariant_literal :: FieldName
- _TermVariant_map :: FieldName
- _TermVariant_nominal :: FieldName
- _TermVariant_optional :: FieldName
- _TermVariant_product :: FieldName
- _TermVariant_record :: FieldName
- _TermVariant_set :: FieldName
- _TermVariant_stream :: FieldName
- _TermVariant_sum :: FieldName
- _TermVariant_union :: FieldName
- _TermVariant_variable :: FieldName
- data TypeScheme m = TypeScheme {}
- _TypeScheme :: Name
- _TypeScheme_variables :: FieldName
- _TypeScheme_type :: FieldName
- data TypeVariant
- = TypeVariantAnnotated
- | TypeVariantApplication
- | TypeVariantElement
- | TypeVariantFunction
- | TypeVariantLambda
- | TypeVariantList
- | TypeVariantLiteral
- | TypeVariantMap
- | TypeVariantNominal
- | TypeVariantOptional
- | TypeVariantProduct
- | TypeVariantRecord
- | TypeVariantSet
- | TypeVariantStream
- | TypeVariantSum
- | TypeVariantUnion
- | TypeVariantVariable
- _TypeVariant :: Name
- _TypeVariant_annotated :: FieldName
- _TypeVariant_application :: FieldName
- _TypeVariant_element :: FieldName
- _TypeVariant_function :: FieldName
- _TypeVariant_lambda :: FieldName
- _TypeVariant_list :: FieldName
- _TypeVariant_literal :: FieldName
- _TypeVariant_map :: FieldName
- _TypeVariant_nominal :: FieldName
- _TypeVariant_optional :: FieldName
- _TypeVariant_product :: FieldName
- _TypeVariant_record :: FieldName
- _TypeVariant_set :: FieldName
- _TypeVariant_stream :: FieldName
- _TypeVariant_sum :: FieldName
- _TypeVariant_union :: FieldName
- _TypeVariant_variable :: FieldName
- data TypedTerm m = TypedTerm {
- typedTermType :: Type m
- typedTermTerm :: Term m
- _TypedTerm :: Name
- _TypedTerm_type :: FieldName
- _TypedTerm_term :: FieldName
Documentation
data Comparison Source #
An equality judgement: less than, equal to, or greater than
Instances
Read Comparison Source # | |
Defined in Hydra.Mantle readsPrec :: Int -> ReadS Comparison # readList :: ReadS [Comparison] # readPrec :: ReadPrec Comparison # readListPrec :: ReadPrec [Comparison] # | |
Show Comparison Source # | |
Defined in Hydra.Mantle showsPrec :: Int -> Comparison -> ShowS # show :: Comparison -> String # showList :: [Comparison] -> ShowS # | |
Eq Comparison Source # | |
Defined in Hydra.Mantle (==) :: Comparison -> Comparison -> Bool # (/=) :: Comparison -> Comparison -> Bool # | |
Ord Comparison Source # | |
Defined in Hydra.Mantle compare :: Comparison -> Comparison -> Ordering # (<) :: Comparison -> Comparison -> Bool # (<=) :: Comparison -> Comparison -> Bool # (>) :: Comparison -> Comparison -> Bool # (>=) :: Comparison -> Comparison -> Bool # max :: Comparison -> Comparison -> Comparison # min :: Comparison -> Comparison -> Comparison # |
_Comparison :: Name Source #
A graph element, having a name, data term (value), and schema term (type)
Element | |
|
data EliminationVariant Source #
The identifier of an elimination constructor
EliminationVariantElement | |
EliminationVariantList | |
EliminationVariantNominal | |
EliminationVariantOptional | |
EliminationVariantRecord | |
EliminationVariantUnion |
Instances
Read EliminationVariant Source # | |
Defined in Hydra.Mantle | |
Show EliminationVariant Source # | |
Defined in Hydra.Mantle showsPrec :: Int -> EliminationVariant -> ShowS # show :: EliminationVariant -> String # showList :: [EliminationVariant] -> ShowS # | |
Eq EliminationVariant Source # | |
Defined in Hydra.Mantle (==) :: EliminationVariant -> EliminationVariant -> Bool # (/=) :: EliminationVariant -> EliminationVariant -> Bool # | |
Ord EliminationVariant Source # | |
Defined in Hydra.Mantle compare :: EliminationVariant -> EliminationVariant -> Ordering # (<) :: EliminationVariant -> EliminationVariant -> Bool # (<=) :: EliminationVariant -> EliminationVariant -> Bool # (>) :: EliminationVariant -> EliminationVariant -> Bool # (>=) :: EliminationVariant -> EliminationVariant -> Bool # max :: EliminationVariant -> EliminationVariant -> EliminationVariant # min :: EliminationVariant -> EliminationVariant -> EliminationVariant # |
data FunctionVariant Source #
The identifier of a function constructor
Instances
Read FunctionVariant Source # | |
Defined in Hydra.Mantle | |
Show FunctionVariant Source # | |
Defined in Hydra.Mantle showsPrec :: Int -> FunctionVariant -> ShowS # show :: FunctionVariant -> String # showList :: [FunctionVariant] -> ShowS # | |
Eq FunctionVariant Source # | |
Defined in Hydra.Mantle (==) :: FunctionVariant -> FunctionVariant -> Bool # (/=) :: FunctionVariant -> FunctionVariant -> Bool # | |
Ord FunctionVariant Source # | |
Defined in Hydra.Mantle compare :: FunctionVariant -> FunctionVariant -> Ordering # (<) :: FunctionVariant -> FunctionVariant -> Bool # (<=) :: FunctionVariant -> FunctionVariant -> Bool # (>) :: FunctionVariant -> FunctionVariant -> Bool # (>=) :: FunctionVariant -> FunctionVariant -> Bool # max :: FunctionVariant -> FunctionVariant -> FunctionVariant # min :: FunctionVariant -> FunctionVariant -> FunctionVariant # |
A graph, or set of named terms, together with its schema graph
Graph | |
|
data LiteralVariant Source #
The identifier of a literal constructor
LiteralVariantBinary | |
LiteralVariantBoolean | |
LiteralVariantFloat | |
LiteralVariantInteger | |
LiteralVariantString |
Instances
Read LiteralVariant Source # | |
Defined in Hydra.Mantle readsPrec :: Int -> ReadS LiteralVariant # readList :: ReadS [LiteralVariant] # | |
Show LiteralVariant Source # | |
Defined in Hydra.Mantle showsPrec :: Int -> LiteralVariant -> ShowS # show :: LiteralVariant -> String # showList :: [LiteralVariant] -> ShowS # | |
Eq LiteralVariant Source # | |
Defined in Hydra.Mantle (==) :: LiteralVariant -> LiteralVariant -> Bool # (/=) :: LiteralVariant -> LiteralVariant -> Bool # | |
Ord LiteralVariant Source # | |
Defined in Hydra.Mantle compare :: LiteralVariant -> LiteralVariant -> Ordering # (<) :: LiteralVariant -> LiteralVariant -> Bool # (<=) :: LiteralVariant -> LiteralVariant -> Bool # (>) :: LiteralVariant -> LiteralVariant -> Bool # (>=) :: LiteralVariant -> LiteralVariant -> Bool # max :: LiteralVariant -> LiteralVariant -> LiteralVariant # min :: LiteralVariant -> LiteralVariant -> LiteralVariant # |
Numeric precision: arbitrary precision, or precision to a specified number of bits
_Precision :: Name Source #
data TermVariant Source #
The identifier of a term expression constructor
Instances
Read TermVariant Source # | |
Defined in Hydra.Mantle readsPrec :: Int -> ReadS TermVariant # readList :: ReadS [TermVariant] # readPrec :: ReadPrec TermVariant # readListPrec :: ReadPrec [TermVariant] # | |
Show TermVariant Source # | |
Defined in Hydra.Mantle showsPrec :: Int -> TermVariant -> ShowS # show :: TermVariant -> String # showList :: [TermVariant] -> ShowS # | |
Eq TermVariant Source # | |
Defined in Hydra.Mantle (==) :: TermVariant -> TermVariant -> Bool # (/=) :: TermVariant -> TermVariant -> Bool # | |
Ord TermVariant Source # | |
Defined in Hydra.Mantle compare :: TermVariant -> TermVariant -> Ordering # (<) :: TermVariant -> TermVariant -> Bool # (<=) :: TermVariant -> TermVariant -> Bool # (>) :: TermVariant -> TermVariant -> Bool # (>=) :: TermVariant -> TermVariant -> Bool # max :: TermVariant -> TermVariant -> TermVariant # min :: TermVariant -> TermVariant -> TermVariant # |
_TermVariant :: Name Source #
data TypeScheme m Source #
A type expression together with free type variables occurring in the expression
Instances
Read m => Read (TypeScheme m) Source # | |
Defined in Hydra.Mantle readsPrec :: Int -> ReadS (TypeScheme m) # readList :: ReadS [TypeScheme m] # readPrec :: ReadPrec (TypeScheme m) # readListPrec :: ReadPrec [TypeScheme m] # | |
Show m => Show (TypeScheme m) Source # | |
Defined in Hydra.Mantle showsPrec :: Int -> TypeScheme m -> ShowS # show :: TypeScheme m -> String # showList :: [TypeScheme m] -> ShowS # | |
Eq m => Eq (TypeScheme m) Source # | |
Defined in Hydra.Mantle (==) :: TypeScheme m -> TypeScheme m -> Bool # (/=) :: TypeScheme m -> TypeScheme m -> Bool # | |
Ord m => Ord (TypeScheme m) Source # | |
Defined in Hydra.Mantle compare :: TypeScheme m -> TypeScheme m -> Ordering # (<) :: TypeScheme m -> TypeScheme m -> Bool # (<=) :: TypeScheme m -> TypeScheme m -> Bool # (>) :: TypeScheme m -> TypeScheme m -> Bool # (>=) :: TypeScheme m -> TypeScheme m -> Bool # max :: TypeScheme m -> TypeScheme m -> TypeScheme m # min :: TypeScheme m -> TypeScheme m -> TypeScheme m # |
_TypeScheme :: Name Source #
data TypeVariant Source #
The identifier of a type constructor
Instances
Read TypeVariant Source # | |
Defined in Hydra.Mantle readsPrec :: Int -> ReadS TypeVariant # readList :: ReadS [TypeVariant] # readPrec :: ReadPrec TypeVariant # readListPrec :: ReadPrec [TypeVariant] # | |
Show TypeVariant Source # | |
Defined in Hydra.Mantle showsPrec :: Int -> TypeVariant -> ShowS # show :: TypeVariant -> String # showList :: [TypeVariant] -> ShowS # | |
Eq TypeVariant Source # | |
Defined in Hydra.Mantle (==) :: TypeVariant -> TypeVariant -> Bool # (/=) :: TypeVariant -> TypeVariant -> Bool # | |
Ord TypeVariant Source # | |
Defined in Hydra.Mantle compare :: TypeVariant -> TypeVariant -> Ordering # (<) :: TypeVariant -> TypeVariant -> Bool # (<=) :: TypeVariant -> TypeVariant -> Bool # (>) :: TypeVariant -> TypeVariant -> Bool # (>=) :: TypeVariant -> TypeVariant -> Bool # max :: TypeVariant -> TypeVariant -> TypeVariant # min :: TypeVariant -> TypeVariant -> TypeVariant # |
_TypeVariant :: Name Source #
A type together with an instance of the type
TypedTerm | |
|
Instances
(Read m, Ord m) => Read (TypedTerm m) Source # | |
Show m => Show (TypedTerm m) Source # | |
Eq m => Eq (TypedTerm m) Source # | |
Ord m => Ord (TypedTerm m) Source # | |
_TypedTerm :: Name Source #