caml-list - the Caml user's mailing list
 help / color / mirror / Atom feed
* [Caml-list] do i need a private row type?
@ 2011-05-15 13:56 Joel Reymont
  2011-05-16  6:24 ` Goswin von Brederlow
  2011-05-19  4:15 ` Pedro Borges
  0 siblings, 2 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-15 13:56 UTC (permalink / raw)
  To: caml-list

https://github.com/wagerlabs/ocaml-zmq/blob/master/src/ZMQ.ml

Looking at the Poll module at the bottom and the definition of poll_item as

  type 'a poll_item = ('a Socket.t * event_mask)

I would like to be able to put different 'a in the same poll_item array. 

This is not possible as written, e.g. 

Error: This expression has type
         ZMQ.Socket.pub ZMQ.Socket.t * ZMQ.Poll.event_mask
       but an expression was expected of type
         ZMQ.Socket.pull ZMQ.Socket.t * ZMQ.Poll.event_mask

How do I type poll_item and poll_item array so that the array is polymorphic with respect to 'a?

Does the definition of Socket a the top of ZMQ.ml need to be changed to make this possible?

	Thanks, Joel

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

* Re: [Caml-list] do i need a private row type?
  2011-05-15 13:56 [Caml-list] do i need a private row type? Joel Reymont
