Bug double inclusion de profiling.cmo.
Unification du parsing ligne de commande avec le compilo. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1907 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
1f39b97ded
commit
2ae922b5c7
|
@ -7,3 +7,4 @@ dumpapprox
|
|||
objinfo
|
||||
cvt_emit
|
||||
cvt_emit.ml
|
||||
ocamlcp
|
||||
|
|
|
@ -3,11 +3,12 @@ include ../config/Makefile
|
|||
CAMLRUN=../boot/ocamlrun
|
||||
CAMLC=$(CAMLRUN) ../boot/ocamlc -I ../boot
|
||||
CAMLLEX=$(CAMLRUN) ../boot/ocamllex
|
||||
INCLUDES=-I ../utils -I ../parsing -I ../typing -I ../bytecomp -I ../asmcomp
|
||||
INCLUDES=-I ../utils -I ../parsing -I ../typing -I ../bytecomp -I ../asmcomp \
|
||||
-I ../driver
|
||||
COMPFLAGS=$(INCLUDES)
|
||||
LINKFLAGS=$(INCLUDES)
|
||||
|
||||
all: ocamldep ocamlprof
|
||||
all: ocamldep ocamlprof ocamlcp
|
||||
|
||||
# The dependency generator
|
||||
|
||||
|
@ -40,13 +41,16 @@ CSLPROF_IMPORTS=misc.cmo config.cmo clflags.cmo terminfo.cmo \
|
|||
ocamlprof: $(CSLPROF) profiling.cmo
|
||||
$(CAMLC) $(LINKFLAGS) -o ocamlprof $(CSLPROF_IMPORTS) $(CSLPROF)
|
||||
|
||||
ocamlcp: ocamlcp.cmo
|
||||
$(CAMLC) $(LINKFLAGS) -o ocamlcp main_args.cmo ocamlcp.cmo
|
||||
|
||||
install::
|
||||
cp ocamlprof $(BINDIR)/ocamlprof
|
||||
cp ocamlcp $(BINDIR)/ocamlcp
|
||||
cp profiling.cmi profiling.cmo $(LIBDIR)
|
||||
|
||||
clean::
|
||||
rm -f ocamlprof
|
||||
rm -f ocamlprof ocamlcp
|
||||
|
||||
# To make custom toplevels
|
||||
|
||||
|
|
|
@ -3,7 +3,8 @@
|
|||
CAMLRUN=..\boot\ocamlrun
|
||||
CAMLC=$(CAMLRUN) ..\boot\ocamlc -I ..\boot
|
||||
CAMLLEX=$(CAMLRUN) ..\boot\ocamllex
|
||||
INCLUDES=-I ..\utils -I ..\parsing -I ..\typing -I ..\bytecomp -I ..\asmcomp
|
||||
INCLUDES=-I ..\utils -I ..\parsing -I ..\typing -I ..\bytecomp -I ..\asmcomp \
|
||||
-I ..\driver
|
||||
COMPFLAGS=$(INCLUDES)
|
||||
LINKFLAGS=$(INCLUDES)
|
||||
|
||||
|
@ -41,7 +42,7 @@ ocamlprof: $(CSLPROF) profiling.cmo
|
|||
$(CAMLC) $(LINKFLAGS) -o ocamlprof $(CSLPROF_IMPORTS) $(CSLPROF)
|
||||
|
||||
ocamlcp.exe: ocamlcp.cmo
|
||||
$(CAMLC) $(LINKFLAGS) -o ocamlcp.exe ocamlcp.cmo
|
||||
$(CAMLC) $(LINKFLAGS) -o ocamlcp.exe main_args.cmo ocamlcp.cmo
|
||||
|
||||
install::
|
||||
cp ocamlprof $(BINDIR)\ocamlprof.exe
|
||||
|
|
BIN
tools/ocamlcp
BIN
tools/ocamlcp
Binary file not shown.
|
@ -4,13 +4,15 @@
|
|||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* Automatique. Distributed only by permission. *)
|
||||
(* Copyright 1998 Institut National de Recherche en Informatique et *)
|
||||
(* en Automatique. Distributed only by permission. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* $Id$ *)
|
||||
|
||||
open Printf
|
||||
|
||||
let compargs = ref ([] : string list)
|
||||
let profargs = ref ([] : string list)
|
||||
let toremove = ref ([] : string list)
|
||||
|
@ -19,37 +21,43 @@ let option opt () = compargs := opt :: !compargs
|
|||
let option_with_arg opt arg = compargs := arg :: opt :: !compargs
|
||||
let process_file filename = compargs := filename :: !compargs
|
||||
|
||||
let make_archive = ref false
|
||||
|
||||
let usage = "Usage: ocamlcp <options> <files>\noptions are:"
|
||||
|
||||
let incompatible o =
|
||||
fprintf stderr "ocamlcp: profiling is incompatible with the %s option\n" o;
|
||||
exit 2
|
||||
|
||||
module Options = Main_args.Make_options (struct
|
||||
let _a () = make_archive := true; option "-a" ()
|
||||
let _c = option "-c"
|
||||
let _cclib s = option_with_arg "-cclib" s
|
||||
let _ccopt s = option_with_arg "-ccopt" s
|
||||
let _custom = option "-custom"
|
||||
let _g = option "-g"
|
||||
let _i = option "-i"
|
||||
let _I s = option_with_arg "-I" s
|
||||
let _impl s = option_with_arg "-impl" s
|
||||
let _intf s = option_with_arg "-intf" s
|
||||
let _linkall = option "-linkall"
|
||||
let _noassert = option "-noassert"
|
||||
let _o s = option_with_arg "-o" s
|
||||
let _output_obj = option "-output-obj"
|
||||
let _pp s = incompatible "-pp"
|
||||
let _thread () = incompatible "-thread"
|
||||
let _unsafe = option "-unsafe"
|
||||
let _v = option "-v"
|
||||
let _verbose = option "-verbose"
|
||||
let _nopervasives = option "-nopervasives"
|
||||
let _drawlambda = option "-drawlambda"
|
||||
let _dlambda = option "-dlambda"
|
||||
let _dinstr = option "-dinstr"
|
||||
let anonymous = process_file
|
||||
end)
|
||||
|
||||
let _ =
|
||||
Arg.parse [
|
||||
(* Same options as the compiler ocamlc *)
|
||||
"-a", Arg.Unit(option "-a"), " Build a library";
|
||||
"-c", Arg.Unit(option "-c"), " Compile only (do not link)";
|
||||
"-cclib", Arg.String(option_with_arg "-cclib"),
|
||||
"<opt> Pass option <opt> to the C linker";
|
||||
"-ccopt", Arg.String(option_with_arg "-ccopt"),
|
||||
"<opt> Pass option <opt> to the C compiler and linker";
|
||||
"-custom", Arg.Unit(option "-custom"), " Link in custom mode";
|
||||
"-i", Arg.Unit(option "-i"), " Print the types";
|
||||
"-I", Arg.String(option_with_arg "-I"),
|
||||
"<d> Add <d> to the list of include directories";
|
||||
(* -impl et -intf ont disparu ?? PWZ *)
|
||||
"-linkall", Arg.Unit(option "-linkall"), " Don't remove unused modules";
|
||||
"-o", Arg.String(option_with_arg "-o"),
|
||||
"<name> Set output file name to <name> (default a.out)";
|
||||
"-v", Arg.Unit(option "-v"), " Print compiler version number";
|
||||
"-unsafe", Arg.Unit(option "-unsafe"),
|
||||
" No bound checking on array and string access";
|
||||
|
||||
"-nopervasives", Arg.Unit(option "-nopervasives"), " (undocumented)";
|
||||
"-drawlambda", Arg.Unit(option "-drawlambda"), " (undocumented)";
|
||||
"-dlambda", Arg.Unit(option "-dlambda"), " (undocumented)";
|
||||
"-dinstr", Arg.Unit(option "-dinstr"), " (undocumented)";
|
||||
|
||||
"-", Arg.String process_file,
|
||||
"<f> Take <f> as a file name (even if it starts with `-')";
|
||||
(* Option specific to the profiler *)
|
||||
let optlist = Options.list @ [
|
||||
"-p", Arg.String(fun s -> profargs := s :: "-m" :: !profargs),
|
||||
"[afilmt] Profile constructs specified by argument:\n\
|
||||
a Everything\n\
|
||||
|
@ -58,10 +66,13 @@ let _ =
|
|||
l while, for\n\
|
||||
m match ... with\n\
|
||||
t try ... with"
|
||||
] process_file usage;
|
||||
]
|
||||
in
|
||||
Arg.parse optlist process_file usage;
|
||||
let status =
|
||||
Sys.command
|
||||
(Printf.sprintf "ocamlc -pp \"ocamlprof -instrument %s\" %s"
|
||||
(Printf.sprintf "ocamlc -pp \"ocamlprof -instrument %s\" %s %s"
|
||||
(String.concat " " (List.rev !profargs))
|
||||
(if !make_archive then "profiling.cmo" else "")
|
||||
(String.concat " " (List.rev !compargs))) in
|
||||
exit status
|
||||
|
|
Loading…
Reference in New Issue