
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.

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

apfelmus@quantentunnel.de wrote:
Calvin Smith wrote:
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.
Thanks very much for checking this on a different platform and GHC. I filed a bug report with the HGL maintainer.
p.s. Any stylistic or other comments about the code welcome too.
It might also be a good idea not to mess with trigonometry when creating the snowflake.
Yes, that is much cleaner.
The following code demonstrates this.
Your solution is very elegant, and a big improvement over my messy first solution. Thanks for the very instructive code! Regards, Calvin
participants (2)
-
apfelmus@quantentunnel.de
-
Calvin Smith