| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Mantle
Description
A set of types which supplement hydra/core with variants and accessors
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 TermAccessor
- = TermAccessorAnnotatedSubject
- | TermAccessorApplicationFunction
- | TermAccessorApplicationArgument
- | TermAccessorLambdaBody
- | TermAccessorListFold
- | TermAccessorOptionalCasesNothing
- | TermAccessorOptionalCasesJust
- | TermAccessorUnionCasesDefault
- | TermAccessorUnionCasesBranch Name
- | TermAccessorLetEnvironment
- | TermAccessorLetBinding Name
- | TermAccessorListElement Int
- | TermAccessorMapKey Int
- | TermAccessorMapValue Int
- | TermAccessorOptionalTerm
- | TermAccessorProductTerm Int
- | TermAccessorRecordField Name
- | TermAccessorSetElement Int
- | TermAccessorSumTerm
- | TermAccessorTypeAbstractionBody
- | TermAccessorTypeApplicationTerm
- | TermAccessorTypedTerm
- | TermAccessorInjectionTerm
- | TermAccessorWrappedTerm
- _TermAccessor :: Name
- _TermAccessor_annotatedSubject :: Name
- _TermAccessor_applicationFunction :: Name
- _TermAccessor_applicationArgument :: Name
- _TermAccessor_lambdaBody :: Name
- _TermAccessor_listFold :: Name
- _TermAccessor_optionalCasesNothing :: Name
- _TermAccessor_optionalCasesJust :: Name
- _TermAccessor_unionCasesDefault :: Name
- _TermAccessor_unionCasesBranch :: Name
- _TermAccessor_letEnvironment :: Name
- _TermAccessor_letBinding :: Name
- _TermAccessor_listElement :: Name
- _TermAccessor_mapKey :: Name
- _TermAccessor_mapValue :: Name
- _TermAccessor_optionalTerm :: Name
- _TermAccessor_productTerm :: Name
- _TermAccessor_recordField :: Name
- _TermAccessor_setElement :: Name
- _TermAccessor_sumTerm :: Name
- _TermAccessor_typeAbstractionBody :: Name
- _TermAccessor_typeApplicationTerm :: Name
- _TermAccessor_typedTerm :: Name
- _TermAccessor_injectionTerm :: Name
- _TermAccessor_wrappedTerm :: Name
- data TermVariant
- = TermVariantAnnotated
- | TermVariantApplication
- | TermVariantFunction
- | TermVariantLet
- | TermVariantList
- | TermVariantLiteral
- | TermVariantMap
- | TermVariantOptional
- | TermVariantProduct
- | TermVariantRecord
- | TermVariantSet
- | TermVariantSum
- | TermVariantTypeAbstraction
- | TermVariantTypeApplication
- | 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_typeAbstraction :: Name
- _TermVariant_typeApplication :: Name
- _TermVariant_typed :: Name
- _TermVariant_union :: Name
- _TermVariant_variable :: Name
- _TermVariant_wrap :: Name
- data TypeConstraint = TypeConstraint {}
- _TypeConstraint :: Name
- _TypeConstraint_left :: Name
- _TypeConstraint_right :: Name
- _TypeConstraint_context :: 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 TermAccessor Source #
A function which maps from a term to a particular immediate subterm
Constructors
Instances
| Read TermAccessor Source # | |
Defined in Hydra.Mantle Methods readsPrec :: Int -> ReadS TermAccessor # readList :: ReadS [TermAccessor] # | |
| Show TermAccessor Source # | |
Defined in Hydra.Mantle Methods showsPrec :: Int -> TermAccessor -> ShowS # show :: TermAccessor -> String # showList :: [TermAccessor] -> ShowS # | |
| Eq TermAccessor Source # | |
Defined in Hydra.Mantle | |
| Ord TermAccessor Source # | |
Defined in Hydra.Mantle Methods compare :: TermAccessor -> TermAccessor -> Ordering # (<) :: TermAccessor -> TermAccessor -> Bool # (<=) :: TermAccessor -> TermAccessor -> Bool # (>) :: TermAccessor -> TermAccessor -> Bool # (>=) :: TermAccessor -> TermAccessor -> Bool # max :: TermAccessor -> TermAccessor -> TermAccessor # min :: TermAccessor -> TermAccessor -> TermAccessor # | |
_TermAccessor :: 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 TypeConstraint Source #
An assertion that two types can be unified into a single type
Constructors
| TypeConstraint | |
Fields | |
Instances
| Read TypeConstraint Source # | |
Defined in Hydra.Mantle Methods readsPrec :: Int -> ReadS TypeConstraint # readList :: ReadS [TypeConstraint] # | |
| Show TypeConstraint Source # | |
Defined in Hydra.Mantle Methods showsPrec :: Int -> TypeConstraint -> ShowS # show :: TypeConstraint -> String # showList :: [TypeConstraint] -> ShowS # | |
| Eq TypeConstraint Source # | |
Defined in Hydra.Mantle Methods (==) :: TypeConstraint -> TypeConstraint -> Bool # (/=) :: TypeConstraint -> TypeConstraint -> Bool # | |
| Ord TypeConstraint Source # | |
Defined in Hydra.Mantle Methods compare :: TypeConstraint -> TypeConstraint -> Ordering # (<) :: TypeConstraint -> TypeConstraint -> Bool # (<=) :: TypeConstraint -> TypeConstraint -> Bool # (>) :: TypeConstraint -> TypeConstraint -> Bool # (>=) :: TypeConstraint -> TypeConstraint -> Bool # max :: TypeConstraint -> TypeConstraint -> TypeConstraint # min :: TypeConstraint -> TypeConstraint -> TypeConstraint # | |
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 #