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
 
            On 27/06/07, Balu Raman 
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)
Your problem lies in this section here. Let's look at the error message:
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
The problem comes from the calculations of 'a' and 'b'. The function sin doesn't return an Int value. It returns types within the type class Floating (annotated as below, for some unspecified 'a').
sin (pi/3) :: Floating a => a side :: Int
Since the type checker has one unknown type, a, and one known, Int, it tries to put the two together. Then it finds that Int is not an instance of the Floating class, so a /= Int. So it asks you to make one:
Probable fix: add an instance declaration for (Floating Int)
In this case, the advice is bad. There is no reasonable way of making a machine integer a member of the floating class. What you need to do instead is ensure that you're using a type that is a member of the Floating class - that is, convert from an Int before you start the calculation. The function fromIntegral should come in handy:
let n = 3 :: Int (fromIntegral n) * sin (pi/3) 2.598076211353316
Good luck! D.
 
            I think that an easier solution is to just change the type of equilateralTri to: equilateralTri :: Window -> Float -> Float -> Float -> IO() But I am on the road and wasn't able to actually run the code. -Paul Dougal Stanton wrote:
On 27/06/07, Balu Raman
wrote: 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)
Your problem lies in this section here. Let's look at the error message:
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
The problem comes from the calculations of 'a' and 'b'. The function sin doesn't return an Int value. It returns types within the type class Floating (annotated as below, for some unspecified 'a').
sin (pi/3) :: Floating a => a side :: Int
Since the type checker has one unknown type, a, and one known, Int, it tries to put the two together. Then it finds that Int is not an instance of the Floating class, so a /= Int. So it asks you to make one:
Probable fix: add an instance declaration for (Floating Int)
In this case, the advice is bad. There is no reasonable way of making a machine integer a member of the floating class. What you need to do instead is ensure that you're using a type that is a member of the Floating class - that is, convert from an Int before you start the calculation.
The function fromIntegral should come in handy:
let n = 3 :: Int (fromIntegral n) * sin (pi/3) 2.598076211353316
Good luck!
D.
 
            On 27/06/07, Paul Hudak 
I think that an easier solution is to just change the type of equilateralTri to:
equilateralTri :: Window -> Float -> Float -> Float -> IO()
But I am on the road and wasn't able to actually run the code.
I don't have my copy of SOE to hand, so I didn't want to say that in case it subverted the point of the exercise. But of course I will defer to authority on this matter ;-) D.
 
            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@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Balu Raman Sent: Wednesday, June 27, 2007 1:25 PM To: Haskell-Cafe@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
 
            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 
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@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Balu Raman Sent: Wednesday, June 27, 2007 1:25 PM To: Haskell-Cafe@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
 
            Is it proper/ok to defines them as : fromIntegral :: (a::Integral) -> (b::Num) and round :: (a::RealFrac) -> (b::Integral) ?
No; Integral, Num and RealFrac are type classes, not types. Think of a type class as a "set of types" which all support certain operations. For example, anything in the Num class must implement +, -, *, and a few other things. So a type signature like (Integral a) => a means "any type a, as long as it is in the type class Integral". Is RealFrac is-a Num ? Yes, any type which is in the RealFrac type class must also be in the Num type class. Does the order matters in (Num b,Integral a) => a -> b or
(Integral a,Num b) => a -> b
No, the order of type class constraints doesn't matter. With your encouragements, I'll keep pluuging. Thanks. Good luck! -Brent
 
            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@haskell.org
[mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Balu Raman
Sent: Wednesday, June 27, 2007 5:37 PM
To: Haskell-Cafe@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 
 
            Thanks Paul.
Yes, I was missing a node in the polygon list.
I did  change to equilateralTri :: Float -> Float -> Float -> IO() for
the scalings that you mentioned. Yes, i was doing the snowflake
problem.
thanks,
balu raman
On 6/27/07, Paul Hudak 
Hi Balu. It looks like you've gotten some excellent advice from others, but permit me to add a further comment regarding the broader context, now that I've had a chance to look a little closer.
It looks like you're trying to solve the "fractal snowflake" exercise. One of the challenges in programming with numbers is deciding what representation to use. Ints are great because they are efficient, but if you need to use trigonometric functions such as sine, etc. then you need Floats or Doubles. The problem here is that you need both -- you need Ints because polygon is defined in terms of pixels, which are represented as Ints, and you need Floats because you need to compute the coordinates of an equilateral triangle, which (interestingly) can't be represented using integer coordinates. But also, in the case of the snowflake fractal, you will need to scale the size as you recurse. The reason that the latter is important is that it implies that the arguments to equilateralTri should perhaps be floats -- otherwise you will once again run into numeric conversion problems as you try to scale the arguments (unless you always start with a pixel size that is a multiple of six).
So -- I would still suggest using Window -> Float -> Float -> Float -> IO() as the type for equilateralTri. It's only when you make the call to polygon that you need Ints. And there you can just use "round" to convert the Floats to Ints.
As an aside, looking at your code a bit closer, I see this:
(polygon [(x,y),(a,b),(x,y)])) where b = y + side * sin(pi/3) a = x + side * cos(pi/3)
Something is not right here -- you repeat (x,y) as a vertex. Probably the third vertex should be (x+side,y). Also, note that sin (pi/3) and cos (pi/3) are constants (namely 0.866... and 0.5, resp.).
I hope this helps,
-Paul
Balu Raman wrote: 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
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@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Balu Raman Sent: Wednesday, June 27, 2007 1:25 PM To: Haskell-Cafe@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
 
            Paul Hudak wrote:
As an aside, looking at your code a bit closer, I see this:
(polygon [(x,y),(a,b),(x,y)])) where b = y + side * sin(pi/3) a = x + side * cos(pi/3)
Something is not right here -- you repeat (x,y) as a vertex. Probably the third vertex should be (x+side,y). Also, note that sin (pi/3) and cos (pi/3) are constants (namely 0.866... and 0.5, resp.).
Constant they may be, but it's still clearer in my opinion to write them like that. To factor them out as constants (except simply as an exercise in the practise of code refactoring) smacks of premature optimization to me. Jules
participants (6)
- 
                 Balu Raman Balu Raman
- 
                 Brent Yorgey Brent Yorgey
- 
                 Dougal Stanton Dougal Stanton
- 
                 Jules Bean Jules Bean
- 
                 Paul Hudak Paul Hudak
- 
                 peterv peterv