caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] module typing issue
@ 2011-03-25  8:34 Joel Reymont
  2011-03-25  8:44 ` [Caml-list] " Joel Reymont
  0 siblings, 1 reply; 20+ messages in thread
From: Joel Reymont @ 2011-03-25  8:34 UTC (permalink / raw)
  To: caml-list

ocamlc x.ml 
File "x.ml", line 30, characters 16-28:
Error: Unbound value Rep.dispatch

Is there a way to make this work?

	Thanks, Joel

--- x.ml
module type Message = 
sig 
  type obj 
  type variant
  val make : unit -> obj
  (* encapsulate object in a variant type *)
  val convert : obj -> variant
  val print : obj -> unit
end

module type Request = 
sig 
  include Message
end

(* dispatches based on a request *)

module type Reply = functor (Req : Request) ->
sig 
  include Message
  val dispatch : Req.variant -> obj
end

module Server (Req : Request) (Rep : Reply) =
struct 
  let server = 
    while true do
      let req = Req.make () in
      let var = Req.convert req in
      let rep = Rep.dispatch var in
      Req.dump req;
      Rep.dump rep
    done
end

--------------------------------------------------------------------------
- for hire: mac osx device driver ninja, kernel extensions and usb drivers
---------------------+------------+---------------------------------------
http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
---------------------+------------+---------------------------------------




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

* [Caml-list] Re: module typing issue
  2011-03-25  8:34 [Caml-list] module typing issue Joel Reymont
@ 2011-03-25  8:44 ` Joel Reymont
  2011-03-25 14:17   ` Joel Reymont
  0 siblings, 1 reply; 20+ messages in thread
From: Joel Reymont @ 2011-03-25  8:44 UTC (permalink / raw)
  To: caml-list

Solved, thanks to the generous help of the #ocaml irc channel.

module type Message = 
sig 
  type obj 
  type variant
  val make : unit -> obj
  (* encapsulate object in a variant type *)
  val convert : obj -> variant
  val print : obj -> unit
end

module type Request = 
sig 
  include Message
end

(* dispatches based on a request *)

module type Reply = functor (Req : Request) ->
sig 
  include Message
  val dispatch : Req.variant -> obj
end

module Server (Req : Request) (REP : Reply) =
struct 
  module Rep = REP(Req)
  let server = 
    while true do
      let req = Req.make () in
      let var = Req.convert req in
      let rep = Rep.dispatch var in
      Req.print req;
      Rep.print rep
    done
end

--------------------------------------------------------------------------
- for hire: mac osx device driver ninja, kernel extensions and usb drivers
---------------------+------------+---------------------------------------
http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
---------------------+------------+---------------------------------------




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

* [Caml-list] Re: module typing issue
  2011-03-25  8:44 ` [Caml-list] " Joel Reymont
@ 2011-03-25 14:17   ` Joel Reymont
  2011-03-25 15:46     ` Andreas Rossberg
  0 siblings, 1 reply; 20+ messages in thread
From: Joel Reymont @ 2011-03-25 14:17 UTC (permalink / raw)
  To: caml-list

It appears that I spoke to early as I'm still having trouble with the implementation of my concept. 

What is it?

I'm working with ZeroMQ and Thrift. The latter generates messages using OCaml classes. 

I have request and reply messages in my system and replies are created (dispatched) based on their request pair.

A server should not have to know what messages it's dealing with.

I would like to wrap each message class in a variant, particularly helpful since some message classes are unions in the original Thrift DSL but the Thrift OCaml code generator implements them poorly.

Is my intent clear in the code below and if so how do I make it work?

	Thanks, Joel

--- error

File "x.ml", line 56, characters 26-35:
Error: Signature mismatch:
       Modules do not match:
         sig
           type obj = MyRequest.obj
           type variant = MyRequest.variant = A
           val make : unit -> int
           val convert : 'a -> variant
           val print : 'a -> unit
         end
       is not included in
         Request
       Values do not match:
         val make : unit -> int
       is not included in
         val make : unit -> obj

--- x.ml

module type Message = 
sig 
  type obj 
  type variant
  val make : unit -> obj
  (* encapsulate object in a variant type *)
  val convert : obj -> variant
  val print : obj -> unit
end

module type Request = 
sig 
  include Message
end

(* dispatches based on a request *)

module type Reply = functor (Req : Request) ->
sig 
  include Message
  val dispatch : Req.variant -> obj
end

module Server (Req : Request) (REP : Reply) =
struct 
  module Rep = REP(Req)
  let server = 
    while true do
      let req = Req.make () in
      let var = Req.convert req in
      let rep = Rep.dispatch var in
      Req.print req;
      Rep.print rep
    done
end

module MyRequest =
struct
  type obj = private int
  type variant = A
  let make () = 1
  let convert o = A
  let print o = ()
end

module MyReply = functor (Req: Request) ->
struct
  type obj = private int
  type variant = B
  let make () = 2
  let convert o = B
  let print o = ()
  let dispatch _ = B
end

module MyServer = Server (MyRequest) (MyReply)

