Safe Haskell | Safe |
---|---|
Language | Haskell98 |
The module with all the different type-classes for vectors. Generally, the main functions you might need from this function are:
magSq
andmag
(defined for all vectors).getX
andgetY
(defined for all vectors) as well asgetZ
(defined for all vectors with 3 or more dimensions).dotProduct
,unitVector
,averageVec
,averageUnitVec
,sameDirection
,projectOnto
,projectPointOnto
,distFrom
(defined for all vectors).iso
, which is defined for all combinations of vectors with the same number of dimensions.
The rest of the functions are mainly just wiring necessary for other functions, but must be exported.
As to the vector types, there are two methods to use this library. One is to use the types from the Data.SG.Vector.Basic library, which support basic vector operations. The other is to use the types from the Data.SG.Geometry.TwoDim and Data.SG.Geometry.ThreeDim modules, where a position vector is differentiated from a relative vector (to increase clarity of code, and help prevent errors such as adding two points together). Both systems can be used with various useful functions (involving lines too) from Data.SG.Geometry.
- class IsomorphicVectors from to where
- class Foldable p => Coord p where
- class Coord p => Coord2 p where
- class Coord2 p => Coord3 p where
- origin :: (Coord p, Num a) => p a
- mag :: (Coord p, Floating a) => p a -> a
- unitVector :: (Coord p, VectorNum p, Ord a, Floating a) => p a -> p a
- averageVec :: (Fractional a, VectorNum p, Num (p a)) => [p a] -> p a
- averageUnitVec :: (Floating a, Ord a, Coord p, VectorNum p, Num (p a)) => [p a] -> p a
- sameDirection :: (VectorNum rel, Coord rel, Ord a, Floating a) => rel a -> rel a -> Bool
- projectOnto :: (Floating a, Ord a, VectorNum rel, Coord rel) => rel a -> rel a -> a
- projectOnto2 :: (Floating a, Ord a, VectorNum rel, Coord rel) => rel a -> (rel a, rel a) -> rel a
- projectPointOnto :: (Floating a, Ord a, VectorNum rel, Coord rel, IsomorphicVectors pt rel) => pt a -> rel a -> a
- projectPointOnto2 :: (Floating a, Ord a, VectorNum rel, Coord rel, IsomorphicVectors pt rel, Coord pt) => pt a -> (rel a, rel a) -> pt a
- distFrom :: (VectorNum pt, Coord pt, Floating a) => pt a -> pt a -> a
- class VectorNum f where
Documentation
class IsomorphicVectors from to where Source #
An isomorphism amongst vectors. Allows you to convert between two vectors that have the same dimensions. You will notice that all the instances reflect this.
class Foldable p => Coord p where Source #
The class that is implemented by all vectors.
Minimal implementation: fromComponents
getComponents :: Num a => p a -> [a] Source #
Gets the components of the vector, in the order x, y (, z).
fromComponents :: Num a => [a] -> p a Source #
Re-constructs a vector from the list of coordinates. If there are too few, the rest will be filled with zeroes. If there are too many, the latter ones are ignored.
magSq :: Num a => p a -> a Source #
Gets the magnitude squared of the vector. This should be fast for
repeated calls on Rel2'
and
Rel3'
, which cache this value.
dotProduct :: Num a => p a -> p a -> a Source #
Computes the dot product of the two vectors.
class Coord p => Coord2 p where Source #
This class is implemented by all 2D and 3D vectors, so getX
gets the X co-ordinate
of both 2D and 3D vectors.
origin :: (Coord p, Num a) => p a Source #
The origin/all-zero vector (can be used with any vector type you like)
unitVector :: (Coord p, VectorNum p, Ord a, Floating a) => p a -> p a Source #
Scales the vector so that it has length 1. Note that due to floating-point inaccuracies and so on, mag (unitVector v) will not necessarily equal 1, but it should be very close. If an all-zero vector is passed, the same will be returned.
This function should be very fast when called on
Rel2'
and Rel3'
;
vectors that are already unit vectors (no processing is done).
averageVec :: (Fractional a, VectorNum p, Num (p a)) => [p a] -> p a Source #
Gets the average vector of all the given vectors. Essentially it is the
sum of the vectors, divided by the length, so averageVec [Point2 (-3, 0), Point2
(5,0)]
will give Point2 (1,0)
. If the list is empty, the
all-zero vector is returned.
averageUnitVec :: (Floating a, Ord a, Coord p, VectorNum p, Num (p a)) => [p a] -> p a Source #
Like averageVec composed with unitVector -- gets the average of the vectors in the list, and normalises the length. If the list is empty, the all-zero vector is returned (which is therefore not a unit vector). Similarly, if the average of all the vectors is all-zero, the all-zero vector will be returned.
sameDirection :: (VectorNum rel, Coord rel, Ord a, Floating a) => rel a -> rel a -> Bool Source #
Works out if the two vectors are in the same direction (to within a small tolerance).
projectOnto :: (Floating a, Ord a, VectorNum rel, Coord rel) => rel a -> rel a -> a Source #
Gives back the vector (first parameter), translated onto given axis (second parameter). Note that the scale is always distance, not related to the size of the axis vector.
projectOnto2 :: (Floating a, Ord a, VectorNum rel, Coord rel) => rel a -> (rel a, rel a) -> rel a Source #
Projects the first parameter onto the given axes (X, Y), returning a point in terms of the new axes.
projectPointOnto :: (Floating a, Ord a, VectorNum rel, Coord rel, IsomorphicVectors pt rel) => pt a -> rel a -> a Source #
Gives back the point (first parameter), translated onto given axis (second parameter). Note that the scale is always distance, not related to the size of the axis vector.
projectPointOnto2 :: (Floating a, Ord a, VectorNum rel, Coord rel, IsomorphicVectors pt rel, Coord pt) => pt a -> (rel a, rel a) -> pt a Source #
Projects the point (first parameter) onto the given axes (X, Y), returning a point in terms of the new axes.
distFrom :: (VectorNum pt, Coord pt, Floating a) => pt a -> pt a -> a Source #
Works out the distance between two points.
class VectorNum f where Source #
A modified version of Functor
and Applicative
that adds the Num
constraint on the result. You are unlikely to need to use this class much
directly. Some vectors have Functor
and Applicative
instances anyway.
fmapNum1 :: Num b => (a -> b) -> f a -> f b Source #
fmapNum2 :: Num c => (a -> b -> c) -> f a -> f b -> f c Source #
fmapNum1inv :: Num a => (a -> a) -> f a -> f a Source #
Like fmapNum1
, but can only be used if you won't change the magnitude:
simpleVec :: Num a => a -> f a Source #
Like pure
(or fromInteger
) but with a Num
constraint.