[Haskell-cafe] New New newbie question/help

peterv bf3 at telenet.be
Wed Jun 27 13:00:20 EDT 2007


Newbie helping newbie, cool J And indeed, this is an amazing mailing list!

 

Personally, I prefer to read fromIntegral :: (Num b, Integral a) => a -> b
like

 

IF (b is a Num) AND (a is an Integral) THEN (fromIntegral is defined and is
a function from a to b)

 

This way it resembles the mathematical symbol for implication (=>)

 

PS: Haskells "generic number system" can be very confusing for the beginner,
but it becomes very cool when you start working with type classes. You will
see that in the later chapters of  the great SOE book (animation and
reactive behaviors). The reactive behavior chapter is really hard, but don't
give up. In my case I got a real revelation, finally understanding the real
power of streams and lazy evaluation; it really changes the way you look at
the "world". As a videogames developer, I still have a lot of unanswered
questions though (for example, how to efficiently handle events between
behaviors, like collision, but I hope to find that in Yampa or newer work)

 

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

 

I am for ever obliged to this haskell community. Who would have thought that
Prof.Hudak would reply instantly, from on-the-road. I am reading his SOE.
Thanks so much.

I went with peterv's response after trying so many things. 
I tried to change to : equilateralTri Window -> Float -> Float -> Float ->
IO()
which bombed because polygon wants list of integer-pairs.

I read the definitions of fromIntegral and round and they are defined as : 
fromIntegral :: (Num b, Integral a) => a -> b
round :: (RealFrac a, Integral b) => a->b
Is it proper/ok to defines them as :
fromIntegral :: (a::Integral) -> (b::Num)
and
round :: (a::RealFrac) -> (b::Integral)  ? 
Is RealFrac is-a Num ?
Does the order matters in (Num b,Integral a) => a -> b or
                                           (Integral a,Num b) => a -> b

With your encouragements, I'll keep pluuging. Thanks. 
- br

On 6/27/07, peterv <bf3 at telenet.be> wrote:

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

 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070627/0a6c12d9/attachment.htm


More information about the Haskell-Cafe mailing list