class parameters to existential datatypes

anatoli anatoli@yahoo.com
Fri, 7 Dec 2001 08:29:44 -0800 (PST)


In similar cases I'm doing this:

> module Shapes where

> class Shape s where
>   area :: s -> Double

> data Rectangle = Rectangle Double Double

> data Circle = Circle Double

> instance Shape Rectangle where
>   area (Rectangle l w) = l*w

> instance Shape Circle where
>   area (Circle r) = 2*pi*r

> data ShapeRef = forall shape . Shape shape => ShapeRef shape
> instance Shape ShapeRef where
>   area (ShapeRef s) = area s

Now, for a heterogeneous list of shapes I can  use [ShapeRef].

The last three (== 2+N, where N is the number of methods
in the class) lines of code form a repeating pattern.
The situation is begging for a language feature! I propose
the following syntax:

> object ShapeRef of Shape

:)

--- Hal Daume III <hdaume@ISI.EDU> wrote:
> Hi,
> 
> I would like to be able to write something like this:
> 
> > data Foo c = forall a . c a => Foo a
> 
> Unfortunately, this isn't allowed (apparently) because it's an illegal
> class assertion (or at least that's what ghc tells me).
> 
> My motivation for doing this is I want to have something like List, but a
> class list where all you know is that every element is a member of some
> class.  I would write something like:
> 
> > data CList c = CNil
> >              | forall a . (c a) => CCons a (CList c)
> 
> that way I could have something like the prototypical:
> 
> > class Shape a where { area :: a -> Double }
> > data Circle = Circle Double
> > data Rectangle = Rectangle Double Double
> > instance Shape Circle where { area (Circle r) = 2 * pi * r }
> > instance Shape Rectangle where { area (Rectangle l w) = l*w }
> > MyList :: CList Shape
> > MyList = CCons (Circle 5) (CCons (Rectangle 2 3) CNil)
> 
> and then maybe have a function:
> 
> > totalArea :: (CList Shape) -> Double
> > totalArea = sum . map area
> 
> obviously this function declaration is also invalid.
> 
> so I have two questions:
> 
>   1) Is there any particular reason whey we can't do this (it would
>      break some type safety things or whatever)
>   2) Any ways to get around it?
> 
> Thanks!


__________________________________________________
Do You Yahoo!?
Send your FREE holiday greetings online!
http://greetings.yahoo.com