Compose total and partial functions - ocaml

I can't wrap my head around where should I put parenthesis to get it working:
let read_lines filename =
let channel = open_in filename in
Std.input_list channel;;
let print_lines filename =
List.map print_string ((^) "\n") (read_lines filename);;
^ This is the closes I've got so far. If my terminology is vague: ((^) "\n") is what I call partial function (well, because it doesn't handle all of its arguments). print_string I call total function because... well, it handles all of its arguments.
Obviously, what I would like to happen is that:
List.map applies first ((^) "\n") to the element of the list.
List.map applies print_string to the result of #1.
How? :)

Maybe you want something like that?
# let ($) f g = fun x -> f(g x);;
val ( $ ) : ('a -> 'b) -> ('c -> 'a) -> 'c -> 'b = <fun>
# let f = print_string $ (fun s -> s^"\n");;
val f : string -> unit = <fun>
# List.iter f ["a";"b";"c";"d"];;
a
b
c
d
- : unit = ()
# let g = string_of_int $ ((+)1) $ int_of_string;;
val g : string -> string = <fun>
# g "1";;
- : string = "2"
Your code didn't work because missing parenthesis:
List.map print_string ((^) "\n") xs
is parsed as
(List.map print_string ((^) "\n")) xs
when you expected
List.map (print_string ((^) "\n")) xs

A few things: List.map is probably not what you want, since it will produce a list (of unit values) rather than just iterating. ((^) "\n") is probably also not what you want, as it prepends a newline, the "\n" being the first argument. (This is not a section as in Haskell, but a straightforward partial application.)
Here's a reasonable solution that is close to what (I think) you want:
let print_lines filename =
List.iter (fun str -> print_string (str ^ "\n")) (read_lines filename)
But I would rather write
let print_lines filename =
List.iter (Printf.printf "%s\n") (read_lines filename)
Which is both clearer and more efficient.

Related

Is this use of Obj.magic necessary?

