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