Fix new dynlink's initialisation checks (#2176)

master
Leo White 2018-12-08 10:15:19 -05:00 committed by GitHub
parent a875e64571
commit 11d759c584
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
37 changed files with 557 additions and 102 deletions

View File

@ -190,8 +190,8 @@ Working version
- GPR#2038: Deprecate vm threads
(Jérémie Dimino)
* PR#4208, PR#4229, PR#4839, PR#6462, PR#6957, PR#6950, GPR#1063: Make
(nat)dynlink sound
* PR#4208, PR#4229, PR#4839, PR#6462, PR#6957, PR#6950, GPR#1063, GPR#2176:
Make (nat)dynlink sound
(Mark Shinwell, Leo White, Nicolás Ojeda Bär, Pierre Chambart)
### Compiler user-interface and warnings:

View File

@ -94,17 +94,11 @@ let is_required (rel, _pos) =
| _ -> false
let add_required compunit =
let add_required_by_reloc (rel, _pos) =
match rel with
Reloc_getglobal id ->
missing_globals := Ident.Set.add id !missing_globals
| _ -> ()
in
let add_required_for_effects id =
let add id =
missing_globals := Ident.Set.add id !missing_globals
in
List.iter add_required_by_reloc compunit.cu_reloc;
List.iter add_required_for_effects compunit.cu_required_globals
List.iter add (Symtable.required_globals compunit.cu_reloc);
List.iter add compunit.cu_required_globals
let remove_required (rel, _pos) =
match rel with

View File

@ -342,6 +342,14 @@ let defined_globals patchlist =
[]
patchlist
let required_globals patchlist =
List.fold_left (fun accu rel ->
match rel with
| (Reloc_getglobal id, _pos) -> id :: accu
| _ -> accu)
[]
patchlist
let check_global_initialized patchlist =
(* First determine the globals we will define *)
let defined_globals = defined_globals patchlist in

View File

@ -40,6 +40,7 @@ val assign_global_value: Ident.t -> Obj.t -> unit
val get_global_position: Ident.t -> int
val check_global_initialized: (reloc_info * int) list -> unit
val defined_globals: (reloc_info * int) list -> Ident.t list
val required_globals: (reloc_info * int) list -> Ident.t list
type global_map

View File

@ -58,6 +58,9 @@ COMPILEROBJS = $(addprefix $(ROOTDIR)/,\
bytecomp/opcodes.cmo bytecomp/runtimedef.cmo bytecomp/bytesections.cmo \
bytecomp/dll.cmo bytecomp/meta.cmo bytecomp/symtable.cmo)
COMPILERINTFS = $(addprefix $(ROOTDIR)/,\
bytecomp/cmo_format.cmi)
all: dynlink.cma extract_crc
allopt: dynlink.cmxa
@ -68,7 +71,7 @@ dynlink.cma: $(OBJS)
dynlink.cmxa: $(NATOBJS)
$(OCAMLOPT) $(COMPFLAGS) -ccopt "$(NATDYNLINKOPTS)" -a -o $@ $^
dynlink_compilerlibs.cmo: $(COMPILEROBJS)
dynlink_compilerlibs.cmo: $(COMPILEROBJS) $(COMPILERINTFS)
$(OCAMLC) $(COMPFLAGS) -pack -o $@ $^
# This rule is ok since there is no corresponding rule for native code

View File

@ -33,7 +33,17 @@ module Bytecode = struct
let crc _t = None
let interface_imports (t : t) = t.cu_imports
let implementation_imports _t = []
let implementation_imports (t : t) =
let required =
t.cu_required_globals
@ Symtable.required_globals t.cu_reloc
in
let required =
List.filter (fun id -> not (Ident.is_predef id)) required
in
List.map
(fun ident -> Ident.name ident, None)
required
let defined_symbols (t : t) =
List.map (fun ident -> Ident.name ident)

View File

