[Haskell-cafe] Mis-understanding something in Haskell interpretation
Edward Ing
inge at ihitacow.com
Tue Oct 3 13:44:27 EDT 2006
Hi,
I am new to Haskell and am learning Haskell on my own with "The Haskell
School of Expression". Unfortunately there is no teacher that comes
along with the book. I am having a problem with loading an excerise.
I get this message from ghci on a :l Shapes.hs
Shapes.hs:40:40:
Couldn't match `Side' against `Int'
Expected type: Side
Inferred type: Int
In the first argument of `sin', namely `angle'
In the second argument of `(*)', namely `(sin angle)'
Failed, modules loaded: none.
The source is below. Side is types as Float. My assumption was that
Haskell would know how to convert the Int to a float and all would be
well. I am I mistaken somewhere? The problem is with the last line.
Tips would be appreciated.
Source Shapes.hs:
module Shapes where
data Shape = Rectangle Side Side
| Ellipse Radius Radius
| RtTriangle Side Side
| Polygon [Vertex]
deriving Show
type Radius = Float
type Side = Float
type Vertex = (Float, Float)
type Angle = Float
rectangle :: Shape -> Shape
rectangle (Rectangle width height )= Polygon [(0, 0),(0, height),
(width, height), (width, 0)]
rtTriangle :: Shape -> Shape
rtTriangle (RtTriangle width height) = Polygon [(0,0),(0,height),
(width, height)]
regularPolygon :: Int -> Side -> Shape
regularPolygon totalSides sideLength =
let initial = (0.0,0.0) in
Polygon (initial : vertices initial 1 totalSides sideLength )
vertices :: Vertex -> Int -> Int -> Side -> [Vertex]
vertices _ 0 _ _ = []
vertices lastVertex currentSide totalSides length =
let currentVertex = vertex lastVertex currentSide totalSides length in
currentVertex: vertices currentVertex (totalSides - (currentSide +
1)) totalSides length
vertex :: Vertex -> Int -> Int -> Side -> Vertex
vertex (a ,b) currentSide totalSides length =
let angle = 1.0 * (360 / totalSides) * currentSide in
( a + ( length * (sin angle)), b + ( (*) (cos angle) length ) )
More information about the Haskell-Cafe
mailing list