Release of coccinelle 1.0.0-rc9
[bpt/coccinelle.git] / ocaml / coccilib.mli
1 (** Library of functions for use with Coccinelle OCaml script code
2 *)
3
4 (** A value of type {b pos} describes a position in a source file.
5 *)
6 type pos = {
7 current_element : string;
8 (** {b current_element} is the name of the function containing the
9 matched position *)
10 file :string ;
11 (** {b file} is the name of the file containing the matched
12 position *)
13 line : int;
14 (** {b line} is the number of the line containing the first
15 character of the matched position *)
16 col : int;
17 (** {b col} is the column containing the first character of the
18 matched position *)
19 line_end : int;
20 (** {b line_end} is the number of the line containing the last
21 character of the matched position *)
22 col_end : int;
23 (** {b col_end} is the column containing the last character of the
24 matched position. *)
25 }
26
27 (**
28 Types describing the metavariables
29 *)
30 type param_type =
31 Pos of pos list
32 | Str of string
33 | Type of Ast_c.fullType
34 | Init of Ast_c.initialiser
35 | InitList of Ast_c.initialiser Ast_c.wrap2 list
36 | Int of int
37 | Param of Ast_c.parameterType
38 | ParamList of Ast_c.parameterType Ast_c.wrap2 list
39 | Expr of Ast_c.expression
40 | ExprList of Ast_c.argument Ast_c.wrap2 list
41 | Decl of Ast_c.declaration
42 | Field of Ast_c.field
43 | FieldList of Ast_c.field list
44 | Stmt of Ast_c.statement
45
46 (* ---------------------------------------------------------------------- *)
47 (* Match management *)
48
49 (** If the argument is true, retain the environment with respect to
50 which the ocaml script code is being executed for use in subsequent
51 rules. If the argument is false, discard this environment. By
52 default, the environment is retained.
53 *)
54 val include_match : bool -> unit
55
56 (**
57 See include_match
58 *)
59 val inc_match : bool ref
60
61 (** If called, aborts the treatment of the current file. All previous
62 changes take effect.
63 *)
64 val exit : unit -> unit
65
66 (**
67 See exit
68 *)
69 val exited : bool ref
70
71 (** Returns the directory on which spatch was launched.*)
72 val dir : unit -> string
73
74 (**/**)
75
76 (**
77 For internal use only
78 *)
79 val fcts : (string, param_type list -> string ref list -> unit) Hashtbl.t
80
81 (* org mode *)
82
83 val print_main : ?color:string -> string -> pos list -> unit
84 val print_sec : ?color:string -> string -> pos list -> unit
85 val print_secs : ?color:string -> string -> pos list -> unit