On 8/19/07, Frank Buss <[EMAIL PROTECTED]> wrote:
> > (*) 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.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to