2007-02-07 00:59:16 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* ocamlbuild *)
|
|
|
|
(* *)
|
|
|
|
(* Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 2007 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
2009-03-03 08:54:58 -08:00
|
|
|
|
2007-02-07 00:59:16 -08:00
|
|
|
(* Original author: Berke Durak *)
|
|
|
|
(* Hygiene *)
|
|
|
|
open My_std
|
|
|
|
open Slurp
|
|
|
|
|
|
|
|
exception Exit_hygiene_violations
|
|
|
|
|
|
|
|
type rule =
|
|
|
|
| Implies_not of pattern * pattern
|
|
|
|
| Not of pattern
|
|
|
|
and pattern = suffix
|
|
|
|
and suffix = string
|
|
|
|
|
|
|
|
type penalty = Warn | Fail
|
|
|
|
|
|
|
|
type law = {
|
|
|
|
law_name : string;
|
|
|
|
law_rules : rule list;
|
|
|
|
law_penalty : penalty
|
|
|
|
}
|
|
|
|
|
|
|
|
let list_collect f l =
|
|
|
|
let rec loop result = function
|
|
|
|
| [] -> List.rev result
|
|
|
|
| x :: rest ->
|
|
|
|
match f x with
|
|
|
|
| None -> loop result rest
|
|
|
|
| Some y -> loop (y :: result) rest
|
|
|
|
in
|
|
|
|
loop [] l
|
|
|
|
|
|
|
|
let list_none_for_all f l =
|
|
|
|
let rec loop = function
|
|
|
|
| [] -> None
|
|
|
|
| x :: rest ->
|
|
|
|
match f x with
|
|
|
|
| None -> loop rest
|
|
|
|
| y -> y
|
|
|
|
in
|
|
|
|
loop l
|
|
|
|
|
|
|
|
let sf = Printf.sprintf
|
|
|
|
|
|
|
|
module SS = Set.Make(String);;
|
|
|
|
|
2007-02-22 07:56:23 -08:00
|
|
|
let check ?sanitize laws entry =
|
2007-02-07 00:59:16 -08:00
|
|
|
let penalties = ref [] in
|
|
|
|
let microbes = ref SS.empty in
|
2007-11-22 10:29:32 -08:00
|
|
|
let () =
|
|
|
|
match sanitize with
|
|
|
|
| Some fn -> if sys_file_exists fn then sys_remove fn
|
|
|
|
| None -> ()
|
|
|
|
in
|
2007-02-07 00:59:16 -08:00
|
|
|
let remove path name =
|
2007-02-22 07:56:23 -08:00
|
|
|
if sanitize <> None then
|
2007-02-07 00:59:16 -08:00
|
|
|
microbes := SS.add (filename_concat path name) !microbes
|
|
|
|
in
|
|
|
|
let check_rule = fun entries -> function
|
|
|
|
| Not suffix ->
|
|
|
|
list_collect
|
|
|
|
begin function
|
|
|
|
| File(path, name, _, true) ->
|
|
|
|
if Filename.check_suffix name suffix then
|
|
|
|
begin
|
|
|
|
remove path name;
|
|
|
|
Some(sf "File %s in %s has suffix %s" name path suffix)
|
|
|
|
end
|
|
|
|
else
|
|
|
|
None
|
|
|
|
| File _ | Dir _| Error _ | Nothing -> None
|
|
|
|
end
|
|
|
|
entries
|
|
|
|
| Implies_not(suffix1, suffix2) ->
|
|
|
|
list_collect
|
|
|
|
begin function
|
|
|
|
| File(path, name, _, true) ->
|
|
|
|
if Filename.check_suffix name suffix1 then
|
|
|
|
begin
|
|
|
|
let base = Filename.chop_suffix name suffix1 in
|
|
|
|
let name' = base ^ suffix2 in
|
|
|
|
if List.exists
|
|
|
|
begin function
|
|
|
|
| File(_, name'', _, true) -> name' = name''
|
|
|
|
| File _ | Dir _ | Error _ | Nothing -> false
|
|
|
|
end
|
|
|
|
entries
|
|
|
|
then
|
|
|
|
begin
|
|
|
|
remove path name';
|
|
|
|
Some(sf "Files %s and %s should not be together in %s" name name' path)
|
|
|
|
end
|
|
|
|
else
|
|
|
|
None
|
|
|
|
end
|
|
|
|
else
|
|
|
|
None
|
|
|
|
| File _ | Dir _ | Error _ | Nothing -> None
|
|
|
|
end
|
|
|
|
entries
|
|
|
|
in
|
|
|
|
let rec check_entry = function
|
|
|
|
| Dir(_,_,_,true,entries) ->
|
|
|
|
List.iter
|
|
|
|
begin fun law ->
|
|
|
|
match List.concat (List.map (check_rule !*entries) law.law_rules) with
|
|
|
|
| [] -> ()
|
|
|
|
| explanations ->
|
|
|
|
penalties := (law, explanations) :: !penalties
|
|
|
|
end
|
|
|
|
laws;
|
|
|
|
List.iter check_entry !*entries
|
|
|
|
| Dir _ | File _ | Error _ | Nothing -> ()
|
|
|
|
in
|
|
|
|
check_entry entry;
|
|
|
|
begin
|
|
|
|
let microbes = !microbes in
|
2007-02-08 08:53:39 -08:00
|
|
|
if not (SS.is_empty microbes) then
|
2007-02-07 00:59:16 -08:00
|
|
|
begin
|
2007-02-22 07:56:23 -08:00
|
|
|
match sanitize with
|
2007-02-08 08:53:39 -08:00
|
|
|
| None ->
|
2007-02-22 07:56:23 -08:00
|
|
|
Log.eprintf "sanitize: the following are files that should probably not be in your\n\
|
2007-02-08 08:53:39 -08:00
|
|
|
source tree:\n";
|
2007-02-07 00:59:16 -08:00
|
|
|
SS.iter
|
|
|
|
begin fun fn ->
|
2007-02-08 08:53:39 -08:00
|
|
|
Log.eprintf " %s" fn
|
2007-02-07 00:59:16 -08:00
|
|
|
end
|
|
|
|
microbes;
|
2007-02-22 07:56:23 -08:00
|
|
|
Log.eprintf "Remove them manually, don't use the -no-sanitize option, use -no-hygiene, or\n\
|
2007-02-08 08:53:39 -08:00
|
|
|
define hygiene exceptions using the tags or plugin mechanism.\n";
|
|
|
|
raise Exit_hygiene_violations
|
|
|
|
| Some fn ->
|
|
|
|
let m = SS.cardinal microbes in
|
2007-02-22 07:56:23 -08:00
|
|
|
Log.eprintf
|
|
|
|
"@[<hov 2>SANITIZE:@ a@ total@ of@ %d@ file%s@ that@ should@ probably\
|
|
|
|
@ not@ be@ in@ your@ source@ tree@ has@ been@ found.\
|
|
|
|
@ A@ script@ shell@ file@ %S@ is@ being@ created.\
|
|
|
|
@ Check@ this@ script@ and@ run@ it@ to@ remove@ unwanted@ files\
|
|
|
|
@ or@ use@ other@ options@ (such@ as@ defining@ hygiene@ exceptions\
|
2010-01-22 04:48:24 -08:00
|
|
|
@ or@ using@ the@ -no-hygiene@ option).@]"
|
2007-02-22 07:56:23 -08:00
|
|
|
m (if m = 1 then "" else "s") fn;
|
2007-02-08 08:53:39 -08:00
|
|
|
let oc = open_out_gen [Open_wronly; Open_creat; Open_trunc; Open_text] 0o755 fn in
|
|
|
|
let fp = Printf.fprintf in
|
|
|
|
fp oc "#!/bin/sh\n\
|
|
|
|
# File generated by ocamlbuild\n\
|
2007-11-22 10:29:32 -08:00
|
|
|
\n\
|
|
|
|
cd %s\n\
|
|
|
|
\n" (Shell.quote_filename_if_needed Pathname.pwd);
|
2007-02-08 08:53:39 -08:00
|
|
|
SS.iter
|
|
|
|
begin fun fn ->
|
|
|
|
fp oc "rm -f %s\n" (Shell.quote_filename_if_needed fn)
|
|
|
|
end
|
|
|
|
microbes;
|
2007-02-22 08:51:39 -08:00
|
|
|
(* Also clean itself *)
|
|
|
|
fp oc "# Also clean the script itself\n";
|
|
|
|
fp oc "rm -f %s\n" (Shell.quote_filename_if_needed fn);
|
2007-02-08 08:53:39 -08:00
|
|
|
close_out oc
|
|
|
|
end;
|
|
|
|
!penalties
|
2007-02-07 00:59:16 -08:00
|
|
|
end
|
|
|
|
;;
|