~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to tools/ocamlprof.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
11
11
(*                                                                     *)
12
12
(***********************************************************************)
13
13
 
14
 
(* $Id: ocamlprof.ml 8705 2007-12-04 13:38:58Z doligez $ *)
 
14
(* $Id: ocamlprof.ml 10444 2010-05-20 14:06:29Z doligez $ *)
15
15
 
16
16
open Printf
17
17
 
285
285
  | Pexp_object (_, fieldl) ->
286
286
      List.iter (rewrite_class_field iflag) fieldl
287
287
 
 
288
  | Pexp_newtype (_, sexp) -> rewrite_exp iflag sexp
 
289
  | Pexp_open (_, e) -> rewrite_exp iflag e
 
290
  | Pexp_pack (smod, _) -> rewrite_mod iflag smod
 
291
 
288
292
and rewrite_ifbody iflag ghost sifbody =
289
293
  if !instr_if && not ghost then
290
294
    insert_profile rw_exp sifbody
317
321
 
318
322
and rewrite_class_field iflag =
319
323
  function
320
 
    Pcf_inher (cexpr, _)     -> rewrite_class_expr iflag cexpr
321
 
  | Pcf_val (_, _, sexp, _)  -> rewrite_exp iflag sexp
322
 
  | Pcf_meth (_, _, ({pexp_desc = Pexp_function _} as sexp), _) ->
 
324
    Pcf_inher (_, cexpr, _)     -> rewrite_class_expr iflag cexpr
 
325
  | Pcf_val (_, _, _, sexp, _)  -> rewrite_exp iflag sexp
 
326
  | Pcf_meth (_, _, _, ({pexp_desc = Pexp_function _} as sexp), _) ->
323
327
      rewrite_exp iflag sexp
324
 
  | Pcf_meth (_, _, sexp, loc) ->
 
328
  | Pcf_meth (_, _, _, sexp, loc) ->
325
329
      if !instr_fun && not loc.loc_ghost then insert_profile rw_exp sexp
326
330
      else rewrite_exp iflag sexp
327
331
  | Pcf_let(_, spat_sexp_list, _) ->
358
362
  | Pmod_functor(param, smty, sbody) -> rewrite_mod iflag sbody
359
363
  | Pmod_apply(smod1, smod2) -> rewrite_mod iflag smod1; rewrite_mod iflag smod2
360
364
  | Pmod_constraint(smod, smty) -> rewrite_mod iflag smod
 
365
  | Pmod_unpack(sexp, _) -> rewrite_exp iflag sexp
361
366
 
362
367
and rewrite_str_item iflag item =
363
368
  match item.pstr_desc with
454
459
  exit 0;
455
460
;;
456
461
 
 
462
let print_version_num () =
 
463
  printf "%s@." Sys.ocaml_version;
 
464
  exit 0;
 
465
;;
 
466
 
457
467
let main () =
458
468
  try
459
469
    Warnings.parse_options false "a";
470
480
       "-m", Arg.String (fun s -> modes := s), "<flags>    (undocumented)";
471
481
       "-version", Arg.Unit print_version,
472
482
                   "     Print version and exit";
 
483
       "-vnum", Arg.Unit print_version_num,
 
484
                "        Print version number and exit";
473
485
      ] process_anon_file usage;
474
486
    exit 0
475
487
  with x ->