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

Calvin Smith cs-haskell at protempore.net
Sun Dec 31 21:52:19 EST 2006


Dear haskell-cafe patrons,

I've been working through an exercise in Hudak's _The Haskell School of 
Expression_ (ex. 3.2, creating a snowflake fractal image), and am seeing 
some strange drawing behavior that I'm hoping somebody can shed some 
light on.

My initial solution is below (it requires HGL for Graphics.SOE):


module Main where

import Graphics.SOE

main =
   runGraphics (
   do w <- openWindow "Snowflake Fractal" (600, 600)
      fillStar w 300 125 256 (cycle $ enumFrom Blue)
      spaceClose w
   )

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

minSize = 2 :: Int

fillStar :: Window -> Int -> Int -> Int -> [Color] -> IO ()
fillStar w x y h clrs | h <= minSize
   = return ()
fillStar w x y h clrs
  = do drawInWindow w
                   (withColor (head clrs)
                              (polygon [t1p1,t1p2,t1p3,t1p1]))
       drawInWindow w
                   (withColor (head clrs)
                              (polygon [t2p1,t2p2,t2p3,t2p1]))
       sequence_ $ map recur [t1p1,t1p2,t1p3,t2p1,t2p2,t2p3]
    where tanPiOverSix = tan(pi/6) :: Float
          halfSide = truncate $ tanPiOverSix * fromIntegral h
          hFrag = truncate $ tanPiOverSix * tanPiOverSix * fromIntegral h
          (t1p1,t1p2,t1p3) =
            ((x, y), (x-halfSide, y+h),(x+halfSide, y+h))
          (t2p1,t2p2,t2p3) =
            ((x-halfSide, y+hFrag),(x, y+h+hFrag),(x+halfSide, y+hFrag))
          reVert y = y - ((h - hFrag) `div` 3)
          recur pnt =
            fillStar w (fst pnt) (reVert (snd pnt)) (h`div`3) (tail clrs)


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

Versioning info:

CPU: Pentium M
OS: Gentoo GNU/Linux, kernel 2.6.18
GCC: 4.1.1
GHC: 6.6
HGL: 3.1
HUGS: March 2005
[all software compiled from source using gentoo ebuilds]

Is anybody else familiar with this behavior? If not, any suggestions as 
to where I should file this as a potential bug? GHC? HGL? Both? Elsewhere?

Thanks in advance for any information.

Calvin

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


More information about the Haskell-Cafe mailing list