@ 2011-05-16  6:24 ` Goswin von Brederlow
  2011-05-16  7:07   ` Gabriel Scherer
  2011-05-19  4:15 ` Pedro Borges
  1 sibling, 1 reply; 18+ messages in thread
From: Goswin von Brederlow @ 2011-05-16  6:24 UTC (permalink / raw)
  To: Joel Reymont; +Cc: caml-list

Joel Reymont <joelr1@gmail.com> writes:

> https://github.com/wagerlabs/ocaml-zmq/blob/master/src/ZMQ.ml
>
> Looking at the Poll module at the bottom and the definition of poll_item as
>
>   type 'a poll_item = ('a Socket.t * event_mask)
>
> I would like to be able to put different 'a in the same poll_item array. 
>
> This is not possible as written, e.g. 
>
> Error: This expression has type
>          ZMQ.Socket.pub ZMQ.Socket.t * ZMQ.Poll.event_mask
>        but an expression was expected of type
>          ZMQ.Socket.pull ZMQ.Socket.t * ZMQ.Poll.event_mask
>
> How do I type poll_item and poll_item array so that the array is polymorphic with respect to 'a?
>
> Does the definition of Socket a the top of ZMQ.ml need to be changed to make this possible?
>
> 	Thanks, Joel

How clean do you want this to be? Lets go with easy and dirty.

First thing is that if you have different 'a poll_items then you need to
include a callback that accepts a matching 'a Socket.t. E.g.:

type 'a poll_item = ('a Socket.t * event_mask * ('a Socket.t -> event_mask -> unit))

Then you can make an unit poll_item array and use

let set i (item : 'a poll_item) =
    array.[i] <- Obj.magic item

let call i =
    let (sock, mask, fn) = array.[i]
    in
    fn sock mask

The important part here is that you ensure the 'a Socket.t is only
accessed through the callback. Only that will have the right type.


If you want to make it clean then you need a 2 layer approach with 2
records and 'a. 'a -> 'b style types. I can't remember how to do this
from memory but search the list archive for something like universal
container. I've asked the same a few years back.

MfG
        Goswin

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  6:24 ` Goswin von Brederlow
@ 2011-05-16  7:07   ` Gabriel Scherer
  2011-05-16  8:57     ` Joel Reymont
                       ` (7 more replies)
  0 siblings, 8 replies; 18+ messages in thread
From: Gabriel Scherer @ 2011-05-16  7:07 UTC (permalink / raw)
  To: Goswin von Brederlow; +Cc: Joel Reymont, caml-list

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

On Mon, May 16, 2011 at 8:24 AM, Goswin von Brederlow <goswin-v-b@web.de>wrote:
>
> First thing is that if you have different 'a poll_items then you need to
> include a callback that accepts a matching 'a Socket.t. E.g.:
>
> type 'a poll_item = ('a Socket.t * event_mask * ('a Socket.t -> event_mask
> -> unit))
>
> Then you can make an unit poll_item array and use
>
> let set i (item : 'a poll_item) =
>    array.[i] <- Obj.magic item
>
> let call i =
>    let (sock, mask, fn) = array.[i]
>    in
>    fn sock mask
>
> The important part here is that you ensure the 'a Socket.t is only
> accessed through the callback. Only that will have the right type.
>

If "call" is the only thing you wish to do on your array, you don't need
such an ugly solution. "sock" and "mask" being constants for a given item,
you can simply capture them in a closure.

  type poll_item_thunk = unit -> unit

  let set i (socket, event_mask, callback) =
    array.(i) <- (fun () -> callback socket event_mask);

  let call i = array.(i) ()


There is no reasonable answer to "how do I force OCaml into breaking type
safety ?". Joel must have an use case in mind which is actually type-safe;
maybe it's only the callback as you demonstrated (I fail to see its
usefulness, but I don't know anything about ZeroMQ), maybe it's something a
bit more complicated. But we won't be able to give him a satisfying solution
unless he describes more precisely what this type-safe use is.

The most general solution, as you alluded, is to use existential types. This
can be done by an encoding into universal types (this is the "2 records"
approach), or using first-class modules and abstract types.

Joel, may you be more explicit as to what you want to do with those
"poll_item" array. More precisely, how do you plan to *use* the data in the
array?

Joel Reymont <joelr1@gmail.com> writes:
>
> > https://github.com/wagerlabs/ocaml-zmq/blob/master/src/ZMQ.ml
> >
> > Looking at the Poll module at the bottom and the definition of poll_item
> as
> >
> >   type 'a poll_item = ('a Socket.t * event_mask)
> >
> > I would like to be able to put different 'a in the same poll_item array.
> >
> > This is not possible as written, e.g.
> >
> > Error: This expression has type
> >          ZMQ.Socket.pub ZMQ.Socket.t * ZMQ.Poll.event_mask
> >        but an expression was expected of type
> >          ZMQ.Socket.pull ZMQ.Socket.t * ZMQ.Poll.event_mask
> >
> > How do I type poll_item and poll_item array so that the array is
> polymorphic with respect to 'a?
> >
> > Does the definition of Socket a the top of ZMQ.ml need to be changed to
> make this possible?
> >
> >       Thanks, Joel
>
> How clean do you want this to be? Lets go with easy and dirty.
>
> First thing is that if you have different 'a poll_items then you need to
> include a callback that accepts a matching 'a Socket.t. E.g.:
>
> type 'a poll_item = ('a Socket.t * event_mask * ('a Socket.t -> event_mask
> -> unit))
>
> Then you can make an unit poll_item array and use
>
> let set i (item : 'a poll_item) =
>    array.[i] <- Obj.magic item
>
> let call i =
>    let (sock, mask, fn) = array.[i]
>    in
>    fn sock mask
>
> The important part here is that you ensure the 'a Socket.t is only
> accessed through the callback. Only that will have the right type.
>
>
> If you want to make it clean then you need a 2 layer approach with 2
> records and 'a. 'a -> 'b style types. I can't remember how to do this
> from memory but search the list archive for something like universal
> container. I've asked the same a few years back.
>
> MfG
>         Goswin
>
> --
> 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
>
>

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

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
@ 2011-05-16  8:57     ` Joel Reymont
  2011-05-16  9:31     ` Joel Reymont
                       ` (6 subsequent siblings)
  7 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16  8:57 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list


On May 16, 2011, at 9:07 AM, Gabriel Scherer wrote:

> If "call" is the only thing you wish to do on your array, you don't need such an ugly solution. "sock" and "mask" being constants for a given item, you can simply capture them in a closure.

All I want to do (and must do) is call "poll" on the poll item set. 

