Polymorphic (typeclass) values in a list?

Why is it illegal to store values of differing types, but which instance the same class, into a list? e.g. a = [ 1, 2.0 ] :: Num a => [a] After all, sometimes all you need to know about a list is that all the elements support a common set of operations. If I'm implementing a 3d renderer for example, I'd like to have class Renderable a where render :: a -> RasterImage scene :: Renderable a => [a] Instead of hardcoding a bunch of types as being Renderable, as in data Renderable = Point Something | Line Something | Polygon Something scene :: [Renderable] Or maybe data Point = Point Something data Line = Line Something data Polygon = Polygon Something scene :: { points :: [Point], lines :: [Line], polygons :: [Polygons] } 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? Thanks a bunch, TJ

On Fri, 19 Oct 2007, TJ wrote:
Why is it illegal to store values of differing types, but which instance the same class, into a list? e.g.
a = [ 1, 2.0 ] :: Num a => [a]
After all, sometimes all you need to know about a list is that all the elements support a common set of operations. If I'm implementing a 3d renderer for example, I'd like to have
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.
Instead of hardcoding a bunch of types as being Renderable, as in
data Renderable = Point Something | Line Something | Polygon Something
scene :: [Renderable]
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 or data Shape = Point Something | Line Something | Polygon Something | Spline Something or whatever he needs. That's a Haskell 98 solution.
Or maybe
data Point = Point Something data Line = Line Something data Polygon = Polygon Something
scene :: { points :: [Point], lines :: [Line], polygons :: [Polygons] }
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...

TJ wrote:
Why is it illegal to store values of differing types, but which instance the same class, into a list? e.g.
a = [ 1, 2.0 ] :: Num a => [a]
The problem is that Num a => [a] really means: forall a. Num a => [a] That is, a list of type Num a => [a] could either be a list of Integers, or a list of Doubles, or ..., but not a heterogeneous list. Slightly varying the type does not help, either: [forall a. Num a => a] This would mean that each and every value in the list is itself polymorphic. What we ultimately need could be written as [exists a. Num a => a] i. e. for each value in the list there is a Num type to which the value belongs. While there is no “exists” quantifier in Haskell types, you can use existentially quantified types (existentials) for your purpose. Given the following data type ExistsNumber data ExistsNumber = forall a. Num a => Number a instance Show Number where -- So we can try this in ghci show (Number a) = show a You may read the data declaration as: “(Number a) has type ExistsNumber if a belongs to the type class Num, i. e. for all a in Num.” Now you can “wrap” any value in the type class Num into an ExistsNumber value, thus “forgetting” its concrete type. You can then construct a list of type [ExistsNumber] easily: [ Number 1, Number (2::Int), Number (3::Double) ] Kalman

On 19/10/2007, Kalman Noel
data ExistsNumber = forall a. Num a => Number a
I'm without a Haskell compiler, but shouldn't that be "exists a."? IIRC forall will work too, but the "right" way to do it is "exists", right? So to avoid confusion, use "exists" rather than "forall" when you want existential rather than universal quantification. Also, you might want to instantiate the existential type in the class too. E.g. class Render a where render :: a -> IO () instance Render ... where -- lots of these data Renderable = exists a . Render a => Renderable a instance Render Renderable where render (Renderable a) = render a Now we can call "render" on both the actual renderable values themselves, as well as well as the "wrapped" ones. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

On Oct 19, 2007, at 12:11 , Sebastian Sylvan wrote:
On 19/10/2007, Kalman Noel
wrote: data ExistsNumber = forall a. Num a => Number a
I'm without a Haskell compiler, but shouldn't that be "exists a."?
The problem is that "exists" is not valid in either Haskell 98 or any current extension, whereas "forall" is a very common extension. But you can simulate "exists" via "forall", which is the thrust of these approaches. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Oct 19, 2007, at 12:11 , Sebastian Sylvan wrote:
On 19/10/2007, Kalman Noel
wrote: data ExistsNumber = forall a. Num a => Number a
I'm without a Haskell compiler, but shouldn't that be "exists a."?
The problem is that "exists" is not valid in either Haskell 98 or any current extension, whereas "forall" is a very common extension. But you can simulate "exists" via "forall", which is the thrust of these approaches.
When 'exists' is not a keyword, why 'forall' is needed at all? Isn't everything 'forall' qualified by default? ... or are type variables sometimes 'exists' qualified by default depending on context? That would be confusing though... I do not understand why 'forall' keyword is needed. Peter.

