caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* Cannot safely evaluate the definition of the recursively-defined module
@ 2009-03-18 12:08 Hugo Ferreira
  2009-03-18 12:48 ` [Caml-list] " Alp Mestan
  2009-03-19  4:01 ` Michael Furr
  0 siblings, 2 replies; 8+ messages in thread
From: Hugo Ferreira @ 2009-03-18 12:08 UTC (permalink / raw)
  To: caml-list

Hello,

I hope this is not a beginners questions.
I am trying to reuse code via functors,
however I am getting the following error:

Cannot safely evaluate the definition of the recursively-defined module
(refers to "AA.empty" when implemented as a constant value)

I circumvented the problem by not using a
constant value but a function instead. As I
understand it this may cause run-time errors.
My question is: is their any way to make the
following example work.

Specifically, for the example below is their
any way of indicating to the compiler that
AA.q = ASet.t ?

TIA,
Hugo F.

module type AA =
   sig
     type q
     type t = string

     val compare: t -> t -> int
     val add: t -> q -> q
     val empty: unit -> q
   end

module rec A1 : AA
                  = struct
                      type q = ASet.t
                      type t = string

                      let compare s1 s2 = Pervasives.compare s1 s2
                      let add e s = ASet.add e s
                      let empty _ = ASet.empty
                    end
         and ASet : Set.S with type elt = A1.t
                  = Set.Make(A1)

module type Wrap_A =
   sig
     type t
     type q

     val init: q
     val add: t -> q -> q
   end

module Make_A (An_A : AA) : Wrap_A
  =
  struct
     type t = An_A.t
     type q = An_A.q

     (*let init = ASet.empty*)
     let init = An_A.empty ()
     let add t q = An_A.add t q
end

module Wrap_A1 = Make_A( A1 )


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

* Re: [Caml-list] Cannot safely evaluate the definition of the  recursively-defined module
  2009-03-18 12:08 Cannot safely evaluate the definition of the recursively-defined module Hugo Ferreira
@ 2009-03-18 12:48 ` Alp Mestan
  2009-03-18 15:56   ` Hugo Ferreira
  2009-03-19  4:01 ` Michael Furr
  1 sibling, 1 reply; 8+ messages in thread
From: Alp Mestan @ 2009-03-18 12:48 UTC (permalink / raw)
  To: caml-list

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

Hi,

replacing :
module rec A1 : AA
                = struct
                    type q = ASet.t
                    type t = string

with :
module rec A1 : AA with type q = ASet.t, type t = string

should be okay. Shouldn't it ?

On Wed, Mar 18, 2009 at 1:08 PM, Hugo Ferreira <hmf@inescporto.pt> wrote:

> Hello,
>
> I hope this is not a beginners questions.
> I am trying to reuse code via functors,
> however I am getting the following error:
>
> Cannot safely evaluate the definition of the recursively-defined module
> (refers to "AA.empty" when implemented as a constant value)
>
> I circumvented the problem by not using a
> constant value but a function instead. As I
> understand it this may cause run-time errors.
> My question is: is their any way to make the
> following example work.
>
> Specifically, for the example below is their
> any way of indicating to the compiler that
> AA.q = ASet.t ?
>
> TIA,
> Hugo F.
>
> module type AA =
>  sig
>    type q
>    type t = string
>
>    val compare: t -> t -> int
>    val add: t -> q -> q
>    val empty: unit -> q
>  end
>
> module rec A1 : AA
>                 = struct
>                     type q = ASet.t
>                     type t = string
>
>                     let compare s1 s2 = Pervasives.compare s1 s2
>                     let add e s = ASet.add e s
>                     let empty _ = ASet.empty
>                   end
>        and ASet : Set.S with type elt = A1.t
>                 = Set.Make(A1)
>
> module type Wrap_A =
>  sig
>    type t
>    type q
>
>    val init: q
>    val add: t -> q -> q
>  end
>
> module Make_A (An_A : AA) : Wrap_A
>  =
>  struct
>    type t = An_A.t
>    type q = An_A.q
>
>    (*let init = ASet.empty*)
>    let init = An_A.empty ()
>    let add t q = An_A.add t q
> end
>
> module Wrap_A1 = Make_A( A1 )
>
> _______________________________________________
> 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
>



-- 
Alp Mestan
In charge of the C++ section on Developpez.com.

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

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

* Re: [Caml-list] Cannot safely evaluate the definition of the  recursively-defined module
  2009-03-18 12:48 ` [Caml-list] " Alp Mestan
