rings-0.1.2: Ring-like objects.

Safe HaskellSafe
LanguageHaskell2010

Data.Semimodule.Operator

Contents

Synopsis

Types

type Basis b f = (Free f, Rep f ~ b, Eq b) Source #

type Basis2 b c f g = (Basis b f, Basis c g) Source #

type Basis3 b c d f g h = (Basis b f, Basis c g, Basis d h) Source #

Vector accessors and constructors

newtype Dual a c Source #

Linear functionals from elements of a free semimodule to a scalar.

f !* (x + y) = (f !* x) + (f !* y)
f !* (x .* a) = a * (f !* x)

Caution: You must ensure these laws hold when using the default constructor.

Constructors

Dual 

Fields

Instances
RightSemimodule r s => RightSemimodule r (Dual s m) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

rscale :: r -> Dual s m -> Dual s m Source #

LeftSemimodule r s => LeftSemimodule r (Dual s m) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

lscale :: r -> Dual s m -> Dual s m Source #

Monad (Dual a) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

(>>=) :: Dual a a0 -> (a0 -> Dual a b) -> Dual a b #

(>>) :: Dual a a0 -> Dual a b -> Dual a b #

return :: a0 -> Dual a a0 #

fail :: String -> Dual a a0 #

Functor (Dual a) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

fmap :: (a0 -> b) -> Dual a a0 -> Dual a b #

(<$) :: a0 -> Dual a b -> Dual a a0 #

Applicative (Dual a) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

pure :: a0 -> Dual a a0 #

(<*>) :: Dual a (a0 -> b) -> Dual a a0 -> Dual a b #

liftA2 :: (a0 -> b -> c) -> Dual a a0 -> Dual a b -> Dual a c #

(*>) :: Dual a a0 -> Dual a b -> Dual a b #

(<*) :: Dual a a0 -> Dual a b -> Dual a a0 #

