Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
introducing the idiom of Structure
s as parameterized constraints.
Synopsis
- type family Structure s x :: Constraint
- data Struct s x where
- class Transformable s t where
- class Transformable1 f s where
- class Transformable1 Op s => TransformableOp s
- class Transformable s Typ => ForgetfulTyp s
- data Typ
- data Ord'
Structure
type family Structure s x :: Constraint Source #
parameterized constraint for a type x
.
Instances
data Struct s x where Source #
attest that the type x
admits the constrains given by the parameter s
.
Instances
Transformable s Typ => TestEquality (Struct s :: Type -> Type) Source # | |
Defined in OAlg.Structure.Definition | |
Eq1 (Struct s) Source # | |
Show1 (Struct s) Source # | |
Singular (Struct s) Source # | |
Defined in OAlg.Structure.Definition | |
Validable1 (Struct s) Source # | |
Show (Struct s x) Source # | |
Eq (Struct s x) Source # | |
Validable (Struct s x) Source # | |
Transformable
class Transformable s t where Source #
transforming structural attests.
Instances
class Transformable1 f s where Source #
transforming structural attests.
Instances
class Transformable1 Op s => TransformableOp s Source #
helper class to avoid undecidable instances.
Instances
TransformableOp Dst Source # | |
Defined in OAlg.Structure.Distributive.Definition | |
TransformableOp Mlt Source # | |
Defined in OAlg.Structure.Multiplicative.Definition | |
TransformableOp Ort Source # | |
Defined in OAlg.Structure.Oriented.Definition |
class Transformable s Typ => ForgetfulTyp s Source #
helper class to avoid undecidable instances.
Instances
ForgetfulTyp Abl Source # | |
Defined in OAlg.Structure.Additive.Definition | |
ForgetfulTyp Add Source # | |
Defined in OAlg.Structure.Additive.Definition | |
ForgetfulTyp Dst Source # | |
Defined in OAlg.Structure.Distributive.Definition | |
ForgetfulTyp Fbr Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulTyp FbrOrt Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulTyp Mlt Source # | |
Defined in OAlg.Structure.Multiplicative.Definition | |
ForgetfulTyp Ort Source # | |
Defined in OAlg.Structure.Oriented.Definition | |
ForgetfulTyp (Alg k) Source # | |
Defined in OAlg.Structure.Algebraic.Definition | |
ForgetfulTyp (Vec k) Source # | |
Defined in OAlg.Structure.Vectorial.Definition |
Some Structure Types
Typeable
structures.
Instances
EmbeddableMorphism GLApp Typ Source # | |
Defined in OAlg.Entity.Matrix.GeneralLinearGroup | |
EmbeddableMorphism TrApp Typ Source # | |
Defined in OAlg.Entity.Matrix.GeneralLinearGroup | |
Transformable Abl Typ Source # | |
Transformable Add Typ Source # | |
Transformable Dst Typ Source # | |
Transformable Fbr Typ Source # | |
Transformable FbrOrt Typ Source # | |
Transformable Mlt Typ Source # | |
Transformable Ort Typ Source # | |
(Semiring r, Commutative r) => EmbeddableMorphism (HomSymbol r) Typ Source # | |
Defined in OAlg.Entity.Matrix.Vector | |
EmbeddableMorphism (SliceFactorDrop s) Typ Source # | |
Defined in OAlg.Entity.Slice.Definition | |
EmbeddableMorphism h Typ => EmbeddableMorphism (OpHom h) Typ Source # | |
Defined in OAlg.Hom.Oriented.Definition | |
Transformable (Alg k) Typ Source # | |
Transformable (Vec k) Typ Source # | |
(Multiplicative c, Sliced i c) => EmbeddableMorphism (SliceCokernelKernel i c) Typ Source # | |
Defined in OAlg.Entity.Slice.Adjunction | |
type Structure Typ x Source # | |
Defined in OAlg.Structure.Definition |