@ 2009-03-18 15:56   ` Hugo Ferreira
  2009-03-18 16:49     ` Julien SIGNOLES
  0 siblings, 1 reply; 8+ messages in thread
From: Hugo Ferreira @ 2009-03-18 15:56 UTC (permalink / raw)
  To: Alp Mestan; +Cc: caml-list

Alp Mestan wrote:
> Hi,
> 
> replacing :
> module rec A1 : AA
>                 = struct
>                     type q = ASet.t
>                     type t = string
> 
> with :
> module rec A1 : AA with type q = ASet.t, type t = string
> 
> should be okay. Shouldn't it ?
> 

You mean?

module rec A1 : AA with type q = ASet.t
                    with type t = string
                  = struct
                      type q = ASet.t
                      type t = string

                      let compare s1 s2 = Pervasives.compare s1 s2
                      let add e s = ASet.add e s
                      let empty = ASet.empty
                    end
         and ASet : Set.S with type elt = A1.t
                  = Set.Make(A1)

No. It doens't work.

R,
Hugo F.


> On Wed, Mar 18, 2009 at 1:08 PM, Hugo Ferreira <hmf@inescporto.pt 
> <mailto:hmf@inescporto.pt>> wrote:
> 
>     Hello,
> 
>     I hope this is not a beginners questions.
>     I am trying to reuse code via functors,
>     however I am getting the following error:
> 
>     Cannot safely evaluate the definition of the recursively-defined module
>     (refers to "AA.empty" when implemented as a constant value)
> 
>     I circumvented the problem by not using a
>     constant value but a function instead. As I
>     understand it this may cause run-time errors.
>     My question is: is their any way to make the
>     following example work.
> 
>     Specifically, for the example below is their
>     any way of indicating to the compiler that
>     AA.q = ASet.t ?
> 
>     TIA,
>     Hugo F.
> 
>     module type AA =
>      sig
>        type q
>        type t = string
> 
>        val compare: t -> t -> int
>        val add: t -> q -> q
>        val empty: unit -> q
>      end
> 
>     module rec A1 : AA
>                     = struct
>                         type q = ASet.t
>                         type t = string
> 
>                         let compare s1 s2 = Pervasives.compare s1 s2
>                         let add e s = ASet.add e s
>                         let empty _ = ASet.empty
>                       end
>            and ASet : Set.S with type elt = A1.t
>                     = Set.Make(A1)
> 
>     module type Wrap_A =
>      sig
>        type t
>        type q
> 
>        val init: q
>        val add: t -> q -> q
>      end
> 
>     module Make_A (An_A : AA) : Wrap_A
>      =
>      struct
>        type t = An_A.t
>        type q = An_A.q
> 
>        (*let init = ASet.empty*)
>        let init = An_A.empty ()
>        let add t q = An_A.add t q
>     end
> 
>     module Wrap_A1 = Make_A( A1 )
> 
>     _______________________________________________
>     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
> 
> 
> 
> 
> -- 
> Alp Mestan
> In charge of the C++ section on Developpez.com.
> 
> 
> ------------------------------------------------------------------------
> 
> _______________________________________________
> 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] 8+ messages in thread

* Re: [Caml-list] Cannot safely evaluate the definition of the recursively-defined module
  2009-03-18 15:56   ` Hugo Ferreira
@ 2009-03-18 16:49     ` Julien SIGNOLES
  2009-03-18 17:01       ` Hugo Ferreira
  0 siblings, 1 reply; 8+ messages in thread
From: Julien SIGNOLES @ 2009-03-18 16:49 UTC (permalink / raw)
  To: Hugo Ferreira; +Cc: Alp Mestan, caml-list

Hello,

> module rec A1 : AA with type q = ASet.t
>                     with type t = string
>                   = struct
>                       type q = ASet.t
>                       type t = string
> 
>                       let compare s1 s2 = Pervasives.compare s1 s2
>                       let add e s = ASet.add e s
>                       let empty = ASet.empty
>                     end
>          and ASet : Set.S with type elt = A1.t
>                   = Set.Make(A1)
> 
> No. It doens't work.

> >     however I am getting the following error:
> > 
> >     Cannot safely evaluate the definition of the recursively-defined module
> >     (refers to "AA.empty" when implemented as a constant value)

That is consistent with the behaviour specified in Section 7.8 of the
reference manual [1]. Both A1 and ASet are not safe according to the
definition given in this section. So a type error occurs because ocaml
does know that the program won't be safely evaluated.

For additional details, you could refer to the Xavier Leroy's notes
describing the implementation of recursive modules in ocaml [2].

[1] http://caml.inria.fr/pub/docs/manual-ocaml/manual021.html#toc75
[2] http://caml.inria.fr/pub/papers/xleroy-recursive_modules-03.pdf

Hope this helps,
Julien Signoles
-- 
Researcher-engineer
CEA LIST, Software Reliability Lab
91191 Gif-Sur-Yvette Cedex
tel:(+33)1.69.08.71.83  fax:(+33)1.69.08.83.95  Julien.Signoles@cea.fr


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

* Re: [Caml-list] Cannot safely evaluate the definition of the recursively-defined module
  2009-03-18 16:49     ` Julien SIGNOLES