--------------------------------------------------------------------------
- for hire: mac osx device driver ninja, kernel extensions and usb drivers
---------------------+------------+---------------------------------------
http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
---------------------+------------+---------------------------------------





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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 14:17   ` Joel Reymont
@ 2011-03-25 15:46     ` Andreas Rossberg
  2011-03-25 15:57       ` Joel Reymont
  2011-03-25 16:42       ` Guillaume Yziquel
  0 siblings, 2 replies; 20+ messages in thread
From: Andreas Rossberg @ 2011-03-25 15:46 UTC (permalink / raw)
  To: Joel Reymont; +Cc: caml-list

I don't think it ever makes sense to define private type abbreviations  
in a structure - they are intended for use in signatures. Just drop  
the private from your example.

/Andreas


On Mar 25, 2011, at 15.17 h, Joel Reymont wrote:

> It appears that I spoke to early as I'm still having trouble with  
> the implementation of my concept.
>
> What is it?
>
> I'm working with ZeroMQ and Thrift. The latter generates messages  
> using OCaml classes.
>
> I have request and reply messages in my system and replies are  
> created (dispatched) based on their request pair.
>
> A server should not have to know what messages it's dealing with.
>
> I would like to wrap each message class in a variant, particularly  
> helpful since some message classes are unions in the original Thrift  
> DSL but the Thrift OCaml code generator implements them poorly.
>
> Is my intent clear in the code below and if so how do I make it work?
>
> 	Thanks, Joel
>
> --- error
>
> File "x.ml", line 56, characters 26-35:
> Error: Signature mismatch:
>       Modules do not match:
>         sig
>           type obj = MyRequest.obj
>           type variant = MyRequest.variant = A
>           val make : unit -> int
>           val convert : 'a -> variant
>           val print : 'a -> unit
>         end
>       is not included in
>         Request
>       Values do not match:
>         val make : unit -> int
>       is not included in
>         val make : unit -> obj
>
> --- x.ml
>
> module type Message =
> sig
>  type obj
>  type variant
>  val make : unit -> obj
>  (* encapsulate object in a variant type *)
>  val convert : obj -> variant
>  val print : obj -> unit
> end
>
> module type Request =
> sig
>  include Message
> end
>
> (* dispatches based on a request *)
>
> module type Reply = functor (Req : Request) ->
> sig
>  include Message
>  val dispatch : Req.variant -> obj
> end
>
> module Server (Req : Request) (REP : Reply) =
> struct
>  module Rep = REP(Req)
>  let server =
>    while true do
>      let req = Req.make () in
>      let var = Req.convert req in
>      let rep = Rep.dispatch var in
>      Req.print req;
>      Rep.print rep
>    done
> end
>
> module MyRequest =
> struct
>  type obj = private int
>  type variant = A
>  let make () = 1
>  let convert o = A
>  let print o = ()
> end
>
> module MyReply = functor (Req: Request) ->
> struct
>  type obj = private int
>  type variant = B
>  let make () = 2
>  let convert o = B
>  let print o = ()
>  let dispatch _ = B
> end
>
> module MyServer = Server (MyRequest) (MyReply)
>
> --------------------------------------------------------------------------
> - for hire: mac osx device driver ninja, kernel extensions and usb  
> drivers
> ---------------------+------------ 
> +---------------------------------------
> http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
> ---------------------+------------ 
> +---------------------------------------
>
>
>
>
>
> -- 
> Caml-list mailing list.  Subscription management and archives:
> https://sympa-roc.inria.fr/wws/info/caml-list
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>


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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 15:46     ` Andreas Rossberg
@ 2011-03-25 15:57       ` Joel Reymont
  2011-03-25 16:04         ` Andreas Rossberg
  2011-03-25 16:42       ` Guillaume Yziquel
  1 sibling, 1 reply; 20+ messages in thread
From: Joel Reymont @ 2011-03-25 15:57 UTC (permalink / raw)
  To: Andreas Rossberg; +Cc: caml-list


On Mar 25, 2011, at 3:46 PM, Andreas Rossberg wrote:

> I don't think it ever makes sense to define private type abbreviations in a structure - they are intended for use in signatures. Just drop the private from your example.

This compiles but fails as soon as I try to replace dispatch in MyReply (bottom) with 

  let dispatch = function | A -> 1

This is obvious conceptually as MyReply doesn't know about the variant type defined in MyRequest. 

How do I make let MyReply know about it?

	Thanks, Joel

--- x.ml

module type Message = 
sig 
 type obj 
 type variant
 val make : unit -> obj
 (* encapsulate object in a variant type *)
 val convert : obj -> variant
 val print : obj -> unit
end

module type Request = 
sig 
 include Message
end

(* dispatches based on a request *)

module type Reply = functor (Req : Request) ->
sig 
 include Message
 val dispatch : Req.variant -> obj
end

module Server (Req : Request) (REP : Reply) =
struct 
 module Rep = REP(Req)
 let server = 
   while true do
     let req = Req.make () in
     let var = Req.convert req in
     let rep = Rep.dispatch var in
     Req.print req;
     Rep.print rep
   done
end

module MyRequest : Request =
struct
 type obj = int
 type variant = A
 let make () = 1
 let convert o = A
 let print o = ()
end

