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.Structure.Fibred.Definition

Description

fibred structures, i.e. type f with an associated root type Root f such that every value in f has a root.

Synopsis

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

  1. On should accept the default for root only for FibredOriented structures!
  2. For Distributive structures the only thing to be implemented is the Root type and should be defined as Root d = Orientation p where-- p = Point d (see the default implementation of root).

Minimal complete definition

Nothing

Associated Types

type Root f Source #

the type of roots.

Methods

root :: f -> Root f Source #

the root of a stalk in f.

default root :: (Root f ~ Orientation (Point f), Oriented f) => f -> Root f Source #

Instances

Instances details
Fibred N Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root N Source #

Methods

root :: N -> Root N Source #

Fibred Q Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root Q Source #

Methods

root :: Q -> Root Q Source #

Fibred Z Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root Z Source #

Methods

root :: Z -> Root Z Source #

Fibred N' Source # 
Instance details

Defined in OAlg.Entity.Natural

Associated Types

type Root N' Source #

Methods

root :: N' -> Root N' Source #

Fibred W' Source # 
Instance details

Defined in OAlg.Entity.Natural

Associated Types

type Root W' Source #

Methods

root :: W' -> Root W' Source #

Fibred Integer Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root Integer Source #

Fibred () Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root () Source #

Methods

root :: () -> Root () Source #

Fibred Int Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root Int Source #

Methods

root :: Int -> Root Int Source #