There are no callbacks since I'm checking to see what socket has data and then issuing a "receive data" call on that socket. 

> Joel must have an use case in mind which is actually type-safe; maybe it's only the callback as you demonstrated (I fail to see its usefulness, but I don't know anything about ZeroMQ), maybe it's something a bit more complicated. But we won't be able to give him a satisfying solution unless he describes more precisely what this type-safe use is.

My type safe use is exactly what Unix select does, i.e. determine what socket has data available. 

> Joel, may you be more explicit as to what you want to do with those "poll_item" array. More precisely, how do you plan to *use* the data in the array?

I need to check the mask for each item in the returned array to see what socket has data. Then I need to read data from the socket. 

I suspect I'll need to change how the socket is typed to convert to a variant of socket types which can be stored easily into a poll set. I really don't know why Socket is typed as it is, maybe Pedro (the creator of ocaml-zmq) can explain.

	Thanks, Joel

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
  2011-05-16  8:57     ` Joel Reymont
@ 2011-05-16  9:31     ` Joel Reymont
  2011-05-16  9:58     ` Joel Reymont
                       ` (5 subsequent siblings)
  7 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16  9:31 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list

The socket is typed the way it is because of these two functions:

  val subscribe : sub t -> string -> unit
  val unsubscribe : sub t -> string -> unit

Meaning that you should only be able to use subscribe and unsubscribe on sockets created with type sub Socket.t ('a = sub).

This reminds me an example with phantom types I saw somewhere, possibly in the context of Xen and its OCaml bindings. 

This is where you can only use certain functions that access memory on memory that has been initialized. 

Maybe phantom types are called for here.

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
  2011-05-16  8:57     ` Joel Reymont
  2011-05-16  9:31     ` Joel Reymont
@ 2011-05-16  9:58     ` Joel Reymont
  2011-05-16 10:05     ` Joel Reymont
                       ` (4 subsequent siblings)
  7 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16  9:58 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list

What about this?

It almost works, e.g. 

File "ZMQ.mli", line 125, characters 7-99:
Error: A type variable is unbound in this type declaration.
In type
  ([> `Dealer | `Pair | `Pub | `Pull | `Push | `Rep | `Req | `Router | `Sub ]
   as 'a)
  Socket.t * event_mask the variable 'a is unbound

I marked line 125 below.

	Thanks, Joel

---

module Socket :
sig
  type 'a t
  type 'a kind

  val pair   : [`Pair] kind
  val pub    : [`Pub] kind
  val sub    : [`Sub] kind
  val req    : [`Req] kind
  val rep    : [`Rep] kind
  val dealer : [`Dealer] kind
  val router : [`Router] kind
  val pull   : [`Pull] kind
  val push   : [`Push] kind

  ...

  val subscribe : [`Sub] t -> string -> unit
  val unsubscribe : [`Sub] t -> string -> unit

end

module Device :
sig

  val streamer  : [`Pull] Socket.t -> [`Push] Socket.t -> unit
  val forwarder : [`Sub] Socket.t -> [`Pub] Socket.t -> unit
  val queue     : [`Router] Socket.t -> [`Dealer] Socket.t -> unit

end

module Poll :
sig

  type t

  type event_mask = In | Out | In_out

  type poll_socket = [>`Pair|`Pub|`Sub|`Req|`Rep|`Dealer|`Router|`Pull|`Push] Socket.t (* <---- line 125 *)
  type poll_item = (poll_socket * event_mask)

  val of_poll_items : poll_item array -> t

  val poll : ?timeout: int -> t -> poll_item array

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
                       ` (2 preceding siblings ...)
  2011-05-16  9:58     ` Joel Reymont
@ 2011-05-16 10:05     ` Joel Reymont
  2011-05-16 12:02     ` Joel Reymont
                       ` (3 subsequent siblings)
  7 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16 10:05 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list

Typing it this way 

module Poll :
sig
  type t

  type poll_socket = [`Pair|`Pub|`Sub|`Req|`Rep|`Dealer|`Router|`Pull|`Push] Socket.t
  type poll_item = (poll_socket * event_mask)

  val of_poll_items : poll_item array -> t
  ...

