caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] recursive modules
@ 2003-05-05  8:21 Xavier Leroy
  2003-05-05 11:29 ` Markus Mottl
                   ` (2 more replies)
  0 siblings, 3 replies; 6+ messages in thread
From: Xavier Leroy @ 2003-05-05  8:21 UTC (permalink / raw)
  To: caml-list

Since the issue of recursive modules has (again) popped up on this
list, it seems that now is a good time to announce an experimental
design and implementation for recursive modules in OCaml that I've
been working on lately.  A note describing the design is at

     http://cristal.inria.fr/~xleroy/publi/recursive-modules-note.pdf

and the implementation can be downloaded from the CVS repository
on camlcvs.inria.fr, tag "recursive_modules".

What this extension provides is a "module rec ... and ..." binding
that allows the definition of mutually-recursive modules within the
same compilation units.  Recursion between compilation units is a
different problem that is not adressed yet.  To give a flavor of the
extension, one can write for instance

    module A : sig
                 type t = Leaf of string | Node of ASet.t
                 val compare: t -> t -> int
               end
             = struct
                 type t = Leaf of string | Node of ASet.t
                 let compare t1 t2 =
                   match (t1, t2) with
                     (Leaf s1, Leaf s2) -> Pervasives.compare s1 s2
                   | (Leaf _, Node _) -> 1
                   | (Node _, Leaf _) -> -1
                   | (Node n1, Node n2) -> ASet.compare n1 n2
               end
    and ASet : Set.S with type elt = A.t
             = Set.Make(A)

The other point worth mentioning is that the detection of ill-founded
recursive definitions (definitions that have no fixpoint in a
call-by-value evaluation regime) is not completely static and may
cause an "Undefined" exception to be thrown at program initialization
time.  Fully static prevention of ill-founded recursion would, in the
current state of our knowledge, either rule out too many valuable
uses, or require major complications in the type system.  The proposed
approach is a pragmatic compromise rather than a 100% intellectually
satisfying solution.

No decision has been taken yet concerning the possible integration of
this extension in a future release of OCaml.

Comments and feedback are most welcome, as long as they are of the
constructive kind.

- Xavier Leroy

-------------------
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] 6+ messages in thread

* Re: [Caml-list] recursive modules
  2003-05-05  8:21 [Caml-list] recursive modules Xavier Leroy
@ 2003-05-05 11:29 ` Markus Mottl
  2003-05-16 16:31   ` brogoff
  2003-05-05 12:20 ` John Max Skaller
  2003-05-05 16:59 ` brogoff
  2 siblings, 1 reply; 6+ messages in thread
From: Markus Mottl @ 2003-05-05 11:29 UTC (permalink / raw)
  To: Xavier Leroy; +Cc: caml-list

On Mon, 05 May 2003, Xavier Leroy wrote:
> What this extension provides is a "module rec ... and ..." binding
> that allows the definition of mutually-recursive modules within the
> same compilation units.

This looks very promising indeed!

> Recursion between compilation units is a different problem that is
> not adressed yet.

I believe this shouldn't be such a big problem in practice, because one
can always functorize one module and tie the recursive knot elsewhere.

> To give a flavor of the extension, one can write for instance
[snip Set-example]

That's surely one of the major examples, where people really want (and
need) recursive modules.

> The other point worth mentioning is that the detection of ill-founded
> recursive definitions (definitions that have no fixpoint in a
> call-by-value evaluation regime) is not completely static and may
> cause an "Undefined" exception to be thrown at program initialization
> time.

Guaranteed at program initialization time? But how about local modules?

> Fully static prevention of ill-founded recursion would, in the current
> state of our knowledge, either rule out too many valuable uses,
> or require major complications in the type system.  The proposed
> approach is a pragmatic compromise rather than a 100% intellectually
> satisfying solution.

I personally could live with some dynamic checking of this sort. It's
always possible to improve static checking afterwards as long as the
language specification allows this in principle. The benefits of recursive
modules surely outweigh the drawbacks of some dynamic checking.

> No decision has been taken yet concerning the possible integration of
> this extension in a future release of OCaml.

This is of course a matter of how progressive (aggressive?) you want the
main distribution to be. I think that more exotic but otherwise usable
features in a distribution won't harm as long as they do not affect
normal work. Why not add this as usual to the "language extensions"
section of the manual?  People who want to be on the safe side are not
forced to use anything that's in there.

This would make it much easier to get feedback, because only few people
are daring enough to test things with some CVS-branch.

Regards,
Markus Mottl

-- 
Markus Mottl          http://www.oefai.at/~markus          markus@oefai.at

-------------------
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] 6+ messages in thread

