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