@@ -343,103 +343,85 @@ let run_program env test_program =
343343 exit 1
344344 end
345345
346- let compile_with_options ?(unix_only =false ) ?( full_only = false ) ~ full env
346+ let compile_with_options ?(unix_only =false ) env
347347 compiler ~native options test_program description =
348- if unix_only && Sys. win32 || full_only && not full then
348+ if unix_only && Sys. win32 then
349349 None
350350 else
351- let cont test_program =
352- if full_only then
353- fun () ->
354- run_program env test_program;
355- Sys. remove test_program;
356- None
357- else
358- fun () ->
359- run_program env test_program;
360- Some test_program
351+ let cont test_program () =
352+ run_program env test_program;
353+ Some test_program
361354 in
362355 compile_with_options
363356 env compiler ~native options test_program description cont
364357
365- let compile_obj ?(unix_only =false ) ?( full_only = false ) ~ full env standard_library
358+ let compile_obj ?(unix_only =false ) env standard_library
366359 compiler ~native runtime test_program description =
367- if unix_only && Sys. win32 || full_only && not full then
360+ if unix_only && Sys. win32 then
368361 None
369362 else
370- let cont test_program =
371- if full_only then
372- fun () ->
373- run_program env test_program;
374- Sys. remove test_program;
375- None
376- else
377- fun () ->
378- run_program env test_program;
379- Some test_program
363+ let cont test_program () =
364+ run_program env test_program;
365+ Some test_program
380366 in
381367 compile_obj env standard_library compiler ~native
382368 runtime test_program description cont
383369
384- let test_standard_library_location ~ full env bindir libdir ocamlc ocamlopt =
370+ let test_standard_library_location env bindir libdir ocamlc ocamlopt =
385371 Printf. printf " \n Testing compilation mechanisms for %s\n %!" bindir;
386372 let ocamlc_where = compiler_where env ocamlc in
387373 let ocamlopt_where = compiler_where env ocamlopt in
388374 Printf. printf " ocamlc -where: %s\n ocamlopt -where: %s\n %!"
389375 ocamlc_where ocamlopt_where;
390376 let unix_only = true in
391- let full_only = true in
392377 let programs = List. filter_map Fun. id [
393- compile_with_options ~full_only ~full env ocamlc ~native: false
378+ compile_with_options env ocamlc ~native: false
394379 [] " test_bytecode"
395380 " Bytecode (with tender)" ;
396- compile_with_options ~full env ocamlc ~native: false
381+ compile_with_options env ocamlc ~native: false
397382 [" -custom" ] " test_custom_static"
398383 " Bytecode (-custom static runtime)" ;
399- compile_with_options ~unix_only ~full env ocamlc ~native: false
384+ compile_with_options ~unix_only env ocamlc ~native: false
400385 [" -custom" ; " -runtime-variant" ; " _shared" ] " test_custom_shared"
401386 " Bytecode (-custom shared runtime)" ;
402- compile_obj ~full env libdir ocamlc ~native: false
387+ compile_obj env libdir ocamlc ~native: false
403388 " -lcamlrun" " test_output_obj_static"
404389 " Bytecode (-output-obj static runtime)" ;
405- compile_obj ~unix_only ~full env libdir ocamlc ~native: false
390+ compile_obj ~unix_only env libdir ocamlc ~native: false
406391 " -lcamlrun_shared" " test_output_obj_shared"
407392 " Bytecode (-output-obj shared runtime)" ;
408- compile_with_options ~full env ocamlc ~native: false
393+ compile_with_options env ocamlc ~native: false
409394 [" -output-complete-exe" ] " test_output_complete_exe_static"
410395 " Bytecode (-output-complete-exe static runtime)" ;
411- compile_with_options ~unix_only ~full env ocamlc ~native: false
396+ compile_with_options ~unix_only env ocamlc ~native: false
412397 [" -output-complete-exe" ; " -runtime-variant" ; " _shared" ]
413398 " test_output_complete_exe_shared"
414399 " Bytecode (-output-complete-exe shared runtime)" ;
415- compile_with_options ~full env ocamlopt ~native: true
400+ compile_with_options env ocamlopt ~native: true
416401 [] " test_native_static"
417402 " Native (static runtime)" ;
418- compile_obj ~full env libdir ocamlopt ~native: true
403+ compile_obj env libdir ocamlopt ~native: true
419404 " -lasmrun" " test_native_output_obj_static"
420405 " Native (-output-obj static runtime)" ;
421- compile_obj ~unix_only ~full env libdir ocamlopt ~native: true
406+ compile_obj ~unix_only env libdir ocamlopt ~native: true
422407 " -lasmrun_shared" " test_native_output_obj_shared"
423408 " Native (-output-obj shared runtime)" ;
424409 ] in
425410 Printf. printf " Running programs\n %!" ;
426411 List. filter_map (fun f -> f () ) programs
427412
428- let run_tests ~ full env bindir libdir libraries =
413+ let run_tests env bindir libdir libraries =
429414 let libraries = sort_libraries libraries in
430415 let ocaml = exe (Filename. concat bindir " ocaml" ) in
431416 let ocamlnat = exe (Filename. concat bindir " ocamlnat" ) in
432417 let ocamlc = exe (Filename. concat bindir " ocamlc" ) in
433418 let ocamlopt = exe (Filename. concat bindir " ocamlopt" ) in
434- if full then
435- load_libraries_in_toplevel env ocaml " cma" libraries;
419+ load_libraries_in_toplevel env ocaml " cma" libraries;
436420 load_libraries_in_toplevel env ocamlnat " cmxa" libraries;
437- if full then
438- load_libraries_in_prog env libdir ocamlc ~native: false libraries;
421+ load_libraries_in_prog env libdir ocamlc ~native: false libraries;
439422 load_libraries_in_prog env libdir ocamlopt ~native: true libraries;
440- if full then
441- test_bytecode_binaries env bindir;
442- test_standard_library_location ~full env bindir libdir ocamlc ocamlopt
423+ test_bytecode_binaries env bindir;
424+ test_standard_library_location env bindir libdir ocamlc ocamlopt
443425
444426let rec split_dir acc dir =
445427 let dirname = Filename. dirname dir in
@@ -475,7 +457,7 @@ let () =
475457 let bindir = Sys. argv.(1 ) in
476458 let libdir = Sys. argv.(2 ) in
477459 let env = make_env bindir libdir in
478- let programs = run_tests ~full: true env bindir libdir libraries in
460+ let programs = run_tests env bindir libdir libraries in
479461 if Sys. argv.(3 ) = " yes" then
480462 let prefix, bindir_suffix, libdir_suffix =
481463 split_to_prefix [] (split_dir [] bindir) (split_dir [] libdir) in
@@ -494,4 +476,4 @@ let () =
494476 List. iter (run_program env) programs;
495477 List. iter Sys. remove programs;
496478 Compmisc. init_path ~standard_library: libdir () ;
497- List. iter Sys. remove (run_tests ~full: false env bindir libdir libraries)
479+ List. iter Sys. remove (run_tests env bindir libdir libraries)
0 commit comments