simple-vec3-0.4.0.1: Three-dimensional vectors of doubles with basic operations

Safe HaskellNone
LanguageHaskell2010

Data.Vec3

Contents

Description

Vec3 class and implementations.

The package provides two different implementations for Vec3 type class, which differ in storage scheme. Benchmarks are included for both. You most likely want to use CVec3 which is based on contiguous storage scheme and offers the best performance.

Synopsis

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 .* v2
0.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)

class Vec3 v where Source #

Three-dimensional vector, with an associated matrix type.

Minimal complete definition

fromXYZ, toXYZ, fromRows, toRows

Associated Types

data Matrix v Source #

Associated type for 3×3 matrix.

Methods

origin :: v Source #

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 Source #

Add two vectors.

(<->) :: v -> v -> v Source #

Subtract two vectors.

(><) :: v -> v -> v Source #

Cross product.

(.^) :: v -> Double -> v Source #

Scale a vector.

(.*) :: v -> v -> Double Source #

Dot product.

norm :: v -> Double Source #

Euclidean norm of a vector.

normalize :: v -> v Source #

Produce unit vector with the same direction as the original one.

distance :: v -> v -> Double Source #

Distance between two points.

invert :: v -> v Source #

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

Vec3 TVec3 Source # 
Vec3 CVec3 Source # 

Implementations

data CVec3 Source #

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.

Constructors

CVec3 !Double !Double !Double 

Instances

Eq CVec3 Source # 

Methods

(==) :: CVec3 -> CVec3 -> Bool #

(/=) :: CVec3 -> CVec3 -> Bool #

Show CVec3 Source # 

Methods

showsPrec :: Int -> CVec3 -> ShowS #

show :: CVec3 -> String #

showList :: [CVec3] -> ShowS #

Arbitrary CVec3 Source # 

Methods

arbitrary :: Gen CVec3 #

shrink :: CVec3 -> [CVec3] #

Storable CVec3 Source # 

Methods

sizeOf :: CVec3 -> Int #

alignment :: CVec3 -> Int #

peekElemOff :: Ptr CVec3 -> Int -> IO CVec3 #

pokeElemOff :: Ptr CVec3 -> Int -> CVec3 -> IO () #

peekByteOff :: Ptr b -> Int -> IO CVec3 #

pokeByteOff :: Ptr b -> Int -> CVec3 -> IO () #

peek :: Ptr CVec3 -> IO CVec3 #

poke :: Ptr CVec3 -> CVec3 -> IO () #

Unbox CVec3 Source # 
Vec3 CVec3 Source # 
Vector Vector CVec3 Source # 
MVector MVector CVec3 Source # 
Eq (Matrix CVec3) Source # 
Show (Matrix CVec3) Source # 
Arbitrary (Matrix CVec3) Source # 
data Vector CVec3 Source # 
data Matrix CVec3 Source # 
data MVector s CVec3 Source # 

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.