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

Dan Licata drl at cs.cmu.edu
Fri Oct 19 15:19:27 EDT 2007


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 <jules at jellybean.co.uk> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 


More information about the Haskell-Cafe mailing list