Re: [Haskell-cafe] Re: capture of idioms and patterns

2010-09-24 Thread Jim Snow

a...@spamcop.net wrote:

G'day all.

Quoting Johannes Waldmann waldm...@imn.htwk-leipzig.de:

you got this backwards: what some folks call idioms and (design) 
patterns

actually *is* FP, because it is just this: higher order functions.
And it's been there some decades (lambda calculus).
That also explains the absence of any Design Patterns/Gang-of-Four
kind of book for Haskell - it's just not needed.


Err... no.

The phrase design patterns is a shorthand for vocabulary of
engineering experience.  Zippers, continuation passing style, Church
encoding... these are not what FP is, but they are specific techniques
that engineers working in Haskell need to know to use the language
effectively.

...
An often-overlooked bit of trivia is that the first books on design 
patters were not in computer science, but rather architecture.  I would 
recommend A Pattern Language: Towns, Buildings, Construction and A 
Timeless Way of Building by Christopher Alexander to anyone who is 
interested in a great example of how design patterns are supposed to 
work (or anyone interested in constructing an attractive and functional 
building).  I've never read GoF (it seemed a bit too focused on 
object-oriented design for my tastes), so I don't know how closely it 
follows Alexander's conventions.


A Pattern Language is essentially a compilation of a couple hundred 
patterns -- a great resource if you want to build a house, but it 
doesn't offer much insight into what a pattern is.  A Timeless Way of 
Building, on the other hand, describes what a pattern is and how to go 
about discovering, documenting, and organizing (and, often, discarding) 
them.


I was initially skeptical of patterns, as they seemed like a rather 
vague concept, but it's actually quite formal.  A pattern consists of 
some context in which the pattern can apply, a conflict that arises 
within that context, and a satisfactory solution to that conflict.  
Described this way, a pattern is an idea that makes itself a target for 
criticism, because a detractor can point out that the given pattern 
doesn't apply to its context, or that it doesn't resolve the conflict, 
or there may be some other pattern that works in a broader context that 
fully covers the narrow context.  However, this makes it much easier to 
distinguish good ideas from bad ones.


One notion about patterns that I'm not sure whether the GoF authors were 
aware of, is that the patterns can be arranged into a directed graph, 
where the most general patters form a sort of root, and the more 
specific, narrow patterns form the leaves.  (Ideally, you would have a 
tree, but you might not.)  A common problem whether designing buildings 
or programs, is that you get halfway into the design and have to start 
over because you come across some constraint that can't be 
circumvented.  By starting with the most general patterns and working 
down to the more specific ones, you can reduce the amount of 
backtracking you will have to do.

There is no GoF-like book for Haskell because it's not an idea that
needs promoting in printed form.  We just point people to the wiki.

Cheers,
Andrew Bromage
__
I think a functional design-pattern section on the Haskell wiki would 
be a good idea.  I think the patterns framework is a good and useful 
one, if we can communicate properly what design patters are and how 
they're supposed to work.  I think a lot of the basic knowledge about 
functional programming patterns is already there, it just needs to be 
formatted properly.


Do people think this is the right way to document the Haskell 
community's oral tradition?


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: GlomeTrace raytracing library

2010-01-23 Thread Jim Snow

I have uploaded to hackage a new version of my ray-tracer, Glome.

In previous releases, Glome was a monolithic application.  In this 
release, the core algorithms have been abstracted out into a pair of 
libraries, GlomeVec and GlomeTrace.


GlomeVec is a vector library.  It's not necessarily any better than any 
of the other vector libraries on Hackage, but it's fairly simple and 
does what I need it to do.  Also included with GlomeVec is a solid 
texture library, which has a perlin noise function that may be useful 
for other projects.


GlomeTrace contains constructors for building scenes out of basic 
primitives like spheres, cones, triangles, and grouping them, moving 
them around, and performing boolean operations on them, and functions to 
test rays for intersection against these objects.  It also has some 
higher-level operations, like tracing a ray corresponding to a certain 
x/y coordinate within the camera's field of view, and returning the 
color by recursively tracing rays against the scene.  (Recursion comes 
into play if the object is reflective.)


GlomeTrace uses a typeclass called Solid for geometric primitives, and 
the composite primitives that are built up from other primitives use an 
existential type SolidItem that is just a container for all types that 
are instances of Solid, so it should be quite easy for an application to 
add new primitives of its own and have them integrate nicely with the 
ones that are already defined, just by making them instances of Solid.


One very useful composite primitive is a BIH (Bounding Interval 
Hierarchy), which is a type of automatically-constructed tree of 
bounding volumes used to speed up the process of tracing a ray against 
many objects.  Constructing a bih is easy: just pass a list of 
SolidItems to the bih constructor, and it returns a Bih object that is 
itself a SolidItem, so you can trace rays against it as if it were a 
single primitive.


GlomeTrace and GlomeVec now have (partial) haddock documentation so it 
should be easier to understand the code than it was previously.  There 
is also a (somewhat out of date) tutorial linked to from the Haskell wiki:


http://www.haskell.org/haskellwiki/Glome

Glome the application requires OpenGL for display, but GlomeVec and 
GlomeTrace do not.



-jim

Packages:

http://hackage.haskell.org/package/GlomeVec
http://hackage.haskell.org/package/GlomeTrace
http://hackage.haskell.org/package/glome-hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Ring -- Pre-announce

2009-12-31 Thread Jim Snow


My first thoughts are that you could implement a Ring type using 
Data.Sequence [1], which is a sort of balanced binary tree where you can 
insert or remove elements at the beginning or end in amortized O(1) time.


You might have a data type like this:

data Ring a = Empty | Ring (Seq a) a

The main difference between a Ring and a Sequence seems to be that the 
former uses a particular element as the focus, whereas you can think of 
a Sequence as having a focus that's in between two elements.


Some advantages of using a Sequence rather than two lists are that you 
could then combine two rings in O(logn) time rather than O(n), and you 
can also find the n'th item to the right or left in log(n) time.  I 
suspect that lists may perform better if all you're doing is inserting 
and removing elements to the right or left, or rotating the ring.


I'm not sure about the worst case behavior of Data.Sequence.  The docs 
also explicitly say that sequences are finite.


-jim

[1] 
http://www.haskell.org/ghc/docs/latest/html/libraries/containers-0.3.0.0/Data-Sequence.html



John Van Enk wrote:

Hi List,

I recently needed a ring structure (circular list with bi-directional 
access) and didn't see anything obvious on Hackage. I threw something 
together fairly quickly and would like some feedback before tossing it 
on Hackage.


I'd really appreciate if some one would:

   1. make sure the code looks goodish (127 lines with full docs)
   2. make sure my tests look saneish

If I hear nothing, I'll assume wild support and push to Hackage.

Code: http://github.com/sw17ch/data-ring/blob/master/src/Data/Ring.hs
Tests: http://github.com/sw17ch/data-ring/blob/master/tests/quickcheck.hs
Package Root: http://github.com/sw17ch/data-ring

Thanks ahead of time,
John Van Enk


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
  


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: GlomeVec, IcoGrid

2009-10-26 Thread Jim Snow