@ 2009-03-18 17:01       ` Hugo Ferreira
  0 siblings, 0 replies; 8+ messages in thread
From: Hugo Ferreira @ 2009-03-18 17:01 UTC (permalink / raw)
  To: Julien SIGNOLES; +Cc: caml-list

Julien SIGNOLES wrote:
> Hello,
> 
>> module rec A1 : AA with type q = ASet.t
>>                     with type t = string
>>                   = struct
>>                       type q = ASet.t
>>                       type t = string
>>
>>                       let compare s1 s2 = Pervasives.compare s1 s2
>>                       let add e s = ASet.add e s
>>                       let empty = ASet.empty
>>                     end
>>          and ASet : Set.S with type elt = A1.t
>>                   = Set.Make(A1)
>>
>> No. It doens't work.
> 
>>>     however I am getting the following error:
>>>
>>>     Cannot safely evaluate the definition of the recursively-defined module
>>>     (refers to "AA.empty" when implemented as a constant value)
> 
> That is consistent with the behaviour specified in Section 7.8 of the
> reference manual [1]. Both A1 and ASet are not safe according to the
> definition given in this section. So a type error occurs because ocaml
> does know that the program won't be safely evaluated.
> 
> For additional details, you could refer to the Xavier Leroy's notes
> describing the implementation of recursive modules in ocaml [2].
> 
> [1] http://caml.inria.fr/pub/docs/manual-ocaml/manual021.html#toc75
> [2] http://caml.inria.fr/pub/papers/xleroy-recursive_modules-03.pdf
> 

Read the manual.
I'll take a look at [2]

Thank you.
Hugo F.


> Hope this helps,
> Julien Signoles


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

* Re: [Caml-list] Cannot safely evaluate the definition of the recursively-defined module
  2009-03-18 12:08 Cannot safely evaluate the definition of the recursively-defined module Hugo Ferreira
  2009-03-18 12:48 ` [Caml-list] " Alp Mestan
@ 2009-03-19  4:01 ` Michael Furr
  2009-03-19  8:09   ` Hugo Ferreira
  1 sibling, 1 reply; 8+ messages in thread
From: Michael Furr @ 2009-03-19  4:01 UTC (permalink / raw)
  To: caml-list


On Wed, 18 Mar 2009, Hugo Ferreira wrote:

> I hope this is not a beginners questions.
> I am trying to reuse code via functors,
> however I am getting the following error:
>
> Cannot safely evaluate the definition of the recursively-defined module
> (refers to "AA.empty" when implemented as a constant value)
>
> I circumvented the problem by not using a
> constant value but a function instead. As I
> understand it this may cause run-time errors.
> My question is: is their any way to make the
> following example work.

If you only need to store a constant value in the module, then you can get 
around the restriction by splitting the module into a (recursively-)safe 
module, and an extension that adds the constants.  Here is a slightly 
modified version of your code showing the transformation:

----
module type AA_Safe =
sig
   type q
   type t = string

   val compare: t -> t -> int
   val add: t -> q -> q
   (* omit empty here, since it is not "safe" *)
end

module rec A1 : AA_Safe with type q = ASet.t  =
struct
   type q = ASet.t
   type t = string
   let compare s1 s2 = Pervasives.compare s1 s2
   let add e s = ASet.add e s
end
and ASet : Set.S with type elt = A1.t = Set.Make(A1)

