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