I just uploaded two packages to hackage.

The first package [1] is the vector library used by my haskell 
ray-tracer, Glome, which has been neglected of late.  It's one of the 
first things I ever wrote in Haskell, so some of the code looks a little 
strange to me now, but it works pretty well for a wide variety of 
computational geometry tasks.  I also included a perlin noise 
implementation.


I released GlomeVec so that I would have a reasonable vector library to 
work off of for my other project, which is the IcoGrid library [2].  
IcoGrid (Icosahedron Grid) is a library for dealing with grids of 
hexagons and pentagons wrapped around a sphere.  Individual grid cells 
are identified by an integer, and the library can find all the neighbors 
of a given cell, it can find all the places where three cells intersect 
at a point, and it can also tell you where in 3-D space the center of 
the cell is.  (The cells are positioned on the surface of a sphere with 
unit 1.)  The one very useful function I haven't implemented yet is, 
given an arbitrary point, find the cell that the point belongs in.


I posted a screenshot on the Haskell wiki [3] showing an OpenGL 
application I wrote that uses IcoGrid.  My initial goal was to write 
some sort of simple environmental simulator that can eventually be made 
into a game.  The grid turned out to be a pretty big project by itself, 
so I turned it into a stand-alone library.


Both libraries have haddock docs, but they aren't showing up on 
hackage.  Is there a trick to tell hackage it needs to generate docs, or 
do I just need to wait for a cron job to run?


-jim

[1] http://hackage.haskell.org/package/GlomeVec
[2] http://hackage.haskell.org/package/IcoGrid
[3] http://www.haskell.org/haskellwiki/IcoGrid
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IORef memory leak

2009-06-19 Thread Jim Snow


Don Stewart wrote:

dvde:
  

Don Stewart schrieb:


It is not possible to write a modifyIORef that *doesn't* leak memory!
  
  

Why? Or can one read about it somewhere?




Try writing a version of this program, using modifyIORef only, 
such that it doesn't exhaust the heap:


import Data.IORef
import Control.Monad
import System.IO.Unsafe

