Can I avoid committing to particular types in a module type and still get pattern matching? - module

I have two module types:
module type ORDERED =
sig
type t
val eq : t * t -> bool
val lt : t * t -> bool
val leq : t * t -> bool
end
module type STACK =
sig
exception Empty
type 'a t
val empty : 'a t
val isEmpty : 'a t -> bool
val cons : 'a * 'a t -> 'a t
val head : 'a t -> 'a
val tail : 'a t -> 'a t
val length : 'a t -> int
end
I want to write a functor which "lifts" the order relation from the basic ORDERED type to STACKs of that type. That can be done by saying that, for example, two stacks of elements will be equal if all its individual elements are equal. And that stacks s1 and s2 are s.t. s1 < s2 if the first of each of their elements, e1 and e2, are also s.t. e1 < e2, etc.
Now, if don't commit to explicitly defining the type in the module type, I will have to write something like this (or won't I?):
module StackLift (O : ORDERED) (S : STACK) : ORDERED =
struct
type t = O.t S.t
let rec eq (x,y) =
if S.isEmpty x
then if S.isEmpty y
then true
else false
else if S.isEmpty y
then false
else if O.eq (S.head x,S.head y)
then eq (S.tail x, S.tail y)
else false
(* etc for lt and leq *)
end
which is a very clumsy way of doing what pattern matching serves so well. An alternative would be to impose the definition of type STACK.t using explicit constructors, but that would tie my general module somewhat to a particular implementation, which I don't want to do.
Question: can I define something different above so that I can still use pattern matching while at the same time keeping the generality of the module types?

As an alternative or supplement to the other access functions, the module can provide a view function that returns a variant type to use in pattern matching.
type ('a, 's) stack_view = Nil | Cons of 'a * 's
module type STACK =
sig
val view : 'a t -> ('a , 'a t) stack_view
...
end
module StackLift (O : ORDERED) (S : STACK) : ORDERED =
struct
let rec eq (x, y) =
match S.view x, S.view y with
Cons (x, xs), Cons (y, ys) -> O.eq (x, y) && eq (xs, ys)
| Nil, Nil -> true
| _ -> false
...
end
Any stack with a head and tail function can have a view function too, regardless of the underlying data structure.

I believe you've answered your own question. A module type in ocaml is an interface which you cannot look behind. Otherwise, there's no point. You cannot keep the generality of the interface while exposing details of the implementation. The only thing you can use is what's been exposed through the interface.
My answer to your question is yes, there might be something you can do to your definition of stack, that would make the type of a stack a little more complex, thereby making it match a different pattern than just a single value, like (val,val) for instance. However, you've got a fine definition of a stack to work with, and adding more type-fluff is probably a bad idea.
Some suggestions with regards to your definitions:
Rename the following functions: cons => push, head => peek, tail => pop_. I would also add a function val pop : 'a t -> 'a * 'a t, in order to combine head and tail into one function, as well as to mirror cons. Your current naming scheme seems to imply that a list is backing your stack, which is a mental leak of the implementation :D.
Why do eq, lt, and leq take a pair as the first parameter? In constraining the type of eq to be val eq : 'a t * 'a t -> 'a t, you're forcing the programmer that uses your interface to keep around one side of the equality predicate until they've got the other side, before finally applying the function. Unless you have a very good reason, I would use the default curried form of the function, since it provides a little more freedom to the user (val eq : 'a t -> 'a t -> 'a t). The freedom comes in that they can partially apply eq and pass the function around instead of the value and function together.

Related

How to create a set of elements without knowing the type of the element?

