
I'm new to functional programming and to haskell. I'm reading ``The Haskell School of Expression'' by Paul Hudak and I'm studying how to solve exercise 2.2. My difficulty here is more algorithmic than Haskellian, but perhaps many here have solved this exercise already, or would know how to solve it; I hope it's okay to post. (*) Exercise 2.2 Define a function regularPolygon :: Int -> Side -> Shape such that regularPolygon n s is a regular polygon with n sides, each of length s. (Hint: consider using some of Haskell's trigonometric functions, such as sin :: Float -> Float, cos :: Float -> Float, and tan :: Float -> Float.) My idea is to start with the vertices (0,0) and (0,s). Then I ``connect a line'' from (0,0) to (0,s) and I then I need to compute the next vertex of the polygon. The angles of a regular polygon are alpha = ((n - 2) * pi)/n, where n is the number of sides of the polygon. So the third vertex of the polygon is x = cos (180 - alpha) * s y = sin (180 - alpha) * s, but I don't know how to teach the computer to get to the forth vertex. Once I figure that in a general way, I would just call myself until I get to the last vertex; if I start at n, we end at at n = 2 in which I return []. Something like:
data Shape = Polygon [Vertex] deriving Show
type Side = Float type Vertex = (Float, Float)
regularPolygon :: Int -> Side -> Shape regularPolygon n s = Polygon ((0,0) : (0,s) : buildList n s (fromIntegral n)) where buildList :: Int -> Side -> Float -> [Vertex] buildList 2 _ _ = [] buildList n s m = let x = cos(pi - alpha) * s y = sin(pi - alpha) * s alpha = ((m - 2) * pi)/m in (x,y) : buildList (n-1) s m
but right now it just repeats all the vertices after the second. Any help is appreciated.

2007/8/19, Daniel C. Bastos
Any help is appreciated.
I also had problem with this exercise. However this was more Haskell newbie problem :) If you're feeling lost you can always try google and come up with this blog with solutions to exercises from this book. You should find it helpful: http://www.elbeno.com/haskell_soe_blog/?p=7 Cheers, Radek. -- Codeside: http://codeside.org/ Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/

(*) Exercise 2.2
Define a function regularPolygon :: Int -> Side -> Shape such that regularPolygon n s is a regular polygon with n sides, each of length s. (Hint: consider using some of Haskell's trigonometric functions, such as sin :: Float -> Float, cos :: Float -> Float, and tan :: Float -> Float.)
I'm a Haskell newbie, too, but I would use the angle between the line, which is defined from the point of orign to every corner of the polygon, and a coordinate axis. Then I would add some Postscript output for easier testing. http://www.frank-buss.de/tmp/polygons.png import System type Shape = [Vertex] type Side = Float type Vertex = (Float, Float) regularPolygon :: Int -> Side -> Shape regularPolygon n s = (buildList n) where buildList 0 = [] buildList i = let x = cos(alpha) * s y = sin(alpha) * s alpha = 2*pi/(fromIntegral n)*(fromIntegral i) in (x,y) : buildList (i-1) showVertex vertex = show (fst vertex) ++ " " ++ show (snd vertex) postscriptPolygon n s = (showVertex first ++ " moveto\n") ++ (unlines (map (\vertex -> (showVertex vertex ++ " lineto")) rest)) ++ (show (fst first) ++ " " ++ show (snd first) ++ " lineto") ++ "\n" where poly = regularPolygon n s first = head poly rest = tail poly main = do let file = "c:\\tmp\\test.ps" writeFile file ("20 20 scale 0.1 setlinewidth\n" ++ "5 5 translate\n" ++ (postscriptPolygon 4 4) ++ "8 4 translate\n" ++ (postscriptPolygon 7 2) ++ "stroke showpage\n") system ("c:\\Programme\\gs\\gs8.15\\bin\\gswin32.exe -g500x500 " ++ file) -- Frank Buss, fb@frank-buss.de http://www.frank-buss.de, http://www.it4-systems.de

On 8/19/07, Frank Buss
(*) Exercise 2.2
Define a function regularPolygon :: Int -> Side -> Shape such that regularPolygon n s is a regular polygon with n sides, each of length s. (Hint: consider using some of Haskell's trigonometric functions, such as sin :: Float -> Float, cos :: Float -> Float, and tan :: Float -> Float.) <snip> import System
type Shape = [Vertex] type Side = Float type Vertex = (Float, Float)
regularPolygon :: Int -> Side -> Shape regularPolygon n s = (buildList n) where buildList 0 = [] buildList i = let x = cos(alpha) * s y = sin(alpha) * s alpha = 2*pi/(fromIntegral n)*(fromIntegral i) in (x,y) : buildList (i-1)
That looks good, but I'd do like this: regularPolygon :: Int -> Side -> Shape regularPolygon n s = (buildList n) where buildList 0 = [] buildList i = let x = cos(alpha) * r y = sin(alpha) * r alpha = 2*(fromIntegral i)*pi / fromIntegral n r = sqrt (s^2 / (2*(1 - cos (2*pi / fromIntegral n)))) in (x,y) : buildList (i-1) I used the cosine law in order to calculate r. After all, s is actually the size of the side of the polygon and not the distance of its vertices from the origin.

From: Rafael Almeida [mailto:almeidaraf@gmail.com]
I used the cosine law in order to calculate r. After all, s is actually the size of the side of the polygon and not the distance of its vertices from the origin.
You are right, my solution was wrong. If you don't mind rounding errors, this is another solution: import List regularPolygon n s = iteratedAdd segments where a = 2 * pi / (fromIntegral n) segments = [rotatedSegment (fromIntegral i) | i <- [0..n-1]] rotatedSegment i = (s*sin(i*a),s*cos(i*a)) iteratedAdd = snd . mapAccumR (\s x->(add s x, add s x)) (0,0) add (x1,y1) (x2,y2) = (x1+x2,y1+y2) With this list comprehension, your solution could be written like this: regularPolygon n s = [(r * cos(a i), r * sin(a i)) | i <- [0..n-1]] where a i = 2 * fromIntegral i * pi / fromIntegral n r = sqrt(s^2 / (2 * (1 - cos(2 * pi / fromIntegral n)))) -- Frank Buss, fb@frank-buss.de http://www.frank-buss.de, http://www.it4-systems.de
participants (4)
-
dbastos@toledo.com
-
Frank Buss
-
Radosław Grzanka
-
Rafael Almeida