| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Vec3
Contents
Description
Synopsis
- class Vec3 v where
- data Matrix v
- origin :: v
- fromXYZ :: (Double, Double, Double) -> v
- toXYZ :: v -> (Double, Double, Double)
- zipWith :: (Double -> Double -> Double) -> v -> v -> v
- (<+>) :: v -> v -> v
- (<->) :: v -> v -> v
- (><) :: v -> v -> v
- (.^) :: v -> Double -> v
- (.*) :: v -> v -> Double
- norm :: v -> Double
- normalize :: v -> v
- distance :: v -> v -> Double
- invert :: v -> v
- fromRows :: (v, v, v) -> Matrix v
- toRows :: Matrix v -> (v, v, v)
- dotM :: v -> v -> Matrix v -> Double
- mxv :: Matrix v -> v -> v
- diag :: Double -> Matrix v
- vxv :: v -> v -> Matrix v
- addM :: Matrix v -> Matrix v -> Matrix v
- data CVec3 = CVec3 !Double !Double !Double
- type TVec3 = (Double, Double, Double)
Examples
>>>let v1 = (-1, 0.0, 0.2) :: TVec3>>>let v2 = ( 1, 2.3, 5.0) :: TVec3>>>let v3 = ( 1, 1, -0.2) :: TVec3
Add two vectors:
>>>v1 <+> v2(0.0,2.3,5.2)
Dot product:
>>>v1 .* v20.0
Multiply by a scalar:
>>>v1 .^ 5(-5.0,0.0,1.0)
Cross product:
>>>v1 >< v3(-0.2,0.0,-1.0)
Matrix-vector product:
>>>diag 2 `mxv` v2(2.0,4.6,10.0)
Three-dimensional vector, with an associated matrix type.
Methods
Origin point (0, 0, 0).
fromXYZ :: (Double, Double, Double) -> v Source #
Construct a new vector from components.
toXYZ :: v -> (Double, Double, Double) Source #
Deconstruct a vector into components.
zipWith :: (Double -> Double -> Double) -> v -> v -> v Source #
Zip two vectors elementwise.
(<+>) :: v -> v -> v infixl 7 Source #
Add two vectors.
(<->) :: v -> v -> v infixl 7 Source #
Subtract two vectors.
(><) :: v -> v -> v infixl 8 Source #
Cross product.
(.^) :: v -> Double -> v infixl 9 Source #
Scale a vector.
(.*) :: v -> v -> Double infixl 8 Source #
Dot product.
Euclidean norm of a vector.
Produce unit vector with the same direction as the original one.
distance :: v -> v -> Double Source #
Distance between two points.
Invert the direction of a vector.
fromRows :: (v, v, v) -> Matrix v Source #
Construct a new matrix from rows.
toRows :: Matrix v -> (v, v, v) Source #
Deconstruct a matrix into rows.
dotM :: v -> v -> Matrix v -> Double Source #
Generic vector dot product.
Multiply the transpose of the first vector by the given matrix, then multiply the result by the second vector.
[ a11 a12 a13 ] [ v2x ]
[ ] [ ]
[ v1x v1y v1z ] . [ a21 a22 a23 ] . [ v2y ] = s
[ ] [ ]
[ a31 a32 a33 ] [ v2z ]
mxv :: Matrix v -> v -> v Source #
Multiply a matrix and a vector.
[ a11 a12 a13 ] [ v2x ] [ rx ] [ ] [ ] [ ] [ a21 a22 a23 ] . [ v2y ] = [ ry ] [ ] [ ] [ ] [ a31 a32 a33 ] [ v2z ] [ rz ]
diag :: Double -> Matrix v Source #
Build a diagonal matrix from a number d.
[ d 0 0 ] [ ] [ 0 d 0 ] [ ] [ 0 0 d ]
vxv :: v -> v -> Matrix v Source #
Transpose a vector and multiply it by another vector, producing a matrix.
[ v1x ] [ r11 r12 r13 ] [ ] [ ] [ v1y ] . [ v2x v2y v2z ] = [ r21 r22 r23 ] [ ] [ ] [ v1z ] [ r31 r32 r33 ]
addM :: Matrix v -> Matrix v -> Matrix v Source #
Add two matrices.
Instances
Implementations
Vec3 implementation with Unbox and
Storable instances based on a single
contiguous array storage scheme, suitable for use with
Data.Vector.Unboxed and Data.Vector.Storable.
interface: [v1 x y z ; v2 x y z ...], length = N = M / 3
| | | | | |
storage: [ v1x v2y v2z ; v2x v2y v2z ...], length = M
This implementation has the best performance.
Instances
type TVec3 = (Double, Double, Double) Source #
Vec3 implementation with Unbox instance
based on default Unbox instance for tuples of arrays, which wraps a
vector of tuples as a tuple of vectors.
interface: [v1 (x, y, z); v2 (x, y, z) ...], length = N
| | | | | |
storage(x): [v1x-+ | | ; v2x-+ | | ...], length = N
storage(y): [v1y----+ | ; v2y----+ | ...], length = N
storage(z): [v1z-------+ ; v2z-------+ ...], length = N
You almost definitely want to use CVec3 instead as it has better
performance.