oalg-base-1.1.4.0: Algebraic structures on oriented entities and limits as a tool kit to solve algebraic problems.
Copyright(c) Erich Gut
LicenseBSD3
Maintainerzerich.gut@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

OAlg.Entity.Definition

Description

definition of entities. All algebraic structures defined here are based on them. They are showable, distinguishable, validable and typeable.

Synopsis

Entity

class (Show a, Eq a, Validable a, Typeable a) => Entity a Source #

entity.

Instances

Instances details
Entity N Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity Q Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity Z Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity Symbol Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity Empty Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity N' Source # 
Instance details

Defined in OAlg.Entity.Natural

Entity W' Source # 
Instance details

Defined in OAlg.Entity.Natural

Entity Integer Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity () Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity Char Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity Int Source # 
Instance details

Defined in OAlg.Entity.Definition

(EmbeddableMorphismTyp m, Entity2 m) => Entity (SomeMorphism m) Source # 
Instance details

Defined in OAlg.Category.Unify

Typeable m => Entity (SomeObjectClass m) Source # 
Instance details

Defined in OAlg.Category.Unify

Entity x => Entity (Op x) Source # 
Instance details

Defined in OAlg.Entity.Definition

(Additive x, FibredOriented x) => Entity (Matrix x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Definition

Galoisian x => Entity (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Oriented x => Entity (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Typeable x => Entity (Transformation x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Oriented x => Entity (ColTrafo x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Distributive k => Entity (DiagonalForm k) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Number k => Entity (DiagonalFormStrictPositive k) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Oriented a => Entity (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Semiring r => Entity (Vector r) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Vector

Entity x => Entity (ProductSymbol x) Source # 
Instance details

Defined in OAlg.Entity.Product.ProductSymbol

Entity x => Entity (U x) Source # 
Instance details

Defined in OAlg.Entity.Product.ProductSymbol

(Entity i, Ord i) => Entity (Permutation i) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Permutation

(Entity i, Ord i) => Entity (PermutationForm i) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Permutation

(Entity x, Ord x) => Entity (Set x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Set

Entity a => Entity (R a) Source # 
Instance details

Defined in OAlg.Entity.Sum.SumSymbol

Fibred f => Entity (Sheaf f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Multiplicative c => Entity (Inv c) Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Entity p => Entity (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Oriented q => Entity (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Entity a => Entity [a] Source # 
Instance details

Defined in OAlg.Entity.Definition

(Typeable n, Typeable m) => Entity (Quiver n m) Source # 
Instance details

Defined in OAlg.Entity.Diagram.Quiver

(Typeable n, Entity a) => Entity (FinList n a) Source # 
Instance details

Defined in OAlg.Entity.FinList

(Oriented x, Typeable p) => Entity (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

(Entity x, Entity i, Ord i) => Entity (Col i x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

(Entity x, Entity j, Ord j) => Entity (Row j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

(Typeable x, Typeable y) => Entity (GLApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

(Typeable x, Typeable y) => Entity (TrApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

(Oriented a, Integral r) => Entity (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

(Oriented a, Number r) => Entity (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

(Entity x, Entity i, Ord i) => Entity (Graph i x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Graph

(Entity x, Entity i, Ord i) => Entity (PSequence i x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.PSequence

(Typeable c, Typeable k) => Entity (Free k c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Free

(Entity a, Entity r) => Entity (LinearCombination r a) Source # 
Instance details

Defined in OAlg.Entity.Sum.Definition

(Fibred a, Semiring r, Commutative r) => Entity (Sum r a) Source # 
Instance details

Defined in OAlg.Entity.Sum.Definition

(Fibred a, Semiring r, Commutative r) => Entity (SumForm r a) Source # 
Instance details

Defined in OAlg.Entity.Sum.Definition

(Semiring r, Commutative r, Entity a) => Entity (SumSymbol r a) Source # 
Instance details

Defined in OAlg.Entity.Sum.SumSymbol

(KnownNat b, Entity r) => Entity (Digits b r) Source # 
Instance details

Defined in OAlg.Structure.Number.Definition

(Entity a, Entity b) => Entity (a, b) Source # 
Instance details

Defined in OAlg.Entity.Definition

(Entity x, Entity i, Entity j, Ord i, Ord j) => Entity (Entries i j x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Entries

(Semiring r, Typeable x, Typeable y) => Entity (HomSymbol r x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Vector

(Oriented c, Sliced i c, Typeable s) => Entity (Slice s i c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

(Multiplicative c, Sliced i c, Typeable s) => Entity (SliceFactor s i c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

(Typeable s, Typeable x, Typeable y) => Entity (SliceFactorDrop s x y) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

(Typeable s, Typeable a, Typeable b) => Entity (HomOp s a b) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(Typeable s, Typeable a, Typeable b) => Entity (IdHom s a b) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(ForgetfulTyp s, Typeable s, Typeable a, Typeable b) => Entity (IsoOp s a b) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(Multiplicative a, Typeable n) => Entity (FactorChain 'From n a) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

(Multiplicative a, Typeable n) => Entity (FactorChain 'To n a) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

(Oriented a, Typeable t, Typeable n, Typeable m) => Entity (Diagram t n m a) Source # 
Instance details

Defined in OAlg.Entity.Diagram.Definition

(Multiplicative a, Typeable t, Typeable n, Typeable m) => Entity (Transformation t n m a) Source # 
Instance details

Defined in OAlg.Entity.Diagram.Transformation

(Typeable i, Typeable c, Typeable x, Typeable y) => Entity (SliceCokernelKernel i c x y) Source # 
Instance details

Defined in OAlg.Entity.Slice.Adjunction

(ForgetfulTyp s, Typeable f, Typeable s, Typeable a, Typeable b) => Entity (IsoOpMap f s a b) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(Typeable f, Typeable s, Typeable a, Typeable b) => Entity (OpMap f s a b) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(Typeable s, Typeable p, Typeable t, Typeable n, Typeable m, Typeable a) => Entity (Cone s p t n m a) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

(Distributive a, Typeable s, Typeable p, Typeable t, Typeable n, Typeable m) => Entity (ConeZeroHead s p t n ('S m) a) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

(Distributive a, XStandardOrtPerspective p a, Typeable p, Typeable t, Typeable n, Typeable m) => Entity (Limes Dst p t n m a) Source # 
Instance details

Defined in OAlg.Limes.Definition

(Multiplicative a, XStandardOrtPerspective p a, Typeable p, Typeable t, Typeable n, Typeable m) => Entity (Limes Mlt p t n m a) Source # 
Instance details

Defined in OAlg.Limes.Definition

data Ent Source #

indexing Entitys.

Instances

Instances details
Transformable Abl Ent Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

Methods

tau :: Struct Abl x -> Struct Ent x Source #

Transformable Add Ent Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

Methods

tau :: Struct Add x -> Struct Ent x Source #

Transformable Dst Ent Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

Methods

tau :: Struct Dst x -> Struct Ent x Source #

Transformable Fbr Ent Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

tau :: Struct Fbr x -> Struct Ent x Source #

Transformable FbrOrt Ent Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

tau :: Struct FbrOrt x -> Struct Ent x Source #

Transformable Mlt Ent Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Methods

tau :: Struct Mlt x -> Struct Ent x Source #

Transformable Ort Ent Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

tau :: Struct Ort x -> Struct Ent x Source #

Transformable (Alg k) Ent Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

Methods

tau :: Struct (Alg k) x -> Struct Ent x Source #

Transformable (Vec k) Ent Source # 
Instance details

Defined in OAlg.Structure.Vectorial.Definition

Methods

tau :: Struct (Vec k) x -> Struct Ent x Source #

type Structure Ent x Source # 
Instance details

Defined in OAlg.Entity.Definition

type Structure Ent x = Entity x

Entity1

class (Show1 a, Eq1 a, Validable1 a, Typeable a) => Entity1 a Source #

entity for parameterized types.

Instances

Instances details
Entity1 (Proxy :: Type -> Type) Source # 
Instance details

Defined in OAlg.Entity.Definition

Typeable k => Entity1 (Free k) Source # 
Instance details

Defined in OAlg.Entity.Slice.Free

Entity2

class (Show2 h, Eq2 h, Validable2 h, Typeable h) => Entity2 h Source #

entity for two parameterized types.

Instances

Instances details
Entity2 Empty2 Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity2 GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Entity2 TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

(Entity2 h, EmbeddableMorphismTyp h) => Entity2 (Path h) Source # 
Instance details

Defined in OAlg.Category.Path

Semiring r => Entity2 (HomSymbol r) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Vector

Typeable s => Entity2 (SliceFactorDrop s) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

Typeable s => Entity2 (HomOp s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Typeable s => Entity2 (IdHom s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(ForgetfulTyp s, Typeable s) => Entity2 (IsoOp s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Entity2 h => Entity2 (OpHom h) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(Entity2 h, Typeable t) => Entity2 (Forget t h) Source # 
Instance details

Defined in OAlg.Entity.Definition

(Entity2 f, Entity2 g) => Entity2 (Either2 f g) Source # 
Instance details

Defined in OAlg.Entity.Definition

(Typeable i, Typeable c) => Entity2 (SliceCokernelKernel i c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Adjunction

(ForgetfulTyp s, Typeable f, Typeable s) => Entity2 (IsoOpMap f s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(Typeable f, Typeable s) => Entity2 (OpMap f s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Basic Entities

Empty

data Empty Source #

the empty entity.

Instances

Instances details
Show Empty Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Eq Empty Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

(==) :: Empty -> Empty -> Bool #

(/=) :: Empty -> Empty -> Bool #

Ord Empty Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

compare :: Empty -> Empty -> Ordering #

(<) :: Empty -> Empty -> Bool #

(<=) :: Empty -> Empty -> Bool #

(>) :: Empty -> Empty -> Bool #

(>=) :: Empty -> Empty -> Bool #

max :: Empty -> Empty -> Empty #

min :: Empty -> Empty -> Empty #

Validable Empty Source # 
Instance details

Defined in OAlg.Entity.Definition

Entity Empty Source # 
Instance details

Defined in OAlg.Entity.Definition

empty :: Empty -> x Source #

the empty function.

data Empty2 a b Source #

the empty entity2.

Instances

Instances details
Eq2 Empty2 Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

eq2 :: Empty2 x y -> Empty2 x y -> Bool Source #

Show2 Empty2 Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

show2 :: Empty2 a b -> String Source #

Validable2 Empty2 Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

valid2 :: Empty2 x y -> Statement Source #

Entity2 Empty2 Source # 
Instance details

Defined in OAlg.Entity.Definition

Show (Empty2 a b) Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

showsPrec :: Int -> Empty2 a b -> ShowS #

show :: Empty2 a b -> String #

showList :: [Empty2 a b] -> ShowS #

Eq (Empty2 a b) Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

(==) :: Empty2 a b -> Empty2 a b -> Bool #

(/=) :: Empty2 a b -> Empty2 a b -> Bool #

Validable (Empty2 x y) Source # 
Instance details

Defined in OAlg.Entity.Definition

Methods

valid :: Empty2 x y -> Statement Source #

empty2 :: Empty2 a b -> x Source #

the empty function.