1999-01-27 02:53:54 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1999-01-27 02:53:54 -08:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1999 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1999-01-27 02:53:54 -08:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
2013-06-05 09:34:40 -07:00
|
|
|
open Compenv
|
1999-01-27 02:53:54 -08:00
|
|
|
open Parsetree
|
2015-11-30 07:07:36 -08:00
|
|
|
module StringMap = Depend.StringMap
|
1999-01-27 02:53:54 -08:00
|
|
|
|
2013-07-17 05:35:26 -07:00
|
|
|
let ppf = Format.err_formatter
|
1999-01-27 02:53:54 -08:00
|
|
|
(* Print the dependencies *)
|
|
|
|
|
2012-01-27 05:46:00 -08:00
|
|
|
type file_kind = ML | MLI;;
|
|
|
|
|
2003-03-03 09:20:39 -08:00
|
|
|
let load_path = ref ([] : (string * string array) list)
|
2011-07-20 02:17:07 -07:00
|
|
|
let ml_synonyms = ref [".ml"]
|
|
|
|
let mli_synonyms = ref [".mli"]
|
2000-02-07 05:08:12 -08:00
|
|
|
let native_only = ref false
|
2003-03-03 09:20:39 -08:00
|
|
|
let error_occurred = ref false
|
2006-08-31 02:50:35 -07:00
|
|
|
let raw_dependencies = ref false
|
2012-01-27 05:46:00 -08:00
|
|
|
let sort_files = ref false
|
|
|
|
let all_dependencies = ref false
|
|
|
|
let one_line = ref false
|
|
|
|
let files = ref []
|
2015-04-12 10:43:04 -07:00
|
|
|
let allow_approximation = ref false
|
2015-11-30 07:07:36 -08:00
|
|
|
let map_files = ref []
|
|
|
|
let module_map = ref StringMap.empty
|
|
|
|
let debug = ref false
|
2003-03-03 09:20:39 -08:00
|
|
|
|
2006-08-30 04:22:24 -07:00
|
|
|
(* Fix path to use '/' as directory separator instead of '\'.
|
|
|
|
Only under Windows. *)
|
|
|
|
|
|
|
|
let fix_slash s =
|
|
|
|
if Sys.os_type = "Unix" then s else begin
|
2014-04-29 04:56:17 -07:00
|
|
|
String.map (function '\\' -> '/' | c -> c) s
|
2006-08-30 04:22:24 -07:00
|
|
|
end
|
|
|
|
|
2013-06-05 09:34:40 -07:00
|
|
|
(* Since we reinitialize load_path after reading OCAMLCOMP,
|
|
|
|
we must use a cache instead of calling Sys.readdir too often. *)
|
|
|
|
let dirs = ref StringMap.empty
|
|
|
|
let readdir dir =
|
|
|
|
try
|
|
|
|
StringMap.find dir !dirs
|
|
|
|
with Not_found ->
|
|
|
|
let contents =
|
|
|
|
try
|
|
|
|
Sys.readdir dir
|
|
|
|
with Sys_error msg ->
|
|
|
|
Format.fprintf Format.err_formatter "@[Bad -I option: %s@]@." msg;
|
|
|
|
error_occurred := true;
|
|
|
|
[||]
|
|
|
|
in
|
|
|
|
dirs := StringMap.add dir contents !dirs;
|
|
|
|
contents
|
|
|
|
|
2014-10-03 13:31:32 -07:00
|
|
|
let add_to_list li s =
|
|
|
|
li := s :: !li
|
|
|
|
|
2003-03-03 09:20:39 -08:00
|
|
|
let add_to_load_path dir =
|
|
|
|
try
|
2003-04-06 05:41:54 -07:00
|
|
|
let dir = Misc.expand_directory Config.standard_library dir in
|
2013-06-05 09:34:40 -07:00
|
|
|
let contents = readdir dir in
|
2014-10-03 13:31:32 -07:00
|
|
|
add_to_list load_path (dir, contents)
|
2003-03-03 09:20:39 -08:00
|
|
|
with Sys_error msg ->
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.fprintf Format.err_formatter "@[Bad -I option: %s@]@." msg;
|
2003-03-03 09:20:39 -08:00
|
|
|
error_occurred := true
|
|
|
|
|
2011-07-20 02:17:07 -07:00
|
|
|
let add_to_synonym_list synonyms suffix =
|
|
|
|
if (String.length suffix) > 1 && suffix.[0] = '.' then
|
2014-10-03 13:31:32 -07:00
|
|
|
add_to_list synonyms suffix
|
2011-07-20 02:17:07 -07:00
|
|
|
else begin
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.fprintf Format.err_formatter "@[Bad suffix: '%s'@]@." suffix;
|
2011-07-20 02:17:07 -07:00
|
|
|
error_occurred := true
|
|
|
|
end
|
|
|
|
|
2012-01-27 05:46:00 -08:00
|
|
|
(* Find file 'name' (capitalized) in search path *)
|
2002-06-07 06:30:00 -07:00
|
|
|
let find_file name =
|
2014-12-21 03:46:14 -08:00
|
|
|
let uname = String.uncapitalize_ascii name in
|
2003-03-03 09:20:39 -08:00
|
|
|
let rec find_in_array a pos =
|
|
|
|
if pos >= Array.length a then None else begin
|
|
|
|
let s = a.(pos) in
|
|
|
|
if s = name || s = uname then Some s else find_in_array a (pos + 1)
|
|
|
|
end in
|
|
|
|
let rec find_in_path = function
|
|
|
|
[] -> raise Not_found
|
|
|
|
| (dir, contents) :: rem ->
|
|
|
|
match find_in_array contents 0 with
|
2007-02-12 00:10:00 -08:00
|
|
|
Some truename ->
|
|
|
|
if dir = "." then truename else Filename.concat dir truename
|
2003-03-03 09:20:39 -08:00
|
|
|
| None -> find_in_path rem in
|
|
|
|
find_in_path !load_path
|
2000-02-07 05:08:12 -08:00
|
|
|
|
2011-07-20 02:17:07 -07:00
|
|
|
let rec find_file_in_list = function
|
|
|
|
[] -> raise Not_found
|
|
|
|
| x :: rem -> try find_file x with Not_found -> find_file_in_list rem
|
|
|
|
|
2012-01-27 05:46:00 -08:00
|
|
|
|
|
|
|
let find_dependency target_kind modname (byt_deps, opt_deps) =
|
1999-01-27 02:53:54 -08:00
|
|
|
try
|
2011-07-20 02:17:07 -07:00
|
|
|
let candidates = List.map ((^) modname) !mli_synonyms in
|
|
|
|
let filename = find_file_in_list candidates in
|
|
|
|
let basename = Filename.chop_extension filename in
|
2012-01-27 05:46:00 -08:00
|
|
|
let cmi_file = basename ^ ".cmi" in
|
2015-11-30 07:07:36 -08:00
|
|
|
let cmx_file = basename ^ ".cmx" in
|
2012-01-27 05:46:00 -08:00
|
|
|
let ml_exists =
|
|
|
|
List.exists (fun ext -> Sys.file_exists (basename ^ ext)) !ml_synonyms in
|
|
|
|
let new_opt_dep =
|
|
|
|
if !all_dependencies then
|
|
|
|
match target_kind with
|
|
|
|
| MLI -> [ cmi_file ]
|
|
|
|
| ML ->
|
2015-11-30 07:07:36 -08:00
|
|
|
cmi_file :: (if ml_exists then [ cmx_file ] else [])
|
2012-01-27 05:46:00 -08:00
|
|
|
else
|
|
|
|
(* this is a make-specific hack that makes .cmx to be a 'proxy'
|
|
|
|
target that would force the dependency on .cmi via transitivity *)
|
|
|
|
if ml_exists
|
2015-11-30 07:07:36 -08:00
|
|
|
then [ cmx_file ]
|
2012-01-27 05:46:00 -08:00
|
|
|
else [ cmi_file ]
|
|
|
|
in
|
|
|
|
( cmi_file :: byt_deps, new_opt_dep @ opt_deps)
|
1999-01-27 02:53:54 -08:00
|
|
|
with Not_found ->
|
|
|
|
try
|
2012-01-27 05:46:00 -08:00
|
|
|
(* "just .ml" case *)
|
2011-07-20 02:17:07 -07:00
|
|
|
let candidates = List.map ((^) modname) !ml_synonyms in
|
|
|
|
let filename = find_file_in_list candidates in
|
|
|
|
let basename = Filename.chop_extension filename in
|
2015-11-30 07:07:36 -08:00
|
|
|
let cmi_file = basename ^ ".cmi" in
|
|
|
|
let cmx_file = basename ^ ".cmx" in
|
2012-01-27 05:46:00 -08:00
|
|
|
let bytenames =
|
|
|
|
if !all_dependencies then
|
|
|
|
match target_kind with
|
2015-11-30 07:07:36 -08:00
|
|
|
| MLI -> [ cmi_file ]
|
|
|
|
| ML -> [ cmi_file ]
|
2012-01-27 05:46:00 -08:00
|
|
|
else
|
|
|
|
(* again, make-specific hack *)
|
|
|
|
[basename ^ (if !native_only then ".cmx" else ".cmo")] in
|
|
|
|
let optnames =
|
|
|
|
if !all_dependencies
|
|
|
|
then match target_kind with
|
2015-11-30 07:07:36 -08:00
|
|
|
| MLI -> [ cmi_file ]
|
|
|
|
| ML -> [ cmi_file; cmx_file ]
|
|
|
|
else [ cmx_file ]
|
2012-01-27 05:46:00 -08:00
|
|
|
in
|
|
|
|
(bytenames @ byt_deps, optnames @ opt_deps)
|
1999-01-27 02:53:54 -08:00
|
|
|
with Not_found ->
|
|
|
|
(byt_deps, opt_deps)
|
|
|
|
|
2010-01-07 07:10:20 -08:00
|
|
|
let (depends_on, escaped_eol) = (":", " \\\n ")
|
1999-01-27 02:53:54 -08:00
|
|
|
|
2005-03-24 09:20:54 -08:00
|
|
|
let print_filename s =
|
2013-06-05 09:34:40 -07:00
|
|
|
let s = if !Clflags.force_slash then fix_slash s else s in
|
2005-03-24 09:20:54 -08:00
|
|
|
if not (String.contains s ' ') then begin
|
|
|
|
print_string s;
|
|
|
|
end else begin
|
|
|
|
let rec count n i =
|
|
|
|
if i >= String.length s then n
|
|
|
|
else if s.[i] = ' ' then count (n+1) (i+1)
|
|
|
|
else count n (i+1)
|
|
|
|
in
|
|
|
|
let spaces = count 0 0 in
|
2014-04-29 04:56:17 -07:00
|
|
|
let result = Bytes.create (String.length s + spaces) in
|
2005-03-24 09:20:54 -08:00
|
|
|
let rec loop i j =
|
|
|
|
if i >= String.length s then ()
|
|
|
|
else if s.[i] = ' ' then begin
|
2014-04-29 04:56:17 -07:00
|
|
|
Bytes.set result j '\\';
|
|
|
|
Bytes.set result (j+1) ' ';
|
2005-03-24 09:20:54 -08:00
|
|
|
loop (i+1) (j+2);
|
|
|
|
end else begin
|
2014-04-29 04:56:17 -07:00
|
|
|
Bytes.set result j s.[i];
|
2005-03-24 09:20:54 -08:00
|
|
|
loop (i+1) (j+1);
|
|
|
|
end
|
|
|
|
in
|
|
|
|
loop 0 0;
|
2014-04-29 04:56:17 -07:00
|
|
|
print_bytes result;
|
2005-03-24 09:20:54 -08:00
|
|
|
end
|
|
|
|
;;
|
|
|
|
|
2012-01-27 05:46:00 -08:00
|
|
|
let print_dependencies target_files deps =
|
2008-08-01 02:02:55 -07:00
|
|
|
let rec print_items pos = function
|
|
|
|
[] -> print_string "\n"
|
|
|
|
| dep :: rem ->
|
2012-01-27 05:46:00 -08:00
|
|
|
if !one_line || (pos + 1 + String.length dep <= 77) then begin
|
|
|
|
if pos <> 0 then print_string " "; print_filename dep;
|
2008-08-01 02:02:55 -07:00
|
|
|
print_items (pos + String.length dep + 1) rem
|
|
|
|
end else begin
|
2010-01-07 07:10:20 -08:00
|
|
|
print_string escaped_eol; print_filename dep;
|
|
|
|
print_items (String.length dep + 4) rem
|
2008-08-01 02:02:55 -07:00
|
|
|
end in
|
2012-01-27 05:46:00 -08:00
|
|
|
print_items 0 (target_files @ [depends_on] @ deps)
|
1999-01-27 02:53:54 -08:00
|
|
|
|
2006-08-31 02:50:35 -07:00
|
|
|
let print_raw_dependencies source_file deps =
|
2012-01-27 05:46:00 -08:00
|
|
|
print_filename source_file; print_string depends_on;
|
2006-08-31 02:50:35 -07:00
|
|
|
Depend.StringSet.iter
|
2011-07-20 02:17:07 -07:00
|
|
|
(fun dep ->
|
2015-03-12 10:55:28 -07:00
|
|
|
(* filter out "*predef*" *)
|
2011-07-20 02:17:07 -07:00
|
|
|
if (String.length dep > 0)
|
2015-03-12 10:55:28 -07:00
|
|
|
&& (match dep.[0] with
|
|
|
|
| 'A'..'Z' | '\128'..'\255' -> true
|
|
|
|
| _ -> false) then
|
|
|
|
begin
|
|
|
|
print_char ' ';
|
|
|
|
print_string dep
|
|
|
|
end)
|
2006-08-31 02:50:35 -07:00
|
|
|
deps;
|
|
|
|
print_char '\n'
|
|
|
|
|
2001-08-04 08:37:39 -07:00
|
|
|
|
1999-03-11 01:56:15 -08:00
|
|
|
(* Process one file *)
|
|
|
|
|
2014-05-12 03:41:21 -07:00
|
|
|
let report_err exn =
|
2012-03-09 00:45:49 -08:00
|
|
|
error_occurred := true;
|
|
|
|
match exn with
|
|
|
|
| Sys_error msg ->
|
|
|
|
Format.fprintf Format.err_formatter "@[I/O error:@ %s@]@." msg
|
2013-09-11 11:10:59 -07:00
|
|
|
| x ->
|
|
|
|
match Location.error_of_exn x with
|
|
|
|
| Some err ->
|
|
|
|
Format.fprintf Format.err_formatter "@[%a@]@."
|
|
|
|
Location.report_error err
|
|
|
|
| None -> raise x
|
2012-03-09 00:45:49 -08:00
|
|
|
|
2014-08-07 02:46:34 -07:00
|
|
|
let tool_name = "ocamldep"
|
|
|
|
|
2015-04-12 10:43:04 -07:00
|
|
|
let rec lexical_approximation lexbuf =
|
|
|
|
(* Approximation when a file can't be parsed.
|
|
|
|
Heuristic:
|
|
|
|
- first component of any path starting with an uppercase character is a
|
|
|
|
dependency.
|
|
|
|
- always skip the token after a dot, unless dot is preceded by a
|
|
|
|
lower-case identifier
|
|
|
|
- always skip the token after a backquote
|
|
|
|
*)
|
|
|
|
try
|
|
|
|
let rec process after_lident lexbuf =
|
|
|
|
match Lexer.token lexbuf with
|
|
|
|
| Parser.UIDENT name ->
|
|
|
|
Depend.free_structure_names :=
|
|
|
|
Depend.StringSet.add name !Depend.free_structure_names;
|
|
|
|
process false lexbuf
|
|
|
|
| Parser.LIDENT _ -> process true lexbuf
|
|
|
|
| Parser.DOT when after_lident -> process false lexbuf
|
|
|
|
| Parser.DOT | Parser.BACKQUOTE -> skip_one lexbuf
|
|
|
|
| Parser.EOF -> ()
|
|
|
|
| _ -> process false lexbuf
|
|
|
|
and skip_one lexbuf =
|
|
|
|
match Lexer.token lexbuf with
|
|
|
|
| Parser.DOT | Parser.BACKQUOTE -> skip_one lexbuf
|
|
|
|
| Parser.EOF -> ()
|
|
|
|
| _ -> process false lexbuf
|
|
|
|
|
|
|
|
in
|
|
|
|
process false lexbuf
|
|
|
|
with Lexer.Error _ -> lexical_approximation lexbuf
|
|
|
|
|
|
|
|
let read_and_approximate inputfile =
|
|
|
|
error_occurred := false;
|
|
|
|
let ic = open_in_bin inputfile in
|
|
|
|
try
|
|
|
|
seek_in ic 0;
|
|
|
|
Location.input_name := inputfile;
|
|
|
|
let lexbuf = Lexing.from_channel ic in
|
|
|
|
Location.init lexbuf inputfile;
|
|
|
|
lexical_approximation lexbuf;
|
|
|
|
close_in ic;
|
|
|
|
!Depend.free_structure_names
|
|
|
|
with exn ->
|
|
|
|
close_in ic;
|
|
|
|
report_err exn;
|
|
|
|
!Depend.free_structure_names
|
|
|
|
|
2015-11-30 07:07:36 -08:00
|
|
|
let read_parse_and_extract parse_function extract_function def magic
|
|
|
|
source_file =
|
2006-08-31 02:50:35 -07:00
|
|
|
Depend.free_structure_names := Depend.StringSet.empty;
|
|
|
|
try
|
2012-07-24 09:24:44 -07:00
|
|
|
let input_file = Pparse.preprocess source_file in
|
2013-02-24 01:11:29 -08:00
|
|
|
begin try
|
|
|
|
let ast =
|
2014-10-03 13:31:34 -07:00
|
|
|
Pparse.file ~tool_name Format.err_formatter
|
2015-09-11 04:58:31 -07:00
|
|
|
input_file parse_function magic
|
2014-10-03 13:31:34 -07:00
|
|
|
in
|
2015-11-30 07:07:36 -08:00
|
|
|
let bound_vars =
|
|
|
|
List.fold_left
|
|
|
|
(fun bv modname ->
|
|
|
|
Depend.open_module bv (Longident.Lident modname))
|
|
|
|
!module_map !Clflags.open_modules
|
|
|
|
in
|
|
|
|
let r = extract_function bound_vars ast in
|
2013-02-24 01:11:29 -08:00
|
|
|
Pparse.remove_preprocessed input_file;
|
2015-11-30 07:07:36 -08:00
|
|
|
(!Depend.free_structure_names, r)
|
2013-02-24 01:11:29 -08:00
|
|
|
with x ->
|
2013-03-18 13:13:53 -07:00
|
|
|
Pparse.remove_preprocessed input_file;
|
2013-02-24 01:11:29 -08:00
|
|
|
raise x
|
|
|
|
end
|
2015-04-12 10:43:04 -07:00
|
|
|
with x -> begin
|
2014-05-12 03:41:21 -07:00
|
|
|
report_err x;
|
2015-04-12 10:43:04 -07:00
|
|
|
if not !allow_approximation
|
2015-11-30 07:07:36 -08:00
|
|
|
then (Depend.StringSet.empty, def)
|
|
|
|
else (read_and_approximate source_file, def)
|
2015-04-12 10:43:04 -07:00
|
|
|
end
|
2012-03-09 00:45:49 -08:00
|
|
|
|
|
|
|
let ml_file_dependencies source_file =
|
2012-08-10 00:19:12 -07:00
|
|
|
let parse_use_file_as_impl lexbuf =
|
|
|
|
let f x =
|
|
|
|
match x with
|
|
|
|
| Ptop_def s -> s
|
|
|
|
| Ptop_dir _ -> []
|
|
|
|
in
|
|
|
|
List.flatten (List.map f (Parse.use_file lexbuf))
|
|
|
|
in
|
2015-11-30 07:07:36 -08:00
|
|
|
let (extracted_deps, ()) =
|
|
|
|
read_parse_and_extract parse_use_file_as_impl Depend.add_implementation ()
|
2012-08-10 00:19:12 -07:00
|
|
|
Config.ast_impl_magic_number source_file
|
2012-03-09 00:45:49 -08:00
|
|
|
in
|
|
|
|
if !sort_files then
|
|
|
|
files := (source_file, ML, !Depend.free_structure_names) :: !files
|
|
|
|
else
|
2006-08-31 02:50:35 -07:00
|
|
|
if !raw_dependencies then begin
|
2012-03-09 00:45:49 -08:00
|
|
|
print_raw_dependencies source_file extracted_deps
|
2006-08-31 02:50:35 -07:00
|
|
|
end else begin
|
2008-01-22 07:46:18 -08:00
|
|
|
let basename = Filename.chop_extension source_file in
|
2013-01-03 09:38:21 -08:00
|
|
|
let byte_targets = [ basename ^ ".cmo" ] in
|
2012-01-27 05:46:00 -08:00
|
|
|
let native_targets =
|
|
|
|
if !all_dependencies
|
|
|
|
then [ basename ^ ".cmx"; basename ^ ".o" ]
|
|
|
|
else [ basename ^ ".cmx" ] in
|
|
|
|
let init_deps = if !all_dependencies then [source_file] else [] in
|
|
|
|
let cmi_name = basename ^ ".cmi" in
|
|
|
|
let init_deps, extra_targets =
|
2012-07-26 12:21:54 -07:00
|
|
|
if List.exists (fun ext -> Sys.file_exists (basename ^ ext))
|
|
|
|
!mli_synonyms
|
2012-01-27 05:46:00 -08:00
|
|
|
then (cmi_name :: init_deps, cmi_name :: init_deps), []
|
2012-07-26 12:21:54 -07:00
|
|
|
else (init_deps, init_deps),
|
|
|
|
(if !all_dependencies then [cmi_name] else [])
|
|
|
|
in
|
2012-01-27 05:46:00 -08:00
|
|
|
let (byt_deps, native_deps) =
|
|
|
|
Depend.StringSet.fold (find_dependency ML)
|
2012-03-09 00:45:49 -08:00
|
|
|
extracted_deps init_deps in
|
2015-11-30 07:07:36 -08:00
|
|
|
if not !native_only then
|
|
|
|
print_dependencies (byte_targets @ extra_targets) byt_deps;
|
2013-01-03 09:38:21 -08:00
|
|
|
print_dependencies (native_targets @ extra_targets) native_deps;
|
2012-03-09 00:45:49 -08:00
|
|
|
end
|
2006-08-31 02:50:35 -07:00
|
|
|
|
|
|
|
let mli_file_dependencies source_file =
|
2015-11-30 07:07:36 -08:00
|
|
|
let (extracted_deps, ()) =
|
|
|
|
read_parse_and_extract Parse.interface Depend.add_signature ()
|
2013-09-04 08:12:37 -07:00
|
|
|
Config.ast_intf_magic_number source_file
|
2012-07-24 09:24:44 -07:00
|
|
|
in
|
2012-03-09 00:45:49 -08:00
|
|
|
if !sort_files then
|
|
|
|
files := (source_file, MLI, extracted_deps) :: !files
|
|
|
|
else
|
2006-08-31 02:50:35 -07:00
|
|
|
if !raw_dependencies then begin
|
2012-03-09 00:45:49 -08:00
|
|
|
print_raw_dependencies source_file extracted_deps
|
2006-08-31 02:50:35 -07:00
|
|
|
end else begin
|
2008-01-22 07:46:18 -08:00
|
|
|
let basename = Filename.chop_extension source_file in
|
2014-05-12 03:41:21 -07:00
|
|
|
let (byt_deps, _opt_deps) =
|
2012-01-27 05:46:00 -08:00
|
|
|
Depend.StringSet.fold (find_dependency MLI)
|
2012-03-09 00:45:49 -08:00
|
|
|
extracted_deps ([], []) in
|
2012-01-27 05:46:00 -08:00
|
|
|
print_dependencies [basename ^ ".cmi"] byt_deps
|
2012-03-09 00:45:49 -08:00
|
|
|
end
|
2006-08-31 02:50:35 -07:00
|
|
|
|
2015-11-30 07:07:36 -08:00
|
|
|
let process_file_as process_fun def source_file =
|
2013-07-17 05:35:26 -07:00
|
|
|
Compenv.readenv ppf Before_compile;
|
2013-06-05 09:34:40 -07:00
|
|
|
load_path := [];
|
|
|
|
List.iter add_to_load_path (
|
|
|
|
(!Compenv.last_include_dirs @
|
2014-08-07 02:46:34 -07:00
|
|
|
!Clflags.include_dirs @
|
2013-06-05 09:34:40 -07:00
|
|
|
!Compenv.first_include_dirs
|
|
|
|
));
|
1999-01-27 02:53:54 -08:00
|
|
|
Location.input_name := source_file;
|
2006-08-31 02:50:35 -07:00
|
|
|
try
|
2015-11-30 07:07:36 -08:00
|
|
|
if Sys.file_exists source_file then process_fun source_file else def
|
|
|
|
with x -> report_err x; def
|
1999-01-27 02:53:54 -08:00
|
|
|
|
2015-11-30 07:07:36 -08:00
|
|
|
let process_file source_file ~ml_file ~mli_file ~def =
|
2011-07-20 02:17:07 -07:00
|
|
|
if List.exists (Filename.check_suffix source_file) !ml_synonyms then
|
2015-11-30 07:07:36 -08:00
|
|
|
process_file_as ml_file def source_file
|
2011-07-20 02:17:07 -07:00
|
|
|
else if List.exists (Filename.check_suffix source_file) !mli_synonyms then
|
2015-11-30 07:07:36 -08:00
|
|
|
process_file_as mli_file def source_file
|
|
|
|
else def
|
|
|
|
|
|
|
|
let file_dependencies source_file =
|
|
|
|
process_file source_file ~def:()
|
|
|
|
~ml_file:ml_file_dependencies
|
|
|
|
~mli_file:mli_file_dependencies
|
|
|
|
|
|
|
|
let file_dependencies_as kind =
|
|
|
|
match kind with
|
2015-12-01 02:54:15 -08:00
|
|
|
| ML -> process_file_as ml_file_dependencies ()
|
2015-11-30 07:07:36 -08:00
|
|
|
| MLI -> process_file_as mli_file_dependencies ()
|
2008-01-22 07:46:18 -08:00
|
|
|
|
2012-01-27 05:46:00 -08:00
|
|
|
let sort_files_by_dependencies files =
|
|
|
|
let h = Hashtbl.create 31 in
|
|
|
|
let worklist = ref [] in
|
|
|
|
|
|
|
|
(* Init Hashtbl with all defined modules *)
|
|
|
|
let files = List.map (fun (file, file_kind, deps) ->
|
2014-04-29 04:56:17 -07:00
|
|
|
let modname =
|
2014-12-21 03:46:14 -08:00
|
|
|
String.capitalize_ascii (Filename.chop_extension (Filename.basename file))
|
2014-04-29 04:56:17 -07:00
|
|
|
in
|
2012-01-27 05:46:00 -08:00
|
|
|
let key = (modname, file_kind) in
|
|
|
|
let new_deps = ref [] in
|
|
|
|
Hashtbl.add h key (file, new_deps);
|
|
|
|
worklist := key :: !worklist;
|
|
|
|
(modname, file_kind, deps, new_deps)
|
|
|
|
) files in
|
|
|
|
|
|
|
|
(* Keep only dependencies to defined modules *)
|
|
|
|
List.iter (fun (modname, file_kind, deps, new_deps) ->
|
|
|
|
let add_dep modname kind =
|
|
|
|
new_deps := (modname, kind) :: !new_deps;
|
|
|
|
in
|
|
|
|
Depend.StringSet.iter (fun modname ->
|
|
|
|
match file_kind with
|
|
|
|
ML -> (* ML depends both on ML and MLI *)
|
|
|
|
if Hashtbl.mem h (modname, MLI) then add_dep modname MLI;
|
|
|
|
if Hashtbl.mem h (modname, ML) then add_dep modname ML
|
|
|
|
| MLI -> (* MLI depends on MLI if exists, or ML otherwise *)
|
|
|
|
if Hashtbl.mem h (modname, MLI) then add_dep modname MLI
|
|
|
|
else if Hashtbl.mem h (modname, ML) then add_dep modname ML
|
|
|
|
) deps;
|
|
|
|
if file_kind = ML then (* add dep from .ml to .mli *)
|
|
|
|
if Hashtbl.mem h (modname, MLI) then add_dep modname MLI
|
|
|
|
) files;
|
|
|
|
|
|
|
|
(* Print and remove all files with no remaining dependency. Iterate
|
|
|
|
until all files have been removed (worklist is empty) or
|
|
|
|
no file was removed during a turn (cycle). *)
|
|
|
|
let printed = ref true in
|
|
|
|
while !printed && !worklist <> [] do
|
|
|
|
let files = !worklist in
|
|
|
|
worklist := [];
|
|
|
|
printed := false;
|
|
|
|
List.iter (fun key ->
|
|
|
|
let (file, deps) = Hashtbl.find h key in
|
|
|
|
let set = !deps in
|
|
|
|
deps := [];
|
|
|
|
List.iter (fun key ->
|
|
|
|
if Hashtbl.mem h key then deps := key :: !deps
|
|
|
|
) set;
|
|
|
|
if !deps = [] then begin
|
|
|
|
printed := true;
|
|
|
|
Printf.printf "%s " file;
|
|
|
|
Hashtbl.remove h key;
|
|
|
|
end else
|
|
|
|
worklist := key :: !worklist
|
|
|
|
) files
|
|
|
|
done;
|
|
|
|
|
|
|
|
if !worklist <> [] then begin
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.fprintf Format.err_formatter
|
2012-01-27 05:46:00 -08:00
|
|
|
"@[Warning: cycle in dependencies. End of list is not sorted.@]@.";
|
2015-08-15 08:57:57 -07:00
|
|
|
let sorted_deps =
|
|
|
|
let li = ref [] in
|
|
|
|
Hashtbl.iter (fun _ file_deps -> li := file_deps :: !li) h;
|
|
|
|
List.sort (fun (file1, _) (file2, _) -> String.compare file1 file2) !li
|
|
|
|
in
|
|
|
|
List.iter (fun (file, deps) ->
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.fprintf Format.err_formatter "\t@[%s: " file;
|
2012-01-27 05:46:00 -08:00
|
|
|
List.iter (fun (modname, kind) ->
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.fprintf Format.err_formatter "%s.%s " modname
|
2012-01-27 05:46:00 -08:00
|
|
|
(if kind=ML then "ml" else "mli");
|
|
|
|
) !deps;
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.fprintf Format.err_formatter "@]@.";
|
2015-08-15 08:57:57 -07:00
|
|
|
Printf.printf "%s " file) sorted_deps;
|
2012-01-27 05:46:00 -08:00
|
|
|
end;
|
|
|
|
Printf.printf "\n%!";
|
|
|
|
()
|
|
|
|
|
2015-11-30 07:07:36 -08:00
|
|
|
(* Map *)
|
|
|
|
|
|
|
|
let rec dump_map s0 ppf m =
|
|
|
|
let open Depend in
|
|
|
|
StringMap.iter
|
|
|
|
(fun key (Node(s1,m')) ->
|
|
|
|
let s = StringSet.diff s1 s0 in
|
|
|
|
if StringSet.is_empty s then
|
|
|
|
Format.fprintf ppf "@ @[<hv2>module %s : sig%a@;<1 -2>end@]"
|
|
|
|
key (dump_map (StringSet.union s1 s0)) m'
|
|
|
|
else
|
|
|
|
Format.fprintf ppf "@ module %s = %s" key (StringSet.choose s))
|
|
|
|
m
|
|
|
|
|
|
|
|
let process_ml_map =
|
|
|
|
read_parse_and_extract Parse.implementation Depend.add_implementation_binding
|
|
|
|
StringMap.empty Config.ast_impl_magic_number
|
|
|
|
|
|
|
|
let process_mli_map =
|
|
|
|
read_parse_and_extract Parse.interface Depend.add_signature_binding
|
|
|
|
StringMap.empty Config.ast_intf_magic_number
|
|
|
|
|
|
|
|
let parse_map fname =
|
|
|
|
map_files := fname :: !map_files ;
|
|
|
|
let old_transp = !Clflags.transparent_modules in
|
|
|
|
Clflags.transparent_modules := true;
|
|
|
|
let (deps, m) =
|
|
|
|
process_file fname ~def:(Depend.StringSet.empty, StringMap.empty)
|
|
|
|
~ml_file:process_ml_map
|
|
|
|
~mli_file:process_mli_map
|
|
|
|
in
|
|
|
|
Clflags.transparent_modules := old_transp;
|
|
|
|
let modname =
|
|
|
|
String.capitalize_ascii
|
|
|
|
(Filename.basename (Filename.chop_extension fname)) in
|
|
|
|
if StringMap.is_empty m then
|
|
|
|
report_err (Failure (fname ^ " : empty map file or parse error"));
|
|
|
|
let mm = Depend.make_node m in
|
|
|
|
if !debug then begin
|
|
|
|
Format.printf "@[<v>%s:%t%a@]@." fname
|
|
|
|
(fun ppf -> Depend.StringSet.iter (Format.fprintf ppf " %s") deps)
|
|
|
|
(dump_map deps) (StringMap.add modname mm StringMap.empty)
|
|
|
|
end;
|
|
|
|
let mm = Depend.(weaken_map (StringSet.singleton modname) mm) in
|
|
|
|
module_map := StringMap.add modname mm !module_map
|
|
|
|
;;
|
|
|
|
|
2012-01-27 05:46:00 -08:00
|
|
|
|
1999-01-27 02:53:54 -08:00
|
|
|
(* Entry point *)
|
|
|
|
|
2006-08-31 02:50:35 -07:00
|
|
|
let usage = "Usage: ocamldep [options] <source files>\nOptions are:"
|
1999-01-27 02:53:54 -08:00
|
|
|
|
2004-11-26 17:04:19 -08:00
|
|
|
let print_version () =
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.printf "ocamldep, version %s@." Sys.ocaml_version;
|
2004-11-26 17:04:19 -08:00
|
|
|
exit 0;
|
|
|
|
;;
|
|
|
|
|
2010-05-20 07:06:29 -07:00
|
|
|
let print_version_num () =
|
2012-03-08 11:52:03 -08:00
|
|
|
Format.printf "%s@." Sys.ocaml_version;
|
2010-05-20 07:06:29 -07:00
|
|
|
exit 0;
|
|
|
|
;;
|
|
|
|
|
1999-01-27 02:53:54 -08:00
|
|
|
let _ =
|
1999-12-13 01:48:38 -08:00
|
|
|
Clflags.classic := false;
|
2014-10-03 13:31:32 -07:00
|
|
|
add_to_list first_include_dirs Filename.current_dir_name;
|
2013-07-17 05:35:26 -07:00
|
|
|
Compenv.readenv ppf Before_args;
|
1999-03-11 01:56:15 -08:00
|
|
|
Arg.parse [
|
2012-08-03 03:22:35 -07:00
|
|
|
"-absname", Arg.Set Location.absname,
|
|
|
|
" Show absolute filenames in error messages";
|
2012-07-26 12:21:54 -07:00
|
|
|
"-all", Arg.Set all_dependencies,
|
|
|
|
" Generate dependencies on all files";
|
2015-11-30 07:07:36 -08:00
|
|
|
"-allow-approx", Arg.Set allow_approximation,
|
|
|
|
" Fallback to a lexer-based approximation on unparseable files";
|
|
|
|
"-as-map", Arg.Set Clflags.transparent_modules,
|
|
|
|
" Omit delayed dependencies for module aliases (-no-alias-deps -w -49)";
|
|
|
|
(* "compiler uses -no-alias-deps, and no module is coerced"; *)
|
|
|
|
"-debug-map", Arg.Set debug,
|
|
|
|
" Dump the delayed dependency map for each map file";
|
2014-10-03 13:31:32 -07:00
|
|
|
"-I", Arg.String (add_to_list Clflags.include_dirs),
|
2011-04-26 05:16:50 -07:00
|
|
|
"<dir> Add <dir> to the list of include directories";
|
2008-01-22 07:46:18 -08:00
|
|
|
"-impl", Arg.String (file_dependencies_as ML),
|
2012-07-26 12:21:54 -07:00
|
|
|
"<f> Process <f> as a .ml file";
|
2008-01-22 07:46:18 -08:00
|
|
|
"-intf", Arg.String (file_dependencies_as MLI),
|
2012-07-26 12:21:54 -07:00
|
|
|
"<f> Process <f> as a .mli file";
|
2015-11-30 07:07:36 -08:00
|
|
|
"-map", Arg.String parse_map,
|
|
|
|
"<f> Read <f> and propagate delayed dependencies to following files";
|
2011-07-20 02:17:07 -07:00
|
|
|
"-ml-synonym", Arg.String(add_to_synonym_list ml_synonyms),
|
2012-07-26 12:21:54 -07:00
|
|
|
"<e> Consider <e> as a synonym of the .ml extension";
|
2011-07-20 02:17:07 -07:00
|
|
|
"-mli-synonym", Arg.String(add_to_synonym_list mli_synonyms),
|
2012-07-26 12:21:54 -07:00
|
|
|
"<e> Consider <e> as a synonym of the .mli extension";
|
2006-08-31 02:50:35 -07:00
|
|
|
"-modules", Arg.Set raw_dependencies,
|
2012-07-26 12:21:54 -07:00
|
|
|
" Print module dependencies in raw form (not suitable for make)";
|
2000-02-07 05:08:12 -08:00
|
|
|
"-native", Arg.Set native_only,
|
2012-07-26 12:21:54 -07:00
|
|
|
" Generate dependencies for native-code only (no .cmo files)";
|
2012-01-27 05:46:00 -08:00
|
|
|
"-one-line", Arg.Set one_line,
|
2012-07-26 12:21:54 -07:00
|
|
|
" Output one line per file, regardless of the length";
|
2014-10-03 13:31:34 -07:00
|
|
|
"-open", Arg.String (add_to_list Clflags.open_modules),
|
|
|
|
"<module> Opens the module <module> before typing";
|
2012-07-24 09:24:44 -07:00
|
|
|
"-pp", Arg.String(fun s -> Clflags.preprocessor := Some s),
|
2012-07-26 12:21:54 -07:00
|
|
|
"<cmd> Pipe sources through preprocessor <cmd>";
|
2014-10-03 13:31:32 -07:00
|
|
|
"-ppx", Arg.String (add_to_list first_ppx),
|
2012-07-24 09:24:44 -07:00
|
|
|
"<cmd> Pipe abstract syntax trees through preprocessor <cmd>";
|
2013-06-05 09:34:40 -07:00
|
|
|
"-slash", Arg.Set Clflags.force_slash,
|
2012-07-26 12:21:54 -07:00
|
|
|
" (Windows) Use forward slash / instead of backslash \\ in file paths";
|
|
|
|
"-sort", Arg.Set sort_files,
|
|
|
|
" Sort files according to their dependencies";
|
2004-11-26 17:04:19 -08:00
|
|
|
"-version", Arg.Unit print_version,
|
2012-07-26 12:21:54 -07:00
|
|
|
" Print version and exit";
|
2010-05-20 07:06:29 -07:00
|
|
|
"-vnum", Arg.Unit print_version_num,
|
2012-07-26 12:21:54 -07:00
|
|
|
" Print version number and exit";
|
1999-03-11 01:56:15 -08:00
|
|
|
] file_dependencies usage;
|
2013-07-17 05:35:26 -07:00
|
|
|
Compenv.readenv ppf Before_link;
|
2012-01-27 05:46:00 -08:00
|
|
|
if !sort_files then sort_files_by_dependencies !files;
|
1999-03-11 01:56:15 -08:00
|
|
|
exit (if !error_occurred then 2 else 0)
|