Use abstract module as part of type definition separate from module - ocaml

I'm trying to use the module type Partial_information which is constructed via the functor Make_partial_information as the type of the field contents in the type Cell.t. However, I'm getting the error Unbound module Partial_information.
open Core
(* module which is used as argument to functor *)
module type Partial_type = sig
type t
val merge : old:t -> new_:t -> t
end
(* type of result from functor *)
module type Partial_information = sig
type a
type t = a option
val merge : old:t -> new_:t -> t
val is_nothing : t -> bool
end
(* The functor *)
module Make_partial_information(Wrapping : Partial_type):
(Partial_information with type a = Wrapping.t)
= struct
type a = Wrapping.t
type t = a option
let merge ~(old : t) ~(new_ : t) =
match (old, new_) with
| (None, None) -> None
| (None, Some a) -> Some a
| (Some a, None) -> Some a
| (Some a, Some b) -> (Wrapping.merge ~old:a ~new_:b) |> Some
let is_nothing (it: t) : bool = (is_none it)
end
(* Checking to make sure understanding of functor is correct *)
module Int_partial_type = struct
type t = int
let merge ~old ~new_ = new_ [##warning "-27"]
end
module Int_partial_information = Make_partial_information(Int_partial_type)
(* Trying to use _any_ type which might have been created by the functor as a field in the record *)
module Cell = struct
type id = { name : string ; modifier : int }
type t = {
(* Error is here stating `Unbound module Partial_information` *)
contents : Partial_information.t ;
id : id
}
end

Module types are specifications for modules. They do not define types by themselves. They are also not constructed by functors in any way.
Consequently, it is hard to tell what you are trying to do.
As far I can see, you can simply define your cell type with a functor:
module Cell(P : Partial_information) = struct
type id = { name : string ; modifier : int }
type partial
type t = {
contents : P.t;
id : id
}
end
Or it might be even simpler to make the cell type polymorphic:
type 'a cell = {
contents : 'a;
id : id
}
since the type in itself is not particularly interesting nor really dependent upon
the type of contents.
P.S:
It is possible to use first class modules and GADTs to existentially quantify over a specific implementation of a module type. But it is unclear if it is worthwhile to explode your complexity budget here:
type 'a partial_information = (module Partial_information with type a = 'a)
module Cell = struct
type id = { name : string ; modifier : int }
type t = E: {
contents : 'a ;
partial_information_implementation: 'a partial_information;
id : id
} -> t
end

Related

