Skip to content

Commit 426afa3

Browse files
committed
Pour l'option -pack, permettre de donner une interface explicite (via un .mli) au module synthetise
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5422 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
1 parent ddaa490 commit 426afa3

11 files changed

+116
-78
lines changed

Changes

+2
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,8 @@ Both compilers:
1919
relaxed some other checks.
2020
- Fixed wrong code that was generated for "for i = a to max_int"
2121
or "for i = a downto min_int".
22+
- An explicit interface Mod.mli can now be provided for the module obtained
23+
by ocamlc -pack -o Mod.cmo ... or ocamlopt -pack -o Mod.cmx ...
2224

2325
Native-code compiler:
2426
- Fixed bug in ocamlopt -pack related to tracking of imported modules.

asmcomp/asmpackager.ml

+16-21
Original file line numberDiff line numberDiff line change
@@ -211,17 +211,15 @@ let build_package_cmx units unit_names target symbols_to_rename cmxfile =
211211
map_end (fun s -> target ^ "__" ^ s)
212212
(List.concat (List.map (fun info -> info.ui_defines) units))
213213
[target] in
214+
let approx =
215+
Compilenv.global_approx (Ident.create_persistent target) in
214216
let pkg_infos =
215217
{ ui_name = target;
216218
ui_defines = defines;
217219
ui_imports_cmi = (target, Env.crc_of_unit target) ::
218220
filter(Asmlink.extract_crc_interfaces());
219221
ui_imports_cmx = filter(Asmlink.extract_crc_implementations());
220-
ui_approx =
221-
Value_tuple
222-
(Array.map
223-
(fun info -> rename_approx mapping info.ui_approx)
224-
(Array.of_list units));
222+
ui_approx = rename_approx mapping approx;
225223
ui_curry_fun = union(List.map (fun info -> info.ui_curry_fun) units);
226224
ui_apply_fun = union(List.map (fun info -> info.ui_apply_fun) units);
227225
ui_force_link = List.exists (fun info -> info.ui_force_link) units
@@ -230,20 +228,16 @@ let build_package_cmx units unit_names target symbols_to_rename cmxfile =
230228

231229
(* Make the .o file for the package (not renamed yet) *)
232230

233-
let make_package_object ppf unit_names objfiles targetobj targetname =
234-
let asmtemp = Filename.temp_file "camlpackage" Config.ext_asm in
231+
let make_package_object ppf unit_names objfiles
232+
targetobj targetname coercion =
235233
let objtemp = Filename.temp_file "camlpackage" Config.ext_obj in
236-
let oc = open_out asmtemp in
237-
Emitaux.output_channel := oc;
238234
Location.input_name := targetname; (* set the name of the "current" input *)
239235
Compilenv.reset targetname; (* set the name of the "current" compunit *)
240-
Emit.begin_assembly();
241-
List.iter (Asmgen.compile_phrase ppf) (Cmmgen.package unit_names targetname);
242-
Emit.end_assembly();
243-
close_out oc;
244-
if Proc.assemble_file asmtemp objtemp <> 0 then
245-
raise(Error(Assembler_error asmtemp));
246-
remove_file asmtemp;
236+
Asmgen.compile_implementation
237+
(chop_extension_if_any objtemp) ppf
238+
(Translmod.transl_store_package
239+
(List.map Ident.create_persistent unit_names)
240+
(Ident.create_persistent targetname) coercion);
247241
let ld_cmd =
248242
sprintf "%s -o %s %s %s"
249243
Config.native_partial_linker
@@ -256,13 +250,14 @@ let make_package_object ppf unit_names objfiles targetobj targetname =
256250

257251
(* Make the .cmx and the .o for the package *)
258252

259-
let package_object_files ppf cmxfiles targetcmx targetobj targetname =
253+
let package_object_files ppf cmxfiles targetcmx
254+
targetobj targetname coercion =
260255
let units = map_left_right read_unit_info cmxfiles in
261256
let unit_names = List.map (fun info -> info.ui_name) units in
262257
check_units cmxfiles units unit_names;
263258
let objfiles =
264259
List.map (fun f -> chop_extension_if_any f ^ Config.ext_obj) cmxfiles in
265-
make_package_object ppf unit_names objfiles targetobj targetname;
260+
make_package_object ppf unit_names objfiles targetobj targetname coercion;
266261
let symbols = rename_in_object_file unit_names targetname targetobj in
267262
build_package_cmx units unit_names targetname symbols targetcmx
268263

@@ -282,10 +277,10 @@ let package_files ppf files targetcmx =
282277
let targetobj = prefix ^ Config.ext_obj in
283278
let targetname = String.capitalize(Filename.basename prefix) in
284279
try
285-
Typemod.package_units cmxfiles targetcmi targetname;
286-
package_object_files ppf cmxfiles targetcmx targetobj targetname
280+
let coercion = Typemod.package_units cmxfiles targetcmi targetname in
281+
package_object_files ppf cmxfiles targetcmx targetobj targetname coercion
287282
with x ->
288-
remove_file targetcmi; remove_file targetcmx; remove_file targetobj;
283+
remove_file targetcmx; remove_file targetobj;
289284
raise x
290285

291286
(* Error report *)

asmcomp/cmmgen.ml

-10
Original file line numberDiff line numberDiff line change
@@ -1632,16 +1632,6 @@ let compunit size ulam =
16321632
Cdefine_symbol glob;
16331633
Cskip(size * size_addr)] :: c3
16341634

