GlomeTrace-0.3: Ray Tracing Library

Safe HaskellSafe-Inferred

Data.Glome.Solid

Synopsis

Documentation

data Rayint tag mat Source

Ray intersection type. If we hit, we store the distance from the ray origin, the position, the normal, the transformed ray, UV coordinates (plus a 3rd coordinate we'll call W) and the texture and tag stacks attached to the object.

Constructors

RayHit 

Fields

ridepth' :: !Flt
 
ripos :: !Vec
 
rinorm :: !Vec
 
riray :: !Ray
 
riuvw :: !Vec
 
ritex :: [Texture tag mat]
 
ritag :: [tag]
 
RayMiss 

Instances

Read (Texture () (Material ())) 
Show (Texture t m)

This is sort of a no-op; textures are functions, and we don't have a good way to show an arbitrary function

Show tag => Show (Rayint tag mat) 

ridepth :: Rayint tag mat -> FltSource

nearest :: Rayint tag mat -> Rayint tag mat -> Rayint tag matSource

Pick the closest of two Rayints

furthest :: Rayint tag mat -> Rayint tag mat -> Rayint tag matSource

Pick the furthest of two Rayints

hit :: Rayint tag mat -> BoolSource

Test if a Rayint is a hit or a miss

dist :: Rayint tag mat -> FltSource

Extract a distance from a Rayint, with infinity for a miss

data PacketResult tag mat Source

Sometimes, it's more efficient to trace multiple rays against an acceleration structure at the same time, provided the rays are almost identical. A PacketResult is the result of tracing 4 rays at once.

Constructors

PacketResult (Rayint tag mat) (Rayint tag mat) (Rayint tag mat) (Rayint tag mat) 

rayint_advance :: SolidItem tag mat -> Ray -> Flt -> [Texture tag mat] -> [tag] -> Flt -> Rayint tag matSource

Move a ray forward and test the new ray against an object. Fix the depth of the result. Useful in CSG

type Texture tag mat = Ray -> Rayint tag mat -> matSource

A texture is a function that takes a Rayint and returns a material. A material will later be rendered by a shader (which in turn can append more tags).

newtype Pcount Source

Constructors

Pcount (Int, Int, Int) 

Instances

debug_wrap :: (Rayint tag mat, Int) -> Int -> (Rayint tag mat, Int)Source

nearest_debug :: (Rayint tag mat, Int) -> (Rayint tag mat, Int) -> (Rayint tag mat, Int)Source

class Show s => Solid s t m | s -> t, s -> m whereSource

A solid is something we can test a ray against or do inside/outside tests. Some of these are simple solids like Sphere or Triangle, but others are composite solids than have other solids as children.

Methods

rayintSource

Arguments

:: s

object to test against

-> Ray

ray

-> Flt

maximum distance we care about

-> [Texture t m]

current texture stack (Tex object pushes new textures)

-> [t]

tag stack (Tag object pushes new tags)

-> Rayint t m

we return a Rayint describing the hit location

Test a ray against a solid, returning a ray intersection. The distance parameter is used to specify a max distance. If it's further away, we aren't interested in the intersection. The b parameter is a default tag, if it's not overridden by a more specific tag (which is useful if we need to be able to identify the thing that was hit).

rayint_debug :: s -> Ray -> Flt -> [Texture t m] -> [t] -> (Rayint t m, Int)Source

Same as rayint, but return a count of the number of primitives checked. Useful for optimizing acceleration structures.

packetint :: s -> Ray -> Ray -> Ray -> Ray -> Flt -> [Texture t m] -> [t] -> PacketResult t mSource

Trace four rays at once against a solid.

shadow :: s -> Ray -> Flt -> BoolSource

Shadow test - we just return a Bool rather than return a a full Rayint.

inside :: s -> Vec -> BoolSource

Test if a point is inside an object. Useful for CSG. Objects with no volume just return False.

bound :: s -> BboxSource

Generate an axis-aligned bounding box than completely encloses the object. For performance, it is important that this fits as tight as possible.

tolist :: s -> [SolidItem t m]Source

Most simple objects just return themselves as a singleton list, but for composite objects, we flatten the structure out and return a list. We usually do this prior to re-building a composite object in a (hopefully) more efficient fashion.

transform :: s -> [Xfm] -> SolidItem t mSource

Create a new object transformed by some transformation. The reason this method exists is so we can override it for the Instance type - if we transform a transformation, we should combine the two matricies into one. Most objects can use the default implementation.

transform_leaf :: s -> [Xfm] -> SolidItem t mSource

Used by flatten_transform. I don't really remember how it works.

flatten_transform :: s -> [SolidItem t m]Source

Take a composite object inside a transform, and turn it into a group of individually-transformed objects. Most objects can use the defaut implementation.

primcount :: s -> PcountSource

Count the number of primitives, transforms, and bounding objects in a scene. Simple objects can just use the default, which is to return a single primitive.

get_metainfo :: s -> Vec -> ([Texture t m], [t])Source

Get texture and tag data for a primitive, from a point.

Instances

Solid [SolidItem t m] t m 
Solid (Instance t m) t m 
Solid (Void t m) t m 
Solid (SolidItem t m) t m 

data SolidItem t m Source

We create an existential type for solids so we can emded them in composite types without know what kind of solid it is. http:notes-on-haskell.blogspot.com200701/proxies-and-delegation-vs-existential.html

Constructors

forall s . Solid s t m => SolidItem s 

Instances

Read SI 
Read [SI] 
Solid [SolidItem t m] t m 
Show (SolidItem t m) 
Solid (SolidItem t m) t m 

group :: [SolidItem t m] -> SolidItem t mSource

A group is just a list of objects. Sometimes its convenient to be able to treat a group as if it were a single object, and that is exactly what we do here. The ray intersection routine tests the ray against each object in turn. Not very efficient for large groups, but this is a useful building block for constructing the leaves of acceleration structures. (See the bih module.)

flatten_group :: [SolidItem t m] -> [SolidItem t m]Source

Smash a group of groups into a single group, so we can build an efficient bounding heirarchy

paircat :: ([a], [b]) -> ([a], [b]) -> ([a], [b])Source

data Void t m Source

A Void is a non-object, that we treat as if it were one. This is functionally equivalent to an empty Group. (Originally I called this Nothing, but that conflicted with the prelude maybe type, so I call it Void instead)

Constructors

Void 

Instances

Show (Void t m) 
Solid (Void t m) t m 

data Instance t m Source

An instance is a primitive that has been modified by a transformation (i.e. some combination of translation, rotation, and scaling). This is a reasonably space-efficient way of making multiple copies of a complex object.

Usually, the application doesn't need to create an instance directly, but should use transform on an existing object.

It's unfortunate that instance is also a reserved word. instance Solid Instance where... is a little confusing.

This would be better in its own module, but we need Instance to be defined here so we can define the default implementation of transform in terms on Instance. (Mutually recursive modules would be useful, if I could get them to work.)

Another good reason to include Instance in Solid.hs is that it's referenced from Cone.hs

Constructors

Instance (SolidItem t m) Xfm 

Instances

Show (Instance t m) 
Solid (Instance t m) t m 

rayint_instance :: Instance tag mat -> Ray -> Flt -> [Texture tag mat] -> [tag] -> Rayint tag matSource

packetint_instance :: Instance tag mat -> Ray -> Ray -> Ray -> Ray -> Flt -> [Texture tag mat] -> [tag] -> PacketResult tag matSource

rayint_debug_instance :: Instance tag mat -> Ray -> Flt -> [Texture tag mat] -> [tag] -> (Rayint tag mat, Int)Source

transform_instance :: Instance tag mat -> [Xfm] -> SolidItem tag matSource

get_metainfo_instance :: Instance tag mat -> Vec -> ([Texture tag mat], [tag])Source