(* now create the full module *)
module type AA = sig
   include AA_Safe
   val empty: q
end

module A2 : AA = struct
   include A1
   let empty = ASet.empty
end

module type Wrap_A =
sig
   type t
   type q

   val init: q
   val add: t -> q -> q
end
module Make_A (An_A : AA) : Wrap_A
   =
struct
   type t = An_A.t
   type q = An_A.q

   (*let init = ASet.empty*)
   let init = An_A.empty
   let add t q = An_A.add t q
end

module Wrap_A1 = Make_A( A2 )
----

Cheers,
-Mike


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

* Re: [Caml-list] Cannot safely evaluate the definition of the recursively-defined module
  2009-03-19  4:01 ` Michael Furr
@ 2009-03-19  8:09   ` Hugo Ferreira
  2009-09-25 20:06     ` Guillaume Yziquel
  0 siblings, 1 reply; 8+ messages in thread
From: Hugo Ferreira @ 2009-03-19  8:09 UTC (permalink / raw)
  To: caml-list

Michael Furr wrote:
> 
> On Wed, 18 Mar 2009, Hugo Ferreira wrote:
> 
>> I hope this is not a beginners questions.
>> I am trying to reuse code via functors,
>> however I am getting the following error:
>>
>> Cannot safely evaluate the definition of the recursively-defined module
>> (refers to "AA.empty" when implemented as a constant value)
>>
>> I circumvented the problem by not using a
>> constant value but a function instead. As I
>> understand it this may cause run-time errors.
>> My question is: is their any way to make the
>> following example work.
> 
> If you only need to store a constant value in the module, then you can 
> get around the restriction by splitting the module into a 
> (recursively-)safe module, and an extension that adds the constants.  
> Here is a slightly modified version of your code showing the 
> transformation:
> 

Ok, I understand this.

Thanks,
Hugo F.


> ----
> module type AA_Safe =
> sig
>   type q
>   type t = string
> 
>   val compare: t -> t -> int
>   val add: t -> q -> q
>   (* omit empty here, since it is not "safe" *)
> end
> 
> module rec A1 : AA_Safe with type q = ASet.t  =
> struct
>   type q = ASet.t
>   type t = string
>   let compare s1 s2 = Pervasives.compare s1 s2
>   let add e s = ASet.add e s
> end
> and ASet : Set.S with type elt = A1.t = Set.Make(A1)
> 
> (* now create the full module *)
> module type AA = sig
>   include AA_Safe
>   val empty: q
> end
> 
> module A2 : AA = struct
>   include A1
>   let empty = ASet.empty
> end
> 
> module type Wrap_A =
> sig
>   type t
>   type q
> 
>   val init: q
>   val add: t -> q -> q
> end
> module Make_A (An_A : AA) : Wrap_A
>   =
> struct
>   type t = An_A.t
>   type q = An_A.q
> 
>   (*let init = ASet.empty*)
>   let init = An_A.empty
>   let add t q = An_A.add t q
> end
> 
> module Wrap_A1 = Make_A( A2 )
> ----
> 
> Cheers,
> -Mike
> 
> _______________________________________________
> 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] 8+ messages in thread

* Re: [Caml-list] Cannot safely evaluate the definition of the recursively-defined module
  2009-03-19  8:09   ` Hugo Ferreira
