I want to explore the construction of objects without depending on the “O” features of “Ocaml”. The code
let current_rand = ref 0;;
let random () =
   current_rand := !current_rand * 25713 + 1345;
   !current_rand;;
is provided as a too simple example of a random number generator here. It exposes the seed and cannot provide concurrent seeds and concomitant number streams as a good generator would. How about
let rngc () = let seed = ref 0 in
   (fun () -> seed := !seed * 25713 + 1345;
   !seed);;
instead? This seems like a perfectly fine Caml object to me. It carries state and behavior and is multiply instantiatable.

There are two ways to go next from here:

v-Tables

v-tables are an implementation technique of C++ but the pattern goes back at least to assembly language in the first operating systems of IBM’s 360 computers. Different file formats were accompanied each by a suite of polymorphic routines. A different v-table for each file format would locate those routines. Opening a file would locate that v-table at runtime. They were not called “v-tables” however. There was also just one v-table layout that was fixed once and for all. There were specific documented offsets for “READ”, “WRITE”, “OPEN”, “CLOSE”, etc. I was eventually impressed by this plan; I had designed an I/O package for the IBM Stretch a couple of years earlier and this plan was better than what we did.

It seemed clear that language support for user defined v-table layouts was needed. I suspect that Simula used v-tables. Can we express this type of a v-table in Caml? More exactly: can we express this pattern in Caml or must we extend Caml as Ocaml did?

How about a type that is a 2-tuple that combines a specific but unknown type, once covariantly and once contravariantly? This type will vary at run time but the types will always match for any tuple of this type.

# type ('a) vt = 'a * ('a -> int);;
type 'a vt = 'a * ('a -> int)
looks promising but it seems that we have defined a type constructor, rather than a type. I think an expression cannot have a type vt at compile time.
# type 'a vt = 'a * ('a -> int);;
type 'a vt = 'a * ('a -> int)
# let a = ref (3, fun x -> x+4);;
val a : (int * (int -> int)) ref = {contents = (3, )}
# a := (false, fun b -> if b then 3 else 4);;
This expression has type bool * (bool -> int) but is here used with type
  int * (int -> int)
Seems to preclude the existence of a dynamic Caml type 'a * ('a -> unit). I don’t know how to type v-tables in light of these results. Notice that C++ compiles efficient code that uses v-tables where the type denoted by 'a is unknown at compile time. Tuncol admitted these types, but tuncol was not complete.

The rules for records are different and the compiler pays more attention to record type definitions. The above declaration of vt produced only a constructor.

Lesser Goal

Note however that combined with rngc above we can define another value of the same type:
let rngcp () = let seed = ref (0, 42) in 
   fun () -> match !seed with l, r ->
   seed := l*25713 + r*2633 + 1345, l*32654 + r*1327 + 4390; l;;
which has the same type as rngc, but a different behavior and different state format. Both have type unit -> unit -> int. They can be used polymorphically. (Notice that the compiler can see that space for the new tuple need not be allocated for each evaluation of the tuple expression since access to the old tuple manifestly dies upon the assignment.)

Is this sort of polymorphism good enough?

Dispatch

To stress-test the above form of polymorphism lets add some sort of method dispatching. We want different signatures for different methods. Lets add ‘clone’ to our rngcp. We could bundle the two procedures using one of the two Caml bundling primitives;
Tupple: type rt = (unit -> int * unit -> rt);;
let rngc () = let rec rf s = (
   (fun () -> s := !s * 25713 + 1345; !s),
   (fun () -> rf (ref !s)))
   in rf (ref 71);;
Record: type rr = {rand : unit -> int; clone : unit -> rr};;
let rngr () = let rec rf s = {
   rand = (fun () -> s := !s * 25713 + 1345; !s);
   clone = (fun () -> rf (ref !s))}
   in rf (ref 71);;
These both require the “-rectypes” option. Some disparage rectypes as it causes more obscure diagnostics.

The tuple package has interface unit -> rt and can be invoked thus:

let p i = print_int i; print_char '\n' in
match rngc() with rand, clone -> begin
  for i = 1 to 5 do p (rand()) done;
  match clone() with r2, c2 -> begin
    for i = 1 to 5 do p (r2()) done;
    for i = 1 to 5 do p (rand()) done
end end;;
The user of rngc gets to choose the name of the component functions.

Using interface unit->rr the record packaging might be used as follows:

let p i = print_int i; print_char '\n' in
let r1 = rngr() in begin
  for i = 1 to 5 do p (r1.rand()) done;
  let r2 = r1.clone() in begin
    for i = 1 to 5 do p (r1.rand()) done;
    for i = 1 to 5 do p (r2.rand()) done;
end end;;

Pipe Dream (on hold)

Here is where I was heading; Caml provides a convenient notation for these ideas. Our instantiable random number generator ...
let rngc () = let rns sr = (fun () -> sr := !sr * 25713 + 1345; !sr) in let rec rf s = (rns s, fun () -> let sed = ref !s in rf sed) in rf (ref 71);; but it requires ocaml -rectypes