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.Limes.KernelsAndCokernels

Description

kernels and cokernels, i.e. limits in a Distributive structure of Diagram (Parallel d) making all arrows zero.

Synopsis

Kernels

type Kernels n = Limits Dst Projective (Parallel LeftToRight) N2 n Source #

kernels for Distributive structures.

kernelFactor :: KernelCone N1 c -> c Source #

the factor of its shell.

kernelDiagram :: Oriented c => c -> KernelDiagram N1 c Source #

the kernel diagram of a given factor.

Construction

kernels :: Distributive a => Kernels N1 a -> Kernels n a Source #

promoting kernels.

kernels0 :: Distributive a => Kernels N0 a Source #

kernels for zero arrows.

kernels1 :: Distributive a => Kernels N1 a -> Kernels (n + 1) a Source #

promoting kernels.

krnEqls :: (Distributive a, Abelian a) => Kernels n a -> Equalizers (n + 1) a Source #

the induced equalizers where its first arrow is zero.

eqlKrns :: Distributive a => Equalizers (n + 1) a -> Kernels n a Source #

the induced kernels given by adjoining a zero arrow as first arrow.

kernelZero :: Distributive c => p c -> Orientation (Point c) -> Kernel N1 c Source #

the kernel of the zero factor given by the orientation, i.e. one

Orientation

kernelsOrnt :: Entity p => p -> Kernels n (Orientation p) Source #

kernels for Orientation.

Cokernels

type Cokernels n = Limits Dst Injective (Parallel RightToLeft) N2 n Source #

cokernels for Distributive structures.

cokernelFactor :: CokernelCone N1 c -> c Source #

the factor of its shell.

cokernelDiagram :: Oriented c => c -> CokernelDiagram N1 c Source #

the cokernel diagram of a given factor.

Construction

cokernels :: Distributive a => Cokernels N1 a -> Cokernels n a Source #

promoting cokernels.

cokernels' :: Distributive a => p n -> Cokernels N1 a -> Cokernels n a Source #

cokernels given by an additional proxy for n.

Orientation

cokernelsOrnt :: Entity p => p -> Cokernels n (Orientation p) Source #

cokernels for Orientation.

Duality

Proposition

prpIsKernel :: Distributive a => Kernel n a -> FinList n a -> a -> Statement Source #

checks if the arrows of the kernel diagram are equal to the given ones and if its shell is equal to the given arrow.

Property Let LimesProjective ('ConeKerenl d k') _ = ker be in Kernel n a, fs in FinList n a and k be in a, then the statement prpIsKernel ker fs k holds if and only if

  1. fs == dgArrows d.
  2. k == k'.

prpIsCokernel :: Distributive a => Cokernel n a -> FinList n a -> a -> Statement Source #

checks if the arrows of the cokernel diagram are equal to the given ones and if its shell is equal to the given arrow.

Property Let LimesInjective ('ConeCokerenl d k') _ = coker be in Cokernel n a, fs in FinList n a and k be in a, then the statement prpIsCokernel coker fs k holds if and only if

  1. fs == dgArrows d.
  2. k == k'.