* Re: [Caml-list] recursive modules
  2003-05-05  8:21 [Caml-list] recursive modules Xavier Leroy
  2003-05-05 11:29 ` Markus Mottl
@ 2003-05-05 12:20 ` John Max Skaller
  2003-05-05 16:59 ` brogoff
  2 siblings, 0 replies; 6+ messages in thread
From: John Max Skaller @ 2003-05-05 12:20 UTC (permalink / raw)
  To: Xavier Leroy; +Cc: caml-list

Xavier Leroy wrote:

> Since the issue of recursive modules has (again) popped up on this
> list, it seems that now is a good time to announce an experimental
> design and implementation for recursive modules in OCaml that I've
> been working on lately.  



> What this extension provides is a "module rec ... and ..." binding
> that allows the definition of mutually-recursive modules within the
> same compilation units.  Recursion between compilation units is a
> different problem that is not adressed yet.  



> Comments and feedback are most welcome, as long as they are of the
> constructive kind.


An interim hack may give the appearance of "almost" separate

compilation: require mutually recursive modules in separate
files be compiled together on the one command line:


ocamlc -bb file1.ml file2.ml -eb

[where -bb and -eb mean begin and end brackets]

and, well, simply concatenate them after adding
wrapper code:

	// file: file12.ml generated
	module file1 = struct
	#include file1.ml
	end
	and
	module file2 = struct
	#include file2.ml
	end

where file12 is implicitly opened.

This isn't separate compilation, but it does allow
something almost more important (since ocaml is so
fast, who cares about separate compilation anyhow?):
it allows breaking up long files into several
smaller ones.

-- 
John Max Skaller, mailto:skaller@ozemail.com.au
snail:10/1 Toxteth Rd, Glebe, NSW 2037, Australia.
voice:61-2-9660-0850


-------------------
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] 6+ messages in thread

* Re: [Caml-list] recursive modules
  2003-05-05  8:21 [Caml-list] recursive modules Xavier Leroy
  2003-05-05 11:29 ` Markus Mottl
  2003-05-05 12:20 ` John Max Skaller
@ 2003-05-05 16:59 ` brogoff
  2 siblings, 0 replies; 6+ messages in thread
From: brogoff @ 2003-05-05 16:59 UTC (permalink / raw)
  To: Xavier Leroy; +Cc: caml-list

On Mon, 5 May 2003, Xavier Leroy wrote:
> The other point worth mentioning is that the detection of ill-founded
> recursive definitions (definitions that have no fixpoint in a
> call-by-value evaluation regime) is not completely static and may
> cause an "Undefined" exception to be thrown at program initialization
> time.  Fully static prevention of ill-founded recursion would, in the
> current state of our knowledge, either rule out too many valuable
> uses, or require major complications in the type system.  The proposed
> approach is a pragmatic compromise rather than a 100% intellectually
> satisfying solution.

It seems like an acceptable compromise. I've only read the note, and I surely 
won't get it until I play with the compiler. One thing that I notice is that 
the scope rule restriction on with type constraints, which adds extra verbosity 
when trying to work around the restriction on module constraints, also adds 
sone extra verbosity to your version of Okasaki's bootstrap heaps. It would 
be nicer to write 

  module rec BE : ORDERED with type t = E | H Elem.t * PrimH.heap = 
    struct
    ... etc., etc., ...

in the same way that it would be nicer to not have to textually copy signatures 
in the workaround. Could that be fixed easily? It looks like it could be fixed 
in the current (nonrecursive) module system pretty easily but I don't know about 
your proposal.

Nice work! This problem is a real pain, and your proposal provides a real 
fix. 

-- Brian

-------------------
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] 6+ messages in thread

* Re: [Caml-list] recursive modules
  2003-05-05 11:29 ` Markus Mottl
@ 2003-05-16 16:31   ` brogoff
  0 siblings, 0 replies; 6+ messages in thread
From: brogoff @ 2003-05-16 16:31 UTC (permalink / raw)
  To: Markus Mottl; +Cc: Xavier Leroy, caml-list

On Mon, 5 May 2003, Markus Mottl wrote:
> On Mon, 05 May 2003, Xavier Leroy wrote:
> > The other point worth mentioning is that the detection of ill-founded
> > recursive definitions (definitions that have no fixpoint in a
> > call-by-value evaluation regime) is not completely static and may
> > cause an "Undefined" exception to be thrown at program initialization
> > time.
> 
> Guaranteed at program initialization time? But how about local modules?

Unfortunately local recursive modules are ruled out by syntax now. Any reason 
not to allow them? 

I agree with Markus' comment about having this in the main distribution. 
I made an mrec version, and I'm testing, but more people will thrash on 
this if it's part of the language. 

It's utility can't be denied, as it fixes the main problem with the ML 
module system, and just happens to sneak polymorphic recursion capabilities 
into OCaml (yes, I know they exist already because of first class 
polymorphism). I hope you decide to include this in 3.07. 

-- Brian

