[Haskell] Dynamic binding

Pal-Kristian Engstad pal_engstad at naughtydog.com
Wed Jun 22 22:52:21 EDT 2005


On Wednesday 22 June 2005 06:38 pm, Andrew Ward wrote:
% This general pattern of dynamic binding I use over and over again. Could
% you give me some example code of this type of thing handled in Haskell's
% way? Assuming that the number of classes deriving from shape might get
% quite large.

What is "large"? Less than, say, 30? If so:

> module Shapes where

> type Position = (Float, Float)

> data Shape = Circle Position Float
>            | Square Position Float

> prim_draw_circle x y radius = 
>     return ("circle(" ++ show x ++ ", " ++ show y ++ ", " ++
>             show radius ++ ")")  
>
> prim_draw_rect x0 y0 x1 y1 = 
>     return ("square(" ++ show x0 ++ ", " ++ show y0 ++ ", " ++ 
>             show x1 ++ ", " ++ show y1 ++ ")")  

> draw :: Shape -> IO String
> draw (Circle (x, y) radius) = prim_draw_circle x y radius
> draw (Square (x, y) size)   = prim_draw_rect x y (x+size) (y+size)

> drawShapes :: [Shape] -> IO String
> drawShapes (x:xs) = do s <- draw x
>                        putStrLn s
>                        drawShapes xs
> drawShapes []     = return ""

> shapes = [ Circle (0.0, 0.0) 1.0, 
>            Circle (1.0, 1.0) 2.0,
>            Square (0.0, 0.0) 2.0 ]

> main = drawShapes shapes

PKE.
-- 
  _       
  \`.       Pål-Kristian Engstad, Lead Programmer,
   \ `|     Naughty Dog, Inc., 1601 Cloverfield Blvd, 6000 North,
  __\ |`.   Santa Monica, CA 90404, USA. (310) 633-9112. 
    /  /o   mailto:engstad at naughtydog.com http://www.naughtydog.com
   /  '~    mailto:mrengstad at yahoo.com    http://www.engstad.com
  / ,'      Hang-gliding Rulez!
  ~'


More information about the Haskell mailing list