@ -153,55 +153,59 @@ module Make (P : Dynlink_platform_intf.S) = struct
inited := true
end
let check_interface_imports filename ui ifaces ~allowed_units =
let set_loaded_implem filename ui implems =
String.Map.add (UH.name ui) (UH.crc ui, filename, DT.Loaded) implems
let set_loaded filename ui (state : State.t) =
{ state with implems = set_loaded_implem filename ui state.implems }
let check_interface_imports filename ui ifaces =
List.fold_left (fun ifaces (name, crc) ->
let add_interface crc =
if String.Set.mem name allowed_units then
String.Map.add name (crc, filename) ifaces
else
raise (DT.Error (Unavailable_unit name))
in
match String.Map.find name ifaces with
| exception Not_found ->
begin match crc with
| None -> add_interface Name
| Some crc -> add_interface (Contents crc)
| exception Not_found -> begin
match crc with
| None -> String.Map.add name (Name, filename) ifaces
| Some crc -> String.Map.add name (Contents crc, filename) ifaces
end
| old_crc, _old_src ->
match old_crc, crc with
| (Name | Contents _), None -> ifaces
| Name, Some crc -> add_interface (Contents crc)
| Name, Some crc ->
String.Map.add name (Contents crc, filename) ifaces
| Contents old_crc, Some crc ->
if old_crc <> crc then raise (DT.Error (Inconsistent_import name))
else ifaces)
ifaces
(UH.interface_imports ui)
let check_implementation_imports filename ui implems =
let check_implementation_imports ~allowed_units filename ui implems =
List.iter (fun (name, crc) ->
match String.Map.find name implems with
| exception Not_found -> raise (DT.Error (Unavailable_unit name))
| ((old_crc, _old_src, unit_state) : implem) ->
begin match old_crc, crc with
| (None | Some _), None -> ()
| None, Some _crc ->
(* The [None] behaves like a CRC different from every other. *)
if not (String.Set.mem name allowed_units) then begin
raise (DT.Error (Unavailable_unit name))
end;
match String.Map.find name implems with
| exception Not_found -> raise (DT.Error (Unavailable_unit name))
| ((old_crc, _old_src, unit_state) : implem) ->
begin match old_crc, crc with
| (None | Some _), None -> ()
| None, Some _crc ->
(* The [None] behaves like a CRC different from every other. *)
raise (DT.Error (Inconsistent_implementation name))
| Some old_crc, Some crc ->
if old_crc <> crc then begin
raise (DT.Error (Inconsistent_implementation name))
| Some old_crc, Some crc ->
if old_crc <> crc then begin
raise (DT.Error (Inconsistent_implementation name))
end
end;
match unit_state with
| Not_initialized ->
end
end;
match unit_state with
| Not_initialized ->
raise (DT.Error (Linking_error (
filename, Uninitialized_global name)))
| Check_inited i ->
if P.num_globals_inited () < i then begin
raise (DT.Error (Linking_error (
filename, Uninitialized_global name)))
| Check_inited i ->
if P.num_globals_inited () < i then begin
raise (DT.Error (Linking_error (
filename, Uninitialized_global name)))
end
| Loaded -> ())
end
| Loaded -> ())
(UH.implementation_imports ui)
let check_name filename ui priv ifaces implems =
@ -229,15 +233,19 @@ module Make (P : Dynlink_platform_intf.S) = struct
check_name filename ui priv state.ifaces implems)
state.implems units
in
let allowed_units = String.Set.union state.allowed_units new_units in
let ifaces =
List.fold_left (fun ifaces ui ->
check_interface_imports filename ui ifaces
~allowed_units:allowed_units)
check_interface_imports filename ui ifaces)
state.ifaces units
in
List.iter (fun ui -> check_implementation_imports filename ui implems)
units;
let allowed_units = String.Set.union state.allowed_units new_units in
let (_ : implem String.Map.t) =
List.fold_left
(fun acc ui ->
check_implementation_imports ~allowed_units filename ui acc;
set_loaded_implem filename ui acc)
implems units
in
let defined_symbols =
List.fold_left (fun defined_symbols ui ->
let descr =
@ -323,19 +331,6 @@ module Make (P : Dynlink_platform_intf.S) = struct
if Filename.is_implicit fname then Filename.concat (Sys.getcwd ()) fname
else fname
let set_loaded filename units (state : State.t) =
let implems =
List.fold_left (fun implems ui ->
String.Map.add (UH.name ui) (UH.crc ui, filename, DT.Loaded)
implems)
state.implems
units
in
{ state with implems; }
let run_units handle priv units =
List.iter (fun unit_header -> P.run handle ~unit_header ~priv) units
let load priv filename =
init ();
let filename = dll_filename filename in
@ -344,10 +339,13 @@ module Make (P : Dynlink_platform_intf.S) = struct
| handle, units ->
try
global_state := check filename units !global_state ~priv;
run_units handle priv units;
if not priv then begin
global_state := set_loaded filename units !global_state
end;
List.iter
(fun unit_header ->
P.run handle ~unit_header ~priv;
if not priv then begin
global_state := set_loaded filename unit_header !global_state
end)
units;
P.finish handle
with exn ->
P.finish handle;

View File

@ -1,2 +1,9 @@
test1_main.ml
test2_main.ml
test3_main.ml
test4_main.ml
test5_main.ml
test6_main.ml
test7_main.ml
test8_main.ml
test9_main.ml

View File

@ -45,12 +45,13 @@ let f x = x + 1 [@@inline never]
let () =
try
if Dynlink.is_native then
if Dynlink.is_native then begin
Dynlink.loadfile "test1_plugin.cmxs"
else
end else begin
Dynlink.loadfile "test1_plugin.cmo"
end;
assert false
with
| Dynlink.Error (
Dynlink.Linking_error (_,
Dynlink.Uninitialized_global "Test1_inited_second")) -> ()
| exn -> raise exn

View File

@ -0,0 +1 @@
let f x = x + 1 [@@inline never]

View File

@ -2,49 +2,49 @@
include dynlink
files = "test2_plugin.ml test2_second_plugin.ml"
files = "test2_inited_first.ml test2_plugin.ml"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test2_inited_first.ml"
*** ocamlc.byte
module = "test2_main.ml"
*** ocamlc.byte
module = "test2_plugin.ml"
*** ocamlc.byte
module = "test2_second_plugin.ml"
*** ocamlc.byte
program = "${test_build_directory}/test2.byte"
libraries = "dynlink"
all_modules = "test2_main.cmo"
all_modules = "test2_inited_first.cmo test2_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test2_inited_first.ml"
**** ocamlopt.byte
module = "test2_main.ml"
**** ocamlopt.byte
program = "test2_plugin.cmxs"
flags = "-shared"
all_modules = "test2_plugin.ml"
**** ocamlopt.byte
program = "test2_second_plugin.cmxs"
flags = "-shared"
all_modules = "test2_second_plugin.ml"
**** ocamlopt.byte
program = "${test_build_directory}/test2.exe"
libraries = "dynlink"
all_modules = "test2_main.cmx"
all_modules = "test2_inited_first.cmx test2_main.cmx"
***** run
*)
(* Check that a module in a loaded shared library whose initializer has not
executed completely cannot be depended upon by another shared library being
loaded. *)
(* Check that a shared library can refer to a module in the main program
as long as that module has already been loaded. *)
let g x = Test2_inited_first.f x
let () =
if Dynlink.is_native then
if Dynlink.is_native then begin
Dynlink.loadfile "test2_plugin.cmxs"
else
end else begin
Dynlink.loadfile "test2_plugin.cmo"
end

