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.Oriented.Definition

Description

definition of Oriented structures.

Synopsis

Oriented

class (Entity q, Entity (Point q)) => Oriented q where Source #

types with a Oriented structure. The values of an Oriented structure will be called arrows and the values of the associated Point type points. To each arrow there is a start and a end point assigned.

Property Let q be a type instance of the class Oriented, then holds:

  1. For all a in q holds: orientation a == start a :> end a.

Note

  1. If the types q and Point q are interpreted as sets A and P and start, end as functions from A to P then this structure forms a quiver with arrows in A and points in P.
  2. Morphisms can be interpreted as Oriented structures via SomeMorphism. The bad thing about this is that we lose the check for composability of two Morphisms given by the type checker, but we gain all the functionality of Oriented structures, i.e we can define homomorphisms, limits etc on Morphisms.

Minimal complete definition

orientation | start, end

Associated Types

type Point q Source #

the associated type of points.

Methods

orientation :: q -> Orientation (Point q) Source #

the orientation of an arrow.

start :: q -> Point q Source #

the start point of an arrow.

end :: q -> Point q Source #

the end point of an arrow.

Instances

Instances details
Oriented N Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point N Source #

Oriented Q Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point Q Source #

Oriented Z Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point Z Source #

Oriented N' Source # 
Instance details

Defined in OAlg.Entity.Natural

Associated Types

type Point N' Source #

Oriented W' Source # 
Instance details

Defined in OAlg.Entity.Natural

Associated Types

type Point W' Source #

Oriented Integer Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point Integer Source #

Oriented () Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point () Source #

Methods

orientation :: () -> Orientation (Point ()) Source #

start :: () -> Point () Source #

end :: () -> Point () Source #

Oriented Int Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point Int Source #

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

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point (SomeMorphism m) Source #

Oriented q => Oriented (Op q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point (Op q) Source #

Methods

orientation :: Op q -> Orientation (Point (Op q)) Source #

start :: Op q -> Point (Op q) Source #

end :: Op q -> Point (Op q) Source #

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

Defined in OAlg.Entity.Matrix.Definition

Associated Types

type Point (Matrix x) Source #

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

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Point (GL2 x) Source #

Methods

orientation :: GL2 x -> Orientation (Point (GL2 x)) Source #

start :: GL2 x -> Point (GL2 x) Source #

end :: GL2 x -> Point (GL2 x) Source #

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

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Point (GLT x) Source #

Methods

orientation :: GLT x -> Orientation (Point (GLT x)) Source #

start :: GLT x -> Point (GLT x) Source #

end :: GLT x -> Point (GLT x) Source #

Oriented x => Oriented (Transformation x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Point (Transformation x) Source #

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

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Point (ColTrafo x) Source #

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

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Point (RowTrafo a) Source #

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

Defined in OAlg.Entity.Product.ProductSymbol

Associated Types

type Point (ProductSymbol x) Source #

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

Defined in OAlg.Entity.Product.ProductSymbol

Associated Types

type Point (U x) Source #

Methods

orientation :: U x -> Orientation (Point (U x)) Source #

start :: U x -> Point (U x) Source #

end :: U x -> Point (U x) Source #

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

Defined in OAlg.Entity.Sequence.Permutation

Associated Types

type Point (Permutation i) Source #

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

Defined in OAlg.Entity.Sequence.Permutation

Associated Types

type Point (PermutationForm i) Source #

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

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Point (Sheaf f) Source #

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

Defined in OAlg.Structure.Multiplicative.Definition

Associated Types

type Point (Inv c) Source #

Methods

orientation :: Inv c -> Orientation (Point (Inv c)) Source #

start :: Inv c -> Point (Inv c) Source #

end :: Inv c -> Point (Inv c) Source #

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

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point (Orientation p) Source #

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

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point (Path q) Source #

Methods

orientation :: Path q -> Orientation (Point (Path q)) Source #

start :: Path q -> Point (Path q) Source #

end :: Path q -> Point (Path q) Source #

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

Defined in OAlg.Entity.Matrix.Dim

Associated Types

type Point (Dim x p) Source #

Methods

orientation :: Dim x p -> Orientation (Point (Dim x p)) Source #

start :: Dim x p -> Point (Dim x p) Source #

end :: Dim x p -> Point (Dim x p) Source #

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

Defined in OAlg.Entity.Product.Definition

Associated Types

type Point (Product r a) Source #

Methods

orientation :: Product r a -> Orientation (Point (Product r a)) Source #

start :: Product r a -> Point (Product r a) Source #

end :: Product r a -> Point (Product r a) Source #

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

Defined in OAlg.Entity.Product.Definition

Associated Types

type Point (ProductForm r a) Source #

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

Defined in OAlg.Entity.Slice.Definition

Associated Types

type Point (SliceFactor s i c) Source #

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

Defined in OAlg.Entity.Diagram.Definition

Associated Types

type Point (Diagram ('Chain t) n m a) Source #

Methods

orientation :: Diagram ('Chain t) n m a -> Orientation (Point (Diagram ('Chain t) n m a)) Source #

start :: Diagram ('Chain t) n m a -> Point (Diagram ('Chain t) n m a) Source #

end :: Diagram ('Chain t) n m a -> Point (Diagram ('Chain t) n m a) Source #