FibredOriented f => Fibred (Op f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root (Op f) Source #

Methods

root :: Op f -> Root (Op f) Source #

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

Defined in OAlg.Entity.Matrix.Definition

Associated Types

type Root (Matrix x) Source #

Methods

root :: Matrix x -> Root (Matrix x) Source #

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

Defined in OAlg.Entity.Matrix.Vector

Associated Types

type Root (Vector r) Source #

Methods

root :: Vector r -> Root (Vector r) Source #

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

Defined in OAlg.Entity.Sum.SumSymbol

Associated Types

type Root (R a) Source #

Methods

root :: R a -> Root (R a) Source #

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

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root (Sheaf f) Source #

Methods

root :: Sheaf f -> Root (Sheaf f) Source #

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

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root (Orientation p) Source #

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

Defined in OAlg.Entity.Sum.Definition

Associated Types

type Root (Sum r a) Source #

Methods

root :: Sum r a -> Root (Sum r a) Source #

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

Defined in OAlg.Entity.Sum.Definition

Associated Types

type Root (SumForm r a) Source #

Methods

root :: SumForm r a -> Root (SumForm r a) Source #

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

Defined in OAlg.Entity.Sum.SumSymbol

Associated Types

type Root (SumSymbol r a) Source #

Methods

root :: SumSymbol r a -> Root (SumSymbol r a) Source #

(Distributive a, Typeable t, Typeable n, Typeable m) => Fibred (Transformation t n m a) Source # 
Instance details

Defined in OAlg.Entity.Diagram.Transformation

Associated Types

type Root (Transformation t n m a) Source #

Methods

root :: Transformation t n m a -> Root (Transformation t n m a) Source #

data Fbr Source #

type representing the class of Fibred structures.

Instances

Instances details
ForgetfulTyp Fbr Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulFbr Fbr Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Transformable Abl Fbr Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

Methods

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

Transformable Add Fbr Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

Methods

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

Transformable Dst Fbr Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

Methods

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

Transformable Fbr Ent Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

Transformable Fbr Typ Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

Transformable FbrOrt Fbr Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

(Semiring r, Commutative r) => EmbeddableMorphism (HomSymbol r) Fbr Source # 
Instance details

Defined in OAlg.Entity.Matrix.Vector

EmbeddableMorphism h Fbr => EmbeddableMorphism (OpHom h) Fbr Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Transformable (Alg k) Fbr Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

Methods

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

Transformable (Vec k) Fbr Source # 
Instance details

Defined in OAlg.Structure.Vectorial.Definition

Methods

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

type Hom Fbr h Source # 
Instance details

Defined in OAlg.Hom.Fibred

type Hom Fbr h = HomFibred h
type Structure Fbr x Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

type Structure Fbr x = Fibred x

class Transformable s Fbr => ForgetfulFbr s Source #

transformable to Fibred structure.

Instances

Instances details
ForgetfulFbr Abl Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

ForgetfulFbr Add Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

ForgetfulFbr Dst Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

ForgetfulFbr Fbr Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulFbr FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulFbr (Alg k) Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

ForgetfulFbr (Vec k) Source # 
Instance details

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.

data FbrOrt Source #

type representing the class of FibredOriented structures.

Instances

Instances details
ForgetfulTyp FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulFbr FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulFbrOrt FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulOrt FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Transformable Dst FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

Methods

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

Transformable FbrOrt Ent Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

Transformable FbrOrt Typ Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

Transformable FbrOrt Fbr Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

Transformable FbrOrt Ort Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

EmbeddableMorphism h FbrOrt => EmbeddableMorphism (OpHom h) FbrOrt Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Transformable (Alg k) FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

Methods

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

type Hom FbrOrt h Source # 
Instance details

Defined in OAlg.Hom.Fibred

type Structure FbrOrt x Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

class (ForgetfulFbr s, ForgetfulOrt s, Transformable s FbrOrt) => ForgetfulFbrOrt s Source #

transformable to FibredOriented structure.

Instances

Instances details
ForgetfulFbrOrt Dst Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

ForgetfulFbrOrt FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulFbrOrt (Alg k) Source # 
Instance details

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

Instances details
OrdRoot (R a) Source # 
Instance details

Defined in OAlg.Entity.Sum.SumSymbol

class Singleton (Root f) => TotalRoot f Source #

type where the associated root type is a singleton.

Sheaf

data Sheaf f Source #

a list in a Fibred structure having all the same root.

Definition Let f be a Fibred structure and s = Sheaf r [t 0 .. t (n-1)] a sheaf in Sheaf f, then s is valid if and only if

  1. r is valid and t i are valid for all i = 0..n-1.
  2. root (t i) == r for all i = 0..n-1.

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.

Constructors

Sheaf (Root f) [f] 

Instances

Instances details
Foldable Sheaf Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

fold :: Monoid m => Sheaf m -> m #

foldMap :: Monoid m => (a -> m) -> Sheaf a -> m #

foldMap' :: Monoid m => (a -> m) -> Sheaf a -> m #

foldr :: (a -> b -> b) -> b -> Sheaf a -> b #

foldr' :: (a -> b -> b) -> b -> Sheaf a -> b #

foldl :: (b -> a -> b) -> b -> Sheaf a -> b #

foldl' :: (b -> a -> b) -> b -> Sheaf a -> b #

foldr1 :: (a -> a -> a) -> Sheaf a -> a #

foldl1 :: (a -> a -> a) -> Sheaf a -> a #

toList :: Sheaf a -> [a] #

null :: Sheaf a -> Bool #

length :: Sheaf a -> Int #

elem :: Eq a => a -> Sheaf a -> Bool #

maximum :: Ord a => Sheaf a -> a #

minimum :: Ord a => Sheaf a -> a #

sum :: Num a => Sheaf a -> a #

product :: Num a => Sheaf a -> a #

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

Defined in OAlg.Structure.Fibred.Definition

Methods

inj :: f -> Sheaf f Source #

Additive a => Projectible a (Sheaf a) Source # 
Instance details

Defined in OAlg.Structure.Additive.Definition

Methods

prj :: Sheaf a -> a Source #

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

Defined in OAlg.Structure.Fibred.Definition

Methods

showsPrec :: Int -> Sheaf f -> ShowS #

show :: Sheaf f -> String #

showList :: [Sheaf f] -> ShowS #

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

Defined in OAlg.Structure.Fibred.Definition

Methods

(==) :: Sheaf f -> Sheaf f -> Bool #

(/=) :: Sheaf f -> Sheaf f -> Bool #

FibredOriented f => Dualisable (Sheaf f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

toDual :: Sheaf f -> Dual (Sheaf f) Source #

fromDual :: Dual (Sheaf f) -> Sheaf f Source #

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

Defined in OAlg.Structure.Fibred.Definition

Methods

valid :: Sheaf f -> Statement Source #

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

Defined in OAlg.Structure.Fibred.Definition

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

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root (Sheaf f) Source #

Methods

root :: Sheaf f -> Root (Sheaf f) Source #

Fibred f => Multiplicative (Sheaf f) Source #

'Data.List.(++)' is not commutative!

Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

one :: Point (Sheaf f) -> Sheaf f Source #

(*) :: Sheaf f -> Sheaf f -> Sheaf f Source #

npower :: Sheaf f -> N -> Sheaf f Source #

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

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Point (Sheaf f) Source #

type Dual (Sheaf f :: Type) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

type Dual (Sheaf f :: Type) = Sheaf (Op f)
type Root (Sheaf f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

type Root (Sheaf f) = Root f
type Point (Sheaf f) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

type Point (Sheaf f) = Root f