module MyReply : Reply = functor (Req: Request) ->
struct
 type obj = int
 type variant = B
 let make () = 2
 let convert o = B
 let print o = ()
 let dispatch _ = 2
end

module MyServer = Server (MyRequest) (MyReply)


--------------------------------------------------------------------------
- for hire: mac osx device driver ninja, kernel extensions and usb drivers
---------------------+------------+---------------------------------------
http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
---------------------+------------+---------------------------------------





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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 15:57       ` Joel Reymont
@ 2011-03-25 16:04         ` Andreas Rossberg
  0 siblings, 0 replies; 20+ messages in thread
From: Andreas Rossberg @ 2011-03-25 16:04 UTC (permalink / raw)
  To: Joel Reymont; +Cc: caml-list

Well, you have to make it transparent in the Request signature then.  
Then you should be able to say Req.A -> 1.

/Andreas


On Mar 25, 2011, at 16.57 h, Joel Reymont wrote:

>
> On Mar 25, 2011, at 3:46 PM, Andreas Rossberg wrote:
>
>> I don't think it ever makes sense to define private type  
>> abbreviations in a structure - they are intended for use in  
>> signatures. Just drop the private from your example.
>
> This compiles but fails as soon as I try to replace dispatch in  
> MyReply (bottom) with
>
>  let dispatch = function | A -> 1
>
> This is obvious conceptually as MyReply doesn't know about the  
> variant type defined in MyRequest.
>
> How do I make let MyReply know about it?
>
> 	Thanks, Joel
>
> --- x.ml
>
> module type Message =
> sig
> type obj
> type variant
> val make : unit -> obj
> (* encapsulate object in a variant type *)
> val convert : obj -> variant
> val print : obj -> unit
> end
>
> module type Request =
> sig
> include Message
> end
>
> (* dispatches based on a request *)
>
> module type Reply = functor (Req : Request) ->
> sig
> include Message
> val dispatch : Req.variant -> obj
> end
>
> module Server (Req : Request) (REP : Reply) =
> struct
> module Rep = REP(Req)
> let server =
>   while true do
>     let req = Req.make () in
>     let var = Req.convert req in
>     let rep = Rep.dispatch var in
>     Req.print req;
>     Rep.print rep
>   done
> end
>
> module MyRequest : Request =
> struct
> type obj = int
> type variant = A
> let make () = 1
> let convert o = A
> let print o = ()
> end
>
> module MyReply : Reply = functor (Req: Request) ->
> struct
> type obj = int
> type variant = B
> let make () = 2
> let convert o = B
> let print o = ()
> let dispatch _ = 2
> end
>
> module MyServer = Server (MyRequest) (MyReply)
>
>
> --------------------------------------------------------------------------
> - for hire: mac osx device driver ninja, kernel extensions and usb  
> drivers
> ---------------------+------------ 
> +---------------------------------------
> http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
> ---------------------+------------ 
> +---------------------------------------
>
>
>
>
>
> -- 
> Caml-list mailing list.  Subscription management and archives:
> https://sympa-roc.inria.fr/wws/info/caml-list
> Beginner's list: http://groups.yahoo.com/group/ocaml_beginners
> Bug reports: http://caml.inria.fr/bin/caml-bugs
>


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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 15:46     ` Andreas Rossberg
  2011-03-25 15:57       ` Joel Reymont
@ 2011-03-25 16:42       ` Guillaume Yziquel
  2011-03-25 16:59         ` Andreas Rossberg
  1 sibling, 1 reply; 20+ messages in thread
From: Guillaume Yziquel @ 2011-03-25 16:42 UTC (permalink / raw)
  To: Andreas Rossberg; +Cc: Joel Reymont, caml-list

Le Friday 25 Mar 2011 à 16:46:47 (+0100), Andreas Rossberg a écrit :
> I don't think it ever makes sense to define private type
> abbreviations in a structure - they are intended for use in
> signatures. Just drop the private from your example.
> 
> /Andreas

Uuh... It does make some sense, sometimes: In bindings, as output of
external stubs, and as phantom type arguments for instance... 'ever' is
somewhat too restrictive.

