camldep reecrit en Caml.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@226 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 1995-08-25 13:54:58 +00:00
parent f360daf981
commit 05709f0f84
5 changed files with 195 additions and 112 deletions

View File

@ -3,7 +3,7 @@ CAMLOPT=../boot/camlrun ../camlopt -I ../stdlib -I KB -I Lex
OPTFLAGS=-S
CAMLYACC=../yacc/camlyacc
CAMLLEX=../boot/camlrun ../lex/camllex
CAMLDEP=../tools/camldep
CAMLDEP=../boot/camlrun ../tools/camldep
CAMLRUN=../byterun/camlrun
CODERUNPARAMS=CAMLRUNPARAM='o=100'

View File

@ -6,7 +6,7 @@ LINKFLAGS=
CAMLYACC=../boot/camlyacc
YACCFLAGS=
CAMLLEX=../boot/camlrun ../boot/camllex
CAMLDEP=../tools/camldep
CAMLDEP=../boot/camlrun ../tools/camldep
DEPFLAGS=$(INCLUDES)
CAMLRUN=../boot/camlrun

View File

@ -1,9 +1,27 @@
CAMLC=../boot/camlrun ../boot/camlc -I ../boot
CAMLRUN=../boot/camlrun
CAMLC=$(CAMLRUN) ../boot/camlc -I ../boot
CAMLLEX=$(CAMLRUN) ../boot/camllex
INCLUDES=-I ../utils -I ../parsing -I ../typing -I ../bytecomp -I ../asmcomp
COMPFLAGS=$(INCLUDES)
LINKFLAGS=$(INCLUDES)
all: dumpobj
all: camldep
CAMLDEP=camldep.cmo
camldep: $(CAMLDEP)
$(CAMLC) $(LINKFLAGS) -o camldep misc.cmo $(CAMLDEP)
clean::
rm -f camldep
camldep.ml: camldep.mll
$(CAMLLEX) camldep.mll
clean::
rm -f camldep.ml
beforedepend:: camldep
DUMPOBJ=opnames.cmo dumpobj.cmo
@ -45,6 +63,6 @@ clean::
rm -f *.cmo *.cmi
depend: beforedepend
camldep $(INCLUDES) *.mli *.ml > .depend
$(CAMLRUN) camldep $(INCLUDES) *.mli *.ml > .depend
include .depend

View File

@ -1,107 +0,0 @@
#!/usr/local/bin/perl
# To scan a Caml Light source file, find all references to external modules
# (open Foo or Foo.bar), and output the dependencies on standard output.
#
# Usage: camldep [-I path] <file> ...
while ($#ARGV >= 0) {
$_ = shift(@ARGV);
if (/^-I(.*)$/) {
$dir = $1 ? $1 : shift(@ARGV);
$dir =~ s|/$||;
unshift(@path, $dir);
}
elsif (/(.*)\.mli$/ || /(.*)\.cmi$/) {
do scan_source ($_, "$1.cmi");
}
elsif (/(.*)\.ml$/ || /(.*)\.cmo$/) {
do scan_source ($_, "$1.cmo");
}
else {
die "Don't know what to do with $_";
}
}
sub scan_source {
local ($source_name, $target_name) = @_;
$modname = $target_name;
$modname =~ s|^.*/||;
$modname =~ s|\.cm[iox]$||;
undef(%imports);
open(SRC, $source_name) || return;
while(<SRC>) {
if (m/\bopen\s*([A-Z][a-zA-Z0-9_]*)\b/) {
$imports{$1} = 1;
}
while(m/\b([A-Z][a-zA-Z0-9_]*)\./) {
$imports{$1} = 1;
$_ = $';
}
}
close(SRC);
undef(@deps);
undef(@optdeps);
if ($target_name =~ m/(.*)\.cmo$/ && -r ($source_name . "i")) {
push(@deps, "$1.cmi");
push(@optdeps, "$1.cmi");
}
foreach $modl (keys(%imports)) {
$modl = do lowercase($modl);
next if ($modl eq $modname);
if ($dep = do find_path ("$modl.mli")) {
$dep =~ s/\.mli$//;
push(@deps, "$dep.cmi");
if (-f "$dep.ml") {
push(@optdeps, "$dep.cmx");
} else {
push(@optdeps, "$dep.cmi");
}
}
elsif ($dep = do find_path ("$modl.ml")) {
$dep =~ s/\.ml$//;
push(@deps, "$dep.cmo");
push(@optdeps, "$dep.cmx");
}
}
if ($#deps >= 0) {
print "$target_name: ";
do print_deps(@deps);
}
if ($target_name =~ /^(.*)\.cmo$/ && $#optdeps >= 0) {
print "$1.cmx: ";
do print_deps(@optdeps);
}
}
sub print_deps {
$col = length($target_name) + 3;
foreach $dep (@_) {
next if $dep eq $target_name;
$col += length($dep) + 1;
if ($col >= 77) {
print "\\\n ";
$col = length($dep) + 5;
}
print $dep, " ";
}
print "\n";
}
sub find_path {
local ($filename) = @_;
return $filename if (-r $filename);
foreach $dir (@path) {
return "$dir/$filename" if (-r "$dir/$filename");
}
return 0;
}
sub lowercase {
local ($_) = @_;
m/^(.)(.*)$/;
$hd = $1;
$tl = $2;
$hd =~ tr/A-Z/a-z/;
return $hd . $tl;
}

