| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Semimodule
Synopsis
- type Free f = (Representable f, Eq (Rep f))
- type Basis b f = (Free f, Rep f ~ b)
- type Module r a = (Ring r, Group a, Semimodule r a)
- class (Semiring r, Semigroup a) => Semimodule r a where
- multl :: Semiring a => Functor f => a -> f a -> f a
- multr :: Semiring a => Functor f => f a -> a -> f a
- negateDef :: Semimodule Integer a => a -> a
- lerp :: Module r a => r -> a -> a -> a
- (.*.) :: Free f => Foldable f => Semiring a => f a -> f a -> a
- quadrance :: Free f => Foldable f => Semiring a => f a -> a
- qd :: Free f => Foldable f => Module a (f a) => f a -> f a -> a
- dirac :: Eq i => Semiring a => i -> i -> a
- idx :: Free f => Semiring a => Rep f -> f a
Documentation
class (Semiring r, Semigroup a) => Semimodule r a where Source #
Semimodule over a commutative semiring.
All instances must satisfy the following identities:
r*.(x<>y)==r*.x<>r*.y
(r+s)*.x==r*.x<>s*.x
(r*s)*.x==r*.(s*.x)
When the ring of coefficients r is unital we must additionally have:
one*.x==x
See the properties module for a detailed specification of the laws.
Minimal complete definition
Nothing
Methods
(*.) :: r -> a -> a infixl 7 Source #
Left-multiply by a scalar.
(.*) :: a -> r -> a infixl 7 Source #
Right-multiply by a scalar.
Instances
multl :: Semiring a => Functor f => a -> f a -> f a Source #
Default definition of '(*.)' for a free module.
multr :: Semiring a => Functor f => f a -> a -> f a Source #
Default definition of '(.*)' for a free module.
negateDef :: Semimodule Integer a => a -> a Source #
Default definition of << for a commutative group.
lerp :: Module 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)
(.*.) :: Free f => Foldable f => Semiring a => f a -> f a -> a infix 6 Source #
Dot product.
>>>V3 1 2 3 .*. V3 1 2 314