GlomeVec-0.2: Simple 3D vector library

Safe HaskellSafe-Inferred

Data.Glome.Vec

Synopsis

Documentation

type Flt = DoubleSource

Performance is pretty similar with Floats or Doubles. Todo: make separate Float and Double instances of this library.

deg :: Flt -> FltSource

Convert from degrees to native angle format (radians).

rad :: Flt -> FltSource

Convert from radians to native format (noop).

rot :: Flt -> FltSource

Convert from rotations to native format. (rot 1 == deg 360)

dcos :: Flt -> FltSource

Trig with degrees instead of radians.

clamp :: Flt -> Flt -> Flt -> FltSource

Force a value to be within a range. Usage: clamp min x max

delta :: FltSource

Tuning parameter.

fmin :: Flt -> Flt -> FltSource

Non-polymorphic fmin; this speeds things up in ocaml, not sure about haskell.

fmax :: Flt -> Flt -> FltSource

Non-polymorphic fmax.

fmin3 :: Flt -> Flt -> Flt -> FltSource

Non-polymorphic min of 3 values.

fmax3 :: Flt -> Flt -> Flt -> FltSource

Non-polymorphic max of 3 values.

fmin4 :: Flt -> Flt -> Flt -> Flt -> FltSource

Min of 4 values.

fmax4 :: Flt -> Flt -> Flt -> Flt -> FltSource

Max of 4 values.

fabs :: Flt -> FltSource

Non-polymorphic absolute value.

iabs :: Int -> IntSource

Non-polymorphic integer absolute value.

abs :: t -> t1Source

Force user to use fabs or iabs, for performance reasons. Not sure if this really helps, though.

about_equal :: Flt -> Flt -> BoolSource

Approximate equality for Flt. True if a and b are almost equal. The (abs $ a-b) test doesn't work if a and b are large.

data Vec Source

3d type represented as a record of unboxed floats.

Constructors

Vec !Flt !Flt !Flt 

Instances

data Ray Source

A Ray is made up of an origin and direction Vec.

Constructors

Ray 

Fields

origin :: !Vec
 
dir :: !Vec
 

Instances