Peter Hercek wrote:
When 'exists' is not a keyword, why 'forall' is needed at all? Isn't everything 'forall' qualified by default?
“forall” isn't a keyword in Haskell 98. As an extension to the language, however, it makes certain types expressible that can not be written in H98, for example f :: (forall a. a) -> T which is different from g :: forall a. a -> T although both are not particularly useful. (The only argument that f will ever take is bottom!) In the context of existentially quantified types, however, the forall keyword is used probably to make the use of an extension more explicit. Without the forall keyword, data U = C a would be an existential, while the programmer maybe really wanted the usual data U a = C a Kalman ---------------------------------------------------------------------- Find out how you can get spam free email. http://www.bluebottle.com/tag/3

On Oct 21, 2007, at 6:41 , Peter Hercek wrote:
Brandon S. Allbery KF8NH wrote:
On 19/10/2007, Kalman Noel
wrote: data ExistsNumber = forall a. Num a => Number a
I'm without a Haskell compiler, but shouldn't that be "exists a."? The problem is that "exists" is not valid in either Haskell 98 or any current extension, whereas "forall" is a very common extension. But you can simulate "exists" via "forall", which is
On Oct 19, 2007, at 12:11 , Sebastian Sylvan wrote: the thrust of these approaches.
When 'exists' is not a keyword, why 'forall' is needed at all?
NB. Haskell98 doesn't have forall. All type variables are implicitly scoped to the entire type (e.g. foo :: (a -> b) -> a -> b is actually foo :: forall a b. (a -> b) -> a -> b). The point of the forall keyword is that it can be scoped. Compare runState to runST: ST carries around a bracketed forall on the state expression (forall s. ST s a), preventing it from being viewed or modified (or initialized!) outside the scope established by runST, whereas you can carry around a State (State s a) and thread the state s through an expression "by hand" via evalState / execState (or pattern matching on the State value, which is what those translate to after a pass through runState). Given scoped forall, you can simulate exists by using something very like (identical to, via Curry-Howard?) de Morgan's Rule. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Sebastian Sylvan wrote:
On 19/10/2007, Kalman Noel
wrote: data ExistsNumber = forall a. Num a => Number a
I'm without a Haskell compiler, but shouldn't that be "exists a."? IIRC forall will work too, but the "right" way to do it is "exists", right?
No. It's been suggested but that's not how GHC or Hugs existentials work. The syntax isn't actually illogical, it's just very confusing. What (by convention) you are actually doing here is you are annotating the type of the constructor. So you are saying that the constructor 'Number' has the type "forall a . Num a => a -> ExistsNumber". This is perfectly correct, but it is confusing that what you are doing is annotating the *constructor* and not the data-type itself, per se, although it doesn't much look like it. This looks very very much clearer in GADT syntax, since in GADT syntax you always give constructors explicit types: type ExistsNumber where Number :: forall a . Num a => ExistsNumber a Jules

Jules Bean wrote:
This looks very very much clearer in GADT syntax, since in GADT syntax you always give constructors explicit types:
type ExistsNumber where Number :: forall a . Num a => ExistsNumber a
The questions in response to my post have been answered already; I'd like to mention, though, the two typos in your example, which should read instead: data ExistsNumber where Number :: forall a. Num a => a -> ExistsNumber Kalman

