I'm writing a library to handle simple images in Standard ML. It should support different types used as colour for each pixel, e.g. bool, Word8.word, etc.
I've got a abstype 'a image with all common functions defined independent of representation ('a is the colour representation) , but the output formats differ, so I'd like to have different structures.
Is there a way to "open" an abstype inside a structure? I can only get this working in a very ugly way:
abstype 'clr absimage = Image of {width : int, height : int, data : 'clr array array}
with
fun createFunc (w, h) f = Image {width = w, height = h, data = ...}
fun createBlank (w, h) clr = createFunc (w, h) (fn _ => clr)
...
end
signature IMAGE = sig
type colour
type image
val createFunc : (int * int) -> (int * int -> colour) -> image
val createBlank : (int * int) -> colour -> image
...
val toBinPPM : image -> string -> unit
end
functor ImageFn(C : sig type colour end) = struct
open C
type image = colour absimage
val createFunc = createFunc
val createBlank = createBlank
...
end
structure Image8 :> IMAGE = struct
structure T = ImageFn(struct type colour = Word8.word end)
open T
fun toBinPPM img filename = ...
end
In particular, the definition of the functor requires to write statements like val name = name for all functions defined in the with ... end part of abstype.
Or is my approach completely wrong?
This combination of abstype and signature is my attempt to recreate OOP's abstract class with common methods from abstype and require implementation of other methods in all structures using the signature
P.S. Why does SML disallow statements like open (ImageFn(struct ... end)) and forces to use a temporary structure (T in the above code)?
There is no reason to use abstype in today's SML. Consider it deprecated. It is a relict of pre-module times. You can achieve the same effect of hiding the constructors of a type with structures, signatures and sealing (the :> operator), but in a more flexible and consistent manner. That also explains why it does not integrate nicely with modules -- it predates them and was essentially replaced by them.
In your concrete example, instead of using abstype, simply define image as a datatype directly in the body of the ImageFn functor, and hide its constructors with a signature annotation, like so:
signature IMAGE =
sig
type colour
type image
val createFunc : int * int -> (int * int -> colour) -> image
val createBlank : int * int -> colour -> image
...
end
signature IMAGE8 =
sig
include IMAGE
val toBinPPM : image -> string -> unit
end
functor ImageFn(type colour) :> IMAGE =
struct
datatype image = Image of {width : int, height : int, data : colour array array}
fun createFunc (w, h) f = Image {width = w, height = h, data = ...}
fun createBlank (w, h) clr = createFunc (w, h) (fn _ => clr)
...
end
structure Image8 :> IMAGE8 =
struct
structure T = ImageFn(type colour = Word8.word)
open T
fun toBinPPM img filename = ...
end
Edit: In fact, it isn't even necessary in this case to define image as a datatype. A plain type would do just as well and makes the code slightly simpler:
type image = {width : int, height : int, data : colour array array}
As for your PS question: yeah, I don't know either. There is no particular reason. Some SML dialects implement it as an extension.
Related
I'm writing a functor to implement sets in standard ML. Since sets don't allow duplicates and I don't want it to be constrained to equality types, it's declared like this:
signature SET = sig
type t
type 'a set
val add : t -> t set -> t set
...
end
functor ListSet (EQ : sig type t val equal : t * t -> bool end) :> SET = struct
type t = EQ.t
type 'a set = 'a list
fun add x s = ...
...
end
I use :> so that list operations cannot be used on sets, hiding the internal implementation and allowing to change the representation (e.g. to a BST)
However, this also hides type t, therefore function add when used like this gives an error:
structure IntSet = ListSet (struct type t = int val equal = op= end);
val s0 = IntSet.empty
val s1 = IntSet.add 0 s0
Function: IntSet.add : IntSet.t -> IntSet.t IntSet.set -> IntSet.t IntSet.set
Argument: 0 : int
Reason:
Can't unify int (*In Basis*) with
IntSet.t (*Created from applying functor ListEqSet*)
(Different type constructors)
Is there a way to keep the implementation hidden but somehow expose the type t? Or is there a better approach to implementing sets?
P.S. The main reason I can't have equality types is to allow sets of sets, and while I can keep the lists sorted and define eqtype 'a set, it adds unnecessary complexity.
You need what's sometimes called a translucent signature ascription, that is, you hide some of the types and expose the others:
functor ListSet (Eq : EQ) :> SET where type t = Eq.t = ...
You have to expose the type t using a type refinement:
functor ListSet (Eq : sig type t val equal : t * t -> bool end) :> SET where type t = Eq.t =
struct
...
end
This is equivalent to an expansion of the signature SET where the type t is specified transparently as
type t = Eq.t
I've read some similar questions and some online examples, but I still don't know how to write an .mli file in this particular case.
In my project, I use a general map module with int keys, which then I specialize depending on the values I want to store in. Let's say I want to use it to store pairs, so I have a file like this:
file dataStr.ml:
module IntOrder =
struct
type t = int
let compare = Pervasives.compare
end
module IntMap = Map.Make( IntOrder )
type couple = int * int
(* pretty names *)
type int2couple = couple IntMap.t
module Couples = struct type t = int2couple end
A file using this submodule would be:
file useMap.ml:
open DataStr
let use k m =
IntMap.add k ((Random.int 6), (Random.int 8)) m
with interface:
file useMap.mli:
open DataStr
val use : int -> Couples.t -> Couples.t
So far, so good.
Let's now suppose that I want to expose submodule Couples, but not type int2couple. I would then write this interface:
file dataStr.mli:
module IntMap : Map.S with type key = int
module Couples : sig type t end
(*
I'd like to avoid the redundancy of using
module Couples : sig type t = (int * int) IntMap.t end
*)
Problem is, if I do add this interface, I get this compile error:
Error: The implementation useMap.ml does not match the interface useMap.cmi:
Values do not match:
val use :
DataStr.IntMap.key ->
(int * int) DataStr.IntMap.t -> (int * int) DataStr.IntMap.t
is not included in
val use : int -> DataStr.Couples.t -> DataStr.Couples.t
Is there a way to write an interface that lets me do what I want to do, other than the "redundant" one in the comment?
As noted in the comments, there is no way to avoid redundancy between interface (mli file) and implementation (ml files) when instantiating a functor.
The best you can do is the following:
$ cat dataStr.mli:
module IntMap : Map.S with type key = int
type couple = int * int
type int2couple = couple IntMap.t
module Couples : sig type t = int2couple end
$ cat dataStr.ml:
module IntOrder =
struct
type t = int
let compare = Pervasives.compare
end
module IntMap = Map.Make( IntOrder )
type couple = int * int
type int2couple = couple IntMap.t
module Couples = struct type t = int2couple end
I am working on recursive modules in OCaml and I have some trouble accessing type fields.
If I try to do :
module A = struct type t = { name : string; } end
module A2 =
struct
include A
let getName (x:t) = x.name
end;;
Everything is alright. However, I need a more complex type, forcing me to define my type in a recursive module.
module rec B:Set.OrderedType =
struct
type t = {name: string; set : S.t}
let compare _ _ = 0
end
and S:Set.S = Set.Make (B);;
Everything still works perfectly. However, the following module is incorrect :
module B2 =
struct
include B
let get_name (x:t) = x.name
end;;
The returned error is "Unbound record field name". What is the problem ?
module rec B:Set.OrderedType =
Your recursive definition says that module B has the signature Set.OrderedType, which hides the definition of t and in this case, its projections. In Set.OrderedType, the type t is abstract, like this: type t;;.
If you want to show the definition of type t, it must be part of the signature. The first example works because you did not offer a signature for module A, so it was typed by default with a signature that exports everything.
The example below works for me with OCaml 4.02.1.
module rec B:
sig type t = { name:string ; set : S.t } val compare: t -> t -> int end
=
struct
type t = {name: string; set : S.t}
let compare _ _ = 0
end
and S:Set.S = Set.Make (B);;
The toplevel confirms the definition thus:
module rec B :
sig type t = { name : string; set : S.t; } val compare : t -> t -> int end
and S : Set.S
I have built a complicated structure with modules, which has a recursion inside. The compilation gives me an error I can't solve (though I don't think it is really due to the recursion). Could anyone help?
First, an interface ZONE and a functor ZoneFunPrec are defined:
(* zone.ml *)
module type ZONE = sig
type prop
type info
type t
end
(* zoneFunPrec.ml *)
open Prop
open Zonesm
module ZoneFunPrec (Prop : PROP)(Prec: ZONESM with type prop = Prop.t) = struct
type prop = Prop.t
type info = { mark: int option; prec: Prec.t option }
type t = { prop: prop; info: info }
end
A functor ZonesFun and an interface ZONES whose element is a list of zones with same property:
(* zones.ml *)
open Prop
open Zone
module type ZONES = sig
type prop
type zone
type t
end
module ZonesFun (Prop: PROP) (Zone: ZONE with type prop = Prop.t) = struct
type prop = Prop.t
type zone = Zone.t
type t = | ZSbot | ZS of zone list
end
A functor ZonesmFun and an interface ZONESM whose element is a map from String into ZONES with same property:
(* zonesm.ml *)
open Prop
open Zone
open Zones
module SMap = Map.Make(String)
module type ZONESM = sig
type prop
type zones
type t
end
module ZonesmFun (Prop: PROP)
(Zone: ZONE with type prop = Prop.t)
(Zones: ZONES with type zone = Zone.t) = struct
type prop = Prop.t
type zones = Zones.t
type t = | Bot | ZSM of Zones.t SMap.t
end
And then, I try to build some modules from EEA whose interface is PROP:
(* modules.ml *)
open E_expression_abs
open Zone
open ZoneFunPrec
open Zones
open Zonesm
module EEA = E_expression_abs
module rec ZoneEEA : ZONE = ZoneFunPrec(EEA)(ZonesmEEA)
and ZonesEEA : ZONES = ZonesFun(EEA)(ZoneEEA)
and ZonesmEEA : ZONESM = ZonesmFun(EEA)(ZoneEEA)(ZonesEEA)
In my makefile, the order of compilation is same as the order I listed the files above. Then the compiler gives me an error in line module rec...:
File "domains/modules.ml", line 7, characters 45-54:
Error: Signature mismatch:
Modules do not match:
sig
type prop = ZonesmEEA.prop
type zones = ZonesmEEA.zones
type t = ZonesmEEA.t
end
is not included in
sig type prop = EEA.t type zones type t end
Type declarations do not match:
type prop = ZonesmEEA.prop
is not included in
type prop = EEA.t
So apparently, the compiler doesn't manage to know ZonesEEA.prop is actually EEA.t...
I am not good at recursive module typing but... I guess your example is simplified to the following
module type S = sig type t end
module rec R : S = (R : S with type t = int)
OCaml rejects this code due to signature mismatch. This is since R has incompatible types in the left and right hands of the equation. You must say:
module rec R : S with type t = int = (R : S with type t = int)
R must have the same module type in the both hands, since R is defined recursively.
If not recursive you can say:
module M = struct type t = int end
module N : S = (M : S with type t = int)
The module type of the left hand side of the equation can be more abstract than the right one.
I understand in OCaml there are concepts of interfaces and module.
And I understand how to use them now.
However, what I don't understand is how to fully utilise them.
For example, in Java, let's say we have a interface Map and we also have Hashtable and HashMap that implement Map.
In code, I can do like:
Map m = new Hashtable();
m.put("key", value);
Someday, if I change my mind, I can change to Hashmap very quickly by changing Map m = new Hashtable(); to Map m = new HashMap();, right?
But how can I easily do that in Ocaml?
For example, I have MapSig and 'HashMap:MapSigand "Hashtable:MapSig in OCaml.
How can I change the implementation easily?
I don't think I can because in OCaml I have to do like:
let m = Hashtable.create ();;
Hashtable.put m key value;;
if I want to use HashMap instead, I have to replace every Hashtable with HashMap in the code, right?
Edit:
I am not only seeking a way to make a alias to modules. I also consider the validity of implementations, i.e., whether the implementation follow the desired interface.
For example, in above Java example, only if HashMap has implemented Map interface, I can replace Hashtable with HashMap. otherwise, Java compiler will complain.
but if I do module M = Hashtable in OCaml, and if HashMap does not follow MapSig and I replace Hashtable with HashMap, what will happen? I think compiler won't complain, right?
Here's an example that shows what I think you're asking for:
# module type HASH = sig type t val hash : t -> int end ;;
module type HASH = sig type t val hash : t -> int end
# module I = struct type t = int let hash i = i end ;;
module I : sig type t = int val hash : 'a -> 'a end
# module J = struct type t = int end ;;
module J : sig type t = int end
# module M : HASH = I ;;
module M : HASH
# module N : HASH = J ;;
Error: Signature mismatch:
Modules do not match: sig type t = int end is not included in HASH
The field `hash' is required but not provided
The extra ": HASH" specifies that the module must match the HASH signature (and it also restricts it to that signature).
Just as a side comment, I believe the OCaml module system is world famous for its expressivity (at least in module system circles). I'm still a beginner at it, but it is worth studying.
Since 3.12.1 OCaml allows this syntax for opening and aliasing modules:
let foo .... =
let module HashTable = HashMap in (* magic is here *)
let h = HashTable.create () in
....
So u just need to rename module what you are using where you are using it.
The most direct correspondence between your Java example and OCaml is using a functor (what OCaml calls a static function from a module to a module). So suppose you have the following implemented in OCaml:
module type Map = sig
(* For simplicity assume any key and value type is allowed *)
type ('k, 'v) t
val make : unit -> ('k, 'v) t
val put : ('k, 'v) t -> ~key:'k -> ~value:'v -> unit
end
module Hashtable : Map = struct ... end
module HashMap : Map = struct ... end
Then you would write a functor like this:
module MyFunctor(Map : Map) = struct
let my_map =
let map = Map.make () in
Map.put map ~key ~value;
map
end
Then you would instantiate a module using the functor:
module MyModule = MyFunctor(Hashtable)
And voila, changing the implementation is a one-line diff because both the module implementations conform to the Map signature:
module MyModule = MyFunctor(HashMap)