Release coccinelle-0.1.8
[bpt/coccinelle.git] / commons / common.ml
CommitLineData
b1b2de81
C
1(* Yoann Padioleau
2 *
3 * Copyright (C) 1998-2009 Yoann Padioleau
34e49164
C
4 *
5 * This library is free software; you can redistribute it and/or
6 * modify it under the terms of the GNU Lesser General Public License
7 * version 2.1 as published by the Free Software Foundation, with the
8 * special exception on linking described in file license.txt.
9 *
10 * This library is distributed in the hope that it will be useful, but
11 * WITHOUT ANY WARRANTY; without even the implied warranty of
12 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the file
13 * license.txt for more details.
14 *)
15
16(*****************************************************************************)
17(* Notes *)
18(*****************************************************************************)
19
20
21
22(* ---------------------------------------------------------------------- *)
23(* Maybe could split common.ml and use include tricks as in ofullcommon.ml or
24 * Jane Street core lib. But then harder to bundle simple scripts like my
25 * make_full_linux_kernel.ml because would then need to pass all the files
26 * either to ocamlc or either to some #load. Also as the code of many
27 * functions depends on other functions from this common, it would
28 * be tedious to add those dependencies. Here simpler (have just the
29 * pb of the Prelude, but it's a small problem).
30 *
31 * pixel means code from Pascal Rigaux
32 * julia means code from Julia Lawall
33 *)
34(* ---------------------------------------------------------------------- *)
35
36(*****************************************************************************)
37(* We use *)
38(*****************************************************************************)
39(*
40 * modules:
41 * - Pervasives, of course
42 * - List
43 * - Str
44 * - Hashtbl
45 * - Format
46 * - Buffer
47 * - Unix and Sys
48 * - Arg
49 *
50 * functions:
51 * - =, <=, max min, abs, ...
52 * - List.rev, List.mem, List.partition,
53 * - List.fold*, List.concat, ...
54 * - Str.global_replace
91eba41f 55 * - Filename.is_relative
0708f913 56 * - String.uppercase, String.lowercase
34e49164
C
57 *
58 *
59 * The Format library allows to hide passing an indent_level variable.
60 * You use as usual the print_string function except that there is
61 * this automatic indent_level variable handled for you (and maybe
62 * more services). src: julia in coccinelle unparse_cocci.
63 *
64 * Extra packages
65 * - ocamlbdb
91eba41f 66 * - ocamlgtk, and gtksourceview
34e49164
C
67 * - ocamlgl
68 * - ocamlpython
69 * - ocamlagrep
70 * - ocamlfuse
71 * - ocamlmpi
72 * - ocamlcalendar
73 *
91eba41f
C
74 * - pcre
75 * - sdl
76 *
77 * Many functions in this file were inspired by Haskell or Lisp librairies.
34e49164
C
78 *)
79
80(*****************************************************************************)
81(* Prelude *)
82(*****************************************************************************)
83
84(* The following functions should be in their respective sections but
85 * because some functions in some sections use functions in other
86 * sections, and because I don't want to take care of the order of
87 * those sections, of those dependencies, I put the functions causing
88 * dependency problem here. C is better than caml on this with the
89 * ability to declare prototype, enabling some form of forward
90 * reference. *)
91
92let (+>) o f = f o
93let (++) = (@)
94
95exception Timeout
96exception UnixExit of int
97
98let rec (do_n: int -> (unit -> unit) -> unit) = fun i f ->
99 if i = 0 then () else (f(); do_n (i-1) f)
100let rec (foldn: ('a -> int -> 'a) -> 'a -> int -> 'a) = fun f acc i ->
101 if i = 0 then acc else foldn f (f acc i) (i-1)
102
103let sum_int = List.fold_left (+) 0
104
105(* could really call it 'for' :) *)
106let fold_left_with_index f acc =
107 let rec fold_lwi_aux acc n = function
108 | [] -> acc
109 | x::xs -> fold_lwi_aux (f acc x n) (n+1) xs
110 in fold_lwi_aux acc 0
111
112
113let rec drop n xs =
114 match (n,xs) with
115 | (0,_) -> xs
116 | (_,[]) -> failwith "drop: not enough"
117 | (n,x::xs) -> drop (n-1) xs
118
119let rec enum_orig x n = if x = n then [n] else x::enum_orig (x+1) n
120
121let enum x n =
122 if not(x <= n)
123 then failwith (Printf.sprintf "bad values in enum, expect %d <= %d" x n);
124 let rec enum_aux acc x n =
125 if x = n then n::acc else enum_aux (x::acc) (x+1) n
126 in
127 List.rev (enum_aux [] x n)
128
129let rec take n xs =
130 match (n,xs) with
131 | (0,_) -> []
132 | (_,[]) -> failwith "take: not enough"
133 | (n,x::xs) -> x::take (n-1) xs
134
135
136let last_n n l = List.rev (take n (List.rev l))
137let last l = List.hd (last_n 1 l)
138
139
140let (list_of_string: string -> char list) = function
141 "" -> []
142 | s -> (enum 0 ((String.length s) - 1) +> List.map (String.get s))
143
144let (lines: string -> string list) = fun s ->
145 let rec lines_aux = function
146 | [] -> []
147 | [x] -> if x = "" then [] else [x]
148 | x::xs ->
149 x::lines_aux xs
150 in
151 Str.split_delim (Str.regexp "\n") s +> lines_aux
152
153
154let push2 v l =
155 l := v :: !l
156
b1b2de81 157let null xs = match xs with [] -> true | _ -> false
34e49164
C
158
159
160
161
162let debugger = ref false
163
164let unwind_protect f cleanup =
165 if !debugger then f() else
166 try f ()
167 with e -> begin cleanup e; raise e end
168
169let finalize f cleanup =
170 if !debugger then f() else
171 try
172 let res = f () in
173 cleanup ();
174 res
175 with e ->
176 cleanup ();
177 raise e
178
179let command2 s = ignore(Sys.command s)
180
181
182let (matched: int -> string -> string) = fun i s ->
183 Str.matched_group i s
184
185let matched1 = fun s -> matched 1 s
186let matched2 = fun s -> (matched 1 s, matched 2 s)
187let matched3 = fun s -> (matched 1 s, matched 2 s, matched 3 s)
188let matched4 = fun s -> (matched 1 s, matched 2 s, matched 3 s, matched 4 s)
189let matched5 = fun s -> (matched 1 s, matched 2 s, matched 3 s, matched 4 s, matched 5 s)
190let matched6 = fun s -> (matched 1 s, matched 2 s, matched 3 s, matched 4 s, matched 5 s, matched 6 s)
191let matched7 = fun s -> (matched 1 s, matched 2 s, matched 3 s, matched 4 s, matched 5 s, matched 6 s, matched 7 s)
192
193let (with_open_stringbuf: (((string -> unit) * Buffer.t) -> unit) -> string) =
194 fun f ->
195 let buf = Buffer.create 1000 in
196 let pr s = Buffer.add_string buf (s ^ "\n") in
197 f (pr, buf);
198 Buffer.contents buf
199
200
485bce71
C
201let foldl1 p = function x::xs -> List.fold_left p x xs | _ -> failwith "foldl1"
202
34e49164
C
203(*****************************************************************************)
204(* Debugging/logging *)
205(*****************************************************************************)
206
207(* I used this in coccinelle where the huge logging of stuff ask for
208 * a more organized solution that use more visual indentation hints.
209 *
210 * todo? could maybe use log4j instead ? or use Format module more
211 * consistently ?
212 *)
213
214let _tab_level_print = ref 0
215let _tab_indent = 5
216
217
218let _prefix_pr = ref ""
219
220let indent_do f =
221 _tab_level_print := !_tab_level_print + _tab_indent;
222 finalize f
223 (fun () -> _tab_level_print := !_tab_level_print - _tab_indent;)
224
225
226let pr s =
227 print_string !_prefix_pr;
228 do_n !_tab_level_print (fun () -> print_string " ");
229 print_string s;
230 print_string "\n";
231 flush stdout
232
233let pr_no_nl s =
234 print_string !_prefix_pr;
235 do_n !_tab_level_print (fun () -> print_string " ");
236 print_string s;
237 flush stdout
238
239
708f4980
C
240
241
242
243
244let _chan_pr2 = ref (None: out_channel option)
245
246let out_chan_pr2 ?(newline=true) s =
247 match !_chan_pr2 with
248 | None -> ()
249 | Some chan ->
250 output_string chan (s ^ (if newline then "\n" else ""));
251 flush chan
252
253
34e49164
C
254let pr2 s =
255 prerr_string !_prefix_pr;
256 do_n !_tab_level_print (fun () -> prerr_string " ");
257 prerr_string s;
258 prerr_string "\n";
708f4980
C
259 flush stderr;
260 out_chan_pr2 s;
261 ()
34e49164
C
262
263let pr2_no_nl s =
264 prerr_string !_prefix_pr;
265 do_n !_tab_level_print (fun () -> prerr_string " ");
266 prerr_string s;
708f4980
C
267 flush stderr;
268 out_chan_pr2 ~newline:false s;
269 ()
270
34e49164
C
271
272let pr_xxxxxxxxxxxxxxxxx () =
273 pr "-----------------------------------------------------------------------"
274
275let pr2_xxxxxxxxxxxxxxxxx () =
276 pr2 "-----------------------------------------------------------------------"
277
278
279let reset_pr_indent () =
280 _tab_level_print := 0
281
282(* old:
283 * let pr s = (print_string s; print_string "\n"; flush stdout)
284 * let pr2 s = (prerr_string s; prerr_string "\n"; flush stderr)
285 *)
286
287(* ---------------------------------------------------------------------- *)
288
289(* I can not use the _xxx ref tech that I use for common_extra.ml here because
290 * ocaml don't like the polymorphism of Dumper mixed with refs.
291 *
292 * let (_dump_func : ('a -> string) ref) = ref
293 * (fun x -> failwith "no dump yet, have you included common_extra.cmo?")
294 * let (dump : 'a -> string) = fun x ->
295 * !_dump_func x
296 *
297 * So I have included directly dumper.ml in common.ml. It's more practical
298 * when want to give script that use my common.ml, I just have to give
299 * this file.
300 *)
301
302(* start of dumper.ml *)
303
304(* Dump an OCaml value into a printable string.
305 * By Richard W.M. Jones (rich@annexia.org).
306 * dumper.ml 1.2 2005/02/06 12:38:21 rich Exp
307 *)
308open Printf
309open Obj
310
311let rec dump r =
312 if is_int r then
313 string_of_int (magic r : int)
314 else ( (* Block. *)
315 let rec get_fields acc = function
316 | 0 -> acc
317 | n -> let n = n-1 in get_fields (field r n :: acc) n
318 in
319 let rec is_list r =
320 if is_int r then (
321 if (magic r : int) = 0 then true (* [] *)
322 else false
323 ) else (
324 let s = size r and t = tag r in
325 if t = 0 && s = 2 then is_list (field r 1) (* h :: t *)
326 else false
327 )
328 in
329 let rec get_list r =
330 if is_int r then []
331 else let h = field r 0 and t = get_list (field r 1) in h :: t
332 in
333 let opaque name =
334 (* XXX In future, print the address of value 'r'. Not possible in
335 * pure OCaml at the moment.
336 *)
337 "<" ^ name ^ ">"
338 in
339
340 let s = size r and t = tag r in
341
342 (* From the tag, determine the type of block. *)
343 if is_list r then ( (* List. *)
344 let fields = get_list r in
345 "[" ^ String.concat "; " (List.map dump fields) ^ "]"
346 )
347 else if t = 0 then ( (* Tuple, array, record. *)
348 let fields = get_fields [] s in
349 "(" ^ String.concat ", " (List.map dump fields) ^ ")"
350 )
351
352 (* Note that [lazy_tag .. forward_tag] are < no_scan_tag. Not
353 * clear if very large constructed values could have the same
354 * tag. XXX *)
355 else if t = lazy_tag then opaque "lazy"
356 else if t = closure_tag then opaque "closure"
357 else if t = object_tag then ( (* Object. *)
358 let fields = get_fields [] s in
359 let clasz, id, slots =
360 match fields with h::h'::t -> h, h', t | _ -> assert false in
361 (* No information on decoding the class (first field). So just print
362 * out the ID and the slots.
363 *)
364 "Object #" ^ dump id ^
365 " (" ^ String.concat ", " (List.map dump slots) ^ ")"
366 )
367 else if t = infix_tag then opaque "infix"
368 else if t = forward_tag then opaque "forward"
369
370 else if t < no_scan_tag then ( (* Constructed value. *)
371 let fields = get_fields [] s in
372 "Tag" ^ string_of_int t ^
373 " (" ^ String.concat ", " (List.map dump fields) ^ ")"
374 )
375 else if t = string_tag then (
376 "\"" ^ String.escaped (magic r : string) ^ "\""
377 )
378 else if t = double_tag then (
379 string_of_float (magic r : float)
380 )
381 else if t = abstract_tag then opaque "abstract"
382 else if t = custom_tag then opaque "custom"
383 else if t = final_tag then opaque "final"
384 else failwith ("dump: impossible tag (" ^ string_of_int t ^ ")")
385 )
386
387let dump v = dump (repr v)
388
389(* end of dumper.ml *)
390
391(*
392let (dump : 'a -> string) = fun x ->
393 Dumper.dump x
394*)
395
396
397(* ---------------------------------------------------------------------- *)
398let pr2_gen x = pr2 (dump x)
399
400
401
402(* ---------------------------------------------------------------------- *)
403
404
405let _already_printed = Hashtbl.create 101
406let disable_pr2_once = ref false
708f4980
C
407
408let xxx_once f s =
34e49164
C
409 if !disable_pr2_once then pr2 s
410 else
411 if not (Hashtbl.mem _already_printed s)
412 then begin
413 Hashtbl.add _already_printed s true;
708f4980 414 f ("(ONCE) " ^ s);
34e49164
C
415 end
416
708f4980
C
417let pr2_once s = xxx_once pr2 s
418
419(* ---------------------------------------------------------------------- *)
420let mk_pr2_wrappers aref =
421 let fpr2 s =
422 if !aref
423 then pr2 s
424 else
425 (* just to the log file *)
426 out_chan_pr2 s
427 in
428 let fpr2_once s =
429 if !aref
430 then pr2_once s
431 else
432 xxx_once out_chan_pr2 s
433 in
434 fpr2, fpr2_once
435
34e49164
C
436
437(* ---------------------------------------------------------------------- *)
438(* could also be in File section *)
439
440let redirect_stdout_stderr file f =
441 begin
442 let chan = open_out file in
443 let descr = Unix.descr_of_out_channel chan in
444
445 let saveout = Unix.dup Unix.stdout in
446 let saveerr = Unix.dup Unix.stderr in
447 Unix.dup2 descr Unix.stdout;
448 Unix.dup2 descr Unix.stderr;
449 flush stdout; flush stderr;
450 f();
451 flush stdout; flush stderr;
452 Unix.dup2 saveout Unix.stdout;
453 Unix.dup2 saveerr Unix.stderr;
454 close_out chan;
455 end
456
457let redirect_stdin file f =
458 begin
459 let chan = open_in file in
460 let descr = Unix.descr_of_in_channel chan in
461
462 let savein = Unix.dup Unix.stdin in
463 Unix.dup2 descr Unix.stdin;
464 f();
465 Unix.dup2 savein Unix.stdin;
466 close_in chan;
467 end
468
469let redirect_stdin_opt optfile f =
470 match optfile with
471 | None -> f()
472 | Some infile -> redirect_stdin infile f
473
474
708f4980
C
475(* cf end
476let with_pr2_to_string f =
477*)
478
34e49164
C
479
480(* ---------------------------------------------------------------------- *)
481
482include Printf
483
484(* cf common.mli, fprintf, printf, eprintf, sprintf.
485 * also what is this ?
486 * val bprintf : Buffer.t -> ('a, Buffer.t, unit) format -> 'a
487 * val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b
488 *)
489
490(* ex of printf:
491 * printf "%02d" i
492 * for padding
493 *)
494
495let spf = sprintf
496
497(* ---------------------------------------------------------------------- *)
498
499let _chan = ref stderr
500let start_log_file () =
501 let filename = (spf "/tmp/debugml%d:%d" (Unix.getuid()) (Unix.getpid())) in
502 pr2 (spf "now using %s for logging" filename);
503 _chan := open_out filename
504
505
506let dolog s = output_string !_chan (s ^ "\n"); flush !_chan
507
508let verbose_level = ref 1
509let log s = if !verbose_level >= 1 then dolog s
510let log2 s = if !verbose_level >= 2 then dolog s
511let log3 s = if !verbose_level >= 3 then dolog s
512let log4 s = if !verbose_level >= 4 then dolog s
513
514let if_log f = if !verbose_level >= 1 then f()
515let if_log2 f = if !verbose_level >= 2 then f()
516let if_log3 f = if !verbose_level >= 3 then f()
517let if_log4 f = if !verbose_level >= 4 then f()
518
519(* ---------------------------------------------------------------------- *)
520
521let pause () = (pr2 "pause: type return"; ignore(read_line ()))
522
523(* src: from getopt from frish *)
524let bip () = Printf.printf "\007"; flush stdout
525let wait () = Unix.sleep 1
526
527(* was used by fix_caml *)
528let _trace_var = ref 0
529let add_var() = incr _trace_var
530let dec_var() = decr _trace_var
531let get_var() = !_trace_var
532
533let (print_n: int -> string -> unit) = fun i s ->
534 do_n i (fun () -> print_string s)
535let (printerr_n: int -> string -> unit) = fun i s ->
536 do_n i (fun () -> prerr_string s)
537
538let _debug = ref true
539let debugon () = _debug := true
540let debugoff () = _debug := false
541let debug f = if !_debug then f () else ()
542
543
544
545(* now in prelude:
546 * let debugger = ref false
547 *)
548
549
550(*****************************************************************************)
551(* Profiling *)
552(*****************************************************************************)
553
554let get_mem() =
555 command2("grep VmData /proc/" ^ string_of_int (Unix.getpid()) ^ "/status")
556
557let memory_stat () =
558 let stat = Gc.stat() in
559 let conv_mo x = x * 4 / 1000000 in
560 Printf.sprintf "maximal = %d Mo\n" (conv_mo stat.Gc.top_heap_words) ^
561 Printf.sprintf "current = %d Mo\n" (conv_mo stat.Gc.heap_words) ^
562 Printf.sprintf "lives = %d Mo\n" (conv_mo stat.Gc.live_words)
563 (* Printf.printf "fragments = %d Mo\n" (conv_mo stat.Gc.fragments); *)
564
565let timenow () =
566 "sys:" ^ (string_of_float (Sys.time ())) ^ " seconds" ^
567 ":real:" ^
568 (let tm = Unix.time () +> Unix.gmtime in
569 tm.Unix.tm_min +> string_of_int ^ " min:" ^
570 tm.Unix.tm_sec +> string_of_int ^ ".00 seconds")
571
572let _count1 = ref 0
573let _count2 = ref 0
574let _count3 = ref 0
575let _count4 = ref 0
576let _count5 = ref 0
577
578let count1 () = incr _count1
579let count2 () = incr _count2
580let count3 () = incr _count3
581let count4 () = incr _count4
582let count5 () = incr _count5
583
584let profile_diagnostic_basic () =
585 Printf.sprintf
586 "count1 = %d\ncount2 = %d\ncount3 = %d\ncount4 = %d\ncount5 = %d\n"
587 !_count1 !_count2 !_count3 !_count4 !_count5
588
589
590
591let time_func f =
592 (* let _ = Timing () in *)
593 let x = f () in
594 (* let _ = Timing () in *)
595 x
596
597(* ---------------------------------------------------------------------- *)
598
599type prof = PALL | PNONE | PSOME of string list
600let profile = ref PNONE
485bce71 601let show_trace_profile = ref false
34e49164
C
602
603let check_profile category =
604 match !profile with
605 PALL -> true
606 | PNONE -> false
607 | PSOME l -> List.mem category l
608
609let _profile_table = ref (Hashtbl.create 100)
485bce71
C
610
611let adjust_profile_entry category difftime =
612 let (xtime, xcount) =
613 (try Hashtbl.find !_profile_table category
614 with Not_found ->
615 let xtime = ref 0.0 in
616 let xcount = ref 0 in
617 Hashtbl.add !_profile_table category (xtime, xcount);
618 (xtime, xcount)
619 ) in
620 xtime := !xtime +. difftime;
621 xcount := !xcount + 1;
622 ()
623
34e49164
C
624let profile_start category = failwith "todo"
625let profile_end category = failwith "todo"
626
485bce71 627
34e49164
C
628(* subtil: don't forget to give all argumens to f, otherwise partial app
629 * and will profile nothing.
0708f913
C
630 *
631 * todo: try also detect when complexity augment each time, so can
632 * detect the situation for a function gets worse and worse ?
34e49164
C
633 *)
634let profile_code category f =
635 if not (check_profile category)
636 then f()
637 else begin
485bce71 638 if !show_trace_profile then pr2 (spf "p: %s" category);
34e49164
C
639 let t = Unix.gettimeofday () in
640 let res, prefix =
641 try Some (f ()), ""
642 with Timeout -> None, "*"
643 in
644 let category = prefix ^ category in (* add a '*' to indicate timeout func *)
645 let t' = Unix.gettimeofday () in
485bce71
C
646
647 adjust_profile_entry category (t' -. t);
34e49164
C
648 (match res with
649 | Some res -> res
650 | None -> raise Timeout
651 );
652 end
653
485bce71
C
654
655let _is_in_exclusif = ref (None: string option)
656
657let profile_code_exclusif category f =
658 if not (check_profile category)
659 then f()
660 else begin
661
662 match !_is_in_exclusif with
663 | Some s ->
664 failwith (spf "profile_code_exclusif: %s but already in %s " category s);
665 | None ->
666 _is_in_exclusif := (Some category);
667 finalize
668 (fun () ->
669 profile_code category f
670 )
671 (fun () ->
672 _is_in_exclusif := None
673 )
674
675 end
676
677let profile_code_inside_exclusif_ok category f =
678 failwith "Todo"
679
680
34e49164
C
681(* todo: also put % ? also add % to see if coherent numbers *)
682let profile_diagnostic () =
683 if !profile = PNONE then "" else
684 let xs =
685 Hashtbl.fold (fun k v acc -> (k,v)::acc) !_profile_table []
686 +> List.sort (fun (k1, (t1,n1)) (k2, (t2,n2)) -> compare t2 t1)
687 in
688 with_open_stringbuf (fun (pr,_) ->
689 pr "---------------------";
690 pr "profiling result";
691 pr "---------------------";
692 xs +> List.iter (fun (k, (t,n)) ->
693 pr (sprintf "%-40s : %10.3f sec %10d count" k !t !n)
694 )
695 )
696
697
698
699let report_if_take_time timethreshold s f =
700 let t = Unix.gettimeofday () in
701 let res = f () in
702 let t' = Unix.gettimeofday () in
703 if (t' -. t > float_of_int timethreshold)
704 then pr2 (sprintf "NOTE: this code takes more than: %ds %s" timethreshold s);
705 res
706
707let profile_code2 category f =
708 profile_code category (fun () ->
709 if !profile = PALL
710 then pr2 ("starting: " ^ category);
711 let t = Unix.gettimeofday () in
712 let res = f () in
713 let t' = Unix.gettimeofday () in
714 if !profile = PALL
715 then pr2 (spf "ending: %s, %fs" category (t' -. t));
716 res
717 )
718
719
720(*****************************************************************************)
721(* Test *)
722(*****************************************************************************)
723let example b = assert b
724
725let _ex1 = example (enum 1 4 = [1;2;3;4])
726
727let assert_equal a b =
728 if not (a = b)
729 then failwith ("assert_equal: those 2 values are not equal:\n\t" ^
730 (dump a) ^ "\n\t" ^ (dump b) ^ "\n")
731
732let (example2: string -> bool -> unit) = fun s b ->
733 try assert b with x -> failwith s
734
735(*-------------------------------------------------------------------*)
736let _list_bool = ref []
737
738let (example3: string -> bool -> unit) = fun s b ->
739 _list_bool := (s,b)::(!_list_bool)
740
741(* could introduce a fun () otherwise the calculus is made at compile time
742 * and this can be long. This would require to redefine test_all.
743 * let (example3: string -> (unit -> bool) -> unit) = fun s func ->
744 * _list_bool := (s,func):: (!_list_bool)
745 *
746 * I would like to do as a func that take 2 terms, and make an = over it
747 * avoid to add this ugly fun (), but pb of type, cant do that :(
748 *)
749
750
751let (test_all: unit -> unit) = fun () ->
752 List.iter (fun (s, b) ->
753 Printf.printf "%s: %s\n" s (if b then "passed" else "failed")
754 ) !_list_bool
755
756let (test: string -> unit) = fun s ->
757 Printf.printf "%s: %s\n" s
758 (if (List.assoc s (!_list_bool)) then "passed" else "failed")
759
760let _ex = example3 "++" ([1;2]++[3;4;5] = [1;2;3;4;5])
761
762(*-------------------------------------------------------------------*)
763(* Regression testing *)
764(*-------------------------------------------------------------------*)
765
766(* cf end of file. It uses too many other common functions so I
767 * have put the code at the end of this file.
768 *)
769
770
771
772(* todo? take code from julien signoles in calendar-2.0.2/tests *)
773(*
774
775(* Generic functions used in the tests. *)
776
777val reset : unit -> unit
778val nb_ok : unit -> int
779val nb_bug : unit -> int
780val test : bool -> string -> unit
781val test_exn : 'a Lazy.t -> string -> unit
782
783
784let ok_ref = ref 0
785let ok () = incr ok_ref
786let nb_ok () = !ok_ref
787
788let bug_ref = ref 0
789let bug () = incr bug_ref
790let nb_bug () = !bug_ref
791
792let reset () =
793 ok_ref := 0;
794 bug_ref := 0
795
796let test x s =
797 if x then ok () else begin Printf.printf "%s\n" s; bug () end;;
798
799let test_exn x s =
800 try
801 ignore (Lazy.force x);
802 Printf.printf "%s\n" s;
803 bug ()
804 with _ ->
805 ok ();;
806*)
807
808
809(*****************************************************************************)
810(* Quickcheck like (sfl) *)
811(*****************************************************************************)
812
813(* Better than quickcheck, cos cant do a test_all_prop in haskell cos
814 * prop were functions, whereas here we have not prop_Unix x = ... but
815 * laws "unit" ...
816 *
817 * How to do without overloading ? objet ? can pass a generator as a
818 * parameter, mais lourd, prefer automatic inferring of the
819 * generator? But at the same time quickcheck does not do better cos
820 * we must explictly type the property. So between a
821 * prop_unit:: [Int] -> [Int] -> bool ...
822 * prop_unit x = reverse [x] == [x]
823 * and
824 * let _ = laws "unit" (fun x -> reverse [x] = [x]) (listg intg)
825 * there is no real differences.
826 *
827 * Yes I define typeg generator but quickcheck too, he must define
828 * class instance. I emulate the context Gen a => Gen [a] by making
829 * listg take as a param a type generator. Moreover I have not the pb of
830 * monad. I can do random independently, so my code is more simple
831 * I think than the haskell code of quickcheck.
832 *
833 * update: apparently Jane Street have copied some of my code for their
834 * Ounit_util.ml and quichcheck.ml in their Core library :)
835 *)
836
837(*---------------------------------------------------------------------------*)
838(* generators *)
839(*---------------------------------------------------------------------------*)
840type 'a gen = unit -> 'a
841
842let (ig: int gen) = fun () ->
843 Random.int 10
844let (lg: ('a gen) -> ('a list) gen) = fun gen () ->
845 foldn (fun acc i -> (gen ())::acc) [] (Random.int 10)
846let (pg: ('a gen) -> ('b gen) -> ('a * 'b) gen) = fun gen1 gen2 () ->
847 (gen1 (), gen2 ())
848let polyg = ig
849let (ng: (string gen)) = fun () ->
850 "a" ^ (string_of_int (ig ()))
851
852let (oneofl: ('a list) -> 'a gen) = fun xs () ->
853 List.nth xs (Random.int (List.length xs))
854(* let oneofl l = oneof (List.map always l) *)
855
856let (oneof: (('a gen) list) -> 'a gen) = fun xs ->
857 List.nth xs (Random.int (List.length xs))
858
859let (always: 'a -> 'a gen) = fun e () -> e
860
861let (frequency: ((int * ('a gen)) list) -> 'a gen) = fun xs ->
862 let sums = sum_int (List.map fst xs) in
863 let i = Random.int sums in
864 let rec freq_aux acc = function
865 | (x,g)::xs -> if i < acc+x then g else freq_aux (acc+x) xs
866 | _ -> failwith "frequency"
867 in
868 freq_aux 0 xs
869let frequencyl l = frequency (List.map (fun (i,e) -> (i,always e)) l)
870
871(*
872let b = oneof [always true; always false] ()
873let b = frequency [3, always true; 2, always false] ()
874*)
875
876(* cant do this:
877 * let rec (lg: ('a gen) -> ('a list) gen) = fun gen -> oneofl [[]; lg gen ()]
878 * nor
879 * let rec (lg: ('a gen) -> ('a list) gen) = fun gen -> oneof [always []; lg gen]
880 *
881 * because caml is not as lazy as haskell :( fix the pb by introducing a size
882 * limit. take the bounds/size as parameter. morover this is needed for
883 * more complex type.
884 *
885 * how make a bintreeg ?? we need recursion
886 *
887 * let rec (bintreeg: ('a gen) -> ('a bintree) gen) = fun gen () ->
888 * let rec aux n =
889 * if n = 0 then (Leaf (gen ()))
890 * else frequencyl [1, Leaf (gen ()); 4, Branch ((aux (n / 2)), aux (n / 2))]
891 * ()
892 * in aux 20
893 *
894 *)
895
896
897(*---------------------------------------------------------------------------*)
898(* property *)
899(*---------------------------------------------------------------------------*)
900
901(* todo: a test_all_laws, better syntax (done already a little with ig in
902 * place of intg. En cas d'erreur, print the arg that not respect
903 *
904 * todo: with monitoring, as in haskell, laws = laws2, no need for 2 func,
905 * but hard i found
906 *
907 * todo classify, collect, forall
908 *)
909
910
911(* return None when good, and Just the_problematic_case when bad *)
912let (laws: string -> ('a -> bool) -> ('a gen) -> 'a option) = fun s func gen ->
913 let res = foldn (fun acc i -> let n = gen() in (n, func n)::acc) [] 1000 in
914 let res = List.filter (fun (x,b) -> not b) res in
915 if res = [] then None else Some (fst (List.hd res))
916
917let rec (statistic_number: ('a list) -> (int * 'a) list) = function
918 | [] -> []
919 | x::xs -> let (splitg, splitd) = List.partition (fun y -> y = x) xs in
920 (1+(List.length splitg), x)::(statistic_number splitd)
921
922(* in pourcentage *)
923let (statistic: ('a list) -> (int * 'a) list) = fun xs ->
924 let stat_num = statistic_number xs in
925 let totals = sum_int (List.map fst stat_num) in
926 List.map (fun (i, v) -> ((i * 100) / totals), v) stat_num
927
928let (laws2:
929 string -> ('a -> (bool * 'b)) -> ('a gen) ->
930 ('a option * ((int * 'b) list ))) =
931 fun s func gen ->
932 let res = foldn (fun acc i -> let n = gen() in (n, func n)::acc) [] 1000 in
933 let stat = statistic (List.map (fun (x,(b,v)) -> v) res) in
934 let res = List.filter (fun (x,(b,v)) -> not b) res in
935 if res = [] then (None, stat) else (Some (fst (List.hd res)), stat)
936
937
938(*
939let b = laws "unit" (fun x -> reverse [x] = [x] )ig
940let b = laws "app " (fun (xs,ys) -> reverse (xs++ys) = reverse ys++reverse xs)(pg (lg ig)(lg ig))
941let b = laws "rev " (fun xs -> reverse (reverse xs) = xs )(lg ig)
942let b = laws "appb" (fun (xs,ys) -> reverse (xs++ys) = reverse xs++reverse ys)(pg (lg ig)(lg ig))
943let b = laws "max" (fun (x,y) -> x <= y ==> (max x y = y) )(pg ig ig)
944
945let b = laws2 "max" (fun (x,y) -> ((x <= y ==> (max x y = y)), x <= y))(pg ig ig)
946*)
947
948
949(* todo, do with coarbitrary ?? idea is that given a 'a, generate a 'b
950 * depending of 'a and gen 'b, that is modify gen 'b, what is important is
951 * that each time given the same 'a, we must get the same 'b !!!
952 *)
953
954(*
955let (fg: ('a gen) -> ('b gen) -> ('a -> 'b) gen) = fun gen1 gen2 () ->
956let b = laws "funs" (fun (f,g,h) -> x <= y ==> (max x y = y) )(pg ig ig)
957 *)
958
959(*
960let one_of xs = List.nth xs (Random.int (List.length xs))
961let take_one xs =
962 if empty xs then failwith "Take_one: empty list"
963 else
964 let i = Random.int (List.length xs) in
965 List.nth xs i, filter_index (fun j _ -> i <> j) xs
966*)
967
968(*****************************************************************************)
969(* Persistence *)
970(*****************************************************************************)
971
972let get_value filename =
973 let chan = open_in filename in
974 let x = input_value chan in (* <=> Marshal.from_channel *)
975 (close_in chan; x)
976
977let write_value valu filename =
978 let chan = open_out filename in
979 (output_value chan valu; (* <=> Marshal.to_channel *)
980 (* Marshal.to_channel chan valu [Marshal.Closures]; *)
981 close_out chan)
982
983let write_back func filename =
984 write_value (func (get_value filename)) filename
985
986
485bce71
C
987let read_value f = get_value f
988
34e49164 989
0708f913
C
990let marshal__to_string2 v flags =
991 Marshal.to_string v flags
992let marshal__to_string a b =
993 profile_code "Marshalling" (fun () -> marshal__to_string2 a b)
994
995let marshal__from_string2 v flags =
996 Marshal.from_string v flags
997let marshal__from_string a b =
998 profile_code "Marshalling" (fun () -> marshal__from_string2 a b)
999
1000
1001
34e49164
C
1002(*****************************************************************************)
1003(* Counter *)
1004(*****************************************************************************)
1005let _counter = ref 0
1006let counter () = (_counter := !_counter +1; !_counter)
1007
1008let _counter2 = ref 0
1009let counter2 () = (_counter2 := !_counter2 +1; !_counter2)
1010
1011let _counter3 = ref 0
1012let counter3 () = (_counter3 := !_counter3 +1; !_counter3)
1013
1014type timestamp = int
1015
1016(*****************************************************************************)
1017(* String_of *)
1018(*****************************************************************************)
1019(* To work with the macro system autogenerated string_of and print_ function
1020 (kind of deriving a la haskell) *)
1021
1022(* int, bool, char, float, ref ?, string *)
1023
1024let string_of_string s = "\"" ^ s "\""
1025
1026let string_of_list f xs =
1027 "[" ^ (xs +> List.map f +> String.concat ";" ) ^ "]"
1028
1029let string_of_unit () = "()"
1030
1031let string_of_array f xs =
1032 "[|" ^ (xs +> Array.to_list +> List.map f +> String.concat ";") ^ "|]"
1033
1034let string_of_option f = function
1035 | None -> "None "
1036 | Some x -> "Some " ^ (f x)
1037
1038
1039
1040
1041let print_bool x = print_string (if x then "True" else "False")
1042
1043let print_option pr = function
1044 | None -> print_string "None"
1045 | Some x -> print_string "Some ("; pr x; print_string ")"
1046
1047let print_list pr xs =
1048 begin
1049 print_string "[";
1050 List.iter (fun x -> pr x; print_string ",") xs;
1051 print_string "]";
1052 end
1053
1054(* specialised
1055let (string_of_list: char list -> string) =
1056 List.fold_left (fun acc x -> acc^(Char.escaped x)) ""
1057*)
1058
1059
1060let rec print_between between fn = function
1061 | [] -> ()
1062 | [x] -> fn x
1063 | x::xs -> fn x; between(); print_between between fn xs
1064
1065
1066
1067
1068let adjust_pp_with_indent f =
1069 Format.open_box !_tab_level_print;
1070 (*Format.force_newline();*)
1071 f();
1072 Format.close_box ();
1073 Format.print_newline()
1074
1075let adjust_pp_with_indent_and_header s f =
1076 Format.open_box (!_tab_level_print + String.length s);
1077 do_n !_tab_level_print (fun () -> Format.print_string " ");
1078 Format.print_string s;
1079 f();
1080 Format.close_box ();
1081 Format.print_newline()
1082
1083
1084
1085let pp_do_in_box f = Format.open_box 1; f(); Format.close_box ()
1086let pp_do_in_zero_box f = Format.open_box 0; f(); Format.close_box ()
1087
1088let pp_f_in_box f =
1089 Format.open_box 1;
1090 let res = f() in
1091 Format.close_box ();
1092 res
1093
1094let pp s = Format.print_string s
1095
0708f913
C
1096let mk_str_func_of_assoc_conv xs =
1097 let swap (x,y) = (y,x) in
1098
1099 (fun s ->
1100 let xs' = List.map swap xs in
1101 List.assoc s xs'
1102 ),
1103 (fun a ->
1104 List.assoc a xs
1105 )
1106
708f4980
C
1107
1108
1109(* julia: convert something printed using format to print into a string *)
1110(* now at bottom of file
1111let format_to_string f =
1112 ...
1113*)
1114
1115
1116
34e49164
C
1117(*****************************************************************************)
1118(* Macro *)
1119(*****************************************************************************)
1120
1121(* put your macro in macro.ml4, and you can test it interactivly as in lisp *)
1122let macro_expand s =
1123 let c = open_out "/tmp/ttttt.ml" in
1124 begin
1125 output_string c s; close_out c;
1126 command2 ("ocamlc -c -pp 'camlp4o pa_extend.cmo q_MLast.cmo -impl' " ^
1127 "-I +camlp4 -impl macro.ml4");
1128 command2 "camlp4o ./macro.cmo pr_o.cmo /tmp/ttttt.ml";
1129 command2 "rm -f /tmp/ttttt.ml";
1130 end
1131
1132(*
1133let t = macro_expand "{ x + y | (x,y) <- [(1,1);(2,2);(3,3)] and x>2 and y<3}"
1134let x = { x + y | (x,y) <- [(1,1);(2,2);(3,3)] and x > 2 and y < 3}
1135let t = macro_expand "{1 .. 10}"
1136let x = {1 .. 10} +> List.map (fun i -> i)
1137let t = macro_expand "[1;2] to append to [2;4]"
1138let t = macro_expand "{x = 2; x = 3}"
1139
1140let t = macro_expand "type 'a bintree = Leaf of 'a | Branch of ('a bintree * 'a bintree)"
1141*)
1142
1143
1144
1145(*****************************************************************************)
1146(* Composition/Control *)
1147(*****************************************************************************)
1148
1149(* I like the obj.func object notation. In OCaml cant use '.' so I use +>
1150 *
1151 * update: it seems that F# agrees with me :) but they use |>
1152 *)
1153
1154(* now in prelude:
1155 * let (+>) o f = f o
1156 *)
1157let (+!>) refo f = refo := f !refo
1158(* alternatives:
1159 * let ((@): 'a -> ('a -> 'b) -> 'b) = fun a b -> b a
1160 * let o f g x = f (g x)
1161 *)
1162
1163let ($) f g x = g (f x)
1164let compose f g x = f (g x)
1165