View File

@ -1,16 +1,2 @@
let x = ref 0
let () =
try
if Dynlink.is_native then
Dynlink.loadfile "test2_second_plugin.cmxs"
else
Dynlink.loadfile "test2_second_plugin.cmo"
with
| Dynlink.Error (
Dynlink.Linking_error (_,
Dynlink.Uninitialized_global "Test2_plugin")) -> ()
| _ -> exit 1
let () =
x := 1
print_int (Test2_inited_first.f 42)

View File

@ -1,2 +0,0 @@
let () =
assert (!Test2_plugin.x = 1)

View File

@ -0,0 +1,55 @@
(* TEST
include dynlink
files = "test3_plugin_a.ml test3_plugin_b.ml"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test3_main.ml"
*** ocamlc.byte
module = "test3_plugin_a.ml"
*** ocamlc.byte
module = "test3_plugin_b.ml"
*** ocamlc.byte
program = "test3_plugin.cma"
flags = "-a"
all_modules = "test3_plugin_a.cmo test3_plugin_b.cmo"
*** ocamlc.byte
program = "${test_build_directory}/test3.byte"
libraries = "dynlink"
all_modules = "test3_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test3_main.ml"
**** ocamlopt.byte
module = "test3_plugin_a.ml"
**** ocamlopt.byte
module = "test3_plugin_b.ml"
**** ocamlopt.byte
program = "test3_plugin.cmxs"
flags = "-shared"
all_modules = "test3_plugin_a.cmx test3_plugin_b.cmx"
**** ocamlopt.byte
program = "${test_build_directory}/test3.exe"
libraries = "dynlink"
all_modules = "test3_main.cmx"
***** run
*)
(* Check that one module in a shared library can refer to another module
in the same shared library as long as the second module has already
been loaded. *)
let () =
if Dynlink.is_native then begin
Dynlink.loadfile "test3_plugin.cmxs"
end else begin
Dynlink.loadfile "test3_plugin.cma"
end

