rings-0.0.3: Ring-like objects.

Safe HaskellSafe
LanguageHaskell2010

Data.Semimodule.Transform

Synopsis

Documentation

type Index b c = forall a. Tran a b c Source #

A binary relation between two basis indices.

Index b c relations correspond to (compositions of) permutation, projection, and embedding transformations.

See also https://en.wikipedia.org/wiki/Logical_matrix.

newtype Tran a b c Source #

A general linear transformation between free semimodules indexed with bases b and c.

Constructors

Tran 

Fields

Instances
Profunctor (Tran a) Source # 
Instance details

Defined in Data.Semimodule.Transform

Methods

dimap :: (a0 -> b) -> (c -> d) -> Tran a b c -> Tran a a0 d #

lmap :: (a0 -> b) -> Tran a b c -> Tran a a0 c #

rmap :: (b -> c) -> Tran a a0 b -> Tran a a0 c #

(#.) :: Coercible c b => q b c -> Tran a a0 b -> Tran a a0 c #

(.#) :: Coercible b a0 => Tran a b c -> q a0 b -> Tran a a0 c #

Category (Tran a :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Semimodule.Transform

Methods

id :: Tran a a0 a0 #

(.) :: Tran a b c -> Tran a a0 b -> Tran a a0 c #

Functor (Tran a b) Source # 
Instance details

Defined in Data.Semimodule.Transform

Methods

fmap :: (a0 -> b0) -> Tran a b a0 -> Tran a b b0 #

(<$) :: a0 -> Tran a b b0 -> Tran a b a0 #

app :: Basis b f => Basis c g => Tran a b c -> g a -> f a Source #

invmap :: (a1 -> a2) -> (a2 -> a1) -> Tran a1 b c -> Tran a2 b c Source #

Tran a b c is an invariant functor on a.

See also http://comonad.com/reader/2008/rotten-bananas/.

type Endo a b = Tran a b b Source #

An endomorphism over a free semimodule.

rows :: Free f => Free g => g a -> f (g a) Source #

Obtain a matrix by stacking rows.

>>> rows (V2 1 2) :: M22 Int
V2 (V2 1 2) (V2 1 2)

cols :: Free f => Free g => f a -> f (g a) Source #

Obtain a matrix by stacking columns.

>>> cols (V2 1 2) :: M22 Int
V2 (V2 1 1) (V2 2 2)

projl :: Free f => Free g => Product f g a -> f a Source #

projr :: Free f => Free g => Product f g a -> g a Source #

compl :: Basis b f1 => Basis c f2 => Free g => Index b c -> f2 (g a) -> f1 (g a) Source #

Left (post) composition with a linear transformation.

compr :: Basis b g1 => Basis c g2 => Free f => Index b c -> f (g2 a) -> f (g1 a) Source #

Right (pre) composition with a linear transformation.

complr :: Basis b1 f1 => Basis c1 f2 => Basis b2 g1 => Basis c2 g2 => Index b1 c1 -> Index b2 c2 -> f2 (g2 a) -> f1 (g1 a) Source #

Left and right composition with a linear transformation.

 'complr f g' = 'compl f' . 'compr g'

When f . g = id this induces a similarity transformation:

>>> perm1 = arr (+ I32)
>>> perm2 = arr (+ I33)
>>> m = m33 1 2 3 4 5 6 7 8 9 :: M33 Int
>>> conjugate perm1 perm2 m :: M33 Int
V3 (V3 5 6 4) (V3 8 9 7) (V3 2 3 1)

See also https://en.wikipedia.org/wiki/Matrix_similarity & https://en.wikipedia.org/wiki/Conjugacy_class.

transpose :: Free f => Free g => f (g a) -> g (f a) Source #

Transpose a matrix.

>>> transpose (V3 (V2 1 2) (V2 3 4) (V2 5 6))
V2 (V3 1 3 5) (V3 2 4 6)
>>> transpose $ m23 1 2 3 4 5 6 :: M32 Int
V3 (V2 1 4) (V2 2 5) (V2 3 6)

arr :: (b -> c) -> Index b c Source #

in1 :: Index (a, b) b Source #

in2 :: Index (a, b) a Source #

exl :: Index a (a + b) Source #

exr :: Index b (a + b) Source #

braid :: Index (a, b) (b, a) Source #

ebraid :: Index (a + b) (b + a) Source #

first :: Index b c -> Index (b, d) (c, d) Source #

second :: Index b c -> Index (d, b) (d, c) Source #

left :: Index b c -> Index (b + d) (c + d) Source #

right :: Index b c -> Index (d + b) (d + c) Source #

(***) :: Index a1 b1 -> Index a2 b2 -> Index (a1, a2) (b1, b2) infixr 3 Source #

(+++) :: Index a1 b1 -> Index a2 b2 -> Index (a1 + a2) (b1 + b2) infixr 2 Source #

(&&&) :: Index a b1 -> Index a b2 -> Index a (b1, b2) infixr 3 Source #

(|||) :: Index a1 b -> Index a2 b -> Index (a1 + a2) b infixr 2 Source #

($$$) :: Index a (b -> c) -> Index a b -> Index a c infixr 0 Source #

adivide :: (a -> (a1, a2)) -> Index a1 b -> Index a2 b -> Index a b Source #

adivide' :: Index a b -> Index a b -> Index a b Source #

adivided :: Index a1 b -> Index a2 b -> Index (a1, a2) b Source #

aselect :: ((b1 + b2) -> b) -> Index a b1 -> Index a b2 -> Index a b Source #

aselect' :: Index a b -> Index a b -> Index a b Source #

aselected :: Index a b1 -> Index a b2 -> Index a (b1 + b2) Source #