| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Semimodule.Vector
Synopsis
- type Basis b f = (Free f, Rep f ~ b)
- (*.) :: Semimodule r a => r -> a -> a
- (.*) :: Semimodule r a => a -> r -> a
- (.*.) :: Free f => Foldable f => Semiring a => f a -> f a -> a
- (><) :: (Representable f, Algebra r (Rep f)) => f r -> f r -> f r
- triple :: Free f => Foldable f => Algebra a (Rep f) => f a -> f a -> f a -> a
- lerp :: Module r a => r -> a -> 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
- data I4
- data V4 a = V4 !a !a !a !a
- type QuaternionBasis = Maybe I3
- data I3
- data V3 a = V3 !a !a !a
- data I2
- data V2 a = V2 !a !a
- i2 :: a -> a -> I2 -> a
- fillI2 :: Basis I2 f => a -> a -> f a
- i3 :: a -> a -> a -> I3 -> a
- fillI3 :: Basis I3 f => a -> a -> a -> f a
- i4 :: a -> a -> a -> a -> I4 -> a
- fillI4 :: Basis I4 f => a -> a -> a -> a -> f a
Documentation
(*.) :: Semimodule r a => r -> a -> a infixl 7 Source #
Left-multiply by a scalar.
(.*) :: Semimodule r a => a -> r -> a infixl 7 Source #
Right-multiply by a scalar.
(.*.) :: Free f => Foldable f => Semiring a => f a -> f a -> a infix 6 Source #
Dot product.
>>>V3 1 2 3 .*. V3 1 2 314
(><) :: (Representable f, Algebra r (Rep f)) => f r -> f r -> f r infixl 7 Source #
Multiplication operator on a free algebra.
In particular this is cross product on the I3 basis in R^3:
>>>V3 1 0 0 >< V3 0 1 0 >< V3 0 1 0 :: V3 IntV3 (-1) 0 0>>>V3 1 0 0 >< (V3 0 1 0 >< V3 0 1 0) :: V3 IntV3 0 0 0
Caution in general (><) needn't be commutative, nor even associative.
The cross product in particular satisfies the following properties:
a><a =memptya><b =negate( b><a ) , a><( b <> c ) = ( a><b ) <> ( a><c ) , ( r a )><b = a><( r b ) = r ( a><b ) . a><( b><c ) <> b><( c><a ) <> c><( a><b ) =mempty.
See Jacobi identity.
For associative algebras, use (*) instead for clarity:
>>>(1 :+ 2) >< (3 :+ 4) :: Complex Int(-5) :+ 10>>>(1 :+ 2) * (3 :+ 4) :: Complex Int(-5) :+ 10>>>qi >< qj :: QuatMQuaternion 0.000000 (V3 0.000000 0.000000 1.000000)>>>qi * qj :: QuatMQuaternion 0.000000 (V3 0.000000 0.000000 1.000000)
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)
qd :: Free f => Foldable f => Module a (f a) => f a -> f a -> a Source #
Squared l2 norm of the difference between two vectors.
Constructors
| V4 !a !a !a !a |
Instances
| Functor V4 Source # | |
| Applicative V4 Source # | |
| Foldable V4 Source # | |
Defined in Data.Semimodule.Vector Methods fold :: Monoid m => V4 m -> m # foldMap :: Monoid m => (a -> m) -> V4 a -> m # foldr :: (a -> b -> b) -> b -> V4 a -> b # foldr' :: (a -> b -> b) -> b -> V4 a -> b # foldl :: (b -> a -> b) -> b -> V4 a -> b # foldl' :: (b -> a -> b) -> b -> V4 a -> b # foldr1 :: (a -> a -> a) -> V4 a -> a # foldl1 :: (a -> a -> a) -> V4 a -> a # elem :: Eq a => a -> V4 a -> Bool # maximum :: Ord a => V4 a -> a # | |
| Distributive V4 Source # | |
| Representable V4 Source # | |
| Foldable1 V4 Source # | |
| Semiring a => Semimodule a (V4 a) Source # | |
| Eq a => Eq (V4 a) Source # | |
| Ord a => Ord (V4 a) Source # | |
| Show a => Show (V4 a) Source # | |
| (Additive - Semigroup) a => Semigroup (Additive (V4 a)) Source # | Matrix addition.
|
| (Additive - Semigroup) a => Semigroup (V4 a) Source # | Vector addition.
|
| (Additive - Monoid) a => Monoid (Additive (V4 a)) Source # | |
| (Additive - Monoid) a => Monoid (V4 a) Source # | |
| (Additive - Group) a => Group (Additive (V4 a)) Source # | |
| (Additive - Group) a => Group (V4 a) Source # | |
Defined in Data.Semimodule.Vector | |
| (Additive - Group) a => Loop (Additive (V4 a)) Source # | |
| (Additive - Group) a => Loop (V4 a) Source # | |
Defined in Data.Semimodule.Vector | |
| (Additive - Group) a => Quasigroup (Additive (V4 a)) Source # | |
| (Additive - Group) a => Quasigroup (V4 a) Source # | |
| (Additive - Group) a => Magma (Additive (V4 a)) Source # | Matrix subtraction.
|
| (Additive - Group) a => Magma (V4 a) Source # | Vector subtraction.
|
| type Rep V4 Source # | |
Defined in Data.Semimodule.Vector | |
type QuaternionBasis = Maybe I3 Source #
Instances
| Eq I3 Source # | |
| Ord I3 Source # | |
| Show I3 Source # | |
| Field r => Division r QuaternionBasis Source # | |
Defined in Data.Semimodule.Vector Methods reciprocalWith :: (QuaternionBasis -> r) -> QuaternionBasis -> r Source # | |
| Ring r => Unital r QuaternionBasis Source # | |
Defined in Data.Semimodule.Vector Methods unitWith :: r -> QuaternionBasis -> r Source # | |
| Ring r => Composition r QuaternionBasis Source # | |
Defined in Data.Semimodule.Vector Methods conjugateWith :: (QuaternionBasis -> r) -> QuaternionBasis -> r Source # normWith :: (QuaternionBasis -> r) -> r Source # | |
| Ring r => Composition r I3 Source # | |
Defined in Data.Semimodule.Vector | |
| Ring r => Algebra r QuaternionBasis Source # | |
Defined in Data.Semimodule.Vector Methods multiplyWith :: (QuaternionBasis -> QuaternionBasis -> r) -> QuaternionBasis -> r Source # | |
| Ring r => Algebra r I3 Source # | |
Defined in Data.Semimodule.Vector | |
| Semigroup (Additive I3) Source # | |
| Monoid (Additive I3) Source # | |
Constructors
| V3 !a !a !a |
Instances
| Functor V3 Source # | |
| Applicative V3 Source # | |
| Foldable V3 Source # | |
Defined in Data.Semimodule.Vector Methods fold :: Monoid m => V3 m -> m # foldMap :: Monoid m => (a -> m) -> V3 a -> m # foldr :: (a -> b -> b) -> b -> V3 a -> b # foldr' :: (a -> b -> b) -> b -> V3 a -> b # foldl :: (b -> a -> b) -> b -> V3 a -> b # foldl' :: (b -> a -> b) -> b -> V3 a -> b # foldr1 :: (a -> a -> a) -> V3 a -> a # foldl1 :: (a -> a -> a) -> V3 a -> a # elem :: Eq a => a -> V3 a -> Bool # maximum :: Ord a => V3 a -> a # | |
| Distributive V3 Source # | |
| Representable V3 Source # | |
| Foldable1 V3 Source # | |
| Semiring a => Semimodule a (V3 a) Source # | |
| Eq a => Eq (V3 a) Source # | |
| Ord a => Ord (V3 a) Source # | |
| Show a => Show (V3 a) Source # | |
| (Additive - Semigroup) a => Semigroup (Additive (V3 a)) Source # | Matrix addition.
|
| (Additive - Semigroup) a => Semigroup (V3 a) Source # | Vector addition.
|
| (Additive - Monoid) a => Monoid (Additive (V3 a)) Source # | |
| (Additive - Monoid) a => Monoid (V3 a) Source # | |
| (Additive - Group) a => Group (Additive (V3 a)) Source # | |
| (Additive - Group) a => Group (V3 a) Source # | |
Defined in Data.Semimodule.Vector | |
| (Additive - Group) a => Loop (Additive (V3 a)) Source # | |
| (Additive - Group) a => Loop (V3 a) Source # | |
Defined in Data.Semimodule.Vector | |
| (Additive - Group) a => Quasigroup (Additive (V3 a)) Source # | |
| (Additive - Group) a => Quasigroup (V3 a) Source # | |
| (Additive - Group) a => Magma (Additive (V3 a)) Source # | Matrix subtraction.
|
| (Additive - Group) a => Magma (V3 a) Source # | Vector subtraction.
|
| type Rep V3 Source # | |
Defined in Data.Semimodule.Vector | |
Constructors
| V2 !a !a |
Instances
| Functor V2 Source # | |
| Applicative V2 Source # | |
| Foldable V2 Source # | |
Defined in Data.Semimodule.Vector Methods fold :: Monoid m => V2 m -> m # foldMap :: Monoid m => (a -> m) -> V2 a -> m # foldr :: (a -> b -> b) -> b -> V2 a -> b # foldr' :: (a -> b -> b) -> b -> V2 a -> b # foldl :: (b -> a -> b) -> b -> V2 a -> b # foldl' :: (b -> a -> b) -> b -> V2 a -> b # foldr1 :: (a -> a -> a) -> V2 a -> a # foldl1 :: (a -> a -> a) -> V2 a -> a # elem :: Eq a => a -> V2 a -> Bool # maximum :: Ord a => V2 a -> a # | |
| Distributive V2 Source # | |
| Representable V2 Source # | |
| Foldable1 V2 Source # | |
| Semiring a => Semimodule a (V2 a) Source # | |
| Eq a => Eq (V2 a) Source # | |
| Ord a => Ord (V2 a) Source # | |
| Show a => Show (V2 a) Source # | |
| (Additive - Semigroup) a => Semigroup (Additive (V2 a)) Source # | Matrix addition.
|
| (Additive - Semigroup) a => Semigroup (V2 a) Source # | Vector addition.
|
| (Additive - Monoid) a => Monoid (Additive (V2 a)) Source # | |
| (Additive - Monoid) a => Monoid (V2 a) Source # | |
| (Additive - Group) a => Group (Additive (V2 a)) Source # | |
| (Additive - Group) a => Group (V2 a) Source # | |
Defined in Data.Semimodule.Vector | |
| (Additive - Group) a => Loop (Additive (V2 a)) Source # | |
| (Additive - Group) a => Loop (V2 a) Source # | |
Defined in Data.Semimodule.Vector | |
| (Additive - Group) a => Quasigroup (Additive (V2 a)) Source # | |
| (Additive - Group) a => Quasigroup (V2 a) Source # | |
| (Additive - Group) a => Magma (Additive (V2 a)) Source # | Matrix subtraction.
|
| (Additive - Group) a => Magma (V2 a) Source # | Vector subtraction.
|
| type Rep V2 Source # | |
Defined in Data.Semimodule.Vector | |