172
tools/camldep.mll Normal file
View File

@ -0,0 +1,172 @@
(***********************************************************************)
(* *)
(* Caml Special Light *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1995 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
(* $Id$ *)
{
(* Remember the possibly free structure identifiers *)
module StringSet =
Set.Make(struct type t = string let compare = compare end)
let free_structure_names = ref StringSet.empty
let add_structure name =
free_structure_names := StringSet.add name !free_structure_names
(* For nested comments *)
let comment_depth = ref 0
}
rule main = parse
"open" [' ' '\010' '\013' '\009' '\012'] *
{ struct_name lexbuf; main lexbuf }
| ['A'-'Z' '\192'-'\214' '\216'-'\222' ]
(['A'-'Z' 'a'-'z' '_' '\192'-'\214' '\216'-'\246' '\248'-'\255'
'\'' '0'-'9' ]) * '.'
{ let s = Lexing.lexeme lexbuf in
add_structure(String.sub s 0 (String.length s - 1));
main lexbuf }
| "\""
{ string lexbuf; main lexbuf }
| "(*"
{ comment_depth := 1; comment lexbuf; main lexbuf }
| eof
{ () }
| _
{ main lexbuf }
and struct_name = parse
['A'-'Z' '\192'-'\214' '\216'-'\222' ]
(['A'-'Z' 'a'-'z' '_' '\192'-'\214' '\216'-'\246' '\248'-'\255'
'\'' '0'-'9' ]) *
{ add_structure(Lexing.lexeme lexbuf) }
| ""
{ () }
and comment = parse
"(*"
{ comment_depth := succ !comment_depth; comment lexbuf }
| "*)"
{ comment_depth := pred !comment_depth;
if !comment_depth > 0 then comment lexbuf }
| "\""
{ string lexbuf; comment lexbuf }
| "''"
{ comment lexbuf }
| "'" [^ '\\' '\''] "'"
{ comment lexbuf }
| "'\\" ['\\' '\'' 'n' 't' 'b' 'r'] "'"
{ comment lexbuf }
| "'\\" ['0'-'9'] ['0'-'9'] ['0'-'9'] "'"
{ comment lexbuf }
| eof
{ () }
| _
{ comment lexbuf }
and string = parse
'"'
{ () }
| '\\' ("\010" | "\013" | "\010\013") [' ' '\009'] *
{ string lexbuf }
| '\\' ['\\' '"' 'n' 't' 'b' 'r']
{ string lexbuf }
| '\\' ['0'-'9'] ['0'-'9'] ['0'-'9']
{ string lexbuf }
| eof
{ () }
| _
{ string lexbuf }
{
(* Print the dependencies *)
let load_path = ref ([] : string list)
let opt_flag = ref true
let find_dependency modname (byt_deps, opt_deps) =
let name = Misc.lowercase modname in
try
let filename = Misc.find_in_path !load_path (name ^ ".mli") in
let basename = Filename.chop_suffix filename ".mli" in
((basename ^ ".cmi") :: byt_deps,
(if !opt_flag & Sys.file_exists (basename ^ ".ml")
then basename ^ ".cmx"
else basename ^ ".cmi") :: opt_deps)
with Not_found ->
try
let filename = Misc.find_in_path !load_path (name ^ ".ml") in
let basename = Filename.chop_suffix filename ".ml" in
((basename ^ ".cmo") :: byt_deps,
(basename ^ ".cmx") :: opt_deps)
with Not_found ->
(byt_deps, opt_deps)
let print_dependencies target_file deps =
match deps with
[] -> ()
| _ ->
print_string target_file; print_string ": ";
let rec print_items pos = function
[] -> print_string "\n"
| dep :: rem ->
if pos + String.length dep <= 77 then begin
print_string dep; print_string " ";
print_items (pos + String.length dep + 1) rem
end else begin
print_string "\\\n "; print_string dep; print_string " ";
print_items (String.length dep + 5) rem
end in
print_items (String.length target_file + 2) deps
let file_dependencies source_file =
try
free_structure_names := StringSet.empty;
let ic = open_in source_file in
let lb = Lexing.from_channel ic in
main lb;
if Filename.check_suffix source_file ".ml" then begin
let basename = Filename.chop_suffix source_file ".ml" in
let init_deps =
if Sys.file_exists (basename ^ ".mli")
then let cmi_name = basename ^ ".cmi" in ([cmi_name], [cmi_name])
else ([], []) in
let (byt_deps, opt_deps) =
StringSet.fold find_dependency !free_structure_names init_deps in
print_dependencies (basename ^ ".cmo") byt_deps;
print_dependencies (basename ^ ".cmx") opt_deps
end else
if Filename.check_suffix source_file ".mli" then begin
let basename = Filename.chop_suffix source_file ".mli" in
let (byt_deps, opt_deps) =
StringSet.fold find_dependency !free_structure_names ([], []) in
print_dependencies (basename ^ ".cmi") byt_deps
end else
();
close_in ic
with Sys_error msg ->
()
(* Entry point *)
let _ =
Arg.parse
["-I", Arg.String(fun dir -> load_path := dir :: !load_path);
"-opt", Arg.Unit(fun () -> opt_flag := true);
"-noopt", Arg.Unit(fun () -> opt_flag := false)]
file_dependencies;
exit 0
}