-- 
     Guillaume Yziquel


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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 16:42       ` Guillaume Yziquel
@ 2011-03-25 16:59         ` Andreas Rossberg
  2011-03-25 19:01           ` Guillaume Yziquel
  0 siblings, 1 reply; 20+ messages in thread
From: Andreas Rossberg @ 2011-03-25 16:59 UTC (permalink / raw)
  To: Guillaume Yziquel; +Cc: Joel Reymont, caml-list

On Mar 25, 2011, at 17.42 h, Guillaume Yziquel wrote:
> Le Friday 25 Mar 2011 à 16:46:47 (+0100), Andreas Rossberg a écrit :
>> I don't think it ever makes sense to define private type
>> abbreviations in a structure - they are intended for use in
>> signatures. Just drop the private from your example.
>
> Uuh... It does make some sense, sometimes: In bindings, as output of
> external stubs, and as phantom type arguments for instance... 'ever'  
> is
> somewhat too restrictive.

Well, fully abstract type definitions are sometimes handy for these  
purposes. But how do private type abbreviations help there?

/Andreas



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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 16:59         ` Andreas Rossberg
@ 2011-03-25 19:01           ` Guillaume Yziquel
  2011-03-25 19:13             ` Andreas Rossberg
  2011-03-28  7:53             ` Alain Frisch
  0 siblings, 2 replies; 20+ messages in thread
From: Guillaume Yziquel @ 2011-03-25 19:01 UTC (permalink / raw)
  To: Andreas Rossberg; +Cc: Joel Reymont, caml-list

Le Friday 25 Mar 2011 à 17:59:41 (+0100), Andreas Rossberg a écrit :
> On Mar 25, 2011, at 17.42 h, Guillaume Yziquel wrote:
> >Le Friday 25 Mar 2011 à 16:46:47 (+0100), Andreas Rossberg a écrit :
> >>I don't think it ever makes sense to define private type
> >>abbreviations in a structure - they are intended for use in
> >>signatures. Just drop the private from your example.
> >
> >Uuh... It does make some sense, sometimes: In bindings, as output of
> >external stubs, and as phantom type arguments for instance...
> >'ever' is
> >somewhat too restrictive.
> 
> Well, fully abstract type definitions are sometimes handy for these
> purposes. But how do private type abbreviations help there?
> 
> /Andreas

type error = private int

external get_error : unit -> error = "zzz"

You get some error level that you can pattern match as an int, and this
also enforces that all values of type error come from a call to
get_error. This is sometimes handy. Depends on your specific use cases
to know if it's really worth it however.

-- 
     Guillaume Yziquel


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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 19:01           ` Guillaume Yziquel
@ 2011-03-25 19:13             ` Andreas Rossberg
  2011-03-28  7:53             ` Alain Frisch
  1 sibling, 0 replies; 20+ messages in thread
From: Andreas Rossberg @ 2011-03-25 19:13 UTC (permalink / raw)
  To: Guillaume Yziquel; +Cc: Joel Reymont, caml-list

On Mar 25, 2011, at 20.01 h, Guillaume Yziquel wrote:
> Le Friday 25 Mar 2011 à 17:59:41 (+0100), Andreas Rossberg a écrit :
>> On Mar 25, 2011, at 17.42 h, Guillaume Yziquel wrote:
>>> Le Friday 25 Mar 2011 à 16:46:47 (+0100), Andreas Rossberg a écrit :
>>>> I don't think it ever makes sense to define private type
>>>> abbreviations in a structure - they are intended for use in
>>>> signatures. Just drop the private from your example.
>>>
>>> Uuh... It does make some sense, sometimes: In bindings, as output of
>>> external stubs, and as phantom type arguments for instance...
>>> 'ever' is
>>> somewhat too restrictive.
>>
>> Well, fully abstract type definitions are sometimes handy for these
>> purposes. But how do private type abbreviations help there?
>
> type error = private int
>
> external get_error : unit -> error = "zzz"
>
> You get some error level that you can pattern match as an int, and  
> this
> also enforces that all values of type error come from a call to
> get_error. This is sometimes handy. Depends on your specific use cases
> to know if it's really worth it however.

I see - I didn't think of such a case.

Thanks,
/Andreas



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

* Re: [Caml-list] Re: module typing issue
  2011-03-25 19:01           ` Guillaume Yziquel
  2011-03-25 19:13             ` Andreas Rossberg
@ 2011-03-28  7:53             ` Alain Frisch
  2011-03-28 10:33               ` Guillaume Yziquel
  2011-03-28 11:32               ` David Allsopp
  1 sibling, 2 replies; 20+ messages in thread
From: Alain Frisch @ 2011-03-28  7:53 UTC (permalink / raw)
  To: caml-list

On 03/25/2011 08:01 PM, Guillaume Yziquel wrote:
> type error = private int
>
> external get_error : unit ->  error = "zzz"
>
> You get some error level that you can pattern match as an int, and this
> also enforces that all values of type error come from a call to
> get_error.

You need to coerce explicitly from type error to type int (... :> int), 
so this is not really different from defining error as an abstract type 
and exposing a function error->int.

-- Alain

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

* Re: [Caml-list] Re: module typing issue
  2011-03-28  7:53             ` Alain Frisch
@ 2011-03-28 10:33               ` Guillaume Yziquel
  2011-03-28 11:29                 ` David Allsopp
  2011-03-28 11:32               ` David Allsopp
  1 sibling, 1 reply; 20+ messages in thread
From: Guillaume Yziquel @ 2011-03-28 10:33 UTC (permalink / raw)
  To: Alain Frisch; +Cc: caml-list

Le Monday 28 Mar 2011 à 09:53:52 (+0200), Alain Frisch a écrit :
> On 03/25/2011 08:01 PM, Guillaume Yziquel wrote:
> >type error = private int
> >
> >external get_error : unit ->  error = "zzz"
> >
> >You get some error level that you can pattern match as an int, and this
> >also enforces that all values of type error come from a call to
> >get_error.
> 
> You need to coerce explicitly from type error to type int (... :>
> int), so this is not really different from defining error as an
> abstract type and exposing a function error->int.
> 
> -- Alain

Yes, doesn't work for private ints. However, it works for stuff like
that, though it's not exactly the same thing as a 'private int':

# type t = private A | B;;
type t = private A | B
# let x : t = Obj.magic 0;;
val x : t = A
# match x with A -> true | _ -> false;;
- : bool = true
# A;;
Error: Cannot create values of the private type t

I thought it also worked on for ints, and in a sense, I'm surprised that
you cannot pattern match private ints as ints without a coercion.

So for enumerating errors coming from C stubs, you can still do it this
way.

-- 
     Guillaume Yziquel


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

* RE: [Caml-list] Re: module typing issue
  2011-03-28 10:33               ` Guillaume Yziquel