ray_ub :: Ray -> (#Flt, Flt, Flt, Flt, Flt, Flt#)Source

vec :: Flt -> Flt -> Flt -> VecSource

Vec constructor.

vzero :: VecSource

Zero Vec.

vunit :: VecSource

For when we need a unit vector, but we don't care where it points.

vx :: VecSource

Unit X vector.

vy :: VecSource

Unit y vector.

vz :: VecSource

Unit z vector.

nvx :: VecSource

Negative x vector.

nvy :: VecSource

Negative y vector.

nvz :: VecSource

Negative z vector.

va :: Vec -> Int -> FltSource

Access the Vec as if it were an array indexed from 0..2. Note: this actually accounts for a noticeable amount of cpu time in the Glome ray tracer.

vset :: Vec -> Int -> Flt -> VecSource

Create a new Vec with the Nth field overwritten by new value. I could have used record update syntax.

vdot :: Vec -> Vec -> FltSource

Dot product of 2 vectors. We use this all the time. Dot product of 2 normal vectors is the cosine of the angle between them.

vcross :: Vec -> Vec -> VecSource

Cross product of 2 vectors. Produces a vector perpendicular to the given vectors. We use this for things like making the forward, up, and right camera vectors orthogonal. If the input vectors are normalized, the output vector will be as well.

vmap :: (Flt -> Flt) -> Vec -> VecSource

Apply a unary Flt operator to each field of the Vec.

vmap2 :: (Flt -> Flt -> Flt) -> Vec -> Vec -> VecSource

Apply a binary Flt operator to pairs of fields from 2 Vecs.

vinvert :: Vec -> VecSource

Reverse the direction of a Vec.

vlensqr :: Vec -> FltSource

Get the length of a Vec squared. We use this to avoid a slow sqrt.

vlen :: Vec -> FltSource

Get the length of a Vec. This is expensive because sqrt is slow.

vadd :: Vec -> Vec -> VecSource

Add 2 vectors.

vadd3 :: Vec -> Vec -> Vec -> VecSource

Add 3 vectors.

vsub :: Vec -> Vec -> VecSource

Subtract vectors. vsub b a is the vector from a to b.

vmul :: Vec -> Vec -> VecSource

Multiply corresponding fields. Rarely useful.

vinc :: Vec -> Flt -> VecSource

Add a value to all the fields of a Vec. Useful, for instance, to get one corner of the bounding box around a sphere.

vdec :: Vec -> Flt -> VecSource

Subtract a value from all fields of a Vec.

vmax :: Vec -> Vec -> VecSource

Get the maximum of all corresponding fields between 2 Vecs.

vmin :: Vec -> Vec -> VecSource

Get the minimum of all corresponding fields between 2 Vecs.

vmaxaxis :: Vec -> IntSource

Return the largest axis. Often used with va.

vscale :: Vec -> Flt -> VecSource

Scale a Vec by some value.

vscaleadd :: Vec -> Vec -> Flt -> VecSource

Take the first Vec, and add to it the second Vec scaled by some amount. This is used quite a lot in Glome.

vnudge :: Vec -> VecSource

Make the length of a Vec just a little shorter.

vnorm :: Vec -> VecSource

Normalize a vector. Division is expensive, so we compute the reciprocol of the length and multiply by that. The sqrt is also expensive.

assert_norm :: Vec -> VecSource

Throw an exception if a vector hasn't been normalized.

bisect :: Vec -> Vec -> VecSource

Get the victor bisecting two other vectors (which ought to be the same length).

vdist :: Vec -> Vec -> FltSource

Distance between 2 vectors.

reflect :: Vec -> Vec -> VecSource

Reflect a vector v off of a surface with normal norm.

vrcp :: Vec -> VecSource

Reciprocol of all fields of a Vec.

veq :: Vec -> Vec -> BoolSource

Test Vecs for approximate equality

veqsign :: Vec -> Vec -> BoolSource

Test Vecs for matching sign on all fields. Returns false if any value is zero. Used by packet tracing.

ray_move :: Ray -> Flt -> RaySource

Translate a ray's origin in ray's direction by d amount.

orth :: Vec -> (Vec, Vec)Source

Find a pair of orthogonal vectors to the one given.

plane_int :: Ray -> Vec -> Vec -> VecSource

Intersect a ray with a plane defined by a point p and a normal norm. (Ray does not need to be normalized.)

plane_int_dist :: Ray -> Vec -> Vec -> FltSource

Find the distance along a ray until it intersects with a plane defined by a point p and normal norm.

data Matrix Source

3x4 Transformation matrix. These are described in most graphics texts.

Constructors

Matrix !Flt !Flt !Flt !Flt !Flt !Flt !Flt !Flt !Flt !Flt !Flt !Flt 

Instances

data Xfm Source

A transformation. Inverting a matrix is expensive, so we keep a forward transformation matrix and a reverse transformation matrix. Note: This can be made a little faster if the matricies are non-strict.

Constructors

Xfm Matrix Matrix 

Instances

ident_matrix :: MatrixSource

Identity matrix. Transforming a vector by this matrix does nothing.

ident_xfm :: XfmSource

Identity transformation.

mat_mult :: Matrix -> Matrix -> MatrixSource

Multiply two matricies. This is unrolled for efficiency, and it's also a little bit easier (in my opinion) to see what's going on.

xfm_mult :: Xfm -> Xfm -> XfmSource

Multiply two tranformations. This just multiplies the forward and reverse transformations.

compose :: [Xfm] -> XfmSource

There is a seemingly-magical property of transformation matricies, that we can combine the effects of any number of transformations into a single transformation just by multiplying them together in reverse order. For instance, we could move a point, then rotate it about the origin by some angle around some vector, then move it again, and this can all be done by a single transformation. This function combines transformations in this way, though it reverses the list first so the transformations take effect in their expected order.

check_xfm :: Xfm -> XfmSource

Make sure a transformation is valid. Multipy the forward and reverse matrix and verify that the result is the identity matrix.

vrotate :: Vec -> Ray -> Flt -> VecSource

Complex transformations: Rotate point (or vector) pt about ray by angle c. The angle is in radians, but using the angle conversion routines deg, rad and rot is recommended.

xfm_point :: Xfm -> Vec -> VecSource

Transform a point. The point is treated as (x y z 1).

invxfm_point :: Xfm -> Vec -> VecSource

Inverse transform a point.

xfm_vec :: Xfm -> Vec -> VecSource

Transform a vector. The vector is treated as (x y z 0).

invxfm_vec :: Xfm -> Vec -> VecSource

Inverse transform a vector.

invxfm_norm :: Xfm -> Vec -> VecSource

Inverse transform a normal. This one is tricky: we need to transform by the inverse transpose.

xfm_ray :: Xfm -> Ray -> RaySource

Transform a Ray.

invxfm_ray :: Xfm -> Ray -> RaySource

Inverse transform a Ray.

translate :: Vec -> XfmSource

Basic transforms: move by some displacement vector.

scale :: Vec -> XfmSource

Basic transforms: stretch along the three axes, by the amount in the given vector. (If x==y==z, then it's uniform scaling.)

rotate :: Vec -> Flt -> XfmSource

Basic transforms: rotate about a given axis by some angle.

xyz_to_uvw :: Vec -> Vec -> Vec -> XfmSource

Basic transforms: Convert coordinate system from canonical xyz coordinates to uvw coordinates.

uvw_to_xyz :: Vec -> Vec -> Vec -> XfmSource

Basic transforms: Convert from uvw coordinates back to normal xyz coordinates.

sas2s :: Flt -> Flt -> Flt -> FltSource

Given a side, angle, and side of a triangle, produce the length of the opposite side.

data Bbox Source

Axis-aligned Bounding Box (AABB), defined by opposite corners. P1 is the min values, p2 has the max values.

Constructors

Bbox 

Fields

p1 :: !Vec
 
p2 :: !Vec
 

Instances

data Interval Source

A near-far pair of distances. Basically just a tuple.

Constructors

Interval !Flt !Flt 

Instances

bbjoin :: Bbox -> Bbox -> BboxSource

Bounding box that encloses two bounding boxes.

bboverlap :: Bbox -> Bbox -> BboxSource

Find the overlap of two bounding boxes.

bbinside :: Bbox -> Vec -> BoolSource

Test if a Vec is inside the bounding box.

bbsplit :: Bbox -> Int -> Flt -> (Bbox, Bbox)Source

Split a bounding box into two, given an axis and offset. Throw exception if the offset isn't inside the bounding box.

bbpts :: [Vec] -> BboxSource

Generate a minimum bounding box that encloses a list of points.

bbsa :: Bbox -> FltSource

Surface area of a bounding box. Useful for cost heuristics when attempting to build optimal bounding box heirarchies. Undefined for degenerate bounding boxes.

bbvol :: Bbox -> FltSource

Volume of a bounding box. Undefined for degenerate bounding boxes.

empty_bbox :: BboxSource

Degenerate bounding box that contains an empty volume.

bbclip_ub :: Ray -> Bbox -> (#Flt, Flt#)Source

Find a ray's entrance and exit from a bounding box. If last entrance is before the first exit, we hit. Otherwise, we miss. (It's up to the caller to figure that out.)