Coccinelle release 1.0.0-rc15
[bpt/coccinelle.git] / ocaml / coccilib.ml
1 (* Function table management *)
2
3 type pos = { current_element : string;
4 file :string ;
5 line : int;
6 col : int;
7 line_end : int;
8 col_end : int; }
9
10 type param_type =
11 Pos of pos list
12 | Str of string
13 | Type of Ast_c.fullType
14 | Init of Ast_c.initialiser
15 | InitList of Ast_c.initialiser Ast_c.wrap2 list
16 | Int of int
17 | Param of Ast_c.parameterType
18 | ParamList of Ast_c.parameterType Ast_c.wrap2 list
19 | Expr of Ast_c.expression
20 | ExprList of Ast_c.argument Ast_c.wrap2 list
21 | Decl of Ast_c.declaration
22 | Field of Ast_c.field
23 | FieldList of Ast_c.field list
24 | Stmt of Ast_c.statement
25
26 let fcts : (string, param_type list -> string ref list -> unit) Hashtbl.t =
27 Hashtbl.create 11 (* Use prime number *)
28
29 (* ---------------------------------------------------------------------- *)
30 (* Match management *)
31
32 let inc_match = ref true
33 let include_match x = inc_match := x
34
35 let exited = ref false
36 let exit _ = exited := true
37
38 let dir () = !Flag.dir
39
40 (* ---------------------------------------------------------------------- *)
41 (* org mode *)
42
43 let build_link p msg color =
44 Printf.sprintf
45 "[[view:%s::face=%s::linb=%d::colb=%d::cole=%d][%s]]"
46 p.file color p.line p.col p.col_end msg
47
48 let print_todo ?color:(color="ovl-face1") ?msg:(msg="") p =
49 let msg =
50 if msg = ""
51 then Printf.sprintf "%s::%d" p.file p.line
52 else msg in
53 Printf.printf "* TODO %s\n" (build_link p msg color)
54
55 let print_link ?color:(color="ovl-face2") ?msg:(msg="") p =
56 let msg =
57 if msg = ""
58 then Printf.sprintf "%s::%d" p.file p.line
59 else msg in
60 Printf.printf "%s\n" (build_link p msg color)
61
62 let print_safe_todo ?color:(color="ovl-face1") ?msg:(msg="") p =
63 let msg = String.concat "@(" (Str.split_delim (Str.regexp_string "[") msg) in
64 let msg = String.concat ")" (Str.split_delim (Str.regexp_string "]") msg) in
65 print_todo ~color:color ~msg:msg p
66
67 let print_safe_link ?color:(color="ovl-face2") ?msg:(msg="") p =
68 let msg = String.concat "@(" (Str.split_delim (Str.regexp_string "[") msg) in
69 let msg = String.concat ")" (Str.split_delim (Str.regexp_string "]") msg) in
70 print_link ~color:color ~msg:msg p
71
72 (*
73 print_main, print_sec and print_secs
74 *)
75 let print_main ?color:(color="ovl-face1") msg ps =
76 let p = List.hd ps in
77 let oldmsgfmt =
78 if msg == ""
79 then Printf.sprintf "%s::%d" p.file p.line
80 else Printf.sprintf "%s %s::%d" msg p.file p.line in
81 print_todo ~color:color ~msg:oldmsgfmt p
82
83 let print_sec ?color:(color="ovl-face2") msg ps =
84 print_link ~color:color ~msg:msg (List.hd ps)
85
86 let print_secs ?color:(color="ovl-face2") msg ps =
87 List.iter (function i -> print_link ~color:color ~msg:msg i) ps
88
89 (*
90 pos transformations
91 *)
92
93 let basename_pos pos = { pos with file = Filename.basename (pos.file) }
94
95
96 (*
97 external analysis results interface
98 (in a separate module to not pollute the namespace)
99 *)
100
101 module Ana = struct
102 type result = Externalanalysis.result
103 type bound = Externalanalysis.bound
104
105 let show_bound = Externalanalysis.show_bound
106 let show_result = Externalanalysis.show_result
107
108 let load_results =
109 Externalanalysis.load_external_results
110
111 let find pos =
112 Externalanalysis.find_results pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
113
114 let inter = Externalanalysis.intersect_results
115
116 let satisfy f pos =
117 Externalanalysis.satisfy f pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
118
119 let satisfy1 f pos =
120 Externalanalysis.satisfy1 f pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
121
122 let has_any pos =
123 Externalanalysis.has_any_result pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
124
125 let for_all p pos =
126 Externalanalysis.for_all p pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
127
128 let for_all1 p pos =
129 Externalanalysis.for_all1 p pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
130
131 let exists p pos =
132 Externalanalysis.exists p pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
133
134 let single_int = Externalanalysis.single_int
135 let contains_int = Externalanalysis.contains_int
136
137 let has_only_nul pos =
138 Externalanalysis.has_only_nul pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
139
140 let has_also_nul pos =
141 Externalanalysis.has_also_nul pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
142
143 let has_also_int c pos =
144 Externalanalysis.has_also_int c pos.file (pos.line, pos.col) (pos.line_end, pos.col_end)
145
146 end