First of all, I'm really excited that GTK2HS 0.9.12 now allows launching SOE 
apps using GHCI.

However, in the code below the blue and green triangle should render on top of 
each other, but the green triangle is rendered incorrectly.

Being a newbie, I hesitate to file a bug report... Can anyone reproduce this? 
Maybe it works fine on unix?

Thanks,
Peter


module Main where

import Graphics.SOE.Gtk

shape = [(200,100), (200,200), (100,200), (200,100)]

main = runGraphics $ do
         w <- openWindow "Buggy polgon fill?" (300,300)
         setGraphic w $ (withColor Red $ polyline shape) `overGraphic` 
(withColor Green $ drawRegion $ createPolygon shape)
         drawInWindow w $ (withColor Red $ polyline shape) `overGraphic` 
(withColor Blue $ polygon shape)
         waitForClose w
         closeWindow w

waitForClose w = do
  e <- getWindowEvent w
  case e of 
    Closed -> return ()
    otherwise -> waitForClose w




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

Reply via email to