Release coccinelle-0.1.2
[bpt/coccinelle.git] / commons / common.mli
CommitLineData
34e49164
C
1(*###########################################################################*)
2(* Globals *)
3(*###########################################################################*)
4
5(* Some conventions:
6 *
7 * When I have some _xxx variables before some functions, it's
8 * because I want to show that those functions internally use a global
9 * variable. That does not mean I want people to modify this global.
10 * In fact they are kind of private, but I still want to show them.
11 * Maybe one day OCaml will have an effect type system so I don't need this.
12 *
13 * The variables that are called _init_xxx show the internal init
14 * side effect of the module (like static var trick used in C/C++)
15 *
16 * Why not split the functionnalities of this file in different files ?
17 * Because when I write ocaml script I want simply to load one
18 * file, common.ml, and that's it. Cf common_extra.ml for more on this.
19 *)
20
21
22(*****************************************************************************)
23(* Flags *)
24(*****************************************************************************)
25(* see the corresponding section for the use of those flags. See also
26 * the "Flags and actions" section at the end of this file.
27 *)
28
29(* if set then will not do certain finalize so faster to go back in replay *)
30val debugger : bool ref
31
32type prof = PALL | PNONE | PSOME of string list
33val profile : prof ref
485bce71
C
34val show_trace_profile : bool ref
35
34e49164
C
36
37val verbose_level : int ref
38
39(* forbid pr2_once to do the once "optimisation" *)
40val disable_pr2_once : bool ref
41
42
43
44(* works with new_temp_file *)
45val save_tmp_files : bool ref
46
47
48
49(*****************************************************************************)
50(* Module side effect *)
51(*****************************************************************************)
52(*
53 * I define a few unit tests via some let _ = example (... = ...).
54 * I also initialize the random seed, cf _init_random .
55 * I also set Gc.stack_size, cf _init_gc_stack .
56*)
57
58(*****************************************************************************)
59(* Semi globals *)
60(*****************************************************************************)
61(* cf the _xxx variables in this file *)
62
63(*###########################################################################*)
64(* Basic features *)
65(*###########################################################################*)
66
67type filename = string
485bce71 68type dirname = string
34e49164
C
69
70(* Trick in case you dont want to do an 'open Common' while still wanting
71 * more pervasive types than the one in Pervasives. Just do the selective
72 * open Common.BasicType.
73 *)
74module BasicType : sig
75 type filename = string
76end
77
78(* Same spirit. Trick found in Jane Street core lib, but originated somewhere
79 * else I think: the ability to open nested modules. *)
80module Infix : sig
81 val ( +> ) : 'a -> ('a -> 'b) -> 'b
82 val ( =~ ) : string -> string -> bool
83 val ( ==~ ) : string -> Str.regexp -> bool
84end
85
86
87(*
88 * Another related trick, found via Jon Harrop to have an extended standard
89 * lib is to do something like
90 *
91 * module List = struct
92 * include List
93 * val map2 : ...
94 * end
95 *
96 * And then can put this "module extension" somewhere to open it.
97 *)
98
99
100
101(* This module defines the Timeout and UnixExit exceptions.
102 * You have to make sure that those exn are not intercepted. So
103 * avoid exn handler such as try (...) with _ -> cos Timeout will not bubble up
104 * enough. In such case, add a case before such as
105 * with Timeout -> raise Timeout | _ -> ...
106 * The same is true for UnixExit (see below).
107 *)
108
109(*****************************************************************************)
110(* Debugging/logging *)
111(*****************************************************************************)
112
113val _tab_level_print: int ref
114val indent_do : (unit -> 'a) -> 'a
115val reset_pr_indent : unit -> unit
116
117(* The following functions first indent _tab_level_print spaces.
118 * They also add the _prefix_pr, for instance used in MPI to show which
119 * worker is talking.
120 *
121 * The use of 2 in pr2 is because 2 is under UNIX the second descriptor
122 * which corresponds to stderr.
123 *)
124val _prefix_pr : string ref
125val pr : string -> unit
126val pr2 : string -> unit
127val pr_no_nl : string -> unit
128val pr2_no_nl : string -> unit
129val pr_xxxxxxxxxxxxxxxxx : unit -> unit
130val pr2_xxxxxxxxxxxxxxxxx : unit -> unit
131
132(* use Dumper.dump *)
133val pr2_gen: 'a -> unit
134val dump: 'a -> string
135
136(* see flag: val disable_pr2_once : bool ref *)
137val _already_printed : (string, bool) Hashtbl.t
138val pr2_once : string -> unit
139
140val redirect_stdout_stderr : filename -> (unit -> unit) -> unit
141val redirect_stdin : filename -> (unit -> unit) -> unit
142val redirect_stdin_opt : filename option -> (unit -> unit) -> unit
143
144val fprintf : out_channel -> ('a, out_channel, unit) format -> 'a
145val printf : ('a, out_channel, unit) format -> 'a
146val eprintf : ('a, out_channel, unit) format -> 'a
147val sprintf : ('a, unit, string) format -> 'a
148
149(* alias *)
150val spf : ('a, unit, string) format -> 'a
151
152(* default = stderr *)
153val _chan : out_channel ref
154(* generate & use a /tmp/debugml-xxx file *)
155val start_log_file : unit -> unit
156
157(* see flag: val verbose_level : int ref *)
158val log : string -> unit
159val log2 : string -> unit
160val log3 : string -> unit
161val log4 : string -> unit
162
163val if_log : (unit -> unit) -> unit
164val if_log2 : (unit -> unit) -> unit
165val if_log3 : (unit -> unit) -> unit
166val if_log4 : (unit -> unit) -> unit
167
168val pause : unit -> unit
169
170(* was used by fix_caml *)
171val _trace_var : int ref
172val add_var : unit -> unit
173val dec_var : unit -> unit
174val get_var : unit -> int
175
176val print_n : int -> string -> unit
177val printerr_n : int -> string -> unit
178
179val _debug : bool ref
180val debugon : unit -> unit
181val debugoff : unit -> unit
182val debug : (unit -> unit) -> unit
183
184(* see flag: val debugger : bool ref *)
185
186
187(*****************************************************************************)
188(* Profiling (cpu/mem) *)
189(*****************************************************************************)
190
191val get_mem : unit -> unit
192val memory_stat : unit -> string
193
194val timenow : unit -> string
195
196val _count1 : int ref
197val _count2 : int ref
198val _count3 : int ref
199val _count4 : int ref
200val _count5 : int ref
201
202val count1 : unit -> unit
203val count2 : unit -> unit
204val count3 : unit -> unit
205val count4 : unit -> unit
206val count5 : unit -> unit
207val profile_diagnostic_basic : unit -> string
208
209val time_func : (unit -> 'a) -> 'a
210
211
212
213(* see flag: type prof = PALL | PNONE | PSOME of string list *)
214(* see flag: val profile : prof ref *)
215
216val _profile_table : (string, (float ref * int ref)) Hashtbl.t ref
217val profile_code : string -> (unit -> 'a) -> 'a
218val profile_diagnostic : unit -> string
219
485bce71
C
220val profile_code_exclusif : string -> (unit -> 'a) -> 'a
221val profile_code_inside_exclusif_ok : string -> (unit -> 'a) -> 'a
222
34e49164
C
223val report_if_take_time : int -> string -> (unit -> 'a) -> 'a
224
225(* similar to profile_code but print some information during execution too *)
226val profile_code2 : string -> (unit -> 'a) -> 'a
227
228(*****************************************************************************)
229(* Test *)
230(*****************************************************************************)
231
232val example : bool -> unit
233(* generate failwith <string> when pb *)
234val example2 : string -> bool -> unit
235(* use Dumper to report when pb *)
236val assert_equal : 'a -> 'a -> unit
237
238val _list_bool : (string * bool) list ref
239val example3 : string -> bool -> unit
240val test_all : unit -> unit
241
242(* regression testing *)
243type score_result = Ok | Pb of string
244type score = (string (* usually a filename *), score_result) Hashtbl.t
245val empty_score : unit -> score
246val regression_testing :
247 score -> filename (* old score file on disk (usually in /tmp) *) -> unit
248val print_score : score -> unit
249
250
251(* quickcheck spirit *)
252type 'a gen = unit -> 'a
253
254(* quickcheck random generators *)
255val ig : int gen
256val lg : 'a gen -> 'a list gen
257val pg : 'a gen -> 'b gen -> ('a * 'b) gen
258val polyg : int gen
259val ng : string gen
260
261val oneofl : 'a list -> 'a gen
262val oneof : 'a gen list -> 'a gen
263val always : 'a -> 'a gen
264val frequency : (int * 'a gen) list -> 'a gen
265val frequencyl : (int * 'a) list -> 'a gen
266
267val laws : string -> ('a -> bool) -> 'a gen -> 'a option
268
269(* example of use:
270 * let b = laws "unit" (fun x -> reverse [x] = [x]) ig
271 *)
272
273val statistic_number : 'a list -> (int * 'a) list
274val statistic : 'a list -> (int * 'a) list
275
276val laws2 :
277 string -> ('a -> bool * 'b) -> 'a gen -> 'a option * (int * 'b) list
278
279(*****************************************************************************)
280(* Persistence *)
281(*****************************************************************************)
282
283(* just wrappers around Marshall *)
284val get_value : filename -> 'a
485bce71 285val read_value : filename -> 'a (* alias *)
34e49164
C
286val write_value : 'a -> filename -> unit
287val write_back : ('a -> 'b) -> filename -> unit
288
289(*****************************************************************************)
290(* Counter *)
291(*****************************************************************************)
292val _counter : int ref
293val _counter2 : int ref
294val _counter3 : int ref
295
296val counter : unit -> int
297val counter2 : unit -> int
298val counter3 : unit -> int
299
300type timestamp = int
301
302(*****************************************************************************)
303(* String_of and (pretty) printing *)
304(*****************************************************************************)
305
306val string_of_string : (string -> string) -> string
307val string_of_list : ('a -> string) -> 'a list -> string
308val string_of_unit : unit -> string
309val string_of_array : ('a -> string) -> 'a array -> string
310val string_of_option : ('a -> string) -> 'a option -> string
311
312val print_bool : bool -> unit
313val print_option : ('a -> 'b) -> 'a option -> unit
314val print_list : ('a -> 'b) -> 'a list -> unit
315val print_between : (unit -> unit) -> ('a -> unit) -> 'a list -> unit
316
317(* use Format internally *)
318val pp_do_in_box : (unit -> unit) -> unit
319val pp_f_in_box : (unit -> 'a) -> 'a
320val pp_do_in_zero_box : (unit -> unit) -> unit
321val pp : string -> unit
322
323(* convert something printed using Format to print into a string *)
324val format_to_string : (unit -> unit) (* printer *) -> string
325
326(* works with _tab_level_print enabling to mix some calls to pp, pr2
327 * and indent_do to sometimes use advanced indentation pretty printing
328 * (with the pp* functions) and sometimes explicit and simple indendation
329 * printing (with pr* and indent_do) *)
330val adjust_pp_with_indent : (unit -> unit) -> unit
331val adjust_pp_with_indent_and_header : string -> (unit -> unit) -> unit
332
333(*****************************************************************************)
334(* Macro *)
335(*****************************************************************************)
336
337(* was working with my macro.ml4 *)
338val macro_expand : string -> unit
339
340(*****************************************************************************)
341(* Composition/Control *)
342(*****************************************************************************)
343
344val ( +> ) : 'a -> ('a -> 'b) -> 'b
345val ( +!> ) : 'a ref -> ('a -> 'a) -> unit
346val ( $ ) : ('a -> 'b) -> ('b -> 'c) -> 'a -> 'c
347
348val compose : ('a -> 'b) -> ('c -> 'a) -> 'c -> 'b
349val flip : ('a -> 'b -> 'c) -> 'b -> 'a -> 'c
350
351val curry : ('a * 'b -> 'c) -> 'a -> 'b -> 'c
352val uncurry : ('a -> 'b -> 'c) -> 'a * 'b -> 'c
353
354val id : 'a -> 'a
355val do_nothing : unit -> unit
356
357val forever : (unit -> unit) -> unit
358
359val applyn : int -> ('a -> 'a) -> 'a -> 'a
360
361class ['a] shared_variable_hook :
362 'a ->
363 object
364 val mutable data : 'a
365 val mutable registered : (unit -> unit) list
366 method get : 'a
367 method modify : ('a -> 'a) -> unit
368 method register : (unit -> unit) -> unit
369 method set : 'a -> unit
370 end
371
372val fixpoint : ('a -> 'a) -> 'a -> 'a
373val fixpoint_for_object : ((< equal : 'a -> bool; .. > as 'a) -> 'a) -> 'a -> 'a
374
375val add_hook : ('a -> ('a -> 'b) -> 'b) ref -> ('a -> ('a -> 'b) -> 'b) -> unit
376val add_hook_action : ('a -> unit) -> ('a -> unit) list ref -> unit
377val run_hooks_action : 'a -> ('a -> unit) list ref -> unit
378
379type 'a mylazy = (unit -> 'a)
380
381(* emacs spirit *)
382val save_excursion : 'a ref -> (unit -> 'b) -> 'b
383
384(* emacs spirit *)
385val unwind_protect : (unit -> 'a) -> (exn -> 'b) -> 'a
386
387(* java spirit *)
388val finalize : (unit -> 'a) -> (unit -> 'b) -> 'a
389
390val memoized : ('a, 'b) Hashtbl.t -> 'a -> (unit -> 'b) -> 'b
391
392
393(* take file from which computation is done, an extension, and the function
394 * and will compute the function only once and then save result in
395 * file ^ extension
396 *)
397val cache_computation :
398 ?verbose:bool -> ?use_cache:bool -> filename -> string (* extension *) ->
399 (unit -> 'a) -> 'a
400
401(* a more robust version where the client describes the dependencies of the
402 * computation so it will relaunch the computation in 'f' if needed.
403 *)
404val cache_computation_robust :
405 filename ->
406 string (* extension for marshalled object *) ->
407 (filename list * 'x) ->
408 string (* extension for marshalled dependencies *) ->
409 (unit -> 'a) ->
410 'a
411
412
413
414val once : ('a -> unit) -> ('a -> unit)
415
416val before_leaving : ('a -> unit) -> 'a -> 'a
417
418(* do some finalize, signal handling, unix exit conversion, etc *)
419val main_boilerplate : (unit -> unit) -> unit
420
421
422(* cf also the timeout function below that are control related too *)
423
424
425(*****************************************************************************)
426(* Concurrency *)
427(*****************************************************************************)
428
429(* how ensure really atomic file creation ? hehe :) *)
430exception FileAlreadyLocked
431val acquire_file_lock : filename -> unit
432val release_file_lock : filename -> unit
433
434(*****************************************************************************)
435(* Error managment *)
436(*****************************************************************************)
437exception Todo
438exception Impossible
439exception Here
440exception ReturnExn
441
442exception WrongFormat of string
443
444
445val internal_error : string -> 'a
446val myassert : bool -> unit
447val warning : string -> 'a -> 'a
448val error_cant_have : 'a -> 'b
449
450val exn_to_s : exn -> string
451
452(*****************************************************************************)
453(* Environment *)
454(*****************************************************************************)
455
456val check_stack_size: int -> unit
457val check_stack_nbfiles: int -> unit
458
459(* internally common.ml set Gc. parameters *)
460val _init_gc_stack : unit
461
462(*****************************************************************************)
463(* Arguments and command line *)
464(*****************************************************************************)
465
466type arg_spec_full = Arg.key * Arg.spec * Arg.doc
467type cmdline_options = arg_spec_full list
468
469
470type options_with_title = string * string * arg_spec_full list
471type cmdline_sections = options_with_title list
472
473
474(* A wrapper around Arg modules that have more logical argument order,
475 * and returns the remaining args.
476 *)
477val parse_options :
478 cmdline_options -> Arg.usage_msg -> string array -> string list
479
480(* Another wrapper that does Arg.align automatically *)
481val usage : Arg.usage_msg -> cmdline_options -> unit
482
483
484
485(* Work with the options_with_title type way to organize a long
486 * list of command line switches.
487 *)
488val short_usage :
489 Arg.usage_msg -> short_opt:cmdline_options -> unit
490val long_usage :
491 Arg.usage_msg -> short_opt:cmdline_options -> long_opt:cmdline_sections ->
492 unit
493
494(* With the options_with_title way, we don't want the default -help and --help
495 * so need adapter of Arg module, not just wrapper.
496 *)
497val arg_align2 : cmdline_options -> cmdline_options
498val arg_parse2 :
499 cmdline_options -> Arg.usage_msg -> (unit -> unit) (* short_usage func *) ->
500 string list
501
502
503
504
505
506(* The action lib. Useful to debug supart of your system. cf some of
507 * my main.ml for example of use. *)
508type flag_spec = Arg.key * Arg.spec * Arg.doc
509type action_spec = Arg.key * Arg.doc * action_func
510 and action_func = (string list -> unit)
511
512type cmdline_actions = action_spec list
513exception WrongNumberOfArguments
514
515val mk_action_0_arg : (unit -> unit) -> action_func
516val mk_action_1_arg : (string -> unit) -> action_func
517val mk_action_2_arg : (string -> string -> unit) -> action_func
518val mk_action_3_arg : (string -> string -> string -> unit) -> action_func
519
520val mk_action_n_arg : (string list -> unit) -> action_func
521
522val options_of_actions:
523 string ref (* the action ref *) -> cmdline_actions -> cmdline_options
524val action_list:
525 cmdline_actions -> Arg.key list
526val do_action:
527 Arg.key -> string list (* args *) -> cmdline_actions -> unit
528
529(*****************************************************************************)
530(* Equality *)
531(*****************************************************************************)
532
533(* Using the generic (=) is tempting, but it backfires, so better avoid it *)
534
535(* To infer all the code that use an equal, and that should be
536 * transformed, is not that easy, because (=) is used by many
537 * functions, such as List.find, List.mem, and so on. The strategy to find
538 * them is to turn what you were previously using into a function, because
539 * (=) return an exception when applied to a function, then you simply
540 * use ocamldebug to detect where the code has to be transformed by
541 * finding where the exception was launched from.
542 *)
543
544val (=|=) : int -> int -> bool
545val (=<=) : char -> char -> bool
546val (=$=) : string -> string -> bool
547val (=:=) : bool -> bool -> bool
548
549val (=*=): 'a -> 'a -> bool
550
551(* if want to restrict the use of '=', uncomment this:
552 *
553 * val (=): int -> int -> bool
554 *
555 * But it will not forbid you to use caml functions like List.find, List.mem
556 * which internaly use this convenient but evolution-unfriendly (=)
557*)
558
559
560
561
562(*###########################################################################*)
563(* And now basic types *)
564(*###########################################################################*)
565
566(*****************************************************************************)
567(* Bool *)
568(*****************************************************************************)
569
570val ( ||| ) : 'a -> 'a -> 'a
571val ( ==> ) : bool -> bool -> bool
572val xor : 'a -> 'a -> bool
573
574
575(*****************************************************************************)
576(* Char *)
577(*****************************************************************************)
578
579val string_of_char : char -> string
580val string_of_chars : char list -> string
581
582val is_single : char -> bool
583val is_symbol : char -> bool
584val is_space : char -> bool
585val is_upper : char -> bool
586val is_lower : char -> bool
587val is_alpha : char -> bool
588val is_digit : char -> bool
589
590val cbetween : char -> char -> char -> bool
591
592(*****************************************************************************)
593(* Num *)
594(*****************************************************************************)
595
596val ( /! ) : int -> int -> int
597
598val do_n : int -> (unit -> unit) -> unit
599val foldn : ('a -> int -> 'a) -> 'a -> int -> 'a
600
34e49164
C
601val pi : float
602val pi2 : float
603val pi4 : float
604
605val deg_to_rad : float -> float
606
607val clampf : float -> float
608
609val square : float -> float
610val power : int -> int -> int
611
612val between : 'a -> 'a -> 'a -> bool
613val between_strict : int -> int -> int -> bool
614val bitrange : int -> int -> bool
615
616val prime1 : int -> int option
617val prime : int -> int option
618
619val sum : int list -> int
620val product : int list -> int
621
622val decompose : int -> int list
623
624val mysquare : int -> int
625val sqr : float -> float
626
627type compare = Equal | Inf | Sup
628val ( <=> ) : 'a -> 'a -> compare
629val ( <==> ) : 'a -> 'a -> int
630
631type uint = int
632
633val int_of_stringchar : string -> int
634val int_of_base : string -> int -> int
635val int_of_stringbits : string -> int
636val int_of_octal : string -> int
637val int_of_all : string -> int
638
639(* useful but sometimes when want grep for all places where do modif,
640 * easier to have just code using ':=' and '<-' to do some modifications.
641 * In the same way avoid using {contents = xxx} to build some ref.
642 *)
643val ( += ) : int ref -> int -> unit
644val ( -= ) : int ref -> int -> unit
645
646val pourcent: int -> int -> int
647val pourcent_float: int -> int -> float
648val pourcent_float_of_floats: float -> float -> float
649
650(*****************************************************************************)
651(* Numeric/overloading *)
652(*****************************************************************************)
653
654type 'a numdict =
655 NumDict of
656 (('a -> 'a -> 'a) * ('a -> 'a -> 'a) * ('a -> 'a -> 'a) * ('a -> 'a))
657val add : 'a numdict -> 'a -> 'a -> 'a
658val mul : 'a numdict -> 'a -> 'a -> 'a
659val div : 'a numdict -> 'a -> 'a -> 'a
660val neg : 'a numdict -> 'a -> 'a
661
662val numd_int : int numdict
663val numd_float : float numdict
664
665val testd : 'a numdict -> 'a -> 'a
666
667
668module ArithFloatInfix : sig
669 val (+) : float -> float -> float
670 val (-) : float -> float -> float
671 val (/) : float -> float -> float
672 val ( * ) : float -> float -> float
673
674
675 val (+..) : int -> int -> int
676 val (-..) : int -> int -> int
677 val (/..) : int -> int -> int
678 val ( *..) : int -> int -> int
679
680 val (+=) : float ref -> float -> unit
681end
682
683(*****************************************************************************)
684(* Random *)
685(*****************************************************************************)
686
687val _init_random : unit
688val random_list : 'a list -> 'a
689val randomize_list : 'a list -> 'a list
690val random_subset_of_list : int -> 'a list -> 'a list
691
692
693(*****************************************************************************)
694(* Tuples *)
695(*****************************************************************************)
696
697type 'a pair = 'a * 'a
698type 'a triple = 'a * 'a * 'a
699
700val fst3 : 'a * 'b * 'c -> 'a
701val snd3 : 'a * 'b * 'c -> 'b
702val thd3 : 'a * 'b * 'c -> 'c
703
704val sndthd : 'a * 'b * 'c -> 'b * 'c
705
706val map_fst : ('a -> 'b) -> 'a * 'c -> 'b * 'c
707val map_snd : ('a -> 'b) -> 'c * 'a -> 'c * 'b
708
709val pair : ('a -> 'b) -> 'a * 'a -> 'b * 'b
710
711val snd : 'a * 'b -> 'b (* alias *)
712val fst : 'a * 'b -> 'a (* alias *)
713
714val double : 'a -> 'a * 'a
715val swap : 'a * 'b -> 'b * 'a
716
717(* maybe a sign of bad programming if use those functions :) *)
718val tuple_of_list1 : 'a list -> 'a
719val tuple_of_list2 : 'a list -> 'a * 'a
720val tuple_of_list3 : 'a list -> 'a * 'a * 'a
721val tuple_of_list4 : 'a list -> 'a * 'a * 'a * 'a
722val tuple_of_list5 : 'a list -> 'a * 'a * 'a * 'a * 'a
723val tuple_of_list6 : 'a list -> 'a * 'a * 'a * 'a * 'a * 'a
724
725(*****************************************************************************)
726(* Maybe *)
727(*****************************************************************************)
728
729type ('a, 'b) either = Left of 'a | Right of 'b
730type ('a, 'b, 'c) either3 = Left3 of 'a | Middle3 of 'b | Right3 of 'c
731
732val just : 'a option -> 'a
733val some : 'a option -> 'a (* alias *)
734
735val fmap : ('a -> 'b) -> 'a option -> 'b option
736val map_option : ('a -> 'b) -> 'a option -> 'b option (* alias *)
737
738val do_option : ('a -> unit) -> 'a option -> unit
739
740val optionise : (unit -> 'a) -> 'a option
741
742val some_or : 'a option -> 'a -> 'a
743
744val partition_either :
745 ('a -> ('b, 'c) either) -> 'a list -> 'b list * 'c list
746
747val filter_some : 'a option list -> 'a list
748val map_filter : ('a -> 'b option) -> 'a list -> 'b list
749val find_some : ('a -> 'b option) -> 'a list -> 'b
750
751(*****************************************************************************)
752(* Strings *)
753(*****************************************************************************)
754
755val slength : string -> int (* alias *)
756val concat : string -> string list -> string (* alias *)
757
758val i_to_s : int -> string
759val s_to_i : string -> int
760
761(* strings take space in memory. Better when can share the space used by
762 * similar strings.
763 *)
764val _shareds : (string, string) Hashtbl.t
765val shared_string : string -> string
766
767val chop : string -> string
768val chop_dirsymbol : string -> string
769
770val ( <!!> ) : string -> int * int -> string
771val ( <!> ) : string -> int -> char
772
773val split_on_char : char -> string -> string list
774
775val lowercase : string -> string
776
777val quote : string -> string
778
779val null_string : string -> bool
780val is_blank_string : string -> bool
781val is_string_prefix : string -> string -> bool
782
783
784val plural : int -> string -> string
785
786val showCodeHex : int list -> unit
787
788val size_mo_ko : int -> string
789val size_ko : int -> string
790
791val edit_distance: string -> string -> int
792
485bce71
C
793val md5sum_of_string : string -> string
794
34e49164
C
795(*****************************************************************************)
796(* Regexp *)
797(*****************************************************************************)
798
799val regexp_alpha : Str.regexp
485bce71 800val regexp_word : Str.regexp
34e49164
C
801
802val _memo_compiled_regexp : (string, Str.regexp) Hashtbl.t
803val ( =~ ) : string -> string -> bool
804val ( ==~ ) : string -> Str.regexp -> bool
805
806
807
808val regexp_match : string -> string -> string
809
810val matched : int -> string -> string
811
812(* not yet politypic functions in ocaml *)
813val matched1 : string -> string
814val matched2 : string -> string * string
815val matched3 : string -> string * string * string
816val matched4 : string -> string * string * string * string
817val matched5 : string -> string * string * string * string * string
818val matched6 : string -> string * string * string * string * string * string
819val matched7 : string -> string * string * string * string * string * string * string
820
821val string_match_substring : Str.regexp -> string -> bool
822
823val split : string (* sep regexp *) -> string -> string list
824val join : string (* sep *) -> string list -> string
825
826val split_list_regexp : string -> string list -> (string * string list) list
827
828val all_match : string (* regexp *) -> string -> string list
485bce71
C
829val global_replace_regexp :
830 string (* regexp *) -> (string -> string) -> string -> string
831
832val regular_words: string -> string list
833val contain_regular_word: string -> bool
34e49164
C
834
835(*****************************************************************************)
836(* Filenames *)
837(*****************************************************************************)
838
839(* now at beginning of this file: type filename = string *)
840val dirname : string -> string
841val basename : string -> string
842
843val filesuffix : filename -> string
844val fileprefix : filename -> string
845
846val adjust_ext_if_needed : filename -> string -> filename
847
848(* db for dir, base *)
849val db_of_filename : filename -> (string * filename)
850val filename_of_db : (string * filename) -> filename
851
852(* dbe for dir, base, ext *)
853val dbe_of_filename : filename -> string * string * string
854val dbe_of_filename_nodot : filename -> string * string * string
855(* Left (d,b,e) | Right (d,b) if file has no extension *)
856val dbe_of_filename_safe :
857 filename -> (string * string * string, string * string) either
858
859val filename_of_dbe : string * string * string -> filename
860
861(* ex: replace_ext "toto.c" "c" "var" *)
862val replace_ext: filename -> string -> string -> filename
863
864(* remove the ., .. *)
865val normalize_path : filename -> filename
866
867val relative_to_absolute : filename -> filename
868
869val filename_without_leading_path : string -> filename -> filename
870
871(*****************************************************************************)
872(* i18n *)
873(*****************************************************************************)
874type langage =
875 | English
876 | Francais
877 | Deutsch
878
879(*****************************************************************************)
880(* Dates *)
881(*****************************************************************************)
882
883(* can also use ocamlcalendar, but heavier, use many modules ... *)
884
885type month =
886 | Jan | Feb | Mar | Apr | May | Jun
887 | Jul | Aug | Sep | Oct | Nov | Dec
888type year = Year of int
889type day = Day of int
890
891type date_dmy = DMY of day * month * year
892
893type hour = Hour of int
894type minute = Min of int
895type second = Sec of int
896
897type time_hms = HMS of hour * minute * second
898
899type full_date = date_dmy * time_hms
900
901
902(* intervalle *)
903type days = Days of int
904
905type time_dmy = TimeDMY of day * month * year
906
907
908(* from Unix *)
909type float_time = float
910
911
912val mk_date_dmy : int -> int -> int -> date_dmy
913
914
915val check_date_dmy : date_dmy -> unit
916val check_time_dmy : time_dmy -> unit
917val check_time_hms : time_hms -> unit
918
919val int_to_month : int -> string
920val int_of_month : month -> int
921val month_of_string : string -> month
922val month_of_string_long : string -> month
923val string_of_month : month -> string
924
925val string_of_date_dmy : date_dmy -> string
926val string_of_unix_time : ?langage:langage -> Unix.tm -> string
927val short_string_of_unix_time : ?langage:langage -> Unix.tm -> string
928val string_of_floattime: ?langage:langage -> float_time -> string
929val short_string_of_floattime: ?langage:langage -> float_time -> string
930
931val floattime_of_string: string -> float_time
932
933val dmy_to_unixtime: date_dmy -> float_time * Unix.tm
934val unixtime_to_dmy: Unix.tm -> date_dmy
935val unixtime_to_floattime: Unix.tm -> float_time
936
937val sec_to_days : int -> string
938val sec_to_hours : int -> string
939
940val today : unit -> float_time
941val yesterday : unit -> float_time
942val tomorrow : unit -> float_time
943
944val lastweek : unit -> float_time
945val lastmonth : unit -> float_time
946
947val week_before: float_time -> float_time
948val month_before: float_time -> float_time
949val week_after: float_time -> float_time
950
951val days_in_week_of_day : float_time -> float_time list
952
953val first_day_in_week_of_day : float_time -> float_time
954val last_day_in_week_of_day : float_time -> float_time
955
956val day_secs: float_time
957
958val rough_days_since_jesus : date_dmy -> days
959val rough_days_between_dates : date_dmy -> date_dmy -> days
960
961val string_of_unix_time_lfs : Unix.tm -> string
962
485bce71
C
963val is_more_recent : date_dmy -> date_dmy -> bool
964val max_dmy : date_dmy -> date_dmy -> date_dmy
965val min_dmy : date_dmy -> date_dmy -> date_dmy
966val maximum_dmy : date_dmy list -> date_dmy
967val minimum_dmy : date_dmy list -> date_dmy
34e49164
C
968
969(*****************************************************************************)
970(* Lines/Words/Strings *)
971(*****************************************************************************)
972
973val list_of_string : string -> char list
974
975val lines : string -> string list
976val unlines : string list -> string
977
978val words : string -> string list
979val unwords : string list -> string
980
981val split_space : string -> string list
982
983val lines_with_nl : string -> string list
984
985val nblines : string -> int
986
987(*****************************************************************************)
988(* Process/Files *)
989(*****************************************************************************)
990val cat : filename -> string list
991val cat_orig : filename -> string list
992
993val interpolate : string -> string list
994
995val echo : string -> string
996
997val usleep : int -> unit
998
999val process_output_to_list : string -> string list
1000val cmd_to_list : string -> string list (* alias *)
1001val cmd_to_list_and_status : string -> string list * Unix.process_status
1002
1003val command2 : string -> unit
1004val command2_y_or_no : string -> bool
1005
1006val do_in_fork : (unit -> unit) -> int
1007
1008val mkdir: ?mode:Unix.file_perm -> string -> unit
1009
1010val read_file : filename -> string
1011val write_file : file:filename -> string -> unit
1012
1013val filesize : filename -> int
1014val filemtime : filename -> float
1015
1016val nblines_file : filename -> int
1017
1018val lfile_exists : filename -> bool
1019val is_directory : filename -> bool
1020
1021val capsule_unix : ('a -> unit) -> 'a -> unit
1022
1023val readdir_to_kind_list : string -> Unix.file_kind -> string list
1024val readdir_to_dir_list : string -> string list
1025val readdir_to_file_list : string -> string list
1026val readdir_to_link_list : string -> string list
1027val readdir_to_dir_size_list : string -> (string * int) list
1028
1029val glob : string -> filename list
1030val files_of_dir_or_files :
1031 string (* ext *) -> string list -> filename list
1032val files_of_dir_or_files_no_vcs :
1033 string (* ext *) -> string list -> filename list
1034(* use a post filter =~ for the ext filtering *)
1035val files_of_dir_or_files_no_vcs_post_filter :
1036 string (* regexp *) -> string list -> filename list
1037
1038
1039val sanity_check_files_and_adjust :
1040 string (* ext *) -> string list -> filename list
1041
1042
1043type rwx = [ `R | `W | `X ] list
1044val file_perm_of : u:rwx -> g:rwx -> o:rwx -> Unix.file_perm
1045
1046val has_env : string -> bool
1047
1048(* scheme spirit. do a finalize so no leak. *)
1049val with_open_outfile :
1050 filename -> ((string -> unit) * out_channel -> 'a) -> 'a
1051val with_open_infile :
1052 filename -> (in_channel -> 'a) -> 'a
1053val with_open_outfile_append :
1054 filename -> ((string -> unit) * out_channel -> 'a) -> 'a
1055
1056val with_open_stringbuf :
1057 (((string -> unit) * Buffer.t) -> unit) -> string
1058
1059exception Timeout
1060
1061(* subtil: have to make sure that Timeout is not intercepted before here. So
1062 * avoid exn handler such as try (...) with _ -> cos Timeout will not bubble up
1063 * enough. In such case, add a case before such as
1064 * with Timeout -> raise Timeout | _ -> ...
1065 *
1066 * The same is true for UnixExit (see below).
1067 *)
1068val timeout_function : int -> (unit -> 'a) -> 'a
1069
1070val timeout_function_opt : int option -> (unit -> 'a) -> 'a
1071
1072
1073(* creation of /tmp files, a la gcc
1074 * ex: new_temp_file "cocci" ".c" will give "/tmp/cocci-3252-434465.c"
1075 *)
1076val _temp_files_created : string list ref
1077(* see flag: val save_tmp_files : bool ref *)
1078val new_temp_file : string (* prefix *) -> string (* suffix *) -> filename
1079val erase_temp_files : unit -> unit
1080
1081(* If the user use some exit 0 in his code, then no one can intercept this
1082 * exit and do something before exiting. There is exn handler for exit 0
1083 * so better never use exit 0 but instead use an exception and just at
1084 * the very toplevel transform this exn in a unix exit code.
1085 *
1086 * subtil: same problem than with Timeout. Do not intercept such exception
1087 * with some blind try (...) with _ -> ...
1088 *)
1089exception UnixExit of int
1090val exn_to_real_unixexit : (unit -> 'a) -> 'a
1091
1092
1093
1094
1095
1096
1097
1098
1099(*###########################################################################*)
1100(* And now collection-like types. See also ocollection.mli *)
1101(*###########################################################################*)
1102
1103(*****************************************************************************)
1104(* List *)
1105(*****************************************************************************)
1106
485bce71 1107
34e49164
C
1108(* tail recursive efficient map (but that also reverse the element!) *)
1109val map_eff_rev : ('a -> 'b) -> 'a list -> 'b list
1110(* tail recursive efficient map, use accumulator *)
1111val acc_map : ('a -> 'b) -> 'a list -> 'b list
1112
1113
1114val zip : 'a list -> 'b list -> ('a * 'b) list
1115val zip_safe : 'a list -> 'b list -> ('a * 'b) list
1116val unzip : ('a * 'b) list -> 'a list * 'b list
1117
1118val take : int -> 'a list -> 'a list
1119val take_safe : int -> 'a list -> 'a list
1120val take_until : ('a -> bool) -> 'a list -> 'a list
1121val take_while : ('a -> bool) -> 'a list -> 'a list
1122
1123val drop : int -> 'a list -> 'a list
1124val drop_while : ('a -> bool) -> 'a list -> 'a list
1125val drop_until : ('a -> bool) -> 'a list -> 'a list
1126
1127val span : ('a -> bool) -> 'a list -> 'a list * 'a list
1128
1129val skip_until : ('a list -> bool) -> 'a list -> 'a list
1130val skipfirst : 'a -> 'a list -> 'a list
1131
1132(* cf also List.partition *)
1133val fpartition : ('a -> 'b option) -> 'a list -> 'b list * 'a list
1134
1135val groupBy : ('a -> 'a -> bool) -> 'a list -> 'a list list
1136val exclude_but_keep_attached: ('a -> bool) -> 'a list -> ('a * 'a list) list
485bce71 1137val group_by_post: ('a -> bool) -> 'a list -> ('a list * 'a) list * 'a list
34e49164
C
1138
1139(* use hash internally to not be in O(n2) *)
1140val group_assoc_bykey_eff : ('a * 'b) list -> ('a * 'b list) list
1141
1142val splitAt : int -> 'a list -> 'a list * 'a list
1143
1144val split_when: ('a -> bool) -> 'a list -> 'a list * 'a * 'a list
1145val split_gen_when: ('a list -> 'a list option) -> 'a list -> 'a list list
1146
1147val pack : int -> 'a list -> 'a list list
1148
1149
1150val enum : int -> int -> int list
1151val repeat : 'a -> int -> 'a list
1152val generate : int -> 'a -> 'a list
1153
1154
1155
1156val index_list : 'a list -> ('a * int) list
1157val index_list_1 : 'a list -> ('a * int) list
1158val index_list_and_total : 'a list -> ('a * int * int) list
1159
1160val iter_index : ('a -> int -> 'b) -> 'a list -> unit
1161val map_index : ('a -> int -> 'b) -> 'a list -> 'b list
1162val filter_index : (int -> 'a -> bool) -> 'a list -> 'a list
1163val fold_left_with_index : ('a -> 'b -> int -> 'a) -> 'a -> 'b list -> 'a
1164
1165val nth : 'a list -> int -> 'a
1166val rang : 'a -> 'a list -> int
1167
1168val last_n : int -> 'a list -> 'a list
1169
1170
1171
1172val snoc : 'a -> 'a list -> 'a list
1173val cons : 'a -> 'a list -> 'a list
1174val uncons : 'a list -> 'a * 'a list
1175val safe_tl : 'a list -> 'a list
1176val head_middle_tail : 'a list -> 'a * 'a list * 'a
1177val last : 'a list -> 'a
1178val list_init : 'a list -> 'a list
1179val list_last : 'a list -> 'a
1180val removelast : 'a list -> 'a list
1181
1182val inits : 'a list -> 'a list list
1183val tails : 'a list -> 'a list list
1184
1185
1186val ( ++ ) : 'a list -> 'a list -> 'a list
1187
1188val foldl1 : ('a -> 'a -> 'a) -> 'a list -> 'a
1189val fold_k : ('a -> 'b -> ('a -> 'a) -> 'a) -> ('a -> 'a) -> 'a -> 'b list -> 'a
1190val fold_right1 : ('a -> 'a -> 'a) -> 'a list -> 'a
1191val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a
1192
1193val rev_map : ('a -> 'b) -> 'a list -> 'b list
1194
1195val join_gen : 'a -> 'a list -> 'a list
1196
1197val do_withenv :
1198 (('a -> 'b) -> 'c -> 'd) -> ('e -> 'a -> 'b * 'e) -> 'e -> 'c -> 'd * 'e
1199val map_withenv : ('a -> 'b -> 'c * 'a) -> 'a -> 'b list -> 'c list * 'a
1200
1201val collect_accu : ('a -> 'b list) -> 'b list -> 'a list -> 'b list
1202val collect : ('a -> 'b list) -> 'a list -> 'b list
1203
1204val remove : 'a -> 'a list -> 'a list
1205
1206val exclude : ('a -> bool) -> 'a list -> 'a list
1207
1208(* Not like unix uniq command line tool that only delete contiguous repeated
1209 * line. Here we delete any repeated line (here list element).
1210 *)
1211val uniq : 'a list -> 'a list
1212val doublon : 'a list -> bool
1213
1214val reverse : 'a list -> 'a list (* alias *)
1215val rev : 'a list -> 'a list (* alias *)
1216val rotate : 'a list -> 'a list
1217
1218val map_flatten : ('a -> 'b list) -> 'a list -> 'b list
1219
1220val map2 : ('a -> 'b) -> 'a list -> 'b list
1221val map3 : ('a -> 'b) -> 'a list -> 'b list
1222
1223
1224val maximum : 'a list -> 'a
1225val minimum : 'a list -> 'a
1226
1227val min_with : ('a -> 'b) -> 'a list -> 'a
1228val two_mins_with : ('a -> 'b) -> 'a list -> 'a * 'a
1229
1230val all_assoc : 'a -> ('a * 'b) list -> 'b list
1231val prepare_want_all_assoc : ('a * 'b) list -> ('a * 'b list) list
1232
1233val or_list : bool list -> bool
1234val and_list : bool list -> bool
1235
485bce71
C
1236val sum_float : float list -> float
1237val sum_int : int list -> int
1238val avg_list: int list -> float
1239
34e49164
C
1240val return_when : ('a -> 'b option) -> 'a list -> 'b
1241
1242
1243val grep_with_previous : ('a -> 'a -> bool) -> 'a list -> 'a list
1244val iter_with_previous : ('a -> 'a -> 'b) -> 'a list -> unit
1245
1246val iter_with_before_after :
1247 ('a list -> 'a -> 'a list -> unit) -> 'a list -> unit
1248
1249val get_pair : 'a list -> ('a * 'a) list
1250
1251val permutation : 'a list -> 'a list list
1252
1253val remove_elem_pos : int -> 'a list -> 'a list
1254val insert_elem_pos : ('a * int) -> 'a list -> 'a list
1255val uncons_permut : 'a list -> (('a * int) * 'a list) list
1256val uncons_permut_lazy : 'a list -> (('a * int) * 'a list Lazy.t) list
1257
1258
1259val pack_sorted : ('a -> 'a -> bool) -> 'a list -> 'a list list
1260
1261val keep_best : ('a * 'a -> 'a option) -> 'a list -> 'a list
1262val sorted_keep_best : ('a -> 'a -> 'a option) -> 'a list -> 'a list
1263
1264val cartesian_product : 'a list -> 'b list -> ('a * 'b) list
1265
1266(* old stuff *)
1267val surEnsemble : 'a list -> 'a list list -> 'a list list
1268val realCombinaison : 'a list -> 'a list list
1269val combinaison : 'a list -> ('a * 'a) list
1270val insere : 'a -> 'a list list -> 'a list list
1271val insereListeContenant : 'a list -> 'a -> 'a list list -> 'a list list
1272val fusionneListeContenant : 'a * 'a -> 'a list list -> 'a list list
1273
1274(*****************************************************************************)
1275(* Arrays *)
1276(*****************************************************************************)
1277
1278val array_find_index : ('a -> bool) -> 'a array -> int
1279
1280type 'a matrix = 'a array array
1281
1282val map_matrix : ('a -> 'b) -> 'a matrix -> 'b matrix
1283
1284(*****************************************************************************)
1285(* Fast array *)
1286(*****************************************************************************)
1287
1288(* ?? *)
1289
1290(*****************************************************************************)
1291(* Set. But have a look too at set*.mli; it's better. Or use Hashtbl. *)
1292(*****************************************************************************)
1293
1294type 'a set = 'a list
1295
1296val empty_set : 'a set
1297
1298val insert_set : 'a -> 'a set -> 'a set
1299val single_set : 'a -> 'a set
1300val set : 'a list -> 'a set
1301
1302val exists_set : ('a -> bool) -> 'a set -> bool
1303val forall_set : ('a -> bool) -> 'a set -> bool
1304
1305val filter_set : ('a -> bool) -> 'a set -> 'a set
1306val fold_set : ('a -> 'b -> 'a) -> 'a -> 'b set -> 'a
1307val map_set : ('a -> 'b) -> 'a set -> 'b set
1308
1309val member_set : 'a -> 'a set -> bool
1310val find_set : ('a -> bool) -> 'a list -> 'a
1311
1312val sort_set : ('a -> 'a -> int) -> 'a list -> 'a list
1313
1314val iter_set : ('a -> unit) -> 'a list -> unit
1315
1316val top_set : 'a set -> 'a
1317
1318val inter_set : 'a set -> 'a set -> 'a set
1319val union_set : 'a set -> 'a set -> 'a set
1320val minus_set : 'a set -> 'a set -> 'a set
1321
1322val union_all : ('a set) list -> 'a set
1323
1324val big_union_set : ('a -> 'b set) -> 'a set -> 'b set
1325val card_set : 'a set -> int
1326
1327val include_set : 'a set -> 'a set -> bool
1328val equal_set : 'a set -> 'a set -> bool
1329val include_set_strict : 'a set -> 'a set -> bool
1330
1331(* could put them in Common.Infix *)
1332val ( $*$ ) : 'a set -> 'a set -> 'a set
1333val ( $+$ ) : 'a set -> 'a set -> 'a set
1334val ( $-$ ) : 'a set -> 'a set -> 'a set
1335
1336val ( $?$ ) : 'a -> 'a set -> bool
1337val ( $<$ ) : 'a set -> 'a set -> bool
1338val ( $<=$ ) : 'a set -> 'a set -> bool
1339val ( $=$ ) : 'a set -> 'a set -> bool
1340
1341val ( $@$ ) : 'a list -> 'a list -> 'a list
1342
1343val nub : 'a list -> 'a list
1344
1345(* use internally a hash and return
1346 * - the common part,
1347 * - part only in a,
1348 * - part only in b
1349 *)
1350val diff_two_say_set_eff : 'a list -> 'a list ->
1351 'a list * 'a list * 'a list
1352
1353(*****************************************************************************)
1354(* Set as normal list *)
1355(*****************************************************************************)
1356
1357(* cf above *)
1358
1359(*****************************************************************************)
1360(* Set as sorted list *)
1361(*****************************************************************************)
1362
1363
1364(*****************************************************************************)
1365(* Sets specialized *)
1366(*****************************************************************************)
1367
1368(*
1369module StringSet = Set.Make(struct type t = string let compare = compare end)
1370*)
1371
1372
1373(*****************************************************************************)
1374(* Assoc. But have a look too at Mapb.mli; it's better. Or use Hashtbl. *)
1375(*****************************************************************************)
1376
1377type ('a, 'b) assoc = ('a * 'b) list
1378
1379val assoc_to_function : ('a, 'b) assoc -> ('a -> 'b)
1380
1381val empty_assoc : ('a, 'b) assoc
1382val fold_assoc : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a
1383val insert_assoc : 'a -> 'a list -> 'a list
1384val map_assoc : ('a -> 'b) -> 'a list -> 'b list
1385val filter_assoc : ('a -> bool) -> 'a list -> 'a list
1386
1387val assoc : 'a -> ('a * 'b) list -> 'b
1388
1389val keys : ('a * 'b) list -> 'a list
1390val lookup : 'a -> ('a * 'b) list -> 'b
1391
1392val del_assoc : 'a -> ('a * 'b) list -> ('a * 'b) list
1393val replace_assoc : 'a * 'b -> ('a * 'b) list -> ('a * 'b) list
1394val apply_assoc : 'a -> ('b -> 'b) -> ('a * 'b) list -> ('a * 'b) list
1395
1396val big_union_assoc : ('a -> 'b set) -> 'a list -> 'b set
1397
1398val assoc_reverse : ('a * 'b) list -> ('b * 'a) list
1399val assoc_map : ('a * 'b) list -> ('a * 'b) list -> ('a * 'a) list
1400
1401val lookup_list : 'a -> ('a, 'b) assoc list -> 'b
1402val lookup_list2 : 'a -> ('a, 'b) assoc list -> 'b * int
1403
1404val assoc_option : 'a -> ('a, 'b) assoc -> 'b option
485bce71 1405val assoc_with_err_msg : 'a -> ('a, 'b) assoc -> 'b
34e49164
C
1406
1407(*****************************************************************************)
1408(* Assoc, specialized. *)
1409(*****************************************************************************)
1410
1411module IntMap :
1412 sig
1413 type key = int
1414 type +'a t
1415 val empty : 'a t
1416 val is_empty : 'a t -> bool
1417 val add : key -> 'a -> 'a t -> 'a t
1418 val find : key -> 'a t -> 'a
1419 val remove : key -> 'a t -> 'a t
1420 val mem : key -> 'a t -> bool
1421 val iter : (key -> 'a -> unit) -> 'a t -> unit
1422 val map : ('a -> 'b) -> 'a t -> 'b t
1423 val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
1424 val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
1425 val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
1426 val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
1427 end
1428val intmap_to_list : 'a IntMap.t -> (IntMap.key * 'a) list
1429val intmap_string_of_t : 'a -> 'b -> string
1430
1431module IntIntMap :
1432 sig
1433 type key = int * int
1434 type +'a t
1435 val empty : 'a t
1436 val is_empty : 'a t -> bool
1437 val add : key -> 'a -> 'a t -> 'a t
1438 val find : key -> 'a t -> 'a
1439 val remove : key -> 'a t -> 'a t
1440 val mem : key -> 'a t -> bool
1441 val iter : (key -> 'a -> unit) -> 'a t -> unit
1442 val map : ('a -> 'b) -> 'a t -> 'b t
1443 val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
1444 val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
1445 val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
1446 val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
1447 end
1448val intintmap_to_list : 'a IntIntMap.t -> (IntIntMap.key * 'a) list
1449val intintmap_string_of_t : 'a -> 'b -> string
1450
1451
1452(*****************************************************************************)
1453(* Hash *)
1454(*****************************************************************************)
1455
1456(* Note that Hashtbl keep old binding to a key so if want a hash
1457 * of a list, then can use the Hashtbl as is. Use Hashtbl.find_all then
1458 * to get the list of bindings
1459 *
1460 * Note that Hashtbl module use different convention :( the object is
1461 * the first argument, not last as for List or Map.
1462 *)
1463
1464(* obsolete: can use directly the Hashtbl module *)
1465val hcreate : unit -> ('a, 'b) Hashtbl.t
1466val hadd : 'a * 'b -> ('a, 'b) Hashtbl.t -> unit
1467val hmem : 'a -> ('a, 'b) Hashtbl.t -> bool
1468val hfind : 'a -> ('a, 'b) Hashtbl.t -> 'b
1469val hreplace : 'a * 'b -> ('a, 'b) Hashtbl.t -> unit
1470val hiter : ('a -> 'b -> unit) -> ('a, 'b) Hashtbl.t -> unit
1471val hfold : ('a -> 'b -> 'c -> 'c) -> ('a, 'b) Hashtbl.t -> 'c -> 'c
1472val hremove : 'a -> ('a, 'b) Hashtbl.t -> unit
1473
1474
1475val hfind_default : 'a -> (unit -> 'b) -> ('a, 'b) Hashtbl.t -> 'b
1476val hfind_option : 'a -> ('a, 'b) Hashtbl.t -> 'b option
1477val hupdate_default :
1478 'a -> ('b -> 'b) -> (unit -> 'b) -> ('a, 'b) Hashtbl.t -> unit
1479
1480val hash_to_list : ('a, 'b) Hashtbl.t -> ('a * 'b) list
1481val hash_to_list_unsorted : ('a, 'b) Hashtbl.t -> ('a * 'b) list
1482val hash_of_list : ('a * 'b) list -> ('a, 'b) Hashtbl.t
1483
1484
1485val hkeys : ('a, 'b) Hashtbl.t -> 'a list
1486
1487(*****************************************************************************)
1488(* Hash sets *)
1489(*****************************************************************************)
1490
1491type 'a hashset = ('a, bool) Hashtbl.t
1492
1493
1494(* common use of hashset, in a hash of hash *)
1495val hash_hashset_add : 'a -> 'b -> ('a, 'b hashset) Hashtbl.t -> unit
1496
1497val hashset_to_set :
1498 < fromlist : ('a ) list -> 'c; .. > -> ('a, 'b) Hashtbl.t -> 'c
1499
1500val hashset_to_list : 'a hashset -> 'a list
1501val hashset_of_list : 'a list -> 'a hashset
1502
1503
1504(*****************************************************************************)
1505(* Stack *)
1506(*****************************************************************************)
1507
1508type 'a stack = 'a list
1509val empty_stack : 'a stack
1510val push : 'a -> 'a stack -> 'a stack
1511val top : 'a stack -> 'a
1512val pop : 'a stack -> 'a stack
1513
1514val push2 : 'a -> 'a stack ref -> unit
1515val pop2: 'a stack ref -> 'a
1516
1517
1518(*****************************************************************************)
1519(* Binary tree *)
1520(*****************************************************************************)
1521type 'a bintree = Leaf of 'a | Branch of ('a bintree * 'a bintree)
1522
1523(*****************************************************************************)
1524(* N-ary tree *)
1525(*****************************************************************************)
1526
1527(* no empty tree, must have one root at least *)
1528type 'a tree = Tree of 'a * ('a tree) list
1529
1530val tree_iter : ('a -> unit) -> 'a tree -> unit
1531
1532
1533(*****************************************************************************)
1534(* N-ary tree with updatable childrens *)
1535(*****************************************************************************)
1536
1537(* Leaf can seem redundant, but sometimes want to directly see if
1538 * a children is a leaf without looking if the list is empty.
1539 *)
1540type ('a, 'b) treeref =
1541 | NodeRef of 'a * ('a, 'b) treeref list ref
1542 | LeafRef of 'b
1543
1544val treeref_node_iter:
1545 (('a * ('a, 'b) treeref list ref) -> unit) -> ('a, 'b) treeref -> unit
1546val treeref_node_iter_with_parents:
1547 (('a * ('a, 'b) treeref list ref) -> ('a list) -> unit) ->
1548 ('a, 'b) treeref -> unit
1549
1550val find_treeref:
1551 (('a * ('a, 'b) treeref list ref) -> bool) ->
1552 ('a, 'b) treeref -> ('a, 'b) treeref
1553
1554
1555
1556
1557
1558(*****************************************************************************)
1559(* Graph. But have a look too at Ograph_*.mli; it's better *)
1560(*****************************************************************************)
1561
1562type 'a graph = 'a set * ('a * 'a) set
1563
1564val add_node : 'a -> 'a graph -> 'a graph
1565val del_node : 'a -> 'a graph -> 'a graph
1566
1567val add_arc : 'a * 'a -> 'a graph -> 'a graph
1568val del_arc : 'a * 'a -> 'a graph -> 'a graph
1569
1570val successors : 'a -> 'a graph -> 'a set
1571val predecessors : 'a -> 'a graph -> 'a set
1572
1573val nodes : 'a graph -> 'a set
1574
1575val fold_upward : ('a -> 'b -> 'a) -> 'b set -> 'a -> 'b graph -> 'a
1576
1577val empty_graph : 'a list * 'b list
1578
1579
1580(*****************************************************************************)
1581(* Generic op *)
1582(*****************************************************************************)
1583
1584(* mostly alias to functions in List *)
1585
1586val map : ('a -> 'b) -> 'a list -> 'b list
1587val filter : ('a -> bool) -> 'a list -> 'a list
1588val fold : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a
1589
1590val member : 'a -> 'a list -> bool
1591
1592val iter : ('a -> unit) -> 'a list -> unit
1593
1594val find : ('a -> bool) -> 'a list -> 'a
1595
1596val exists : ('a -> bool) -> 'a list -> bool
1597val forall : ('a -> bool) -> 'a list -> bool
1598
1599val big_union : ('a -> 'b set) -> 'a list -> 'b set
1600
1601(* same than [] but easier to search for, because [] can also be a pattern *)
1602val empty_list : 'a list
1603
1604val sort : ('a -> 'a -> int) -> 'a list -> 'a list
1605
1606val length : 'a list -> int
1607
1608val null : 'a list -> bool
1609
1610val head : 'a list -> 'a
1611val tail : 'a list -> 'a list
1612
1613val is_singleton : 'a list -> bool
1614
1615
1616
1617
1618
1619
1620
1621
1622
1623(*###########################################################################*)
1624(* And now misc functions *)
1625(*###########################################################################*)
1626
1627(*****************************************************************************)
1628(* DB (LFS) *)
1629(*****************************************************************************)
1630
1631(* cf oassocbdb.ml or oassocdbm.ml *)
1632
1633(*****************************************************************************)
1634(* GUI (LFS, CComment, otimetracker) *)
1635(*****************************************************************************)
1636
1637(* cf ocamlgtk and my gui.ml *)
1638
1639
1640(*****************************************************************************)
1641(* Graphics (otimetracker) *)
1642(*****************************************************************************)
1643
1644(* cf ocamlgl and my opengl.ml *)
1645
1646
1647
1648(*****************************************************************************)
1649(* Geometry (ICFP raytracer) *)
1650(*****************************************************************************)
1651
1652type vector = float * float * float
1653
1654type point = vector
1655type color = vector
1656
1657val dotproduct : vector * vector -> float
1658
1659val vector_length : vector -> float
1660
1661val minus_point : point * point -> vector
1662
1663val distance : point * point -> float
1664
1665val normalise : vector -> vector
1666
1667val mult_coeff : vector -> float -> vector
1668
1669val add_vector : vector -> vector -> vector
1670val mult_vector : vector -> vector -> vector
1671val sum_vector : vector list -> vector
1672
1673
1674(*****************************************************************************)
1675(* Pics (ICFP raytracer) *)
1676(*****************************************************************************)
1677type pixel = int * int * int
1678val write_ppm : int -> int -> pixel list -> filename -> unit
1679val test_ppm1 : unit -> unit
1680
1681(*****************************************************************************)
1682(* Diff (LFS) *)
1683(*****************************************************************************)
1684
1685type diff = Match | BnotinA | AnotinB
1686val diff : (int -> int -> diff -> unit) -> string list * string list -> unit
1687val diff2 : (int -> int -> diff -> unit) -> string * string -> unit
1688
1689(*****************************************************************************)
1690(* Parsers (aop-colcombet) *)
1691(*****************************************************************************)
1692
1693val parserCommon : Lexing.lexbuf -> ('a -> Lexing.lexbuf -> 'b) -> 'a -> 'b
1694val getDoubleParser :
1695 ('a -> Lexing.lexbuf -> 'b) -> 'a -> (string -> 'b) * (string -> 'b)
1696
1697(*****************************************************************************)
1698(* Parsers (cocci) *)
1699(*****************************************************************************)
1700
1701
1702(* Currently lexing.ml does not handle the line number position.
1703 * Even if there is some fields in the lexing structure, they are not
1704 * maintained by the lexing engine :( So the following code does not work:
1705 *
1706 * let pos = Lexing.lexeme_end_p lexbuf in
1707 * sprintf "at file %s, line %d, char %d" pos.pos_fname pos.pos_lnum
1708 * (pos.pos_cnum - pos.pos_bol) in
1709 *
1710 * Hence those functions to overcome the previous limitation.
1711 *)
1712
1713type parse_info = {
1714 str: string;
1715 charpos: int;
1716
1717 line: int;
1718 column: int;
1719 file: filename;
1720 }
1721val fake_parse_info : parse_info
1722val string_of_parse_info : parse_info -> string
485bce71 1723val string_of_parse_info_bis : parse_info -> string
34e49164
C
1724
1725(* array[i] will contain the (line x col) of the i char position *)
1726val full_charpos_to_pos : filename -> (int * int) array
1727
1728(* fill in the line and column field of parse_info that were not set
1729 * during lexing because of limitations of ocamllex. *)
1730val complete_parse_info :
1731 filename -> (int * int) array -> parse_info -> parse_info
1732
1733(* return line x col x str_line from a charpos. This function is quite
1734 * expensive so don't use it to get the line x col from every token in
1735 * a file. Instead use full_charpos_to_pos.
1736 *)
1737val info_from_charpos : int -> filename -> (int * int * string)
1738
1739val error_message : filename -> (string * int) -> string
1740val error_message_short : filename -> (string * int) -> string
1741
1742(* add a 'decalage/shift' argument to handle stuff such as cpp which includes
1743 * files and who can make shift.
1744 *)
1745val error_messagebis : filename -> (string * int) -> int -> string
1746
1747(*****************************************************************************)
1748(* Scope managment (cocci) *)
1749(*****************************************************************************)
1750
1751(* for example of use, see the code used in coccinelle *)
1752type ('a, 'b) scoped_env = ('a, 'b) assoc list
1753
1754val lookup_env : 'a -> ('a, 'b) scoped_env -> 'b
1755val member_env_key : 'a -> ('a, 'b) scoped_env -> bool
1756
1757val new_scope : ('a, 'b) scoped_env ref -> unit
1758val del_scope : ('a, 'b) scoped_env ref -> unit
1759
1760val do_in_new_scope : ('a, 'b) scoped_env ref -> (unit -> unit) -> unit
1761
1762val add_in_scope : ('a, 'b) scoped_env ref -> 'a * 'b -> unit
1763
1764
1765
1766
1767(* for example of use, see the code used in coccinelle *)
1768type ('a, 'b) scoped_h_env = {
1769 scoped_h : ('a, 'b) Hashtbl.t;
1770 scoped_list : ('a, 'b) assoc list;
1771}
1772val empty_scoped_h_env : unit -> ('a, 'b) scoped_h_env
1773val clone_scoped_h_env : ('a, 'b) scoped_h_env -> ('a, 'b) scoped_h_env
1774
1775val lookup_h_env : 'a -> ('a, 'b) scoped_h_env -> 'b
1776val member_h_env_key : 'a -> ('a, 'b) scoped_h_env -> bool
1777
1778val new_scope_h : ('a, 'b) scoped_h_env ref -> unit
1779val del_scope_h : ('a, 'b) scoped_h_env ref -> unit
1780
1781val do_in_new_scope_h : ('a, 'b) scoped_h_env ref -> (unit -> unit) -> unit
1782
1783val add_in_scope_h : ('a, 'b) scoped_h_env ref -> 'a * 'b -> unit
1784
1785(*****************************************************************************)
1786(* Terminal (LFS) *)
1787(*****************************************************************************)
1788
1789val _execute_and_show_progress_func :
1790 (int (* length *) -> ((unit -> unit) -> unit) -> unit) ref
1791val execute_and_show_progress :
1792 int (* length *) -> ((unit -> unit) -> unit) -> unit
1793
1794(*****************************************************************************)
1795(* Flags and actions *)
1796(*****************************************************************************)
1797
1798val cmdline_flags_devel : unit -> cmdline_options
1799val cmdline_flags_verbose : unit -> cmdline_options
1800val cmdline_flags_other : unit -> cmdline_options
1801
1802(*****************************************************************************)
1803(* Misc/test *)
1804(*****************************************************************************)
1805
1806val generic_print : 'a -> string -> string
1807
1808class ['a] olist :
1809 'a list ->
1810 object
1811 val xs : 'a list
1812 method fold : ('b -> 'a -> 'b) -> 'b -> 'b
1813 method view : 'a list
1814 end
1815
1816val typing_sux_test : unit -> unit
1817