Well, perhaps you can help me figure out the problem with my exact program.
Just in case it matters, the program draws a Mandelbox via volumetric ray casting. I can provide more information about the function, but I wouldn't think it's necessary, since my problem is with parsing. The error I'm getting is with the where-clause at the very bottom:

traceRay (x,y) r@((cx,cy,cz):n) (vx,vy,vz) iter
    | m > 100        = do
        color $ Color3 (sin vx) (cos vy) (cos vz)
        vertex $ Vertex2 x y
    | otherwise      = do
        [boxx,boxy,boxz] <- boxFold [vx,vy,vz]
        (ballx,bally,ballz) <- ballFold (boxx,boxy,boxz)
traceRay (x, y) r (2*ballx + cx, 2*bally + cy, 2*ballz + cz) (iter-1)
        where
            boxFold [] = return []
            boxFold (a:b)
                | a > 2        = do
                    rem <- boxFold b
                    return $ (2-a):rem
                | a < (-2)     = do
                    rem <- boxFold b
                    return $ (-2-a):rem
                |otherwise     = do
                    rem <- boxFold b
                    return $ (a):rem
            ballFold (x,y,z)
                | n < 0.5       = return (4*x, 4*y, 4*z)
                | n < 1         = return (x/(n*n), y/(n*n), z/(n*n))
                | otherwise     = return (x, y, z)
                where n = sqrt $ x*x + y*y + z*z
    where m = sqrt $ vx*vx + vy*vy + vz*vz

On 7/21/2010 3:13 AM, Nicolas Wu wrote:
There's nothing wrong with the use of your example, I'm guessing it's
something in your ... that's leading to the parse error. This compiles
just fine:

f a b
  | c>  1      = 1
  | c<  1      = 2
  | otherwise  = 3
  where c = a+b

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

Reply via email to