[camlp4] Improve and debug the clean target. No longer use the Unix module on Windows in Camlp4Printers.Auto
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7620 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
fbea66a95e
commit
5524a775d5
|
@ -16,7 +16,11 @@
|
|||
* - Nicolas Pouillard: initial version
|
||||
*)
|
||||
|
||||
IFDEF UNIX THEN
|
||||
if (Unix.fstat Unix.stdout).Unix.st_kind = Unix.S_CHR then
|
||||
Camlp4.Printers.OCaml.enable ()
|
||||
else
|
||||
Camlp4.Printers.DumpOCamlAst.enable ();
|
||||
Camlp4.Printers.DumpOCamlAst.enable ()
|
||||
ELSE
|
||||
Camlp4.Printers.DumpOCamlAst.enable ()
|
||||
ENDIF;
|
||||
|
|
|
@ -23,19 +23,30 @@ opt install doc all pack just_doc: yam
|
|||
@echo 'YAM $@ (use "make $@ VERBOSE=1" for a verbose make)'
|
||||
@$(YAM) $(YAM_OPTIONS) $@
|
||||
|
||||
genclean: yam
|
||||
$(YAM) -genclean Makefile.clean
|
||||
|
||||
clean:
|
||||
if test -x ../ocaml; then \
|
||||
$(OCAML) build/build.ml -clean; \
|
||||
if test -x ../boot/ocamlrun; then \
|
||||
if test -x ../ocaml; then \
|
||||
$(OCAML) build/build.ml -clean; \
|
||||
else \
|
||||
if test -x ./yam; then \
|
||||
$(YAM) $(YAM_OPTIONS) -clean; \
|
||||
else \
|
||||
$(MAKE) staticclean; \
|
||||
fi; \
|
||||
fi; \
|
||||
else \
|
||||
if test -x $(YAM); then \
|
||||
$(YAM) $(YAM_OPTIONS) -clean; \
|
||||
else : ; \
|
||||
fi; \
|
||||
$(MAKE) staticclean; \
|
||||
fi
|
||||
|
||||
cleanall:
|
||||
$(OCAML) build/build.ml -cleanall
|
||||
|
||||
staticclean:
|
||||
rm -f $(CLEANFILES)
|
||||
|
||||
yam: build/build.ml
|
||||
$(OCAML) build/build.ml
|
||||
|
||||
|
@ -68,3 +79,4 @@ compare:
|
|||
.PHONY: clean install all uninstall backup restore boot-clean promote-debug \
|
||||
promote compare opt doc cleanall all-local clean-local depend
|
||||
|
||||
-include Makefile.clean
|
||||
|
|
File diff suppressed because it is too large
Load Diff
|
@ -74,12 +74,16 @@ let () =
|
|||
|
||||
let options_without_camlp4 = new_scope (lazy !options)
|
||||
|
||||
let windows = Sys.os_type = "Win32"
|
||||
|
||||
let may_define_unix = if windows then [] else ["-D UNIX"]
|
||||
|
||||
let () =
|
||||
!options.ocaml_Flags ^= "-w Ale -warn-error Ale"^^
|
||||
(if getenv "DTYPES" "" <> "" then "-dtypes"
|
||||
else "");
|
||||
!options.ocaml_P4 := camlp4boot_may_debug [];
|
||||
!options.ocaml_P4_opt := camlp4boot_may_debug ["-D OPT"];
|
||||
!options.ocaml_P4 := camlp4boot_may_debug may_define_unix;
|
||||
!options.ocaml_P4_opt := camlp4boot_may_debug ("-D OPT" :: may_define_unix);
|
||||
()
|
||||
|
||||
let options_without_debug () = { (!options) with ocaml_P4 = ref camlp4boot
|
||||
|
@ -463,8 +467,6 @@ let all =
|
|||
] @ extensions
|
||||
|
||||
|
||||
let windows = Sys.os_type = "Win32"
|
||||
|
||||
(* X.run -> X.exe || X.run -> X *)
|
||||
let conv_byte_extension f =
|
||||
if windows then
|
||||
|
@ -535,19 +537,19 @@ main ~rebuild:(ocaml ^ "build/build.ml")
|
|||
(all @ [
|
||||
phony_unit ~depends:byte "all";
|
||||
phony_unit ~depends:opt "opt";
|
||||
generic_unit ~name:"install" ~targets:["install"]
|
||||
generic_unit ~name:"install" ~targets:["install"] ~trash:[]
|
||||
~dependencies:(fun ~native:_ _ -> [])
|
||||
~compile_cmd:(fun _ -> install (); exit 0)
|
||||
();
|
||||
generic_unit ~name:"doc" ~targets:["doc"]
|
||||
generic_unit ~name:"doc" ~targets:["doc"] ~trash:[]
|
||||
~dependencies:(fun ~native:_ _ -> [])
|
||||
~compile_cmd:(fun _ -> doc (); exit 0)
|
||||
();
|
||||
generic_unit ~name:"just_doc" ~targets:["just_doc"]
|
||||
generic_unit ~name:"just_doc" ~targets:["just_doc"] ~trash:[]
|
||||
~dependencies:(fun ~native:_ _ -> [])
|
||||
~compile_cmd:(fun _ -> just_doc (); exit 0)
|
||||
();
|
||||
generic_unit ~name:"pack" ~targets:["pack"]
|
||||
generic_unit ~name:"pack" ~targets:["pack"] ~trash:[]
|
||||
~dependencies:(fun ~native:_ _ -> [])
|
||||
~compile_cmd:(fun _ -> pack (); exit 0)
|
||||
();
|
||||
|
|
|
@ -560,6 +560,7 @@ let ocaml_Program ?(o= !options) ?flags ?byte_flags ?opt_flags ?includes ?(libra
|
|||
let phony_unit ?(depends=["@FORCE@"]) ?(command="") name =
|
||||
generic_unit ~targets:[name]
|
||||
~name
|
||||
~trash:[]
|
||||
~dependencies:(fun ~native f -> depends)
|
||||
~compile_cmd: (fun _ -> command,[])
|
||||
()
|
||||
|
@ -733,6 +734,14 @@ let clean p =
|
|||
silent_remove st_cache;
|
||||
iter_units (fun u -> List.iter silent_remove u.trash) p.units
|
||||
|
||||
let genclean p out =
|
||||
let trash =
|
||||
fold_units (fun u -> List.fold_right (fun x acc -> x :: acc) u.trash)
|
||||
[] p.units in
|
||||
let out = open_out out in
|
||||
Format.fprintf (Format.formatter_of_out_channel out)
|
||||
"CLEANFILES = \\\n %s@." (String.concat " \\\n " trash);
|
||||
close_out out
|
||||
|
||||
(* (\* génération de la documentation *\) *)
|
||||
(* let doc p = *)
|
||||
|
@ -848,6 +857,7 @@ let main ?rebuild ?deps l =
|
|||
in
|
||||
let version() = alone "-version"; Printf.printf "YaM version 1.0\n"; exit 0 in
|
||||
let clean() = alone "-clean"; clean p; exit 0 in
|
||||
let genclean s = genclean p s; exit 0 in
|
||||
let verbosity s =
|
||||
match s with
|
||||
| ""|"0" -> print_cmds := false
|
||||
|
@ -855,6 +865,7 @@ let main ?rebuild ?deps l =
|
|||
Arg.parse [
|
||||
"-version", Arg.Unit version, " \tdisplay version information";
|
||||
"-clean", Arg.Unit clean, " \tremove all generated files";
|
||||
"-genclean",Arg.String genclean, " \tgenerate a clean file list in the given file";
|
||||
"-v", Arg.Set print_deps, " \t\tbe verbose: print dependencies commands";
|
||||
"-q", Arg.Clear print_cmds, " \t\tbe quiet: do not print commands";
|
||||
"-r", Arg.String Sys.chdir, " <dir>\tset `dir' as root directory";
|
||||
|
|
Loading…
Reference in New Issue