caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] functors and objects
@ 2004-02-03 18:06 Damien
  2004-02-03 19:37 ` Matt Gushee
                   ` (2 more replies)
  0 siblings, 3 replies; 9+ messages in thread
From: Damien @ 2004-02-03 18:06 UTC (permalink / raw)
  To: caml-list

Hello,

I would like to write something like

<<
class type o = 
object 
	method react: unit
end

module type O = 
sig
	type t :> o (* sigh... *)
end

module R(M: O) = 
struct
	let l: M.t list ref = []
	let register (o: M.t) = l := o :: !l
	let react() = List.iter (fun o -> o#react) !l
end
>>

and then, in a second layer, something like 

<<
class type o' = 
object 
	inherit o
	method render: unit
end

module type O' = 
sig
	type t :> o' 
end

module R(M: O') = 
struct
	include R(M)
	let render() = List.iter (fun o -> o#render) !l
end
>>

I tried all sort of tricks with #o, type 'a t = #o as 'a ...
but I didn't managed to to it :(
(without turning my objects into plain modules)

Any idea ?

Is it unsound to let a functor use an object type ?
(not to inherit from the class, 
just to use the methods of objects belonging to this type)

thanks,
damien

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects
  2004-02-03 18:06 [Caml-list] functors and objects Damien
@ 2004-02-03 19:37 ` Matt Gushee
  2004-02-03 19:39 ` [Caml-list] functors and objects' Matt Gushee
  2004-02-04  2:57 ` [Caml-list] functors and objects Jacques Garrigue
  2 siblings, 0 replies; 9+ messages in thread
From: Matt Gushee @ 2004-02-03 19:37 UTC (permalink / raw)
  To: caml-list

On Tue, Feb 03, 2004 at 07:06:35PM +0100, Damien wrote:
> 
> I would like to write something like
> 
> <<
> class type o = 
> object 
> 	method react: unit
> end
> 
> module type O = 
> sig
> 	type t :> o (* sigh... *)
> end

The first problem is that you're mixing type declarations and class
casts ... not a hard mistake to make, since the class cast syntax is a
bit confusing, and doesn't seem to be explained very well anywhere.
Anyway, you seem to have missed the simplest solution:

  module type O =
    sig
      type t = o
    end


> module R(M: O') = 
> struct
> 	include R(M)

I don't see how this can work, because this module R takes an argument
of type O', whereas the other R (do you really want to give them the
same name?) takes an argument of type O. Regardless of their contents,
they are different interfaces and thus not interchangeable. There's
undoubtedly a way to achieve the result you want, but I don't really
understand what you are trying to do. Do you actually have a specific
goal in mind, or are you just experimenting?

-- 
Matt Gushee                 When a nation follows the Way,
Englewood, Colorado, USA    Horses bear manure through
mgushee@havenrock.com           its fields;
http://www.havenrock.com/   When a nation ignores the Way,
                            Horses bear soldiers through
                                its streets.
                                
                            --Lao Tzu (Peter Merel, trans.)

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects'
  2004-02-03 18:06 [Caml-list] functors and objects Damien
  2004-02-03 19:37 ` Matt Gushee
@ 2004-02-03 19:39 ` Matt Gushee
  2004-02-03 20:26   ` Damien Pous
  2004-02-04  2:57 ` [Caml-list] functors and objects Jacques Garrigue
  2 siblings, 1 reply; 9+ messages in thread
From: Matt Gushee @ 2004-02-03 19:39 UTC (permalink / raw)
  To: caml-list

On Tue, Feb 03, 2004 at 07:06:35PM +0100, Damien wrote:
> 
> I would like to write something like
> 
> <<
> class type o = 
> object 
> 	method react: unit
> end
> 
> module type O = 
> sig
> 	type t :> o (* sigh... *)
> end

The first problem is that you're mixing type declarations and class
casts ... not a hard mistake to make, since the class cast syntax is a
bit confusing, and doesn't seem to be explained very well anywhere.
Anyway, you seem to have missed the simplest solution:

  module type O =
    sig
      type t = o
    end


> module R(M: O') = 
> struct
> 	include R(M)

I don't see how this can work, because this module R takes an argument
of type O', whereas the other R (do you really want to give them the
same name?) takes an argument of type O. Regardless of their contents,
they are different interfaces and thus not interchangeable. There's
undoubtedly a way to achieve the result you want, but I don't really
understand what you are trying to do. Do you actually have a specific
goal in mind, or are you just experimenting?

-- 
Matt Gushee                 When a nation follows the Way,
Englewood, Colorado, USA    Horses bear manure through
mgushee@havenrock.com           its fields;
http://www.havenrock.com/   When a nation ignores the Way,
                            Horses bear soldiers through
                                its streets.
                                
                            --Lao Tzu (Peter Merel, trans.)

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects'
  2004-02-03 19:39 ` [Caml-list] functors and objects' Matt Gushee
@ 2004-02-03 20:26   ` Damien Pous
  0 siblings, 0 replies; 9+ messages in thread
From: Damien Pous @ 2004-02-03 20:26 UTC (permalink / raw)
  To: caml-list

En réponse à Matt Gushee <mgushee@havenrock.com>:

> On Tue, Feb 03, 2004 at 07:06:35PM +0100, Damien wrote:
> > 	type t :> o (* sigh... *)
>
> The first problem is that you're mixing type declarations and class
> casts ... not a hard mistake to make, since the class cast syntax is a
> bit confusing, and doesn't seem to be explained very well anywhere.
of course, this was not "real OCaml code" :)
I just wanted to express the fact that my functor R has to accept any module M
defining an object type `t' with at least a method `react'
(that is, t :> o)

> > module R(M: O') = 
> > struct
> > 	include R(M)
> 
> I don't see how this can work, because this module R takes an argument
> of type O', whereas the other R (do you really want to give them the
> same name?) takes an argument of type O. Regardless of their contents,
> they are different interfaces and thus not interchangeable. 
since o' :> o, M: O' should be a valid candidate for R...

> There's undoubtedly a way to achieve the result you want, but I don't 
> really understand what you are trying to do. 

the following correct code does partially what I want :

module type O = sig 
  type t
  val send: [<`React] -> t -> unit
end
module R(M: O) = struct
  let l = ref []
  let register (o: M.t) = l := o :: !l
  let react() = List.iter (M.send `React) !l
end

module type O' = sig
  type t
  val send: [<`React|`Render] -> t -> unit
end
module R'(M: O') = struct
  include R(M)   (* <-- "subtyping" is automagically done *)
  let render() = List.iter (M.send `Render) !l
end

but I am partially re-encoding objects with modules and variants,
and this encoding becomes quite ugly when it comes to _real_ objects
(with inheritance, virtual methods...)


> Do you actually have a specific goal in mind, or are you just experimenting?

both !

I am working on a project that use a "Reactor" where a lots of "Objects" react.
This project is cut into three layers :
  Base       reactor and objects (generic)
  Meaningful reactor and objects (objects really react)
  Rendered   reactor and objects (Gtk, maybe GL some day)

Currently both reactor and objects are "OCaml objects", but the project only use 
_one_ instance of the rendered reactor class. Thus I am wondering how I could
turn it into a module...
This module has to be defined incrementally : Base, Meaningful, Rendered.
but at the Base level, the final type of contained objects is unknown,
whence the need for a functor.
(with objects, this is done with parametrized classes)

Since objects really need to be "objects" (late binding), 
I cannot turn both objects and reactor into modules (or at least in a beautiful way)

arf...

damien

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects
  2004-02-03 18:06 [Caml-list] functors and objects Damien
  2004-02-03 19:37 ` Matt Gushee
  2004-02-03 19:39 ` [Caml-list] functors and objects' Matt Gushee
@ 2004-02-04  2:57 ` Jacques Garrigue
  2004-02-05  8:55   ` Damien
  2 siblings, 1 reply; 9+ messages in thread
From: Jacques Garrigue @ 2004-02-04  2:57 UTC (permalink / raw)
  To: Damien.Pous; +Cc: caml-list

From: Damien <Damien.Pous@ens-lyon.fr>

> I would like to write something like
> 
> <<
> class type o = 
> object 
> 	method react: unit
> end
> 
> module type O = 
> sig
> 	type t :> o (* sigh... *)
> end
> 
> module R(M: O) = 
> struct
> 	let l: M.t list ref = []
> 	let register (o: M.t) = l := o :: !l
> 	let react() = List.iter (fun o -> o#react) !l
> end
> >>

The closest I can see to what you ask for is

module type O = sig
  type t
  val as_o : t -> o
end

module R(M: O) = struct
  let l: M.t list ref = ref []
  let register (o: M.t) = l := o :: !l
  let react() = List.iter (fun o -> (M.as_o o)#react) !l
end

module RO = R(struct type t = o let as_o x = x end)

Then your second layer would be

class type o' = object 
  inherit o
  method render: unit
end

module type O' = sig
  include O
  val as_o' : t -> o'
end

module R(M: O') = struct
  include R(M)
  let render() = List.iter (fun o -> (M.as_o' o)#render) !l
end

module O' = struct
  type t = o'
  let as_o  x = (x : t :> o)
  let as_o' x = x
end

module RO' = R(O')

> Is it unsound to let a functor use an object type ?
> (not to inherit from the class, 
> just to use the methods of objects belonging to this type)

This isn't a problem of soundness.
There is just no such thing as a "partially abstract" object type.
But as shown above, you can easily simulate it by coupling an abstract
type with a coercion to an object type.

Note however that it would be probably simpler to turn your functors
into parameterized classes: then you can specify constraints on the
parameters with #-types.

class ['a] r = object
  constraint 'a = #o
  val mutable l : 'a list = []
  method register o = l <- o :: l
  method react = List.iter (fun o -> o#react) l
end

class ['a] r' = object
  constraint 'a = #o'
  inherit ['a] r
  method render = List.iter (fun o -> o#render) l
end

But I don't know what you have precisely in mind.

     Jacques

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects
  2004-02-04  2:57 ` [Caml-list] functors and objects Jacques Garrigue
@ 2004-02-05  8:55   ` Damien
  2004-02-05  9:18     ` Jacques Garrigue
  0 siblings, 1 reply; 9+ messages in thread
From: Damien @ 2004-02-05  8:55 UTC (permalink / raw)
  To: caml-list

On Wed, 04 Feb 2004 11:57:45 +0900 Jacques Garrigue wrote:

> The closest I can see to what you ask for is
> 
> module type O = sig
>   type t
>   val as_o : t -> o
> end
> ...
> 
> This isn't a problem of soundness.
> There is just no such thing as a "partially abstract" object type.
there is no such thing...
...in the type system or in the compiler ?

Sorry for mixing variants and objects again, 
but I have got the feeling that since the example I posted with variants
works, the first example with objects could/should work :
It seems quite natural and reasonable. So why should it be rejected...

I don't really see what can prevent the compiler to do it.
It looks like an additional check in the type checker,
and almost nothing in the compiler
(that's just a feeling, I never looked at ocamlc sources...)

> But as shown above, you can easily simulate it by coupling an abstract
> type with a coercion to an object type.
still curious : are such "coercion identity functions" eliminated by the
compiler ?
 
> Note however that it would be probably simpler to turn your functors
> into parameterized classes: then you can specify constraints on the
> parameters with #-types.
yes, the project is currently written with classes like
['reactor] obj 
['obj] reactor

I was just wondering whether the  class "reactor"
could be translated into a module, since it is instantiated only once.

cheers,
damien

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects
  2004-02-05  8:55   ` Damien
@ 2004-02-05  9:18     ` Jacques Garrigue
  2004-02-05 13:45       ` Damien
  0 siblings, 1 reply; 9+ messages in thread
From: Jacques Garrigue @ 2004-02-05  9:18 UTC (permalink / raw)
  To: Damien.Pous; +Cc: caml-list

From: Damien <Damien.Pous@ens-lyon.fr>

> > This isn't a problem of soundness.
> > There is just no such thing as a "partially abstract" object type.
> there is no such thing...
> ...in the type system or in the compiler ?
> 
> Sorry for mixing variants and objects again, 
> but I have got the feeling that since the example I posted with variants
> works, the first example with objects could/should work :
> It seems quite natural and reasonable. So why should it be rejected...

Because instanciation/specialization only works for values, not for
types.
This is reasonable enough: once you have defined a type, you may use
it both in covariant and contravariant positions, so allowing to
specialize it would be unsound.
(So, yes, in the long run this is a soundness problem.)

The solution you describe with polymorphic variants use values, so
specialization works as expected.

> I don't really see what can prevent the compiler to do it.
> It looks like an additional check in the type checker,
> and almost nothing in the compiler
> (that's just a feeling, I never looked at ocamlc sources...)

Have a look if you have lots of free time :-)

> > But as shown above, you can easily simulate it by coupling an abstract
> > type with a coercion to an object type.
> still curious : are such "coercion identity functions" eliminated by the
> compiler ?

Unfortunately, no.
In general, functorial code (or object-oriented code) is much less
optimized than a first order style.
But it's not going to be very expensive either: just a few more jumps.

Jacques Garrigue

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects
  2004-02-05  9:18     ` Jacques Garrigue
@ 2004-02-05 13:45       ` Damien
  2004-02-06  1:30         ` Jacques Garrigue
  0 siblings, 1 reply; 9+ messages in thread
From: Damien @ 2004-02-05 13:45 UTC (permalink / raw)
  To: caml-list

On Thu, 05 Feb 2004 18:18:45 +0900 Jacques Garrigue wrote:

> Because instanciation/specialization only works for values, not for
> types.
> This is reasonable enough: once you have defined a type, you may use
> it both in covariant and contravariant positions, so allowing to
> specialize it would be unsound.
> (So, yes, in the long run this is a soundness problem.)

I don't see the point :-(

module type O = 
sig
	type " t :> o "
end

can be read as

module type O =
sig
	type ellipsis (* abstract *)
	type t = " <o; ellipsis> "
end

therefore, a functor F(M: O) cannot create objects of type t without the
help of M. 

module F(M: O) = 
struct
	(* correct invariant use *)
	let l: M.t list ref  = ref []   

	(* correct covariant use *)
	let get: unit -> M.t list = fun () -> !l

	(* correct contravariant use *)
	let add: M.t -> unit = fun o -> l := o : !l 

	(* unsound has type `unit -> o' but not `unit -> M.t' *)
	let unsound() = new object method react = () end 
end

where is it wrong ?

damien

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

* Re: [Caml-list] functors and objects
  2004-02-05 13:45       ` Damien
@ 2004-02-06  1:30         ` Jacques Garrigue
  0 siblings, 0 replies; 9+ messages in thread
From: Jacques Garrigue @ 2004-02-06  1:30 UTC (permalink / raw)
  To: Damien.Pous; +Cc: caml-list

From: Damien <Damien.Pous@ens-lyon.fr>
> On Thu, 05 Feb 2004 18:18:45 +0900 Jacques Garrigue wrote:
> 
> > Because instanciation/specialization only works for values, not for
> > types.
> > This is reasonable enough: once you have defined a type, you may use
> > it both in covariant and contravariant positions, so allowing to
> > specialize it would be unsound.
> > (So, yes, in the long run this is a soundness problem.)
> 
> I don't see the point :-(
> 
> module type O = 
> sig
> 	type " t :> o "
> end
> 
> can be read as
> 
> module type O =
> sig
> 	type ellipsis (* abstract *)
> 	type t = " <o; ellipsis> "
> end
> 
> therefore, a functor F(M: O) cannot create objects of type t without the
> help of M. 

I see.
This way you can coerce from t to o, but not the other way round.
The trouble is just that in ocaml, the row variable of an object type
is not a type in itself (even if it uses the same datatype
representation in the compiler).
There are actually three possible row-endings:
  Tvar -> an extensible row, as the one in "#o"
  Tnil -> a closed row, as in "o"
  Tunivar -> an existential row variable, unifies only with itself,
          and must be bound locally. used for polymorphic variables in
          polymorphic methods.
What you are asking for is actually adding a 4th form,
  Tconstr (path, args, memo) ->
      extension through a type (abstract or concrete) 
Not only would this require to extend all existing handling of
row-endings (which occur in many places in the compiler), but this
should also include the possibility that the extension is concrete
(needed as you want to be able to add methods through functor
application), and should be expanded when looking for a method. This
breaks another assumption in the compiler (that no expansion is needed
to access the method types.)

But all this technical part is possible.
The real question is: would it be useful?
Note that compared to a class-based approach, the extensibility would
still be weaker: in declaration
   type ('a1,..,'an) t :> ('a1,..,'an) o
only the type variables 'a1 to 'an can be used in extra methods.
This is a well-known problem with functors, but would be even more
problematic if we allow this kind of semi-abstract types.

For all these reasons, your idea, while theoretically interesting,
does not attract me so much: lots of work for a rather weak result,
while there are already simpler ways to do the same thing.

Jacques Garrigue

-------------------
To unsubscribe, mail caml-list-request@inria.fr Archives: http://caml.inria.fr
Bug reports: http://caml.inria.fr/bin/caml-bugs FAQ: http://caml.inria.fr/FAQ/
Beginner's list: http://groups.yahoo.com/group/ocaml_beginners


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

end of thread, other threads:[~2004-02-06  1:30 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2004-02-03 18:06 [Caml-list] functors and objects Damien
2004-02-03 19:37 ` Matt Gushee
2004-02-03 19:39 ` [Caml-list] functors and objects' Matt Gushee
2004-02-03 20:26   ` Damien Pous
2004-02-04  2:57 ` [Caml-list] functors and objects Jacques Garrigue
2004-02-05  8:55   ` Damien
2004-02-05  9:18     ` Jacques Garrigue
2004-02-05 13:45       ` Damien
2004-02-06  1:30         ` Jacques Garrigue

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