caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* Objects, dynamic cast, Obj.magic abuse and dragons
@ 2008-02-26 11:35 Berke Durak
  2008-02-26 12:14 ` [Caml-list] " Richard Jones
                   ` (3 more replies)
  0 siblings, 4 replies; 14+ messages in thread
From: Berke Durak @ 2008-02-26 11:35 UTC (permalink / raw)
  To: Caml-list List

[-- Attachment #1: Type: text/plain, Size: 1727 bytes --]

Hello,

It seems that objects are back in fashion again on the list.

As records of functions or functors dont quite cut the mustard for some applications, I decided to give Ocaml's object 
system another try.  I tried to implement a conventional text adventure using those, of the "go north take sword kill 
dragon" kind.  Actually I had one such small prototype I wrote while learning Java, so I decided to port that one.

I've stumbled on a situation where I feel dynamic casting could be useful.  At least, that is the way I did it in the 
Java version.  I've worked around it using Obj.magic, but I can't check the class, so this could lead to nastiness.
I'd rather eat a runtime Class_cast_exception than a segmentation fault.

In this adventure, things can contain other things; a class physical has a list of things it contains, and an optional 
pointer to its container.

Persons, places and objects are things so they inherit from physical.  Hence, a forest is a place that can contain
a sword (an object), a dragon (a person) or another place (a small house).  Persons can be contained in places
or things (coffins).

The problem is that the main game loop gets the current location by taking the container of the hero... which is a 
physical.  However, it needs to call the place-specific method "go".

I'm submitting my example so that you can propose alternative solutions.  A few ideas:

* Add a go method in physical, raise an exception - not scalable, if I want to add other categories of things,
I'll have to add the corresponding method to physical.
* Parametrize physical with the type of contents.
* Use a sum type; but then it wouldn't be an object any more, and it's a centralized place.
-- 
Berke DURAK

[-- Attachment #2: adventure.ml --]
[-- Type: text/plain, Size: 5102 bytes --]

(* Adventure *)

exception QuitException

let mandatory = function
  | None -> raise Not_found
  | Some x -> x

let pf = Printf.printf

let split_at c u =
  let m = String.length u in
  let b = Buffer.create m in
  let rec loop0 r i =
    if i >= m then
      List.rev r
    else
      if u.[i] = c then
        loop0 r (i + 1)
      else
        loop1 r i
  and loop1 r i =
    if i = m or u.[i] = c then
      begin
        let x = Buffer.contents b in
        Buffer.clear b;
        loop0 (x::r) (i + 1)
      end
    else
      begin
        Buffer.add_char b u.[i];
        loop1 r (i + 1)
      end
  in
  loop0 [] 0

let ( & ) f x = f x

class ['subject] io in_channel () =
  object
    val mutable subject : 'subject option = None
    method set_subject s = subject <- Some s
    method get_subject = mandatory subject
    
    method read =
      pf "< %!";
      split_at ' ' & input_line in_channel

    method write u =
      pf ">>> %s\n%!" u
  end

class virtual command =
  object
    method virtual get_verb : string
    method virtual perform : string list -> unit
  end

class virtual describable =
  object
    method virtual describe : 'a . 'a io -> unit
    method virtual get_name : string
  end

class virtual physical =
  object(self)
    inherit describable as super
    val mass = 1.0
    val takeable = true
    val mutable contents : physical list = []
    val mutable container : physical option = None
    method contents = contents
    method container = mandatory container

    method add : physical -> unit = fun thing -> contents <- thing :: contents

    method remove (thing : physical) = contents <- List.filter ((<>) thing) contents

    method unlink =
      match container with
      | None -> ()
      | Some t -> t#remove (self :> physical)

    method put (target : physical) =
      self#unlink;
      container <- Some target;
      target#add (self :> physical)
      
  end

class biscuit =
  object
    inherit physical as super
    method describe io =
      io#write "A square biscuit with chocolate in it.  It is organic, or at least that's what the writing on it, presumably in edible, organic ink, says.";
    method get_name = "a chocolate biscuit"
    method to_string = "the biscuit"
  end

type direction = N | S | E | W

let invert = function
| N -> S
| S -> N
| E -> W
| W -> E

let connect p1 d p2 =
  p1#connect d p2;
  p2#connect (invert d) p1

class virtual place =
  object(self)
    inherit physical as super
    val mutable seen = false
    val mutable outlinks : (direction * place) list = []

    method go d = List.assoc d outlinks

    method connect d t = outlinks <- (d, t) :: outlinks

    method describe_items : 'a . 'a io -> unit = fun io ->
      io#write "You can see:";
      List.iter
        (fun p ->
          let (q : physical) = p in
          q#describe io
        )
        contents

    method virtual describe_place : 'a . 'a io -> unit

    method describe io =
      self#describe_place io;
      self#describe_items io
  end

class virtual person =
  object
    inherit physical as super
    val takeable = false
  end

class hero =
  object
    inherit person as super
    method get_name = "John"
    method describe io = io#write "John is a tall man."
  end

let sf = Printf.sprintf

class forest name () =
  object(self)
    inherit place as super
    method get_name = name
    method describe_place io =
      io#write (sf "You are in %s" self#get_name)
  end

class sword =
  object(self)
    inherit physical as super

    method describe io =
      io#write "A one-meter long, titanium alloy, gold-plated, emerald-incrusted, Dragon-repelling adventurer's heavy duty sword."

    method get_name = "A golden sword"
  end

class game io =
  let f1 = new forest "the big dark forest" () in
  let f2 = new forest "the small dark forest" () in
  let f3 = new forest "the small light forest" () in
  let f4 = new forest "the tropical forest" () in
  let h  = new hero in
  let _ = h#put (f1 :> physical) in
  let _ = connect f1 N f2 in
  let _ = connect f2 E f3 in
  let _ = connect f3 S f4 in
  let _ = connect f4 E f1 in
  let _ = io#set_subject h in
  let sw = new sword in
  let _ = sw#put (f1 :> physical) in
  let b = new biscuit in
  let _ = b#put (f4 :> physical) in
  object(self)
    method where =
      let wh' = h#container in
      (* XXXXXXXX here *)
      let wh : place = Obj.magic wh' in (* I'd like a dynamic cast here! *)
      (* XXXXXXXX *)
      (*let wh' = (h#container : physical <: place) in*)
      wh

    method go d =
      try
        let wh = self#where in
        let wh = wh#go d in
        h#put (wh : place :> physical)
      with
      | Not_found ->
          io#write "Can't go there"
      
    method run =
      let wh = self#where in
      wh#describe io;
      begin
        match io#read with
        | ["n"] -> self#go N
        | ["s"] -> self#go S
        | ["e"] -> self#go E
        | ["w"] -> self#go W
        | _ -> io#write "Wtf?"
      end
  end

let play () =
  let io = new io stdin () in
  let g = new game io in
  while true do
    g#run
  done

^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 11:35 Objects, dynamic cast, Obj.magic abuse and dragons Berke Durak
@ 2008-02-26 12:14 ` Richard Jones
  2008-02-26 14:28   ` Berke Durak
  2008-02-27 13:26   ` Tiphaine.Turpin
  2008-02-26 12:48 ` ketti
                   ` (2 subsequent siblings)
  3 siblings, 2 replies; 14+ messages in thread
From: Richard Jones @ 2008-02-26 12:14 UTC (permalink / raw)
  To: Berke Durak; +Cc: Caml-list List

On Tue, Feb 26, 2008 at 12:35:10PM +0100, Berke Durak wrote:
> The problem is that the main game loop gets the current location by taking 
> the container of the hero... which is a physical.  However, it needs to 
> call the place-specific method "go".

I only briefly read over this, but maybe the thing you want is an
object memo.  There's a specialized one in lablgtk called GUtil.memo,
but the basic source for it could be adapted:

  class ['a] memo () = object
    constraint 'a = #widget
    val tbl = Hashtbl.create 7
    method add (obj : 'a) =
      Hashtbl.add tbl obj#get_id obj
    method find (obj : widget) = Hashtbl.find tbl obj#get_id
    method remove (obj : widget) = Hashtbl.remove tbl obj#get_id
  end

There's an example of using this if you search down for 'memo' on this
page:

  http://www.ocaml-tutorial.org/introduction_to_gtk

Rich.

-- 
Richard Jones
Red Hat


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 11:35 Objects, dynamic cast, Obj.magic abuse and dragons Berke Durak
  2008-02-26 12:14 ` [Caml-list] " Richard Jones
@ 2008-02-26 12:48 ` ketti
  2008-02-26 13:10 ` Berke Durak
  2008-02-26 15:07 ` Dirk Thierbach
  3 siblings, 0 replies; 14+ messages in thread
From: ketti @ 2008-02-26 12:48 UTC (permalink / raw)
  To: Berke Durak; +Cc: Caml-list List

Hi,

2008/2/26 Berke Durak <berke.durak@exalead.com>:
>  Persons, places and objects are things so they inherit from physical.  Hence, a forest is a place that can contain
>  a sword (an object), a dragon (a person) or another place (a small house).  Persons can be contained in places
>  or things (coffins).
>
>  The problem is that the main game loop gets the current location by taking the container of the hero... which is a
>  physical.  However, it needs to call the place-specific method "go".

I too have only read your code briefly, but i would suggest you use
multiple inheritanse. Coffin would inherit from both object and place.
That way the container of the hero is always a place. In fact, that is
the way i would encode it in java too (using interfaces).


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 11:35 Objects, dynamic cast, Obj.magic abuse and dragons Berke Durak
  2008-02-26 12:14 ` [Caml-list] " Richard Jones
  2008-02-26 12:48 ` ketti
@ 2008-02-26 13:10 ` Berke Durak
  2008-02-26 15:07 ` Dirk Thierbach
  3 siblings, 0 replies; 14+ messages in thread
From: Berke Durak @ 2008-02-26 13:10 UTC (permalink / raw)
  Cc: Caml-list List

I have found a where, for each category C (such as place or person), you add a method

   as_C : C

in physical that throws a Class_cast_exception, and override it with a method that returns
self in class C.  However this means that the type C must appear in the definition of physical,
which means that either

   (a) All categories C1, ..., Cn are defined in the same file in the same bunch
of mutually-recursive class definitions; a solution evidently not scalable.

   (b) The physical class is parametrized by n paramters 'C1, 'C2, ... 'Cn, which
must be repeated everywhere.

The latter solution works for small n but the complexity of incremental maintenance is in O(n).
This means that if you define your n classes in n files, you'll have to edit n files to add
an (n+1)-th class.

This leads me back to an idea I was talking about with Yann Régis-Gianas a few months ago :
the ability to bundle type parameters as a named record and to access their components.

You could write, in a file

f.ml:
   type ''bundle := ('place, 'person, 'c3, 'c4 ...)

then in physical.ml :

   class [F.''bundle] physical =
     object
       method as_place : raise Class_cast_exception
       method as_person : raise Class_cast_exception
       method as_c3 : raise Class_cast_exception
     end

and in place.ml
   class [F.''bundle] place =
     object(self : 'a)
       constraint ''bundle.'place = 'a
       method as_place = self
     end

and so on...  I don't know how much sense this makes with respect to separate compilation.
However, this would allow you to add a category by just editing two files.
-- 
Berke DURAK


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 12:14 ` [Caml-list] " Richard Jones
@ 2008-02-26 14:28   ` Berke Durak
  2008-02-26 14:48     ` Richard Jones
  2008-02-27 13:26   ` Tiphaine.Turpin
  1 sibling, 1 reply; 14+ messages in thread
From: Berke Durak @ 2008-02-26 14:28 UTC (permalink / raw)
  To: Richard Jones; +Cc: Caml-list List

Richard Jones a écrit :
> On Tue, Feb 26, 2008 at 12:35:10PM +0100, Berke Durak wrote:
>> The problem is that the main game loop gets the current location by taking 
>> the container of the hero... which is a physical.  However, it needs to 
>> call the place-specific method "go".
> 
> I only briefly read over this, but maybe the thing you want is an
> object memo.  There's a specialized one in lablgtk called GUtil.memo,
> but the basic source for it could be adapted:
> 
>   class ['a] memo () = object
>     constraint 'a = #widget
>     val tbl = Hashtbl.create 7
>     method add (obj : 'a) =
>       Hashtbl.add tbl obj#get_id obj
>     method find (obj : widget) = Hashtbl.find tbl obj#get_id
>     method remove (obj : widget) = Hashtbl.remove tbl obj#get_id
>   end
> 
> There's an example of using this if you search down for 'memo' on this
> page:
> 
>   http://www.ocaml-tutorial.org/introduction_to_gtk
> 
> Rich.
> 

Hello,

Your solution first seemed like a kludge but, given the alternatives, it appears to be the best solution.
It's nicer than having to add type parameters everywhere and it's scalable: just add one memo kind for each
category and make sure everyone registers itself on creation.  For destruction, we can use weak hash tables.
And it's reasonably efficient (after all, we're using objects here.)
-- 
Berke DURAK


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 14:28   ` Berke Durak
@ 2008-02-26 14:48     ` Richard Jones
  2008-02-26 14:59       ` Berke Durak
  0 siblings, 1 reply; 14+ messages in thread
From: Richard Jones @ 2008-02-26 14:48 UTC (permalink / raw)
  To: Berke Durak; +Cc: Caml-list List

On Tue, Feb 26, 2008 at 03:28:01PM +0100, Berke Durak wrote:
> Your solution first seemed like a kludge but, given the alternatives, it 
> appears to be the best solution.
[...]
> And it's reasonably efficient (after all, we're using objects here.)

Yeah, I suspect the real lesson here is don't use objects at all.
They are rarely as useful as people make out, and most uses of them
seem to be because lesser languages lack good compiler checks on
variants.  After all, there's no real problem at all spreading match
statements around the program if I can be sure that the compiler will
highlight everywhere which needs to change when I change my variant.

Rich.

-- 
Richard Jones
Red Hat


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 14:48     ` Richard Jones
@ 2008-02-26 14:59       ` Berke Durak
  0 siblings, 0 replies; 14+ messages in thread
From: Berke Durak @ 2008-02-26 14:59 UTC (permalink / raw)
  To: Richard Jones; +Cc: Caml-list List

Richard Jones a écrit :
> On Tue, Feb 26, 2008 at 03:28:01PM +0100, Berke Durak wrote:
>> Your solution first seemed like a kludge but, given the alternatives, it 
>> appears to be the best solution.
> [...]
>> And it's reasonably efficient (after all, we're using objects here.)
> 
> Yeah, I suspect the real lesson here is don't use objects at all.
> They are rarely as useful as people make out, and most uses of them
> seem to be because lesser languages lack good compiler checks on
> variants.  After all, there's no real problem at all spreading match
> statements around the program if I can be sure that the compiler will
> highlight everywhere which needs to change when I change my variant.
> 
> Rich.
> 

Subtyping is useful, however. I dont use objects much and I was wondering
if I'm missing much.  Toda I'd be willing to trade in the class system for
an extensible record system.
-- 
Berke DURAK


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 11:35 Objects, dynamic cast, Obj.magic abuse and dragons Berke Durak
                   ` (2 preceding siblings ...)
  2008-02-26 13:10 ` Berke Durak
@ 2008-02-26 15:07 ` Dirk Thierbach
  2008-02-26 16:25   ` Berke Durak
  3 siblings, 1 reply; 14+ messages in thread
From: Dirk Thierbach @ 2008-02-26 15:07 UTC (permalink / raw)
  To: caml-list

On Tue, Feb 26, 2008 at 12:35:10PM +0100, Berke Durak wrote:
> In this adventure, things can contain other things; a class physical has a 
> list of things it contains, and an optional pointer to its container.
> 
> Persons, places and objects are things so they inherit from physical.  
> Hence, a forest is a place that can contain
> a sword (an object), a dragon (a person) or another place (a small house).  
> Persons can be contained in places
> or things (coffins).
> 
> The problem is that the main game loop gets the current location by taking 
> the container of the hero... which is a physical.  However, it needs to 
> call the place-specific method "go".

I think I wouldn't use objects at all in this situation. You're trying
to model the location-tree of "physical" things. A tree must be uniform
in its contents, but you want to put different things into it. That
means you must use an algebraic type, or variants. I'd probably either
use a zipper, or connect the tree nodes with "refs" for the non-pure
version. 

Attaching operations like "go" to a specific object is also a leftover
from the "everything is an object" philosophy. If you must move a physical
thing, just move it. If you need to attach special behaviour for some
sort of movements, find out what it depends on (source, destination,
thing moved, or a combination) and handle those cases in the move-routine.

- Dirk




^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 15:07 ` Dirk Thierbach
@ 2008-02-26 16:25   ` Berke Durak
  2008-02-27  7:37     ` Dirk Thierbach
  0 siblings, 1 reply; 14+ messages in thread
From: Berke Durak @ 2008-02-26 16:25 UTC (permalink / raw)
  To: Dirk Thierbach, Caml-list List

Dirk Thierbach wrote :
> I think I wouldn't use objects at all in this situation. You're trying
> to model the location-tree of "physical" things. A tree must be uniform
> in its contents, but you want to put different things into it. That
> means you must use an algebraic type, or variants. I'd probably either
> use a zipper, or connect the tree nodes with "refs" for the non-pure
> version. 

You are preaching to the choir.  I'm not Gerd Stolpmann and I don't use
objects very much because every time I try I get seven-page-long errors.

However it seems that objects could be actually useful in situations
where you have a hierarchy of objects with behaviours, such as a graphical
user interface made of widgets, or, say, a text adventure.

-- 
Berke DURAK


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 16:25   ` Berke Durak
@ 2008-02-27  7:37     ` Dirk Thierbach
  2008-02-27 10:26       ` Berke Durak
  0 siblings, 1 reply; 14+ messages in thread
From: Dirk Thierbach @ 2008-02-27  7:37 UTC (permalink / raw)
  To: caml-list

On Tue, Feb 26, 2008 at 05:25:05PM +0100, Berke Durak wrote:
> Dirk Thierbach wrote :
>> I think I wouldn't use objects at all in this situation. You're trying
>> to model the location-tree of "physical" things. A tree must be uniform
>> in its contents, but you want to put different things into it. That
>> means you must use an algebraic type, or variants. I'd probably either
>> use a zipper, or connect the tree nodes with "refs" for the non-pure
>> version. 

> You are preaching to the choir.  

I'm not preaching here :-)

> I'm not Gerd Stolpmann and I don't use objects very much because
> every time I try I get seven-page-long errors.

I, OTOH, use them frequently. I also get seven-page-long errors,
but usually I can find the bug nevertheless :-)