View File

@ -0,0 +1 @@
let f x = x + 3 [@@inline never]

View File

@ -0,0 +1,2 @@
let () =
print_int (Test3_plugin_a.f 42)

View File

@ -0,0 +1,60 @@
(* TEST
include dynlink
files = "test4_plugin_a.ml test4_plugin_b.ml"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test4_main.ml"
*** ocamlc.byte
module = "test4_plugin_b.ml"
*** ocamlc.byte
module = "test4_plugin_a.ml"
*** ocamlc.byte
program = "test4_plugin.cma"
flags = "-a"
all_modules = "test4_plugin_a.cmo test4_plugin_b.cmo"
*** ocamlc.byte
program = "${test_build_directory}/test4.byte"
libraries = "dynlink"
all_modules = "test4_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test4_main.ml"
**** ocamlopt.byte
module = "test4_plugin_b.ml"
**** ocamlopt.byte
module = "test4_plugin_a.ml"
**** ocamlopt.byte
program = "test4_plugin.cmxs"
flags = "-shared"
all_modules = "test4_plugin_a.cmx test4_plugin_b.cmx"
**** ocamlopt.byte
program = "${test_build_directory}/test4.exe"
libraries = "dynlink"
all_modules = "test4_main.cmx"
***** run
*)
(* Check that a module in a shared library cannot refer to another
module in the same shared library if it has not yet been loaded. *)
let () =
try
if Dynlink.is_native then begin
Dynlink.loadfile "test4_plugin.cmxs"
end else begin
Dynlink.loadfile "test4_plugin.cma"
end;
assert false
with
| Dynlink.Error (
Dynlink.Linking_error (_,
Dynlink.Uninitialized_global "Test4_plugin_b")) -> ()

View File

@ -0,0 +1,2 @@
let () =
print_int (Test4_plugin_b.f 42)

View File

@ -0,0 +1 @@
let f x = x + 3 [@@inline never]

View File

