| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Semimodule.Operator
Contents
Synopsis
- type Free f = Representable f
- type Basis b f = (Free f, Rep f ~ b, Eq b)
- type Basis2 b c f g = (Basis b f, Basis c g)
- type Basis3 b c d f g h = (Basis b f, Basis c g, Basis d h)
- newtype Dual a c = Dual {
- runDual :: (c -> a) -> a
- dual :: FreeCounital a f => f a -> Dual a (Rep f)
- image' :: Semiring a => Foldable f => f (a, c) -> Dual a c
- dirac :: Eq i => Semiring a => i -> i -> a
- idx :: Semiring a => Basis b f => b -> f a
- elt :: Basis b f => b -> f a -> a
- lensRep :: Basis b f => b -> forall g. Functor g => (a -> g a) -> f a -> g (f a)
- grateRep :: Basis b f => forall g. Functor g => (b -> g a1 -> a2) -> g (f a1) -> f a2
- (.*) :: RightSemimodule r a => a -> r -> a
- (!*) :: Free f => Dual a (Rep f) -> f a -> a
- (.#) :: Free f => FreeCounital a g => (f ** g) a -> g a -> f a
- (!#) :: Free f => Free g => Tran a (Rep f) (Rep g) -> g a -> f a
- (*.) :: LeftSemimodule l a => l -> a -> a
- (*!) :: Free f => f a -> Dual a (Rep f) -> a
- (#.) :: FreeCounital a f => Free g => f a -> (f ** g) a -> g a
- (#!) :: Free f => Free g => g a -> Tran a (Rep f) (Rep g) -> f a
- inner :: FreeCounital a f => f a -> f a -> a
- outer :: Semiring a => Free f => Free g => f a -> g a -> (f ** g) a
- lerp :: LeftModule r a => r -> a -> a -> a
- quadrance :: FreeCounital a f => f a -> a
- newtype Tran a b c = Tran {
- runTran :: (c -> a) -> b -> a
- tran :: Free f => FreeCounital a g => (f ** g) a -> Tran a (Rep f) (Rep g)
- image :: Semiring a => (b -> [(a, c)]) -> Tran a b c
- elt2 :: Basis2 b c f g => b -> c -> (f ** g) a -> a
- row :: Free f => Rep f -> (f ** g) a -> g a
- rows :: Free f => Free g => g a -> (f ** g) a
- col :: Free f => Free g => Rep g -> (f ** g) a -> f a
- cols :: Free f => Free g => f a -> (f ** g) a
- diag :: FreeAlgebra a f => (f ** f) a -> f a
- codiag :: FreeCoalgebra a f => f a -> (f ** f) a
- scalar :: FreeCoalgebra a f => a -> (f ** f) a
- identity :: FreeCoalgebra a f => (f ** f) a
- (.#.) :: Free f => FreeCounital a g => Free h => (f ** g) a -> (g ** h) a -> (f ** h) a
- (!#!) :: Tran a c d -> Tran a b c -> Tran a b d
- trace :: FreeBialgebra a f => (f ** f) a -> a
- transpose :: Free f => Free g => (f ** g) a -> (g ** f) a
Types
type Free f = Representable f Source #
Vector accessors and constructors
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.
Instances
dual :: FreeCounital a f => f a -> Dual a (Rep f) Source #
Take the dual of a vector.
>>>dual (V2 3 4) !% V2 1 2 :: Int11
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 :: Int5
idx :: Semiring a => Basis b f => b -> f a Source #
Create a unit vector at an index.
>>>idx E21 :: V2 IntV2 1 0
>>>idx E42 :: V4 IntV4 0 1 0 0
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 => 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 8V3 15 18 21
>>>V2 1 2 #. m23 3 4 5 6 7 8 #. m32 1 0 0 0 0 0 :: V2 IntV2 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 314
outer :: Semiring a => Free f => Free g => f a -> g a -> (f ** g) a Source #
Outer product.
>>>V2 1 1 `outer` V2 1 1Compose (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 vV3 (6 % 4) (12 % 4) (18 % 4)
quadrance :: FreeCounital a f => f a -> a Source #
Squared l2 norm of a vector.
Matrix accessors and constructors
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.
Instances
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 IntV2 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 41
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 6V3 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 IntV2 (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 64
cols :: Free f => Free g => f a -> (f ** g) a Source #
Obtain a matrix by stacking columns.
>>>cols (V2 1 2) :: M22 IntV2 (V2 1 1) (V2 2 2)
diag :: FreeAlgebra a f => (f ** f) a -> f a Source #
codiag :: FreeCoalgebra a f => f a -> (f ** f) a Source #
scalar :: FreeCoalgebra a f => a -> (f ** f) a Source #
Obtain a scalar matrix from a scalar.
>>>scalar 4.0 :: M22 DoubleCompose (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 IntCompose (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 IntCompose (V2 (V2 7 10) (V2 15 22))
>>>m23 1 2 3 4 5 6 .#. m32 1 2 3 4 4 5 :: M22 IntCompose (V2 (V2 19 25) (V2 43 58))
trace :: FreeBialgebra a f => (f ** f) a -> a Source #
Trace of an endomorphism.
>>>trace $ m22 1.0 2.0 3.0 4.05.0