ocamltest: complete and clarify support for runtime flags

master
Sébastien Hinderer 2018-02-19 08:23:12 +01:00
parent 42ff6e44b2
commit b7184e017e
5 changed files with 36 additions and 22 deletions

View File

@ -17,6 +17,10 @@
type t = Native | Bytecode
let is_bytecode t = t=Bytecode
let is_native t = t=Native
let string_of_backend = function
| Native -> "native"
| Bytecode -> "bytecode"

View File

@ -17,6 +17,10 @@
type t = Native | Bytecode
val is_bytecode : t -> bool
val is_native : t -> bool
val string_of_backend : t -> string
val make_backend_function : 'a -> 'a -> t -> 'a

View File

@ -29,3 +29,9 @@ let toplevel ocamlsrcdir =
let runtime ocamlsrcdir =
Filename.make_path [ocamlsrcdir; "byterun"]
let runtime_library backend ocamlsrcdir =
let backend_lib_dir = match backend with
| Ocaml_backends.Native -> "asmrun"
| Ocaml_backends.Bytecode -> "byterun" in
Filename.make_path [ocamlsrcdir; backend_lib_dir]

View File

@ -22,3 +22,5 @@ val stdlib : string -> string
val toplevel : string -> string
val runtime : string -> string
val runtime_library : Ocaml_backends.t -> string -> string

View File

@ -26,25 +26,23 @@ let c_includes ocamlsrcdir =
let dir = Ocaml_directories.runtime ocamlsrcdir in
"-ccopt -I" ^ dir
let runtime_flags ocamlsrcdir backend c_files = match backend with
| Ocaml_backends.Native -> ""
| Ocaml_backends.Bytecode ->
if c_files then begin (* custm mode *)
let runtime_variant = Ocaml_files.runtime_variant() in
let variant_flag = match runtime_variant with
| Ocaml_files.Normal -> ""
| Ocaml_files.Debug -> " -runtime-variant d"
| Ocaml_files.Instrumented -> " -runtime-variant i" in
"-custom" ^ variant_flag ^ " -I " ^
(Ocaml_directories.runtime ocamlsrcdir)
(* when using the debug or instrumented runtimes, we need to include
the byterun directory so that libcamlrund and libcamlruni
can be found. This is not necessary with the normal runtime
because libcamlrun is copied to the stdlib directory which
will be included anyway
*)
end else begin (* non-custom mode *)
let ocamlrun = Ocaml_files.ocamlrun ocamlsrcdir in
"-use-runtime " ^ ocamlrun
end
let runtime_variant_flags () = match Ocaml_files.runtime_variant() with
| Ocaml_files.Normal -> ""
| Ocaml_files.Debug -> " -runtime-variant d"
| Ocaml_files.Instrumented -> " -runtime-variant i"
let runtime_flags ocamlsrcdir backend c_files =
let runtime_library_flags = "-I " ^
(Ocaml_directories.runtime_library backend ocamlsrcdir) in
let rt_flags = match backend with
| Ocaml_backends.Native -> runtime_variant_flags ()
| Ocaml_backends.Bytecode ->
begin
if c_files then begin (* custom mode *)
"-custom " ^ (runtime_variant_flags ())
end else begin (* non-custom mode *)
"-use-runtime " ^ (Ocaml_files.ocamlrun ocamlsrcdir)
end
end in
rt_flags ^ " " ^ runtime_library_flags