@ -0,0 +1,60 @@
(* TEST
include dynlink
files = "test5_plugin_a.ml test5_plugin_b.ml test5_second_plugin.ml"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test5_main.ml"
*** ocamlc.byte
module = "test5_plugin_a.ml"
*** ocamlc.byte
module = "test5_plugin_b.ml"
*** ocamlc.byte
module = "test5_second_plugin.ml"
*** ocamlc.byte
program = "test5_plugin.cma"
flags = "-a"
all_modules = "test5_plugin_a.cmo test5_plugin_b.cmo"
*** ocamlc.byte
program = "${test_build_directory}/test5.byte"
libraries = "dynlink"
all_modules = "test5_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test5_main.ml"
**** ocamlopt.byte
module = "test5_plugin_a.ml"
**** ocamlopt.byte
module = "test5_plugin_b.ml"
**** ocamlopt.byte
program = "test5_plugin.cmxs"
flags = "-shared"
all_modules = "test5_plugin_a.cmx test5_plugin_b.cmx"
**** ocamlopt.byte
program = "test5_second_plugin.cmxs"
flags = "-shared"
all_modules = "test5_second_plugin.ml"
**** ocamlopt.byte
program = "${test_build_directory}/test5.exe"
libraries = "dynlink"
all_modules = "test5_main.cmx"
***** run
*)
(* Check that when one shared library loads another shared library then
modules of the second shared library can refer to modules of the
first shared library, as long as they have already been loaded. *)
let () =
if Dynlink.is_native then
Dynlink.loadfile "test5_plugin.cmxs"
else
Dynlink.loadfile "test5_plugin.cma"

View File

@ -0,0 +1,4 @@
let x = ref 0
let () =
x := 1

View File

@ -0,0 +1,6 @@
let () =
if Dynlink.is_native then begin
Dynlink.loadfile "test5_second_plugin.cmxs"
end else begin
Dynlink.loadfile "test5_second_plugin.cmo"
end

View File

@ -0,0 +1,2 @@
let () =
assert (!Test5_plugin_a.x = 1)

View File

@ -0,0 +1,50 @@
(* TEST
include dynlink
files = "test6_plugin.ml test6_second_plugin.ml"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test6_main.ml"
*** ocamlc.byte
module = "test6_plugin.ml"
*** ocamlc.byte
module = "test6_second_plugin.ml"
*** ocamlc.byte
program = "${test_build_directory}/test6.byte"
libraries = "dynlink"
all_modules = "test6_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test6_main.ml"
**** ocamlopt.byte
program = "test6_plugin.cmxs"
flags = "-shared"
all_modules = "test6_plugin.ml"
**** ocamlopt.byte
program = "test6_second_plugin.cmxs"
flags = "-shared"
all_modules = "test6_second_plugin.ml"
**** ocamlopt.byte
program = "${test_build_directory}/test6.exe"
libraries = "dynlink"
all_modules = "test6_main.cmx"
***** run
*)
(* Check that a module in a loaded shared library whose initializer has not
executed completely cannot be depended upon by another shared library being
loaded. *)
let () =
if Dynlink.is_native then
Dynlink.loadfile "test6_plugin.cmxs"
else
Dynlink.loadfile "test6_plugin.cmo"

View File

@ -0,0 +1,17 @@
let x = ref 0
let () =
try
if Dynlink.is_native then begin
Dynlink.loadfile "test6_second_plugin.cmxs"
end else begin
Dynlink.loadfile "test6_second_plugin.cmo"
end;
assert false
with
| Dynlink.Error (
Dynlink.Linking_error (_,
Dynlink.Uninitialized_global "Test6_plugin")) -> ()
let () =
x := 1

View File

@ -0,0 +1,2 @@
let () =
assert (!Test6_plugin.x = 1)

View File

@ -0,0 +1,2 @@
type t = int

View File

@ -0,0 +1,49 @@
(* TEST
include dynlink
files = "test7_interface_only.mli test7_plugin.ml"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test7_interface_only.mli"
*** ocamlc.byte
module = "test7_main.ml"
*** ocamlc.byte
module = "test7_plugin.ml"
*** ocamlc.byte
program = "${test_build_directory}/test7.byte"
libraries = "dynlink"
all_modules = "test7_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test7_interface_only.mli"
**** ocamlopt.byte
module = "test7_main.ml"
**** ocamlopt.byte
program = "test7_plugin.cmxs"
flags = "-shared"
all_modules = "test7_plugin.ml"
**** ocamlopt.byte
program = "${test_build_directory}/test7.exe"
libraries = "dynlink"
all_modules = "test7_main.cmx"
***** run
*)
(* Check that a shared library can depend on an interface-only module
that is also depended on by modules in the main program *)
let f (x : Test7_interface_only.t) = x + 1 [@@inline never]
let () =
if Dynlink.is_native then
Dynlink.loadfile "test7_plugin.cmxs"
else
Dynlink.loadfile "test7_plugin.cmo"

