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

« back to all changes in this revision

Viewing changes to driver/optcompile.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stefano Zacchiroli
  • Date: 2009-02-22 08:49:13 UTC
  • mfrom: (12.1.1 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090222084913-3i0uw2bhd0lgw0ok
* Uploading to unstable
* debian/control: bump dh-ocaml to (>= 0.4) to avoid buggy ocamlinit.mk

Show diffs side-by-side

added added

removed removed

Lines of Context:
10
10
(*                                                                     *)
11
11
(***********************************************************************)
12
12
 
13
 
(* $Id: optcompile.ml,v 1.53 2005/08/08 09:41:51 xleroy Exp $ *)
 
13
(* $Id: optcompile.ml,v 1.56.2.2 2008/10/17 14:01:35 doligez Exp $ *)
14
14
 
15
15
(* The batch compiler *)
16
16
 
43
43
    then Env.initial
44
44
    else Env.open_pers_signature "Pervasives" Env.initial
45
45
  with Not_found ->
46
 
    fatal_error "cannot open Pervasives.cmi"
 
46
    fatal_error "cannot open pervasives.cmi"
 
47
 
 
48
(* Note: this function is duplicated in compile.ml *)
 
49
let check_unit_name ppf filename name =
 
50
  try
 
51
    begin match name.[0] with
 
52
    | 'A'..'Z' -> ()
 
53
    | _ ->
 
54
       Location.print_warning (Location.in_file filename) ppf
 
55
        (Warnings.Bad_module_name name);
 
56
       raise Exit;
 
57
    end;
 
58
    for i = 1 to String.length name - 1 do
 
59
      match name.[i] with
 
60
      | 'A'..'Z' | 'a'..'z' | '0'..'9' | '_' | '\'' -> ()
 
61
      | _ ->
 
62
         Location.print_warning (Location.in_file filename) ppf
 
63
           (Warnings.Bad_module_name name);
 
64
         raise Exit;
 
65
    done;
 
66
  with Exit -> ()
 
67
;;
47
68
 
48
69
(* Compile a .mli file *)
49
70
 
50
71
let interface ppf sourcefile outputprefix =
 
72
  Location.input_name := sourcefile;
51
73
  init_path ();
52
74
  let modulename =
53
75
    String.capitalize(Filename.basename(chop_extension_if_any sourcefile)) in
 
76
  check_unit_name ppf sourcefile modulename;
54
77
  Env.set_unit_name modulename;
55
78
  let inputfile = Pparse.preprocess sourcefile in
56
79
  try
64
87
    Warnings.check_fatal ();
65
88
    if not !Clflags.print_types then
66
89
      Env.save_signature sg modulename (outputprefix ^ ".cmi");
67
 
    Pparse.remove_preprocessed inputfile
 
90
    Pparse.remove_preprocessed inputfile;
 
91
    Stypes.dump (outputprefix ^ ".annot");
68
92
  with e ->
69
93
    Pparse.remove_preprocessed_if_ast inputfile;
 
94
    Stypes.dump (outputprefix ^ ".annot");
70
95
    raise e
71
96
 
72
97
(* Compile a .ml file *)
79
104
let (+++) (x, y) f = (x, f y)
80
105
 
81
106
let implementation ppf sourcefile outputprefix =
 
107
  Location.input_name := sourcefile;
82
108
  init_path ();
83
109
  let modulename =
84
110
    String.capitalize(Filename.basename(chop_extension_if_any sourcefile)) in
 
111
  check_unit_name ppf sourcefile modulename;
85
112
  Env.set_unit_name modulename;
86
113
  let inputfile = Pparse.preprocess sourcefile in
87
114
  let env = initial_env() in
88
115
  Compilenv.reset ?packname:!Clflags.for_package modulename;
 
116
  let cmxfile = outputprefix ^ ".cmx" in
 
117
  let objfile = outputprefix ^ ext_obj in
89
118
  try
90
119
    if !Clflags.print_types then ignore(
91
120
      Pparse.file ppf inputfile Parse.implementation ast_impl_magic_number
102
131
      +++ Simplif.simplify_lambda
103
132
      +++ print_if ppf Clflags.dump_lambda Printlambda.lambda
104
133
      ++ Asmgen.compile_implementation outputprefix ppf;
105
 
      Compilenv.save_unit_info (outputprefix ^ ".cmx");
 
134
      Compilenv.save_unit_info cmxfile;
106
135
    end;
107
136
    Warnings.check_fatal ();
108
 
    Pparse.remove_preprocessed inputfile
 
137
    Pparse.remove_preprocessed inputfile;
 
138
    Stypes.dump (outputprefix ^ ".annot");
109
139
  with x ->
 
140
    remove_file objfile;
 
141
    remove_file cmxfile;
110
142
    Pparse.remove_preprocessed_if_ast inputfile;
 
143
    Stypes.dump (outputprefix ^ ".annot");
111
144
    raise x
112
145
 
113
146
let c_file name =