TJ wrote:
Why is it illegal to store values of differing types, but which instance the same class, into a list? e.g.
a = [ 1, 2.0 ] :: Num a => [a]
That type signature doesn't mean what you want it to mean. That reads "A list of things of type a ([a]) with the restriction that the type a is a member of the Num class"
After all, sometimes all you need to know about a list is that all the elements support a common set of operations. If I'm implementing a 3d renderer for example, I'd like to have
That's a reasonable thing to want.
class Renderable a where render :: a -> RasterImage
scene :: Renderable a => [a]
Instead of hardcoding a bunch of types as being Renderable, as in
data Renderable = Point Something | Line Something | Polygon Something
scene :: [Renderable]
Quite often an explicit ADT is much nicer. But they represent two opposing patterns of code-writing. Explicit ADT allows you to write case statements handling 'all the logic in one place'; a class forces you to separate the differences into 'separate instances'. Both styles have their place. It's partly a question of taste, partly an issue of drawing your abstraction boundaries at different angles! This is how you do it: class CanRender a where render :: a -> RasterImage data Renderable = forall a. (CanRender a) => Renderable a scene :: [Renderable]
I even if I use those, I'll still have to wrap things up in a constructor, won't I?
Yes. It's not as onerous as all that though. You can normally set things up with pleasant helper functions. One helpful trick is to make the existential-type itself a member of the class, as in: instance CanRender Renderable where render (Renderable a) = render a I think it's interesting to note, in passing, that you don't have to use typeclasses. It can be perfectly useful to use existentials over other structures, like: data Particle s = Particle { x :: Double, y :: Double, z :: Double, state :: s, drawme :: Particle s -> IO () } ...which is some representation of a 'particle' but it is parametric in some generic kind of state. Then if you don't care which state, you can do data AnyParticle = forall s . Any (Particle s) Including the last member 'drawme' makes this technique look rather like 'dictionaries-by-hand'. Which it is. And 'dictionaries-by-hand' is actually much nicer than type classes. The point is : just passing higher-order functions around in your data structures is a very useful trick. Taking existentials of these can be useful too. The *only* time it's useful to make this paradigm into a type-class, is when you want the compiler to automatically provide the dictionary for you, based on the types you use. Since I can imagine several different kinds of particle which might use 'int' as state , but draw themselves differently, type-based dictionary choice is not the be-all and end-all. If you really really want to use type-based dictionary choice you can of course use newtypes... but it pays to remember there is a more elementary approach. IF you draw the analogy between existentials and OO programming, then you might say the following: Typeclass dictionaries are like class-based OO (e.g. Java) where to define a new kind of behaviour you need to make a new class. Dictionaries-by-hand is like object-based OO (e.g. javascript) where to define a new kind of behaviour you can just change a method, one-off, for a particular object or bunch of objets. However, I prefer to think that this is all about different kinds of abstraction. Java is at one extreme of the spectrum, with objects and classes being its only tools of abstraction (all code goes in classes, all data goes in objects). With Haskell the various parts of the abstraction are split up : custom data types, higher order functions, polymorphic functions, existential types. This means (with a little experience) you can apply the right tool for the job. Jules

Dan Licata: Thanks for explaining the mechanics behind it. Knowing how
it (could) be implemented always helps me understand things.
On 10/20/07, Jules Bean
Quite often an explicit ADT is much nicer. But they represent two opposing patterns of code-writing. Explicit ADT allows you to write case statements handling 'all the logic in one place'; a class forces you to separate the differences into 'separate instances'.
Nice ADT example. Indeed that would be how I'd do it in SML. Use a record type holding closures referencing an object of unknown type. The nice thing I've found about doing it in SML this way is that I can extract the object back out, using exceptions. e.g. (* Start Standard ML *) datatype Renderable = Renderable { render : unit -> RenderedImage, extract : unit -> unit, tag : exn } local datatype Point = Point Something exception ExtractMe Point exception Tag in fun mkPoint Something = let val p = Point Something in { render = fn () => ... , extract = fn () => raise ExtractMe p, tag = Tag } end (* extractPoint would return the Point hidden away in a Renderable. *) fun extractPoint (Renderable { tag = Tag, extract, ... }) = (extract (); Point SomethingPointless) handle ExtractMe p => p end (* End SML *) I don't know if this would work in Haskell, as I'm not familiar with Haskell exceptions. Anyway I see that Haskell has a Dynamic type... I've got a good grip on this now, I think. Thanks everyone. TJ

