Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Limes s p t n m a where
- LimesProjective :: Cone s Projective t n m a -> (Cone s Projective t n m a -> a) -> Limes s Projective t n m a
- LimesInjective :: Cone s Injective t n m a -> (Cone s Injective t n m a -> a) -> Limes s Injective t n m a
- universalPoint :: Limes s p t n m a -> Point a
- universalCone :: Limes s p t n m a -> Cone s p t n m a
- universalShell :: Limes s p t n m a -> FinList n a
- universalFactor :: Limes s p t n m a -> Cone s p t n m a -> a
- diagram :: Limes s p t n m a -> Diagram t n m a
- lmDiagramTypeRefl :: Limes s p t n m a -> Dual (Dual t) :~: t
- eligibleCone :: Oriented a => Limes s p t n m a -> Cone s p t n m a -> Bool
- eligibleFactor :: Limes s p t n m a -> Cone s p t n m a -> a -> Bool
- lmMap :: IsoOrt s h => h a b -> Limes s p t n m a -> Limes s p t n m b
- lmToOp :: LimesDuality s f g a -> f a -> g (Op a)
- lmFromOp :: LimesDuality s f g a -> g (Op a) -> f a
- data LimesDuality s f g a where
- LimesDuality :: ConeStruct s a -> (f a :~: Limes s p t n m a) -> (g (Op a) :~: Dual (Limes s p t n m a)) -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> LimesDuality s f g a
- coLimes :: ConeStruct s a -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> Limes s p t n m a -> Dual (Limes s p t n m a)
- coLimesInv :: ConeStruct s a -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> Dual (Limes s p t n m a) -> Limes s p t n m a
- lmFromOpOp :: ConeStruct s a -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> Limes s p t n m (Op (Op a)) -> Limes s p t n m a
- lmToPrjOrnt :: (Entity p, a ~ Orientation p) => p -> Diagram t n m a -> Limes Mlt Projective t n m a
- lmFromInjOrnt :: (Entity p, a ~ Orientation p) => p -> Diagram t n m a -> Limes Mlt Injective t n m a
- relLimes :: ConeStruct s a -> XOrtPerspective p a -> Limes s p t n m a -> Statement
- data LimesException = ConeNotEligible String
Limes
data Limes s p t n m a where Source #
limes of a diagram, i.e. a distinguished cone over a given diagram having the following universal property
Property Let a
be a Multiplicative
structure and
u
in
then holds:
Let Limes
s p t n m al =
inuniversalCone
u
l
isvalid
.
.eligibleCone
u l
.eligibleFactor
u l (one
(tip
l))For all
c
in
withCone
s p t n m a
holds: LeteligibleCone
u cf =
inuniversalFactor
u cf
isvalid
.
.eligibleFactor
u c f- For all
x
ina
with
holds:eligibleFactor
u c xx
.==
f
Note
- As the function
for a given limesuniversalFactor
ll
is uniquely determined by the underlying cone ofl
, it is permissible to test equality of two limits just by there underling cones. In every computation equal limits can be safely replaced by each other. - It is not required that the evaluation of universal factor on a non eligible cone yield an exception! The implementation of the general algorithms for limits do not check for eligibility.
LimesProjective :: Cone s Projective t n m a -> (Cone s Projective t n m a -> a) -> Limes s Projective t n m a | |
LimesInjective :: Cone s Injective t n m a -> (Cone s Injective t n m a -> a) -> Limes s Injective t n m a |
Instances
IsoMultiplicative h => Applicative1 h (Limes Mlt p t n m) Source # | |
Oriented a => Show (Limes s p t n m a) Source # | |
Oriented a => Eq (Limes s p t n m a) Source # | |
(Distributive a, XStandardOrtPerspective p a, Typeable p, Typeable t, Typeable n, Typeable m) => Validable (Limes Dst p t n m a) Source # | |
(Multiplicative a, XStandardOrtPerspective p a) => Validable (Limes Mlt p t n m a) Source # | |
(Distributive a, XStandardOrtPerspective p a, Typeable p, Typeable t, Typeable n, Typeable m) => Entity (Limes Dst p t n m a) Source # | |
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 # | |
Defined in OAlg.Limes.Definition | |
type Dual (Limes s p t n m a :: Type) Source # | |
universalPoint :: Limes s p t n m a -> Point a Source #
the universal point of a limes, i.e. the tip of the universal cone.
universalCone :: Limes s p t n m a -> Cone s p t n m a Source #
the underlying universal cone of a limes.
universalShell :: Limes s p t n m a -> FinList n a Source #
the shell of the universal cone.
universalFactor :: Limes s p t n m a -> Cone s p t n m a -> a Source #
the universal factor of a Limes
l
to a given eligible cone.
Property Let l
be in
then holds:
For all Limes
s p t n m ac
in
with Cone
s p t n m a
holds: eligibleCone
l c
.eligibleFactor
l c (universalFactor
l c)
lmDiagramTypeRefl :: Limes s p t n m a -> Dual (Dual t) :~: t Source #
reflexivity of the underlying diagram type.
eligibleFactor :: Limes s p t n m a -> Cone s p t n m a -> a -> Bool Source #
eligibility of a factor with respect to a limes and a cone.
Property Let u
be in
,
Limes
s p t n m ac
in
with Cone
s p t n m a
and eligibleCone
u cx
in a
then holds:
- If
u
matches
then holds:LimesProjective
l _
is true if and only ifeligibleFactor
u c x
is true.cnEligibleFactor
x c l - If
u
matches
then holds:LimesInjective
l _
is true if and only ifeligibleFactor
u c x
is true.cnEligibleFactor
x l c
lmMap :: IsoOrt s h => h a b -> Limes s p t n m a -> Limes s p t n m b Source #
mapping between limits.
Duality
data LimesDuality s f g a where Source #
Op
-duality between limes types.
LimesDuality :: ConeStruct s a -> (f a :~: Limes s p t n m a) -> (g (Op a) :~: Dual (Limes s p t n m a)) -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> LimesDuality s f g a |
coLimes :: ConeStruct s a -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> Limes s p t n m a -> Dual (Limes s p t n m a) Source #
the co limes with its inverse coLimesInv
.
coLimesInv :: ConeStruct s a -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> Dual (Limes s p t n m a) -> Limes s p t n m a Source #
the inverse of coLimes
.
lmFromOpOp :: ConeStruct s a -> (Dual (Dual p) :~: p) -> (Dual (Dual t) :~: t) -> Limes s p t n m (Op (Op a)) -> Limes s p t n m a Source #
Construction
lmToPrjOrnt :: (Entity p, a ~ Orientation p) => p -> Diagram t n m a -> Limes Mlt Projective t n m a Source #
projective limes on oriented structures.
lmFromInjOrnt :: (Entity p, a ~ Orientation p) => p -> Diagram t n m a -> Limes Mlt Injective t n m a Source #
injective limes on oriented structures.
Proposition
relLimes :: ConeStruct s a -> XOrtPerspective p a -> Limes s p t n m a -> Statement Source #
validity of a Limes
.
Exception
data LimesException Source #
limes exceptions which are sub exceptions from SomeOAlgException
.
Instances
Exception LimesException Source # | |
Defined in OAlg.Limes.Definition | |
Show LimesException Source # | |
Defined in OAlg.Limes.Definition showsPrec :: Int -> LimesException -> ShowS # show :: LimesException -> String # showList :: [LimesException] -> ShowS # | |
Eq LimesException Source # | |
Defined in OAlg.Limes.Definition (==) :: LimesException -> LimesException -> Bool # (/=) :: LimesException -> LimesException -> Bool # |