Coalgebra a b => Semigroup (Multiplicative (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

(Additive - Semigroup) a => Semigroup (Additive (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

(<>) :: Additive (Dual a b) -> Additive (Dual a b) -> Additive (Dual a b) #

sconcat :: NonEmpty (Additive (Dual a b)) -> Additive (Dual a b) #

stimes :: Integral b0 => b0 -> Additive (Dual a b) -> Additive (Dual a b) #

Counital a b => Monoid (Multiplicative (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

(Additive - Monoid) a => Monoid (Additive (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

mempty :: Additive (Dual a b) #

mappend :: Additive (Dual a b) -> Additive (Dual a b) -> Additive (Dual a b) #

mconcat :: [Additive (Dual a b)] -> Additive (Dual a b) #

(Additive - Monoid) a => Alternative (Dual a) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

empty :: Dual a a0 #

(<|>) :: Dual a a0 -> Dual a a0 -> Dual a a0 #

some :: Dual a a0 -> Dual a [a0] #

many :: Dual a a0 -> Dual a [a0] #

(Additive - Monoid) a => MonadPlus (Dual a) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

mzero :: Dual a a0 #

mplus :: Dual a a0 -> Dual a a0 -> Dual a a0 #

(Additive - Group) a => Group (Additive (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

inv :: Additive (Dual a b) -> Additive (Dual a b) #

greplicate :: Integer -> Additive (Dual a b) -> Additive (Dual a b) #

(Additive - Group) a => Loop (Additive (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

lempty :: Additive (Dual a b) #

lreplicate :: Natural -> Additive (Dual a b) -> Additive (Dual a b) #

(Additive - Group) a => Quasigroup (Additive (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

(//) :: Additive (Dual a b) -> Additive (Dual a b) -> Additive (Dual a b) #

(\\) :: Additive (Dual a b) -> Additive (Dual a b) -> Additive (Dual a b) #

(Additive - Group) a => Magma (Additive (Dual a b)) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

(<<) :: Additive (Dual a b) -> Additive (Dual a b) -> Additive (Dual a b) #

(Ring a, Counital a b) => Ring (Dual a b) Source # 
Instance details

Defined in Data.Semimodule.Dual

Counital a b => Semiring (Dual a b) Source # 
Instance details

Defined in Data.Semimodule.Dual

Coalgebra a b => Presemiring (Dual a b) Source # 
Instance details

Defined in Data.Semimodule.Dual

Counital r m => RightSemimodule (Dual r m) (Dual r m) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

rscale :: Dual r m -> Dual r m -> Dual r m Source #

Counital r m => LeftSemimodule (Dual r m) (Dual r m) Source # 
Instance details

Defined in Data.Semimodule.Dual

Methods

lscale :: Dual r m -> Dual r m -> Dual r m Source #

dual :: FreeCounital a f => f a -> Dual a (Rep f) Source #

Take the dual of a vector.

>>> dual (V2 3 4) !% V2 1 2 :: Int
11

image' :: Semiring a => Foldable f => f (a, c) -> Dual a c Source #

Create a Dual from a linear combination of basis vectors.

>>> image' [(2, E31),(3, E32)] !* V3 1 1 1 :: Int
5

dirac :: Eq i => Semiring a => i -> i -> a Source #

Dirac delta function.

idx :: Semiring a => Basis b f => b -> f a Source #

Create a unit vector at an index.

>>> idx E21 :: V2 Int
V2 1 0
>>> idx E42 :: V4 Int
V4 0 1 0 0

elt :: Basis b f => b -> f a -> a Source #

Retrieve an element of a vector.

>>> elt E21 (V2 1 2)
1

lensRep :: Basis b f => b -> forall g. Functor g => (a -> g a) -> f a -> g (f a) Source #

Create a lens from a representable functor.

grateRep :: Basis b f => forall g. Functor g => (b -> g a1 -> a2) -> g (f a1) -> f a2 Source #

Create an indexed grate from a representable functor.

Vector arithmetic

(.*) :: RightSemimodule r a => a -> r -> a infixl 7 Source #

Right-multiply a module element by a scalar.

(!*) :: Free f => Dual a (Rep f) -> f a -> a infixr 3 Source #

Apply a linear functional to a vector.

(.#) :: Free f => FreeCounital a g => (f ** g) a -> g a -> f a infixr 7 Source #

Multiply a matrix on the right by a column vector.

 (.#) = (!#) . tran
>>> tran (m23 1 2 3 4 5 6) !# V3 7 8 9 :: V2 Int
V2 50 122
>>> m23 1 2 3 4 5 6 .# V3 7 8 9 :: V2 Int
V2 50 122
>>> m22 1 0 0 0 .# m23 1 2 3 4 5 6 .# V3 7 8 9 :: V2 Int
V2 50 0

(!#) :: Free f => Free g => Tran a (Rep f) (Rep g) -> g a -> f a infixr 2 Source #

Apply a transformation to a vector.

(*.) :: LeftSemimodule l a => l -> a -> a infixr 7 Source #

Left-multiply a module element by a scalar.

(*!) :: Free f => f a -> Dual a (Rep f) -> a infixl 3 Source #

Apply a linear functional to a vector.

(#.) :: FreeCounital a f => Free g => f a -> (f ** g) a -> g a infixl 7 Source #

Multiply a matrix on the left by a row vector.

>>> V2 1 2 #. m23 3 4 5 6 7 8
V3 15 18 21
>>> V2 1 2 #. m23 3 4 5 6 7 8 #. m32 1 0 0 0 0 0 :: V2 Int
V2 15 0

(#!) :: Free f => Free g => g a -> Tran a (Rep f) (Rep g) -> f a infixl 2 Source #

Apply a transformation to a vector.

inner :: FreeCounital a f => f a -> f a -> a infix 6 Source #

Inner product.

This is a variant of xmult restricted to free functors.

>>> V3 1 2 3 `inner` V3 1 2 3
14

outer :: Semiring a => Free f => Free g => f a -> g a -> (f ** g) a Source #

Outer product.

>>> V2 1 1 `outer` V2 1 1
Compose (V2 (V2 1 1) (V2 1 1))

lerp :: LeftModule r a => r -> a -> a -> a Source #

Linearly interpolate between two vectors.

>>> u = V3 (1 :% 1) (2 :% 1) (3 :% 1) :: V3 Rational
>>> v = V3 (2 :% 1) (4 :% 1) (6 :% 1) :: V3 Rational
>>> r = 1 :% 2 :: Rational
>>> lerp r u v
V3 (6 % 4) (12 % 4) (18 % 4)

quadrance :: FreeCounital a f => f a -> a Source #

Squared l2 norm of a vector.

Matrix accessors and constructors

newtype Tran a b c Source #

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

f !# x + y = (f !# x) + (f !# y)
f !# (r .* x) = r .* (f !# x)

Caution: You must ensure these laws hold when using the default constructor.

Prefer image or tran where appropriate.

Constructors

Tran 

Fields

Instances
RightSemimodule r s => RightSemimodule r (Tran s b m) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

rscale :: r -> Tran s b m -> Tran s b m Source #

LeftSemimodule r s => LeftSemimodule r (Tran s b m) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

lscale :: r -> Tran s b m -> Tran s b m Source #

Coalgebra a c => Semigroup (Multiplicative (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

(<>) :: Multiplicative (Tran a b c) -> Multiplicative (Tran a b c) -> Multiplicative (Tran a b c) #

sconcat :: NonEmpty (Multiplicative (Tran a b c)) -> Multiplicative (Tran a b c) #

stimes :: Integral b0 => b0 -> Multiplicative (Tran a b c) -> Multiplicative (Tran a b c) #

(Additive - Semigroup) a => Semigroup (Additive (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

(<>) :: Additive (Tran a b c) -> Additive (Tran a b c) -> Additive (Tran a b c) #

sconcat :: NonEmpty (Additive (Tran a b c)) -> Additive (Tran a b c) #

stimes :: Integral b0 => b0 -> Additive (Tran a b c) -> Additive (Tran a b c) #

Counital a c => Monoid (Multiplicative (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

mempty :: Multiplicative (Tran a b c) #

mappend :: Multiplicative (Tran a b c) -> Multiplicative (Tran a b c) -> Multiplicative (Tran a b c) #

mconcat :: [Multiplicative (Tran a b c)] -> Multiplicative (Tran a b c) #

(Additive - Monoid) a => Monoid (Additive (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

mempty :: Additive (Tran a b c) #

mappend :: Additive (Tran a b c) -> Additive (Tran a b c) -> Additive (Tran a b c) #

mconcat :: [Additive (Tran a b c)] -> Additive (Tran a b c) #

Arrow (Tran a) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

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

first :: Tran a b c -> Tran a (b, d) (c, d) #

second :: Tran a b c -> Tran a (d, b) (d, c) #

(***) :: Tran a b c -> Tran a b' c' -> Tran a (b, b') (c, c') #

(&&&) :: Tran a b c -> Tran a b c' -> Tran a b (c, c') #

(Additive - Monoid) a => ArrowZero (Tran a) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

zeroArrow :: Tran a b c #

(Additive - Monoid) a => ArrowPlus (Tran a) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

(<+>) :: Tran a b c -> Tran a b c -> Tran a b c #

ArrowChoice (Tran a) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

left :: Tran a b c -> Tran a (Either b d) (Either c d) #

right :: Tran a b c -> Tran a (Either d b) (Either d c) #

(+++) :: Tran a b c -> Tran a b' c' -> Tran a (Either b b') (Either c c') #

(|||) :: Tran a b d -> Tran a c d -> Tran a (Either b c) d #

ArrowApply (Tran a) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

app :: Tran a (Tran a b c, b) c #

(Additive - Group) a => Group (Additive (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

inv :: Additive (Tran a b c) -> Additive (Tran a b c) #

greplicate :: Integer -> Additive (Tran a b c) -> Additive (Tran a b c) #

(Additive - Group) a => Loop (Additive (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

lempty :: Additive (Tran a b c) #

lreplicate :: Natural -> Additive (Tran a b c) -> Additive (Tran a b c) #

(Additive - Group) a => Quasigroup (Additive (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

(//) :: Additive (Tran a b c) -> Additive (Tran a b c) -> Additive (Tran a b c) #

(\\) :: Additive (Tran a b c) -> Additive (Tran a b c) -> Additive (Tran a b c) #

(Additive - Group) a => Magma (Additive (Tran a b c)) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

(<<) :: Additive (Tran a b c) -> Additive (Tran a b c) -> Additive (Tran a b c) #

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

Defined in Data.Semimodule.Algebra

Methods

id :: Tran a a0 a0 #

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

Monad (Tran a b) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

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

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

return :: a0 -> Tran a b a0 #

fail :: String -> Tran a b a0 #

Functor (Tran a b) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

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

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

Applicative (Tran a b) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

pure :: a0 -> Tran a b a0 #

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

liftA2 :: (a0 -> b0 -> c) -> Tran a b a0 -> Tran a b b0 -> Tran a b c #

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

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

(Ring a, Counital a c) => Ring (Tran a b c) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Counital a c => Semiring (Tran a b c) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Coalgebra a c => Presemiring (Tran a b c) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Counital a m => RightSemimodule (Tran a b m) (Tran a b m) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

rscale :: Tran a b m -> Tran a b m -> Tran a b m Source #

Counital a m => LeftSemimodule (Tran a b m) (Tran a b m) Source # 
Instance details

Defined in Data.Semimodule.Algebra

Methods

lscale :: Tran a b m -> Tran a b m -> Tran a b m Source #

tran :: Free f => FreeCounital a g => (f ** g) a -> Tran a (Rep f) (Rep g) Source #

Lift a matrix into a linear transformation

 (.#) = (!#) . tran

image :: Semiring a => (b -> [(a, c)]) -> Tran a b c Source #

Create a Tran from a linear combination of basis vectors.

>>> image (e2 [(2, E31),(3, E32)] [(1, E33)]) !# V3 1 1 1 :: V2 Int
V2 5 1

elt2 :: Basis2 b c f g => b -> c -> (f ** g) a -> a Source #

Retrieve an element of a matrix.

>>> elt2 E21 E21 $ m22 1 2 3 4
1

row :: Free f => Rep f -> (f ** g) a -> g a Source #

Retrieve a row of a matrix.

>>> row E22 $ m23 1 2 3 4 5 6
V3 4 5 6

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)

col :: Free f => Free g => Rep g -> (f ** g) a -> f a Source #

Retrieve a column of a matrix.

>>> elt E22 . col E31 $ m23 1 2 3 4 5 6
4

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)

diag :: FreeAlgebra a f => (f ** f) a -> f a Source #

Obtain the diagonal of a tensor product as a vector.

When the coalgebra is trivial we have:

 diag f = tabulate $ joined (index . index (getCompose f))
>>> diag $ m22 1.0 2.0 3.0 4.0
V2 1.0 4.0

codiag :: FreeCoalgebra a f => f a -> (f ** f) a Source #

Obtain a tensor from a vector.

When the coalgebra is trivial we have:

 codiag = flip bindRep id . getCompose

scalar :: FreeCoalgebra a f => a -> (f ** f) a Source #

Obtain a scalar matrix from a scalar.

>>> scalar 4.0 :: M22 Double
Compose (V2 (V2 4.0 0.0) (V2 0.0 4.0))

identity :: FreeCoalgebra a f => (f ** f) a Source #

Obtain an identity matrix.

>>> identity :: M33 Int
Compose (V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1))

Matrix arithmetic

(.#.) :: Free f => FreeCounital a g => Free h => (f ** g) a -> (g ** h) a -> (f ** h) a infixr 7 Source #

Multiply two matrices.

>>> m22 1 2 3 4 .#. m22 1 2 3 4 :: M22 Int
Compose (V2 (V2 7 10) (V2 15 22))
>>> m23 1 2 3 4 5 6 .#. m32 1 2 3 4 4 5 :: M22 Int
Compose (V2 (V2 19 25) (V2 43 58))

(!#!) :: Tran a c d -> Tran a b c -> Tran a b d infix 2 Source #

Compose two transformations.

trace :: FreeBialgebra a f => (f ** f) a -> a Source #

Trace of an endomorphism.

>>> trace $ m22 1.0 2.0 3.0 4.0
5.0

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

Transpose a matrix.

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