> However it seems that objects could be actually useful in situations
> where you have a hierarchy of objects with behaviours, such as a graphical
> user interface made of widgets, or, say, a text adventure.

Yes, they can be very useful in some situations, especially in GUIs.
However, I think they are not useful in the particular situation of
a text adventure.

And I think that the criterion is not having a hierarchy of behaviours
(first, "inheritance is not subtyping", second, as you've seen, you
can run into trouble with static type checking easily), but the criterion
is having substantial state that should be partitioned and decoupled.

This also applies to the text adventure to some degree, but the actual
state is much simpler: Must items will have no state at all, or
at most a boolean like "open/closed". Their *relationship*, OTOH
(i.e. location, attachment) can be described uniformly and globally.
Also, for the actual actions, you need multi-dispatch: The outcome
of the action depends on the verb and multiple items ("tie rope to
railing"). And all this says that single-dispatch statically typed 
objects, like in OCaml, are a bad match for this situation.

- Dirk


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-27  7:37     ` Dirk Thierbach
@ 2008-02-27 10:26       ` Berke Durak
  0 siblings, 0 replies; 14+ messages in thread
From: Berke Durak @ 2008-02-27 10:26 UTC (permalink / raw)
  To: Dirk Thierbach; +Cc: Caml-list List

Dirk Thierbach a écrit :

>> You are preaching to the choir.  
> 
> I'm not preaching here :-)
> 
>> I'm not Gerd Stolpmann and I don't use objects very much because
>> every time I try I get seven-page-long errors.
> 
> I, OTOH, use them frequently. I also get seven-page-long errors,
> but usually I can find the bug nevertheless :-)

