Glome tutorial

From HaskellWiki
Revision as of 05:42, 26 April 2008 by Jsnow (talk | contribs)
Jump to navigation Jump to search

Installing Glome

First, you need to install the software. I will assume that you already have ghc and the Haskell OpenGL libraries installed, and are comfortable with "tar" and the like. See How to install a Cabal package. Familiarity with Haskell is not required, but it will help.

The source code is available from hackage. You must untar the file ("tar xvfz [filename]", "cd glome-hs[version]") , and then build the binary with:

runhaskell Setup.lhs configure --prefix=$HOME --user
runhaskell Setup.lhs build
runhaskell Setup.lhs install

Glome doesn't really need to be installed in order to run it. If you'd prefer, you can invoke it directly from the build directory as "./dist/build/glome/glome".

If everything works, a window should open and you should (after a pause) see a test scene with a variety of geometric shapes. If it doesn't work, then let me know.

Command line options

These are pretty sparse at the moment. You can specify an input scene file in NFF format with the "-n [filename]" option, and there is one such scene included with Glome, a standard SPD level-3 sphereflake.

NFF isn't very expressive (and it was never intended to be), so I won't say much about it here. Glome supports most of the basic features of NFF except for refraction. My approach to polygon tesselation is also questionable: the SPD "gears" scene, for instance, doesn't render correctly.

You may have to adjust the lighting to get satisfactory results (i.e. by adjusting the value of "intensity" in "shade" function in the Trace.hs file and recompiling). NFF doesn't define a specific intensity, and I'm not sure what sort of falloff (if any) Eric Haines used when he rendered the reference images.

Describing Scenes in Haskell

Ideally, using Glome would be a matter of firing up Blender and editing 3-d geometry in a graphical, interactive way and then exporting the scene to Glome, which would do the final render.

Unfortunately, Glome isn't able to import files from any standard 3-d format except NFF (which isn't typically used for anything but benchmark scenes).

So, with only limited import functionality, how do we model complex scenes?

One option we have left is to describe our scene directly in Haskell, and then compile the description and link it with the Glome binary. This is the approach we will be following for the remainder of this tutorial.

This isn't quite as difficult as it sounds. POV-Ray, for instance, has a very user-friendly scene description language (SDL), and many artists type their scenes in directly as text.

Glome was, in fact, quite heavily influenced by POV-Ray, so anyone familiar with POV's SDL and Haskell should be able to write scenes for Glome without much trouble.

Unlike POV-Ray, in which the SDL is separate from the implementation language (C, or more recently, C++), in Glome there is no distinction. In that sense, Glome is more of an API than a standalone rendering system.

The default scene, which is loaded if the user does not specify an input file on the command line, is defined in TestScene.hs. To define a new scene, you must edit this file and then recompile the source.

TestScene.hs: Camera, Lights, and the minimal scene

TestScene.hs import a number of modules at the beginning, and it contains a handful of objects and then defines a single function.

 scn :: IO Scene
 scn = return (Scene geom lits cust_cam (t_matte (Color 0.8 0.5 0.4)) c_sky)

"scn" is called from Glome.hs to specify a scene if there wasn't one passed in as a command line argument.

"scn" uses the IO monad, in case we want to load a file from disk. We won't be doing that in any of our examples, so you can safely ignore the "IO" part. It returns an object of type "Scene".

A Scene is described like this in Solid.hs:

data Scene = Scene {sld     :: Solid, 
                    lights  :: [Light], 
                    cam     :: Camera, 
                    dtex    :: Texture, 
                    bground :: Color} deriving Show

So, in order to construct a valid scene we need to put something into all the fields.

The first field takes a Solid. A Solid is any of the basic primitive types that Glome supports. These might be triangles, spheres, cones, etc...

You might wonder why we only need one primitive to define a scene. Certainly, we'd want to have a scene that contains more than a single sphere!

The solution is that Glome includes several primitive types that let us create more complex Solids out of simple ones. For instance, a Group is a list of Solids, and Glome treats that list as if it was a single Solid. This will be discussed in more detail later on.