How to apply [##deriving show] to a type from module parameter of my functor?

I have a functor that takes a Set type like:
module type MySet = functor (S : Set.S) -> sig
val my_method : S.t -> S.elt -> S.elt list option
end
module MySet_Make : MySet = functor (S : Set.S) -> struct
let my_method set el = Some [el] (* whatever *)
end
module IntSet = Set.Make(Int)
module MyIntSet = MySet_Make(IntSet)
S.elt is the type of elements of the set
I want to apply [##deriving show] (from https://github.com/ocaml-ppx/ppx_deriving#plugin-show) to S.elt within my functor somehow, so that in one of my methods I can rely on having a show : S.elt -> string function available.
I feel like it must be possible but I can't work out the right syntax.
Alternatively - if there's a way to specify in the signature that the Set type S was made having elements of a "showable" type.
e.g. I can define:
module type Showable = sig
type t [##deriving show]
end
...but I can't work out how to specify that as a type constraint to elements of (S : Set.S)
You can construct new signatures that specify the exact function show you need:
module MySet_Make(S : sig
include Set.S
val show : elt -> string
end) = struct
let my_method _set el =
print_endline (S.show el);
Some [el]
end
Then you can build the actual module instance by constructing the module with the needed function:
module IntSet = struct
include Set.Make(Int)
(* For other types, this function could be created by just using [##deriving show] *)
let show = string_of_int
end
module MyIntSet = MySet_Make(IntSet)
Ok, after a couple of hours more fumbling around in the dark I found a recipe that does everything I wanted...
First we define a "showable" type, representing a module type that has had [##deriving show] (from https://github.com/ocaml-ppx/ppx_deriving#plugin-show) applied to it:
module type Showable = sig
type t
val pp : Format.formatter -> t -> unit
val show : t -> string
end
(I don't know if there's some way to get this directly from ppx_deriving.show without defining it manually?)
Then we re-define and extend the Set and Set.OrderedType (i.e. element) types to require that the elements are "showable":
module type OrderedShowable = sig
include Set.OrderedType
include Showable with type t := t
end
module ShowableSet = struct
include Set
module type S = sig
include Set.S
end
module Make (Ord : OrderedShowable) = struct
include Set.Make(Ord)
end
end
I think with the original code in my question I had got confused and used some kind of higher-order functor syntax (?) ...I don't know how it seemed to work at all, but at some point I realised my MySet_Make was returning a functor rather than a module. So we'll fix that now and just use a normal functor.
The other thing we can fix is to make MySet a further extension of ShowableSet ... so MySet_Make will take the element type as a parameter instead of another Set type. This makes the eventual code all simpler too:
module type MySet = sig
include ShowableSet.S
val my_method : t -> elt -> elt list option
val show_el : elt -> string
end
module AdjacencySet_Make (El : OrderedShowable) : AdjacencySet
with type elt = El.t
= struct
include ShowableSet.Make(El)
let my_method set el = Some [el] (* whatever *)
let show_el el = El.show el (* we can use the "showable" elements! *)
end
Then we just need an OrderedShowable version of Int as the element type. Int is already ordered so we just have to extend it by deriving "show" and then we can make a concrete MySet:
module Int' = struct
include Int
type t = int [##deriving show]
end
module MyIntSet = MySet_Make(Int')
And we can use it like:
# let myset = MyIntSet.of_list [3; 2; 8];;
# print_endline (MyIntSet.show_el 3);;
"3"

Functors with multiple inputs in Standard ML

High level question: How do I use functors with multiple arguments in SML?
I've looked at this, this, this and this(PDF). All of them seem to conflict in terms of structure or functor definition syntax, and none of them show anything other than a unary functor.
Specifics: I'm trying to write a web server in Standard ML (you can see the effort here), and have decided to partition it into BUFFER, PARSER and TCPSERVER chunks. The BUFFER and PARSER are both just straightforward structures. The idea with the TCPSERVER is that it handles listening/accepting logic, but allows the user to specify an appropriate buffering/parsing strategy by passing the other two in. What I've got is something like
signature TCPSERVER =
sig
type SockAction
type Request
val serve : int -> (Request -> (INetSock.inet,Socket.active Socket.stream) Socket.sock -> SockAction) -> 'u
end
functor Server (Buf : BUFFER) (Par : PARSER) : TCPSERVER =
struct
type Request = Par.Request
datatype SockAction = CLOSE | LEAVE_OPEN
local
...
[eliding more definitions, including calls to Par.* and Buf.* functions]
...
fun serve port serverFn =
let val s = INetSock.TCP.socket()
in
Socket.Ctl.setREUSEADDR (s, true);
Socket.bind(s, INetSock.any port);
Socket.listen(s, 5);
print "Entering accept loop...\n";
acceptLoop s [] serverFn
end
end
end
The above seems to be accepted by smlnj...
- use "server.sml" ;
[opening server.sml]
type Response =
{body:string, headers:(string * string) list, httpVersion:string,
responseType:string}
val fst = fn : 'a * 'b -> 'a
val snd = fn : 'a * 'b -> 'b
val a_ = fn : 'a * 'b * 'c -> 'a
val b_ = fn : 'a * 'b * 'c -> 'b
val c_ = fn : 'a * 'b * 'c -> 'c
val curry = fn : ('a * 'b -> 'c) -> 'a -> 'b -> 'c
signature TCPSERVER =
sig
type SockAction
type Request
val serve : int
-> (Request
-> (INetSock.inet,Socket.active Socket.stream) Socket.sock
-> SockAction)
-> 'a
end
functor HTTPServer(Buf: sig
type Buffer
val readInto : Buffer
-> ('a,Socket.active Socket.stream)
Socket.sock
-> BufferStatus
val new : int -> Buffer
val toSlice : Buffer -> Word8ArraySlice.slice
val printBuffer : Buffer -> unit
end) :
sig functor <functor> : <fctsig> end
val it = () : unit
... but rejected by mlton.
~/projects/serve-sml $ mlton server.mlb
Error: server.sml 23.1. # (line with "functor Server...")
Syntax error: replacing FUNCTOR with FUN.
Error: server.sml 24.1.
Syntax error: replacing STRUCT with ASTERISK.
Error: server.sml 87.1.
Syntax error found at END.
Error: server.sml 88.0.
Parse error.
...
Additionally, I'm not entirely sure how to use the definition once it's evaluated. Even in smlnj, the obvious fails:
- HTTPServer(DefaultBuffer, DefaultParser) ;
stdIn:1.2-1.12 Error: unbound variable or constructor: HTTPServer
stdIn:2.7-3.1 Error: unbound variable or constructor: DefaultParser
stdIn:1.13-2.5 Error: unbound variable or constructor: DefaultBuffer
-
Can anyone tell me what I'm doing wrong? Or even point me to a good piece of documentation?
Your Server functor does multiple arguments via currying. That does not work in plain SML, because it does not have higher-order functors (which SML/NJ supports as a non-standard extension). You need to use uncurried form, by introducing an auxiliary structure, like you would use a tuple or record in the core language:
functor Server(X : sig structure Buffer : BUFFER; structure Parser : PARSER end) =
...X.Buffer...X.Parser...
structure MyServer =
Server(struct structure Buffer = MyBuffer; structure Parser = MyParser end)
Obviously, this is pretty clumsy and verbose, so at least SML has some syntactic sugar for the above, allowing you to keep the auxiliary structure implicit:
functor Server(structure Buffer : BUFFER; structure Parser : PARSER) =
...Buffer...Parser...
structure MyServer =
Server(structure Buffer = MyBuffer; structure Parser = MyParser)
But that is as short as it gets in current SML.
It's useful to understand that Standard ML is composed of two languages — the core language of values (ordinary functions, numbers, booleans, their types, etc.) and the language of modules, comprised of signatures, structures and functors.
Functors are similar to core functions, they always accept a single argument and return a module-level value. A functor's argument type is specified by a signature, while the actual value of the argument, when "calling" the functor, will be a structure implementing that signature. A functor returns a structure, whose type is again determined by a signature. This is the basic skeleton:
signature ARG = sig end
signature RESULT = sig end
functor FUNCTOR(A : ARG) : RESULT
Now, as mentioned and examplified by Andreas Rossberg, the standard provides some syntactic sugar for expressing a functor's param type. However, I tend to favor the above skeleton when a functor requires more than a few structures as input:
signature SERVER_ARGS =
sig
structure ARG_0 = sig end
structure ARG_1 = sig end
structure ARG_2 = sig end
structure ARG_3 = sig end
end
signature SERVER = sig end
functor ServerFn(ARGS : SERVER_ARGS) : SERVER =
struct
end
Now, when calling a functor, there are several choices as to the syntax:
(* Using an anonymous structure *)
ServerFn(struct
structure ARG_0 = struct end
structure ARG_1 = struct end
structure ARG_2 = struct end
structure ARG_3 = struct end
end)
(* Using a named structure *)
structure ServerArgs =
struct
structure ARG_0 = struct end
structure ARG_1 = struct end
structure ARG_2 = struct end
structure ARG_3 = struct end
end
ServerFn(ServerArgs)
(* Using an anonynous structure, with syntactic sugar *)
ServerFn(
structure ARG_0 = struct end
structure ARG_1 = struct end
structure ARG_2 = struct end
structure ARG_3 = struct end
)
A functor's result, being a structure, may only be found in a structure position in source code, i.e., you either give it a name using the structure keyword, or you pass it along as an argument to some other functor:
structure Server = ServerFn(ServerArgs)
structure Quux = OtherFunctor(ServerFn(ServerArgs))
The structure keyword is the module-level equivalent of the val keyword in the core language. A way to bind "variables" at the module level. In the same vein, the signature keyword is the module-level equivalent of the type keyword in the core language — a helpful way to introduce aliases for anonymous signatures denoted by sig ... end.
This is why your last example fails, because the SML top-level tries to interpret HTTPServer(DefaultBuffer, DefaultParser); as a core-level function call, not as a module-level function/functor call.
I think the StandardML syntax for multi-argument functors is:
signature PARSER = sig
val parse : unit -> unit
end
signature BUFFER = sig
val read : unit -> unit
end
functor Server (structure buffer : BUFFER
structure parser : PARSER) = struct
end
I guess the issue is that SML-NJ supports higher-order functors while MLton does not.

Mutually recursive module and functor in OCaml

I have defined an interface A to be used by several functors, and notably by MyFunctor :
module type A = sig
val basic_func: ...
val complex_func: ...
end
module MyFunctor :
functor (SomeA : A) ->
struct
...
let complex_impl params =
...
(* Here I call 'basic_func' from SomeA *)
SomeA.basic_func ...
...
end
Now I want to define a module B with implements the interface A. In particular, the implementation of complex_func should use basic_func through complex_impl in MyFunctor :
module B = struct
let basic_func = ...
let complex_func ... =
let module Impl = MyFunctor(B) in
Impl.complex_impl ...
end
However, this code doesn't compile as B is not fully declared in the context of MyFunctor(B). Obviously B depends on MyFunctor(B), which itself depends on B, so I tried to use the rec keyword on module B, but it didn't work out.
So, is it possible to do something like this ? It would be useful as I have several modules B_1, ..., B_n that use the same implementation of B_k.complex_func in terms of B_k.basic_func.
Or is there a better pattern for my problem ? I know that I can declare complex_impl as a regular function taking basic_func as a parameter, without using a functor at all :
let complex_impl basic_func params =
...
basic_func ...
...
But in my case complex_impl uses many basic functions of A, and I think that the paradigm of functors is clearer and less error-prone.
Edit : I followed this answer, but in fact, A uses some type t that is specialized in B :
module type A = sig
type t
val basic_func: t -> unit
val complex_func: t -> unit
end
module MyFunctor :
functor (SomeA : A) ->
struct
let complex_impl (x : SomeA.t) =
SomeA.basic_func x
...
end
module rec B : A = struct
type t = int
val basic_func (x : t) = ...
val complex_func (x : t) =
let module Impl = MyFunctor(B) in
Impl.complex_impl x
end
And now I get the error (for x at line Impl.complex_impl x) :
This expression has type t = int but an expression was expected of type B.t
Edit 2 : I solved this second problem with the following code :
module rec B :
A with type t = int
= struct
type t = int
...
end
You can use recursive modules just like you'd write recursive let bindings
module type A = sig
val basic_func : unit -> int
val complex_func : unit -> int
end
module MyFunctor =
functor (SomeA : A) ->
struct
let complex_impl = SomeA.basic_func
end
module rec B : A = struct
let basic_func () = 0
let complex_func () =
let module Impl = MyFunctor(B) in
Impl.complex_impl ()
end
Note (a) the module rec bit in the definition of B and (b) that I am required to provide a module signature for a recursive module definition.
# B.basic_func ();;
- : int = 0
# B.complex_func ();;
- : int = 0
There's a small caveat, however, in that this only works because the signature A has only values which are function types. It is thus known as a "safe module". If basic_func and complex_func were values instead of function types then it would fail upon compilation
Error: Cannot safely evaluate the definition
of the recursively-defined module B

Explicit polymorphic type in record

In OCaml, it is possible to define explicit polymorphic type in a record
type foo = { f : 'a. unit -> 'a };;
It seems we can assign only general values to f like
{ f = fun () -> failwith ""; }
or
{ f = fun () -> exit 1; }
How to use this language feature in real world? Is there any good practical example?
This isn't really connected with records. If you declare any function to have type 'a. unit -> 'a (takes nothing and returns whatever the caller wanted) then you can only use it for functions that don't return.
Here's a slightly more useful example: a record containing a function for finding the length of lists (of any type).
# type foo = { f : 'a. 'a list -> int };;
type foo = { f : 'a. 'a list -> int; }
# let foo = { f = List.length };;
val foo : foo = {f = <fun>}
# foo.f [1;2;3];;
- : int = 3
It can be useful if you wanted to pass a function like List.length as an argument to another function, and have it use it on multiple types:
Say we want to pass List.length to test. We can't do it directly:
# let test fn = fn [1;2;3] + fn ["a";"b";"c"];;
Error: This expression has type string but an expression was expected of type
int
But we can use a record:
# let test foo = foo.f [1;2;3] + foo.f ["a";"b";"c"];;
val test : foo -> int = <fun>
# test foo;;
- : int = 6

How can I declare a module (actually a Set.Make) in mli file?

I have airport.mli and airport.ml.
In airport.ml, I have
module AirportSet = Set.Make(struct type t = airport let compare = compare end);;
This is no problem.
I then have a function
val get_all_airport : unit -> AirportSet.t;;
, which generates a AirportSet.
so in airport.mli, I need to show the module AirportSet so AirportSet is recognized.
How can I do that?
module AirportSet : (Set.S with type elt = airport)
(The parens are actually unnecessary, putting them there so that you know this is a signature expected, in the general case of the form sig ... end).
The elegant solution is was gasche proposed; a more pragmatic/straight forward/naive solution is to simply use the ocaml-compiler ocamlc to infer (-i) the type of the module for you:
ocamlc -i airport.ml
which gives you a more verbose type like
AirportSet :
sig
type elt = airport
type t
val empty : t
val is_empty : t -> bool
val mem : elt -> t -> bool
...
val split : elt -> t -> t * bool * t
end