View File

@ -0,0 +1,2 @@
let () =
print_int (42 : Test7_interface_only.t)

View File

@ -0,0 +1,58 @@
(* TEST
include dynlink
files = "test8_plugin_a.ml test8_plugin_b.ml test8_plugin_b.mli"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test8_main.ml"
*** ocamlc.byte
module = "test8_plugin_b.mli"
*** ocamlc.byte
module = "test8_plugin_a.ml"
*** ocamlc.byte
module = "test8_plugin_b.ml"
*** ocamlc.byte
program = "test8_plugin.cma"
flags = "-a"
all_modules = "test8_plugin_a.cmo test8_plugin_b.cmo"
*** ocamlc.byte
program = "${test_build_directory}/test8.byte"
libraries = "dynlink"
all_modules = "test8_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test8_main.ml"
**** ocamlopt.byte
module = "test8_plugin_b.mli"
**** ocamlopt.byte
module = "test8_plugin_a.ml"
**** ocamlopt.byte
module = "test8_plugin_b.ml"
**** ocamlopt.byte
program = "test8_plugin.cmxs"
flags = "-shared"
all_modules = "test8_plugin_a.cmx test8_plugin_b.cmx"
**** ocamlopt.byte
program = "${test_build_directory}/test8.exe"
libraries = "dynlink"
all_modules = "test8_main.cmx"
***** run
*)
(* Check that modules of a shared library can have interface-only
dependencies to later modules in the same shared library. *)
let () =
if Dynlink.is_native then begin
Dynlink.loadfile "test8_plugin.cmxs"
end else begin
Dynlink.loadfile "test8_plugin.cma"
end

View File

@ -0,0 +1,4 @@
let () =
print_int (42 : Test8_plugin_b.t)
let f x = x + 3

View File

@ -0,0 +1,4 @@
type t = int
let () =
print_int (Test8_plugin_a.f 42)

View File

@ -0,0 +1,2 @@
type t = int

View File

@ -0,0 +1,57 @@
(* TEST
include dynlink
files = "test9_plugin.ml test9_second_plugin.ml test9_second_plugin.mli"
libraries = ""
* shared-libraries
** setup-ocamlc.byte-build-env
*** ocamlc.byte
module = "test9_second_plugin.mli"
*** ocamlc.byte
module = "test9_main.ml"
*** ocamlc.byte
module = "test9_plugin.ml"
*** ocamlc.byte
module = "test9_second_plugin.ml"
*** ocamlc.byte
program = "${test_build_directory}/test9.byte"
libraries = "dynlink"
all_modules = "test9_main.cmo"
**** run
** native-dynlink
*** setup-ocamlopt.byte-build-env
**** ocamlopt.byte
module = "test9_second_plugin.mli"
**** ocamlopt.byte
module = "test9_main.ml"
**** ocamlopt.byte
program = "test9_plugin.cmxs"
flags = "-shared"
all_modules = "test9_plugin.ml"
**** ocamlopt.byte
program = "test9_second_plugin.cmxs"
flags = "-shared"
all_modules = "test9_second_plugin.ml"
**** ocamlopt.byte
program = "${test_build_directory}/test9.exe"
libraries = "dynlink"
all_modules = "test9_main.cmx"
***** run
*)
(* Check that a shared library can depend on an interface-only module
that is implemented by another shared library that is loaded
later. *)
let () =
if Dynlink.is_native then begin
Dynlink.loadfile "test9_plugin.cmxs";
Dynlink.loadfile "test9_second_plugin.cmxs"
end else begin
Dynlink.loadfile "test9_plugin.cmo";
Dynlink.loadfile "test9_second_plugin.cmo"
end

View File

@ -0,0 +1,2 @@
let () =
print_int (42 : Test9_second_plugin.t)

View File

@ -0,0 +1,4 @@
type t = int
let () = print_endline "Second"

View File

@ -0,0 +1,2 @@
type t = int