[Haskell-cafe] New New newbie question/help

peterv bf3 at telenet.be
Wed Jun 27 09:02:23 EDT 2007


I'm also a haskell newbie, but I'll try to help; the experts here will
correct me if I'm wrong.

The compiler cannot in all cases infer the type of a number. pi can be a
Float, a Double, or even a complex number. 

Furthermore unlike in C/C++ you cannot just mix integer and floating
operations.

For example, the following works for me:

f :: Int -> Int
f side = round ( (fromIntegral side) * sin ( (pi::Float) / 3 ) )

or easier

f side = round ( (fromIntegral side) * sin (pi / 3.0) )

I'm sure the experts here will have a better solution.

Peter
-----Original Message-----
From: haskell-cafe-bounces at haskell.org
[mailto:haskell-cafe-bounces at haskell.org] On Behalf Of Balu Raman
Sent: Wednesday, June 27, 2007 1:25 PM
To: Haskell-Cafe at haskell.org
Subject: [Haskell-cafe] New New newbie question/help

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
Haskell-Cafe at haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list