Well it's all a question of not losing patience and switching to a non-object
representation :)

>> However it seems that objects could be actually useful in situations
>> where you have a hierarchy of objects with behaviours, such as a graphical
>> user interface made of widgets, or, say, a text adventure.
> 
> Yes, they can be very useful in some situations, especially in GUIs.
> However, I think they are not useful in the particular situation of
> a text adventure.

I wouldn't bet on that :)

> And I think that the criterion is not having a hierarchy of behaviours
> (first, "inheritance is not subtyping", second, as you've seen, you
> can run into trouble with static type checking easily), but the criterion
> is having substantial state that should be partitioned and decoupled.
> 
> This also applies to the text adventure to some degree, but the actual
> state is much simpler: Must items will have no state at all, or
> at most a boolean like "open/closed".  Their *relationship*, OTOH
> (i.e. location, attachment) can be described uniformly and globally.

But there is an excellent mapping between containment in the modeled
world, and logical containment in the objects.  Hence, I'd like to have
the contents of an object as part of its state.  Properties of an object
may change depending on what they contain, where they are contained or
what objects they are contained with.

For instance, a wooden box containing a bronze statue will be heavy,
cheese contained in a hot oven will melt and hydrogen peroxide contained
in a bottle also containing acetone will, well, get you in trouble.

