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 type t = Native | Bytecode
let is_bytecode t = t=Bytecode
let is_native t = t=Native
let string_of_backend = function let string_of_backend = function
| Native -> "native" | Native -> "native"
| Bytecode -> "bytecode" | Bytecode -> "bytecode"

View File

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

View File

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