Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hydra.Mantle
Description
A set of types which supplement hydra/core with type variants, graphs, and elements
Synopsis
- data Either_ a b
- = EitherLeft a
- | EitherRight b
- _Either :: Name
- _Either_left :: Name
- _Either_right :: Name
- data EliminationVariant
- _EliminationVariant :: Name
- _EliminationVariant_list :: Name
- _EliminationVariant_optional :: Name
- _EliminationVariant_product :: Name
- _EliminationVariant_record :: Name
- _EliminationVariant_union :: Name
- _EliminationVariant_wrap :: Name
- data FunctionVariant
- _FunctionVariant :: Name
- _FunctionVariant_elimination :: Name
- _FunctionVariant_lambda :: Name
- _FunctionVariant_primitive :: Name
- data LiteralVariant
- _LiteralVariant :: Name
- _LiteralVariant_binary :: Name
- _LiteralVariant_boolean :: Name
- _LiteralVariant_float :: Name
- _LiteralVariant_integer :: Name
- _LiteralVariant_string :: Name
- data Precision
- _Precision :: Name
- _Precision_arbitrary :: Name
- _Precision_bits :: Name
- data TermVariant
- = TermVariantAnnotated
- | TermVariantApplication
- | TermVariantFunction
- | TermVariantLet
- | TermVariantList
- | TermVariantLiteral
- | TermVariantMap
- | TermVariantOptional
- | TermVariantProduct
- | TermVariantRecord
- | TermVariantSet
- | TermVariantSum
- | TermVariantTyped
- | TermVariantUnion
- | TermVariantVariable
- | TermVariantWrap
- _TermVariant :: Name
- _TermVariant_annotated :: Name
- _TermVariant_application :: Name
- _TermVariant_function :: Name
- _TermVariant_let :: Name
- _TermVariant_list :: Name
- _TermVariant_literal :: Name
- _TermVariant_map :: Name
- _TermVariant_optional :: Name
- _TermVariant_product :: Name
- _TermVariant_record :: Name
- _TermVariant_set :: Name
- _TermVariant_sum :: Name
- _TermVariant_typed :: Name
- _TermVariant_union :: Name
- _TermVariant_variable :: Name
- _TermVariant_wrap :: Name
- data TypeVariant
- _TypeVariant :: Name
- _TypeVariant_annotated :: Name
- _TypeVariant_application :: Name
- _TypeVariant_function :: Name
- _TypeVariant_lambda :: Name
- _TypeVariant_list :: Name
- _TypeVariant_literal :: Name
- _TypeVariant_map :: Name
- _TypeVariant_optional :: Name
- _TypeVariant_product :: Name
- _TypeVariant_record :: Name
- _TypeVariant_set :: Name
- _TypeVariant_sum :: Name
- _TypeVariant_union :: Name
- _TypeVariant_variable :: Name
- _TypeVariant_wrap :: Name
Documentation
A disjoint union between a left
type and a right
type
Constructors
EitherLeft a | |
EitherRight b |
Instances
(Read a, Read b) => Read (Either_ a b) Source # | |
(Show a, Show b) => Show (Either_ a b) Source # | |
(Eq a, Eq b) => Eq (Either_ a b) Source # | |
(Ord a, Ord b) => Ord (Either_ a b) Source # | |
Defined in Hydra.Mantle |
_Either_left :: Name Source #
_Either_right :: Name Source #
data EliminationVariant Source #
The identifier of an elimination constructor
Constructors
EliminationVariantList | |
EliminationVariantOptional | |
EliminationVariantProduct | |
EliminationVariantRecord | |
EliminationVariantUnion | |
EliminationVariantWrap |
Instances
data FunctionVariant Source #
The identifier of a function constructor
Instances
Read FunctionVariant Source # | |
Defined in Hydra.Mantle Methods readsPrec :: Int -> ReadS FunctionVariant # readList :: ReadS [FunctionVariant] # | |
Show FunctionVariant Source # | |
Defined in Hydra.Mantle Methods showsPrec :: Int -> FunctionVariant -> ShowS # show :: FunctionVariant -> String # showList :: [FunctionVariant] -> ShowS # | |
Eq FunctionVariant Source # | |
Defined in Hydra.Mantle Methods (==) :: FunctionVariant -> FunctionVariant -> Bool # (/=) :: FunctionVariant -> FunctionVariant -> Bool # | |
Ord FunctionVariant Source # | |
Defined in Hydra.Mantle Methods compare :: FunctionVariant -> FunctionVariant -> Ordering # (<) :: FunctionVariant -> FunctionVariant -> Bool # (<=) :: FunctionVariant -> FunctionVariant -> Bool # (>) :: FunctionVariant -> FunctionVariant -> Bool # (>=) :: FunctionVariant -> FunctionVariant -> Bool # max :: FunctionVariant -> FunctionVariant -> FunctionVariant # min :: FunctionVariant -> FunctionVariant -> FunctionVariant # |
data LiteralVariant Source #
The identifier of a literal constructor
Constructors
LiteralVariantBinary | |
LiteralVariantBoolean | |
LiteralVariantFloat | |
LiteralVariantInteger | |
LiteralVariantString |
Instances
Read LiteralVariant Source # | |
Defined in Hydra.Mantle Methods readsPrec :: Int -> ReadS LiteralVariant # readList :: ReadS [LiteralVariant] # | |
Show LiteralVariant Source # | |
Defined in Hydra.Mantle Methods showsPrec :: Int -> LiteralVariant -> ShowS # show :: LiteralVariant -> String # showList :: [LiteralVariant] -> ShowS # | |
Eq LiteralVariant Source # | |
Defined in Hydra.Mantle Methods (==) :: LiteralVariant -> LiteralVariant -> Bool # (/=) :: LiteralVariant -> LiteralVariant -> Bool # | |
Ord LiteralVariant Source # | |
Defined in Hydra.Mantle Methods 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
Constructors
PrecisionArbitrary | |
PrecisionBits Int |
Instances
Read Precision Source # | |
Show Precision Source # | |
Eq Precision Source # | |
Ord Precision Source # | |
_Precision :: Name Source #
data TermVariant Source #
The identifier of a term expression constructor
Constructors
Instances
Read TermVariant Source # | |
Defined in Hydra.Mantle Methods readsPrec :: Int -> ReadS TermVariant # readList :: ReadS [TermVariant] # readPrec :: ReadPrec TermVariant # readListPrec :: ReadPrec [TermVariant] # | |
Show TermVariant Source # | |
Defined in Hydra.Mantle Methods showsPrec :: Int -> TermVariant -> ShowS # show :: TermVariant -> String # showList :: [TermVariant] -> ShowS # | |
Eq TermVariant Source # | |
Defined in Hydra.Mantle | |
Ord TermVariant Source # | |
Defined in Hydra.Mantle Methods 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 TypeVariant Source #
The identifier of a type constructor
Constructors
Instances
Read TypeVariant Source # | |
Defined in Hydra.Mantle Methods readsPrec :: Int -> ReadS TypeVariant # readList :: ReadS [TypeVariant] # readPrec :: ReadPrec TypeVariant # readListPrec :: ReadPrec [TypeVariant] # | |
Show TypeVariant Source # | |
Defined in Hydra.Mantle Methods showsPrec :: Int -> TypeVariant -> ShowS # show :: TypeVariant -> String # showList :: [TypeVariant] -> ShowS # | |
Eq TypeVariant Source # | |
Defined in Hydra.Mantle | |
Ord TypeVariant Source # | |
Defined in Hydra.Mantle Methods 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 #