@ 2011-03-28 11:29                 ` David Allsopp
  2011-03-28 11:58                   ` Guillaume Yziquel
  0 siblings, 1 reply; 20+ messages in thread
From: David Allsopp @ 2011-03-28 11:29 UTC (permalink / raw)
  To: Guillaume Yziquel, Alain Frisch; +Cc: caml-list

Guillaume Yziquel wrote:
> Le Monday 28 Mar 2011 à 09:53:52 (+0200), Alain Frisch a écrit :
> > On 03/25/2011 08:01 PM, Guillaume Yziquel wrote:
> > >type error = private int
> > >
> > >external get_error : unit ->  error = "zzz"
> > >
> > >You get some error level that you can pattern match as an int, and
> > >this also enforces that all values of type error come from a call to
> > >get_error.
> >
> > You need to coerce explicitly from type error to type int (... :>
> > int), so this is not really different from defining error as an
> > abstract type and exposing a function error->int.
> >
> > -- Alain
> 
> Yes, doesn't work for private ints. However, it works for stuff like that,
> though it's not exactly the same thing as a 'private int':
> 
> # type t = private A | B;;
> type t = private A | B
> # let x : t = Obj.magic 0;;
> val x : t = A
> # match x with A -> true | _ -> false;;
> - : bool = true
> # A;;
> Error: Cannot create values of the private type t
> 
> I thought it also worked on for ints, and in a sense, I'm surprised that
> you cannot pattern match private ints as ints without a coercion.

I asked a similar question when private ints were introduced in OCaml 3.11 - full explanation from Jacques as to why in: https://sympa-roc.inria.fr/wws/arc/caml-list/2008-10/msg00375.html


David


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

* RE: [Caml-list] Re: module typing issue
  2011-03-28  7:53             ` Alain Frisch
  2011-03-28 10:33               ` Guillaume Yziquel
@ 2011-03-28 11:32               ` David Allsopp
  2011-03-28 12:02                 ` Guillaume Yziquel
  1 sibling, 1 reply; 20+ messages in thread
From: David Allsopp @ 2011-03-28 11:32 UTC (permalink / raw)
  To: Alain Frisch, caml-list

Alain Frisch wrote:
> On 03/25/2011 08:01 PM, Guillaume Yziquel wrote:
> > type error = private int
> >
> > external get_error : unit ->  error = "zzz"
> >
> > You get some error level that you can pattern match as an int, and
> > this also enforces that all values of type error come from a call to
> > get_error.
> 
> You need to coerce explicitly from type error to type int (... :> int), so
> this is not really different from defining error as an abstract type and
> exposing a function error->int.

Except that calling an identity function like that requires an optimising compiler to spot that the call is irrelevant and can be removed whereas the coercion is handled (and stripped out) during type inference. So although they're roughly equivalent, the private int approach is "neater" by several orders of magnitude (and as long as you only need an abbreviated coercion, a similar amount of keyboard-typing)!


David


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

* Re: [Caml-list] Re: module typing issue
  2011-03-28 11:29                 ` David Allsopp
@ 2011-03-28 11:58                   ` Guillaume Yziquel
  2011-03-28 12:11                     ` David Allsopp
  2011-03-28 12:23                     ` Alain Frisch
  0 siblings, 2 replies; 20+ messages in thread
From: Guillaume Yziquel @ 2011-03-28 11:58 UTC (permalink / raw)
  To: David Allsopp; +Cc: Alain Frisch, caml-list

Le Monday 28 Mar 2011 à 11:29:51 (+0000), David Allsopp a écrit :
> Guillaume Yziquel wrote:
> > Le Monday 28 Mar 2011 à 09:53:52 (+0200), Alain Frisch a écrit :
> > > On 03/25/2011 08:01 PM, Guillaume Yziquel wrote:
> > > >type error = private int
> > > >
> > > >external get_error : unit ->  error = "zzz"
> > > >
> > > >You get some error level that you can pattern match as an int, and
> > > >this also enforces that all values of type error come from a call to
> > > >get_error.
> > >
> > > You need to coerce explicitly from type error to type int (... :>
> > > int), so this is not really different from defining error as an
> > > abstract type and exposing a function error->int.
> > >
> > > -- Alain
> > 
> > Yes, doesn't work for private ints. However, it works for stuff like that,
> > though it's not exactly the same thing as a 'private int':
> > 
> > # type t = private A | B;;
> > type t = private A | B
> > # let x : t = Obj.magic 0;;
> > val x : t = A
> > # match x with A -> true | _ -> false;;
> > - : bool = true
> > # A;;
> > Error: Cannot create values of the private type t
> > 
> > I thought it also worked on for ints, and in a sense, I'm surprised that
> > you cannot pattern match private ints as ints without a coercion.
> 
> I asked a similar question when private ints were introduced in OCaml 3.11 - full explanation from Jacques as to why in: https://sympa-roc.inria.fr/wws/arc/caml-list/2008-10/msg00375.html

