Certain AST nodes not possible in Parsetree.signature (mli files) - ocaml

I'm writing a tool that generates ml stubs from mli files. I have the meaningful mappings complete (var f : int -> float to let f _ = 0.), but I'm having a little trouble reasoning about the AST nodes for classes and modules, specifically the Pmty_* and Pcty_* nodes. These two types of nodes (given the type hierarchy) seem to most most associated with mli files. Some of the trivial members--which appear in -dparsetrees of mli files (like Pmty_ident and Pcty_constr) have obvious mappings to nodes most associated with ml files (again by the hierarchy of the signature and structure types, in the aforementioned example to Pmod_ident and Pcl_constr). However, some of the nodes don't have an obvious parallel. Specifically, I'm having trouble reasoning about:
Pmty_with and Pmty_typeof - it seems like these two can never be parsed from a valid mli file; they only occur in a structure context that has a module_type as one of its members (I've checked my suspicions against all of OCaml's parser test files)
Pcty_signature - it seems like the only case this can occur is within a Psig_class_type (which I already directly map to Pstr_class_type); I against the OCaml test files and found a Pcty_signature only in this location, but are there other valid locations for it in an mli that I am missing?
Pcty_arrow - there are no test files containing this, so I can't be sure where it is valid, but my intuition says this also goes in a class_type context within a structure only (or within one of the other Pcty_*, in which case its conversion would be handled as a child by that node's mapping from Pcty_* to Pcl_*); is this incorrect?
I'm fairly deep into this and don't completely understand what's going on with all of these advanced language features and the AST nodes representing them, so here's an attempt at a simpler explanation of my questions:
Relevant types extracted from Parsetree:
type module_type_desc =
(* .. snip .. *)
| Pmty_with of module_type * with_constraint list
(* MT with ... *)
| Pmty_typeof of module_expr
(* module type of ME *)
type class_type_desc =
(* .. snip .. *)
| Pcty_signature of class_signature
(* object ... end *)
| Pcty_arrow of arg_label * core_type * class_type
(* T -> CT Simple
~l:T -> CT Labelled l
?l:T -> CT Optional l
*)
I believe that Pmty_with and Pmty_typeof can only occur in ml files (and not mli files). Is this assumption correct?
Can Pcty_signature occur as a node that isn't the child of a Psig_class_type?
Can a Pcty_arrow occur in a valid mli file? Where? As a child of what?
As I mentioned before, I'm fairly confident of my handling of every besides these two (modules and classes). In case the above isn't clear, here's an annotated snippet of the code that transforms Parsetree.signature -> Parsetree.structure with all of the non-module/class stuff removed for brevity:
(* Parsetree.signature -> Parsetree.structure *)
let rec stub signature_items =
(* Handles the module_type_desc *)
let rec stub_module_type module_type =
match module_type with
| { pmty_desc = type_; pmty_attributes = attrs; _ } ->
let expr =
match type_ with
| Pmty_ident ident -> Pmod_ident ident
| Pmty_signature signatures -> Pmod_structure (stub signatures)
| Pmty_functor (name, a, b) -> Pmod_functor (name, a, (stub_module_type b))
(* XXX: unclear if these two can occur in an mli *)
(* | Pmty_with (type_, constraints) -> _ TODO *)
(* | Pmty_typeof type_ -> _ TODO *)
| Pmty_extension ext -> Pmod_extension ext
| Pmty_alias name -> Pmod_ident name
in
make_module_expr expr attrs
in
(* The next three functions handles the module_type for single and multiple (rec) modules *)
let stub_module_decl module_decl =
match module_decl with
| { pmd_name = name; pmd_type = type_; pmd_attributes = attrs; _ } ->
make_module_binding name (stub_module_type type_) attrs
in
let stub_module module_ = Pstr_module (stub_module_decl module_)
and stub_modules modules = Pstr_recmodule (List.map stub_module_decl modules)
and stub_include include_ =
match include_ with
| { pincl_mod = module_type; pincl_attributes = attrs; _ } ->
Pstr_include (make_include_decl (stub_module_type module_type) attrs)
in
(* Handles classes (class_type) *)
let stub_classes classes =
(* Handles class_type_desc *)
let stub_class_descr descr =
let rec stub_class class_ =
let stub_class_type type_ =
match type_ with
| Pcty_constr (ident, types) -> Pcl_constr (ident, types)
| Pcty_signature class_ -> (* XXX: Is my below assumption true? *)
failwith "should be covered by Psig_class_type -> Pstr_class_type"
(* XXX: do we ever need to handle Pcty_arrow for mli files? *)
(* | Pcty_arrow (label, a, b) -> _ *)
| Pcty_extension ext -> Pcl_extension ext
| Pcty_open (override, ident, class_) ->
Pcl_open (override, ident, (stub_class class_))
in
match class_ with
| { pcty_desc = type_; pcty_attributes = attrs; _ } ->
make_class_expr (stub_class_type type_) attrs
in
match descr with
| { pci_virt = virt; pci_params = params; pci_name = name;
pci_expr = class_; pci_attributes = attrs } ->
make_class_decl virt params name (stub_class class_) attrs
in
Pstr_class (List.map stub_class_descr classes)
in
let transform_signature signature_item =
match signature_item with
| { psig_desc = signature; _ } ->
let desc =
match signature with
(* ... clip non-module/class stuff ... *)
| Psig_module module_ -> stub_module module_
| Psig_recmodule modules -> stub_modules modules
| Psig_include include_ -> stub_include include_
| Psig_class classes -> stub_classes classes
| Psig_class_type classes -> Pstr_class_type classes
in
make_str desc
in
List.map transform_signature signature_items
Unfortunately the module/class stuff is rather complex logic, so trimmed down there's still a lot. There are a ton of helps for creating the *_desc wrappers that encapsulate location in the file, attributes, etc., but those shouldn't be key to understanding how I'm handling modules and classes. But just for clarity, here are the types of all of the helpers:
val make_str : Parsetree.structure_item_desc -> Parsetree.structure_item
val make_module_expr :
Parsetree.module_expr_desc -> Parsetree.attributes -> Parsetree.module_expr
val make_module_binding :
string Asttypes.loc ->
Parsetree.module_expr -> Parsetree.attributes -> Parsetree.module_binding
val make_include_decl :
'a -> Parsetree.attributes -> 'a Parsetree.include_infos
val make_class_decl :
Asttypes.virtual_flag ->
(Parsetree.core_type * Asttypes.variance) list ->
string Asttypes.loc ->
'a -> Parsetree.attributes -> 'a Parsetree.class_infos
val make_class_expr :
Parsetree.class_expr_desc -> Parsetree.attributes -> Parsetree.class_expr
Relevant docs:
parsetree.ml (better than docs, because of some comments)
Edit: As an aside, besides reading documentation on these features (which didn't yield any AST patterns I didn't already know about), I recalled that the compiled can derive the interface from the implementation ocamlc -i. I traced down the variable in the compiler (it's called print_types) that's linked to this flag and found all of its uses, but it was not immediately apparent to me where at any of its uses code is called that derives the mli file (perhaps it is done progressively with the parse, since compiling produces a cmi?). If someone with more OCaml chops or more experience with the compiler could point me to where the mli file is derived, it may be easier to reverse engineer these module and class AST nodes.
Edit 2: I am also aware of How to auto-generate stubs from mli file?, however the answer there is "do it manually," which definitely conflicts with what I'm attempting! (The answerer also claims that such a tool would be trivial, but after pouring over these AST nodes for a while, I beg to differ!)

(I did not include the -dparsetree in my answer as it is heavy and not that interesting).
I believe that Pmty_with and Pmty_typeof can only occur in ml files (and not mli files). Is this assumption correct?
module M : module type of struct type t end with type t = int
As you can see from this valid mli file, this assumption isn't correct. .mli files require the same parser as .ml files do.
Can Pcty_signature occur as a node that isn't the child of a Psig_class_type?
class type c = object inherit object method x : int end end
Yes it can. Pcty_signature can occur anywhere a class type can occur. (note that there are two Pcty_signature here, one is the child of Pctf_inherit).
a Pcty_arrow occur in a valid mli file? Where? As a child of what?
class c' : int -> object method x : int end
Yes it can! And it can occur anywhere you'd indicate a class type.
Basically, you can consider that if a constructor can happen somewhere, then all the constructors of the same type can happen there too. Any type-related constructor can be in a .mli file (and non-type related constructors can happen too through the devious module type of).
If you have questions about where those are constructed, just take a look at parser.mly. Note that the same parser is used for the two file types.

This is a great game. Give me a list of AST Nodes, I'll write you a file that uses them all. :D
module K : module type of String
module M : Map.S with type key = K.t
class fakeref : K.t -> object
method get : K.t
method set : K.t -> unit
end
So, to summarize: Classes can take arguments, hence Pcty_arrow. Pcty_signature can also be the child of Psig_class, as shown above. The other two are standard module constructions that can absolutely appear in .mli files.
As for how ocamlc -i works ... well, it returns the signature inferred by the typechecker. There is no single point of access to this. You can read typing/HACKING.md if you want, but beware, the rabbit hole goes very deep. That being said, I do not think this will be all that helpful to achieve your goal.
My advice would be the following: all the nodes above are fairly easy to handle, except for with_type. This one is very hard, because it basically allows to compute in signatures. Just give up on that one for now.
Also, be aware that values, modules, module types, class and class types all have different namespaces. Pmty_ident x -> Pmod_ident x is not correct.

Related

evaluation monitor in ocaml

What I am trying to achieve is similar to a logging facility but for monitoring and streaming arbitrary data from a running simulation. Here is the simplified situation:
module Sim (V:VEC) = struct
module V = V
module M = struct type data = V.t end
let loop n init_data =
let running_data = ref init_data in
for _i = 1 to n do
(*?*) (* monitor here: data => outside world *)
rdata := process_data !rdata
done
end
While simulation loops, at the ? I may want to 'tap' data and accumulate it. Other times, I want to just let it run and disable the data stream with minimal overhead -- the ? is in a tight loop. So I want the streaming to be configurable with little cost.
What I have now is this:
module Sim (V:VEC) = struct
module V = V
module M = struct type data = V.t end
let data_monitor : (M.data -> unit) ref = ref (fun d -> ())
let loop n init_data =
let running_data = ref init_data in
for _i = 1 to n do
!data_monitor !rdata; (* monitor here *)
rdata := process_data !rdata
done
end
Ie. I put a stub monitoring function reference in there. In the actual application script I can then assign a function which e.g. accumulates the data values into a list or some such. It works.
So the question is: is this the best/lowest overhead/nicest way to achieve what I want?
This approach seems a bit hackish, I would rather use the module system instead of function pointers. However, the data type to be streamed is only defined inside the functor Sim. So making a monitoring function in another module Sampler outside of Sim and parametrizing Sim by that, seems not convenient and/or requires duplication of code or recursive modules. I tried, but I was not able to make all types equal.
Edit: Here is roughly what it tried without function refs:
module Sampler (V:VEC) : sig
module V : VEC
type data = V.t
val monitor_data : data -> unit
end
with type data = V.t = struct
module V = V
type data = V.t
let monitor_data data = store_away_the data
end
module Sim (V:VEC) (Sampler:??) : sig
...
end with type M.data = V.t
At the ?? I was not sure how to specify the output signature of Sampler, since the input signature VEC is still free; also I was not sure how exactly to make the type equality work. Maybe I'm doing it wrong here.
As discussed in the comments, you may be able to do something like this using higher-order functions (instead of having to resort to a higher-order functor):
module type VEC = sig type t end
module Vec = struct type t = unit end
module Sim (V : VEC) =
struct
module M = struct type data = V.t list end
let process x = x
let rec loop ?(monitor : M.data -> unit = ignore) n data =
if n <= 0 then data
else
(monitor [];
process data |> loop ~monitor (n - 1))
end
module MySim = Sim (Vec)
let monitor _ = print_endline "foo"
let () =
MySim.loop ~monitor 5 ()
loop above takes an optional function as argument, which you can pass with the syntax ~monitor:my_fun or ~monitor:(fun data -> ...). If you already have a value called monitor in scope, you can simply do ~monitor to pass it. If you don't pass anything, the default value is ignore (i.e. fun _ -> ()).
I also rewrote loop in recursive style. The code above prints foo 5 times. Note that your monitor function can still come from Sampler module, you just have no need to pass the whole module in when instantiating Sim.
EDIT: If you still want to declare a higher-order functor, here is how you do it (...)
EDIT 2: Changed the example given additional information that the reason for the higher-order functor is that there are multiple monitoring functions to call. Note that in this case, there are still other solutions besides a higher-order functor: you could group the functions into a record, and pass the record to loop. Similar to this, you could pass a first-class module. Or, you could create one function that takes a variant type whose cases indicate at what stage the monitoring function is being called, and carry the data associated with each stage. You can also use classes for this, though I wouldn't recommend it. The functor approach does have an advantage, however, if you are committed to declaring M inside Sim.
I have omitted the signature VEC from the sketch because I'm under the impression that the questioner understands where to add it, and there is no problem with it :)
module type SAMPLER =
sig
type data
val monitor : data -> unit
val monitor' : data list -> unit
end
(* These are created inside Sim. *)
module type DATA =
sig
type data
val show : data -> string
end
(* Note that I am using destructive substitution (:=) to avoid the need
to have a type data declared in the body of MySampler below. If you
use a regular type equality constraint, you need to add a field
"type data = Data.data" to the body. *)
module type SAMPLER_FN =
functor (Data : DATA) -> SAMPLER with type data := Data.data
(* This is the higher-order functor (it takes another functor as an
argument). *)
module Sim (Sampler_fn : SAMPLER_FN) =
struct
(* Corresponds to module "Sim.M" in the question. *)
module Data =
struct
type data = string
let show s = s
end
(* Note that without additional type constraints or rearrangements,
the type data is abstract to Sampler (more precisely, Sampler_fn
is parametric over Data). This means that Sampler_fn can't
analyze values of type data, which is why we need to provide
functions such as Data.show to Sampler_fn for instances of
Sampler_fn to be "useful". If you are trying to avoid this and
are having trouble with these specific constraints, let me
know. The ability to pass types and related values (functions
in this case) to Sampler_fn is the main argument in favor of
using a higher-order functor. *)
module Sampler = Sampler_fn (Data)
let simulate x =
(* Call one monitoring function. *)
Sampler.monitor "hi!";
(* Do some computation and call another monitoring function. *)
Sampler.monitor' ["hello"; "world"]
end
Usage:
module MySampler (Data : DATA) =
struct
let monitor data = data |> Data.show |> print_endline
let monitor' data =
data
|> List.map Data.show
|> String.concat " "
|> print_endline
end
module MySim = Sim (MySampler)
let () = MySim.simulate ()
This prints
hi!
hello world
For completeness:
Building on the functor part of antron's answer, this is what I am currently using. It is still a bit involved, and maybe it could be made more concise, but it has some nice advantages. Namely: the monitoring of individual aspects can be switched on and off in a centralized place (a module of type SAMPLER) and arbitrary types can be exported, even if they become defined only somewhere inside the simulator module.
I define the monitoring (=sampling) modules and module types like so:
module type STYPE = sig type t end
module type SSAMPLER = sig
type t
val ev : t React.event
val mon : t -> unit
end
module type SAMPLER_FN = functor (Data : STYPE) -> SSAMPLER
with type t := Data.t
(* stub sampler function for a single one *)
module Never : SAMPLER_FN = functor (Data : STYPE) -> struct
let ev = React.E.never
let mon = ignore
end
(* event primitive generating sampling function *)
module Event : SAMPLER_FN = functor (Data : STYPE) -> struct
let (ev : Data.t React.event), mon' = React.E.create ()
let mon = mon' ?step:None
end
Here, I am using the React library to generate output streams of data. The React.E.never event does nothing and corresponds to sampling being switched off. Then the full sampling configuration is specified like so:
(* the full sampling config *)
module type SAMPLER = sig
val sampler_pos : (module SAMPLER_FN)
val sampler_step : (module SAMPLER_FN)
(* and several more... *)
end
module NoSampling : SAMPLER = struct
let sampler_pos = (module Never: SAMPLER_FN)
let sampler_step = (module Never: SAMPLER_FN)
(* ... *)
end
(* default sampling config *)
module DefaultSampling : SAMPLER = struct
include NoSampling
(* this is only possible when using first class modules *)
let sampler_pos = (module Event : SAMPLER_FN)
end
One could avoid the first-class modules, but then the convenient inclusion and override in DefaultSampling would not be allowed.
In the simulation library code this is used like this:
module type VEC = sig
type t
val zeropos : t
val wiggle : t -> t
end
module Sim (V:VEC) (Sampler:SAMPLER) = struct
module V = V
module M = struct
type t = { mutable pos : V.t }
val create () = { pos=V.zeropos }
module Sampler_pos = (val Sampler.sampler_pos) (struct type nonrec t = t end)
let update f m = m.pos <- f m.pos
end
module Sampler_b = (val Sampler.sampler_b) (struct type t = int end)
let loop n (running_data:M.t) =
for i = 1 to n do
(* monitor step number: *)
Sampler_b.mon i;
(* monitor current pos: *)
Sampler_pos.mon running_data;
M.update V.wiggle running_data
done
end
Here, the sampling functors are applied at appropriate places in the simulation loop. (val ...) is again necessary only because of the first class module wrapping.
Finally, in an application script, one would then do this:
module Simulator = Sim (V) (DefaultSampling);;
let trace = Simulator.M.Sampler_pos.ev
|> React.E.fold (fun l h -> h :: l) []
|> React.S.hold [];;
let init_m = Simulator.M.create () in
Simulator.loop 100 init_m;;
React.S.value trace;;
The last line then contains the accumulated list of values of type Simulator.M.t that occurred during the loop. Monitoring of the step counter (a silly example) is switched off. By making another sampling functor of type SAMPLER and parametrizing Sim by that, one could further customize the monitoring, if desired.

Type-safe template variable substitution

I had this idea of a type-safe templating language that would use polymorphic variants as a source of type-safe variables that can be substituted for text, for example:
type 'a t = Var of 'a | Text of string | Join of 'a t * 'a t
let rec render ~vars = function
| Text source -> source
| Var label -> vars label
| Join (left, right) -> render left ~vars ^ render right ~vars
let result = render (Join (Var `Foo, Text "bar")) ~vars:(function `Foo -> "foo");;
let () = assert (result = "foobar")
This is all fine: compiler will enforce that you don't forget a substitution variable, or that you don't have a typo in a variable name—thanks to polymorphic variants.
However, I find two problems:
You can accidentally supply an unused variable.
If template contains no variables, you are still forced to supply a ~vars function, and the only one that would work would be fun _ -> "" or fun _ -> assert false, which compromizes type-safety in case the template ever changes.
I'm looking for advice on the problems above, but I also appreciate any applicable advice on API design.
Nothing force you to always use polymorphic variants. you could have a void type that is guaranteed to be different to every polymorphic variant.
type void
let empty_vars : void -> string = fun _ assert false
When you apply it to an empty template, you end up with
let result = render (Text "bar") ~vars:empty_vars
That way, if you later add a variable to your template, you will immediately notice it through the type error.
For unused variables, the best I can suggest is also not to use polymorphic variants:
type v = Foo
let result = render (Join (Var Foo, Text "bar")) ~vars:(function Foo -> "foo");;
This will only catch unused cases in the function definition, but of course if you remove a part of your template, you won't notice anything.
One other solution that have similar properties but may, or may not suit your taste is to use objects.
let rec render ~vars = function
| Text source -> source
| Var label -> label vars
| Join (left, right) -> render left ~vars ^ render right ~vars
let foo v = v#foo
let result = render (Join (Var foo, Text "bar")) ~vars:object method foo = "foo" end
That way you can keep the same pattern when no variables are used:
let result = render (Text "bar") ~vars:object end
But still no unused variable check.
I think it is impossible with polymorphic variants. The type of render function is:
val render : var:('a -> string) -> 'a t -> string
and the partial application render (Join (Var `Foo, Text "var")) has the following type:
vars:([> `Foo ] -> string) -> string
What you want to do is to close the opened variant type [> `Foo ] and restrict it to [ `Foo ] -> string in order to exclude functions which can get larger inputs like [< `Foo | `Bar ] -> string.
The only way to restrict the type is to add a type constraint: (vars : [ `Foo ] -> string), listing all the tags you want explicitly, but this is what you want to avoid...

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.

How handling a list of polymorphic variants?

Let two variant types :
type typeA =
| A1
| A2
;;
type typeB =
| B1 of typeA
| B2 of typeA
;;
and type-checking functions :
let isA1 = function A1 -> true | _ -> false;;
let isA2 = function A2 -> true | _ -> false;;
let isB1 = function B1 e -> true | _ -> false;;
let isB2 = function B2 e -> true | _ -> false;;
I'd like to create a list of those functions to check elements of type A or B
as they're of different types, I need polymorphic variants and I get :
type filterA =
{
handleA : typeA -> bool;
};;
type filterB =
{
handleB : typeB -> bool;
};;
type filterslist = [`FilterA of filterA | `FilterB of filterB] list ;;
let filters1 = [`FilterA { handleA = isA1 }; `FilterB { handleB = isB1 }] ;;
So now I want to iterate over filters1 to check the type of the argument
I tried :
let exec_filters filters event = List.iter (fun fil -> match fil with `FilterA -> fil.handleA event; ()| `FilterB -> fil.handleB event; () ) filters;;
but it's not appreciated :
Error: This expression has type [< `FilterA | `FilterB ]
but an expression was expected of type filterA
How can I handle this ?
The fact that you're using "type checking predicates" similar to Scheme or instanceOf indicates that there is probably something very wrong with your code. OCaml is a statically typed language, you should not:
iterate over filters1 to check the type of the argument I tried
Why are you doing this? If you are trying to handle multiple types, the way to do it is to use polymorphism. Polymorphic variants can be helpful for this, but I'm still not convinced that your code isn't just written in a strange way.
I think your code should read like:
let exec_filters filters event =
List.iter
(fun fil -> match fil with
| `FilterA fA -> fA.handleA event; ()
| `FilterB fB -> fB.handleB event; () )
filters;;
EDIT: However, this won't typecheck, since event can't have types typeA and typeB...
Why not make your initial variants (typeA and typeB) polymorphic?
What are you trying to do?
When you say
match fil with
`FilterA -> ...
You seem to expect that this will change the type of fil, but that's not how it works. The expression with the type filterA appears inside the pattern. You want something more like this:
match fil with
`FilterA { handleA = h } -> h event
I'm not sure I see the purpose of having your handlers return bool if you're going to use List.iter to execute them. This will return unit, and the bool values are going to be discarded.
Edit
There's a deeper typing problem, explained well by Ptival. So even if you fix your patterns you'll still need to rethink your plan. One possible thing to do would be to use variants (not necessarily polymorphic variants, by the way) to track the types of the events.

Ocaml - Forward Declaration (Classes)

I need to have two classes refering to each other. Is there any way in Ocaml to make Forward Declaration of one of them?
(I don't think it's possible as with easier stuff with word and).
Or maybe it is possible, but different way than how i tried?
Ocaml doesn't have anything like forward declarations (i.e. a promise that something will be defined eventually), but it has recursive definitions (i.e. a block of things that are declared and then immediately defined in terms of each other). Recursive definitions are possible between expressions, types, classes, and modules (and more); mutually recursive modules allow mixed sets of objects to be defined recursively.
You can solve your problem using a recursive definition with the keyword and:
class foo(x : bar) = object
method f () = x#h ()
method g () = 0
end
and bar(x : foo) = object
method h () = x#g()
end
Or you could use parameterized classes. Following the previous example you have:
class ['bar] foo (x : 'bar) =
object
method f () = x#h ()
method g () = 0
end
class ['foo] bar (x : 'foo) =
object
method h () = x#g()
end
The inferred interface is:
class ['a] foo : 'a ->
object
constraint 'a = < h : unit -> 'b; .. >
method f : unit -> 'b
method g : unit -> int
end
class ['a] bar : 'a ->
object
constraint 'a = < g : unit -> 'b; .. >
method h : unit -> 'b
end