stop passing the constant ocamlsrcdir to each function

master
Nicolás Ojeda Bär 2020-05-21 07:16:03 +02:00 committed by Gabriel Scherer
parent e68b75eb82
commit 6c311f3007
16 changed files with 202 additions and 210 deletions

View File

@ -221,10 +221,12 @@ ocaml_directories.cmi :
ocaml_files.cmo : \ ocaml_files.cmo : \
ocamltest_stdlib.cmi \ ocamltest_stdlib.cmi \
ocamltest_config.cmi \ ocamltest_config.cmi \
ocaml_directories.cmi \
ocaml_files.cmi ocaml_files.cmi
ocaml_files.cmx : \ ocaml_files.cmx : \
ocamltest_stdlib.cmx \ ocamltest_stdlib.cmx \
ocamltest_config.cmx \ ocamltest_config.cmx \
ocaml_directories.cmx \
ocaml_files.cmi ocaml_files.cmi
ocaml_files.cmi : ocaml_files.cmi :
ocaml_filetypes.cmo : \ ocaml_filetypes.cmo : \

View File

@ -94,7 +94,7 @@ let default_ocaml_env = [|
type module_generator = { type module_generator = {
description : string; description : string;
command : string -> string; command : string;
flags : Environments.t -> string; flags : Environments.t -> string;
generated_compilation_units : generated_compilation_units :
string -> (string * Ocaml_filetypes.t) list string -> (string * Ocaml_filetypes.t) list
@ -122,7 +122,7 @@ let ocamlyacc =
] ]
} }
let generate_module generator ocamlsrcdir output_variable input log env = let generate_module generator output_variable input log env =
let basename = fst input in let basename = fst input in
let input_file = Ocaml_filetypes.make_filename input in let input_file = Ocaml_filetypes.make_filename input in
let what = let what =
@ -132,7 +132,7 @@ let generate_module generator ocamlsrcdir output_variable input log env =
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
let commandline = let commandline =
[ [
generator.command ocamlsrcdir; generator.command;
generator.flags env; generator.flags env;
input_file input_file
] in ] in
@ -159,7 +159,7 @@ let generate_lexer = generate_module ocamllex
let generate_parser = generate_module ocamlyacc let generate_parser = generate_module ocamlyacc
let prepare_module ocamlsrcdir output_variable log env input = let prepare_module output_variable log env input =
let input_type = snd input in let input_type = snd input in
let open Ocaml_filetypes in let open Ocaml_filetypes in
match input_type with match input_type with
@ -168,9 +168,9 @@ let prepare_module ocamlsrcdir output_variable log env input =
| Backend_specific _ -> [input] | Backend_specific _ -> [input]
| C_minus_minus -> assert false | C_minus_minus -> assert false
| Lexer -> | Lexer ->
generate_lexer ocamlsrcdir output_variable input log env generate_lexer output_variable input log env
| Grammar -> | Grammar ->
generate_parser ocamlsrcdir output_variable input log env generate_parser output_variable input log env
| Text -> assert false | Text -> assert false
let get_program_file backend env = let get_program_file backend env =
@ -208,18 +208,18 @@ let cmas_need_dynamic_loading directories libraries =
in in
List.find_map loads_c_code (String.words libraries) List.find_map loads_c_code (String.words libraries)
let compile_program ocamlsrcdir (compiler : Ocaml_compilers.compiler) log env = let compile_program (compiler : Ocaml_compilers.compiler) log env =
let program_variable = compiler#program_variable in let program_variable = compiler#program_variable in
let program_file = Environments.safe_lookup program_variable env in let program_file = Environments.safe_lookup program_variable env in
let all_modules = let all_modules =
Actions_helpers.words_of_variable env Ocaml_variables.all_modules in Actions_helpers.words_of_variable env Ocaml_variables.all_modules in
let output_variable = compiler#output_variable in let output_variable = compiler#output_variable in
let prepare = prepare_module ocamlsrcdir output_variable log env in let prepare = prepare_module output_variable log env in
let modules = let modules =
List.concatmap prepare (List.map Ocaml_filetypes.filetype all_modules) in List.concatmap prepare (List.map Ocaml_filetypes.filetype all_modules) in
let has_c_file = List.exists is_c_file modules in let has_c_file = List.exists is_c_file modules in
let c_headers_flags = let c_headers_flags =
if has_c_file then Ocaml_flags.c_includes ocamlsrcdir else "" in if has_c_file then Ocaml_flags.c_includes else "" in
let expected_exit_status = let expected_exit_status =
Ocaml_tools.expected_exit_status env (compiler :> Ocaml_tools.tool) in Ocaml_tools.expected_exit_status env (compiler :> Ocaml_tools.tool) in
let module_names = let module_names =
@ -250,11 +250,11 @@ let compile_program ocamlsrcdir (compiler : Ocaml_compilers.compiler) log env =
let bytecode_links_c_code = (cmas_need_dynamic_loading = Some (Ok ())) in let bytecode_links_c_code = (cmas_need_dynamic_loading = Some (Ok ())) in
let commandline = let commandline =
[ [
compiler#name ocamlsrcdir; compiler#name;
Ocaml_flags.runtime_flags ocamlsrcdir env compiler#target Ocaml_flags.runtime_flags env compiler#target
(has_c_file || bytecode_links_c_code); (has_c_file || bytecode_links_c_code);
c_headers_flags; c_headers_flags;
Ocaml_flags.stdlib ocamlsrcdir; Ocaml_flags.stdlib;
directory_flags env; directory_flags env;
flags env; flags env;
libraries; libraries;
@ -283,7 +283,7 @@ let compile_program ocamlsrcdir (compiler : Ocaml_compilers.compiler) log env =
(Result.fail_with_reason reason, env) (Result.fail_with_reason reason, env)
end end
let compile_module ocamlsrcdir compiler module_ log env = let compile_module compiler module_ log env =
let expected_exit_status = let expected_exit_status =
Ocaml_tools.expected_exit_status env (compiler :> Ocaml_tools.tool) in Ocaml_tools.expected_exit_status env (compiler :> Ocaml_tools.tool) in
let what = Printf.sprintf "Compiling module %s" module_ in let what = Printf.sprintf "Compiling module %s" module_ in
@ -291,11 +291,11 @@ let compile_module ocamlsrcdir compiler module_ log env =
let module_with_filetype = Ocaml_filetypes.filetype module_ in let module_with_filetype = Ocaml_filetypes.filetype module_ in
let is_c = is_c_file module_with_filetype in let is_c = is_c_file module_with_filetype in
let c_headers_flags = let c_headers_flags =
if is_c then Ocaml_flags.c_includes ocamlsrcdir else "" in if is_c then Ocaml_flags.c_includes else "" in
let commandline = let commandline =
[ [
compiler#name ocamlsrcdir; compiler#name;
Ocaml_flags.stdlib ocamlsrcdir; Ocaml_flags.stdlib;
c_headers_flags; c_headers_flags;
directory_flags env; directory_flags env;
flags env; flags env;
@ -459,20 +459,19 @@ let setup_ocamlnat_build_env =
Ocaml_toplevels.ocamlnat) Ocaml_toplevels.ocamlnat)
let compile (compiler : Ocaml_compilers.compiler) log env = let compile (compiler : Ocaml_compilers.compiler) log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
match Environments.lookup_nonempty Builtin_variables.commandline env with match Environments.lookup_nonempty Builtin_variables.commandline env with
| None -> | None ->
begin begin
match Environments.lookup_nonempty Ocaml_variables.module_ env with match Environments.lookup_nonempty Ocaml_variables.module_ env with
| None -> compile_program ocamlsrcdir compiler log env | None -> compile_program compiler log env
| Some module_ -> compile_module ocamlsrcdir compiler module_ log env | Some module_ -> compile_module compiler module_ log env
end end
| Some cmdline -> | Some cmdline ->
let expected_exit_status = let expected_exit_status =
Ocaml_tools.expected_exit_status env (compiler :> Ocaml_tools.tool) in Ocaml_tools.expected_exit_status env (compiler :> Ocaml_tools.tool) in
let what = Printf.sprintf "Compiling using commandline %s" cmdline in let what = Printf.sprintf "Compiling using commandline %s" cmdline in
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
let commandline = [compiler#name ocamlsrcdir; cmdline] in let commandline = [compiler#name; cmdline] in
let exit_status = let exit_status =
Actions_helpers.run_cmd Actions_helpers.run_cmd
~environment:default_ocaml_env ~environment:default_ocaml_env
@ -515,8 +514,8 @@ let ocamlopt_opt =
"ocamlopt.opt" "ocamlopt.opt"
(compile Ocaml_compilers.ocamlopt_opt)) (compile Ocaml_compilers.ocamlopt_opt))
let env_with_lib_unix ocamlsrcdir env = let env_with_lib_unix env =
let libunixdir = Ocaml_directories.libunix ocamlsrcdir in let libunixdir = Ocaml_directories.libunix in
let newlibs = let newlibs =
match Environments.lookup Ocaml_variables.caml_ld_library_path env with match Environments.lookup Ocaml_variables.caml_ld_library_path env with
| None -> libunixdir | None -> libunixdir
@ -525,20 +524,19 @@ let env_with_lib_unix ocamlsrcdir env =
Environments.add Ocaml_variables.caml_ld_library_path newlibs env Environments.add Ocaml_variables.caml_ld_library_path newlibs env
let debug log env = let debug log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let program = Environments.safe_lookup Builtin_variables.program env in let program = Environments.safe_lookup Builtin_variables.program env in
let what = Printf.sprintf "Debugging program %s" program in let what = Printf.sprintf "Debugging program %s" program in
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
let commandline = let commandline =
[ [
Ocaml_commands.ocamlrun_ocamldebug ocamlsrcdir; Ocaml_commands.ocamlrun_ocamldebug;
Ocaml_flags.ocamldebug_default_flags ocamlsrcdir; Ocaml_flags.ocamldebug_default_flags;
program program
] in ] in
let systemenv = let systemenv =
Array.append Array.append
default_ocaml_env default_ocaml_env
(Environments.to_system_env (env_with_lib_unix ocamlsrcdir env)) (Environments.to_system_env (env_with_lib_unix env))
in in
let expected_exit_status = 0 in let expected_exit_status = 0 in
let exit_status = let exit_status =
@ -548,7 +546,7 @@ let debug log env =
~stdout_variable:Builtin_variables.output ~stdout_variable:Builtin_variables.output
~stderr_variable:Builtin_variables.output ~stderr_variable:Builtin_variables.output
~append:true ~append:true
log (env_with_lib_unix ocamlsrcdir env) commandline in log (env_with_lib_unix env) commandline in
if exit_status=expected_exit_status if exit_status=expected_exit_status
then (Result.pass, env) then (Result.pass, env)
else begin else begin
@ -561,14 +559,13 @@ let debug log env =
let ocamldebug = Actions.make "ocamldebug" debug let ocamldebug = Actions.make "ocamldebug" debug
let objinfo log env = let objinfo log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in let tools_directory = Ocaml_directories.tools in
let tools_directory = Ocaml_directories.tools ocamlsrcdir in
let program = Environments.safe_lookup Builtin_variables.program env in let program = Environments.safe_lookup Builtin_variables.program env in
let what = Printf.sprintf "Running ocamlobjinfo on %s" program in let what = Printf.sprintf "Running ocamlobjinfo on %s" program in
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
let commandline = let commandline =
[ [
Ocaml_commands.ocamlrun_ocamlobjinfo ocamlsrcdir; Ocaml_commands.ocamlrun_ocamlobjinfo;
Ocaml_flags.ocamlobjinfo_default_flags; Ocaml_flags.ocamlobjinfo_default_flags;
program program
] in ] in
@ -578,7 +575,7 @@ let objinfo log env =
[ [
default_ocaml_env; default_ocaml_env;
ocamllib; ocamllib;
(Environments.to_system_env (env_with_lib_unix ocamlsrcdir env)) (Environments.to_system_env (env_with_lib_unix env))
] ]
in in
let expected_exit_status = 0 in let expected_exit_status = 0 in
@ -588,7 +585,7 @@ let objinfo log env =
~stdout_variable:Builtin_variables.output ~stdout_variable:Builtin_variables.output
~stderr_variable:Builtin_variables.output ~stderr_variable:Builtin_variables.output
~append:true ~append:true
log (env_with_lib_unix ocamlsrcdir env) commandline in log (env_with_lib_unix env) commandline in
if exit_status=expected_exit_status if exit_status=expected_exit_status
then (Result.pass, env) then (Result.pass, env)
else begin else begin
@ -601,20 +598,19 @@ let objinfo log env =
let ocamlobjinfo = Actions.make "ocamlobjinfo" objinfo let ocamlobjinfo = Actions.make "ocamlobjinfo" objinfo
let mklib log env = let mklib log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let program = Environments.safe_lookup Builtin_variables.program env in let program = Environments.safe_lookup Builtin_variables.program env in
let what = Printf.sprintf "Running ocamlmklib to produce %s" program in let what = Printf.sprintf "Running ocamlmklib to produce %s" program in
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
let ocamlc_command = let ocamlc_command =
String.concat " " String.concat " "
[ [
Ocaml_commands.ocamlrun_ocamlc ocamlsrcdir; Ocaml_commands.ocamlrun_ocamlc;
Ocaml_flags.stdlib ocamlsrcdir; Ocaml_flags.stdlib;
] ]
in in
let commandline = let commandline =
[ [
Ocaml_commands.ocamlrun_ocamlmklib ocamlsrcdir; Ocaml_commands.ocamlrun_ocamlmklib;
"-ocamlc '" ^ ocamlc_command ^ "'"; "-ocamlc '" ^ ocamlc_command ^ "'";
"-o " ^ program "-o " ^ program
] @ modules env in ] @ modules env in
@ -637,11 +633,11 @@ let mklib log env =
let ocamlmklib = Actions.make "ocamlmklib" mklib let ocamlmklib = Actions.make "ocamlmklib" mklib
let finalise_codegen_cc ocamlsrcdir test_basename _log env = let finalise_codegen_cc test_basename _log env =
let test_module = let test_module =
Filename.make_filename test_basename "s" Filename.make_filename test_basename "s"
in in
let archmod = Ocaml_files.asmgen_archmod ocamlsrcdir in let archmod = Ocaml_files.asmgen_archmod in
let modules = test_module ^ " " ^ archmod in let modules = test_module ^ " " ^ archmod in
let program = Filename.make_filename test_basename "out" in let program = Filename.make_filename test_basename "out" in
let env = Environments.add_bindings let env = Environments.add_bindings
@ -651,7 +647,7 @@ let finalise_codegen_cc ocamlsrcdir test_basename _log env =
] env in ] env in
(Result.pass, env) (Result.pass, env)
let finalise_codegen_msvc ocamlsrcdir test_basename log env = let finalise_codegen_msvc test_basename log env =
let obj = Filename.make_filename test_basename Ocamltest_config.objext in let obj = Filename.make_filename test_basename Ocamltest_config.objext in
let src = Filename.make_filename test_basename "s" in let src = Filename.make_filename test_basename "s" in
let what = "Running Microsoft assembler" in let what = "Running Microsoft assembler" in
@ -667,7 +663,7 @@ let finalise_codegen_msvc ocamlsrcdir test_basename log env =
log env commandline in log env commandline in
if exit_status=expected_exit_status if exit_status=expected_exit_status
then begin then begin
let archmod = Ocaml_files.asmgen_archmod ocamlsrcdir in let archmod = Ocaml_files.asmgen_archmod in
let modules = obj ^ " " ^ archmod in let modules = obj ^ " " ^ archmod in
let program = Filename.make_filename test_basename "out" in let program = Filename.make_filename test_basename "out" in
let env = Environments.add_bindings let env = Environments.add_bindings
@ -684,7 +680,6 @@ let finalise_codegen_msvc ocamlsrcdir test_basename log env =
end end
let run_codegen log env = let run_codegen log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let testfile = Actions_helpers.testfile env in let testfile = Actions_helpers.testfile env in
let testfile_basename = Filename.chop_extension testfile in let testfile_basename = Filename.chop_extension testfile in
let what = Printf.sprintf "Running codegen on %s" testfile in let what = Printf.sprintf "Running codegen on %s" testfile in
@ -705,7 +700,7 @@ let run_codegen log env =
let env = Environments.add Builtin_variables.output output env in let env = Environments.add Builtin_variables.output output env in
let commandline = let commandline =
[ [
Ocaml_commands.ocamlrun_codegen ocamlsrcdir; Ocaml_commands.ocamlrun_codegen;
flags env; flags env;
"-S " ^ testfile "-S " ^ testfile
] in ] in
@ -724,7 +719,7 @@ let run_codegen log env =
then finalise_codegen_msvc then finalise_codegen_msvc
else finalise_codegen_cc else finalise_codegen_cc
in in
finalise ocamlsrcdir testfile_basename log env finalise testfile_basename log env
end else begin end else begin
let reason = let reason =
(Actions_helpers.mkreason (Actions_helpers.mkreason
@ -735,7 +730,6 @@ let run_codegen log env =
let codegen = Actions.make "codegen" run_codegen let codegen = Actions.make "codegen" run_codegen
let run_cc log env = let run_cc log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let program = Environments.safe_lookup Builtin_variables.program env in let program = Environments.safe_lookup Builtin_variables.program env in
let what = Printf.sprintf "Running C compiler to build %s" program in let what = Printf.sprintf "Running C compiler to build %s" program in
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
@ -746,7 +740,7 @@ let run_cc log env =
[ [
Ocamltest_config.cc; Ocamltest_config.cc;
Ocamltest_config.cflags; Ocamltest_config.cflags;
"-I" ^ Ocaml_directories.runtime ocamlsrcdir; "-I" ^ Ocaml_directories.runtime;
output_exe ^ program; output_exe ^ program;
Environments.safe_lookup Builtin_variables.arguments env; Environments.safe_lookup Builtin_variables.arguments env;
] @ modules env in ] @ modules env in
@ -769,13 +763,13 @@ let run_cc log env =
let cc = Actions.make "cc" run_cc let cc = Actions.make "cc" run_cc
let run_expect_once ocamlsrcdir input_file principal log env = let run_expect_once input_file principal log env =
let expect_flags = Sys.safe_getenv "EXPECT_FLAGS" in let expect_flags = Sys.safe_getenv "EXPECT_FLAGS" in
let repo_root = "-repo-root " ^ ocamlsrcdir in let repo_root = "-repo-root " ^ Ocaml_directories.srcdir in
let principal_flag = if principal then "-principal" else "" in let principal_flag = if principal then "-principal" else "" in
let commandline = let commandline =
[ [
Ocaml_commands.ocamlrun_expect_test ocamlsrcdir; Ocaml_commands.ocamlrun_expect_test;
expect_flags; expect_flags;
flags env; flags env;
repo_root; repo_root;
@ -792,13 +786,13 @@ let run_expect_once ocamlsrcdir input_file principal log env =
(Result.fail_with_reason reason, env) (Result.fail_with_reason reason, env)
end end
let run_expect_twice ocamlsrcdir input_file log env = let run_expect_twice input_file log env =
let corrected filename = Filename.make_filename filename "corrected" in let corrected filename = Filename.make_filename filename "corrected" in
let (result1, env1) = run_expect_once ocamlsrcdir input_file false log env in let (result1, env1) = run_expect_once input_file false log env in
if Result.is_pass result1 then begin if Result.is_pass result1 then begin
let intermediate_file = corrected input_file in let intermediate_file = corrected input_file in
let (result2, env2) = let (result2, env2) =
run_expect_once ocamlsrcdir intermediate_file true log env1 in run_expect_once intermediate_file true log env1 in
if Result.is_pass result2 then begin if Result.is_pass result2 then begin
let output_file = corrected intermediate_file in let output_file = corrected intermediate_file in
let output_env = Environments.add_bindings let output_env = Environments.add_bindings
@ -811,9 +805,8 @@ let run_expect_twice ocamlsrcdir input_file log env =
end else (result1, env1) end else (result1, env1)
let run_expect log env = let run_expect log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let input_file = Actions_helpers.testfile env in let input_file = Actions_helpers.testfile env in
run_expect_twice ocamlsrcdir input_file log env run_expect_twice input_file log env
let run_expect = Actions.make "run-expect" run_expect let run_expect = Actions.make "run-expect" run_expect
@ -893,18 +886,17 @@ let compare_programs backend comparison_tool log env =
(Result.pass_with_reason reason, env) (Result.pass_with_reason reason, env)
end else really_compare_programs backend comparison_tool log env end else really_compare_programs backend comparison_tool log env
let make_bytecode_programs_comparison_tool ocamlsrcdir = let make_bytecode_programs_comparison_tool =
let ocamlrun = Ocaml_files.ocamlrun ocamlsrcdir in let ocamlrun = Ocaml_files.ocamlrun in
let cmpbyt = Ocaml_files.cmpbyt ocamlsrcdir in let cmpbyt = Ocaml_files.cmpbyt in
let tool_name = ocamlrun ^ " " ^ cmpbyt in let tool_name = ocamlrun ^ " " ^ cmpbyt in
Filecompare.make_comparison_tool tool_name "" Filecompare.make_comparison_tool tool_name ""
let native_programs_comparison_tool = Filecompare.default_comparison_tool let native_programs_comparison_tool = Filecompare.default_comparison_tool
let compare_bytecode_programs_code log env = let compare_bytecode_programs_code log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let bytecode_programs_comparison_tool = let bytecode_programs_comparison_tool =
make_bytecode_programs_comparison_tool ocamlsrcdir in make_bytecode_programs_comparison_tool in
compare_programs compare_programs
Ocaml_backends.Bytecode bytecode_programs_comparison_tool log env Ocaml_backends.Bytecode bytecode_programs_comparison_tool log env
@ -920,8 +912,7 @@ let compare_native_programs =
"compare-native-programs" "compare-native-programs"
(compare_programs Ocaml_backends.Native native_programs_comparison_tool)) (compare_programs Ocaml_backends.Native native_programs_comparison_tool))
let compile_module let compile_module compiler compilername compileroutput log env
ocamlsrcdir compiler compilername compileroutput log env
(module_basename, module_filetype) = (module_basename, module_filetype) =
let backend = compiler#target in let backend = compiler#target in
let filename = let filename =
@ -938,7 +929,7 @@ let compile_module
| Some file -> "-o " ^ file in | Some file -> "-o " ^ file in
[ [
compilername; compilername;
Ocaml_flags.stdlib ocamlsrcdir; Ocaml_flags.stdlib;
flags env; flags env;
backend_flags env backend; backend_flags env backend;
optional_flags; optional_flags;
@ -980,19 +971,18 @@ let compile_module
let _object_filename = module_basename ^ object_extension in let _object_filename = module_basename ^ object_extension in
let commandline = let commandline =
compile_commandline filename None compile_commandline filename None
(Ocaml_flags.c_includes ocamlsrcdir) in Ocaml_flags.c_includes in
exec commandline exec commandline
| _ -> | _ ->
let reason = Printf.sprintf "File %s of type %s not supported yet" let reason = Printf.sprintf "File %s of type %s not supported yet"
filename (Ocaml_filetypes.string_of_filetype module_filetype) in filename (Ocaml_filetypes.string_of_filetype module_filetype) in
(Result.fail_with_reason reason, env) (Result.fail_with_reason reason, env)
let compile_modules let compile_modules compiler compilername compileroutput
ocamlsrcdir compiler compilername compileroutput
modules_with_filetypes log initial_env modules_with_filetypes log initial_env
= =
let compile_mod env mod_ = let compile_mod env mod_ =
compile_module ocamlsrcdir compiler compilername compileroutput compile_module compiler compilername compileroutput
log env mod_ in log env mod_ in
let rec compile_mods env = function let rec compile_mods env = function
| [] -> (Result.pass, env) | [] -> (Result.pass, env)
@ -1024,13 +1014,12 @@ let run_test_program_in_toplevel (toplevel : Ocaml_toplevels.toplevel) log env =
let expected_exit_status = let expected_exit_status =
Ocaml_tools.expected_exit_status env (toplevel :> Ocaml_tools.tool) in Ocaml_tools.expected_exit_status env (toplevel :> Ocaml_tools.tool) in
let compiler_output_variable = toplevel#output_variable in let compiler_output_variable = toplevel#output_variable in
let ocamlsrcdir = Ocaml_directories.srcdir () in
let compiler = toplevel#compiler in let compiler = toplevel#compiler in
let compiler_name = compiler#name ocamlsrcdir in let compiler_name = compiler#name in
let modules_with_filetypes = let modules_with_filetypes =
List.map Ocaml_filetypes.filetype (modules env) in List.map Ocaml_filetypes.filetype (modules env) in
let (result, env) = compile_modules let (result, env) = compile_modules
ocamlsrcdir compiler compiler_name compiler_output_variable compiler compiler_name compiler_output_variable
modules_with_filetypes log env in modules_with_filetypes log env in
if Result.is_pass result then begin if Result.is_pass result then begin
let what = let what =
@ -1040,7 +1029,7 @@ let run_test_program_in_toplevel (toplevel : Ocaml_toplevels.toplevel) log env =
(Ocaml_backends.string_of_backend backend) (Ocaml_backends.string_of_backend backend)
expected_exit_status in expected_exit_status in
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
let toplevel_name = toplevel#name ocamlsrcdir in let toplevel_name = toplevel#name in
let ocaml_script_as_argument = let ocaml_script_as_argument =
match match
Environments.lookup_as_bool Environments.lookup_as_bool
@ -1054,9 +1043,9 @@ let run_test_program_in_toplevel (toplevel : Ocaml_toplevels.toplevel) log env =
toplevel_name; toplevel_name;
Ocaml_flags.toplevel_default_flags; Ocaml_flags.toplevel_default_flags;
toplevel#flags; toplevel#flags;
Ocaml_flags.stdlib ocamlsrcdir; Ocaml_flags.stdlib;
directory_flags env; directory_flags env;
Ocaml_flags.include_toplevel_directory ocamlsrcdir; Ocaml_flags.include_toplevel_directory;
flags env; flags env;
libraries; libraries;
binary_modules backend env; binary_modules backend env;
@ -1106,13 +1095,12 @@ let check_ocamlnat_output =
"check-ocamlnat-output" Ocaml_toplevels.ocamlnat) "check-ocamlnat-output" Ocaml_toplevels.ocamlnat)
let config_variables _log env = let config_variables _log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
Environments.add_bindings Environments.add_bindings
[ [
Ocaml_variables.arch, Ocamltest_config.arch; Ocaml_variables.arch, Ocamltest_config.arch;
Ocaml_variables.ocamlrun, Ocaml_files.ocamlrun ocamlsrcdir; Ocaml_variables.ocamlrun, Ocaml_files.ocamlrun;
Ocaml_variables.ocamlc_byte, Ocaml_files.ocamlc ocamlsrcdir; Ocaml_variables.ocamlc_byte, Ocaml_files.ocamlc;
Ocaml_variables.ocamlopt_byte, Ocaml_files.ocamlopt ocamlsrcdir; Ocaml_variables.ocamlopt_byte, Ocaml_files.ocamlopt;
Ocaml_variables.bytecc_libs, Ocamltest_config.bytecc_libs; Ocaml_variables.bytecc_libs, Ocamltest_config.bytecc_libs;
Ocaml_variables.nativecc_libs, Ocamltest_config.nativecc_libs; Ocaml_variables.nativecc_libs, Ocamltest_config.nativecc_libs;
Ocaml_variables.mkdll, Ocaml_variables.mkdll,
@ -1131,7 +1119,7 @@ let config_variables _log env =
Ocaml_variables.ocamlopt_default_flags, Ocaml_variables.ocamlopt_default_flags,
Ocamltest_config.ocamlopt_default_flags; Ocamltest_config.ocamlopt_default_flags;
Ocaml_variables.ocamlrunparam, Sys.safe_getenv "OCAMLRUNPARAM"; Ocaml_variables.ocamlrunparam, Sys.safe_getenv "OCAMLRUNPARAM";
Ocaml_variables.ocamlsrcdir, Ocaml_directories.srcdir(); Ocaml_variables.ocamlsrcdir, Ocaml_directories.srcdir;
Ocaml_variables.os_type, Sys.os_type; Ocaml_variables.os_type, Sys.os_type;
] env ] env
@ -1247,9 +1235,9 @@ let compiled_doc_name input = input ^ ".odoc"
(* The compiler used for compiling both cmi file (* The compiler used for compiling both cmi file
and plugins *) and plugins *)
let compiler_for_ocamldoc ocamlsrcdir = let compiler_for_ocamldoc =
let compiler = Ocaml_compilers.ocamlc_byte in let compiler = Ocaml_compilers.ocamlc_byte in
compile_modules ocamlsrcdir compiler (compiler#name ocamlsrcdir) compile_modules compiler compiler#name
compiler#output_variable compiler#output_variable
(* Within ocamldoc tests, (* Within ocamldoc tests,
@ -1257,21 +1245,21 @@ let compiler_for_ocamldoc ocamlsrcdir =
secondaries documentation modules that need to be secondaries documentation modules that need to be
compiled into cmi files and odoc file (serialized ocamldoc information) compiled into cmi files and odoc file (serialized ocamldoc information)
before the main documentation is generated *) before the main documentation is generated *)
let compile_ocamldoc ocamlsrcdir (basename,filetype as module_) log env = let compile_ocamldoc (basename,filetype as module_) log env =
let expected_exit_status = let expected_exit_status =
Ocaml_tools.expected_exit_status env (ocamldoc :> Ocaml_tools.tool) in Ocaml_tools.expected_exit_status env (ocamldoc :> Ocaml_tools.tool) in
let what = Printf.sprintf "Compiling documentation for module %s" basename in let what = Printf.sprintf "Compiling documentation for module %s" basename in
Printf.fprintf log "%s\n%!" what; Printf.fprintf log "%s\n%!" what;
let filename = let filename =
Ocaml_filetypes.make_filename (basename, filetype) in Ocaml_filetypes.make_filename (basename, filetype) in
let (r,env) = compiler_for_ocamldoc ocamlsrcdir [module_] log env in let (r,env) = compiler_for_ocamldoc [module_] log env in
if not (Result.is_pass r) then (r,env) else if not (Result.is_pass r) then (r,env) else
let commandline = let commandline =
(* currently, we are ignoring the global ocamldoc_flags, since we (* currently, we are ignoring the global ocamldoc_flags, since we
don't have per-module flags *) don't have per-module flags *)
[ [
Ocaml_commands.ocamlrun_ocamldoc ocamlsrcdir; Ocaml_commands.ocamlrun_ocamldoc;
Ocaml_flags.stdlib ocamlsrcdir; Ocaml_flags.stdlib;
"-dump " ^ compiled_doc_name basename; "-dump " ^ compiled_doc_name basename;
filename; filename;
] in ] in
@ -1292,12 +1280,12 @@ let compile_ocamldoc ocamlsrcdir (basename,filetype as module_) log env =
(Result.fail_with_reason reason, env) (Result.fail_with_reason reason, env)
end end
let rec ocamldoc_compile_all ocamlsrcdir log env = function let rec ocamldoc_compile_all log env = function
| [] -> (Result.pass, env) | [] -> (Result.pass, env)
| a :: q -> | a :: q ->
let (r,env) = compile_ocamldoc ocamlsrcdir a log env in let (r,env) = compile_ocamldoc a log env in
if Result.is_pass r then if Result.is_pass r then
ocamldoc_compile_all ocamlsrcdir log env q ocamldoc_compile_all log env q
else else
(r,env) (r,env)
@ -1341,10 +1329,9 @@ let run_ocamldoc =
let modules = List.map Ocaml_filetypes.filetype @@ modules env in let modules = List.map Ocaml_filetypes.filetype @@ modules env in
(* plugins are used for custom documentation generators *) (* plugins are used for custom documentation generators *)
let plugins = List.map Ocaml_filetypes.filetype @@ plugins env in let plugins = List.map Ocaml_filetypes.filetype @@ plugins env in
let ocamlsrcdir = Ocaml_directories.srcdir () in let (r,env) = compiler_for_ocamldoc plugins log env in
let (r,env) = compiler_for_ocamldoc ocamlsrcdir plugins log env in
if not (Result.is_pass r) then r, env else if not (Result.is_pass r) then r, env else
let (r,env) = ocamldoc_compile_all ocamlsrcdir log env modules in let (r,env) = ocamldoc_compile_all log env modules in
if not (Result.is_pass r) then r, env else if not (Result.is_pass r) then r, env else
let input_file = Actions_helpers.testfile env in let input_file = Actions_helpers.testfile env in
Printf.fprintf log "Generating documentation for %s\n%!" input_file; Printf.fprintf log "Generating documentation for %s\n%!" input_file;
@ -1356,9 +1343,9 @@ let run_ocamldoc =
List.map (fun name -> "-g " ^ ocamldoc_plugin (fst name)) plugins in List.map (fun name -> "-g " ^ ocamldoc_plugin (fst name)) plugins in
let commandline = let commandline =
[ [
Ocaml_commands.ocamlrun_ocamldoc ocamlsrcdir; Ocaml_commands.ocamlrun_ocamldoc;
ocamldoc_backend_flag env; ocamldoc_backend_flag env;
Ocaml_flags.stdlib ocamlsrcdir; Ocaml_flags.stdlib;
ocamldoc_flags env] ocamldoc_flags env]
@ load_all @ with_plugins @ @ load_all @ with_plugins @
[ input_file; [ input_file;

View File

@ -15,31 +15,31 @@
(* Helper functions to build OCaml-related commands *) (* Helper functions to build OCaml-related commands *)
let ocamlrun ocamlsrcdir program = let ocamlrun program =
(Ocaml_files.ocamlrun ocamlsrcdir) ^ " " ^ (program ocamlsrcdir) Ocaml_files.ocamlrun ^ " " ^ program
let ocamlrun_ocamlc ocamlsrcdir = ocamlrun ocamlsrcdir Ocaml_files.ocamlc let ocamlrun_ocamlc = ocamlrun Ocaml_files.ocamlc
let ocamlrun_ocamlopt ocamlsrcdir = ocamlrun ocamlsrcdir Ocaml_files.ocamlopt let ocamlrun_ocamlopt = ocamlrun Ocaml_files.ocamlopt
let ocamlrun_ocaml ocamlsrcdir = ocamlrun ocamlsrcdir Ocaml_files.ocaml let ocamlrun_ocaml = ocamlrun Ocaml_files.ocaml
let ocamlrun_expect_test ocamlsrcdir = let ocamlrun_expect_test =
ocamlrun ocamlsrcdir Ocaml_files.expect_test ocamlrun Ocaml_files.expect_test
let ocamlrun_ocamllex ocamlsrcdir = ocamlrun ocamlsrcdir Ocaml_files.ocamllex let ocamlrun_ocamllex = ocamlrun Ocaml_files.ocamllex
let ocamlrun_ocamldoc ocamlsrcdir = let ocamlrun_ocamldoc =
ocamlrun ocamlsrcdir Ocaml_files.ocamldoc ocamlrun Ocaml_files.ocamldoc
let ocamlrun_ocamldebug ocamlsrcdir = let ocamlrun_ocamldebug =
ocamlrun ocamlsrcdir Ocaml_files.ocamldebug ocamlrun Ocaml_files.ocamldebug
let ocamlrun_ocamlobjinfo ocamlsrcdir = let ocamlrun_ocamlobjinfo =
ocamlrun ocamlsrcdir Ocaml_files.ocamlobjinfo ocamlrun Ocaml_files.ocamlobjinfo
let ocamlrun_ocamlmklib ocamlsrcdir = let ocamlrun_ocamlmklib =
ocamlrun ocamlsrcdir Ocaml_files.ocamlmklib ocamlrun Ocaml_files.ocamlmklib
let ocamlrun_codegen ocamlsrcdir = let ocamlrun_codegen =
ocamlrun ocamlsrcdir Ocaml_files.codegen ocamlrun Ocaml_files.codegen

View File

@ -15,21 +15,21 @@
(* Helper functions to build OCaml-related commands *) (* Helper functions to build OCaml-related commands *)
val ocamlrun_ocamlc : string -> string val ocamlrun_ocamlc : string
val ocamlrun_ocamlopt : string -> string val ocamlrun_ocamlopt : string
val ocamlrun_ocaml : string -> string val ocamlrun_ocaml : string
val ocamlrun_expect_test : string -> string val ocamlrun_expect_test : string
val ocamlrun_ocamllex : string -> string val ocamlrun_ocamllex : string
val ocamlrun_ocamldoc : string -> string val ocamlrun_ocamldoc : string
val ocamlrun_ocamldebug : string -> string val ocamlrun_ocamldebug : string
val ocamlrun_ocamlobjinfo : string -> string val ocamlrun_ocamlobjinfo : string
val ocamlrun_ocamlmklib : string -> string val ocamlrun_ocamlmklib : string
val ocamlrun_codegen : string -> string val ocamlrun_codegen : string

View File

@ -18,7 +18,7 @@
open Ocamltest_stdlib open Ocamltest_stdlib
class compiler class compiler
~(name : string -> string) ~(name : string)
~(flags : string) ~(flags : string)
~(directory : string) ~(directory : string)
~(exit_status_variable : Variables.t) ~(exit_status_variable : Variables.t)

View File

@ -16,7 +16,7 @@
(* Descriptions of the OCaml compilers *) (* Descriptions of the OCaml compilers *)
class compiler : class compiler :
name : (string -> string) -> name : string ->
flags : string -> flags : string ->
directory : string -> directory : string ->
exit_status_variable : Variables.t -> exit_status_variable : Variables.t ->

View File

@ -17,21 +17,21 @@
open Ocamltest_stdlib open Ocamltest_stdlib
let srcdir () = let srcdir =
Sys.getenv_with_default_value "OCAMLSRCDIR" Ocamltest_config.ocamlsrcdir Sys.getenv_with_default_value "OCAMLSRCDIR" Ocamltest_config.ocamlsrcdir
let stdlib ocamlsrcdir = let stdlib =
Filename.make_path [ocamlsrcdir; "stdlib"] Filename.make_path [srcdir; "stdlib"]
let libunix ocamlsrcdir = let libunix =
let subdir = if Sys.os_type="Win32" then "win32unix" else "unix" in let subdir = if Sys.os_type="Win32" then "win32unix" else "unix" in
Filename.make_path [ocamlsrcdir; "otherlibs"; subdir] Filename.make_path [srcdir; "otherlibs"; subdir]
let toplevel ocamlsrcdir = let toplevel =
Filename.make_path [ocamlsrcdir; "toplevel"] Filename.make_path [srcdir; "toplevel"]
let runtime ocamlsrcdir = let runtime =
Filename.make_path [ocamlsrcdir; "runtime"] Filename.make_path [srcdir; "runtime"]
let tools ocamlsrcdir = let tools =
Filename.make_path [ocamlsrcdir; "tools"] Filename.make_path [srcdir; "tools"]

View File

@ -15,14 +15,14 @@
(* Locations of directories in the OCaml source tree *) (* Locations of directories in the OCaml source tree *)
val srcdir : unit -> string val srcdir : string
val stdlib : string -> string val stdlib : string
val libunix : string -> string val libunix : string
val toplevel : string -> string val toplevel : string
val runtime : string -> string val runtime : string
val tools : string -> string val tools : string

View File

@ -28,62 +28,65 @@ let runtime_variant() =
else if use_runtime="i" then Instrumented else if use_runtime="i" then Instrumented
else Normal else Normal
let ocamlrun ocamlsrcdir = let ocamlrun =
let runtime = match runtime_variant () with let runtime = match runtime_variant () with
| Normal -> "ocamlrun" | Normal -> "ocamlrun"
| Debug -> "ocamlrund" | Debug -> "ocamlrund"
| Instrumented -> "ocamlruni" in | Instrumented -> "ocamlruni" in
let ocamlrunfile = Filename.mkexe runtime in let ocamlrunfile = Filename.mkexe runtime in
Filename.make_path [ocamlsrcdir; "runtime"; ocamlrunfile] Filename.make_path [Ocaml_directories.srcdir; "runtime"; ocamlrunfile]
let ocamlc ocamlsrcdir = let ocamlc =
Filename.make_path [ocamlsrcdir; "ocamlc"] Filename.make_path [Ocaml_directories.srcdir; "ocamlc"]
let ocaml ocamlsrcdir = let ocaml =
Filename.make_path [ocamlsrcdir; "ocaml"] Filename.make_path [Ocaml_directories.srcdir; "ocaml"]
let ocamlc_dot_opt ocamlsrcdir = let ocamlc_dot_opt =
Filename.make_path [ocamlsrcdir; "ocamlc.opt"] Filename.make_path [Ocaml_directories.srcdir; "ocamlc.opt"]
let ocamlopt ocamlsrcdir = let ocamlopt =
Filename.make_path [ocamlsrcdir; "ocamlopt"] Filename.make_path [Ocaml_directories.srcdir; "ocamlopt"]
let ocamlopt_dot_opt ocamlsrcdir = let ocamlopt_dot_opt =
Filename.make_path [ocamlsrcdir; "ocamlopt.opt"] Filename.make_path [Ocaml_directories.srcdir; "ocamlopt.opt"]
let ocamlnat ocamlsrcdir = let ocamlnat =
Filename.make_path [ocamlsrcdir; Filename.mkexe "ocamlnat"] Filename.make_path [Ocaml_directories.srcdir; Filename.mkexe "ocamlnat"]
let cmpbyt ocamlsrcdir = let cmpbyt =
Filename.make_path [ocamlsrcdir; "tools"; "cmpbyt"] Filename.make_path [Ocaml_directories.srcdir; "tools"; "cmpbyt"]
let expect_test ocamlsrcdir = let expect_test =
Filename.make_path Filename.make_path
[ocamlsrcdir; "testsuite"; "tools"; Filename.mkexe "expect_test"] [Ocaml_directories.srcdir; "testsuite"; "tools";
Filename.mkexe "expect_test"]
let ocamllex ocamlsrcdir = let ocamllex =
Filename.make_path [ocamlsrcdir; "lex"; "ocamllex"] Filename.make_path [Ocaml_directories.srcdir; "lex"; "ocamllex"]
let ocamlyacc ocamlsrcdir = let ocamlyacc =
Filename.make_path [ocamlsrcdir; "yacc"; Filename.mkexe "ocamlyacc"] Filename.make_path
[Ocaml_directories.srcdir; "yacc"; Filename.mkexe "ocamlyacc"]
let ocamldoc ocamlsrcdir = let ocamldoc =
Filename.make_path [ocamlsrcdir; "ocamldoc"; "ocamldoc"] Filename.make_path [Ocaml_directories.srcdir; "ocamldoc"; "ocamldoc"]
let ocamldebug ocamlsrcdir = let ocamldebug =
Filename.make_path [ocamlsrcdir; "debugger"; Filename.mkexe "ocamldebug"] Filename.make_path
[Ocaml_directories.srcdir; "debugger"; Filename.mkexe "ocamldebug"]
let ocamlobjinfo ocamlsrcdir = let ocamlobjinfo =
Filename.make_path [ocamlsrcdir; "tools"; "ocamlobjinfo"] Filename.make_path [Ocaml_directories.srcdir; "tools"; "ocamlobjinfo"]
let ocamlmklib ocamlsrcdir = let ocamlmklib =
Filename.make_path [ocamlsrcdir; "tools"; "ocamlmklib"] Filename.make_path [Ocaml_directories.srcdir; "tools"; "ocamlmklib"]
let codegen ocamlsrcdir = let codegen =
Filename.make_path [ocamlsrcdir; "testsuite"; "tools"; "codegen"] Filename.make_path [Ocaml_directories.srcdir; "testsuite"; "tools"; "codegen"]
let asmgen_archmod ocamlsrcdir = let asmgen_archmod =
let objname = let objname =
"asmgen_" ^ Ocamltest_config.arch ^ "." ^ Ocamltest_config.objext "asmgen_" ^ Ocamltest_config.arch ^ "." ^ Ocamltest_config.objext
in in
Filename.make_path [ocamlsrcdir; "testsuite"; "tools"; objname] Filename.make_path [Ocaml_directories.srcdir; "testsuite"; "tools"; objname]

View File

@ -22,32 +22,32 @@ type runtime_variant =
val runtime_variant : unit -> runtime_variant val runtime_variant : unit -> runtime_variant
val ocamlrun : string -> string val ocamlrun : string
val ocamlc : string -> string val ocamlc : string
val ocaml : string -> string val ocaml : string
val ocamlc_dot_opt : string -> string val ocamlc_dot_opt : string
val ocamlopt : string -> string val ocamlopt : string
val ocamlopt_dot_opt : string -> string val ocamlopt_dot_opt : string
val ocamlnat : string -> string val ocamlnat : string
val cmpbyt : string -> string val cmpbyt : string
val expect_test : string -> string val expect_test : string
val ocamllex : string -> string val ocamllex : string
val ocamlyacc : string -> string val ocamlyacc : string
val ocamldoc : string -> string val ocamldoc : string
val ocamldebug : string -> string val ocamldebug : string
val ocamlobjinfo : string -> string val ocamlobjinfo : string
val ocamlmklib : string -> string val ocamlmklib : string
val codegen : string -> string val codegen : string
val asmgen_archmod : string -> string val asmgen_archmod : string

View File

@ -15,15 +15,15 @@
(* Flags used in OCaml commands *) (* Flags used in OCaml commands *)
let stdlib ocamlsrcdir = let stdlib =
let stdlib_path = Ocaml_directories.stdlib ocamlsrcdir in let stdlib_path = Ocaml_directories.stdlib in
"-nostdlib -I " ^ stdlib_path "-nostdlib -I " ^ stdlib_path
let include_toplevel_directory ocamlsrcdir = let include_toplevel_directory =
"-I " ^ (Ocaml_directories.toplevel ocamlsrcdir) "-I " ^ Ocaml_directories.toplevel
let c_includes ocamlsrcdir = let c_includes =
let dir = Ocaml_directories.runtime ocamlsrcdir in let dir = Ocaml_directories.runtime in
"-ccopt -I" ^ dir "-ccopt -I" ^ dir
let runtime_variant_flags () = match Ocaml_files.runtime_variant() with let runtime_variant_flags () = match Ocaml_files.runtime_variant() with
@ -31,9 +31,9 @@ let runtime_variant_flags () = match Ocaml_files.runtime_variant() with
| Ocaml_files.Debug -> " -runtime-variant d" | Ocaml_files.Debug -> " -runtime-variant d"
| Ocaml_files.Instrumented -> " -runtime-variant i" | Ocaml_files.Instrumented -> " -runtime-variant i"
let runtime_flags ocamlsrcdir env backend c_files = let runtime_flags env backend c_files =
let runtime_library_flags = "-I " ^ let runtime_library_flags = "-I " ^
(Ocaml_directories.runtime ocamlsrcdir) in Ocaml_directories.runtime in
let rt_flags = match backend with let rt_flags = match backend with
| Ocaml_backends.Native -> runtime_variant_flags () | Ocaml_backends.Native -> runtime_variant_flags ()
| Ocaml_backends.Bytecode -> | Ocaml_backends.Bytecode ->
@ -46,16 +46,16 @@ let runtime_flags ocamlsrcdir env backend c_files =
in in
if use_runtime = Some false if use_runtime = Some false
then "" then ""
else "-use-runtime " ^ (Ocaml_files.ocamlrun ocamlsrcdir) else "-use-runtime " ^ Ocaml_files.ocamlrun
end end
end in end in
rt_flags ^ " " ^ runtime_library_flags rt_flags ^ " " ^ runtime_library_flags
let toplevel_default_flags = "-noinit -no-version -noprompt" let toplevel_default_flags = "-noinit -no-version -noprompt"
let ocamldebug_default_flags ocamlsrcdir = let ocamldebug_default_flags =
"-no-version -no-prompt -no-time -no-breakpoint-message " ^ "-no-version -no-prompt -no-time -no-breakpoint-message " ^
("-I " ^ (Ocaml_directories.stdlib ocamlsrcdir) ^ " ") ^ ("-I " ^ Ocaml_directories.stdlib ^ " ") ^
("-topdirs-path " ^ (Ocaml_directories.toplevel ocamlsrcdir)) ("-topdirs-path " ^ Ocaml_directories.toplevel)
let ocamlobjinfo_default_flags = "-null-crc" let ocamlobjinfo_default_flags = "-null-crc"

View File

@ -15,17 +15,17 @@
(* Flags used in OCaml commands *) (* Flags used in OCaml commands *)
val stdlib : string -> string val stdlib : string
val include_toplevel_directory : string -> string val include_toplevel_directory : string
val c_includes : string -> string val c_includes : string
val runtime_flags : val runtime_flags :
string -> Environments.t -> Ocaml_backends.t -> bool -> string Environments.t -> Ocaml_backends.t -> bool -> string
val toplevel_default_flags : string val toplevel_default_flags : string
val ocamldebug_default_flags : string -> string val ocamldebug_default_flags : string
val ocamlobjinfo_default_flags : string val ocamlobjinfo_default_flags : string

View File

@ -18,7 +18,7 @@
open Ocamltest_stdlib open Ocamltest_stdlib
class tool class tool
~(name : string -> string) ~(name : string)
~(family : string) ~(family : string)
~(flags : string) ~(flags : string)
~(directory : string) ~(directory : string)

View File

@ -16,7 +16,7 @@
(* Descriptions of the OCaml tools *) (* Descriptions of the OCaml tools *)
class tool : class tool :
name : (string -> string) -> name : string ->
family : string -> family : string ->
flags : string -> flags : string ->
directory : string -> directory : string ->
@ -24,7 +24,7 @@ class tool :
reference_variable : Variables.t -> reference_variable : Variables.t ->
output_variable : Variables.t -> output_variable : Variables.t ->
object object
method name : string -> string method name : string
method family : string method family : string
method flags : string method flags : string
method directory : string method directory : string

View File

@ -18,7 +18,7 @@
open Ocamltest_stdlib open Ocamltest_stdlib
class toplevel class toplevel
~(name : string -> string) ~(name : string)
~(flags : string) ~(flags : string)
~(directory : string) ~(directory : string)
~(exit_status_variable : Variables.t) ~(exit_status_variable : Variables.t)

View File

@ -16,7 +16,7 @@
(* Descriptions of the OCaml toplevels *) (* Descriptions of the OCaml toplevels *)
class toplevel : class toplevel :
name : (string -> string) -> name : string ->
flags : string -> flags : string ->
directory : string -> directory : string ->
exit_status_variable : Variables.t -> exit_status_variable : Variables.t ->