Yes an no. From a type inference perspective, that's right. However, you
can already do such pattern matching on private row types for variant
types.

module X : sig
	type t = private [< `A ]
	val x : t
end = struct
	type t = [ `A ]
	let x = `A
end

match X.x with `A -> ()

and the X.x is correctly unified with `A. So the type inference issue is
solved in this case.

What I'm wondering is why, when there is a known way to pattern match on
a given base type (like ints or strings), could this behaviour not be
extended. The work seems to have already been done for variant types.

While making type inference implicitly cross the border of type
coercion (as in your post) seems excessive, pattern-matching private
ints as you would for private row types seems OK to me.

Moreover, I somehow disagree with Jacques when he says:

>> type t = private int      (* can be used as though it were an int  *)
>> type t = very_private int (* requires a coercion to be used an int *)
>
> Explicit coercions in ocaml are completely unrelated to casts in C or
> Java, in that they only allow upcast (cast to a supertype). They are
> also completely erasable: they do not produce any code after type
> checking. So they are not there for any soundness reason, but just for
> type inference purposes. There would be no point at all in having two
> constructs: if the 1st one were possible, we wouldn't need the second.

There is a point:

The first 'private int' would simply be a way to forbid construction,
while allowing type-inference to go beyond the :> barrier.

The second 'very_private int' would be a way to block type inference.

Both would have their use cases.

-- 
     Guillaume Yziquel


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

* Re: [Caml-list] Re: module typing issue
  2011-03-28 11:32               ` David Allsopp
@ 2011-03-28 12:02                 ` Guillaume Yziquel
  0 siblings, 0 replies; 20+ messages in thread
From: Guillaume Yziquel @ 2011-03-28 12:02 UTC (permalink / raw)
  To: David Allsopp; +Cc: Alain Frisch, caml-list

Le Monday 28 Mar 2011 à 11:32:48 (+0000), David Allsopp a écrit :
> Alain Frisch wrote:
> > On 03/25/2011 08:01 PM, Guillaume Yziquel wrote:
> > > type error = private int
> > >
> > > external get_error : unit ->  error = "zzz"
> > >
> > > You get some error level that you can pattern match as an int, and
> > > this also enforces that all values of type error come from a call to
> > > get_error.
> > 
> > You need to coerce explicitly from type error to type int (... :> int), so
> > this is not really different from defining error as an abstract type and
> > exposing a function error->int.
> 
> Except that calling an identity function like that requires an optimising compiler to spot that the call is irrelevant and can be removed whereas the coercion is handled (and stripped out) during type inference. So although they're roughly equivalent, the private int approach is "neater" by several orders of magnitude (and as long as you only need an abbreviated coercion, a similar amount of keyboard-typing)!
> 
> David

True. But it seems that for most OCaml people, the weirdness of ':>'
isn't worth the few CPU cycles. Haven't seen much code using :>.
external "%identity" seems to be favoured.

-- 
     Guillaume Yziquel


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

* RE: [Caml-list] Re: module typing issue
  2011-03-28 11:58                   ` Guillaume Yziquel
