Re: [Haskell-cafe] Polymorphic (typeclass) values in a list?

Henning Thielemann:
class Renderable a where render :: a -> RasterImage
scene :: Renderable a => [a]
This signature is valid, but it means that all list elements must be of the same Renderable type.
Yes, that's exactly the restriction I'm unhappy about.
You could let the user plug together the alternatives for Renderable. That is, declare the class Renderable and let the user define and instantiate
data Figure = Point Something | Line Something | Polygon Something
But if I already have the types Point, Line, and Polygon, and I want to create a "union type" Figure as above, then my code will look like this: data Point = Point Something data Line = Line Something data Polygon = Polygon Something data Figure = FPoint Point | FLine Line | FPolygon Polygon aFigure = FPoint Point Something aListOfFigures = [FPoint Point Something, FPolygon Polygon Something, FLine Line Something]
Is there a way of achieving what I want to do? Existentials maybe? I'm still learning the basic stuff and don't grok existentials at all, but I even if I use those, I'll still have to wrap things up in a constructor, won't I?
I assume, that you could use http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html...
That's a nice page :) From a quick reading, the best I came up with was this: data R = forall a. Renderable a => V a instance Show R where render (R a) = render a Which is precisely what I meant when I said that I'd still have to wrap things up in a constructor. Is this hidden type variable thing what "existential types" mean? OT: forall just introduces a new type variable, right? Thanks, TJ

On Fri, 2007-10-19 at 23:57 +0800, TJ wrote:
Henning Thielemann:
class Renderable a where render :: a -> RasterImage
scene :: Renderable a => [a]
This signature is valid, but it means that all list elements must be of the same Renderable type.
Yes, that's exactly the restriction I'm unhappy about.
You could let the user plug together the alternatives for Renderable. That is, declare the class Renderable and let the user define and instantiate
data Figure = Point Something | Line Something | Polygon Something
But if I already have the types Point, Line, and Polygon, and I want to create a "union type" Figure as above, then my code will look like this:
data Point = Point Something data Line = Line Something data Polygon = Polygon Something
data Figure = FPoint Point | FLine Line | FPolygon Polygon
aFigure = FPoint Point Something aListOfFigures = [FPoint Point Something, FPolygon Polygon Something, FLine Line Something]
Is there a way of achieving what I want to do? Existentials maybe? I'm still learning the basic stuff and don't grok existentials at all, but I even if I use those, I'll still have to wrap things up in a constructor, won't I?
I assume, that you could use http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html...
That's a nice page :) From a quick reading, the best I came up with was this:
data R = forall a. Renderable a => V a
instance Show R where render (R a) = render a
Which is precisely what I meant when I said that I'd still have to wrap things up in a constructor. Is this hidden type variable thing what "existential types" mean?
Yes.
OT: forall just introduces a new type variable, right?
No. The type variable really is universally quantified (in one place: V :: forall a. Renderable a => V a). forall is used here to avoid introducing an exists keyword. jcc

You've almost got it right below. Here's an example of using existentials: {-# OPTIONS -fglasgow-exts #-} data AnyNum where E :: forall a. Num a => a -> AnyNum l :: [AnyNum] l = [E (1 :: Integer), E (2.0 :: Float)] neg :: [AnyNum] -> [AnyNum] neg = map (\ (E x) -> E (0 - x)) -- testing: instance Show AnyNum where show (E x) = show x main = print (show (neg l)) What's going on here? The idea is that the constructor 'E' of type AnyNum takes three things a) a type 'a' b) a witness that 'a' supports the operations of the Num class c) a particular value of that type 'a' So, in a very explicit notation, a value constructed with E might look like E Int <evidence of Num Int> 1 or E Float <evidence of Num Float> 2.0 That is, E pairs up a type (with some type class constraints) and a value of that type. (Of course, in Haskell you only write the value explicitly.) The type that you pair up with a value is hidden (existentially quantified)---it does not show up in the result type of the pair, which is just AnyNum. So if you just have something of type AnyNum, you don't know what the type component of the pair is. Now, when you want to use an AnyNum, you can pattern match against the pair. In a very explicit notation, you'd write case x :: AnyNum of E a <evidence of Num a> x -> body and in the body, you know that x has type 'a' for some abstract 'a' that is an instance of Num---but that's all you know! So you can work with x using the operations of the Num class, but that's it. Incidentally, why does the Haskell syntax use the keyword "forall" to introduce an existential type? The above type forall a. Num a => a -> AnyNum is just a curried version of the type (exists a. Num a => a) -> AnyNum The argument to E is morally an existential package (a pair) of a type and a term (whose type may mention the paired type). Existentials are the primitive notion here; GHC just happens to provide them using the data mechanism. -Dan On Oct19, TJ wrote:
Henning Thielemann:
class Renderable a where render :: a -> RasterImage
scene :: Renderable a => [a]
This signature is valid, but it means that all list elements must be of the same Renderable type.
Yes, that's exactly the restriction I'm unhappy about.
You could let the user plug together the alternatives for Renderable. That is, declare the class Renderable and let the user define and instantiate
data Figure = Point Something | Line Something | Polygon Something
But if I already have the types Point, Line, and Polygon, and I want to create a "union type" Figure as above, then my code will look like this:
data Point = Point Something data Line = Line Something data Polygon = Polygon Something
data Figure = FPoint Point | FLine Line | FPolygon Polygon
aFigure = FPoint Point Something aListOfFigures = [FPoint Point Something, FPolygon Polygon Something, FLine Line Something]
Is there a way of achieving what I want to do? Existentials maybe? I'm still learning the basic stuff and don't grok existentials at all, but I even if I use those, I'll still have to wrap things up in a constructor, won't I?
I assume, that you could use http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html...
That's a nice page :) From a quick reading, the best I came up with was this:
data R = forall a. Renderable a => V a
instance Show R where render (R a) = render a
Which is precisely what I meant when I said that I'd still have to wrap things up in a constructor. Is this hidden type variable thing what "existential types" mean?
OT: forall just introduces a new type variable, right?
Thanks,
TJ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Dan Licata
-
Jonathan Cast
-
TJ