end

I get a different error when using of_poll_items with two different socket types:

File "src/dawn.ml", line 73, characters 44-52:
Error: This expression has type [ `Pub ] ZMQ.Socket.t * ZMQ.Poll.event_mask
       but an expression was expected of type
         [ `Pull ] ZMQ.Socket.t * ZMQ.Poll.event_mask
       These two variant types have no intersection

This is the difference between 

type poll_socket = [>...] Socket.t

and 

type poll_socket = [...] Socket.t

What is the proper way to type this?

	Thanks, Joel

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
                       ` (3 preceding siblings ...)
  2011-05-16 10:05     ` Joel Reymont
@ 2011-05-16 12:02     ` Joel Reymont
  2011-05-16 12:32     ` Joel Reymont
                       ` (2 subsequent siblings)
  7 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16 12:02 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list

Here's the problem reduced to a single file. 

Two files, actually, the first one showing my intended use.

The error is 

File "zmq.ml", line 72, characters 7-86:
Error: A type variable is unbound in this type declaration.
In type
  ([< `Dealer | `Pair | `Pub | `Pull | `Push | `Rep | `Req | `Router | `Sub ]
   as 'a)
  Socket.t the variable 'a is unbound

	Thanks, Joel

P.S. 

--- foo.ml

#use "topfind";;

#require "zmq";;

open ZMQ;;
open ZMQ.Socket;;
open ZMQ.Poll;;

let context = init ();;

let pub_endpoint = "tcp://127.0.0.1:9997";;
let pull_endpoint = "tcp://127.0.0.1:9996";;

let pub = 
  let sock = Socket.create context pub in
  connect sock pub_endpoint;
  sock;;

let pull = 
  let sock = Socket.create context pull in
  connect sock pull_endpoint;
  sock;;

let timeout = 1000000 (* 1s *);;

let poll_set = of_poll_items [| pull, In; pub, Out |] in
match poll ~timeout poll_set with
  | [| pull, In |] ->
    let msg = recv pull in 
    ()
  | _ ->
    ()
;;

--- zmq.ml

module Socket :
sig
  type 'a t
  type 'a kind

  val pair   : [`Pair] kind
  val pub    : [`Pub] kind
  val sub    : [`Sub] kind
  val req    : [`Req] kind
  val rep    : [`Rep] kind
  val dealer : [`Dealer] kind
  val router : [`Router] kind
  val pull   : [`Pull] kind
  val push   : [`Push] kind

  val create : 'a kind -> 'a t

  val connect : 'a t -> string -> unit
  val bind : 'a t -> string -> unit

  val subscribe : [`Sub] t -> string -> unit
  val unsubscribe : [`Sub] t -> string -> unit

end = struct

  type 'a t = int

  type 'a kind = int

  let pair   = 0
  let pub    = 1
  let sub    = 2
  let req    = 3
  let rep    = 4
  let dealer = 5
  let router = 6
  let pull   = 7
  let push   = 8

  let create kind = 1

  let connect sock endpoint = ()
  let bind sock endpoint = ()

  let subscribe socket new_subscription = ()
  let unsubscribe socket old_subscription = ()

end

module Device :
sig

  val streamer  : [`Pull] Socket.t -> [`Push] Socket.t -> unit
  val forwarder : [`Sub] Socket.t -> [`Pub] Socket.t -> unit
  val queue     : [`Router] Socket.t -> [`Dealer] Socket.t -> unit

end = struct

  let streamer sock1 sock2 = ()
  let forwarder sock1 sock2 = ()
  let queue sock1 sock2 = ()

end

module Poll :
sig

  type t

  type event_mask = In | Out | In_out

  type poll_socket = [<`Pair|`Pub|`Sub|`Req|`Rep|`Dealer|`Router|`Pull|`Push] Socket.t
  type poll_item = (poll_socket * event_mask)

  val of_poll_items : poll_item array -> t