I am reading a repository and I encountered this function in the body of some Yojson json parsing code:
let load_problems channel =
let open Yojson.Basic.Util in
let j = Yojson.Basic.from_channel channel in
...
let rec unpack x =
try magical (x |> to_int) with _ ->
try magical (x |> to_float) with _ ->
try magical (x |> to_bool) with _ ->
try
let v = x |> to_string in
if String.length v = 1 then magical v.[0] else magical v
with _ ->
try
x |> to_list |> List.map ~f:unpack |> magical
with _ -> raise (Failure "could not unpack")
in
...
where magical = Obj.magic. I understand what Obj.magic is (it's the equivalent to Unsafe.Coerce in Haskell), but I don't see why a type coercion is necessary here. The Yojson.Basic.Util functions the author uses should already either succeed or fail to do this conversion. Any intuition?
EDIT:
I feel I was depriving #glennsl of context, so here is the immediately following passage in which unpack is used:
let tf = j |> member "tasks" |> to_list |> List.map ~f:(fun j ->
let e = j |> member "examples" |> to_list in
let task_type = j |> member "request" |> deserialize_type in
let examples = e |> List.map ~f:(fun ex -> (ex |> member "inputs" |> to_list |> List.map ~f:unpack,
ex |> member "output" |> unpack)) in
let maximum_frontier = j |> member "maximumFrontier" |> to_int in
let name = j |> member "name" |> to_string in
let task =
(try
let special = j |> member "specialTask" |> to_string in
match special |> Hashtbl.find task_handler with
| Some(handler) -> handler (j |> member "extras")
| None -> (Printf.eprintf " (ocaml) FATAL: Could not find handler for %s\n" special;
exit 1)
with _ -> supervised_task) ~timeout:timeout name task_type examples
in
(task, maximum_frontier))
in
There are a number of different task_handlers, but the one I happen to be concerned with is defined as follows:
(fun extras ?timeout:(timeout = 0.001) name ty examples ->
let open Yojson.Basic.Util in
let cost_matters =
try
extras |> member "costMatters" |> to_bool
with _ -> assert false
in
let by = match examples with
| [([0],y)] ->
Bigarray.(Array1.of_array int8_unsigned c_layout (Array.of_list y))
| [([1],y)] ->
Bigarray.(Array1.of_array int8_unsigned c_layout (Array.of_list y))
| _ -> failwith "not a turtle task" in
{ name = name ;
task_type = ty ;
log_likelihood =
(fun p ->
try
match run_recent_logo ~timeout p with
| Some(bx,cost) when (LogoLib.LogoInterpreter.fp_equal bx by 0) ->
(if cost_matters then (0.-.cost)*.10. else 0.)
| _ -> log 0.
with (* We have to be a bit careful with exceptions if the
* synthesized program generated an exception, then we just
* terminate w/ false but if the enumeration timeout was
* triggered during program evaluation, we need to pass the
* exception on
*)
| UnknownPrimitive(n) -> raise (Failure ("Unknown primitive: "^n))
| EnumerationTimeout -> raise EnumerationTimeout
| _ -> log 0.0)
});;
The author also uses ;; in a lot of files..another quirk.

How to zip each individual element from two lists into one list using OCaml

If I have an input of a tuple containing two lists of integers of the same length, and I want my output to be a list of these two lists zipped, after extracting these two lists from the tuple how do I zip each individual element into one list? For example, if my input is twolists= ([1;2;3], [4;5;6]), then I want my output to be [(1,4); (2,5); (3,6)]. How do I zip each element and add it to my output?
The function name and type is as follows:
let rec pairlists twolists = ...
val pairlists : 'a list * 'b list -> ('a * 'b) list = fun
So far I have:
let rec pairlists twolists =
let (l1, l2) = twolists in
let rec zip (l1,l2) =
match l1 with
|[] -> l2
|x :: xs -> x :: zip(l2, xs) in
twolists ;;
but this is clearly not doing what I want.
Are you looking for List.combine ?
val combine : 'a list -> 'b list -> ('a * 'b) list
Transform a pair of lists into a list of pairs: combine [a1; ...; an] [b1; ...; bn] is [(a1,b1); ...; (an,bn)].
Raises Invalid_argument if the two lists have different lengths. Not tail-recursive.
If your result list should contain elements that consist of the elements of both sublists, then you obviously have to destructure each sublist on each iteration.
If the lists are guaranteed to have the same lengths, the solution can be as simple as:
let rec zip paired_lists =
match paired_lists with
| [], [] -> []
| h1::t1, h2::t2 -> (h1, h2)::(zip (t1, t2))
| _, _ -> failwith "oops, the lists seems to have different lengths"
;;
zip ([1;2;3], [4;5;6]);;
- : (int * int) list = [(1, 4); (2, 5); (3, 6)]
But this one is not tail-recursive, which is obviously not good. The second sub-optimal thing is this reconstruction of tuple of lists on each iteration (I'm a newbie in OCaml, so chances are compiler is smart enough to avoid the unnecessary allocations, but still...). Fixing both flaws is trivial too:
let zip_tr paired_lists =
let list1, list2 = paired_lists in
let rec aux l1 l2 acc =
match l1, l2 with
| [], [] -> List.rev acc
| h1::t1, h2::t2 -> aux t1 t2 (h1, h2)::acc
| _, _ -> failwith "oops, the lists seems to have different lengths"
in aux list1 list2 []
;;
zip_tr ([1;2;3], [4;5;6]);;
- : (int * int) list = [(1, 4); (2, 5); (3, 6)]
The signature of your code does not match the expected signature :
line 2, characters 11-13:
Warning 26: unused variable l2.
Line 2, characters 7-9:
Warning 26: unused variable l1.
val pairlists : 'a list * 'a list -> 'a list = <fun>
Indeed, both possible matches return either a 'a list (this is l2) or x::zip... which is also a list of 'a type.
There should be sth like (x,y)::list in your code.
In addition, pairlists is not recursive and does not need to be declared as such, only zip is recursive.
The end of your function shall be like this (otherwise zip has no effect) :
....
let rec zip (l1,l2) =
match l1 with
|[] -> l2
|x :: xs -> x :: zip(l2, xs) in
zip twolists ;;
In addition to the other solutions mentioned, ocaml-4.08 onwards enables you to provide let+ and and+ operators which will zip a list sum-wise, where you might otherwise think of using applicatives. Whether it is an improvement on them is in the eye of the beholder:
let (let+) list f = List.map f list
let (and+) a b =
let rec loop first second =
match first,second with
first_hd::first_tl,second_hd::second_tl ->
(first_hd,second_hd)::(loop first_tl second_tl)
| _ -> []
in
loop a b
let pairlists = function
first,second ->
let+ elt1 = first
and+ elt2 = second in
[elt1 ; elt2]
(* example *)
let () =
let res = pairlists ([1;2;3], [4;5;6]) in
List.iter
(fun list -> List.iter (fun i -> Printf.printf "%d " i) list ;
print_endline "")
res
Here by way of comparison is the more traditional approach if you are using applicatives
let pure x = [x]
let (<*>) aps args =
List.concat (List.map (fun f -> List.map (fun x -> f x) args) aps)
let (<|>) aps args =
let rec loop args_rest aps_rest =
match args_rest,aps_rest with
args_hd::args_tl,aps_hd::aps_tl ->
(aps_hd args_hd)::(loop args_tl aps_tl)
| _ -> []
in
loop args aps
let pairlists = function
first,second ->
let two_list a b = a :: [b] in
pure two_list <*> first <|> second
(* example *)
let () =
let res = pairlists ([1;2;3], [4;5;6]) in
List.iter
(fun list -> List.iter (fun i -> Printf.printf "%d " i) list ;
print_endline "")
res

Ocaml cast string to list of tuples

I have the file "example.dat" with text "[(1,2); (3,4); (5,6)]". I need to get list of tuples from it. I know, how I can get it from list of ints.
# let f line = List.map int_of_string line;;
# open Printf
let file = "example.dat"
let () =
let ic = open_in file in
try
let line = input_line ic in
f line;
flush stdout;
close_in ic
with e ->
close_in_noerr ic;
raise e;;
How I must to change my functions?
Given a list of strings that represent ints, your function f returns a list of ints. It doesn't return a list of tuples.
You don't say whether you want to verify that the input has some kind of proper form. If you want to verify that it has the form of (say) a list of type (int * int) list in OCaml, this is a parsing problem that would take some work.
If you just want to extract the parts of the input line that look like ints, you can use regular expression processing from the Str module:
# let re = Str.regexp "[^0-9]+" in
Str.split re "[(1,2); (37,4); (5,6)]";;
- : string list = ["1"; "2"; "37"; "4"; "5"; "6"]
Then you can rewrite your function f to collect up each pair of ints into a tuple. I don't see a good way to use List.map for this. You might have to write your own recursive function or use List.fold_left.
Update
I will write you a function that changes a list of values into a list of pairs. I hope this isn't for a school assignment, in which case you should be figuring this out for yourself.
let rec mkpairs l =
match l with
| [] | [_] -> []
| a :: b :: rest -> (a, b) :: mkpairs rest
As you can see, this function silently discards the last element of the list if the list has an odd number of elements.
This function is not tail recursive. So that's something you could think about improving.
let open Genlex in
let open Stream in
let lexer = make_lexer ["["; "("; ","; ")"; ";"; "]";] in
let stream = lexer (of_string array_string) in
let fail () = failwith "Malformed string" in
let parse_tuple acc = match next stream with
| Int first -> ( match next stream with
| Kwd "," -> ( match next stream with
| Int second -> ( match next stream with
| Kwd ")" -> (first, second) :: acc
| _ -> fail () )
| _ -> fail () )
| _ -> fail () )
| _ -> fail ()
in
let rec parse_array acc =
match next stream with
| Kwd "(" -> parse_array (parse_tuple acc)
| Kwd ";" -> parse_array acc
| Kwd "]" -> acc
| _ -> fail ()
in
try
match next stream with
| Kwd "[" -> List.rev (parse_array [])
| _ -> fail ()
with Stream.Failure -> fail ();;

F# Regex matching chain

As I am not completely happy with F#'s regex implementation for my usage, I wanted to implement a so-called regex chain. It basically works as follows:
The given string s will be checked, whether it matches the first pattern. If it does, it should execute a function associated with the first pattern. If it does not, it should continue with the next one.
I tried to implement it as follows:
let RegexMatch ((s : string, c : bool), p : string, f : GroupCollection -> unit) =
if c then
let m = Regex.Match(s, p)
if m.Success then
f m.Groups
(s, false)
else (s, c)
else (s, c)
("my input text", true)
|> RegexMatch("pattern1", fun g -> ...)
|> RegexMatch("pattern2", fun g -> ...)
|> RegexMatch("pattern3", fun g -> ...)
|> .... // more patterns
|> ignore
The problem is, that this code is invalid, as the forward-pipe operator does not seem to pipe tuples or does not like my implementation 'design'.
My question is: Can I fix this code above easily or should I rather implement some other kind of regex chain?
Your function RegexMatch won't support piping, because it has tupled parameters.
First, look at the definition of the pipe:
let (|>) x f = f x
From this, one can clearly see that this expression:
("text", true)
|> RegexMatch("pattern", fun x -> ...)
would be equivalent to this:
RegexMatch("pattern", fun x -> ...) ("text", true)
Does this match your function signature? Obviously not. In your signature, the text/bool pair comes first, and is part of the triple of parameters, together with pattern and function.
To make it work, you need to take the "piped" parameter in curried form and last:
let RegexMatch p f (s, c) = ...
Then you can do the piping:
("input", true)
|> RegexMatch "pattern1" (fun x -> ...)
|> RegexMatch "pattern2" (fun x -> ...)
|> RegexMatch "pattern3" (fun x -> ...)
As an aside, I must note that your approach is not very, ahem, functional. You're basing your whole logic on side effects, which will make your program not composable and hard to test, and probably prone to bugs. You're not reaping the benefits of F#, effectively using it as "C# with nicer syntax".
Also, there are actually well researched ways to achieve what you want. For one, check out Railway-oriented programming (also known as monadic computations).
To me this sounds like what you are trying to implement is Active Patterns.
Using Active Patterns you can use regular pattern matching syntax to match against RegEx patterns:
let (|RegEx|_|) p i =
let m = System.Text.RegularExpressions.Regex.Match (i, p)
if m.Success then
Some m.Groups
else
None
[<EntryPoint>]
let main argv =
let text = "123"
match text with
| RegEx #"\d+" g -> printfn "Digit: %A" g
| RegEx #"\w+" g -> printfn "Word : %A" g
| _ -> printfn "Not recognized"
0
Another approach is to use what Fyodor refers to as Railway Oriented Programming:
type RegexResult<'T> =
| Found of 'T
| Searching of string
let lift p f = function
| Found v -> Found v
| Searching i ->
let m = System.Text.RegularExpressions.Regex.Match (i, p)
if m.Success then
m.Groups |> f |> Found
else
Searching i
[<EntryPoint>]
let main argv =
Searching "123"
|> lift #"\d+" (fun g -> printfn "Digit: %A" g)
|> lift #"\w+" (fun g -> printfn "Word : %A" g)
|> ignore
0

Print a List in OCaml

I want to do something as simple as this:
Print a list.
let a = [1;2;3;4;5]
How can I print this list to Standard Output?
You should become familiar with the List.iter and List.map functions. They are essential for programming in OCaml. If you also get comfortable with the Printf module, you can then write:
open Printf
let a = [1;2;3;4;5]
let () = List.iter (printf "%d ") a
I open Printf in most of my code because I use the functions in it so often. Without that you would have to write Printf.printf in the last line. Also, if you're working in the toploop, don't forget to end the above statements with double semi-colons.
You can do this with a simple recursion :
let rec print_list = function
[] -> ()
| e::l -> print_int e ; print_string " " ; print_list l
The head of the list is printed, then you do a recursive call on the tail of the list.
print_string (String.concat " " (List.map string_of_int list))
If the question is about finding the quickiest way to implement this, for example when debugging, then we could say that:
extended standard libraries (e.g. batteries) typically have some additional functions:
List.print
~first:"[" ~sep:";" ~last:"]" (fun c x -> Printf.fprintf c "%d" x) stdout a
this tiny syntax extension that I wrote some time ago allows you to write:
<:print<[$!i <- a${$d:i$}{;}]>>
automatic generation is not immediately available (because of the lack of run-time type information in OCaml data representation) but can be achieved using either code generation from the types, or run-time types.
I'm very late answering, but here's another way:
let print_list f lst =
let rec print_elements = function
| [] -> ()
| h::t -> f h; print_string ";"; print_elements t
in
print_string "[";
print_elements lst;
print_string "]";;
To print an int list, we could write:
print_list print_int [3;6;78;5;2;34;7];;
However if we were going to do this a lot, it would save time to specialize the function using partial application:
let print_int_list = print_list print_int;;
Which we can now use like so:
print_int_list [3;6;78;5;2;34;7];;
What if we wanted to do something pretty complex, like printing an int list list? With this function, it's easy:
(* Option 1 *)
print_list (print_list print_int) [[3;6;78];[];[5];[2;34;7]];;
(* Option 2 *)
let print_int_list_list = print_list (print_list print_int);;
print_int_list_list [[3;6;78];[];[5];[2;34;7]];;
(* Option 3 *)
let print_int_list_list = print_list print_int_list;;
print_int_list_list [[3;6;78];[];[5];[2;34;7]];;
Printing an (int * string) list (i.e. a list of pairs of ints and strings):
(* Option 1 *)
print_list (fun (a, b) -> print_string "("; print_int a; print_string ", "; print_string b; print_string ")") [(1, "one"); (2, "two"); (3, "three")];;
(* Option 2 *)
let print_pair f g (a, b) =
print_string "(";
f a;
print_string ", ";
g b;
print_string ")";;
print_list (print_pair print_int print_string) [(1, "one"); (2, "two"); (3, "three")];;
(* Option 3 *)
let print_pair f g (a, b) =
print_string "(";
f a;
print_string ", ";
g b;
print_string ")";;
let print_int_string_pair = print_pair print_int print_string;;
print_list print_int_string_pair [(1, "one"); (2, "two"); (3, "three")];;
(* Option 4 *)
let print_pair f g (a, b) =
print_string "(";
f a;
print_string ", ";
g b;
print_string ")";;
let print_int_string_pair = print_pair print_int print_string;;
let print_int_string_pair_list = print_list print_int_string_pair;;
print_int_string_pair_list [(1, "one"); (2, "two"); (3, "three")];;
I would do this in the following way:
let a = [1;2;3;4;5];;
List.iter print_int a;;
Actually, you can decouple printing a list and turning a list into a string. The main advantage for doing this is that you can use this method to show lists in logs, export them to CSVs...
I often use a listHelper module, with the following :
(** Generic method to print the elements of a list *)
let string_of_list input_list string_of_element sep =
let add a b = a^sep^(string_of_element b) in
match input_list with
| [] -> ""
| h::t -> List.fold_left add (string_of_element h) t
So, if I wanted to output a list of floats to a csv file, I could just use the following :
let float_list_to_csv_row input_list = string_of_list input_list string_of_float ","
Just a solution with %a :
open Printf
let print_l outx l =
List.map string_of_int l
|> String.concat ";"
|> fprintf outx "%s"
Test :
# printf "[%a]" print_l [1;2;3] ;;
[1;2;3]- : unit = ()
# printf "[%a]" print_l [];;
[]- : unit = ()
let print_list l =
let rec aux acc =
match acc with
| [] -> ()
| x :: tl ->
Printf.fprintf stdout "%i"; aux tl
in aux l
Or
let sprintf_list l =
let acc = ref "{" in
List.iteri (fun i x ->
acc := !acc ^
if i <> 0
then Printf.sprintf "; %i" x
else Printf.sprintf "%i" x
) l;
!acc ^ "}"
let print_list l =
let output = sprintf_list l in
Printf.fprintf stdout "%s\n" output