@ 2009-09-25 20:06     ` Guillaume Yziquel
  0 siblings, 0 replies; 8+ messages in thread
From: Guillaume Yziquel @ 2009-09-25 20:06 UTC (permalink / raw)
  To: Hugo Ferreira; +Cc: caml-list

Hello.

Sorry for reviving this short thread. I have the same error message, but 
I really do not understand what "safety" means in this context.

If I specify the signature of the recursive module, shouldn't the type 
checker work out right out of the box?

Sorry, but I'm a bit confused. You'll find the recursive submodule that 
I'm having problems with below Hugo's email.

All the best,

Guillaume Yziquel.

Hugo Ferreira a écrit :
> Michael Furr wrote:
>>
>> On Wed, 18 Mar 2009, Hugo Ferreira wrote:
>>
>>> I hope this is not a beginners questions.
>>> I am trying to reuse code via functors,
>>> however I am getting the following error:
>>>
>>> Cannot safely evaluate the definition of the recursively-defined module
>>> (refers to "AA.empty" when implemented as a constant value)
>>>
>>> I circumvented the problem by not using a
>>> constant value but a function instead. As I
>>> understand it this may cause run-time errors.
>>> My question is: is their any way to make the
>>> following example work.
>>
>> If you only need to store a constant value in the module, then you can 
>> get around the restriction by splitting the module into a 
>> (recursively-)safe module, and an extension that adds the constants.  
>> Here is a slightly modified version of your code showing the 
>> transformation:
>>
> 
> Ok, I understand this.
> 
> Thanks,
> Hugo F.
> 
> 
>> ----
>> module type AA_Safe =
>> sig
>>   type q
>>   type t = string
>>
>>   val compare: t -> t -> int
>>   val add: t -> q -> q
>>   (* omit empty here, since it is not "safe" *)
>> end
>>
>> module rec A1 : AA_Safe with type q = ASet.t  =
>> struct
>>   type q = ASet.t
>>   type t = string
>>   let compare s1 s2 = Pervasives.compare s1 s2
>>   let add e s = ASet.add e s
>> end
>> and ASet : Set.S with type elt = A1.t = Set.Make(A1)
>>
>> (* now create the full module *)
>> module type AA = sig
>>   include AA_Safe
>>   val empty: q
>> end
>>
>> module A2 : AA = struct
>>   include A1
>>   let empty = ASet.empty
>> end
>>
>> module type Wrap_A =
>> sig
>>   type t
>>   type q
>>
>>   val init: q
>>   val add: t -> q -> q
>> end
>> module Make_A (An_A : AA) : Wrap_A
>>   =
>> struct
>>   type t = An_A.t
>>   type q = An_A.q
>>
>>   (*let init = ASet.empty*)
>>   let init = An_A.empty
>>   let add t q = An_A.add t q
>> end
>>
>> module Wrap_A1 = Make_A( A2 )
>> ----
>>
>> Cheers,
>> -Mike

Here's my recursive submodule:

> module rec Registry : sig
> 
>   val new_status_signal : t -> status React.signal
>   val registry : (t * status React.signal) list React.signal
>   val status_of_agent : t -> status
> 
> end = struct 
> 
>   let new_status_signal agent = React.S.fold
>     begin function current_status -> function
>       | AgentPresent (agent_of_signal, status_information) ->
>           begin match agent = agent_of_signal with
>           | false -> current_status
>           | true -> status_information
>           end
>       | AsteriskStatus (Asterisk.Active activity) ->
>           let agent_ip = match Registry.status_of_agent agent with
>           | Present ip -> Some ip
>           | Online (ip, _) -> Some ip
>           | _ -> None in
>           begin match agent_ip with None -> current_status
>           | Some ip -> current_status (* To do... *)
>           end
>       | AsteriskStatus _ -> current_status
>     end Offline (React.E.select [
>       agent_status_notification;
>       (React.E.map begin function s -> AsteriskStatus s end
>         (Asterisk.server # status_change))
>     ])
> 
>   let registry = React.S.fold
>     begin fun live_registry new_agent -> new_agent::live_registry end
>     begin Lwt_main.run (persistent_registry >>= Ocsipersist.get >>=
>       begin function a_list -> Lwt.return (List.map
>         begin function (nom, prenom) ->
>           let a = {nom = nom; prenom = prenom} in
>           a, (Registry.new_status_signal a)
>         end a_list)
>       end)
>     end
>     begin React.E.map
>       begin function agent -> agent, (Registry.new_status_signal agent) end
>       adding_to_registry
>     end
> 
>   let status_of_agent agent =
>     try React.S.value (List.assoc agent (React.S.value Registry.registry))
>     with Not_found -> raise (invalid_arg ("Agent.status_of_agent: "^agent.prenom^" "^agent.nom))
> 
> end


-- 
      Guillaume Yziquel
http://yziquel.homelinux.org/


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

end of thread, other threads:[~2009-09-25 20:11 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-03-18 12:08 Cannot safely evaluate the definition of the recursively-defined module Hugo Ferreira
2009-03-18 12:48 ` [Caml-list] " Alp Mestan
2009-03-18 15:56   ` Hugo Ferreira
2009-03-18 16:49     ` Julien SIGNOLES
2009-03-18 17:01       ` Hugo Ferreira
2009-03-19  4:01 ` Michael Furr
2009-03-19  8:09   ` Hugo Ferreira
2009-09-25 20:06     ` Guillaume Yziquel

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