caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* Re: [Caml-list] Re: OO programming
@ 2008-02-21 16:59 Tiphaine.Turpin
  2008-02-21 19:47 ` Tiphaine.Turpin
  0 siblings, 1 reply; 4+ messages in thread
From: Tiphaine.Turpin @ 2008-02-21 16:59 UTC (permalink / raw)
  To: caml-list

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



[-- Attachment #2: Re: [Caml-list] Re: OO programming --]
[-- Type: message/rfc822, Size: 3255 bytes --]

From: "Tiphaine.Turpin" <Tiphaine.Turpin@free.fr>
To: Remi Vanicat <vanicat@debian.org>
Subject: Re: [Caml-list] Re: OO programming
Date: Thu, 21 Feb 2008 17:55:49 +0100
Message-ID: <47BDAD15.9020501@free.fr>

Remi Vanicat a écrit :
> something like that might work (from the Dider Remy example)
>
>
> class ['observer] subject =
> object (self : 'mytype)
>   val mutable observers : 'observer list = []
>   method add obs = observers <- obs :: observers
>   method notify (message : 'observer -> 'mytype -> unit) =
>     List.iter (fun obs -> message obs self) observers
> end;;
>
> class ['subject] observer =
> object
>   constraint 'subject = 'a #subject
> end;;
>
> Note that it doesn't solve completely the problem (as #subject is
> still an open type) but it might catch some problem.
>
>   
Thanks for your answer. It seems to be an interesting direction. Here is 
a try to expand the example further, where I assume that messages will 
go through one single method :

class ['observer] subject =
object (self : 'mytype)
  val mutable observers : 'observer list = []
  method add obs = observers <- obs :: observers
  method notify (message : 'message) =
    List.iter (fun obs -> obs#send message self) observers
end

class virtual ['subject, 'message] observer =
object (self : 'self)
  constraint 'subject = 'observer #subject
  method virtual send : 'message -> 'subject -> unit
end

This is still not enough, as I can for example, forget the 'subject 
argument in the type of send, without any type error (at this point). 
However, adding the constraint

  constraint 'observer = (_, _) #observer

in the observer class does the work: if I write

  method virtual send : 'message -> 'subject -> unit

then the class is rejected (with a horrible message, though, which I 
don't reproduce here to avoid hurting the sensibility of inocent ocaml 
users). the two classes seem to be "usable". Still, there is no link 
between the type 'self in the observer, and the type of the observer as 
viewed by the subject. I don't have a precise example in mind, but I 
feel that something is missing.

A stronger possibility (which doesn't work) is to add the following 
constraint instead :

  constraint 'observer = 'self

The class is rejected and I even get an understandable message:

    method virtual send : 'message -> unit
    ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
The method send has type 'a -> unit but is expected to have type
  'a -> < send : 'b; .. > #subject -> unit as 'b

However, this constraint seems to be too restrictive, since, as I 
understand, it forces the subject to know the exact type of the 
observers which prevents (at least in my first tries) to add to a same 
subject different sub-classes of observer (or maybe I'm not using the 
right coercion).

let s = new subject
let o = object inherit [_, _] observer method send _ _ = () method foo = 
() end
let _ = s#add (o :> (_, _) observer)

=> long  complicated message


Tiphaine Turpin



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

* Re: [Caml-list] Re: OO programming
  2008-02-21 16:59 [Caml-list] Re: OO programming Tiphaine.Turpin
@ 2008-02-21 19:47 ` Tiphaine.Turpin
  2008-02-21 23:56   ` Julien Moutinho
  0 siblings, 1 reply; 4+ messages in thread
From: Tiphaine.Turpin @ 2008-02-21 19:47 UTC (permalink / raw)
  To: caml-list

Tiphaine.Turpin a écrit :
>
>
> ------------------------------------------------------------------------
>
> Sujet:
> Re: [Caml-list] Re: OO programming
> Expéditeur:
> "Tiphaine.Turpin" <Tiphaine.Turpin@free.fr>
> Date:
> Thu, 21 Feb 2008 17:55:49 +0100
> Destinataire:
> Remi Vanicat <vanicat@debian.org>
>
> Destinataire:
> Remi Vanicat <vanicat@debian.org>
>
>
> Remi Vanicat a écrit :
>> something like that might work (from the Dider Remy example)
>>
>>
>> class ['observer] subject =
>> object (self : 'mytype)
>>   val mutable observers : 'observer list = []
>>   method add obs = observers <- obs :: observers
>>   method notify (message : 'observer -> 'mytype -> unit) =
>>     List.iter (fun obs -> message obs self) observers
>> end;;
>>
>> class ['subject] observer =
>> object
>>   constraint 'subject = 'a #subject
>> end;;
>>
>> Note that it doesn't solve completely the problem (as #subject is
>> still an open type) but it might catch some problem.
>>
>>   
> Thanks for your answer. It seems to be an interesting direction. Here 
> is a try to expand the example further, where I assume that messages 
> will go through one single method :
>
> class ['observer] subject =
> object (self : 'mytype)
>  val mutable observers : 'observer list = []
>  method add obs = observers <- obs :: observers
>  method notify (message : 'message) =
>    List.iter (fun obs -> obs#send message self) observers
> end
>
> class virtual ['subject, 'message] observer =
> object (self : 'self)
>  constraint 'subject = 'observer #subject
>  method virtual send : 'message -> 'subject -> unit
> end
>
> This is still not enough, as I can for example, forget the 'subject 
> argument in the type of send, without any type error (at this point). 
> However, adding the constraint
>
>  constraint 'observer = (_, _) #observer
>
> in the observer class does the work: if I write
>
>  method virtual send : 'message -> 'subject -> unit
>
> then the class is rejected (with a horrible message, though, which I 
> don't reproduce here to avoid hurting the sensibility of inocent ocaml 
> users). the two classes seem to be "usable". Still, there is no link 
> between the type 'self in the observer, and the type of the observer 
> as viewed by the subject. I don't have a precise example in mind, but 
> I feel that something is missing.
Of course something is missing : if I just forget the method send, then 
I have no error, which is problematic.

>
>
> A stronger possibility (which doesn't work) is to add the following 
> constraint instead :
>
>  constraint 'observer = 'self
>
> The class is rejected
(when doing the same mistake as above: forgetting the 'subject argument, 
otherwise it typechecks normally)
> and I even get an understandable message:
>
>    method virtual send : 'message -> unit
>    ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> The method send has type 'a -> unit but is expected to have type
>  'a -> < send : 'b; .. > #subject -> unit as 'b
>
In addition, if I now forget the virtual method send, it gets added 
automagically in the type !
> However, this constraint seems to be too restrictive, since, as I 
> understand, it forces the subject to know the exact type of the 
> observers which prevents (at least in my first tries) to add to a same 
> subject different sub-classes of observer (or maybe I'm not using the 
> right coercion).
>
> let s = new subject
> let o = object inherit [_, _] observer method send _ _ = () method foo 
> = () end
> let _ = s#add (o :> (_, _) observer)
>
> => long  complicated message
>
I have the impression that the right constraint would be something like
" 'self must be coercible to 'observer "
but I don't know if this makes sense...
>
> Tiphaine Turpin
>
>
> ------------------------------------------------------------------------
>
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>   


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

* Re: [Caml-list] Re: OO programming
  2008-02-21 19:47 ` Tiphaine.Turpin