I'm running into problems around recursive/mutually referential module definitions trying to use Caml's Map/Set stuff. I really want ones that just work on types, not modules. I feel like it should be possible to do this with first-class modules, but I'm failing to make the syntax work.
The signature I want is:
module type NonFunctorSet = sig
type 'a t
val create : ('a -> 'a -> int) -> 'a t
val add : 'a t -> 'a -> 'a t
val remove : 'a t -> 'a -> 'a t
val elements : 'a t -> 'a list
end
Possibly with other Caml.Set functions included. My idea for how this would work is something like:
type 'a t = {
m : (module Caml.Set.S with type elt = 'a);
set : m.t
}
let create (compare : 'a -> 'a -> t) =
module m = Caml.Set.Make(struct type t = 'a let compare = compare end) in
let set = m.empty in
{m = m; set = set;}
end
But that doesn't work for a number of reasons; 'a isn't exposed in the right places, I can't reference m.t in the same record where m was defined, etc.
Is there a version of this that works?
Adding more context about my use case:
I have two modules, Region and Tribe. Tribe needs access to a lot of the interface of Region, so I am currently creating Tribe as a functor, MakeTribe(Region : RegionT). Region mostly doesn't need to know about Tribe, but it does need to be able to store a mutable collection of Tribe.t that represent the tribes living in that region.
So, somehow or other, I need a RegionT like
module type RegionT = sig
type <region>
val get_local_tribes : <region> -> <tribes>
val add_tribe : <region> -> <tribe> -> unit
...
end
I don't really care about the specific syntax of <tribe>, <tribes> and <region> in this, so long as the fully built Tribe module can know that Region.get_local_tribes, etc, will yield an actual Tribe.t
The circular dependency problem is that the type <tribe> does not exist until the module Tribe is created. My idea so far has been to have RegionT.t actually be 'a RegionT.t, and then Tribe could simply refer to Tribe.t Region.t. This is all fine if I'm satisfied with keeping a <tribe> list inside Region, but I want it to be a set.
I feel this should be possible based on the following example code :
module Example : sig
type t
val compare : t -> t -> int
end = struct
type t = int
let compare = Int.compare
end
module ExampleSet = Caml.Set.Make(struct type t = Example.t let compare = Example.compare end)
All that Example exposes in its interface is a type and a function from two instances of that type to an int; why is that more than having a 'a -> 'a -> int, which has the same things?
Using Polymoprhic Sets and Maps from the Base Library
In Base and Core libraries, from Jane Street, ordered data structures, such as maps, sets, hash tables, and hash sets, are all implemented as polymorphic data structures, instead of functorized versions as in the vanilla OCaml standard library.
You can read about them more in the Real World OCaml Maps and Hashtbales chapter. But here are quick recipes. When you see a comparator in the function interface, e.g., in Map.empty what it actually wants you is to give you a module that implements the comparator interface. The good news is that most of the modules in Base/Core are implementing it, so you don't have to worry or know anything about this to use it, e.g.,
# open Base;;
# let empty = Map.empty (module Int);;
val empty : (Base.Int.t, 'a, Base.Int.comparator_witness) Base.Map.t =
<abstr>
# Map.add empty 1 "one";;
- : (Base.Int.t, string, Base.Int.comparator_witness) Base.Map.t
Base.Map.Or_duplicate.t
= `Ok <abstr>
So the simple rule, if you want a set,map,hashtable,hashset where the key element has type foo, just pass (module Foo) as a comparator.
Now, what if you want to make a mapping from your custom type? E.g., a pair of ints that you would like to compare in lexicographical order.
First of all, we need to define sexp_of and compare functions. For our type. We will use ppx derivers for it, but it is easy to make it manually if you need.
module Pair = struct
type t = int * int [##deriving compare, sexp_of]
end
Now, to create a comparator, we just need to use the Base.Comparator.Make functor, e.g.,
module Lexicographical_order = struct
include Pair
include Base.Comparator.Make(Pair)
end
So now we can do,
# let empty = Set.empty (module Lexicographical_order);;
val empty :
(Lexicographical_order.t, Lexicographical_order.comparator_witness)
Base.Set.t = <abstr>
# Set.add empty (1,2);;
- : (Lexicographical_order.t, Lexicographical_order.comparator_witness)
Base.Set.t
= <abstr>
Despite that Base's data structures are polymorphic they strictly require that the module that provides the comparator is instantiated and known. You can just use the compare function to create a polymorphic data structure because Base will instantiate a witness type for each defined compare function and capture it in the data structure type to enable binary methods. Anyway, it is a complex issue, read on for easier (and harder) solutions.
Instantiating Sets on mutually dependent modules
In fact, OCaml supports mutually recursive funtors and although I would suggest you to break the recursion by introducing a common abstraction on which both Region and Tribe depend, you can still encode your problem in OCaml, e.g.,
module rec Tribe : sig
type t
val create : string -> t
val compare : t -> t -> int
val regions : t -> Region.t list
end = struct
type t = string * Region.t list
let create name = name,[]
let compare (x,_) (y,_) = String.compare x y
let regions (_,r) = r
end
and Region : sig
type t
val empty : t
val add_tribe : Tribe.t -> t -> t
val tribes : t -> Tribe.t list
end = struct
module Tribes = Set.Make(Tribe)
type t = Tribes.t
let empty = Tribes.empty
let add_tribe = Tribes.add
let tribes = Tribes.elements
end
Breaking the Dependency Loop
A much better solution would be to redesign your modules and break the dependency loop. The simplest approach would be just to choose some identifier that will be used to compare tribes, e.g., by their unique names,
module Region : sig
type 'a t
val empty : 'a t
val add_tribe : string -> 'a -> 'a t -> 'a t
val tribes : 'a t -> 'a list
end = struct
module Tribes = Map.Make(String)
type 'a t = 'a Tribes.t
let empty = Tribes.empty
let add_tribe = Tribes.add
let tribes r = Tribes.bindings r |> List.map snd
end
module Tribe : sig
type t
val create : string -> t
val name : t -> string
val regions : t -> t Region.t list
val conquer : t Region.t -> t -> t Region.t
end = struct
type t = Tribe of string * t Region.t list
let create name = Tribe (name,[])
let name (Tribe (name,_)) = name
let regions (Tribe (_,r)) = r
let conquer region tribe =
Region.add_tribe (name tribe) tribe region
end
There are also tons of other options and in general, when you have mutual dependencies it is actually an indicator of a problem in your design. So, I would still revisit the design stage and eschew the circular dependencies.
Creating Polymorphic Sets using the Vanilla OCaml Standard Library
It is not an easy task, especially if you need to handle operations that involve several sets, e.g., Set.union. The problem is that Set.Make is generating a new type for the set per each compare function so when we need to union two sets it is hard for us to prove to the OCaml compiler that they were created from the same type. It is possible but really painful, I am showing how to do this only to discourage you from doing this (and to showcase OCaml's dynamic typing capabilities).
First of all we need a witness type that will reify an OCaml type for the set into a concrete value.
type _ witness = ..
module type Witness = sig
type t
type _ witness += Id : t witness
end
Now we can define our polymorphic set as an existential that holds the set itself and the module with operations. It also holds the tid (for type identifier) that we will later use to recover the type 's of the set.
type 'a set = Set : {
set : 's;
ops : (module Set.S with type elt = 'a and type t = 's);
tid : (module Witness with type t = 's);
} -> 'a set
Now we can write the create function that will take the compare function and turn it into a set,
let create : type a s. (a -> a -> int) -> a set =
fun compare ->
let module S = Set.Make(struct
type t = a
let compare = compare
end) in
let module W = struct
type t = S.t
type _ witness += Id : t witness
end in
Set {
set = S.empty;
ops = (module S);
tid = (module W);
}
The caveat here is that each call to create will generate a new instance of the set type 's so we can compare/union/etc two sets that were created with the same create function. In other words, all sets in our implementation shall share the same ancestor. But before that lets take a pain and implement at least two operations, add and union,
let add : type a. a -> a set -> a set =
fun elt (Set {set; tid; ops=(module Set)}) -> Set {
set = Set.add elt set;
ops = (module Set);
tid;
}
let union : type a. a set -> a set -> a set =
fun (Set {set=s1; tid=(module W1); ops=(module Set)})
(Set {set=s2; tid=(module W2)}) ->
match W1.Id with
| W2.Id -> Set {
set = Set.union s1 s2;
tid = (module W1);
ops = (module Set);
}
| _ -> failwith "sets are potentially using different types"
Now, we can play with it a bit,
# let empty = create compare;;
val empty : '_weak1 set = Set {set = <poly>; ops = <module>; tid = <module>}
# let x1 = add 1 empty;;
val x1 : int set = Set {set = <poly>; ops = <module>; tid = <module>}
# let x2 = add 2 empty;;
val x2 : int set = Set {set = <poly>; ops = <module>; tid = <module>}
# let x3 = union x1 x2;;
val x3 : int set = Set {set = <poly>; ops = <module>; tid = <module>}
# let x4 = create compare;;
val x4 : '_weak2 set = Set {set = <poly>; ops = <module>; tid = <module>}
# union x3 x4;;
Exception: Failure "sets are potentially using different types".
#

The signature for this packaged module couldn't be inferred in recursive function

I'm still trying to figure out how to split code when using mirage and it's myriad of first class modules.
I've put everything I need in a big ugly Context module, to avoid having to pass ten modules to all my functions, one is pain enough.
I have a function to receive commands over tcp :
let recvCmds (type a) (module Ctx : Context with type chan = a) nodeid chan = ...
After hours of trial and errors, I figured out that I needed to add (type a) and the "explicit" type chan = a to make it work. Looks ugly, but it compiles.
But if I want to make that function recursive :
let rec recvCmds (type a) (module Ctx : Context with type chan = a) nodeid chan =
Ctx.readMsg chan >>= fun res ->
... more stuff ...
|> OtherModule.getStorageForId (module Ctx)
... more stuff ...
recvCmds (module Ctx) nodeid chan
I pass the module twice, the first time no problem but
I get an error on the recursion line :
The signature for this packaged module couldn't be inferred.
and if I try to specify the signature I get
This expression has type a but an expression was expected of type 'a
The type constructor a would escape its scope
And it seems like I can't use the whole (type chan = a) thing.
If someone could explain what is going on, and ideally a way to work around it, it'd be great.
I could just use a while of course, but I'd rather finally understand these damn modules. Thanks !
The pratical answer is that recursive functions should universally quantify their locally abstract types with let rec f: type a. .... = fun ... .
More precisely, your example can be simplified to
module type T = sig type t end
let rec f (type a) (m: (module T with type t = a)) = f m
which yield the same error as yours:
Error: This expression has type (module T with type t = a)
but an expression was expected of type 'a
The type constructor a would escape its scope
This error can be fixed with an explicit forall quantification: this can be done with
the short-hand notation (for universally quantified locally abstract type):
let rec f: type a. (module T with type t = a) -> 'never = fun m -> f m
The reason behind this behavior is that locally abstract type should not escape
the scope of the function that introduced them. For instance, this code
let ext_store = ref None
let store x = ext_store := Some x
let f (type a) (x:a) = store x
should visibly fail because it tries to store a value of type a, which is a non-sensical type outside of the body of f.
By consequence, values with a locally abstract type can only be used by polymorphic function. For instance, this example
let id x = x
let f (x:a) : a = id x
is fine because id x works for any x.
The problem with a function like
let rec f (type a) (m: (module T with type t = a)) = f m
is then that the type of f is not yet generalized inside its body, because type generalization in ML happens at let definition. The fix is therefore to explicitly tell to the compiler that f is polymorphic in its argument:
let rec f: 'a. (module T with type t = 'a) -> 'never =
fun (type a) (m:(module T with type t = a)) -> f m
Here, 'a. ... is an universal quantification that should read forall 'a. ....
This first line tells to the compiler that the function f is polymorphic in its first argument, whereas the second line explicitly introduces the locally abstract type a to refine the packed module type. Splitting these two declarations is quite verbose, thus the shorthand notation combines both:
let rec f: type a. (module T with type t = a) -> 'never = fun m -> f m

SML converting a string to an int with error catching

So what I want to do is to convert a string into an int and do some error catching on it. I would also like to know where I would put what I want it to do after it fails if it does.
I know how to convert, but I am not sure how to catch it and where the code will jump to after the error
I believe the method for converting it Int.fromString(x)
Thank you.
SML has two approaches to error handling. One, based on raise to raise errors and handle to catch the error, is somewhat similar to how error handling works in languages like Python or Java. It is effective, but the resulting code tends to lose some of its functional flavor. The other method is based on the notion of options. Since the return type of Int.fromString is
string -> int option
it makes the most sense to use the option-based approach.
An int option is either SOME n, where n is and integer, or it is NONE. The function Int.fromString returns the latter if it fails in its attempt to convert the string to an integer. The function which calls Int.fromString can explicitly test for NONE and use the valOf to extract the value in the case that the return value is of the form SOME n. Alternatively, and somewhat more idiomatically, you can use pattern matching in a case expression. Here is a toy example:
fun squareString s =
case Int.fromString(s) of
SOME n => Int.toString (n * n) |
NONE => s ^ " isn't an integer";
This function has type string -> string. Typical output:
- squareString "4";
val it = "16" : string
- squareString "Bob";
val it = "Bob isn't an integer" : string
Note that the clause which starts NONE => is basically an error handler. If the function that you are defining isn't able to handle such errors, it could pass the buck. For example:
fun squareString s =
case Int.fromString(s) of
SOME n => SOME (Int.toString (n * n))|
NONE => NONE;
This has type string -> string option with output now looking like:
- squareString "4";
val it = SOME "16" : string option
- squareString "Bob";
val it = NONE : string option
This would make it the responsibility of the caller to figure out what to do with the option.
The approach to error handling that John explains is elaborated in the StackOverflow question 'Unpacking' the data in an SML DataType without a case statement. The use-case there is a bit different, since it also involves syntax trees, but the same convenience applies for smaller cases:
fun squareString s = Int.fromString s >>= (fn i => SOME (i*i))
Assuming you defined the >>= operator as:
infix 3 >>=
fun NONE >>= _ = NONE
| (SOME a) >>= f = f a
The drawback of using 'a option for error handling is that you have to take into account, every single time you use a function that has this return type, whether it errored. This is not unreasonable. It's like mandatory null-checking. But it comes at the cost of not being able to easily compose your functions (using e.g. the o operator) and a lot of nested case-ofs:
fun inputSqrt s =
case TextIO.inputLine TextIO.stdIn of
NONE => NONE
| SOME s => case Real.fromString s of
NONE => NONE
| SOME x => SOME (Math.sqrt x) handle Domain => NONE
A workaround is that you can build this constant error handling into your function composition operator, as long as all your functions share the same way of expressing errors, e.g. using 'a option:
fun safeSqrt x = SOME (Math.sqrt x) handle Domain => NONE
fun inputSqrt () =
TextIO.inputLine TextIO.stdIn >>=
(fn s => Real.fromString s >>=
(fn x => safeSqrt x))
Or even shorter by applying Eta conversion:
fun inputSqrt () = TextIO.inputLine TextIO.stdIn >>= Real.fromString >>= safeSqrt
This function could fail either because of a lack of input, or because the input didn't convert to a real, or because it was negative. Naturally, this error handling isn't smart enough to say what the error was, so you might want to extend your functions from using an 'a option to using an ('a, 'b) either:
datatype ('a, 'b) either = Left of 'a | Right of 'b
infix 3 >>=
fun (Left msg) >>= _ = Left msg
| (Right a) >>= f = f a
fun try (SOME x) _ = Right x
| try NONE msg = Left msg
fun inputLine () =
try (TextIO.inputLine TextIO.stdIn) "Could not read from stdIn."
fun realFromString s =
try (Real.fromString s) "Could not derive real from string."
fun safeSqrt x =
try (SOME (Math.sqrt x) handle Domain => NONE) "Square root of negative number"
fun inputSqrt () =
inputLine () >>= realFromString >>= safeSqrt
And trying this out:
- ​inputSqrt ();
​9
> val it = Right 3.0 : (string, real) either
- ​inputSqrt ();
​~42
> val it = Left "Square root of negative number" : (string, real) either
- ​inputSqrt ();
Hello
> val it = Left "Could not derive real from string." : (string, real) either
- (TextIO.closeIn TextIO.stdIn; inputSqrt ());
> val it = Left "Could not read from stdIn." : (string, real) either

Extend a module from Map in OCaml

I have a module StringMap built by the functor Map.Make given a type String:
module StringMap = Map.Make(String)
Besides the ordinary operations provided by Map, I would like to add more definitions in this module, for instance, my_own_function, such that I could call StringMap.my_own_function. Does anyone know where I should define this kind of functions and their signature?
You can use the include keyword inside a new module to add all the same functions. This was also extended to the signature in OCaml 3.12.
module StringMap =
struct
include Map.Make(String)
end
If you want to access the structure of the map, you'll have to add some Obj.magic or the %identity special external function. The redefinition of the type must be exact since no type checking is happening,
module Make (Ord : Map.OrderedType) =
struct
include Map.Make(Ord)
type 'a impl = Empty
| Node of 'a impl * key * 'a * 'a impl * int
external impl_of_t : 'a t -> 'a impl = "%identity"
external t_of_impl : 'a impl -> 'a t = "%identity"
let cardinal map =
let rec cardinal = function
| Empty -> 0
| Node(l,_,_,r,_) -> cardinal l + 1 + cardinal r
in
cardinal (impl_of_t map)
end

Modules and record fields

I have stumbled across a rather simple OCaml problem, but I can't seem to find an elegant solution. I'm working with functors that are applied to relatively simple modules (they usually define a type and a few functions on that type) and extend those simple modules by adding additional more complex functions, types and modules. A simplified version would be:
module type SIMPLE = sig
type t
val to_string : t -> string
val of_string : string -> t
end
module Complex = functor (S:SIMPLE) -> struct
include S
let write db id t = db # write id (S.to_string t)
let read db id = db # read id |> BatOption.map S.of_string
end
There is no need to give the simple module a name because all its functionality is present in the extended module, and the functions in the simple module are generated by camlp4 based on the type. The idiomatic use of these functors is:
module Int = Complex(struct
type t = int
end)
The problem appears when I'm working with records:
module Point2D = Complex(struct
type t = { x : int ; y : int }
end)
let (Some location) = Point2D.read db "location"
There seems to be no simple way of accessing the x and y fields defined above from outside the Point2D module, such as location.x or location.Point2D.x. How can I achieve this?
EDIT: as requested, here's a complete minimal example that displays the issue:
module type TYPE = sig
type t
val default : t
end
module Make = functor(Arg : TYPE) -> struct
include Arg
let get = function None -> default | Some x -> (x : t)
end
module Made = Make(struct
type t = {a : int}
let default = { a = 0 } (* <-- Generated by camlp4 based on type t above *)
end)
let _ = (Made.get None).a (* <-- ERROR *)
Let's look at the signature of some of the modules involved. These are the signatures generated by Ocaml, and they're principal signatures, i.e. they are the most general signatures allowed by the theory.
module Make : functor (Arg : TYPE) -> sig
type t = Arg.t
val default : t
val get : t option -> t
end
module Made : sig
type t
val default : t
val get : t option -> t
end
Notice how the equation Make(A).t = A.t is retained (so Make(A).t is a transparent type abbreviation), yet Made.t is abstract. This is because Made is the result of applying the functor to an anonymous structure, so there is no canonical name for the argument type in this case.
Record types are generative. At the level of the underlying type theory, all generative types behave like abstract types with some syntactic sugar for constructors and destructors. The only way to designate a generative type is to give its name, either the original name or one that expands to the original name via a series of type equations.
Consider what happens if you duplicate the definition of Made:
module Made1 = Make(struct
type t = {a : int}
let default = { a = 0 } (* <-- Generated by camlp4 based on type t above *)
end)
module Made2 = Make(struct
type t = {a : int}
let default = { a = 0 } (* <-- Generated by camlp4 based on type t above *)
end)
You get two different types Made1.t and Made2.t, even though the right-hand sides of the definitions are the same. That's what generativity is all about.
Since Made.t is abstract, it's not a record type. It doesn't have any constructor. The constructors were lost when the structure argument was closed, for a lack of a name.
It so happens that with records, one often wants the syntactic sugar but not the generativity. But Ocaml doesn't have any structural record types. It has generative record types, and it has objects, which from a type theoretical view subsume records but in practice can be a little more work to use and have a small performance penalty.
module Made_object = Make(struct
type t = <a : int>
let default = object method a = 0 end
end)
Or, if you want to keep the same type definition, you need to provide a name for the type and its constructors, which means naming the structure.
module A = struct
type t = {a : int}
let default = { a = 0 } (* <-- Generated by camlp4 based on type t above *)
end
module MadeA = Make(A)
Note that if you build Make(A) twice, you get the same types all around.
module MadeA1 = Make(A)
module MadeA2 = Make(A)
(Ok, this isn't remarkable here, but you'd still get the same abstract types in MadeA1 and MakeA2, unlike the Made1 and Made2 case above. That's because now there's a name for these types: MadeA1.t = Make(A).t.)
First of all, in your last code sample, last line, you probably mean .a rather than .x.
The problem with your code is that, with the way you define your Make functor, the type t is abstract in Made: indeed, the functors use the TYPE signature which seals {a : int} as an abstract type.
The following design circumvent the issue, but, well, its a different design.
module type TYPE = sig
type t
val default : t
end
module Extend = functor(Arg : TYPE) -> struct
open Arg
let get = function None -> default | Some x -> (x : t)
end
module T = struct
type t = {a : int}
let default = { a = 0 }
end
module Made = struct
include T
include Extend(T)
end
let _ = Made.((get None).a)
The problem is that OCaml doesn't have a name to refer to the qualified components of the type t (in this case a record, but the same problem would be present with normal variants) outside Made. Naming the unnamed solves the problem:
module F = struct
type t = {a : int}
let default = { a = 0 }
end
module Made = Make(F)
let _ = (Made.get None).F.a (* <-- WORKS *)
You can also declare explicitly the type outside the functorial application:
type rcd = {a : int}
module Made = Make(struct
type t = rcd
let default = { a = 0 }
end)
let _ = (Made.get None).a (* <-- WORKS *)