Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- class (Entity f, Entity (Root f)) => Fibred f where
- data Fbr
- class Transformable s Fbr => ForgetfulFbr s
- class (Fibred d, Oriented d, Root d ~ Orientation (Point d)) => FibredOriented d
- data FbrOrt
- class (ForgetfulFbr s, ForgetfulOrt s, Transformable s FbrOrt) => ForgetfulFbrOrt s
- class Ord (Root f) => OrdRoot f
- class Singleton (Root f) => TotalRoot f
- data Sheaf f = Sheaf (Root f) [f]
Fibred
class (Entity f, Entity (Root f)) => Fibred f where Source #
types with a Fibred
structure. An entity of a Fibred
structure will be
called a stalk.
Note
- On should accept the
default
forroot
only forFibredOriented
structures! - For
Distributive
structures the only thing to be implemented is theRoot
type and should be defined as
where--Root
d =Orientation
pp =
(see the default implementation ofPoint
droot
).
Nothing
the root
of a stalk in f
.
Instances
type representing the class of Fibred
structures.
Instances
ForgetfulTyp Fbr Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulFbr Fbr Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
Transformable Abl Fbr Source # | |
Transformable Add Fbr Source # | |
Transformable Dst Fbr Source # | |
Transformable Fbr Ent Source # | |
Transformable Fbr Typ Source # | |
Transformable FbrOrt Fbr Source # | |
(Semiring r, Commutative r) => EmbeddableMorphism (HomSymbol r) Fbr Source # | |
Defined in OAlg.Entity.Matrix.Vector | |
EmbeddableMorphism h Fbr => EmbeddableMorphism (OpHom h) Fbr Source # | |
Defined in OAlg.Hom.Oriented.Definition | |
Transformable (Alg k) Fbr Source # | |
Transformable (Vec k) Fbr Source # | |
type Hom Fbr h Source # | |
Defined in OAlg.Hom.Fibred | |
type Structure Fbr x Source # | |
Defined in OAlg.Structure.Fibred.Definition |
class Transformable s Fbr => ForgetfulFbr s Source #
transformable to Fibred
structure.
Instances
ForgetfulFbr Abl Source # | |
Defined in OAlg.Structure.Additive.Definition | |
ForgetfulFbr Add Source # | |
Defined in OAlg.Structure.Additive.Definition | |
ForgetfulFbr Dst Source # | |
Defined in OAlg.Structure.Distributive.Definition | |
ForgetfulFbr Fbr Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulFbr FbrOrt Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulFbr (Alg k) Source # | |
Defined in OAlg.Structure.Algebraic.Definition | |
ForgetfulFbr (Vec k) Source # | |
Defined in OAlg.Structure.Vectorial.Definition |
Fibred Oriented
class (Fibred d, Oriented d, Root d ~ Orientation (Point d)) => FibredOriented d Source #
Fibred
and Oriented
structure with matching root
and orientation
.
Property Let d
be a FibredOriented
structure, then holds:
For all s
in d
holds:
.root
s ==
orientation
s
Note FibredOriented
structures are required for
Distributive
structures.
Instances
FibredOriented N Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
FibredOriented Q Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
FibredOriented Z Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
FibredOriented N' Source # | |
Defined in OAlg.Entity.Natural | |
FibredOriented W' Source # | |
Defined in OAlg.Entity.Natural | |
FibredOriented Integer Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
FibredOriented () Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
FibredOriented Int Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
FibredOriented f => FibredOriented (Op f) Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
(Additive x, FibredOriented x) => FibredOriented (Matrix x) Source # | |
Defined in OAlg.Entity.Matrix.Definition | |
Entity p => FibredOriented (Orientation p) Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
(Distributive a, Typeable t, Typeable n, Typeable m) => FibredOriented (Transformation t n m a) Source # | |
Defined in OAlg.Entity.Diagram.Transformation |
type representing the class of FibredOriented
structures.
Instances
ForgetfulTyp FbrOrt Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulFbr FbrOrt Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulFbrOrt FbrOrt Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulOrt FbrOrt Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
Transformable Dst FbrOrt Source # | |
Transformable FbrOrt Ent Source # | |
Transformable FbrOrt Typ Source # | |
Transformable FbrOrt Fbr Source # | |
Transformable FbrOrt Ort Source # | |
EmbeddableMorphism h FbrOrt => EmbeddableMorphism (OpHom h) FbrOrt Source # | |
Defined in OAlg.Hom.Oriented.Definition | |
Transformable (Alg k) FbrOrt Source # | |
type Hom FbrOrt h Source # | |
Defined in OAlg.Hom.Fibred | |
type Structure FbrOrt x Source # | |
Defined in OAlg.Structure.Fibred.Definition |
class (ForgetfulFbr s, ForgetfulOrt s, Transformable s FbrOrt) => ForgetfulFbrOrt s Source #
transformable to FibredOriented
structure.
Instances
ForgetfulFbrOrt Dst Source # | |
Defined in OAlg.Structure.Distributive.Definition | |
ForgetfulFbrOrt FbrOrt Source # | |
Defined in OAlg.Structure.Fibred.Definition | |
ForgetfulFbrOrt (Alg k) Source # | |
Defined in OAlg.Structure.Algebraic.Definition |
Spezial classes
class Ord (Root f) => OrdRoot f Source #
type where the associated root type is ordered.
Note Helper class to circumvent undecidable instances.
Instances
OrdRoot (R a) Source # | |
Defined in OAlg.Entity.Sum.SumSymbol |
Sheaf
a list in a Fibred
structure having all the same root
.
Definition Let f
be a Fibred
structure and s =
a
sheaf in Sheaf
r [t 0 .. t (n-1)]
, then Sheaf
fs
is valid
if and only if
furthermore n
is called the length of s
.
If two sheafs have the same root
then there stalks can be composed - via (
-
to a new sheaf having the same ++
)root
. But as (
is not commutative they
are equipped with a ++
)Multiplicative
structure.