]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/ocamlbuild/fda.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / ocamlbuild / fda.ml
1 (***********************************************************************)
2 (*                             ocamlbuild                              *)
3 (*                                                                     *)
4 (*  Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
5 (*                                                                     *)
6 (*  Copyright 2007 Institut National de Recherche en Informatique et   *)
7 (*  en Automatique.  All rights reserved.  This file is distributed    *)
8 (*  under the terms of the Q Public License version 1.0.               *)
9 (*                                                                     *)
10 (***********************************************************************)
11
12
13 (* Original author: Berke Durak *)
14 (* FDA *)
15
16 open Log
17 open Hygiene
18 ;;
19
20 exception Exit_hygiene_failed
21 ;;
22
23 let laws =
24   [
25     { law_name = "Leftover Ocaml compilation files";
26       law_rules = [Not ".cmo"; Not ".cmi"; Not ".cmx"; Not ".cma"; Not ".cmxa"];
27       law_penalty = Fail };
28     { law_name = "Leftover Ocaml type annotation files";
29       law_rules = [Not ".annot"];
30       law_penalty = Warn };
31     { law_name = "Leftover object files";
32       law_rules = [Not ".o"; Not ".a"; Not ".so"; Not ".obj"; Not ".lib"; Not ".dll"];
33       law_penalty = Fail };
34     { law_name = "Leftover ocamlyacc-generated files";
35       law_rules = [Implies_not(".mly",".ml"); Implies_not(".mly",".mli")];
36       law_penalty = Fail };
37     { law_name = "Leftover ocamllex-generated files";
38       law_rules = [Implies_not(".mll",".ml")];
39       law_penalty = Fail };
40     { law_name = "Leftover dependency files";
41       law_rules = [Not ".ml.depends"; Not ".mli.depends"];
42       law_penalty = Fail }
43   ]
44
45 let inspect entry =
46   dprintf 5 "Doing sanity checks";
47   let evil = ref false in
48   match Hygiene.check
49     ?sanitize:
50       begin
51         if !Options.sanitize then
52           Some(Pathname.concat !Options.build_dir !Options.sanitization_script)
53         else
54           None
55       end
56       laws entry
57   with
58   | [] -> ()
59   | stuff ->
60     List.iter
61       begin fun (law, msgs) ->
62         Printf.printf "%s: %s:\n"
63           (match law.law_penalty with
64            | Warn -> "Warning"
65            | Fail ->
66                if not !evil then
67                  begin
68                    Printf.printf "IMPORTANT: I cannot work with leftover compiled files.\n%!";
69                    evil := true
70                  end;
71               "ERROR")
72           law.law_name;
73         List.iter
74           begin fun msg ->
75             Printf.printf "  %s\n" msg
76           end
77           msgs
78       end
79       stuff;
80     if !evil then raise Exit_hygiene_failed;
81 ;;