end = struct

  type t = string

  let of_poll_items items = "create poll set"

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
                       ` (4 preceding siblings ...)
  2011-05-16 12:02     ` Joel Reymont
@ 2011-05-16 12:32     ` Joel Reymont
  2011-05-16 13:02     ` Joel Reymont
  2011-05-17  4:26     ` Goswin von Brederlow
  7 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16 12:32 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list

Everything in a single file is here:

https://gist.github.com/974321

Can repost to the list if needed.

Compiling gives the error.

File "zmq.ml", line 108, characters 42-50:
Error: This expression has type [ `Pub ] Socket.t * Poll.event_mask
       but an expression was expected of type
         [ `Pull ] Socket.t * Poll.event_mask
       These two variant types have no intersection

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
                       ` (5 preceding siblings ...)
  2011-05-16 12:32     ` Joel Reymont
@ 2011-05-16 13:02     ` Joel Reymont
  2011-05-16 13:39       ` Gabriel Scherer
  2011-05-17  4:26     ` Goswin von Brederlow
  7 siblings, 1 reply; 18+ messages in thread
From: Joel Reymont @ 2011-05-16 13:02 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list

Issue solved thanks to Anil Madhavapeddy.

val pair   : [>`Pair] kind
val pub    : [>`Pub] kind

etc.

and then 

type poll_socket = [`Pair|`Pub|`Sub|`Req|`Rep|`Dealer|`Router|`Pull|`Push] Socket.t
type poll_item = (poll_socket * event_mask)

val of_poll_items : poll_item array -> t

This does it!

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16 13:02     ` Joel Reymont
@ 2011-05-16 13:39       ` Gabriel Scherer
  2011-05-16 13:46         ` Joel Reymont
  2011-05-16 14:02         ` Joel Reymont
  0 siblings, 2 replies; 18+ messages in thread
From: Gabriel Scherer @ 2011-05-16 13:39 UTC (permalink / raw)
  To: Joel Reymont; +Cc: Goswin von Brederlow, caml-list

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

The problem with this solution, if I understand it correctly, is that it
amounts to losing type information. Your values begin with some type
information attached to them, that allows more fine-grained typing of some
information (subscription), but then you coerce them into a big magma of
"everything" to put them in the array, and the type information is lost.
When you get back an element of this array, you don't know anymore if it was
a `Pair or a `Sub for example. You probably won't be able to use the more
restrictive operations of your interface.

A solution to this problem would be to tag each item with its provenance
type, so that you can regain fine-grained types dynamically :

type any_poll =
  | Pair of pair poll
  | Sub of sub poll
  | ...

Then, given an array of `any_poll` elements, you can pattern match and, if
it's a `Sub`, you have a `sub poll` available. I think this is more precise
than your current solution.
More generally, I don't think the polymorphic variants bring anything more
that what you could have with simple abstract types here. For example to
coerce everything to a common type with the `pair poll`, `sub poll` solution
you could define a `any` abstract datatype and provide a `val lose_type_info
: 'a poll -> any poll` function. Unless I'm mistaken, this is equivalent to
your current solution, and shields you of any superfluous polymorphic
variant oddities.

On Mon, May 16, 2011 at 3:02 PM, Joel Reymont <joelr1@gmail.com> wrote:

> Issue solved thanks to Anil Madhavapeddy.
>
> val pair   : [>`Pair] kind
> val pub    : [>`Pub] kind
>
> etc.
>
> and then
>
> type poll_socket = [`Pair|`Pub|`Sub|`Req|`Rep|`Dealer|`Router|`Pull|`Push]
> Socket.t
> type poll_item = (poll_socket * event_mask)
>
> val of_poll_items : poll_item array -> t
>
> This does it!
>
> --------------------------------------------------------------------------
> - for hire: mac osx device driver ninja, kernel extensions and usb drivers
> ---------------------+------------+---------------------------------------
> http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
> ---------------------+------------+---------------------------------------
>
>
>
>

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

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16 13:39       ` Gabriel Scherer
@ 2011-05-16 13:46         ` Joel Reymont
  2011-05-16 14:02         ` Joel Reymont
  1 sibling, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16 13:46 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list

Gabriel,

On May 16, 2011, at 3:39 PM, Gabriel Scherer wrote:

> A solution to this problem would be to tag each item with its provenance type, so that you can regain fine-grained types dynamically :
> 
> type any_poll =
>   | Pair of pair poll
>   | Sub of sub poll
>   | ...

I do agree with you on the losing of types.

I cannot have a pair poll, sub poll, etc. because poll takes in the array of 'any socket' types. 

I wonder if the right solution here is -not- to return the socket from the call to poll but just return the flags. 

You can then get hold of the socket itself in the original poll set and that socket would have the original type information.

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16 13:39       ` Gabriel Scherer
  2011-05-16 13:46         ` Joel Reymont
@ 2011-05-16 14:02         ` Joel Reymont
  2011-05-16 14:06           ` Gabriel Scherer
  1 sibling, 1 reply; 18+ messages in thread
From: Joel Reymont @ 2011-05-16 14:02 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, caml-list


On May 16, 2011, at 3:39 PM, Gabriel Scherer wrote:

> More generally, I don't think the polymorphic variants bring anything more that what you could have with simple abstract types here.

How would I accomplish this with simple abstract types?

For example, how do I do this?

module Device :
sig

  val streamer  : [`Pull] Socket.t -> [`Push] Socket.t -> unit
  val forwarder : [`Sub] Socket.t -> [`Pub] Socket.t -> unit
  val queue     : [`Router] Socket.t -> [`Dealer] Socket.t -> unit

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16 14:02         ` Joel Reymont
@ 2011-05-16 14:06           ` Gabriel Scherer
  2011-05-16 14:08             ` Joel Reymont
  0 siblings, 1 reply; 18+ messages in thread
From: Gabriel Scherer @ 2011-05-16 14:06 UTC (permalink / raw)
  To: Joel Reymont; +Cc: caml-list

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

module Device : sig
  type pull
  type push
  type pub
  type sub
  type router
  type dealer
  val streamer  : pull Socket.t -> push Socket.t -> unit
  val forwarder : sub Socket.t -> pub Socket.t -> unit
  val queue     : router Socket.t -> dealer Socket.t -> unit
end

On Mon, May 16, 2011 at 4:02 PM, Joel Reymont <joelr1@gmail.com> wrote:

>
> On May 16, 2011, at 3:39 PM, Gabriel Scherer wrote:
>
> > More generally, I don't think the polymorphic variants bring anything
> more that what you could have with simple abstract types here.
>
> How would I accomplish this with simple abstract types?
>
> For example, how do I do this?
>
> module Device :
> sig
>
>  val streamer  : [`Pull] Socket.t -> [`Push] Socket.t -> unit
>  val forwarder : [`Sub] Socket.t -> [`Pub] Socket.t -> unit
>  val queue     : [`Router] Socket.t -> [`Dealer] Socket.t -> unit
>
> end
>
> --------------------------------------------------------------------------
> - for hire: mac osx device driver ninja, kernel extensions and usb drivers
> ---------------------+------------+---------------------------------------
> http://wagerlabs.com | @wagerlabs | http://www.linkedin.com/in/joelreymont
> ---------------------+------------+---------------------------------------
>
>
>
>

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

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16 14:06           ` Gabriel Scherer
@ 2011-05-16 14:08             ` Joel Reymont
  0 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-16 14:08 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: caml-list


On May 16, 2011, at 4:06 PM, Gabriel Scherer wrote:

> module Device : sig
>   type pull
>   type push
>   type pub
>   type sub
>   type router
>   type dealer
>   val streamer  : pull Socket.t -> push Socket.t -> unit
>   val forwarder : sub Socket.t -> pub Socket.t -> unit
>   val queue     : router Socket.t -> dealer Socket.t -> unit
> end

This is very much how it was before and then I could not implement the poll

module Poll :
sig

  type t

  type event_mask = In | Out | In_out
  type poll_socket = [`Pair|`Pub|`Sub|`Req|`Rep|`Dealer|`Router|`Pull|`Push] Socket.t
  type poll_item = (poll_socket * event_mask)

  val of_poll_items : poll_item array -> t
  val poll : ?timeout: int -> t -> poll_item array

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

* Re: [Caml-list] do i need a private row type?
  2011-05-16  7:07   ` Gabriel Scherer
                       ` (6 preceding siblings ...)
  2011-05-16 13:02     ` Joel Reymont
@ 2011-05-17  4:26     ` Goswin von Brederlow
  7 siblings, 0 replies; 18+ messages in thread
From: Goswin von Brederlow @ 2011-05-17  4:26 UTC (permalink / raw)
  To: Gabriel Scherer; +Cc: Goswin von Brederlow, Joel Reymont, caml-list

Gabriel Scherer <gabriel.scherer@gmail.com> writes:

> On Mon, May 16, 2011 at 8:24 AM, Goswin von Brederlow <goswin-v-b@web.de>
> wrote:
>
>     First thing is that if you have different 'a poll_items then you need to
>     include a callback that accepts a matching 'a Socket.t. E.g.:
>
>     type 'a poll_item = ('a Socket.t * event_mask * ('a Socket.t -> event_mask
>     -> unit))
>
>     Then you can make an unit poll_item array and use
>
>     let set i (item : 'a poll_item) =
>        array.[i] <- Obj.magic item
>
>     let call i =
>        let (sock, mask, fn) = array.[i]
>        in
>        fn sock mask
>
>     The important part here is that you ensure the 'a Socket.t is only
>     accessed through the callback. Only that will have the right type.
>
>
> If "call" is the only thing you wish to do on your array, you don't need such
> an ugly solution. "sock" and "mask" being constants for a given item, you can
> simply capture them in a closure.
>
>   type poll_item_thunk = unit -> unit
>
>   let set i (socket, event_mask, callback) =
>     array.(i) <- (fun () -> callback socket event_mask);
>
>   let call i = array.(i) ()
>
>
> There is no reasonable answer to "how do I force OCaml into breaking type
> safety ?". Joel must have an use case in mind which is actually type-safe;
> maybe it's only the callback as you demonstrated (I fail to see its usefulness,
> but I don't know anything about ZeroMQ), maybe it's something a bit more
> complicated. But we won't be able to give him a satisfying solution unless he
> describes more precisely what this type-safe use is.

This is still type safe given sufficient encapsulation in a module so it
can't be abused. But as I said, it is the dirty solution, like anything
requireing Obj.magic is. And you are right, if all you have is one
callback then a simple closure is better.

But you also need access to the Unix.file_descr underlying the socket to
select on it. And then you need a second callback to handle error
conditions. And then your socket probably has some state and things
become mutable and closures quickly become ugly and use up a lot more
memory if you have many sockets.

> The most general solution, as you alluded, is to use existential types. This
> can be done by an encoding into universal types (this is the "2 records"
> approach), or using first-class modules and abstract types.

I haven't tried this with first-class modules and the better support for
abstract types yet. But I would be interested to see in how they improve
on the 2 records solution.

Another thing I didn't mention is to use objects. This use case is
actually the poster child for objects with virtual functions.

> Joel, may you be more explicit as to what you want to do with those "poll_item"
> array. More precisely, how do you plan to *use* the data in the array?

MfG
        Goswin

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

* Re: [Caml-list] do i need a private row type?
  2011-05-15 13:56 [Caml-list] do i need a private row type? Joel Reymont
  2011-05-16  6:24 ` Goswin von Brederlow
@ 2011-05-19  4:15 ` Pedro Borges
  2011-05-19  7:33   ` Joel Reymont
  1 sibling, 1 reply; 18+ messages in thread
From: Pedro Borges @ 2011-05-19  4:15 UTC (permalink / raw)
  To: Joel Reymont; +Cc: caml-list

Hi Joel,

the current version is a bit ahead of your version I think.

you can cast any socket type to (generic Socket.t) so you can have
different socket types inside the poll.

This weekend I'm going to look at the bindings again. They need a serious fix.


On Sun, May 15, 2011 at 2:56 PM, Joel Reymont <joelr1@gmail.com> wrote:
> https://github.com/wagerlabs/ocaml-zmq/blob/master/src/ZMQ.ml
>
> Looking at the Poll module at the bottom and the definition of poll_item as
>
>  type 'a poll_item = ('a Socket.t * event_mask)
>
> I would like to be able to put different 'a in the same poll_item array.
>
> This is not possible as written, e.g.
>
> Error: This expression has type
>         ZMQ.Socket.pub ZMQ.Socket.t * ZMQ.Poll.event_mask
>       but an expression was expected of type
>         ZMQ.Socket.pull ZMQ.Socket.t * ZMQ.Poll.event_mask
>
> How do I type poll_item and poll_item array so that the array is polymorphic with respect to 'a?
>
> Does the definition of Socket a the top of ZMQ.ml need to be changed to make this possible?
>
>        Thanks, Joel
>
> --------------------------------------------------------------------------
> - 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] 18+ messages in thread

* Re: [Caml-list] do i need a private row type?
  2011-05-19  4:15 ` Pedro Borges
@ 2011-05-19  7:33   ` Joel Reymont
  0 siblings, 0 replies; 18+ messages in thread
From: Joel Reymont @ 2011-05-19  7:33 UTC (permalink / raw)
  To: Pedro Borges; +Cc: caml-list


On May 19, 2011, at 6:15 AM, Pedro Borges wrote:

> the current version is a bit ahead of your version I think.

Maybe, maybe not :-). 

> you can cast any socket type to (generic Socket.t) so you can have
> different socket types inside the poll.

I don't need to cast in my new phantom types version, I can just stick the various 
sockets into the poll mask, regardless of type. There's no type loss information either
because I don't return sockets, I return flags, e.g.

module Poll : sig

  type t

  type poll_event = In | Out | In_out
  type poll_socket = [`Pair|`Pub|`Sub|`Req|`Rep|`Dealer|`Router|`Pull|`Push] Socket.t
  type poll_mask = (poll_socket * poll_event)

  val mask_of : poll_mask array -> t
  val poll : ?timeout: int -> t -> poll_event option array

end

This also does not rely on OCaml figuring out that the socket I returned is the same
as the socket I put in. I know that the returned flags in position N apply 
to the socket in the same position in the poll mask.

> This weekend I'm going to look at the bindings again. They need a serious fix.

I have fixed the bindings enough for our ad serving use. Please take a look at 
the batch of commits in your pull queue on Github.

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

end of thread, other threads:[~2011-05-19  7:33 UTC | newest]

Thread overview: 18+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-05-15 13:56 [Caml-list] do i need a private row type? Joel Reymont
2011-05-16  6:24 ` Goswin von Brederlow
2011-05-16  7:07   ` Gabriel Scherer
2011-05-16  8:57     ` Joel Reymont
2011-05-16  9:31     ` Joel Reymont
2011-05-16  9:58     ` Joel Reymont
2011-05-16 10:05     ` Joel Reymont
2011-05-16 12:02     ` Joel Reymont
2011-05-16 12:32     ` Joel Reymont
2011-05-16 13:02     ` Joel Reymont
2011-05-16 13:39       ` Gabriel Scherer
2011-05-16 13:46         ` Joel Reymont
2011-05-16 14:02         ` Joel Reymont
2011-05-16 14:06           ` Gabriel Scherer
2011-05-16 14:08             ` Joel Reymont
2011-05-17  4:26     ` Goswin von Brederlow
2011-05-19  4:15 ` Pedro Borges
2011-05-19  7:33   ` Joel Reymont

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