(Oriented a, Typeable d, Typeable n, Typeable m) => Oriented (Diagram ('Parallel d) n m a) Source # 
Instance details

Defined in OAlg.Entity.Diagram.Definition

Associated Types

type Point (Diagram ('Parallel d) n m a) Source #

Methods

orientation :: Diagram ('Parallel d) n m a -> Orientation (Point (Diagram ('Parallel d) n m a)) Source #

start :: Diagram ('Parallel d) n m a -> Point (Diagram ('Parallel d) n m a) Source #

end :: Diagram ('Parallel d) n m a -> Point (Diagram ('Parallel d) n m a) Source #

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

Defined in OAlg.Entity.Diagram.Transformation

Associated Types

type Point (Transformation t n m a) Source #

(Oriented a, Typeable s, Typeable p, Typeable d, Typeable m) => Oriented (Cone s p ('Parallel d) N2 m a) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

Associated Types

type Point (Cone s p ('Parallel d) N2 m a) Source #

Methods

orientation :: Cone s p ('Parallel d) N2 m a -> Orientation (Point (Cone s p ('Parallel d) N2 m a)) Source #

start :: Cone s p ('Parallel d) N2 m a -> Point (Cone s p ('Parallel d) N2 m a) Source #

end :: Cone s p ('Parallel d) N2 m a -> Point (Cone s p ('Parallel d) N2 m a) Source #

class Singleton (Point x) => Total x Source #

structures where its associated Point type is singleton. They yield globally defiend algebraic operations.

Instances

Instances details
Total N Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Total Q Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Total Z Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Total N' Source # 
Instance details

Defined in OAlg.Entity.Natural

Total W' Source # 
Instance details

Defined in OAlg.Entity.Natural

Total Integer Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Total () Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Total Int Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Total (Permutation i) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Permutation

