Partial application of Printf.ksprintf - printf

I'm trying to write a version of Printf.printf that always appends a newline character after writing its formatted output. My first attempt was
# let say fmt = Printf.ksprintf print_endline fmt;;
val say : ('a, unit, string, unit) format4 -> 'a = <fun>
The type signature looks right and say works as expected. I noticed that fmt is listed twice, and thought that partial application could eliminate it. So I tried this instead:
# let say = Printf.ksprintf print_endline;;
val say : ('_weak1, unit, string, unit) format4 -> '_weak1 = <fun>
The function definition looks cleaner, but the type signature looks wrong and say no longer works as expected. For example, say doesn't type check if the format string needs a variable number of arguments: I get an error that say "is applied to too many arguments".
I can use the let say fmt = … implementation, but why doesn't partial application work?

OCaml's type-checker loses polymorphism during partial application. That is, when you partially apply a function, the resulting function is no longer polymorphic. That's why you see '_weak1 in the second type signature.
When you include the fmt argument, you help the type-checker recognize that polymorphism is still present.
This process is called "eta conversion." Removing your fmt argument is "eta reduction" and adding it back in is called "eta expansion." You may encounter that terminology when working with other functional programming languages.

This is the value restriction at work: https://ocaml.org/manual/polymorphism.html#s:weak-polymorphism . In brief, only syntactic values can be safely generalized in let-binding in presence of mutable variables in the language.
In particular,
let f = fun x -> g y x
is a syntactic value that can be generalized, whereas
let f = g y
is a computation that cannot (always) be generalized.
A example works quite well to illustrate the issue, consider:
let fake_pair x =
let store = ref None in
fun y ->
match !store with
| None ->
store := Some y;
x, y
| Some s ->
x, s
then the type of fake_pair is 'a -> 'b -> 'a * 'b.
However, once partially applied
let p = fake_pair 0
we have initialized the store mutable value, and it is important that all subsequent call to p share the same type (because they must match the stored value). Thus the type of p is '_weak1 -> int * '_weak1 where '_weak1 is a weak type variable, aka a temporary placeholder for a concrete type.

Related

How can I access image constructors for a pattern-matching in Vg, Ocaml?

I'm trying to re-write the equal function from the Vg.I module for Ocaml but when I try to do a pattern-matching with an image (of type t) I got an error.
Here is my code :
open Vg;;
open Gg;;
let rec decompose i = match i with
| I.Primitive x -> Printf.printf "primitive\n\n"
| I.Cut(a,p,i) -> Printf.printf "cut\n\n"; decompose i
| I.Cut_glyphs(a,r,i) -> Printf.printf "cut_glyphs\n\n"; decompose i
| I.Blend(b,a,i1,i2) ->
Printf.printf "blend: t1\n\n"; decompose i1;
Printf.printf "blend: t2\n\n"; decompose i2
| I.Tr(tr,i) -> Printf.printf "tr\n\n"; decompose i
| _ -> failwith "some error";;
and here is the error
| I.Primitive x -> Printf.printf "primitive\n\n"
^^^^^^^^^^^
Error: Unbound constructor I.Primitive
I've also tried 'Vg.Primitive' and just 'Primitive' (even if it didn't make a lot of sense '^^) but I've got the same error every time.
If anyone knows how to properly use these constructors in a pattern-matching it would really help
Thanks in advance
The type image of the Vg library is abstract.
This means that the Vg library considers that the explicit definition of
this type is an implementation detail that no external users should rely upon.
In particular, different variants of the library may use different implementation for this type.
Consequently, you should not pattern match on values of this type, and OCaml module system enforces that you cannot do so.
To complement octachron's excellent answer, consider a simple contrived example. A module A which contains a type t. Internally this type has a constructor A_ that takes an int. But the module's signature does not expose this type constructor. We only know the type exists, but nothing else about it. Values of that type, therefore can only be manipulated via the functions the module exposes.
Within the module A, that type can be pattern-matched as normal.
module A : sig
type t
val make : int -> t
val get_val : t -> int
end = struct
type t = A_ of int
let make x = A_ x
let get_val (A_ x) = x
end
utop # A.A_ 42;;
Error: Unbound constructor A.A_
utop # A.make 42;;
- : A.t = <abstr>
utop # A.(make 42 |> get_val);;
- : int = 42

List of types from a function type

I would like to make a function that given a function type (e.g. String -> Nat -> Bool), would return a list of types corresponding to that function type (e.g. [String, Nat, Bool]). Presumably the signature of such a function would be Type -> List Type, but I am struggling to determine how it would be implemented.
I don't believe it could be done in general, because you cannot patter-match on functions. Neither can you check for the type of a function. That is not what dependent types are about. Just like in Haskell or OCaml the only thing you can actually do with a function is apply it to some argument. However, I devised some trick which might do:
myFun : {a, b : Type} -> (a -> b) -> List Type
myFun {a} {b} _ = [a, b]
Now the problem is that a -> b is the only signature that would match any arbitrary function. But, of course it does not behave the way you'd like for functions with arity higher than one:
> myFun (+)
[Integer, Integer -> Integer] : List Type
So some sort of recursive call to itself would be necessary to extract more argument types:
myFun : {a, b : Type} -> (a -> b) -> List Type
myFun {a} {b} _ = a :: myFun b
The problem here is that b is an arbitrary type, not necessarily a function type and there is no way I can figure out to dynamically check whether it is a function or not, so I suppose this is as much as you can do with Idris.
However, dynamic checking for types (at least in my opinion) is not a feature to be desired in a statically typed language. After all the whole point of static typing is to specify in advance what kind of arguments a function can handle and prevent calling functions with invalid arguments at compile time. So basically you probably don't really need it at all. If you specified what you grander goal was, someone would likely have shown you the right way of doing it.

Is there a nice way to use `->` directly as a function in Idris?

One can return a type in a function in Idris, for example
t : Type -> Type -> Type
t a b = a -> b
But the situation came up (when experimenting with writing some parsers) that I wanted to use -> to fold a list of types, ie
typeFold : List Type -> Type
typeFold = foldr1 (->)
So that typeFold [String, Int] would give String -> Int : Type. This doesn't compile though:
error: no implicit arguments allowed
here, expected: ")",
dependent type signature,
expression, name
typeFold = foldr1 (->)
^
But this works fine:
t : Type -> Type -> Type
t a b = a -> b
typeFold : List Type -> Type
typeFold = foldr1 t
Is there a better way to work with ->, and if not is it worth raising as a feature request?
The problem with using -> in this way is that it's not a type constructor but a binder, where the name bound for the domain is in scope in the range, so -> itself doesn't have a type directly. Your definition of t for example wouldn't capture a dependent type like (x : Nat) -> P x.
While it is a bit fiddly, what you're doing is the right way to do this. I'm not convinced we should make special syntax for (->) as a type constructor - partly because it really isn't one, and partly because it feels like it would lead to more confusion when it doesn't work with dependent types.
The Data.Morphisms module provides something like this, except you have to do all the wrapping/unwrapping around the Morphism "newtype".

Error: Cannot safely evaluate the definition of the recursively-defined module

I'm curious to understand why this error happens and which is the best way to get around it.
I have a couple of files types.ml and types.mli which define a variant type value that can be of many different builtin OCaml types (float, int, list, map, set, etc..).
Since I have to use the std-lib over this variant type I needed to concretize the Set module through the functor to be able to use sets of value type by defining the ValueSet module.
The final .ml file is something like:
module rec I :
sig
type value =
Nil
| Int of int
| Float of float
| Complex of Complex.t
| String of string
| List of (value list) ref
| Array of value array
| Map of (value, value) Hashtbl.t
| Set of ValueSet.t ref
| Stack of value Stack.t
...
type t = value
val compare : t -> t -> int
end
= struct
(* same variant type *)
and string_value v =
match v with
(* other cases *)
| Set l -> sprintf "{%s} : set" (ValueSet.fold (fun i v -> v^(string_value i)^" ") !l "")
end
and OrderedValue :
sig
type t = I.value
val compare : t -> t -> int
end
= struct
type t = I.value
let compare = Pervasives.compare
end
and ValueSet : Set.S with type elt = I.value = Set.Make(I)
As you can see I had to define the ValueSet module from the functor to be able to use that datatype. The problem occurs when I want to use that module inside the declaration of I. So that I obtain the following error:
Error: Cannot safely evaluate the definition of the recursively-defined module I
Why does this happen? Which is a good way to solve it? And just to know, is my approach to what I'm trying to do correct? Apart from that it works as intended (I'm able to use the ValueSet type with my operations in other modules, but I have to comment the involved line in types.ml to pass compilation phase).
I tried to remove all the superfluous code and reduce the code to essential needed to investigate this error.. if it's not enought just ask :)
EDIT: according to OCaml reference we have that
Currently, the compiler requires that all dependency cycles between the recursively-defined module identifiers go through at least one “safe” module. A module is “safe” if all value definitions that it contains have function types typexpr1 -> typexpr2.
This is everything I found so far, but I don't get the exact meaning..
Thank in advance
After fixing the obvious errors, your example does compile (with OCaml 3.10, but I think this hasn't changed since recursive modules were introduced in 3.07). Hopefully my explanations below will help you find what, amongst the definitions you left out, caused your code to be rejected.
Here is some example code that is accepted:
module rec Value : sig
type t =
Nil
| Set of ValueSet.t
val compare : t -> t -> int
val nil : t
(*val f_empty : unit -> t*)
end
= struct
type t =
Nil
| Set of ValueSet.t
let compare = Pervasives.compare
let nil = Nil
(*let f_empty () = Set ValueSet.empty*)
end
and ValueSet : Set.S with type elt = Value.t = Set.Make(Value)
At the expression level, the module Value has no dependency on ValueSet. Therefore the compiler generates the code to initialize Value before the code to initialize Value, and all goes well.
Now try commenting out the definition of f_empty.
File "simple.ml", line 11, characters 2-200:
Cannot safely evaluate the definition of the recursively-defined module Value
Now Value does depend on ValueSet, and ValueSet always depends on Value because of the compare function. So they are mutually recursive, and the “safe module” condition must apply.
Currently, the compiler requires that all dependency cycles between the
recursively-defined module identifiers go through at least one "safe" module. A
module is "safe" if all value definitions that it contains have function types
typexpr_1 -> typexpr_2.
Here, ValueSet isn't safe because of ValueSet.empty, and Value isn't safe because of nil.
The reason to the “safe module” condition is the chosen implementation technique for recursive module:
Evaluation of a recursive module definition proceeds
by building initial values for the safe modules involved, binding all
(functional) values to fun _ -> raise Undefined_recursive_module. The defining
module expressions are then evaluated, and the initial values for the safe
modules are replaced by the values thus computed.
If you comment out the declaration of nil in the signature of Value, you can leave the definition and declaration of f_empty. That's because Value is now a safe module: it contains only functions. It's ok to leave the definition of nil in the implementation: the implementation of Value is not a safe module, but Value itself (which is its implementation coerced to a signature) is safe.
I'm really not sure what kind of syntax you're using in the signature that allows let ... I'm going to assume it was a mistake while reducing the code for us. You also don't need that OrderedType definition, possibly another fiddling error for us, since you don't use it in parameterisation of the Set module.
Aside from that, I have no problem running the following in the toplevel. Since this works pretty directly, I am unsure how you're getting that error.
module rec Value :
sig
type t =
| Nil
| Int of int
| Float of float
| String of string
| Set of ValueSet.t
val compare : t -> t -> int
val to_string : t -> string
end = struct
type t =
| Nil
| Int of int
| Float of float
| String of string
| Set of ValueSet.t
let compare = Pervasives.compare
let rec to_string = function
| Nil -> ""
| Int x -> string_of_int x
| Float x -> string_of_float x
| String x -> x
| Set l ->
Printf.sprintf "{%s} : set"
(ValueSet.fold (fun i v -> v^(to_string i)^" ") l "")
end
and ValueSet : Set.S with type elt = Value.t = Set.Make (Value)

Understanding functors in OCaml

I'm quite stuck with the following functor problem in OCaml. I paste some of the code just to let you understand. Basically
I defined these two modules in pctl.ml:
module type ProbPA = sig
include Hashtbl.HashedType
val next: t -> (t * float) list
val print: t -> float -> unit
end
module type M = sig
type s
val set_error: float -> unit
val check: s -> formula -> bool
val check_path: s -> path_formula -> float
val check_suite: s -> suite -> unit
end
and the following functor:
module Make(P: ProbPA): (M with type s = P.t) = struct
type s = P.t
(* implementation *)
end
Then to actually use these modules I defined a new module directly in a file called prism.ml:
type state = value array
type t = state
type value =
| VBOOL of bool
| VINT of int
| VFLOAT of float
| VUNSET
(* all the functions required *)
From a third source (formulas.ml) I used the functor with Prism module:
module PrismPctl = Pctl.Make(Prism)
open PrismPctl
And finally from main.ml
open Formulas.PrismPctl
(* code to prepare the object *)
PrismPctl.check_suite s.sys_state suite (* error here *)
and compiles gives the following error
Error: This expression has type Prism.state = Prism.value array
but an expression was expected of type Formulas.PrismPctl.s
From what I can understand there a sort of bad aliasing of the names, they are the same (since value array is the type defined as t and it's used M with type s = P.t in the functor) but the type checker doesn't consider them the same.
I really don't understand where is the problem, can anyone help me?
Thanks in advance
(You post non-compilable code. That's a bad idea because it may make it harder for people to help you, and because reducing your problem down to a simple example is sometimes enough to solve it. But I think I see your difficulty anyway.)
Inside formulas.ml, Ocaml can see that PrismPctl.s = Pctl.Make(Prism).t = Prism.t; the first equality is from the definition of PrismPctl, and the second equality is from the signature of Pctl.Make (specifically the with type s = P.t bit).
If you don't write an mli file for Formulas, your code should compile. So the problem must be that the .mli file you wrote doesn't mention the right equality. You don't show your .mli files (you should, they're part of the problem), but presumably you wrote
module PrismPctl : Pctl.M
That's not enough: when the compiler compiles main.ml, it won't know anything about PrismPctl that's not specified in formulas.mli. You need to specify either
module PrismPctl : Pctl.M with type s = Prism.t
or, assuming you included with type s = P.t in the signature of Make in pctl.mli
module PrismPctl : Pctl.M with type s = Pctl.Make(Prism).s
This is a problem I ran into as well when learning more about these. When you create the functor you expose the signature of the functor, in this case M. It contains an abstract type s, parameterized by the functor, and anything more specific is not exposed to the outside. Thus, accessing any record element of s (as in sys_state) will result in a type error, as you've encountered.
The rest looks alright. It is definitely hard to get into using functors properly, but remember that you can only manipulate instances of the type parameterized by the functor through the interface/signature being exposed by the functor.