If I understand what you're going for with the code below, then here's another way to program it in SML that doesn't use exceptions (the control flow mechanism) at all. I think what you want is an extensible datatype. Here's the interface I program to: signature TAGGED = sig (* a tag is the equivalent of a datatype constructor for our extensible datatype *) type 'a tag val newtag : unit -> 'a tag (* the extensible datatype itself: - the datatype is statically extensible (you can add new constructors in different parts of the program text) - the datatype is dynamically extensible (you can add new constructors at runtime) *) type tagged (* tag a value (i.e., the equivalent of a datatype constructor application) *) val tag : 'a tag -> 'a -> tagged (* match with a given tag (i.e., the equivalent of pattern matching) *) val istagof : 'a tag -> tagged -> 'a option end A simple use is as follows: structure Use = struct open Tagged val i : int tag = newtag () val s : string tag = newtag () val l : tagged list = [tag i 1, tag s "hi"] fun toString (t : tagged) = case istagof i t of SOME (x : int) => Int.toString x | NONE => case istagof s t of SOME (x : string) => x | NONE => raise Fail "don't know about that tag" end Of course, we could have written this particular code with a datatype. But you could also add new tags elsewhere in the program, or even generate them in a loop at runtime. So for your example below, the point stuff would look like: type point = int * int val p : point tag = newtag () fun extractPoint (t : tagged) : point = case istagof p t of SOME p => p | NONE => (0,0) (* whatever default value you want *) And then you'd write render : tagged -> RenderedImage (Now, you may want render to be an extensible function, so you can add cases elsewhere in the program, but that's a story for another time.) Now, the implementation of TAGGED uses the SML exn type, which, despite the concrete syntax, has absolutely nothing to do with exceptions. It's much better to think of exn as standing for EXteNsible: it's just an extensible datatype; the choice of keyword "exception" for adding a new datatype constructor is misleading. In fact, TAGGED is just a nicer interface on top of exn: structure Tagged :> TAGGED = struct type 'a tag = ('a -> exn) * (exn -> 'a option) type tagged = exn fun newtag () = let exception E of 'a in (E, fn (E x) => SOME x | _ => NONE) end fun tag (f, _) x = f x fun istagof (_, g) x = g x end -Dan On Oct20, TJ wrote:
Dan Licata: Thanks for explaining the mechanics behind it. Knowing how it (could) be implemented always helps me understand things.
On 10/20/07, Jules Bean
wrote: Quite often an explicit ADT is much nicer. But they represent two opposing patterns of code-writing. Explicit ADT allows you to write case statements handling 'all the logic in one place'; a class forces you to separate the differences into 'separate instances'.
Nice ADT example. Indeed that would be how I'd do it in SML. Use a record type holding closures referencing an object of unknown type. The nice thing I've found about doing it in SML this way is that I can extract the object back out, using exceptions. e.g.
(* Start Standard ML *)
datatype Renderable = Renderable { render : unit -> RenderedImage, extract : unit -> unit, tag : exn }
local datatype Point = Point Something exception ExtractMe Point exception Tag in fun mkPoint Something = let val p = Point Something in { render = fn () => ... , extract = fn () => raise ExtractMe p, tag = Tag } end (* extractPoint would return the Point hidden away in a Renderable. *) fun extractPoint (Renderable { tag = Tag, extract, ... }) = (extract (); Point SomethingPointless) handle ExtractMe p => p end
(* End SML *)
I don't know if this would work in Haskell, as I'm not familiar with Haskell exceptions. Anyway I see that Haskell has a Dynamic type...
I've got a good grip on this now, I think. Thanks everyone.
TJ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

TJ:
After all, sometimes all you need to know about a list is that all the elements support a common set of operations. If I'm implementing a 3d renderer for example, I'd like to have
class Renderable a where render :: a -> RasterImage
scene :: Renderable a => [a]
Everyone has launched into explanations of how to use existentials to do this, but you may be happy in just haskell 98. In the above, you could just have: scene :: [RasterImage] Laziness will ensure that the computation/storage of the images will not occur until they are used. Tim

On 10/22/07, Tim Docker
TJ:
After all, sometimes all you need to know about a list is that all the elements support a common set of operations. If I'm implementing a 3d renderer for example, I'd like to have
class Renderable a where render :: a -> RasterImage
scene :: Renderable a => [a]
Everyone has launched into explanations of how to use existentials to do this, but you may be happy in just haskell 98. In the above, you could just have:
scene :: [RasterImage]
Laziness will ensure that the computation/storage of the images will not occur until they are used.
Tim
Ah... indeed it can, in this case. It won't work if class Renderable also has a method for saving to file, etc, I suppose, unless scene :: [(RasterImage,IO (),...whatever other operations...)] Thanks for the heads up :) TJ

TJ:
Ah... indeed it can, in this case. It won't work if class Renderable also has a method for saving to file, etc, I suppose, unless scene :: [(RasterImage,IO (),...whatever other operations...)]
In this case I would generally create a record: data Renderable = Renderable { image :: RasterImage, saveToFile :: FilePath -> IO (), ... etc ... } scene :: [Renderable] You may then like to add a type class to turn things into renderables: class IsRenderable where toRenderable :: a -> Renderable instance IsRendeable Point where ... instance IsRenderable Line where ... It depends on your needs, but in my limited experience, records are often more convenient for emulating OO-style programming than are type classes. Tim

On 10/22/07, Tim Docker
[...] You may then like to add a type class to turn things into renderables:
class IsRenderable where toRenderable :: a -> Renderable
instance IsRendeable Point where ... instance IsRenderable Line where ... [...]
Cool. I should get more familiar with basic Haskell98 before I decide on using GHC extensions... Thanks, TJ
participants (9)
-
Brandon S. Allbery KF8NH
-
Dan Licata
-
Henning Thielemann
-
Jules Bean
-
Kalman Noel
-
Peter Hercek
-
Sebastian Sylvan
-
Tim Docker
-
TJ