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