ref :: IORef Int
ref = unsafePerformIO $ newIORef 0
{-# NOINLINE ref #-}

main = do
modifyIORef ref (\a - a + 1)
main

Run it in a constrained environment, so you don't thrash:

$ ./A +RTS -M100M
Heap exhausted;
Current maximum heap size is 9744 bytes (95 MB);
use `+RTS -Msize' to increase it.

The goal is to run in constant space.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
  
Thanks, that's good to know. 


do x - readIORef ior
 writeIORef ior $! (x+1)

Works for me.  The laziness of modifyIORef and workarounds would be a 
good thing to have documented in the modifyIORef docs [1], since it's 
probably a common source of memory leaks.  I'd also be in favor of a 
strict version of modifyIORef.


[1] 
http://www.haskell.org/ghc/dist/current/docs/libraries/base/Data-IORef.html#v%3AmodifyIORef


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] IORef memory leak

2009-06-18 Thread Jim Snow


I'm having some trouble with excessive memory use in a program that uses 
a lot of IORefs.  I was able to write a much simpler program which 
exhibits the same sort of behavior.  It appears that modifyIORef and 
writeIORef leak memory; perhaps they keep a reference to the old 
value.  I tried both ghc-6.8.3 and ghc-6.10.1.


Is this a known limitation, or is this a ghc bug, or am I using IORefs 
in the wrong way?


-jim


module Main where

import Data.IORef
import Control.Monad

-- Leaks memory
leakcheck1 ior =
do go 10
where
   go 0 = return ()
   go n = do modifyIORef ior (+1)
 go (n-1)

-- Leaks memory
leakcheck2 ior =
do go 10
where
   go 0 = return ()
   go n = do x - readIORef ior
 writeIORef ior (x+1)
 go (n-1)

-- Runs in constant memory
leakcheck3 ior =
do go 10
where
   go 0 = return ()
   go n = do x - readIORef ior
 go (n-1)

main :: IO ()
main =
do ior - newIORef 0
   leakcheck2 ior


compiled with: ghc -O2 --make Leak.hs -o Leak
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IORef memory leak

2009-06-18 Thread Jim Snow


Luke Palmer wrote:
On Thu, Jun 18, 2009 at 9:55 PM, Ross Mellgren rmm-hask...@z.odi.ac 
mailto:rmm-hask...@z.odi.ac wrote:


It looks offhand like you're not being strict enough when you put
things back in the IORef, and so it's building up thunks of (+1)...

With two slight mods:


  go 0 = return ()
  go n = do modifyIORef ior (+1)
go (n-1)

--

  go 0 = return ()
  go n = do modifyIORef ior (\ x - let x' = x+1 in x `seq` x')
go (n-1)


Just a slight prettification of that line:

modifyIORef ior ((1+) $!)

Or applied prefix if you prefer.  Prefix ($!) has the nice 
interpretation as the HOF that makes its argument into a strict function.


Luke


   do modifyIORef ior (\ x - let x' = x+1 in x `seq` x')

and

   do modifyIORef ior ((1+) $!)

both still leak memory for me.  However,

   do x - readIORef ior
writeIORef ior $! x+1


runs in constant space.  I was able to fix my original program, and now 
it uses a predictable amount of memory.


Thanks!


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] IORef vs TVar performance: 6 seconds versus 4 minutes

2008-12-28 Thread Jim Snow


I decided to try to implement a graph algorithm using STM.  Each node in 
the graph has a set of TVar-protected lists of the nodes it links to and 
the nodes that link to it.  Also, there is a global TVar-protected 
Data.Map that contains all the nodes in the graph, indexed by name 
(which is polymorphic):


data Node k r = Node {
fwdPos :: TVar [Node k r],  -- forward links (nodes we like)
fwdNeg :: TVar [Node k r],  -- we allow negative links, too (nodes we 
don't like)

revPos :: TVar [Node k r],  -- backlinks (nodes that like us)
revNeg :: TVar [Node k r], -- negative back links (nodes that don't 
like us)

currRep :: r,-- extra user-defined data
name   :: k -- node's unique identifier
} deriving Show

data Network k r = Network {
node:: TVar (M.Map k (Node k r)),  -- map of nodes by name
trusted :: TVar [Node k r]-- a list of nodes we need to iterate 
over occasionally

} deriving Show


I tried loading a datafile of about 20,000 nodes into the graph in one 
big transaction, and found that it takes about 4 minutes.  This seemed 
rather slow, so I replaced all the TVars with IORefs (and substituted 
STM with IO in the type signatures), and the same operation with the new 
version took about 6 seconds!


This is all with one thread, so there should be no contention for the 
TVars.  Is there something about STM that makes it scale worse than 
linearly wrt the number of mutations in a transaction?


Above performance numbers are for ghc-6.10.1.  With ghc-6.8.3, the STM 
version takes more than 9 minutes.


According to profiling, one of my trouble spots is this function, which 
just adds an entry onto a TVar [a]:


stmcons :: k - TVar [k] - STM ()
stmcons x tv =
do xs - readTVar tv
 writeTVar tv (x:xs)

This seems like it ought to be pretty innocuous, unless the whole list 
is getting evaluated each time I cons a new entry, or if readTVar or 
writeTVar are much more expensive than they appear.


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IORef vs TVar performance: 6 seconds versus 4 minutes

2008-12-28 Thread Jim Snow
Thanks, that's good to know. 

I tried incrementally loading the graph one node per transaction.  It's 
faster: about 38 seconds instead of 4 minutes, but I think I'll stick 
with IORefs and one thread for the present.


-jim

Ryan Ingram wrote:

Both readTVar and writeTVar are worse than O(1); they have to look up
the TVar in the transaction log to see if you have made local changes
to it.

Right now it looks like that operation is O(n) where n is the number
of TVars accessed by a transaction, so your big transaction which is
just accessing a ton of TVars is likely O(n^2).

From ghc/HEAD/rts/STM.c:

static TRecEntry *get_entry_for(StgTRecHeader *trec, StgTVar *tvar,
StgTRecHeader **in) {
  TRecEntry *result = NULL;

  TRACE(%p : get_entry_for TVar %p, trec, tvar);
  ASSERT(trec != NO_TREC);

  do {
FOR_EACH_ENTRY(trec, e, {
  if (e - tvar == tvar) {
result = e;
if (in != NULL) {
  *in = trec;
}
BREAK_FOR_EACH;
  }
});
trec = trec - enclosing_trec;
  } while (result == NULL  trec != NO_TREC);

  return result;
}

STM performance is not really geared towards big transactions right
now; in large part because big transactions are likely to starve under
any real workload anyways.  If you have a single-threaded startup bit
to populate your data followed by concurrent small mutations, you can
put the startup in IO using small transactions to populate the data.

  -- ryan

  


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OT: Haskell desktop wallpaper?

2008-10-09 Thread Jim Snow

Ray tracing about a million spheres in a regular grid with reflections:

lattice =
let n = 50 :: Flt
in bih [sphere (vec x y z) 0.2 | x - [(-n)..n],
 y - [(-n)..n],
 z - [(-n)..n]]

http://syn.cs.pdx.edu/~jsnow/glome/Glome.hs-lattice-1e6-720p.png
I don't remember if I disabled shadows for that particular render.

There are some more screenshots on the Glome web page, but most of them 
were rendered in my Ocaml ray tracer and are low resolution:


http://syn.cs.pdx.edu/~jsnow/glome

I just now rendered a level 5 sphereflake (a standard benchmark scene 
from Eric Haine's standard procedural database):


http://syn.cs.pdx.edu/~jsnow/glome/sphereflake5-720p.png

It took about a minute and a half to parse, sort, and render with about 
98k spheres. 


-jim

Magnus Therning wrote:

This morning I got tired of my desktop wallpaper (one that ships with
Debian's Gnome packages).  Typing haskell desktop wallpaper yeilded
a lot of links to wallpapers with Colleen Haskell, while she's a
beautiful lady it wasn't exactly what I was hoping to find.  Hence
this email.  Where can I find some nice wallpapers inspired by
Haskell, or maybe even created by Haskell code?

Oh yes, wallpapers related to XMonad would do, I suppose ;-)

/M

  



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
  


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OT: Haskell desktop wallpaper?

2008-10-09 Thread Jim Snow

Magnus Therning wrote:

Very nice indeed.  You don't have any images in aspect 8x5 that don't
include the window decorations? ;-)  (Yes, I'm lazy!)

  

I replaced the sphereflake image with one without window decorations:

http://syn.cs.pdx.edu/~jsnow/glome/sphereflake5-720p.png

I don't have any sort of image export functionality, so I just do a screen 
capture.


It took about a minute and a half to parse, sort, and render with about 98k
spheres.



I'm afraid it'd take me considerably longer, since I have to first get
all the software compiled and installed and then I'll have to read up
on how to generate the graphics.  I suspect the latter will take a
long time since the closest I've ever come to rendering something is
watching Elephants Dream.

/M
  
Glome doesn't have any particularly weird dependencies (assuming you 
have a recent ghc and a working OpenGL setup and GLUT), so it shouldn't 
be a big deal to compile it.  In case you want to give it a try, here's 
the steps I do to generate a sphereflake from a tarball:


tar xvfz glome-hs-0.51.tar.gz
cd glome-hs-0.51
runhaskell Setup.lhs configure --prefix=$HOME --user
runhaskell Setup.lhs build
./dist/build/glome/glome -n balls3.spd

(balls3.spd is included in the glome tarball and is the output of the 
SPD program spd/balls -r 1 -s 4.  SPD is available from 
http://tog.acm.org/resources/SPD/ )


If it works, you should see an OpenGL window with a sphereflake in it.  
Alternatively, if you omit a scene file, Glome will render whatever it 
finds in TestScene.hs.


There is a hastily written and somewhat out-of-date tutorial here:
http://www.haskell.org/haskellwiki/Glome_tutorial

If you don't get an image (note: the demo scene in TestScene.hs takes a 
while to render; about 20 seconds on my middle-of-the-road computer) or 
glome segfaults, try commenting out the line that enables pointSmooth in 
Glome.hs.  If that still doesn't work, send me an email.  I'd be 
interested to know what systems glome does or does not work on.


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread Jim Snow

Achim Schneider wrote:

Aaron Denney [EMAIL PROTECTED] wrote:

  

On 2008-05-30, Achim Schneider [EMAIL PROTECTED] wrote:


Bryan O'Sullivan [EMAIL PROTECTED] wrote:

  

A Bloom filter is a probabilistic data
structure that provides a fast set membership querying capability.
It does not give false negatives, but has a tunable false positive
rate.  (A false positive arises when the filter claims that an
element is present, but in fact it is not.)



/me squints.

Please tell me that this isn't reversible.
  

Tell me what you mean by reversible.  You can't, for instance,
extract the items in the set.



I guess invertible would have been the right word, though it's still
ambiguous.

Turning it into something that does not give false positives, but has a
tunable false negative rate.

Without looking at the algorithm, I imagine it working somewhat like a
hashtable, and this inversion would utterly destroy my intuition.
  
Without looking at the code to verify that this is how it has really 
been implemented, a bloom filter is like a series of hash tables, where 
the hash table entries are one bit.  The bit is set if there is an item 
that hashes to that value in the bloom filter.  So, assuming a single 
hash table where half the bits are set, there's a 50% false positive 
rate and no false negatives when you do a membership test.


To reduce the false positives, we can add another hash table with a 
different hash function.  Assuming it also is half full, we can check if 
an item is in both tables, and our false positive rate drops to 25%.


In practice, one might use something like 32 hash tables.  This yields a 
false positive rate of 1/(2^32).  Their most obvious application is to 
store the dictionary for a spell checker in a space-efficient way, 
though I have a friend who wrote a paper on using them for router caches.


There was a google tech talk on bloom filters awhile ago: 
http://www.youtube.com/watch?v=947gWqwkhu0


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Announce: glome-hs-0.51 (Haskell raytracer, now with type classes)

2008-05-25 Thread Jim Snow

A new version of my raytracer has been posted:

http://syn.cs.pdx.edu/~jsnow/glome/
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/glome-hs-0.51

(This should really be named 0.5.1, but I didn't think of that until 
after I uploaded it to hackage.)


There's not much new functionality, but it now uses type classes for the 
supported primitives, and has been optimized a bit more.  Much of the 
tutorial I hastily wrote for 0.4.x 
(http://www.haskell.org/haskellwiki/Glome_tutorial) is now quite out of 
date.


Most of the primitives have been moved to their own module, with the 
exception of SolidItem (an existential type used to make composite 
primitives), [SolidItem] (allowing me to treat lists of Solids like 
single solids), Void (a non-object, equivalent to []::[SolidItem]), and 
Instance (used for transformations).  It might be possible to move those 
to their own modules as well, but it would require mutual recursion 
between modules, and that's probably more trouble than it's worth.  (I 
made an attempt at that, but I quickly gave up.)


I also gave up on trying to use a global mutable variable to count the 
number of bounding hierarchy nodes a particular ray hits; instead, I 
added rayint_debug, which behaves just like rayint (the standard 
ray-object intersection routine), except that it returns an integer 
(that I can use to count whatever I like) along with the ray 
intersection.  Using a global counter in this instance would have been 
much simpler, but I don't think I understand seq well enough to be 
able to force the increment to actually happen.


http://syn.cs.pdx.edu/~jsnow/glome/Screenshot-glome-hs-bih.png

The resulting renders can be very useful to determine where Glome is 
spending most of its time, and to verify that the the bounding interval 
hierarchy is really doing the right thing.


I also added packet tracing, which makes it possible to trace four rays 
at a time, using a specialized ray intersection method packetint.  
(This is a common technique to amortize the acceleration structure's 
memory lookup cost over multiple rays.)  It seemed to be a big win when 
I first implemented it before converting over to type classes, but now 
it seems to be faster without it, so I probably made a mistake somewhere.


A cosmetic change is that Glome now renders into a drawlist instead of 
directly to the screen, so the whole image doesn't get laboriously 
re-traced whenever there's window damage.  Unfortunately, that means you 
can't watch as it draws anymore, which was a useful way of knowing which 
parts of the image were slow to render.


I've started looking more seriously into optimization (suggestions 
welcome).  Don Stewart's blog post 
(http://cgi.cse.unsw.edu.au/~dons/blog/2008/05/16#fast) was quite 
useful, but it seems like there's a lot of arcane knowledge required to 
understand what's really happening in core code.  Is there any better 
reference than Andrew Tolmach's paper An External Representation for 
the GHC Core Language (2001) 
http://citeseer.ist.psu.edu/tolmach01external.html?


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Glome.hs-0.3 (bounding objects, heterogeneous lists)

2008-04-28 Thread Jim Snow

Andrew Coppin wrote:
Well, for example, Haskell doesn't have hetrogenous lists - which 
are trivial in any OOP language. That's quite awkward to get around. 
Also, both spheres and cylinders have a radius property, but then 
you end up with name clashes. Again, a non-issue in OOP languages. 
[I gather there's some new GHC language extension to partially solve 
this one - but only when types are statically known. In the general 
case, you'd have to write a radius class and define instances... 
yuck!]


It's funny you mention that, those are actually problems I ran into, 
but (having learned my lesson the hard way in Ocaml), I decided not 
to try and force the language to do things my way, but instead try to 
do things in a way that Haskell makes easy.
For instance, I started out by making each primitive a separate type 
(Sphere, Triangle, etc...), and then made a type class that defines a 
ray intersection method (and a few other odds and ends), but then I 
realized that I can't do something as simple as store a list of 
primitives (or if there is in fact a way, I'm not aware of it).

Instead, I made a single large sum type with all my primitives:
so that now I can easily make a list of primitives.  (In fact, that's 
what a Group is.)  I also gave up on using named fields, since coming 
up with a separate name for each one gets ugly:  instead of radius, 
you have sphere_radius, cylinder_radius, cone_radius disc_radius, etc...


All of which works, but now it's a pain to add new primitives. And 
*all* supported primitives must be defined in a single monolithic 
module. And you can't reuse spheres as bounding volumes without either 
reimplementing them or loosing type safety.
The part about spheres and bounding spheres is actually not so much of a 
problem:  I implemented a general Bound primitive that can bound any 
primitive with any other.  In general, you would use a simple object 
like a sphere or box as the left argument and a complex object as the 
right argument.


data Solid =  ...
   | Bound Solid Solid
 ...

and then to intersect the Bound object, you first do a shadow test on 
the left object before testing the right object:


rayint :: Solid - Ray - Flt - Texture - Rayint
rayint (Bound sa sb) r d t =
let (Ray orig _) = r
in if inside sa orig || shadow sa r d
   then rayint sb r d t
   else RayMiss

Some kinds of primitives aren't likely to work well for bounding since 
they don't have a well-defined inside and outside (like triangles and 
discs), but I'd rather provide maximum flexibility and assume that users 
know how to use it sensibly.


http://www.haskell.org/haskellwiki/Glome_tutorial#Bounding_Objects

As for the maintenance issues, that is still a problem.  It would be 
nice to split all the individual primitives into their own modules.


Sebastian Sylvan wrote:


On 4/27/08, Jim Snow [EMAIL PROTECTED] wrote:
  

 For instance, I started out by making each primitive a separate type
 (Sphere, Triangle, etc...), and then made a type class that defines a
 ray intersection method (and a few other odds and ends), but then I
 realized that I can't do something as simple as store a list of
 primitives (or if there is in fact a way, I'm not aware of it).



You can, by using a wrapper type which wraps up any instance of the
Intersect class:

data Intersectable = forall a. Intersect a = MkIntersectable a

For convenience you probably want to instantiate this wrapper in the
class itself:

instance Intersect Intersectable where
  rayIntersection (MkIntersectable x) ray = rayIntersection x ray
  boundingVolume (MkIntersectable x) = boundingVolume x
  -- etc...

Now you can stick Intersectables in lists etc.

  

I think that sounds like what I ought to be doing.

-jim


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] announce: Glome.hs-0.3 (ray tracing digression, glome tutorial)

2008-04-26 Thread Jim Snow

David48 wrote:

On Sat, Apr 26, 2008 at 9:33 AM, Andrew Coppin
[EMAIL PROTECTED] wrote:

  

  Personally, I don't see the point in rendering a couple of million
 mathematically flat surfaces,



What about speed ?
That is a good point.  Ray tracing may give you a better image 
approximation than rasterizing triangles, but unless you're tracing an 
infinite number of rays, it is still just an approximation.  Some shapes 
(like spheres) can be rendered more quickly in a ray tracer than 
triangles, and they use less memory as well, so if you really want a 
sphere, there's no reason to approximate it with triangles.  For other 
objects, the trade-offs are more complex.

...

Unfortunately, the SDL is so complex it's well-nigh impossible to 
support in other third-party applications.


I don't think it would be impossible to support in 3rd party apps. A 
lot of work, certainly! Especially the way the parser does parsing and 
macro expansion in the same pass, so a macro body need not contain a 
syntactically-complete code fragment. I think if somebody sat down and 
wrote something that would do all the macro expansion, variable 
substitution and so forth to leave just few geometry descriptions, 
*those* would be quite easy to parse and manipulate for 3rd parties.


I guess a pov importer wouldn't necessarily be all that difficult, or an 
exporter, for that matter.  (Supporting every single primitive type, 
texture, and rendering feature would be a daunting challenge, but just 
supporting the basics might be relatively simple.)  The problem comes 
when you want to import a nice short hand-edited script, and then do a 
few things to it and export it again: suddenly the file turns into a 
multi-megabyte monstrosity with all the loops unrolled and all the 
recursive macros expanded and you lose the ability to hand-edit the 
scene.  Depending on what you're doing, this might not be a problem.




Personally, I'd quite like to write my own ray tracer to address 
some of these limitations. But every time I try, I end up hitting 
design issues [Haskell works very differently to Java] or 
performance issues [which I don't even know how to begin debugging]. 
Not to mention that POV-Ray uses sophisticated techniques like 
volume bounding that I know nothing about. (There's nothing like 
using an inherantly superior algorithm to make your code orders of 
magnitude faster...)


I haven't really run into any issues where Haskell didn't let me do 
what I want, except for the performance counters thing mentioned way 
back at the beginning of this thread (and which I've more or less 
given up on for now, since the acceleration structure seems to be 
working okay and I have other things to work on).


Well, for example, Haskell doesn't have hetrogenous lists - which are 
trivial in any OOP language. That's quite awkward to get around. Also, 
both spheres and cylinders have a radius property, but then you end 
up with name clashes. Again, a non-issue in OOP languages. [I gather 
there's some new GHC language extension to partially solve this one - 
but only when types are statically known. In the general case, you'd 
have to write a radius class and define instances... yuck!]


It's funny you mention that, those are actually problems I ran into, but 
(having learned my lesson the hard way in Ocaml), I decided not to try 
and force the language to do things my way, but instead try to do things 
in a way that Haskell makes easy. 

For instance, I started out by making each primitive a separate type 
(Sphere, Triangle, etc...), and then made a type class that defines a 
ray intersection method (and a few other odds and ends), but then I 
realized that I can't do something as simple as store a list of 
primitives (or if there is in fact a way, I'm not aware of it). 


Instead, I made a single large sum type with all my primitives:

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
etc...

(strictness annotations and a few broken primitives omitted for brevity)

so that now I can easily make a list of primitives.  (In fact, that's 
what a Group is.)  I also gave up on using named fields, since coming up 
with a separate name for each one gets ugly:  instead of radius, you 
have sphere_radius, cylinder_radius, cone_radius disc_radius, etc...


Cones and spheres and boxes and 

Re: [Haskell-cafe] announce: Glome.hs-0.3 (Haskell raytracer)

2008-04-24 Thread Jim Snow

Andrew Coppin wrote:


Wow. The POV-Ray guys are talking about Haskell [or rather, my 
personal addiction to it] and the Haskell guys are talking about 
POV-Ray... on the same day... How unlikely is that? ;-)


That's odd; I had a personal addiction to POV-Ray for a few years, and 
just now have started using Haskell.



I've been using POV-Ray for a long time. I like it for several reasons:

1. It's the only program I've ever seen [on a PC] that does ray 
tracing. [I'm sure there must be others...]
2. It's the only program I've seen that can render *real* curves, not 
fake trickery with triangle meshes.
3. It can render *arbitrary* mathematical surfaces. Want to render a 
3D slice of the 4D cubic Mandelbrot set? No problem!
4. It has a novel scene description language, which does far more 
than describe scenes. It's Turing-complete, and you can build physics 
engines with it. [It's painfully slow though!]


The Scene Description Language (SDL) is the best and worst thing about 
POV-Ray.  It's very intuitive and user-friendly, so a person can 
reasonably write a complex scene in pure code without using an external 
GUI editor.  Unfortunately, the SDL is so complex it's well-nigh 
impossible to support in other third-party applications.  It's also 
slow.  I don't know if this is still the case, but the standard way of 
doing an animation was to reference a clock variable in your scene 
source code that went from 0 to 1; for instance, a command to make a 
swing swing back and forth might looks like this:


rotate 15*sin((clock/2)*seconds*(2*pi)-((2/3)*pi))*x

seconds here is a variable set to the number of seconds in the 
animation, and x is the X axis unit vector 1,0,0.  The (2/3)*pi 
thing is to make it swing out of phase with the other swings.


(this rather obfuscatory example taken from an actual ancient povray 
source file, you can see a rendering here: 
http://syn.cs.pdx.edu/~jsnow/playground.png)


The scene then has to be re-parsed for every frame.  For complex scenes, 
the scene parsing could take longer than the actual render.


There are many other PC programs that do ray tracing, but POV-Ray is the 
only one I've had any experience with.


The POV-Ray team is currently working on the first multi-threaded 
version. [After years of saying it would never happen.] It's taking a 
while. (That's partly because the developers take product quality very 
seriously.) It should be interesting when it's done, but it's still 
taking a while.
Personally, I'd quite like to write my own ray tracer to address some 
of these limitations. But every time I try, I end up hitting design 
issues [Haskell works very differently to Java] or performance issues 
[which I don't even know how to begin debugging]. Not to mention that 
POV-Ray uses sophisticated techniques like volume bounding that I know 
nothing about. (There's nothing like using an inherantly superior 
algorithm to make your code orders of magnitude faster...)


I haven't really run into any issues where Haskell didn't let me do what 
I want, except for the performance counters thing mentioned way back at 
the beginning of this thread (and which I've more or less given up on 
for now, since the acceleration structure seems to be working okay and I 
have other things to work on).


I would certainly welcome any patches to Glome if you want to contribute 
in some way rather than write something from scratch.


A good acceleration structure definitely makes everything go a lot 
faster.  It's the difference between rendering a scene in a few seconds 
or ten minutes.


BIH is what I'm using.  It's relatively new.  Here's a paper about it:  
http://ainc.de/Research/BIH.pdf


The actual constructor is based loosely on this pseudocode: 
http://ompf.org/forum/viewtopic.php?p=1411#p1411



Evan Laforge wrote:

Not knowing anything about raytracing, one of the things I found
interesting about the paper was that he claimed that the speedups were
from using coherent ray packets, and that the shader model was
orthogonal, and enough much is spent raycasting that the shader code
to make much difference.  The implication was that you could graft a
packet style raycasting engine onto even povray and give it a nice
speed boost... though you might have to lose the nifty real shapes
to tessellated approximations.

Is this accurate?  True but reality is more complicated?
  
You don't need to drop support for the whole multitude of primitives, 
though the ones that are packet-friendly will render faster.  Many 
modern ray tracers spend most of their time traversing the acceleration 
structure rather than doing intersection tests with actual geometry, so 
all you really need to do to get most of the benefit of packet tracing 
is to make the acceleration structure support packets.  (For the actual 
geometry, you can fall back on mono-rays.)  I tried 2x2 packets out last 
night and got about a 10-15% speed improvement on the level-3 SPD 
sphereflake.  (Shadow and reflection rays 

Re: [Haskell-cafe] announce: Glome.hs-0.3 (Haskell raytracer)

2008-04-23 Thread Jim Snow

Derek Elkins wrote:


Ingo Wald's work on interactive coherent raytracing springs to mind.
http://www.sci.utah.edu/~wald/Publications/

Interactive Rendering with Coherent Raytracing
http://graphics.cs.uni-sb.de/~wald/Publications/EG2001_IRCRT/InteractiveRenderingWithCoherentRayTracing.pdf
is a decent, if dated, introduction.  He clearly has much more newer stuff as 
well.

  
Those are good links.  It's good to see that the groups of people who 
know about Haskell and people who know about ray tracing do, in fact, 
overlap.


Background information for everyone else:  Wald's work is related to 
OpenRT, which is an OpenGL-like api for interactive ray tracing  
(despite the name, it is not, in fact, open source).  OpenRT makes for 
stiff competition.  Arauna (http://igad.nhtv.nl/~bikker/) is very 
impressive, as well.  On the other end of the spectrum, there's POV-Ray, 
which isn't known for its speed, but it is very flexible in the kinds of 
things it can render and can generate some fairly realistic images.  
Unlike most real-time ray tracers, which only render triangles, POV-Ray 
can render native representations of spheres, cones, toruses, 
heightfields, julia fractals, and a few dozen other kinds of 
primitives.  Pbrt (http://www.pbrt.org/) is another renderer, more 
modern than POV-Ray, that focuses more on output quality than speed.


Unfortunately, all the notable ray tracers that I'm aware of are written 
in C or C++ (often with a little hand-coded SSE), and as you might 
imagine I find this to be a sad state of affairs.  Not that those are 
bad languages for this kind of work, but they shouldn't be the only option.


I've ended up writing something more like POV-Ray than OpenRT, and 
that's fine with me.  I'd rather have something that's slower but more 
expressive than fast but inflexible.  (The former is also perhaps more 
easily attainable, particularly in Haskell.) 

This isn't to say that I'm not interested in making it fast as well.  
There are plenty of ways to make my raytracer faster: Kd-trees built 
using a surface area heuristic performed better than naively-built BIH 
when I implemented them in my ocaml raytracer (though they take longer 
to construct).  If I can figure out how quaternions work, I could 
probably use them instead of transformation matricies to store cones in 
order to cut down on memory overhead (4 floats versus 24, if I 
understand correctly).  Ray packets, as described in Wald's paper linked 
above, might help as well.


Simon Marlow wrote:
There's definitely a bug here, regardless of whether this example 
demonstrates it.  Use of par shouldn't introduce a space leak, and 
currently it can.


(fortunately I'm fixing it as we speak...)

Cheers,
Simon 

Oh, good.

-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] announce: Glome-hs-0.4.1 (Haskell raytracer, now with cabal support)

2008-04-19 Thread Jim Snow

Don Stewart wrote:

jsnow:
  

A new version of my raytracer is out...



Very impressive. Did you consider cabalising the Haskell code, so it 
can be easily distributed from hackage.haskell.org?


...

-- Don
  


A new version is up on hackage now:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/glome-hs

In addition to the cabal conversion, it has a few bug fixes, performance 
improvements, and various code cleanups relative to version 0.3.


If anyone has any problems with it, let me know.

-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] announce: Glome.hs-0.3 (Haskell raytracer)

2008-04-18 Thread Jim Snow

Don Stewart wrote:

jsnow:
  

A new version of my raytracer is out. ...



Very impressive. Did you consider cabalising the Haskell code, so it 
can be easily distributed from hackage.haskell.org?


I note on the website you say:

no threading (shared-memory concurrency is not supported by ocaml,
in haskell it's buggy)

Could you elaborate on this? Shared memory concurrency is a sweet spot
in Haskell, and heavily utilised, so I think we'd all like to know more
details..

-- Don
  

The concurrency bug has to do with excessive memory use, and was discussed 
earlier here on the mailing list (search for Glome).
http://hackage.haskell.org/trac/ghc/ticket/2185


The other problem I had with concurrency is that I was getting about a 
50% speedup instead of the 99% or so that I'd expect on two cores.  I 
figured I'm probably doing something wrong.


I don't have any objection to using cabal, I just haven't gone to the 
trouble to figure it out yet.  Maybe in the next release.



Sebastian Sylvan wrote:
Not sure what you need shared memory concurrency for in this case as 
it seems to be a straightforward parallelism problem (i.e. the 
different threads would be different pixels, there is no sharing needed).


The scene is shared between threads.  (Complex scenes can be quite 
large.)  I'm assuming this is handled as a read-only shared memory 
region or something similar, as one might expect, and is not actually 
copied.


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] announce: Glome.hs-0.3 (Haskell raytracer)

2008-04-18 Thread Jim Snow

David Roundy wrote:

On Sat, Apr 19, 2008 at 12:19:19AM +0400, Bulat Ziganshin wrote:
  

Saturday, April 19, 2008, 12:10:23 AM, you wrote:


The other problem I had with concurrency is that I was getting about a
50% speedup instead of the 99% or so that I'd expect on two cores.  I 
  

2 cores doesn't guarantee 2x speedup. some programs are limited by
memory access speed and you still have just one memory :)



In fact, this is relatively easily tested (albeit crudely):  just run two
copies of your single-threaded program at the same time.  If they take
longer than when run one at a time, you can guess that you're
memory-limited, and you won't get such good performance from threading your
code.  But this is only a crude hint, since memory performance is strongly
dependent on cache behavior, and running one threaded job may either do
better or worse than two single-threaded jobs.  If you've got two separate CPUs
with two separate caches, the simultaneous single-threaded jobs should beat the
threaded job (meaning take less than twice as long), since each job should
have full access to one cache.  If you've got two cores sharing a single
cache, the behavior may be the opposite:  the threaded job uses less total
memory than the two single-threaded jobs, so more of the data may stay in
cache.

For reference, on a friend's dual quad-core Intel system (i.e. 8 cores
total), if he runs 8 simultaneous (identical) memory-intensive job he only
gets about five times the throughput of a job, meaning that each core is
running at something like 60% of it's CPU capacity due to memory
contention.  It's possible that your system is comparably limited, although
I'd be suprised, somehow it seems unlikely that your ray tracer is
stressing the cache all that much.
  

On a particular scene with one instance of the single-threaded renderer
running, it takes about 19 seconds to render an image.  With two
instances running, they each take about 23 seconds.  This is on an
Athlon-64 3800+ dual core, with 512kB of L2 cache per core.  So, it
seems my memory really is slowing things down noticeably.

-jim

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] announce: Glome.hs-0.3 (Haskell raytracer)

2008-04-18 Thread Jim Snow

David Roundy wrote:

On Fri, Apr 18, 2008 at 02:09:28PM -0700, Jim Snow wrote:
  

On a particular scene with one instance of the single-threaded renderer
running, it takes about 19 seconds to render an image.  With two
instances running, they each take about 23 seconds.  This is on an
Athlon-64 3800+ dual core, with 512kB of L2 cache per core.  So, it
seems my memory really is slowing things down noticeably.



This doesn't mean there's no hope, it just means that you'll need to be
extra-clever if you're to get a speedup that is close to optimal.  The key
to overcoming memory bandwidth issues is to think about cache use and
figure out how to improve it.  For instance, O(N^3) matrix multiplication
can be done in close to O(N^2) time provided it's memory-limited, by
blocking memory accesses so that you access less memory at once.

In the case of ray-tracing I've little idea where or how you could improve
memory access patterns, but this is what you should be thinking about (if
you want to optimize this code).  Of course, improving overall scaling is
best (e.g. avoiding using lists if you need random access).  Next I'd ask
if there are more efficent or compact data structures that you could be
using.  If your program uses less memory, a greater fraction of that memory
will fit into cache.  Switching to stricter data structures and turning on
-funbox-strict-fields (or whatever it's called) may help localize your
memory access.  Even better if you could manage to use unboxed arrays, so
that your memory accesses really would be localized (assuming that you
actually do have localize memory-access patterns).

Of course, also ask yourself how much memory your program is using in
total.  If it's not much more than 512kB, for instance, we may have
misdiagnosed your problem.
  
Interestingly, switching between Float and Double doesn't make any 
noticeable difference in speed (though I see more rendering artifacts 
with Float).  Transformation matrices are memory hogs, at 24 floats each 
(a 4x4 matrix and its inverse with the bottom rows omitted (they're 
always 0 0 0 1)).  This may be one reason why many real-time ray tracers 
just stick with triangles; a triangle can be transformed by transforming 
its verticies, and then you can throw the matrix away.


There are a lot of tricks for making ray tracers more memory-coherent.  
You can trace packets of rays instead of single rays against whatever 
acceleration structure you may be using.  Kd-tree nodes can be compacted 
to fit in a single cacheline if you arrange the tree in memory in a 
particular way that allows you to omit some of the pointers.  (I use BIH 
trees, but the same ideas probably apply.)  A lot of these sorts of 
tricks make the resulting code more complex and/or uglier.


Useful references: What Every Programmer Needs to Know About Memory 
http://lwn.net/Articles/250967/
Siggraph presentation on optimizing ray tracers (warning: ppt) 
http://www.openrt.de/Siggraph05/UpdatedCourseNotes/Stoll_Realtime.ppt


Bryan O'Sullivan wrote:

Jim Snow wrote:

  

 The concurrency bug has to do with excessive memory use, and was
 discussed earlier here on the mailing list (search for Glome).
 http://hackage.haskell.org/trac/ghc/ticket/2185



Interesting.  I looked at your test case.  I can reproduce your problem
when I build with the threaded runtime and run with a single core, but
not if I use +RTS -N2.  Did you overlook the possibility that you may
not have told GHC how many cores to use?

  
I just tested it again.  Memory usage behaves differently depending on 
how many cores I tell it to run on, but it always used the least memory 
when I compiled without threading support.  With -N1 memory usage grows 
faster than -N2, but memory is smaller and doesn't grow larger with each 
re-render (except by a very small amount) if I don't use parmap.

Also, your code is sprinkled with many more strictness annotations than
it needs.

b
  
That doesn't surprise me.  I haven't really figured out why somethings 
are faster strict or not strict, or where it doesn't matter or the 
annotations are redundant.


-jim

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] announce: Glome.hs-0.3 (Haskell raytracer)

2008-04-17 Thread Jim Snow
A new version of my raytracer is out.  It now supports cones, cylinders, 
disks, boxes, and planes as base primitives (previously it only 
supported triangles and spheres), as well as transformations of 
arbitrary objects (rotate, scale, translate) and the CSG operations 
difference and intersection.  Perlin noise and Blinn highlights have 
been added, as well.


http://syn.cs.pdx.edu/~jsnow/glome/

Glome can parse NFF-format scene files (see 
http://tog.acm.org/resources/SPD/), but many features are only 
accessible via raw Haskell, since NFF doesn't support very many kinds of 
primitives.  I included a TestScene.hs file that demonstrates how to 
create a scene with various kinds of geometry (including a crude attempt 
at a recursively-defined oak tree) in haskell.  There isn't any 
documentation yet, but many of the primitives have constructors that 
resemble their equivalents in povray, so anyone familiar with povray's 
syntax should be able to figure out what's going on.


-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Glome raytracer bug: bad output with -O2 -fasm

2008-03-28 Thread Jim Snow
I was trying to get Blinn highlights working with my raytracer, and kept 
getting ugly artifacts.  After trying a bunch of things, I finally 
compiled without -O2, and the artifacts went away.


Here's what I mean:
http://syn.cs.pdx.edu/~jsnow/glome/Glome.hs-noartifact.png
http://syn.cs.pdx.edu/~jsnow/glome/Glome.hs-artifact.png

Here's the offending code, run ./make and ./run and you should see 
the artifacts if your setup is the same as mine. (Requires OpenGL.)

http://syn.cs.pdx.edu/~jsnow/glome/glome.hs-0.2-bug.tar.gz

The artifacts also go away if I use -fvia-C.  It doesn't seem to matter 
whether I use Floats or Doubles in the rendering code.  The artifacts 
also show up with -O1.  Have I stumbled across a known compiler bug?  Or 
perhaps an OpenGL bug?  (The bug could, of course, be in my code, but 
then one might expect to get the same erroneous output every time 
regardless of compiler flags.)


To reiterate, I'm using ghc 8.6.2.

thanks,

-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Glome raytracer bug: bad output with -O2 -fasm

2008-03-28 Thread Jim Snow

Luke Palmer wrote:

On Fri, Mar 28, 2008 at 6:28 AM, Jim Snow [EMAIL PROTECTED] wrote:
  

I was trying to get Blinn highlights working with my raytracer, and kept
 getting ugly artifacts.  After trying a bunch of things, I finally
 compiled without -O2, and the artifacts went away.

 Here's what I mean:
 http://syn.cs.pdx.edu/~jsnow/glome/Glome.hs-noartifact.png
 http://syn.cs.pdx.edu/~jsnow/glome/Glome.hs-artifact.png

 Here's the offending code, run ./make and ./run and you should see
 the artifacts if your setup is the same as mine. (Requires OpenGL.)
 http://syn.cs.pdx.edu/~jsnow/glome/glome.hs-0.2-bug.tar.gz

 The artifacts also go away if I use -fvia-C.  It doesn't seem to matter
 whether I use Floats or Doubles in the rendering code.  The artifacts
 also show up with -O1.  Have I stumbled across a known compiler bug?  Or
 perhaps an OpenGL bug?  (The bug could, of course, be in my code, but
 then one might expect to get the same erroneous output every time
 regardless of compiler flags.)

 To reiterate, I'm using ghc 8.6.2.



You probably mean 6.8.2.

  

Yes, my mistake.  6.8.2.

Works for me in all cases.

% uname -a
Linux madhatter 2.6.22-gentoo-r8 #6 PREEMPT Sat Oct 20 04:19:22 GMT
2007 i686 AMD Turion(tm) 64 Mobile Technology ML-40 AuthenticAMD
GNU/Linux
% ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.8.2

Looks to me like Glome is depending on some very fine details of
floating point arithmetic.

Luke
  
After looking into this for awhile, I found that the problem was that in 
computing my Blinn factor:

blinn = fmax 0 $ (vdot halfangle n) ** shine

the (vdot halfangle n) was sometimes negative, resulting in blinn being 
NaN.  OpenGL apparently interprets NaN as 1.0 for the purposes of 
color*, so those patches were rendered bright white.  It's still a bit 
mysterious why the case where (vdot halfangle n) is negative only occurs 
if I compile with -fasm, but I can work around it for now.


-jim


* I'm using the binary-only nvidia drivers; different OpenGL 
implementations may behave differently.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] announce: Glome.hs raytracer (memory leak with parMap)

2008-03-27 Thread Jim Snow

pepe wrote:


On 27/03/2008, at 3:49, Ian Lynagh wrote:

On Wed, Mar 26, 2008 at 02:33:20PM -0700, Jim Snow wrote:


-Memory consumption is atrocious: 146 megs to render a scene that's a
33k ascii file.  Where does it all go?  A heap profile reports the max
heap size at a rather more reasonable 500k or so.  (My architecture is
64 bit ubuntu on a dual-core amd.)


I haven't looked properly yet, but it looks like something is leaking
memory that shouldn't be. The attached Gloom.hs uses constant memory,
but if you replace the map with the commented out (parMap rnf) then
the memory use seems to keep increasing, even once it has run display
once and is running it a second or third time.



In my system the leak only appears with +RTS -N1 (which is the default).
If I use -N2 or higher, then your version runs in constant memory with 
(parmap rnf).


Cheers
pepe
Using Ian Lynagh's Gloom.hs (I'm not sure if that's a typo, but it's a 
convenient way to distinguish it

from my original Glome.hs):

With parMap and +RTS -N2, I get 59 megs total mapped memory, 18 megs 
resident all three iterations.
With parMap and +RTS -N1, I get 53/21, then 99/66, then 145/112 megs 
total/resident.

With map and no RTS options, memory use is 37/4.8 all three iterations.

I'm using ghc 6.8.2 on 64-bit ubuntu.

-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] announce: Glome.hs raytracer

2008-03-26 Thread Jim Snow

I have recently posted a haskell port of my ocaml raytracer, Glome:

http://syn.cs.pdx.edu/~jsnow/glome/

It supports spheres and triangles as base primitives, and is able to 
parse files in the NFF format used by the standard procedural database 
(http://tog.acm.org/resources/SPD/).  It uses a bounding interval 
heirarchy acceleration structure, so it can render fairly complicated 
scenes in a reasonable amount of time.  Shadows and reflections are 
supported, but not specular highlights or refraction.


It's still slower than the ocaml version, but at least they're in the 
same ballpark (and a good part of that difference may be inefficiencies 
in my BIH traversal).  I would welcome any advice on making it go faster 
or use less memory.


I compile the program with ghc Glome.hs --make -fasm -O2 -threaded 
-fglasgow-exts -funbox-strict-fields -fbang-patterns -fexcess-precision 
-optc-ffast-math -optc-O2 -optc-mfpmath=sse -optc-msse2.  (I assume the 
-optc options don't do anything unless you compile via C.)


Here are some of my current concerns:

-Multi-core parallelism is working, but not as well as I'd expect: I get 
about a 25% reduction in runtime on two cores rather than 50%.  I split 
the default screen size of 512x512 into 16 blocks, and run parMap on 
those blocks with a function that turns the screen coordinates of that 
block into a list of (x,y,r,g,b) tuples that get drawn as pixels to the 
screen through OpenGL by the original thread.


-Memory consumption is atrocious: 146 megs to render a scene that's a 
33k ascii file.  Where does it all go?  A heap profile reports the max 
heap size at a rather more reasonable 500k or so.  (My architecture is 
64 bit ubuntu on a dual-core amd.)


-Collecting rendering stats is not easy without global variables.  It 
occurs to me that it would be neat if there were some sort of write-only 
global variables that can be incremented by pure code but can only be 
read from within monadic code; that would be sufficient to ensure that 
the pure code wasn't affected by the values.  The sorts of things I'm 
looking for are the number of calls to trace per image, the number of 
BIH branches traversed and ray/triangle and ray/sphere intersections per 
pixel.   (Disclaimer: I don't really fully understand monads, so I may 
be oblivious to an obvious solution.)


-Is there a fast way to cast between Float and Double?  I'm using Float 
currently, and the only reason is because that's what the OpenGL api 
expects.  I'd like to be able to use either representation, but the only 
way to cast that I've found so far is float_conv x = 
fromRational(toRational x), which is too slow.


thanks,
-jim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] announce: Glome.hs raytracer

2008-03-26 Thread Jim Snow

David Roundy wrote:

On Wed, Mar 26, 2008 at 05:07:10PM -0700, Don Stewart wrote:
  

droundy:


On Thu, Mar 27, 2008 at 01:09:47AM +0300, Bulat Ziganshin wrote:
  

-Collecting rendering stats is not easy without global variables.  It
occurs to me that it would be neat if there were some sort of write-only
global variables that can be incremented by pure code but can only be 
read from within monadic code; that would be sufficient to ensure that

the pure code wasn't affected by the values.
  

the code is called *pure* exactly because it has no side-effects and
compiler may select either to call some function two times or reuse
already computed result. actually, you can make sideeffects with
unsafePerformIO, but there is no guarantees of how many times such
code will be executed. try this:

plus a b = unsafePerformIO (modifyIORef counter (+1)) `seq` a+b


This is exactly what he wants to do.  The point of putting traces into the
code is precisely to figure out how many times it is called.  The only
trouble is that unsafePerformIO (I believe) can inhibit optimizations,
since there are certain transformations that ghc won't do to
unsafePerformIO code.
  

could we just use -fhpc or profiling here. HPC at least will tell you
how many times top level things are called, and print pretty graphs
about it.



It depends what the point is.  I've found traces to be very helpful at
times when debugging (for instance, to get values as well as counts).
Also, I imagine that manual tracing is likely to be far less invasive (if
you do it somewhat discretely) than profiling or using hpc.
  
The unsafePerformIO looks like what I want.  Profiling isn't really that 
helpful in this situation, since sometimes what you want is the number 
of times something gets called per ray and then add a bit to the color 
value of the corresponding pixel.  Something like this 
http://syn.cs.pdx.edu/~jsnow/glome/dragon-bih.png tells you a lot more 
about where your code is spending its time (the bright green places) 
than some numbers from a profiler.


I could return the relevant stats as part of the standard results from 
ray-intersection tests, but I think that would clutter the code 
unnecessarily.


Thanks everyone for the advice, it'll keep me busy for awhile. 

I got converted over to doubles, it seems to be about 10% faster or so 
with -fvia-C than regular floats with -fasm.  (I'm using ghc 6.8.2 by 
the way, which seems to generate faster code than the 6.6.1 version I 
was using earlier, so maybe the difference between -fasm and -fvia-C 
isn't as significant as it used to be.)


I'm looking into using ByteString, but it doesn't seem compatible with 
lex and reads.  I should probably do more heap profiling before I 
get too carried away, though.


-jim



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe