Skip to content

Commit

Permalink
Fix #8769 (#8770)
Browse files Browse the repository at this point in the history
* Don't generate illegal Pfield's when compiling alias coercions

* Simplify lambda code when compiling packs

* Add regression test for pr8769

* Add Changes entry
  • Loading branch information
lpw25 committed Jun 28, 2019
1 parent ad5333d commit c4dc6ba
Show file tree
Hide file tree
Showing 9 changed files with 47 additions and 1 deletion.
3 changes: 3 additions & 0 deletions Changes
Expand Up @@ -7,6 +7,9 @@ OCaml 4.08 maintenance branch:
native-code on amd64. (observed with the mingw64 compiler)
(Nicolás Ojeda Bär, review by David Allsopp)

- #8769, #8770: Fix assertion failure with -pack
(Leo White, review by Gabriel Scherer, report by Fabian @copy)

OCaml 4.08.0 (13 June 2019)
---------------------------

Expand Down
2 changes: 2 additions & 0 deletions asmcomp/asmpackager.ml
Expand Up @@ -101,6 +101,7 @@ let make_package_object ~ppf_dump members targetobj targetname coercion
let prefixname = Filename.remove_extension objtemp in
if Config.flambda then begin
let size, lam = Translmod.transl_package_flambda components coercion in
let lam = Simplif.simplify_lambda targetname lam in
let flam =
Middle_end.middle_end ~ppf_dump
~prefixname
Expand All @@ -116,6 +117,7 @@ let make_package_object ~ppf_dump members targetobj targetname coercion
let main_module_block_size, code =
Translmod.transl_store_package
components (Ident.create_persistent targetname) coercion in
let code = Simplif.simplify_lambda targetname code in
Asmgen.compile_implementation_clambda
prefixname ~ppf_dump { Lambda.code; main_module_block_size;
module_ident; required_globals = Ident.Set.empty }
Expand Down
1 change: 1 addition & 0 deletions bytecomp/bytepackager.ml
Expand Up @@ -195,6 +195,7 @@ let build_global_target ~ppf_dump oc target_name members mapping pos coercion =
let lam =
Translmod.transl_package
components (Ident.create_persistent target_name) coercion in
let lam = Simplif.simplify_lambda target_name lam in
if !Clflags.dump_lambda then
Format.fprintf ppf_dump "%a@." Printlambda.lambda lam;
let instrs =
Expand Down
5 changes: 4 additions & 1 deletion bytecomp/translmod.ml
Expand Up @@ -72,7 +72,10 @@ let rec apply_coercion loc strict restr arg =
arg
| Tcoerce_structure(pos_cc_list, id_pos_list) ->
name_lambda strict arg (fun id ->
let get_field pos = Lprim(Pfield pos,[Lvar id], loc) in
let get_field pos =
if pos < 0 then lambda_unit
else Lprim(Pfield pos,[Lvar id], loc)
in
let lam =
Lprim(Pmakeblock(0, Immutable, None),
List.map (apply_coercion_field loc get_field) pos_cc_list,
Expand Down
Empty file.
3 changes: 3 additions & 0 deletions testsuite/tests/regression/pr8769/nocrypto.mli
@@ -0,0 +1,3 @@
module Rng : sig
module F : sig end
end
1 change: 1 addition & 0 deletions testsuite/tests/regression/pr8769/ocamltests
@@ -0,0 +1 @@
pr8769.ml
32 changes: 32 additions & 0 deletions testsuite/tests/regression/pr8769/pr8769.ml
@@ -0,0 +1,32 @@
(* TEST
modules = "nocrypto.mli fortuna.ml rng.ml"
* setup-ocamlc.byte-build-env
** ocamlc.byte
module = "nocrypto.mli"
** ocamlc.byte
flags = "-for-pack Nocrypto"
module = "fortuna.ml"
** ocamlc.byte
flags = "-for-pack Nocrypto"
module = "rng.ml"
** ocamlc.byte
program = "nocrypto.cmo"
flags = "-pack"
all_modules = "fortuna.cmo rng.cmo"
* setup-ocamlopt.byte-build-env
** ocamlopt.byte
module = "nocrypto.mli"
** ocamlopt.byte
flags = "-for-pack Nocrypto"
module = "fortuna.ml"
** ocamlopt.byte
flags = "-for-pack Nocrypto"
module = "rng.ml"
** ocamlopt.byte
program = "nocrypto.cmx"
flags = "-pack"
all_modules = "fortuna.cmx rng.cmx"
*)
1 change: 1 addition & 0 deletions testsuite/tests/regression/pr8769/rng.ml
@@ -0,0 +1 @@
module F = Fortuna

0 comments on commit c4dc6ba

Please sign in to comment.