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.Data.Canonical

Description

canonical mappings between two types.

Synopsis

Canonical Mappings

class Embeddable a b where Source #

canonical embedding from a in to b.

Property

  1. inj is injective.
  2. if the two types a and b are also Projectible a b then prj . inj is the identical mapping.

Methods

inj :: a -> b Source #

canonical injetion from a in to b.

Instances

Instances details
Embeddable N Q Source # 
Instance details

Defined in OAlg.Data.Number

Methods

inj :: N -> Q Source #

Embeddable N Z Source # 
Instance details

Defined in OAlg.Data.Number

Methods

inj :: N -> Z Source #

Embeddable N Integer Source # 
Instance details

Defined in OAlg.Data.Number

Methods

inj :: N -> Integer Source #

Embeddable Z Q Source # 
Instance details

Defined in OAlg.Data.Number

Methods

inj :: Z -> Q Source #

Embeddable Integer Z Source # 
Instance details

Defined in OAlg.Data.Number

Methods

inj :: Integer -> Z Source #

Boolean b => Embeddable Bool b Source # 
Instance details

Defined in OAlg.Data.Canonical

Methods

inj :: Bool -> b Source #

Embeddable Int Z Source # 
Instance details

Defined in OAlg.Data.Number

Methods

inj :: Int -> Z Source #

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

Defined in OAlg.Structure.Fibred.Definition

Methods

inj :: f -> Sheaf f Source #

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

Defined in OAlg.Structure.Oriented.Definition

Methods

inj :: q -> Path q Source #

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

Defined in OAlg.Entity.Product.Definition

Methods

inj :: a -> Product r a Source #

Embeddable a (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

inj :: a -> ProductForm r a Source #

Embeddable (Inv c) c Source # 
Instance details

Defined in OAlg.Structure.Multiplicative.Definition

Methods

inj :: Inv c -> c Source #

Embeddable (GLT x) (ProductForm N (Transformation x)) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

(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 #

Embeddable [x] (PSequence N x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.PSequence

Methods

inj :: [x] -> PSequence N x Source #

Integral r => Embeddable (ProductForm N a) (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

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

(Embeddable a a', Embeddable b b') => Embeddable (a, b) (a', b') Source # 
Instance details

Defined in OAlg.Data.Canonical

Methods

inj :: (a, b) -> (a', b') Source #

(Embeddable a a', Embeddable b b', Embeddable c c') => Embeddable (a, b, c) (a', b', c') Source # 
Instance details

Defined in OAlg.Data.Canonical

Methods

inj :: (a, b, c) -> (a', b', c') Source #

class Projectible a b where Source #

canonical projection from b on to a.

Property

  1. prj is surjective.
  2. if the two types a and b are also Projectible a b then prj . inj is the identical mapping.

Methods

prj :: b -> a Source #

canonical projection from b on to a

Instances

Instances details
Projectible N Q Source # 
Instance details

Defined in OAlg.Data.Number

Methods

prj :: Q -> N Source #

Projectible N Z Source # 
Instance details

Defined in OAlg.Data.Number

Methods

prj :: Z -> N Source #

Projectible N Integer Source # 
Instance details

Defined in OAlg.Data.Number

Methods

prj :: Integer -> N Source #

Projectible Z Q Source # 
Instance details

Defined in OAlg.Data.Number

Methods

prj :: Q -> Z Source #

Projectible Integer Z Source # 
Instance details

Defined in OAlg.Data.Number

Methods

prj :: Z -> Integer Source #

Projectible Bool Valid Source # 
Instance details

Defined in OAlg.Data.Statement.Definition

Methods

prj :: Valid -> Bool Source #

Projectible Int Z Source # 
Instance details

Defined in OAlg.Data.Number

Methods

prj :: Z -> Int Source #

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

Defined in OAlg.Structure.Additive.Definition

Methods

prj :: Sheaf a -> a Source #

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

Defined in OAlg.Structure.Multiplicative.Definition

Methods

prj :: Path c -> c 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 #

Projectible [x] (PSequence N x) Source # 
Instance details

Defined in OAlg.Entity.Sequence.PSequence

Methods

prj :: PSequence N x -> [x] Source #

Integral r => Projectible (ProductForm N a) (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

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

(Projectible a a', Projectible b b') => Projectible (a, b) (a', b') Source # 
Instance details

Defined in OAlg.Data.Canonical

Methods

prj :: (a', b') -> (a, b) Source #

(Projectible a a', Projectible b b', Projectible c c') => Projectible (a, b, c) (a', b', c') Source # 
Instance details

Defined in OAlg.Data.Canonical

Methods

prj :: (a', b', c') -> (a, b, c) Source #