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

Safe HaskellNone
LanguageHaskell2010

Data.Vec3

Description

Vec3 class and implementations.

Synopsis

Documentation

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 UVec3 Source # 
Vec3 UVec3 Source # 
Vec3 SVec3 Source # 

data SVec3 Source #

Vec3 implementation with Storable instance based on a single contiguous array storage scheme, suitable for use with Data.Vector.Storable.

Unbox instance provides the required index transformations.

interface: [d1 x   y   z  ; d2 x   y   z  ...], length = N = M / 3
               |   |   |       |   |   |
storage:   [  d1x d2y d2z ;   d2x d2y d2z ...], length = M

Constructors

SVec3 !CDouble !CDouble !CDouble 

Instances

Eq SVec3 Source # 

Methods

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

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

Show SVec3 Source # 

Methods

showsPrec :: Int -> SVec3 -> ShowS #

show :: SVec3 -> String #

showList :: [SVec3] -> ShowS #

Arbitrary SVec3 Source # 

Methods

arbitrary :: Gen SVec3 #

shrink :: SVec3 -> [SVec3] #

Storable SVec3 Source # 

Methods

sizeOf :: SVec3 -> Int #

alignment :: SVec3 -> Int #

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

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

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

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

peek :: Ptr SVec3 -> IO SVec3 #

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

Vec3 SVec3 Source # 
Eq (Matrix SVec3) Source # 
Show (Matrix SVec3) Source # 
data Matrix SVec3 Source # 

newtype UVec3 Source #

Vec3 implementation with Unbox instance based on tuples, suitable for use with Data.Vector.Unboxed.

This represents 3-vector as a triple of doubles, using the default Unbox instance for tuples as provided by Data.Vector.Unboxed, which wraps a vector of tuples as a tuple of vectors.

interface:  [d1 (x, y, z); d2 (x, y, z) ...], length = N
                 |  |  |       |  |  |
storage(x): [d1x-+  |  | ; d2x-+  |  |  ...], length = N
storage(y): [d1y----+  | ; d2y----+  |  ...], length = N
storage(z): [d1z-------+ ; d2z-------+  ...], length = N

Constructors

UVec3 (Double, Double, Double) 

Instances

Eq UVec3 Source # 

Methods

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

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

Show UVec3 Source # 

Methods

showsPrec :: Int -> UVec3 -> ShowS #

show :: UVec3 -> String #

showList :: [UVec3] -> ShowS #

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