And most actions in an adventure game involve shifting things around
and the occasional state change now and then.

> Also, for the actual actions, you need multi-dispatch: The outcome
> of the action depends on the verb and multiple items ("tie rope to
> railing").
> And all this says that single-dispatch statically typed 
> objects, like in OCaml, are a bad match for this situation.

I'm actually working on a multi-dispatched language and I find it
a little bit over-hyped.  It helps with dispatching, but once you've
dispatched and got the objects with the types you want, you still have
to decide what to do and issue individual commands to the implicated
objects, and then collect back the results.

Provided that you have some representation of the types as values
(say as variant tags) you could as well pattern-match on the tuple of types
representations and on the verb.  This is not very scalable, so you could
hack a hand-made dispatch mechanism.  And, certainly, the properties you want
to dispatch on might not be easily representable in types, so your multiple-dispatch
needs guards.
-- 
Berke DURAK


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-26 12:14 ` [Caml-list] " Richard Jones
  2008-02-26 14:28   ` Berke Durak
@ 2008-02-27 13:26   ` Tiphaine.Turpin
  2008-02-29 10:36     ` Berke Durak
  1 sibling, 1 reply; 14+ messages in thread
From: Tiphaine.Turpin @ 2008-02-27 13:26 UTC (permalink / raw)
  To: Caml-list List

Here is another try. it has the drawback that classes need to be 
parametric, but it seems to work, and to be scalable (the added code is 
always the same). Of course, some syntactic sugar would help.

Tiphaine Turpin

Richard Jones a écrit :
> I only briefly read over this, but maybe the thing you want is an
> object memo.  There's a specialized one in lablgtk called GUtil.memo,
> but the basic source for it could be adapted:
>
>   class ['a] memo () = object
>     constraint 'a = #widget
>     val tbl = Hashtbl.create 7
>     method add (obj : 'a) =
>       Hashtbl.add tbl obj#get_id obj
>     method find (obj : widget) = Hashtbl.find tbl obj#get_id
>     method remove (obj : widget) = Hashtbl.remove tbl obj#get_id
>   end
>
> There's an example of using this if you search down for 'memo' on this
> page:
>
>   http://www.ocaml-tutorial.org/introduction_to_gtk
>
> Rich.
>
>   
#load "extLib.cma"

open ExtList
exception Class_cast_exception

let cast f o =
  match List.filter_map f o#supers with
    | [] -> raise Class_cast_exception
    | o' :: _ -> o'

class ['super] a = object (self : 'self)
  method supers : 'super list = [`a (self :> _ a)]
  method a = ()
end

class ['super] b = object (self : 'self)
  inherit ['super] a as a
  method supers = `b (self :> _ b) :: a#supers
  method b = ()
end

class ['super] c = object (self : 'self)
  inherit ['super] a as a
  method supers = `c (self :> _ c) :: a#supers
  method c = ()
end

class ['super] d = object (self : 'self)
  inherit ['super] b as b
  inherit ['super] c as c
  method supers =  `d (self :> _ d) :: b#supers @ c#supers
  method d = ()
end

class ['super] e = object (self : 'self)
  inherit ['super] d as d
  method supers = `e (self :> _ e) :: d#supers
  method e = ()
end

let d = (new d :> _ a)
let a : _ a = cast (function `a o -> Some o | _ -> None) d
let b : _ b = cast (function `b o -> Some o | _ -> None) d
let c : _ c = cast (function `c o -> Some o | _ -> None) d
let d : _ d = cast (function `d o -> Some o | _ -> None) d

let c = new c
let error : _ b = cast (function `b o -> Some o | _ -> None) c


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-27 13:26   ` Tiphaine.Turpin
@ 2008-02-29 10:36     ` Berke Durak
  2008-02-29 12:23       ` Tiphaine.Turpin
  0 siblings, 1 reply; 14+ messages in thread
From: Berke Durak @ 2008-02-29 10:36 UTC (permalink / raw)
  To: Tiphaine.Turpin; +Cc: Caml-list List

Tiphaine.Turpin a écrit :
> Here is another try. it has the drawback that classes need to be 
> parametric, but it seems to work, and to be scalable (the added code is 
> always the same). Of course, some syntactic sugar would help.

That seems to be a very good solution!  I didn't think it was possible.
The classes are parametric but there is only one parameter, right?  So it is
scalable.  Sweet, I'll give it a try.  Thanks!

-- 
Berke DURAK


^ permalink raw reply	[flat|nested] 14+ messages in thread

* Re: [Caml-list] Objects, dynamic cast, Obj.magic abuse and dragons
  2008-02-29 10:36     ` Berke Durak
@ 2008-02-29 12:23       ` Tiphaine.Turpin
  0 siblings, 0 replies; 14+ messages in thread
From: Tiphaine.Turpin @ 2008-02-29 12:23 UTC (permalink / raw)
  To: Berke Durak; +Cc: Caml-list List

Berke Durak a écrit :
> Tiphaine.Turpin a écrit :
>> Here is another try. it has the drawback that classes need to be 
>> parametric, but it seems to work, and to be scalable (the added code 
>> is always the same). Of course, some syntactic sugar would help.
>
> That seems to be a very good solution!  I didn't think it was possible.
> The classes are parametric but there is only one parameter, right?
Yes (but you may want to add your own parameters for other purposes). 
However, since there is a single tag for each classes, if you use a 
parameterized class with different arguments in the same context, you 
can probably have typing problems...

Tiphaine Turpin


^ permalink raw reply	[flat|nested] 14+ messages in thread

end of thread, other threads:[~2008-02-29 12:27 UTC | newest]

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-02-26 11:35 Objects, dynamic cast, Obj.magic abuse and dragons Berke Durak
2008-02-26 12:14 ` [Caml-list] " Richard Jones
2008-02-26 14:28   ` Berke Durak
2008-02-26 14:48     ` Richard Jones
2008-02-26 14:59       ` Berke Durak
2008-02-27 13:26   ` Tiphaine.Turpin
2008-02-29 10:36     ` Berke Durak
2008-02-29 12:23       ` Tiphaine.Turpin
2008-02-26 12:48 ` ketti
2008-02-26 13:10 ` Berke Durak
2008-02-26 15:07 ` Dirk Thierbach
2008-02-26 16:25   ` Berke Durak
2008-02-27  7:37     ` Dirk Thierbach
2008-02-27 10:26       ` Berke Durak

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for NNTP newsgroup(s).