[Haskell-cafe] Re: Possible (GHC or HGL) bug or ??

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Mon Jan 1 07:55:04 EST 2007


Calvin Smith wrote:
> This basically works, in that it does exactly what I want in Hugs, but
> GHC sometimes pauses partway through rendering, and does not continue
> rendering until I type any key (except space, which exits) or
> unfocus/refocus the window, or move the mouse pointer across the window.
>
> Sometimes, more often the first time in a GHCI session, it renders
> completely with no pauses, and it seems to pause more and more if I
> evaluate main, then close the window, evaluate again in the same GHCI
> session, repeatedly. The same pausing behavior is observed in a
> GHC-compiled executable.
> 
> When the problem occurs, there is a message to the console that says:
> "thread blocked indefinitely".

I can reproduce this on OS X with ghc-6.4.2, X11-1.1 and HGL-3.1. The
console message is rare but I also got it once. This looks like a bug in
HGL, perhaps some issue with polling the event queue in a threaded fashion.

> p.s. Any stylistic or other comments about the code welcome too.

The infinite list of colors is a very good idea.

It might also be a good idea not to mess with trigonometry when creating
the snowflake. These things can be put into a single function (rotate)
which rotates a point around the origin by a specified number of
degrees. The following code demonstrates this. Note that the resulting
snowflake has slightly different proportions than your original one, but
it shouldn't be a problem to adjust this.

    module Main where

    import Graphics.SOE

    main = runGraphics $ do
        w <- openWindow "Snowflake Fractal" (600, 600)
        drawInWindow w $ snowflake (300,300) 200 (cycle $ enumFrom Blue)
        spaceClose w

    spaceClose w = do
        k <- getKey w
        if k == ' ' then closeWindow w else spaceClose w

    rotate :: Double -> Point -> Point
    rotate deg (x,y) = (truncate $ c*x' - s*y', truncate $ s*x' + c*y')
        where
        (x',y') = (fromIntegral x, fromIntegral y)
        rad     = deg * pi / 180
        (s,c)   = (sin rad, cos rad)

    translate :: (Int, Int) -> Point -> Point
    translate (dx,dy) (x,y) = (x + dx, y + dy)

    minSize = 2 :: Int

    snowflake :: Point -> Int -> [Color] -> Graphic
    snowflake _   h _       | h <= minSize = emptyGraphic
    snowflake pos h (c:cs)  = overGraphics $
        map (\pos -> snowflake pos (h `div` 3) cs) (mkPoints corners)
        ++ map (withColor c . polygon . mkPoints) [triangle1, triangle2]
        where
        -- things gets specified by their angle
        -- with respect to the y-axis
        mkPoints  = map $ translate pos . flip rotate (0,h)
        triangle1 = [0, 120, 240]
        triangle2 = map (180+) triangle1
        corners   = map (60*) [0..5]

Also note that I eschewed (drawInWindow) in favor of (overGraphic), but
I think that SOE will introduce that at some point, too.

A minor hint is to use Double instead of Float. It doesn't really
matter, but today's computers internally favor Double ("double precision
floating point number").


Regards,
apfelmus



More information about the Haskell-Cafe mailing list