1635-
(* Translate a package *)
1636-
1637-
let package unit_names target =
1638-
[Cdata (Cint(block_header 0 (List.length unit_names)) ::
1639-
Cglobal_symbol target ::
1640-
Cdefine_symbol target ::
1641-
List.map (fun s -> Csymbol_address s) unit_names);
1642-
Cfunction {fun_name = target ^ "__entry"; fun_args = [];
1643-
fun_body = Ctuple[]; fun_fast = false}]
1644-
16451635
(* Generate an application function:
16461636
(defun caml_applyN (a1 ... aN clos)
16471637
(if (= clos.arity N)

asmcomp/cmmgen.mli

-1
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@
1616

1717
val compunit: int -> Clambda.ulambda -> Cmm.phrase list
1818

19-
val package: string list -> string -> Cmm.phrase list
2019
val apply_function: int -> Cmm.phrase
2120
val curry_function: int -> Cmm.phrase list
2221
val entry_point: string list -> Cmm.phrase

bytecomp/bytepackager.ml

+18-36
Original file line numberDiff line numberDiff line change
@@ -130,40 +130,21 @@ let rec rename_append_bytecode_list oc mapping defined ofs = function
130130
oc mapping (Ident.create_persistent compunit.cu_name :: defined)
131131
(ofs + size) rem
132132

133-
(* Generate the code that builds the tuple representing the package
134-
module:
135-
GETGLOBAL M.An
136-
PUSHGETGLOBAL M.An-1
137-
...
138-
PUSHGETGLOBAL M.A1
139-
MAKEBLOCK tag = 0 size = n
140-
SETGLOBAL M
141-
*)
142-
143-
let build_global_target oc target_name mapping ofs =
144-
let out_word n =
145-
output_byte oc n;
146-
output_byte oc (n lsr 8);
147-
output_byte oc (n lsr 16);
148-
output_byte oc (n lsr 24) in
149-
let rec build_global first pos = function
150-
[] ->
151-
out_word opMAKEBLOCK; (* pos *)
152-
out_word (List.length mapping); (* pos + 4 *)
153-
out_word 0; (* pos + 8 *)
154-
out_word opSETGLOBAL; (* pos + 12 *)
155-
out_word 0; (* pos + 16 *)
156-
relocs := (Reloc_setglobal target_name, pos + 16) :: !relocs
157-
| (oldname, newname) :: rem ->
158-
out_word (if first then opGETGLOBAL else opPUSHGETGLOBAL); (* pos *)
159-
out_word 0; (* pos + 4 *)
160-
relocs := (Reloc_getglobal newname, pos + 4) :: !relocs;
161-
build_global false (pos + 8) rem in
162-
build_global true ofs (List.rev mapping)
133+
(* Generate the code that builds the tuple representing the package module *)
134+
135+
let build_global_target oc target_name mapping pos coercion =
136+
let lam =
137+
Translmod.transl_package (List.map snd mapping)
138+
(Ident.create_persistent target_name) coercion in
139+
let instrs =
140+
Bytegen.compile_implementation target_name lam in
141+
let rel =
142+
Emitcode.to_packed_file oc instrs in
143+
relocs := List.map (fun (r, ofs) -> (r, pos + ofs)) rel @ !relocs
163144

164145
(* Build the .cmo file obtained by packaging the given .cmo files. *)
165146

166-
let package_object_files objfiles targetfile targetname =
147+
let package_object_files objfiles targetfile targetname coercion =
167148
let units =
168149
List.map (fun f -> (f, read_unit_info f)) objfiles in
169150
let unit_names =
@@ -181,9 +162,10 @@ let package_object_files objfiles targetfile targetname =
181162
output_binary_int oc 0;
182163
let pos_code = pos_out oc in
183164
let ofs = rename_append_bytecode_list oc mapping [] 0 units in
184-
build_global_target oc (Ident.create_persistent targetname) mapping ofs;
165+
build_global_target oc targetname mapping ofs coercion;
185166
let pos_debug = pos_out oc in
186-
if !Clflags.debug && !events <> [] then output_value oc (List.rev !events);
167+
if !Clflags.debug && !events <> [] then
168+
output_value oc (List.rev !events);
187169
let pos_final = pos_out oc in
188170
let imports =
189171
List.filter
@@ -220,10 +202,10 @@ let package_files files targetfile =
220202
let targetcmi = prefix ^ ".cmi" in
221203
let targetname = String.capitalize(Filename.basename prefix) in
222204
try
223-
Typemod.package_units objfiles targetcmi targetname;
224-
package_object_files objfiles targetfile targetname
205+
let coercion = Typemod.package_units objfiles targetcmi targetname in
206+
package_object_files objfiles targetfile targetname coercion
225207
with x ->
226-
remove_file targetcmi; remove_file targetfile; raise x
208+
remove_file targetfile; raise x
227209

228210
(* Error report *)
229211

bytecomp/emitcode.ml

+10
Original file line numberDiff line numberDiff line change
@@ -425,3 +425,13 @@ let to_memory init_code fun_code =
425425
and code_size = !out_position in
426426
init();
427427
(code, code_size, reloc)
428+
429+
(* Emission to a file for a packed library *)
430+
431+
let to_packed_file outchan code =
432+
init();
433+
emit code;
434+
output outchan !out_buffer 0 !out_position;
435+
let reloc = !reloc_info in
436+
init();
437+
reloc

bytecomp/emitcode.mli

+7-1
Original file line numberDiff line numberDiff line change
@@ -76,4 +76,10 @@ val to_memory: instruction list -> instruction list ->
7676
block of relocatable bytecode
7777
size of this block
7878
relocation information *)
79-
79+
val to_packed_file:
80+
out_channel -> instruction list -> (reloc_info * int) list
81+
(* Arguments:
82+
channel on output file
83+
list of instructions to emit
84+
Result:
85+
relocation information (reversed) *)

bytecomp/translmod.ml

+41
Original file line numberDiff line numberDiff line change
@@ -453,3 +453,44 @@ let transl_toplevel_item_and_close itm =
453453
let transl_toplevel_definition str =
454454
reset_labels ();
455455
make_sequence transl_toplevel_item_and_close str
456+
457+
(* Compile the initialization code for a packed library *)
458+
459+
let transl_package component_names target_name coercion =
460+
let components =
461+
match coercion with
462+
Tcoerce_none ->
463+
List.map (fun id -> Lprim(Pgetglobal id, [])) component_names
464+
| Tcoerce_structure pos_cc_list ->
465+
let g = Array.of_list component_names in
466+
List.map
467+
(fun (pos, cc) -> apply_coercion cc (Lprim(Pgetglobal g.(pos), [])))
468+
pos_cc_list
469+
| _ ->
470+
assert false in
471+
Lprim(Psetglobal target_name, [Lprim(Pmakeblock(0, Immutable), components)])
472+
473+
let transl_store_package component_names target_name coercion =
474+
let rec make_sequence fn pos arg =
475+
match arg with
476+
[] -> lambda_unit
477+
| hd :: tl -> Lsequence(fn pos hd, make_sequence fn (pos + 1) tl) in
478+
match coercion with
479+
Tcoerce_none ->
480+
(List.length component_names,
481+
make_sequence
482+
(fun pos id ->
483+
Lprim(Psetfield(pos, false),
484+
[Lprim(Pgetglobal target_name, []);
485+
Lprim(Pgetglobal id, [])]))
486+
0 component_names)
487+
| Tcoerce_structure pos_cc_list ->
488+
let id = Array.of_list component_names in
489+
(List.length pos_cc_list,
490+
make_sequence
491+
(fun dst (src, cc) ->
492+
Lprim(Psetfield(dst, false),
493+
[Lprim(Pgetglobal target_name, []);
494+
apply_coercion cc (Lprim(Pgetglobal id.(src), []))]))
495+
0 pos_cc_list)
496+
| _ -> assert false

bytecomp/translmod.mli

+4
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,10 @@ val transl_implementation: string -> structure * module_coercion -> lambda
2222
val transl_store_implementation:
2323
string -> structure * module_coercion -> int * lambda
2424
val transl_toplevel_definition: structure -> lambda
25+
val transl_package: Ident.t list -> Ident.t -> module_coercion -> lambda
26+
val transl_store_package:
27+
Ident.t list -> Ident.t -> module_coercion -> int * lambda
28+
2529
val toplevel_name: Ident.t -> string
2630

2731
val primitive_declarations: string list ref

typing/typemod.ml

+17-8
Original file line numberDiff line numberDiff line change
@@ -564,14 +564,23 @@ let package_units objfiles cmifile modulename =
564564
objfiles in
565565
(* Compute signature of packaged unit *)
566566
let sg = package_signatures Subst.identity units in
567-
(* Determine imports *)
568-
let unit_names = List.map fst units in
569-
let imports =
570-
List.filter
571-
(fun (name, crc) -> not (List.mem name unit_names))
572-
(Env.imported_units()) in
573-
(* Write packaged signature *)
574-
Env.save_signature_with_imports sg modulename cmifile imports
567+
(* See if explicit interface is provided *)
568+
let mlifile =
569+
chop_extension_if_any cmifile ^ !Config.interface_suffix in
570+
if Sys.file_exists mlifile then begin
571+
let dclsig = Env.read_signature modulename cmifile in
572+
Includemod.compunit "(obtained by packing)" sg mlifile dclsig
573+
end else begin
574+
(* Determine imports *)
575+
let unit_names = List.map fst units in
576+
let imports =
577+
List.filter
578+
(fun (name, crc) -> not (List.mem name unit_names))
579+
(Env.imported_units()) in
580+
(* Write packaged signature *)
581+
Env.save_signature_with_imports sg modulename cmifile imports;
582+
Tcoerce_none
583+
end
575584

576585
(* Error report *)
577586

typing/typemod.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ val check_nongen_schemes:
3232
val simplify_signature: signature -> signature
3333

3434
val package_units:
35-
string list -> string -> string -> unit
35+
string list -> string -> string -> Typedtree.module_coercion
3636

3737
type error =
3838
Unbound_module of Longident.t

0 commit comments

Comments
 (0)