Hi,
Hope someone can help me, just starting out with SOE.My code :
module Main where
import Graphics.SOE.Gtk

spaceClose :: WIndow -> IO()
spaceClose w = do k <- getKey w
                                  if k == ' ' then closeWindow w
                                                  else spaceClose w

equilateralTri :: Window -> Int -> Int -> Int -> IO()
equilateralTri w x y side
                      = drawInWindow w (withColor Red
                                                          (polygon
[(x,y),(a,b),(x,y)]))
                          where
                           b = y + side * sin(pi/3)
                           a = x + side * cos(pi/3)
main =
      runGraphics(
                             do w <- openWindow "Equilateral
Triangle" (400,400)
                                   equilateralTri w 50 300 200
                                   spaceClose w
                           )

all of the above in file triangle.hs
when I do a :l triangle.h in ghci,  I get the following error
triangle.hs:17:36:
       No instance for (Floating Int)
            arising from use of 'pi' at triangle.hs:17:36-37
       Probable fix: add an instance declaration for (Floating Int)
       In the first argument of '(/)', namely 'pi'
       In the first argument of 'cos', namely '(pi / 3)'
       In the second argument of '(*)', namely 'cos (pi/3)'
Failed, modules loaded: none

Can someone help me what's going on to a brand new newbie. All I can
figure out is that some type mismatch between float and int . I tried various
combinations of lets and wheres and I still get the same complaints.
I am just linearly studying SOE
Thanks,
- br
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to