> > No decision has been taken yet concerning the possible integration of
> > this extension in a future release of OCaml.
> 
> This is of course a matter of how progressive (aggressive?) you want the
> main distribution to be. I think that more exotic but otherwise usable
> features in a distribution won't harm as long as they do not affect
> normal work. Why not add this as usual to the "language extensions"
> section of the manual?  People who want to be on the safe side are not
> forced to use anything that's in there.
> 
> This would make it much easier to get feedback, because only few people
> are daring enough to test things with some CVS-branch.
> 
> Regards,
> Markus Mottl
> 
> -- 
> Markus Mottl          http://www.oefai.at/~markus          markus@oefai.at
> 
> -------------------
> 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
> 

-------------------
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] 6+ messages in thread

* [Caml-list] Recursive Modules
@ 2003-08-29 20:17 Christopher Dutchyn
  0 siblings, 0 replies; 6+ messages in thread
From: Christopher Dutchyn @ 2003-08-29 20:17 UTC (permalink / raw)
  To: CAML List

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

I think the recursive modules definitions do not completely propagate safe
definitions: I get

Exception: Undefined_recursive_module ("SimpleLayer.ml", 104, 23)

with the attached code.

 

Chris D.

 

module type LAYER =

  sig

    type topT

    type topV

    val topInj : string -> topT

    val topOp  : topT -> topV

    val topExt : topV -> string

 

    type t

    type v

 

    val inj : string -> t

    val op : t -> v

    val ext : v -> string

  end

 

 

(* base module -- no lower layer present, empty types, all operations are
errors *)

(* *** ``safe'' module (section 7.8 of refman) *** *)

module MakeBase =

  functor (Above : LAYER) ->

  struct

    type topT = Above.topT

    type topV = Above.topV

    let topInj = fun x -> Above.topInj x(*safe*)

    let topOp  = fun x -> Above.topOp x (*safe*)

    let topExt = fun x -> Above.topExt x(*safe*)

 

    type t = EmptyT              (* wouldn't revised syntax be nice *)

    type v = EmptyV

          

    let inj = fun _ -> raise (Failure "inj")

    let op  = fun _ -> raise (Failure "op")

    let ext = fun _ -> raise (Failure "ext")

  end

 

(* an intermediate level *)

module MakeMiddle =

  functor (Below : LAYER) ->

    functor (Above : LAYER) ->

  struct

    type topT = Above.topT

    type topV = Above.topV

    let topInj = Above.topInj

    let topOp  = Above.topOp

    let topExt = Above.topExt

 

    type t =

      | BelowT of Below.t

      | OneT of char

      | TwoT of char * topT

            

    type v =

      | BelowV of Below.v

      | StringV of string

            

    let inj = fun s ->           (* <T> ::= 1_ [OneT _] | 2_? [TwoT _ ?] |
<Below.T> *)

      match (String.get s 0) with

      | '1' -> OneT (String.get s 1)

      | '2' -> TwoT(String.get s 1, topInj (String.sub s 2 ((String.length
s)-2)))

      | _ ->   BelowT (Below.inj s)

          

    let op =

      function

        | BelowT t -> BelowV (Below.op t)

        | OneT(c) -> StringV ("1" ^ (String.make 1 c))

        | TwoT(c,t) -> StringV ("2" ^ (String.make 1 c) ^ (topExt (topOp
t)))

              

    let ext =

      function

        | BelowV v -> Below.ext v

        | StringV s -> s

  end

 

(* imagine there were more levels -- maybe even tree/graph structured *)

 

(* top level -- close the open recursion of topInj and topExt *)

(* *** ``safe'' module (section 7.8 of refman) *** *)

module MakeTop =

  functor (Below : LAYER) ->

  struct

    type t = Below.t

    type v = Below.v

          

    let inj = fun x -> Below.inj x      (*safe*)

    let op  = fun x -> Below.op x       (*safe*)

    let ext = fun x -> Below.ext x      (*safe*)

 

    type topT = t

    type topV = v

    let topInj = fun x -> inj x         (*safe*)

    let topOp  = fun x -> op x          (*safe*)

    let topExt = fun x -> ext x         (*safe*)

  end

 

(* simplest test *)

module rec B : LAYER = MakeBase(T)

       and T : LAYER = MakeTop(B)

 

(* simple test *)

module rec B : LAYER = MakeBase(M)

       and M : LAYER = MakeMiddle(B)(T)

      (* imagine there were more levels *)

       and T : LAYER = MakeTop(M);;

 

T.topOp (T.topInj "2x1x");;

T.topExt (T.topOp (T.topInj "2x1x"))

 


[-- Attachment #2: Type: text/html, Size: 18585 bytes --]

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

end of thread, other threads:[~2003-08-29 20:17 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2003-05-05  8:21 [Caml-list] recursive modules Xavier Leroy
2003-05-05 11:29 ` Markus Mottl
2003-05-16 16:31   ` brogoff
2003-05-05 12:20 ` John Max Skaller
2003-05-05 16:59 ` brogoff
2003-08-29 20:17 [Caml-list] Recursive Modules Christopher Dutchyn

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