From mboxrd@z Thu Jan 1 00:00:00 1970 Received: (from majordomo@localhost) by pauillac.inria.fr (8.7.6/8.7.3) id WAA05117; Fri, 29 Aug 2003 22:17:22 +0200 (MET DST) X-Authentication-Warning: pauillac.inria.fr: majordomo set sender to owner-caml-list@pauillac.inria.fr using -f Received: from nez-perce.inria.fr (nez-perce.inria.fr [192.93.2.78]) by pauillac.inria.fr (8.7.6/8.7.3) with ESMTP id WAA19009 for ; Fri, 29 Aug 2003 22:17:21 +0200 (MET DST) Received: from badenpowell.cs.ubc.ca (badenpowell.cs.ubc.ca [142.103.6.71]) by nez-perce.inria.fr (8.11.1/8.11.1) with ESMTP id h7TKHJT06502 for ; Fri, 29 Aug 2003 22:17:19 +0200 (MET DST) Received: from cypress (cypress.cs.ubc.ca [142.103.11.23]) by badenpowell.cs.ubc.ca (8.12.8/8.12.9) with ESMTP id h7TKHHAV027504 for ; Fri, 29 Aug 2003 13:17:17 -0700 From: "Christopher Dutchyn" To: "CAML List" Subject: [Caml-list] Recursive Modules Date: Fri, 29 Aug 2003 13:17:17 -0700 Message-ID: <009e01c36e6a$8b2d81f0$170b678e@cs.ubc.ca> MIME-Version: 1.0 Content-Type: multipart/alternative; boundary="----=_NextPart_000_009F_01C36E2F.DECEA9F0" X-Priority: 3 (Normal) X-MSMail-Priority: Normal X-Mailer: Microsoft Outlook, Build 10.0.4510 X-MimeOLE: Produced By Microsoft MimeOLE V6.00.2800.1165 Importance: Normal X-Spam-Score: -0.8 BAYES_30,HTML_60_70 X-Scanned-By: MIMEDefang 2.35 X-Loop: caml-list@inria.fr X-Spam: no; 0.00; ubc:99 104,:01 val:01 val:01 functor:01 struct:01 functor:01 struct:01 char:01 char:01 recursion:01 104,:01 W9:99 W11:99 W11:99 Sender: owner-caml-list@pauillac.inria.fr Precedence: bulk This is a multi-part message in MIME format. ------=_NextPart_000_009F_01C36E2F.DECEA9F0 Content-Type: text/plain; charset="us-ascii" Content-Transfer-Encoding: 7bit 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 -> (* ::= 1_ [OneT _] | 2_? [TwoT _ ?] | *) 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")) ------=_NextPart_000_009F_01C36E2F.DECEA9F0 Content-Type: text/html; charset="us-ascii" Content-Transfer-Encoding: quoted-printable

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 =3D

  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 =3D

  functor (Above : LAYER) ->

  struct

    type topT =3D Above.topT

    type topV =3D Above.topV

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

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

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

 

    type t =3D = EmptyT           &= nbsp;  (* wouldn't revised syntax be nice *)

    type v =3D EmptyV

          =

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

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

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

  end

 

(* an intermediate level *)

module MakeMiddle =3D

  functor (Below : LAYER) ->

    functor (Above : LAYER) = ->

  struct

    type topT =3D Above.topT

    type topV =3D Above.topV

    let topInj =3D Above.topInj

    let topOp  =3D = Above.topOp

    let topExt =3D Above.topExt

 

    type t =3D

      | BelowT of = Below.t

      | OneT of char

      | TwoT of char * = topT

           = ;

    type v =3D

      | BelowV of = Below.v

      | StringV of = string

           = ;

    let inj =3D fun s ->           (* = <T> ::=3D 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 =3D

      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 =3D

      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 =3D

  functor (Below : LAYER) ->

  struct

    type t =3D Below.t

    type v =3D Below.v

          =

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

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

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

 

    type topT =3D t

    type topV =3D v

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

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

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

  end

 

(* simplest test *)

module rec B : LAYER =3D MakeBase(T)

       and T : LAYER =3D = MakeTop(B)

 

(* simple test *)

module rec B : LAYER =3D MakeBase(M)

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

      (* imagine there were more levels = *)

       and T : LAYER =3D = MakeTop(M);;

 

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

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

 

------=_NextPart_000_009F_01C36E2F.DECEA9F0-- ------------------- 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