@ 2008-02-21 23:56   ` Julien Moutinho
  2008-02-22 13:52     ` Tiphaine.Turpin
  0 siblings, 1 reply; 4+ messages in thread
From: Julien Moutinho @ 2008-02-21 23:56 UTC (permalink / raw)
  To: caml-list

On Thu, Feb 21, 2008 at 08:47:17PM +0100, Tiphaine.Turpin wrote:
> [...]

Below is a couple of design patterns which may be of interest to you.
The first one uses the [and] keyword with [class].
The second one uses the [and] keyword with [class type].

One advantage of the later being its capacity to be split
into several files (namely: header.ml, observer.ml and subject.ml),
but it is a little bit more verbose.

BTW, See also this chapter focusing on POO with OCaml:
  http://caml.inria.fr/pub/docs/oreilly-book/html/index.html#chap-POO

HTH.


# First design: implementation
# -----------------------------

% cat tiph_oo_and.ml
class ['msg] observer
  (subject: 'msg subject) =
  object
    method subject = subject
    method send : 'msg -> unit = fun _ -> ()
  end
and ['msg] subject =
  object (self)
    method private coerce =
        (self :> 'msg subject)
    val mutable observers : 'msg observer list = []
    method add () =
        let o = new observer self#coerce in
        observers <- o :: observers; o
    method notify (msg: 'msg) =
        List.iter
          (fun obs -> obs#send msg)
          observers
  end

let s = new subject
let o = s#add ()
let () = o#send `HELLO

# First design: interface
# -----------------------------

% ocamlc -i tiph_oo.ml
class ['a] observer :
  'a subject ->
  object
    method send : 'a -> unit
    method subject : 'a subject
  end

and ['a] subject :
  object
    val mutable observers : 'a observer list
    method add : unit -> 'a observer
    method private coerce : 'a subject
    method notify : 'a -> unit
  end

val s : _[> `HELLO ] subject
val o : _[> `HELLO ] observer

# Second design: implementation
# -----------------------------

% cat tiph_oo_mod.ml
module Header =
  struct
    class type ['msg] observer =
      object
        method subject : 'msg subject
        method send    : 'msg -> unit
      end
    and ['msg] subject =
      object
        method add    : unit -> 'msg observer
        method notify : 'msg -> unit
      end
  end

module Observer =
  struct
    class ['msg] observer :
      'msg Header.subject ->
      ['msg] Header.observer =
      fun subject ->
      object
        method subject = subject
        method send = fun _ -> ()
      end
  end

module Subject =
  struct
    class ['msg] subject :
      ['msg] Header.subject =
      object (self)
        method private coerce =
            (self :> 'msg subject)
        val mutable observers = []
        method add () =
            let o = (new Observer.observer self#coerce :> 'msg Header.observer) in
            observers <- o :: observers; o
        method notify (msg: 'msg) =
            List.iter
              (fun obs -> obs#send msg)
              observers
      end
  end

let s = new Subject.subject
let o = s#add ()
let () = o#send `HELLO

module Subject__alternative =
  (* NOTE: in this alternative, a double coercion is used
   * in order to have a [subject] class bigger than
   * [Header.subject] (a public method [some_method] here). *)
  struct
    class ['msg] subject =
      object (self)
        method private coerce =
            ((self :> 'msg subject) :> 'msg Header.subject)
        val mutable observers = []
        method add () =
            let o = (new Observer.observer self#coerce :> 'msg Header.observer) in
            observers <- o :: observers; o
        method notify (msg: 'msg) =
            List.iter
              (fun obs -> obs#send msg)
              observers
        method some_method = ()
      end
  end

let s_a = new Subject__alternative.subject
let o_a = s_a#add ()
let () = o_a#send `HI


# Second design: interface
# -----------------------------

% ocamlc -i tiph_oo_mod.ml
module Header :
  sig
    class type ['a] observer =
      object method send : 'a -> unit method subject : 'a subject end
    and ['a] subject =
      object method add : unit -> 'a observer method notify : 'a -> unit end
  end

module Observer :
  sig class ['a] observer : 'a Header.subject -> ['a] Header.observer end

module Subject : sig class ['a] subject : ['a] Header.subject end

val s : _[> `HELLO ] Subject.subject
val o : _[> `HELLO ] Header.observer


module Subject__alternative :
  sig
    class ['a] subject :
      object
        val mutable observers : 'a Header.observer list
        method add : unit -> 'a Header.observer
        method private coerce : 'a Header.subject
        method notify : 'a -> unit
        method some_method : unit
      end
  end

val s_a : _[> `HI ] Subject__alternative.subject
val o_a : _[> `HI ] Header.observer


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

* Re: [Caml-list] Re: OO programming
  2008-02-21 23:56   ` Julien Moutinho
@ 2008-02-22 13:52     ` Tiphaine.Turpin
  0 siblings, 0 replies; 4+ messages in thread
From: Tiphaine.Turpin @ 2008-02-22 13:52 UTC (permalink / raw)
  To: Julien Moutinho, caml-list

This is a nice account on how to write those things in a clean and 
modular way. It does not meet all of my requirements however...

The 'msg parameter seems to allow the extension of the set of messages 
that may be used at the interface, and the use of closed types enforce 
strong consistency checks between the two classes. However, a first 
problem is that the communication can only be extended through the  'msg 
parameter: although we may add methods to both classes, it will not be 
possible to for a class to use the new methods of the other (at least, 
if the objects are taken from the existing "subject" and "observers" 
fields). For instance, the following extension to your first design 
fails to typecheck:

class  ['msg] observer'
  (subject: 'msg subject) = object
    inherit ['msg'] observer subject
    method send' = ()
  end
and ['msg] subject' = object
  inherit ['msg] subject
  method notify' =
    List.iter
      (fun obs -> obs#foo)
      observers
end

Second, if We try to be more concrete, we certainly don't want to write

    method send' : 'msg -> unit = function _ -> ()

but instead (as soon as we don't want the method to be virtual 
anymore),  something like:

    method send' : 'msg -> unit = function `HELLO -> ()

which prevents any further extension, as we get: constraint 'a = [ `HELLO ].

A solution that works is

    method send' : 'msg -> unit = function `HELLO -> () | _ -> assert false

because this only implies constraint 'a = [> `HELLO ], but then we loose 
the guarantee that `HELLO is indeed handled (we could have said fun _ -> 
assert false).

In fact, the use of a parameter message type allows to separate the type 
of the interface between the two objects from the "structure" of the 
link between the two classes. So the pattern may be "applied", but not 
really "extended" in the most general sense. The interesting point is 
that successive extension (i.e., adding methods) can be simulated by 
adding messages and extending the handler, but we loose the strong 
consistency guarantee that the messages are actually handled. 
Interestingly, we will still detect a use of a message with different 
number or type of parameters : exactly as when using constraints with 
open types as suggested by Remi Vanicat.

Tiphaine Turpin



Julien Moutinho a écrit :
> On Thu, Feb 21, 2008 at 08:47:17PM +0100, Tiphaine.Turpin wrote:
>   
>> [...]
>>     
>
> Below is a couple of design patterns which may be of interest to you.
> The first one uses the [and] keyword with [class].
> The second one uses the [and] keyword with [class type].
>
> One advantage of the later being its capacity to be split
> into several files (namely: header.ml, observer.ml and subject.ml),
> but it is a little bit more verbose.
>
> BTW, See also this chapter focusing on POO with OCaml:
>   http://caml.inria.fr/pub/docs/oreilly-book/html/index.html#chap-POO
>
> HTH.
>
>
> # First design: implementation
> # -----------------------------
>
> % cat tiph_oo_and.ml
> class ['msg] observer
>   (subject: 'msg subject) =
>   object
>     method subject = subject
>     method send : 'msg -> unit = fun _ -> ()
>   end
> and ['msg] subject =
>   object (self)
>     method private coerce =
>         (self :> 'msg subject)
>     val mutable observers : 'msg observer list = []
>     method add () =
>         let o = new observer self#coerce in
>         observers <- o :: observers; o
>     method notify (msg: 'msg) =
>         List.iter
>           (fun obs -> obs#send msg)
>           observers
>   end
>
> let s = new subject
> let o = s#add ()
> let () = o#send `HELLO
>
> # First design: interface
> # -----------------------------
>
> % ocamlc -i tiph_oo.ml
> class ['a] observer :
>   'a subject ->
>   object
>     method send : 'a -> unit
>     method subject : 'a subject
>   end
>
> and ['a] subject :
>   object
>     val mutable observers : 'a observer list
>     method add : unit -> 'a observer
>     method private coerce : 'a subject
>     method notify : 'a -> unit
>   end
>
> val s : _[> `HELLO ] subject
> val o : _[> `HELLO ] observer
>
> # Second design: implementation
> # -----------------------------
>
> % cat tiph_oo_mod.ml
> module Header =
>   struct
>     class type ['msg] observer =
>       object
>         method subject : 'msg subject
>         method send    : 'msg -> unit
>       end
>     and ['msg] subject =
>       object
>         method add    : unit -> 'msg observer
>         method notify : 'msg -> unit
>       end
>   end
>
> module Observer =
>   struct
>     class ['msg] observer :
>       'msg Header.subject ->
>       ['msg] Header.observer =
>       fun subject ->
>       object
>         method subject = subject
>         method send = fun _ -> ()
>       end
>   end
>
> module Subject =
>   struct
>     class ['msg] subject :
>       ['msg] Header.subject =
>       object (self)
>         method private coerce =
>             (self :> 'msg subject)
>         val mutable observers = []
>         method add () =
>             let o = (new Observer.observer self#coerce :> 'msg Header.observer) in
>             observers <- o :: observers; o
>         method notify (msg: 'msg) =
>             List.iter
>               (fun obs -> obs#send msg)
>               observers
>       end
>   end
>
> let s = new Subject.subject
> let o = s#add ()
> let () = o#send `HELLO
>
> module Subject__alternative =
>   (* NOTE: in this alternative, a double coercion is used
>    * in order to have a [subject] class bigger than
>    * [Header.subject] (a public method [some_method] here). *)
>   struct
>     class ['msg] subject =
>       object (self)
>         method private coerce =
>             ((self :> 'msg subject) :> 'msg Header.subject)
>         val mutable observers = []
>         method add () =
>             let o = (new Observer.observer self#coerce :> 'msg Header.observer) in
>             observers <- o :: observers; o
>         method notify (msg: 'msg) =
>             List.iter
>               (fun obs -> obs#send msg)
>               observers
>         method some_method = ()
>       end
>   end
>
> let s_a = new Subject__alternative.subject
> let o_a = s_a#add ()
> let () = o_a#send `HI
>
>
> # Second design: interface
> # -----------------------------
>
> % ocamlc -i tiph_oo_mod.ml
> module Header :
>   sig
>     class type ['a] observer =
>       object method send : 'a -> unit method subject : 'a subject end
>     and ['a] subject =
>       object method add : unit -> 'a observer method notify : 'a -> unit end
>   end
>
> module Observer :
>   sig class ['a] observer : 'a Header.subject -> ['a] Header.observer end
>
> module Subject : sig class ['a] subject : ['a] Header.subject end
>
> val s : _[> `HELLO ] Subject.subject
> val o : _[> `HELLO ] Header.observer
>
>
> module Subject__alternative :
>   sig
>     class ['a] subject :
>       object
>         val mutable observers : 'a Header.observer list
>         method add : unit -> 'a Header.observer
>         method private coerce : 'a Header.subject
>         method notify : 'a -> unit
>         method some_method : unit
>       end
>   end
>
> val s_a : _[> `HI ] Subject__alternative.subject
> val o_a : _[> `HI ] Header.observer
>
> _______________________________________________
> Caml-list mailing list. Subscription management:
> http://yquem.inria.fr/cgi-bin/mailman/listinfo/caml-list
> Archives: http://caml.inria.fr
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>   


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

end of thread, other threads:[~2008-02-22 13:56 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-02-21 16:59 [Caml-list] Re: OO programming Tiphaine.Turpin
2008-02-21 19:47 ` Tiphaine.Turpin
2008-02-21 23:56   ` Julien Moutinho
2008-02-22 13:52     ` Tiphaine.Turpin

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).