A light is defined by a Color and a Vec:

data Light = Light {litpos :: !Vec,
                    litcol :: !Color} deriving Show

A "Vec" is a vector of three floating point numbers, while a "Color" is also three floats as red, green, and blue values. (This may change in the future: RGB isn't necessarily the best representation for colors.)

(See Vec.hs and Clr.hs for the definitions and useful functions for dealing with vectors and colors, respectively.)

We can define a light like so:

Light (Vec (-3) 5 8) (Color 1.5 2 2)

Note that the rgb values don't have to be between 0 and 1. In fact, we may wish to make them quite a bit larger if they're far away.

Also note that a decimal point isn't mandatory. Haskell is smart enough to infer that the Color constructor expects a float. The parentheses around the "-3", on the other hand, are required.

The square brackets is the definition of Scene tells us that we need a list of lights rather than a single light, and we can turn our single light into a list simply by enclosing it in square brackets. We could also use the empty list [], but then our scene would be completely black except the background.

A camera describes the location and orientation of the viewer. There is a function for creating a camera defined in Solid.hs:

camera :: Vec -> Vec -> Vec -> Flt -> Camera
camera pos at up angle =
 let fwd   = vnorm $ vsub at pos
     right = vnorm $ vcross up fwd
     up_   = vnorm $ vcross fwd right
     cam_scale = tan ((pi/180)*(angle/2))
 in
  Camera pos fwd
         (vscale up_ cam_scale) 
         (vscale right cam_scale)

It's arguments are: a point defining it's position, another point defining where it's looking, an "up" vector, and an angle. At this point, we need to decide which direction is up. I usually pick the "Y" axis as pointing up, So, to set up a camera at position <20,3,0> looking at the origin <0,0,0>, and a 45 degree field of view (measured from the top of the image to the bottom, not right to left or diagonal) we might write:

 camera (vec 20 3 0) (vec 0 0 0) (vec 0 1 0) 45

"dtex" and "background" define a default texture and a background color. The background color is the color if we miss everything in the scene. The defaults should work okay for the present.

Spheres, Triangles, Etc..

Now with all that out of the way, we can describe some geometry. As we mentioned earlier, every primitive is of type "Solid". The definition of Solid is quite long:

data Solid =  Sphere {center :: Vec, 
                      radius, invradius :: Flt}
            | Triangle {v1, v2, v3 :: Vec}
            | TriangleNorm {v1, v2, v3, n1, n2, n3 :: Vec}
            | Disc Vec Vec Flt  -- position, normal, r*r
            | Cylinder Flt Flt Flt -- radius height1 height2
            | Cone Flt Flt Flt Flt -- r clip1 clip2 height
            | Plane Vec Flt -- normal, offset from origin
            | Box Bbox
            | Group [Solid]
            | Intersection [Solid]
            | Bound Solid Solid
            | Difference Solid Solid
            | Bih {bihbb :: Bbox, bihroot :: BihNode}
            | Instance Solid Xfm
            | Tex Solid Texture
            | Nothing deriving Show

(this list has been simplified a bit: the actual code may be different)

The simplest primitive is the sphere and that's where we'll start. (Its ubiquity in ray tracing might lead some to believe that it's the only primitive ray tracers are any good at rendering.)

The standard constructor takes a radius and the reciprocal of the radius: this is for efficiency, to avoid a division (which is typically much slower than multiplication). We don't really want to specify the inverse radius every time, so there's a simpler constructor we'll use instead (note the lower case vs upper case):

sphere :: Vec -> Flt -> Solid
sphere c r =
 Sphere c r (1.0/r)

We can, for instance, construct a Sphere at the origin with radius 3 like this:

sphere (Vec 0 0 0) 3

Triangles are described by the coordinates of their vertices. There is a second kind of triangle, "TriangleNorm" that deserves a little bit of explanation. This second kind of triangle allows the user to specify a normal vector at each vertex. The normal vector is a unit vector perpendicular to the surface. Usually, this is computed automatically. However, sometimes the resulting image looks too angular, and by interpolating the normal vectors, Glome can render a curve that appears curved even if it really isn't.

This is, perhaps, an inelegant trick, but it works well. Sometimes, we'll be able to define surfaces exactly without approximation, but many models are only available as triangle meshes. Also, triangles may be useful to approximate shapes that Glome doesn't support natively (like toruses).

Discs are another simple primitive that just happens to have a very simple, fast ray-intersection test. They are defined by a center point, a normal vector, and a radius. The surface of the Disc is oriented perpendicular to the normal. The radius is actually specified as radius squared, so you need to be aware of that if you're going to use them.

Planes are even simpler than the Disc, they're defined as a normal vector and a perpendicular offset from the origin. Essentially, a plane is a half-space; everything on one side is inside, and everything on the other side (the direction pointed at by the normal) is on the outside.

A (usually) more convenient way to specify a Plane is with a point on the surface, and a normal, and a function that does just that has been provided:

plane :: Vec -> Vec -> Solid
plane orig norm_ = Plane norm d
 where norm = vnorm norm_
       d = vdot orig norm

If we want a horizon stretching to infinity, we simply add a plane oriented to the Y axis (assuming that's our current definition of "up").

plane (Vec 0 0 0) (Vec 0 1 0)

Glome supports Z-axis aligned cones and cylinders. The cones are perhaps more accurately described as tapered cylinders; they need not come to a point.

As is, the primitives are fairly useless unless we really want a Z-aligned cone or cylinder. Fortunately, Glome provides more convenient constructors:

cylinder_z :: Flt -> Flt -> Flt -> Solid
cylinder_z r h1 h2 = Cylinder r h1 h2

cone_z :: Flt -> Flt -> Flt -> Flt -> Solid
cone_z r h1 h2 height = Cone r h1 h2 height

-- construct a general cylinder from p1 to p2 with radius r
cylinder :: Vec -> Vec -> Flt -> Solid
cylinder p1 p2 r =
 let axis = vsub p2 p1
     len  = vlen axis
     ax1  = vscale axis (1/len)
     (ax2,ax3) = orth ax1 
 in Instance (cylinder_z r 0 len)
             (compose [ (xyz_to_uvw ax2 ax3 ax1),
                        (translate p1) ])
                        
-- similar for cone
cone :: Vec -> Flt -> Vec -> Flt -> Solid
cone p1 r1 p2 r2 =
 if r1 < r2 
 then cone p2 r2 p1 r1
 else if r1-r2 < delta
      then cylinder p1 p2 r2
      else
        let axis = vsub p2 p1
            len  = vlen axis
            ax1  = vscale axis (1/len)
            (ax2,ax3) = orth ax1 
            height = (r1*len)/(r1-r2) -- distance to end point
        in
         Instance (cone_z r1 0 len height)
                  (compose [ (xyz_to_uvw ax2 ax3 ax1),
                             (translate p1) ])

cone_z and cylinder_z don't do anything the regular constructors don't do, but "cylinder" and "cone" are much more interesting. "cylinder" takes a start point and an end point and a radius, and creates a cone whose axis stretches from one point to the other. The "cone" constructor is similar, but it takes a radius for each end. Note that if you call "cone" with an identical radius at both ends, it automatically simplifies it to a cylinder. We'll see how to use cones effectively in the next section.

Boxes are axis-aligned, and can be created with a constructor that takes two corner points:

box :: Vec -> Vec -> Solid
box p1 p2 =
 Box (Bbox p1 p2)

Groups

Sometimes it's convenient to treat a whole group of object as if they were a single object, and for that purpose we have Group. One reason we might want to do this has already been mentioned: the scene needs to be described in terms of a single object. There are several others. We might want to apply a texture or move or rotate a whole group of objects at once, instead of treating them individually. Using groups is quite simple. For instance:

 Group [ (sphere (Vec (-1) 0 0) 2), 
         (sphere (Vec 1 0 0) 2),
         (sphere (Vec 0 (-1) 0) 2),
         (sphere (Vec 0 1 0) 2) ]

This gives us four spheres we can treat as a single object.

Group has a special constructor, "group", that does a little bit of extra optimization for us:

group :: [Solid] -> Solid
group [] = Solid.Nothing
group (sld:[]) = sld
group slds =
 Group (flatten_group slds)

If you try to create an empty group, Glome will replace it with a primitive of type Nothing, which is a degenerate object that has no appearance. ("Nothing" conflicts with the Maybe type in the Haskell prelude, so we say Solid.Nothing to disambiguate.)

If you try to create a group that contains only one object, Glome throws the group away and just uses that object directly.

If you try to create a group that contains other groups, Glome will consolidate those into one big group. (This is what "flatten_group" does.)

In general, it's better to use "group" than "Group". Even better than "group", though, is "bih", which behaves similarly to group but performs much better. I'll explain why later.

Haskell has some convenient syntax for creating lists. For instance, if you want to create a lot of spheres, you can use:

let lattice = 
 let n = 20
 in [sphere (Vec x y z) 0.1 | x <- [(-n)..n],
                              y <- [(-n)..n], 
                              z <- [(-n)..n]]

This gives you a list of spheres arranged in a 41x41x41 3-D grid. You can then create a group out of it:

group lattice

But it will render very slowly. If you use "bih" instead of "group", it will render much faster. Here is a rendering of over a million reflective spheres. It took about ten minutes or so to render, largely because of the reflections.

We can use cones and spheres together in a useful way by stringing a series of cones together with a sphere to hide each joint.

spiral = [ ((Vec ((sin (rot n))*n) 
                 ((cos (rot n))*n) 
                 (n-3)), (n/15)) | n <- [0, 0.05..6]]
                               
coil = bih (zipWith (\ (p1,r1) (p2,r2) -> (Solid.group [(cone p1 r1 p2 r2), 
                                                        (sphere p1 r1)] )) 
                    spiral 
                    (tail spiral))

Here, "spiral" is a list of (location,radius) tuples, and we use zipWith to create cylinders and cones from pairs of (location,radius) tuples. We save the result into the variable "coil".

CSG

The basic primitives give us something to work with, and we might make reasonably complex scenes from them, but many simple objects are still difficult or impossible to create, unless we approximate them with triangles.

Constructive Solid Geometry (CSG) gives us the ability to combine objects in more interesting ways than we can with "group".

With a Difference object, we can subtract one object from another. For instance, to make a pipe, we could start with a cylinder, and then subtract a cylinder with a smaller radius. Or, to make a house, we might start with a box, and then subtract a smaller box to make the interior space, and then subtract more boxes to make space for windows and doors.

Creating a difference is simple: it's just
Difference a b
, where b is the solid subtracted from a.

In order for CSG to be meaningful, it needs to be performed with objects that have a well-defined inside and outside (like planes, spheres, cones, and cylinders, but not triangles or discs). It won't break anything if you use objects that don't have volume, but you might not get the results you want.

CSG can be performed on composite objects, like group or bih, and they can be nested. (Note, however, that not all combinations have been tested, so things might not work the way you expect. If this happens, send me an email about it.)

One caveat on difference is that you shouldn't ever create objects with infinitely thin walls. They might render correctly, or they might not depending on floating point approximations.

Intersection is like Difference, but it takes a list of objects, and the resulting object is the overlap of all those objects. Planes are very useful in intersections; we could easily define a box as the intersection of six axis-aligned planes, with their normals all facing outward.

We can define a dodecahedron succinctly:

dodecahedron pos r =
 let gr = (1+(sqrt 5))/2 -- golden ratio, 1.618033988749895
     n11 = [(-r),r]
     ngrgr = [(-gr)*r,gr*r]
     points = [Vec 0 y z | y <- n11, z <- ngrgr] ++
              [Vec x 0 z | z <- n11, x <- ngrgr] ++
              [Vec x y 0 | x <- n11, y <- ngrgr]
     pln x = (Plane (vnorm x) (r+(vdot (vnorm x) pos)))
 in
  Intersection ((sphere pos (1.26*r)):(map pln points))

This is a function that takes a position and a radius, and generates a dodecahedron circumscribed about the sphere with that center and radius.

The plane normal vectors are taken from the coordinates for the verticies of an icosahedron. (Similarly, we can create an Icosahedron by using the coordinates of the verticies of a dodecahedron.)

I put a sphere in the list of objects as an optimization. Any ray that misses the first sphere can be assumed to miss the whole object. This also allows Glome to compute an efficient bounding box for the intersection: all the planes are infinite objects, so they have infinite bounding boxes.

Transformations

Transformations are a convenient way of moving, rotating, and stretching objects.

To move an object a by some vector v, we can say:

 transform a [translate v]

In pure Haskell there are no side effects, so this doesn't actually move "a" but rather creates a copy that has been moved. This is, in fact, an efficient way of creating many copies of a complex object without using much extra space. (Each transform uses 24 floating point numbers to store a matrix and its inverse that describe the transformation.)

"transform" takes a list, and we can combine several transformation and they behave as you might expect:

 transform a [translate (Vec 0 3 0),
              rotate (Vec 0 1 0) (deg 90),
              scale (Vec 2 2 2)]

This moves object "a" up three units, then rotates 90 degrees about the Y axis, and then stretches the object equally on all three axes by a factor of 2.

Stretching and rotations happen about the origin, so you might need to translate an object to the origin, rotate it, then translate it back in order for the translations to do what you want.

Interestingly, performing multiple transformations at a time doesn't produce any more overhead than just performing one transformation; internally, any combination of transformations can be represented as a single matrix.

(Arcane trivia: internally, "transform" reverses the list of transformations before applying them.)

One caveat is that you should use transformations sparingly. For instance, rather than creating a unit sphere and then scaling it and moving it into position, it's better to use the sphere's constructor the way it was intended. A transformed sphere consumes more memory than just a sphere by itself, and rendering will be a little slower.

Cones and cylinders, on the other hand, are already stored as transformations (except for the rare case when you really do want a Z-axis aligned cone or cylinder), so transforming them won't take up any extra space.

Bounding Objects

The preceding sections have (hopefully) shown everything you need to know to model the kinds of shapes you want to render. However, there are many equivalent ways to represent the same scene, and some of them render much faster than others. To understand why, you will need to know a little bit about how a ray tracer works.

A ray tracer sends rays out from the camera into the scene, one ray per pixel. (Or more than one ray, if the ray tracer supports anti-aliasing, which Glome does not.) Each ray has to be tested for intersection with each object in the scene. (Conceptually, scenes in Glome are only comprised of a single object, but in practice intersecting with that object usually means doing a lot of ray-intersections with sub-objects.) For scenes with many objects, this can be very slow. Supposing we have a thousand spheres in our scene, and at the default resolution of 720x480, we have 345,600 rays. This means that for each image, we have to do 345.6 million ray-sphere intersection tests! Hardware may be getting faster, but we need to do better than that if we want anything near reasonable rendering speed.

Fortunately, we don't really need to do that many ray-intersection tests. What we can do instead is place bounding objects around the complicated bits of our scene. If a ray doesn't hit the bounding object, then we know it won't hit anything inside the bounding object, and we don't have to do any of those intersection tests.

Glome has a "Bound" primitive just for this purpose: If you have some complicated solid "a" and a simple bounding solid (such as a sphere or a box) "b", you can declare the bounded object as
Bound b a
(the simple object comes first).

You could do a similar thing with Intersection, but Bound is a bit more efficient.

Bounding objects are great for improving performance, but they're unwieldy. Finding the smallest bounding object that will enclose another object is a non-trivial task, and it's easy to make mistakes, leading to incorrect renderings.

Fortunately, there's an easier way, and we've mentioned it before: use "bih".

The "bih" constructor takes a list of primitives and sorts them into a hierarchy of bounding planes called a Bounding Interval Hierarchy.

(more information on this method can be found here: Carsten Wächter and Alexander Keller,Instant Ray Tracing: The Bounding Interval Hierarchy)



The Bounding Interval Hierarchy

Textures, Lighting

Advanced Topics, and things that don't quite work yet

Navigation