@ 2011-03-28 12:11                     ` David Allsopp
  2011-03-28 12:29                       ` Guillaume Yziquel
  2011-03-28 12:23                     ` Alain Frisch
  1 sibling, 1 reply; 20+ messages in thread
From: David Allsopp @ 2011-03-28 12:11 UTC (permalink / raw)
  To: 'Guillaume Yziquel'; +Cc: 'Alain Frisch', 'caml-list'

Guillaume Yziquel wrote:
> Le Monday 28 Mar 2011 à 11:29:51 (+0000), David Allsopp a écrit :
> > Guillaume Yziquel wrote:
> > > Yes, doesn't work for private ints. However, it works for stuff like
> > > that, though it's not exactly the same thing as a 'private int':
> > >
> > > # type t = private A | B;;
> > > type t = private A | B
> > > # let x : t = Obj.magic 0;;
> > > val x : t = A
> > > # match x with A -> true | _ -> false;;
> > > - : bool = true
> > > # A;;
> > > Error: Cannot create values of the private type t
> > >
> > > I thought it also worked on for ints, and in a sense, I'm surprised
> > > that you cannot pattern match private ints as ints without a
> coercion.
> >
> > I asked a similar question when private ints were introduced in OCaml
> > 3.11 - full explanation from Jacques as to why in:
> > https://sympa-roc.inria.fr/wws/arc/caml-list/2008-10/msg00375.html
> 
> Yes an no. From a type inference perspective, that's right. However, you
> can already do such pattern matching on private row types for variant
> types.
> 
> module X : sig
> 	type t = private [< `A ]
> 	val x : t
> end = struct
> 	type t = [ `A ]
> 	let x = `A
> end
> 
> match X.x with `A -> ()
> 
> and the X.x is correctly unified with `A. So the type inference issue is
> solved in this case.

There's nothing special needed to do this - the type of `A is [> `A ] so that unifies with type X.t without any special handling at all.

> What I'm wondering is why, when there is a known way to pattern match on
> a given base type (like ints or strings), could this behaviour not be
> extended. The work seems to have already been done for variant types.

There's no extra work been done here - it's just normal type inference (i.e. there are no special cases that have been added for this to work). I'm not completely convinced by the argument against inferring coercions in the type checker, but arguing with Jacques is usually a route to being proven comprehensively wrong :o)

> While making type inference implicitly cross the border of type coercion
> (as in your post) seems excessive, pattern-matching private ints as you
> would for private row types seems OK to me.

There's nothing special going on for private row types - it's simply that the constants (variant or polymorphic variants) can only have only one type where integer constants can have more than one type (sort of - it's the wrong terminology really but from the type inference perspective, it's what's happening).


David


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

* Re: [Caml-list] Re: module typing issue
  2011-03-28 11:58                   ` Guillaume Yziquel
  2011-03-28 12:11                     ` David Allsopp
@ 2011-03-28 12:23                     ` Alain Frisch
  2011-03-28 12:39                       ` Guillaume Yziquel
  1 sibling, 1 reply; 20+ messages in thread
From: Alain Frisch @ 2011-03-28 12:23 UTC (permalink / raw)
  To: Guillaume Yziquel; +Cc: David Allsopp, caml-list

On 03/28/2011 01:58 PM, Guillaume Yziquel wrote:
> Yes an no. From a type inference perspective, that's right. However, you
> can already do such pattern matching on private row types for variant
> types.
>
> module X : sig
> 	type t = private [<  `A ]
> 	val x : t
> end = struct
> 	type t = [ `A ]
> 	let x = `A
> end
>
> match X.x with `A ->  ()
>
> and the X.x is correctly unified with `A. So the type inference issue is
> solved in this case.

Private row types are not the same as private type abbreviations. The 
syntax might be a source of confusion here, but the keyword "private" 
really means three different things:

- Private type declarations: constructors/labels are available for 
deconstructing values (pattern matching, dot notation), not for building 
values.

- Private type abbreviations (where the abbreviated type is not an 
object type or a polymorphic variant type): the behavior is very much 
the same as an abstract type, except that the abbreviation is a subtype 
of the abbreviated type (and the compiler can use the concrete type to 
choose a runtime representation of -- e.g. for records of floats -- and 
to trigger optimizations).

- Private row types: you can think of the 'private' annotation as a way 
to name (as an abstract type) the implicit row type variable of the 
abbreviated type. There is no hiding as for type abbreviation and no 
access control as for private type declarations.


The syntax for private type abbreviation and private row types is the 
same; they are distinguished only in the type-checker. As far as I know, 
there is no way to create a private type abbreviation on a object or 
variant type.



Alain

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

* Re: [Caml-list] Re: module typing issue
  2011-03-28 12:11                     ` David Allsopp
@ 2011-03-28 12:29                       ` Guillaume Yziquel
  0 siblings, 0 replies; 20+ messages in thread
From: Guillaume Yziquel @ 2011-03-28 12:29 UTC (permalink / raw)
  To: David Allsopp; +Cc: 'Alain Frisch', 'caml-list'

Le Monday 28 Mar 2011 à 12:11:47 (+0000), David Allsopp a écrit :
> Guillaume Yziquel wrote:
> > Le Monday 28 Mar 2011 à 11:29:51 (+0000), David Allsopp a écrit :
> > > Guillaume Yziquel wrote:
> > > > Yes, doesn't work for private ints. However, it works for stuff like
> > > > that, though it's not exactly the same thing as a 'private int':
> > > >
> > > > # type t = private A | B;;
> > > > type t = private A | B
> > > > # let x : t = Obj.magic 0;;
> > > > val x : t = A
> > > > # match x with A -> true | _ -> false;;
> > > > - : bool = true
> > > > # A;;
> > > > Error: Cannot create values of the private type t
> > > >
> > > > I thought it also worked on for ints, and in a sense, I'm surprised
> > > > that you cannot pattern match private ints as ints without a
> > coercion.
> > >
> > > I asked a similar question when private ints were introduced in OCaml
> > > 3.11 - full explanation from Jacques as to why in:
> > > https://sympa-roc.inria.fr/wws/arc/caml-list/2008-10/msg00375.html
> > 
> > Yes an no. From a type inference perspective, that's right. However, you
> > can already do such pattern matching on private row types for variant
> > types.
> > 
> > module X : sig
> > 	type t = private [< `A ]
> > 	val x : t
> > end = struct
> > 	type t = [ `A ]
> > 	let x = `A
> > end
> > 
> > match X.x with `A -> ()
> > 
> > and the X.x is correctly unified with `A. So the type inference issue is
> > solved in this case.
> 
> There's nothing special needed to do this - the type of `A is [> `A ] so that unifies with type X.t without any special handling at all.

OK, there's no special handling.

Type of `A is [> `A] and type of X.x is t = private [< `A ].

But that's hardly different from:

Type of 1 is int and type of X.x is t = private int.

What I meant is that the fact that 'function `A -> ()' gets properly
unified with X.x which is of type 't = private [< `A]' is a solved type
inference issue. Because of what private row types mean: you can feed a
private row type to a function accepting the correct polymorphic variant
types.

It isn't the case for private ints. It's not a private row type, but
while I understand why type inference is screened by the private
keyword, I do not really understand why we couldn't pattern-match it as
an int. Except for the fact that you cannot feed a private int to a
function accepting an int for type inference reasons (opposite behaviour
than for private row types).

> > What I'm wondering is why, when there is a known way to pattern match on
> > a given base type (like ints or strings), could this behaviour not be
> > extended. The work seems to have already been done for variant types.
> 
> There's no extra work been done here - it's just normal type inference (i.e. there are no special cases that have been added for this to work). I'm not completely convinced by the argument against inferring coercions in the type checker, but arguing with Jacques is usually a route to being proven comprehensively wrong :o)

I wouldn't complain about that. I like the type hackery flexibility this
distinction brings.

> > While making type inference implicitly cross the border of type coercion
> > (as in your post) seems excessive, pattern-matching private ints as you
> > would for private row types seems OK to me.
> 
> There's nothing special going on for private row types - it's simply that the constants (variant or polymorphic variants) can only have only one type where integer constants can have more than one type (sort of - it's the wrong terminology really but from the type inference perspective, it's what's happening).

I do not understand the 'integer constants can have more than one type'
part of your sentence.

> David

-- 
     Guillaume Yziquel


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

* Re: [Caml-list] Re: module typing issue
  2011-03-28 12:23                     ` Alain Frisch
@ 2011-03-28 12:39                       ` Guillaume Yziquel
  0 siblings, 0 replies; 20+ messages in thread
From: Guillaume Yziquel @ 2011-03-28 12:39 UTC (permalink / raw)
  To: Alain Frisch; +Cc: David Allsopp, caml-list

Le Monday 28 Mar 2011 à 14:23:50 (+0200), Alain Frisch a écrit :
> On 03/28/2011 01:58 PM, Guillaume Yziquel wrote:
> >Yes an no. From a type inference perspective, that's right. However, you
> >can already do such pattern matching on private row types for variant
> >types.
> >
> >module X : sig
> >	type t = private [<  `A ]
> >	val x : t
> >end = struct
> >	type t = [ `A ]
> >	let x = `A
> >end
> >
> >match X.x with `A ->  ()
> >
> >and the X.x is correctly unified with `A. So the type inference issue is
> >solved in this case.
> 
> Private row types are not the same as private type abbreviations.
> The syntax might be a source of confusion here, but the keyword
> "private" really means three different things:

Yes. I just find it too bad that the distinction between these three
different 'private' types is so neat.

> - Private type declarations: constructors/labels are available for
> deconstructing values (pattern matching, dot notation), not for
> building values.

That's where I'd like type t = private int to stand at times. Having it
as a private type abbreviation is sometimes too strong.

> - Private type abbreviations (where the abbreviated type is not an
> object type or a polymorphic variant type): the behavior is very
> much the same as an abstract type, except that the abbreviation is a
> subtype of the abbreviated type (and the compiler can use the
> concrete type to choose a runtime representation of -- e.g. for
> records of floats -- and to trigger optimizations).

Yes. I'm just sad that when you have predefined pattern-matching way to
deal with a type (such as strings or ints), these private type
abbreviations drop the deconstructing features of private type
declarations.

> - Private row types: you can think of the 'private' annotation as a
> way to name (as an abstract type) the implicit row type variable of
> the abbreviated type. There is no hiding as for type abbreviation
> and no access control as for private type declarations.

Yes. And in a signature, you can replace them with the 'with type :='
construct. This is again different, and also handy.

> The syntax for private type abbreviation and private row types is
> the same; they are distinguished only in the type-checker. As far as
> I know, there is no way to create a private type abbreviation on a
> object or variant type.

Except than aliasing the object or variant type to another type and
doing a private type abbreviation on the alias.

> Alain

-- 
     Guillaume Yziquel


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

end of thread, other threads:[~2011-03-28 12:39 UTC | newest]

Thread overview: 20+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-03-25  8:34 [Caml-list] module typing issue Joel Reymont
2011-03-25  8:44 ` [Caml-list] " Joel Reymont
2011-03-25 14:17   ` Joel Reymont
2011-03-25 15:46     ` Andreas Rossberg
2011-03-25 15:57       ` Joel Reymont
2011-03-25 16:04         ` Andreas Rossberg
2011-03-25 16:42       ` Guillaume Yziquel
2011-03-25 16:59         ` Andreas Rossberg
2011-03-25 19:01           ` Guillaume Yziquel
2011-03-25 19:13             ` Andreas Rossberg
2011-03-28  7:53             ` Alain Frisch
2011-03-28 10:33               ` Guillaume Yziquel
2011-03-28 11:29                 ` David Allsopp
2011-03-28 11:58                   ` Guillaume Yziquel
2011-03-28 12:11                     ` David Allsopp
2011-03-28 12:29                       ` Guillaume Yziquel
2011-03-28 12:23                     ` Alain Frisch
2011-03-28 12:39                       ` Guillaume Yziquel
2011-03-28 11:32               ` David Allsopp
2011-03-28 12:02                 ` 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).