Total q => Total (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Total (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

class Entity (Point x) => EntityPoint x Source #

helper class to avoid undecidable instances.

Instances

Instances details
EntityPoint N Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

EntityPoint Q Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

EntityPoint Z Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

EntityPoint Integer Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

EntityPoint () Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

EntityPoint Int Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Oriented.Definition

EntityPoint q => EntityPoint (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

class Ord (Point x) => OrdPoint x Source #

helper class to circumvent undecidable instances.

Instances

Instances details
OrdPoint N Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

OrdPoint Q Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

OrdPoint Z Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

OrdPoint Integer Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

OrdPoint () Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

OrdPoint Int Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

OrdPoint (U x) Source # 
Instance details

Defined in OAlg.Entity.Product.ProductSymbol

OrdPoint q => OrdPoint (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

isEndo :: Oriented q => q -> Bool Source #

check for being an endo.

Definition Let q be a Oriented structure, then an arrow a in q is called endo if and only if start a == end a.

isEndoAt :: Oriented a => Point a -> a -> Bool Source #

check for being an endo at the given point.

type OS = Orientation Symbol Source #

as Orientation p is an instance of almost every structured class it serves as a standard type for validating.

data Ort Source #

type representing the class of Oriented structures.

Instances

Instances details
ForgetfulTyp Ort Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

TransformableOp Ort Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

ForgetfulOrt Ort Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

EmbeddableMorphism GLApp Ort Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

EmbeddableMorphism TrApp Ort Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Transformable Dst Ort Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

Methods

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

Transformable FbrOrt Ort Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

Methods

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

Transformable Mlt Ort Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Methods

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

Transformable Ort Ent Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

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

Transformable Ort Typ Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

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

Transformable1 Op Ort Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

tau1 :: Struct Ort x -> Struct Ort (Op x) Source #

EmbeddableMorphism (SliceFactorDrop s) Ort Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

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

Defined in OAlg.Hom.Oriented.Definition

Transformable (Alg k) Ort Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

Methods

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

(Multiplicative c, Sliced i c) => EmbeddableMorphism (SliceCokernelKernel i c) Ort Source # 
Instance details

Defined in OAlg.Entity.Slice.Adjunction

type Hom Ort h Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

type Hom Ort h = HomOriented h
type Structure Ort x Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

structOrtOp :: Struct Ort x -> Struct Ort (Op x) Source #

attest that if x is Oriented then also Op x is Oriented.

class Transformable s Ort => ForgetfulOrt s Source #

transformable to Oriented structure.

Instances

Instances details
ForgetfulOrt Dst Source # 
Instance details

Defined in OAlg.Structure.Distributive.Definition

ForgetfulOrt FbrOrt Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

ForgetfulOrt Mlt Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

ForgetfulOrt Ort Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

ForgetfulOrt (Alg k) Source # 
Instance details

Defined in OAlg.Structure.Algebraic.Definition

Transposable

Orientation

data Orientation p Source #

orientation given by the start point as its first component and the end point as its second.

Property For all o in Orientation p holds: o == start o :> end o.

Note As Orientations are instances of almost all algebraic structures defined here, they serve as a proof that this structures are instanceable.

Constructors

p :> p infix 5 

Instances

Instances details
Functor Orientation Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

fmap :: (a -> b) -> Orientation a -> Orientation b #

(<$) :: a -> Orientation b -> Orientation a #

XStandard p => XStandardOrtSite 'From (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

XStandard p => XStandardOrtSite 'To (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

XStandardOrtSite 'From (SliceFactor 'To (Proxy :: Type -> Type) OS) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

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

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Oriented.Definition

Transposable (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Singleton u => Singleton (Orientation u) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

unit :: Orientation u Source #

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

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Additive.Definition

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

Defined in OAlg.Structure.Additive.Definition

(Entity p, XStandard p) => XStandardAdd (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Additive.Proposition

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

Defined in OAlg.Structure.Algebraic.Definition

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

Defined in OAlg.Structure.Distributive.Definition

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

Defined in OAlg.Structure.Distributive.Definition

(Entity p, XStandard p) => XStandardDst (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Distributive.Proposition

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

Defined in OAlg.Structure.Exponential

Methods

power :: Number r => Orientation p -> r -> Orientation p Source #

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

Defined in OAlg.Structure.Fibred.Definition

Associated Types

type Root (Orientation p) Source #

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

Defined in OAlg.Structure.Fibred.Definition

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

Defined in OAlg.Structure.Multiplicative.Definition

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

Defined in OAlg.Structure.Multiplicative.Definition

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

Defined in OAlg.Structure.Multiplicative.Definition

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

Defined in OAlg.Structure.Multiplicative.Definition

(Entity p, XStandard p) => XStandardMlt (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Proposition

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

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point (Orientation p) Source #

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

Defined in OAlg.Structure.Oriented.Definition

XStandard p => XStandardOrtOrientation (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

XStandard p => XStandardOrtSiteFrom (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

XStandard p => XStandardOrtSiteTo (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

XStandard p => XStandardPoint (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Vectorial.Definition

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

Defined in OAlg.Structure.Vectorial.Definition

Associated Types

type Scalar (Orientation p) Source #

Sliced (Proxy :: Type -> Type) OS Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

XStandardOrtSiteFrom (SliceFactor 'To (Proxy :: Type -> Type) OS) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

(Entity p, t ~ 'Parallel 'RightToLeft, n ~ N2, XStandard p, XStandard (Diagram t n m (Orientation p))) => XStandard (Cone Dst 'Injective t n m (Orientation p)) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

Methods

xStandard :: X (Cone Dst 'Injective t n m (Orientation p)) Source #

(Entity p, t ~ 'Parallel 'LeftToRight, n ~ N2, XStandard p, XStandard (Diagram t n m (Orientation p))) => XStandard (Cone Dst 'Projective t n m (Orientation p)) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

Methods

xStandard :: X (Cone Dst 'Projective t n m (Orientation p)) Source #

(Entity p, XStandard p, XStandard (Diagram t n m (Orientation p))) => XStandard (Cone Mlt 'Injective t n m (Orientation p)) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

Methods

xStandard :: X (Cone Mlt 'Injective t n m (Orientation p)) Source #

(Entity p, XStandard p, XStandard (Diagram t n m (Orientation p))) => XStandard (Cone Mlt 'Projective t n m (Orientation p)) Source # 
Instance details

Defined in OAlg.Limes.Cone.Definition

Methods

xStandard :: X (Cone Mlt 'Projective t n m (Orientation p)) Source #

type Root (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Fibred.Definition

type Point (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

type Point (Orientation p) = p
type Scalar (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Vectorial.Definition

type Scalar (Orientation p) = Q

opposite :: Orientation p -> Orientation p Source #

the opposite orientation.

Path

data Path q Source #

a path in a Oriented structure q starting at a given point.

Definition Let q be a Oriented structure and p = Path s [a 0..a (n-1)] a path in q, then p is valid if and only if

  1. s is valid and a i are valid for all i = 0..n-1.
  2. start (a (n-1)) == s and start (a i) == end (a (n+1)) for all i = 0..n-2.

furthermore n is called the length of p.

Note Paths admit a canonical embedding in to Product.

Constructors

Path (Point q) [q] 

Instances

Instances details
Foldable Path Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

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

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

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

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

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

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

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

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

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

toList :: Path a -> [a] #

null :: Path a -> Bool #

length :: Path a -> Int #

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

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

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

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

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

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

Defined in OAlg.Structure.Oriented.Definition

Methods

inj :: q -> Path q Source #

Multiplicative c => Projectible c (Path c) Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Methods

prj :: Path c -> c Source #

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

Defined in OAlg.Structure.Oriented.Definition

Methods

showsPrec :: Int -> Path q -> ShowS #

show :: Path q -> String #

showList :: [Path q] -> ShowS #

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

Defined in OAlg.Structure.Oriented.Definition

Methods

(==) :: Path q -> Path q -> Bool #

(/=) :: Path q -> Path q -> Bool #

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

Defined in OAlg.Structure.Oriented.Definition

Methods

toDual :: Path q -> Dual (Path q) Source #

fromDual :: Dual (Path q) -> Path q Source #

Reflexive (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

toBidual :: Path q -> Dual (Dual (Path q)) Source #

fromBidual :: Dual (Dual (Path q)) -> Path q Source #

LengthN (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

lengthN :: Path q -> N Source #

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

Defined in OAlg.Structure.Oriented.Definition

Methods

valid :: Path q -> Statement Source #

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

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Multiplicative.Definition

Methods

one :: Point (Path q) -> Path q Source #

(*) :: Path q -> Path q -> Path q Source #

npower :: Path q -> N -> Path q Source #

EntityPoint q => EntityPoint (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

OrdPoint q => OrdPoint (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Structure.Oriented.Definition

Associated Types

type Point (Path q) Source #

Methods

orientation :: Path q -> Orientation (Point (Path q)) Source #

start :: Path q -> Point (Path q) Source #

end :: Path q -> Point (Path q) Source #

Total q => Total (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

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

Defined in OAlg.Entity.Product.Definition

Methods

inj :: Path a -> Product r a Source #

Embeddable (Path a) (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

inj :: Path a -> ProductForm r a Source #

Oriented a => Projectible (Path a) (Product N a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

prj :: Product N a -> Path a Source #

Oriented a => Projectible (Path a) (ProductForm N a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

prj :: ProductForm N a -> Path a Source #

ForgetfulOrt s => Applicative (IsoOpMap Path s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Methods

amap :: IsoOpMap Path s a b -> a -> b Source #

ForgetfulOrt s => Applicative (OpMap Path s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Methods

amap :: OpMap Path s a b -> a -> b Source #

ForgetfulOrt s => Functorial (IsoOpMap Path s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(TransformableOp s, ForgetfulOrt s, ForgetfulTyp s, Typeable s) => FunctorialHomOriented (IsoOpMap Path s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

(TransformableOp s, ForgetfulOrt s, ForgetfulTyp s, Typeable s) => HomOriented (IsoOpMap Path s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Methods

pmap :: IsoOpMap Path s a b -> Point a -> Point b Source #

(TransformableOp s, ForgetfulOrt s, ForgetfulTyp s, Typeable s) => HomOriented (OpMap Path s) Source # 
Instance details

Defined in OAlg.Hom.Oriented.Definition

Methods

pmap :: OpMap Path s a b -> Point a -> Point b Source #

type Dual (Path q :: Type) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

type Dual (Path q :: Type) = Path (Op q)
type Point (Path q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

type Point (Path q) = Point q

pthLength :: Path q -> N Source #

the length of a path.

pthOne :: Point q -> Path q Source #

path of length 0 at the given point.

pthMlt :: Oriented q => Path q -> Path q -> Path q Source #

composition of two paths.

X

Site

data XOrtSite s q where Source #

random variables X q and X (Point q) for Oriented structure q.

Properties Let q be an instance of the class Oriented, then holds:

  1. Let XStart xp xStart be in XOrtSite From q, then holds: For all p in Point q and x in the range of xStart p holds: start x == p.
  2. Let XEnd xp xEnd be in XOrtSite To q, then holds: For all p in Point q and x in the range of xEnd p holds: end x == p.

Note The random variables xp should have a bias to non trivial random variables xp >>= xStart or xp >>= xEnd.

Constructors

XStart :: X (Point q) -> (Point q -> X q) -> XOrtSite From q 
XEnd :: X (Point q) -> (Point q -> X q) -> XOrtSite To q 

Instances

Instances details
Dualisable (XOrtSite 'To q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Oriented q => Validable (XOrtSite s q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

Methods

valid :: XOrtSite s q -> Statement Source #

type Dual (XOrtSite s q :: Type) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

type Dual (XOrtSite s q :: Type) = XOrtSite (Dual s) (Op q)

class XStandardOrtSite s a where Source #

standard random variable for XOrtSite.

Instances

Instances details
XStandardOrtSite 'From (Matrix Z) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Definition

XStandard p => XStandardOrtSite 'From (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

XStandardOrtSite 'From a => XStandardOrtSite 'To (Op a) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

XStandardOrtSite 'To (Matrix Z) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Definition

XStandard p => XStandardOrtSite 'To (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

(Multiplicative c, Sliced i c, XStandardOrtSite 'From c) => XStandardOrtSite 'From (SliceFactor 'From i c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

XStandardOrtSite 'From (SliceFactor 'To (Proxy :: Type -> Type) OS) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

(Multiplicative c, Sliced i c, XStandardOrtSite 'To c) => XStandardOrtSite 'To (SliceFactor 'To i c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

class XStandardOrtSite To a => XStandardOrtSiteTo a Source #

standard random variable for XOrtSite To, helper class to avoid undecidable instances.

Instances

Instances details
XStandard p => XStandardOrtSiteTo (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

(Multiplicative c, Sliced i c, XStandardOrtSite 'To c) => XStandardOrtSiteTo (SliceFactor 'To i c) Source # 
Instance details

Defined in OAlg.Entity.Slice.Definition

class XStandardOrtSite From a => XStandardOrtSiteFrom a Source #

standard random variable for XOrtSite From, helper class to avoid undecidable instances.

coXOrtSite :: XOrtSite s q -> Dual (XOrtSite s q) Source #

to the dual of a XOrtSite s q, with inverse coXOrtSiteInv.

coXOrtSiteInv :: (Dual (Dual s) :~: s) -> Dual (XOrtSite s q) -> XOrtSite s q Source #

from the dual of a Dual (XOrtSite s q), with inverse coXOrtSite.

xosFromOpOp :: XOrtSite s (Op (Op q)) -> XOrtSite s q Source #

from the bidual.

xosStart :: XOrtSite From q -> Point q -> X q Source #

the random variable of arrows in q having all as start the given point.

xosEnd :: XOrtSite To q -> Point q -> X q Source #

the random variable of arrows in q having all as end the given point.

xosPathMaxAt :: Oriented q => XOrtSite s q -> N -> Point q -> X (Path q) Source #

tries to make a path at the given point with maximal length of the given length.

Properties Let xPath = xosPathMaxAt xos n x, then holds:

  1. If xos matches XStart _ xq then for all p in the range of xPath holds:

    1. start p == x.
    2. If pthLength p < n then xq (end p) matches XEmpty.
  2. If xos matches XEnd _ xq then for all p in the range of xPath holds:

    1. end p == x.
    2. If pthLength p < n then xq (start p) matches XEmpty.

xosPathMax :: Oriented q => XOrtSite s q -> N -> X (Path q) Source #

random variable of paths with maximal length of the given length.

Orientation

data XOrtOrientation q Source #

random variable of arrows given by an orientation.

Properties Let XOrtOrientation xo xArrow be in XOrtOrientation q for a Oriented structure q, then holds: For all o in Orientation q and x in the range of xArrow o holds: orientation x == o.

Note The random variable xo should have a bias to non trivial random variables xo >>= xArrow and as such the range of xo should be included in one connection component of q.

Constructors

XOrtOrientation (X (Orientation (Point q))) (Orientation (Point q) -> X q) 

Instances

Instances details
Oriented q => Validable (XOrtOrientation q) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

type Dual (XOrtOrientation q :: Type) Source # 
Instance details

Defined in OAlg.Structure.Oriented.Definition

xoOrientation :: XOrtOrientation q -> X (Orientation (Point q)) Source #

the underlying random variable of orientations.

xoArrow :: XOrtOrientation q -> Orientation (Point q) -> X q Source #

the underlying random variable of arrow given by the orientation.

xoPoint :: Oriented q => XOrtOrientation q -> X (Point q) Source #

the underlying random variable of points, i.e. the union of the induced start and end random variable of xoOrientation.

xoTtl :: Total q => X q -> XOrtOrientation q Source #

random variable of XOrtOrientation q for a total q.

xoOrnt :: X p -> XOrtOrientation (Orientation p) Source #

the induced random variable of Orientation q.

Orientation

class XStandard (Point a) => XStandardPoint a Source #

standard random variable of Points of a.

xStartOrnt :: X p -> XOrtSite From (Orientation p) Source #

the XOrtSite From for Orientation p of the given random variable.

xEndOrnt :: X p -> XOrtSite To (Orientation p) Source #

the XOrtSite To of Orientation p of the given random variable.