rings-0.0.3.1: Ring-like objects.

Safe HaskellSafe
LanguageHaskell2010

Data.Semimodule.Transform

Contents

Synopsis

Types

type (**) f g = Compose f g infixr 2 Source #

type (++) f g = Product f g infixr 1 Source #

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

A dimensional (binary) relation between two bases.

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

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

type Endo a b = Tran a b b Source #

An endomorphism over a free semimodule.

newtype Tran a b c Source #

A morphism 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 :: Basis2 b c f g => Tran a b c -> g a -> f a Source #

Apply a transformation to a vector.

arr :: (b -> c) -> Tran a b c Source #

Lift a function on basis indices into a transformation.

 arr f = rmap f id

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/.

Matrix combinators

rows :: Basis2 b c f 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 :: Basis2 b c f 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 :: Basis2 b c f g => (f ++ g) a -> f a Source #

Project onto the left-hand component of a direct sum.

projr :: Basis2 b c f g => (f ++ g) a -> g a Source #

Project onto the right-hand component of a direct sum.

compl :: Basis3 b c d f1 f2 g => Dim b c -> (f2 ** g) a -> (f1 ** g) a Source #

Left (post) composition with a linear transformation.

compr :: Basis3 b c d f g1 g2 => Dim c d -> (f ** g2) a -> (f ** g1) a Source #

Right (pre) composition with a linear transformation.

complr :: Basis2 b1 c1 f1 f2 => Basis2 b2 c2 g1 g2 => Dim b1 c1 -> Dim 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 (+ E32)
>>> perm2 = arr (+ E33)
>>> m = m33 1 2 3 4 5 6 7 8 9 :: M33 Int
>>> complr 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 :: Basis2 b c f 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)

Dimensional combinators

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

Swap components of a tensor product.

sbraid :: Dim (a + b) (b + a) Source #

Swap components of a direct sum.

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

Lift a transform into a transform on tensor products.

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

Lift a transform into a transform on tensor products.

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

Lift a transform into a transform on direct sums.

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

Lift a transform into a transform on direct sums.

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

Create a transform on a tensor product of semimodules.

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

Create a transform on a direct sum of semimodules.

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

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

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

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

adivide' :: Dim a1 b -> Dim a2 b -> Dim (a1, a2) b Source #

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

aselect' :: Dim a b1 -> Dim a b2 -> Dim a (b1 + b2) Source #