Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
\(d\)-dimensional vectors.
Synopsis
- module Data.Geometry.Vector.VectorFamily
- outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a)
- unit :: (Additive t, Num a) => ASetter' (t a) a -> t a
- scaled :: (Traversable t, Num a) => t a -> t (t a)
- basisFor :: (Traversable t, Num a) => t b -> [t a]
- basis :: (Additive t, Traversable t, Num a) => [t a]
- (^/) :: (Functor f, Fractional a) => f a -> a -> f a
- (^*) :: (Functor f, Num a) => f a -> a -> f a
- (*^) :: (Functor f, Num a) => a -> f a -> f a
- sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a
- negated :: (Functor f, Num a) => f a -> f a
- class Functor f => Additive (f :: Type -> Type) where
- data C (n :: Nat) = C
- class Additive (Diff p) => Affine (p :: Type -> Type) where
- quadrance :: (Metric f, Num a) => f a -> a
- qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a
- distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a
- dot :: (Metric f, Num a) => f a -> f a -> a
- norm :: (Metric f, Floating a) => f a -> a
- signorm :: (Metric f, Floating a) => f a -> f a
- isScalarMultipleOf :: (Eq r, Fractional r, Arity d) => Vector d r -> Vector d r -> Bool
- scalarMultiple :: (Eq r, Fractional r, Arity d) => Vector d r -> Vector d r -> Maybe r
- replicate :: Vector v a => a -> v a
- xComponent :: (1 <= d, Arity d) => Lens' (Vector d r) r
- yComponent :: (2 <= d, Arity d) => Lens' (Vector d r) r
- zComponent :: (3 <= d, Arity d) => Lens' (Vector d r) r
Documentation
outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a) #
Outer (tensor) product of two vectors
unit :: (Additive t, Num a) => ASetter' (t a) a -> t a #
Create a unit vector.
>>>
unit _x :: V2 Int
V2 1 0
scaled :: (Traversable t, Num a) => t a -> t (t a) #
Produce a diagonal (scale) matrix from a vector.
>>>
scaled (V2 2 3)
V2 (V2 2 0) (V2 0 3)
basisFor :: (Traversable t, Num a) => t b -> [t a] #
Produce a default basis for a vector space from which the argument is drawn.
basis :: (Additive t, Traversable t, Num a) => [t a] #
Produce a default basis for a vector space. If the dimensionality
of the vector space is not statically known, see basisFor
.
(^/) :: (Functor f, Fractional a) => f a -> a -> f a infixl 7 #
Compute division by a scalar on the right.
(^*) :: (Functor f, Num a) => f a -> a -> f a infixl 7 #
Compute the right scalar product
>>>
V2 3 4 ^* 2
V2 6 8
(*^) :: (Functor f, Num a) => a -> f a -> f a infixl 7 #
Compute the left scalar product
>>>
2 *^ V2 3 4
V2 6 8
sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a #
Sum over multiple vectors
>>>
sumV [V2 1 1, V2 3 4]
V2 4 5
negated :: (Functor f, Num a) => f a -> f a #
Compute the negation of a vector
>>>
negated (V2 2 4)
V2 (-2) (-4)
class Functor f => Additive (f :: Type -> Type) where #
A vector is an additive group with additional structure.
Nothing
The zero vector
(^+^) :: Num a => f a -> f a -> f a infixl 6 #
Compute the sum of two vectors
>>>
V2 1 2 ^+^ V2 3 4
V2 4 6
(^-^) :: Num a => f a -> f a -> f a infixl 6 #
Compute the difference between two vectors
>>>
V2 4 5 ^-^ V2 3 1
V2 1 4
lerp :: Num a => a -> f a -> f a -> f a #
Linearly interpolate between two vectors.
liftU2 :: (a -> a -> a) -> f a -> f a -> f a #
Apply a function to merge the 'non-zero' components of two vectors, unioning the rest of the values.
liftI2 :: (a -> b -> c) -> f a -> f b -> f c #
Apply a function to the components of two vectors.
- For a dense vector this is equivalent to
liftA2
. - For a sparse vector this is equivalent to
intersectionWith
.
Instances
A proxy which can be used for the coordinates.
class Additive (Diff p) => Affine (p :: Type -> Type) where #
An affine space is roughly a vector space in which we have forgotten or at least pretend to have forgotten the origin.
a .+^ (b .-. a) = b@ (a .+^ u) .+^ v = a .+^ (u ^+^ v)@ (a .-. b) ^+^ v = (a .+^ v) .-. q@
(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 #
Get the difference between two points as a vector offset.
(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 #
Add a vector offset to a point.
(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 #
Subtract a vector offset from a point.
Instances
quadrance :: (Metric f, Num a) => f a -> a #
Compute the squared norm. The name quadrance arises from Norman J. Wildberger's rational trigonometry.
qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a #
Compute the quadrance of the difference (the square of the distance)
distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a #
Distance between two points in an affine space
dot :: (Metric f, Num a) => f a -> f a -> a #
Compute the inner product of two vectors or (equivalently)
convert a vector f a
into a covector f a -> a
.
>>>
V2 1 2 `dot` V2 3 4
11
isScalarMultipleOf :: (Eq r, Fractional r, Arity d) => Vector d r -> Vector d r -> Bool Source #
'isScalarmultipleof u v' test if v is a scalar multiple of u.
>>>
Vector2 1 1 `isScalarMultipleOf` Vector2 10 10
True>>>
Vector3 1 1 2 `isScalarMultipleOf` Vector3 10 10 20
True>>>
Vector2 1 1 `isScalarMultipleOf` Vector2 10 1
False>>>
Vector2 1 1 `isScalarMultipleOf` Vector2 (-1) (-1)
True>>>
Vector2 1 1 `isScalarMultipleOf` Vector2 11.1 11.1
True>>>
Vector2 1 1 `isScalarMultipleOf` Vector2 11.1 11.2
False>>>
Vector2 2 1 `isScalarMultipleOf` Vector2 11.1 11.2
False>>>
Vector2 2 1 `isScalarMultipleOf` Vector2 4 2
True>>>
Vector2 2 1 `isScalarMultipleOf` Vector2 4 0
False>>>
Vector3 2 1 0 `isScalarMultipleOf` Vector3 4 0 5
False>>>
Vector3 0 0 0 `isScalarMultipleOf` Vector3 4 0 5
True
scalarMultiple :: (Eq r, Fractional r, Arity d) => Vector d r -> Vector d r -> Maybe r Source #
scalarMultiple u v computes the scalar labmda s.t. v = lambda * u (if it exists)
replicate :: Vector v a => a -> v a #
Replicate value n times.
Examples:
>>>
import Data.Vector.Fixed.Boxed (Vec2)
>>>
replicate 1 :: Vec2 Int
fromList [1,1]
>>>
replicate 2 :: (Double,Double,Double)
(2.0,2.0,2.0)
>>>
import Data.Vector.Fixed.Boxed (Vec4)
>>>
replicate "foo" :: Vec4 String
fromList ["foo","foo","foo","foo"]