ocamltest: machinery for ocamldoc tests

* a new test ocamldoc
* three new modifiers: html, latex and man for each ocamldoc backend
* new variables:
   * plugins
   * skip_header_lines, skip_header_bytes
   * ocamldoc_{backend,exit_status,flags,output,reference}
* make it possible to skip lines in the result file in text mode
* check_output reads skip_header_{lines,bytes} when comparing
output and reference files
master
octachron 2018-03-05 11:09:57 +01:00
parent 4583eb1a05
commit ece7e44d1a
24 changed files with 352 additions and 17 deletions

View File

@ -175,6 +175,13 @@ ocamltest.opt$(EXE): $(native_modules)
%.$(O): %.c
$(CC) $(CFLAGS) $(CPPFLAGS) $(BYTECCCOMPOPTS) -c $<
ifeq "$(WITH_OCAMLDOC)" "ocamldoc"
WITH_OCAMLDOC := true
else
WITH_OCAMLDOC := false
endif
ocamltest_config.ml: ocamltest_config.ml.in
sed \
-e 's|@@AFL_INSTRUMENT@@|$(AFL_INSTRUMENT)|' \
@ -190,6 +197,7 @@ ocamltest_config.ml: ocamltest_config.ml.in
-e 's|@@SPACETIME@@|$(WITH_SPACETIME)|' \
-e 's|@@FORCE_SAFE_STRING@@|$(FORCE_SAFE_STRING)|' \
-e 's|@@FLAT_FLOAT_ARRAY@@|$(FLAT_FLOAT_ARRAY)|' \
-e 's|@@OCAMLDOC@@|$(WITH_OCAMLDOC)|' \
$< > $@
.PHONY: clean

View File

@ -243,7 +243,13 @@ let run_hook hook_name log input_env =
then (Result.skip_with_reason reason, hookenv)
else (Result.fail_with_reason reason, hookenv)
let check_output kind_of_output output_variable reference_variable log env =
let check_output kind_of_output output_variable reference_variable log
env =
let to_int = function None -> 0 | Some s -> int_of_string s in
let skip_lines =
to_int (Environments.lookup Builtin_variables.skip_header_lines env) in
let skip_bytes =
to_int (Environments.lookup Builtin_variables.skip_header_bytes env) in
let reference_filename = Environments.safe_lookup reference_variable env in
let output_filename = Environments.safe_lookup output_variable env in
Printf.fprintf log "Comparing %s output %s to reference %s\n%!"
@ -254,7 +260,9 @@ let check_output kind_of_output output_variable reference_variable log env =
Filecompare.reference_filename = reference_filename;
Filecompare.output_filename = output_filename
} in
match Filecompare.check_file files with
let tool =
Filecompare.(make_cmp_tool ~ignore:{lines=skip_lines;bytes=skip_bytes}) in
match Filecompare.check_file ~tool files with
| Filecompare.Same -> (Result.pass, env)
| Filecompare.Different ->
let diff = Filecompare.diff files in

View File

@ -53,6 +53,16 @@ let promote = make ("promote",
let reference = make ("reference",
"Path of file to which program output should be compared")
let skip_header_lines =
make ( "skip_header_lines",
"The number of lines to skip when comparing program output \
with the reference file")
let skip_header_bytes =
make ( "skip_header_bytes",
"The number of bytes to skip when comparing program output \
with the reference file")
let script = make ("script",
"External script to run")
@ -93,6 +103,8 @@ let _ = List.iter register_variable
output;
program; program2;
reference;
skip_header_lines;
skip_header_bytes;
script;
stdin;
stdout;

View File

@ -36,6 +36,9 @@ val promote : Variables.t
val reference : Variables.t
val skip_header_lines : Variables.t
val skip_header_bytes : Variables.t
val script : Variables.t
val stdin : Variables.t

View File

@ -23,21 +23,22 @@ type result =
| Unexpected_output
| Error of string * int
type ignore = {bytes: int; lines: int}
type tool =
| External of {
tool_name : string;
tool_flags : string;
result_of_exitcode : string -> int -> result
}
| Internal of int
| Internal of ignore
let cmp_result_of_exitcode commandline = function
| 0 -> Same
| 1 -> Different
| exit_code -> (Error (commandline, exit_code))
let make_cmp_tool bytes_to_ignore =
Internal bytes_to_ignore
let make_cmp_tool ~ignore =
Internal ignore
let make_comparison_tool ?(result_of_exitcode = cmp_result_of_exitcode)
name flags =
@ -48,7 +49,7 @@ let make_comparison_tool ?(result_of_exitcode = cmp_result_of_exitcode)
result_of_exitcode
}
let default_comparison_tool = make_cmp_tool 0
let default_comparison_tool = make_cmp_tool ~ignore:{bytes=0;lines=0}
type filetype = Binary | Text
@ -58,14 +59,20 @@ type files = {
output_filename : string;
}
let read_text_file fn =
let read_text_file lines_to_drop fn =
let ic = open_in_bin fn in
let drop_cr s =
let l = String.length s in
if l > 0 && s.[l - 1] = '\r' then String.sub s 0 (l - 1)
else raise Exit
in
let rec loop acc =
let rec drop k =
if k = 0 then
loop []
else
let stop = try ignore (input_line ic); false with End_of_file -> true in
if stop then [] else drop (k-1)
and loop acc =
match input_line ic with
| s -> loop (s :: acc)
| exception End_of_file ->
@ -73,10 +80,10 @@ let read_text_file fn =
try List.rev_map drop_cr acc
with Exit -> List.rev acc
in
loop []
drop lines_to_drop
let compare_text_files file1 file2 =
if read_text_file file1 = read_text_file file2 then
let compare_text_files dropped_lines file1 file2 =
if read_text_file 0 file1 = read_text_file dropped_lines file2 then
Same
else
Different
@ -138,13 +145,14 @@ let compare_files ?(tool = default_comparison_tool) files =
~stdout_fname:dev_null ~stderr_fname:dev_null commandline in
let status = Run_command.run settings in
result_of_exitcode commandline status
| Internal bytes_to_ignore ->
| Internal ignore ->
match files.filetype with
| Text ->
(* bytes_to_ignore is silently ignored for text files *)
compare_text_files files.reference_filename files.output_filename
compare_text_files ignore.lines
files.reference_filename files.output_filename
| Binary ->
compare_binary_files bytes_to_ignore
compare_binary_files ignore.bytes
files.reference_filename files.output_filename
let check_file ?(tool = default_comparison_tool) files =

View File

@ -23,7 +23,8 @@ type result =
type tool
val make_cmp_tool : int -> tool
type ignore = {bytes: int; lines: int}
val make_cmp_tool : ignore:ignore -> tool
val make_comparison_tool :
?result_of_exitcode:(string -> int -> result) -> string -> string -> tool

View File

@ -28,6 +28,9 @@ let get_backend_value_from_env env bytecode_var native_var =
let modules env =
Actions_helpers.words_of_variable env Ocaml_variables.modules
let plugins env =
Actions_helpers.words_of_variable env Ocaml_variables.plugins
let directories env =
Actions_helpers.words_of_variable env Ocaml_variables.directories
@ -141,6 +144,7 @@ let prepare_module ocamlsrcdir output_variable log env input =
generate_lexer ocamlsrcdir output_variable input log env
| Grammar ->
generate_parser ocamlsrcdir output_variable input log env
| Text -> assert false
let get_program_file backend env =
let testfile = Actions_helpers.testfile env in
@ -258,7 +262,7 @@ let find_source_modules log env =
let source_directory = Actions_helpers.test_source_directory env in
let specified_modules =
List.map Ocaml_filetypes.filetype
((modules env) @ [(Actions_helpers.testfile env)]) in
((plugins env) @ (modules env) @ [(Actions_helpers.testfile env)]) in
print_module_names log "Specified" specified_modules;
let source_modules =
List.concatmap
@ -369,6 +373,7 @@ let setup_ocamlnat_build_env =
"setup-ocamlnat-build-env"
Ocaml_toplevels.ocamlnat
let compile (compiler : Ocaml_compilers.compiler) log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
match Environments.lookup_nonempty Ocaml_variables.module_ env with
@ -492,7 +497,7 @@ let really_compare_programs backend comparison_tool log env =
(Sys.os_type="Win32" || Sys.os_type="Cygwin")
then
let bytes_to_ignore = 512 (* comparison_start_address program *) in
Filecompare.make_cmp_tool bytes_to_ignore
Filecompare.(make_cmp_tool ~ignore:{bytes=bytes_to_ignore; lines=0})
else comparison_tool in
match Filecompare.compare_files ~tool:comparison_tool files with
| Filecompare.Same -> (Result.pass, env)
@ -752,6 +757,159 @@ let no_afl_instrument = Actions.make
"AFL instrumentation disabled"
"AFL instrumentation enabled")
let ocamldoc = Ocaml_tools.ocamldoc
let ocamldoc_output_file env prefix =
let backend =
Environments.safe_lookup Ocaml_variables.ocamldoc_backend env in
let suffix = match backend with
| "latex" -> ".tex"
| "html" -> ".html"
| "man" -> ".3o"
| _ -> ".result" in
prefix ^ suffix
let check_ocamldoc_output = make_check_tool_output
"check-ocamldoc-output" ocamldoc
let ocamldoc_flags env =
Environments.safe_lookup Ocaml_variables.ocamldoc_flags env
let compiled_doc_name input = input ^ ".odoc"
(* The compiler used for compiling both cmi file
and plugins *)
let compiler_for_ocamldoc ocamlsrcdir =
let compiler = Ocaml_compilers.ocamlc_byte in
compile_modules ocamlsrcdir compiler (compiler#name ocamlsrcdir)
compiler#output_variable
(* Within ocamldoc tests,
modules="a.ml b.ml" is interpreted as a list of
secondaries documentation modules that need to be
compiled into cmi files and odoc file (serialized ocamldoc information)
before the main documentation is generated *)
let compile_ocamldoc ocamlsrcdir (basename,filetype as module_) log env =
let expected_exit_status =
Ocaml_tools.expected_exit_status env (ocamldoc :> Ocaml_tools.tool) in
let what = Printf.sprintf "Compiling documentation for module %s" basename in
Printf.fprintf log "%s\n%!" what;
let filename =
Ocaml_filetypes.make_filename (basename, filetype) in
let (r,env) = compiler_for_ocamldoc ocamlsrcdir [module_] log env in
if not (Result.is_pass r) then (r,env) else
let commandline =
(* currently, we are ignoring the global ocamldoc_flags, since we
don't have per-module flags *)
[
Ocaml_commands.ocamlrun_ocamldoc ocamlsrcdir;
Ocaml_flags.stdlib ocamlsrcdir;
"-dump " ^ compiled_doc_name basename;
filename;
] in
let exit_status =
Actions_helpers.run_cmd
~environment:(Environments.to_system_env env)
~stdout_variable:ocamldoc#output_variable
~stderr_variable:ocamldoc#output_variable
~append:true
log env commandline in
if exit_status=expected_exit_status
then (Result.pass, env)
else begin
let reason =
(Actions_helpers.mkreason
what (String.concat " " commandline) exit_status) in
(Result.fail_with_reason reason, env)
end
let rec ocamldoc_compile_all ocamlsrcdir log env = function
| [] -> (Result.pass, env)
| a :: q ->
let (r,env) = compile_ocamldoc ocamlsrcdir a log env in
if Result.is_pass r then
ocamldoc_compile_all ocamlsrcdir log env q
else
(r,env)
let setup_ocamldoc_build_env =
Actions.make "setup_ocamldoc_build_env" @@ fun log env ->
let (r,env) = setup_tool_build_env ocamldoc log env in
if not (Result.is_pass r) then (r,env) else
let source_directory = Actions_helpers.test_source_directory env in
let root_file = Filename.chop_extension (Actions_helpers.testfile env) in
let reference_prefix = Filename.make_path [source_directory; root_file] in
let output = ocamldoc_output_file env root_file in
let reference= reference_prefix ^ ocamldoc#reference_filename_suffix env in
let backend = Environments.safe_lookup Ocaml_variables.ocamldoc_backend env in
let env =
Environments.apply_modifiers env Ocaml_modifiers.(str @ unix)
|> Environments.add Builtin_variables.reference reference
|> Environments.add Builtin_variables.output output in
let env =
if backend = "man" then Environments.add_if_undefined
Builtin_variables.skip_header_lines "1" env
else env in
Result.pass, env
let ocamldoc_plugin name = name ^ ".cmo"
let ocamldoc_backend_flag env =
let backend = Environments.safe_lookup Ocaml_variables.ocamldoc_backend env in
if backend = "" then "" else "-" ^ backend
let ocamldoc_o_flag env =
let output = Environments.safe_lookup Builtin_variables.output env in
match Environments.safe_lookup Ocaml_variables.ocamldoc_backend env with
| "html" | "manual" -> "index"
| _ -> output
let run_ocamldoc =
Actions.make "ocamldoc" @@ fun log env ->
(* modules corresponds to secondaries modules of which the
documentation and cmi files need to be build before the main
module documentation *)
let modules = List.map Ocaml_filetypes.filetype @@ modules env in
(* plugins are used for custom documentation generators *)
let plugins = List.map Ocaml_filetypes.filetype @@ plugins env in
let ocamlsrcdir = Ocaml_directories.srcdir () in
let (r,env) = compiler_for_ocamldoc ocamlsrcdir plugins log env in
if not (Result.is_pass r) then r, env else
let (r,env) = ocamldoc_compile_all ocamlsrcdir log env modules in
if not (Result.is_pass r) then r, env else
let input_file = Actions_helpers.testfile env in
Printf.fprintf log "Generating documentation for %s\n%!" input_file;
let load_all =
List.map (fun name -> "-load " ^ compiled_doc_name (fst name))
@@ (* sort module in alphabetical order *)
List.sort Pervasives.compare modules in
let with_plugins =
List.map (fun name -> "-g " ^ ocamldoc_plugin (fst name)) plugins in
let commandline =
[
Ocaml_commands.ocamlrun_ocamldoc ocamlsrcdir;
ocamldoc_backend_flag env;
Ocaml_flags.stdlib ocamlsrcdir;
ocamldoc_flags env]
@ load_all @ with_plugins @
[ input_file;
"-o"; ocamldoc_o_flag env
] in
let exit_status =
Actions_helpers.run_cmd ~environment:(Environments.to_system_env env)
~stdout_variable:ocamldoc#output_variable
~stderr_variable:ocamldoc#output_variable
~append:true
log env commandline in
if exit_status=0 then
(Result.pass, env)
else begin
let reason = (Actions_helpers.mkreason
"ocamldoc" (String.concat " " commandline) exit_status) in
(Result.fail_with_reason reason, env)
end
let _ =
Environments.register_initializer "find_source_modules" find_source_modules;
Environments.register_initializer "config_variables" config_variables;
@ -788,4 +946,7 @@ let _ =
native_compiler;
afl_instrument;
no_afl_instrument;
setup_ocamldoc_build_env;
run_ocamldoc;
check_ocamldoc_output
]

View File

@ -37,6 +37,10 @@ val setup_ocamlnat_build_env : Actions.t
val ocamlnat : Actions.t
val check_ocamlnat_output : Actions.t
val setup_ocamldoc_build_env : Actions.t
val run_ocamldoc: Actions.t
val check_ocamldoc_output: Actions.t
val flat_float_array : Actions.t
val no_flat_float_array : Actions.t

View File

@ -28,3 +28,6 @@ let ocamlrun_expect_test ocamlsrcdir =
ocamlrun ocamlsrcdir Ocaml_files.expect_test
let ocamlrun_ocamllex ocamlsrcdir = ocamlrun ocamlsrcdir Ocaml_files.ocamllex
let ocamlrun_ocamldoc ocamlsrcdir =
ocamlrun ocamlsrcdir Ocaml_files.ocamldoc

View File

@ -24,3 +24,5 @@ val ocamlrun_ocaml : string -> string
val ocamlrun_expect_test : string -> string
val ocamlrun_ocamllex : string -> string
val ocamlrun_ocamldoc : string -> string

View File

@ -66,3 +66,7 @@ let ocamllex ocamlsrcdir =
let ocamlyacc ocamlsrcdir =
Filename.make_path [ocamlsrcdir; "yacc"; Filename.mkexe "ocamlyacc"]
let ocamldoc ocamlsrcdir =
Filename.make_path
[ocamlsrcdir; "ocamldoc"; "ocamldoc"]

View File

@ -43,3 +43,5 @@ val expect_test : string -> string
val ocamllex : string -> string
val ocamlyacc : string -> string
val ocamldoc : string -> string

View File

@ -26,6 +26,7 @@ type t =
| Grammar
| Binary_interface
| Backend_specific of Ocaml_backends.t * backend_specific
| Text (* used by ocamldoc for text only documentation *)
let string_of_backend_specific = function
| Object -> "object"
@ -43,6 +44,7 @@ let string_of_filetype = function
| Backend_specific (backend, filetype) ->
((Ocaml_backends.string_of_backend backend) ^ " " ^
(string_of_backend_specific filetype))
| Text -> "text"
let extension_of_filetype = function
| Implementation -> "ml"
@ -61,6 +63,7 @@ let extension_of_filetype = function
| (Ocaml_backends.Bytecode, Library) -> "cma"
| (Ocaml_backends.Bytecode, Program) -> "byte"
end
| Text -> "txt"
let filetype_of_extension = function
| "ml" -> Implementation
@ -76,6 +79,7 @@ let filetype_of_extension = function
| "cmo" -> Backend_specific (Ocaml_backends.Bytecode, Object)
| "cma" -> Backend_specific (Ocaml_backends.Bytecode, Library)
| "byte" -> Backend_specific (Ocaml_backends.Bytecode, Program)
| "txt" -> Text
| _ -> raise Not_found
let split_filename name =

View File

@ -26,6 +26,7 @@ type t =
| Grammar
| Binary_interface
| Backend_specific of Ocaml_backends.t * backend_specific
| Text (** text-only documentation file *)
val string_of_filetype : t -> string

View File

@ -25,6 +25,31 @@ let principal =
Add (Ocaml_variables.compiler_reference_suffix, ".principal");
]
let latex =
[
Add (Ocaml_variables.ocamldoc_backend, "latex");
Append (Ocaml_variables.ocamldoc_flags, "-latex-type-prefix=TYP ");
Append (Ocaml_variables.ocamldoc_flags, "-latex-module-prefix= ");
Append (Ocaml_variables.ocamldoc_flags, "-latex-value-prefix= ");
Append (Ocaml_variables.ocamldoc_flags, "-latex-module-type-prefix= ");
Append (Ocaml_variables.ocamldoc_flags, "-latextitle=1,subsection* ");
Append (Ocaml_variables.ocamldoc_flags, "-latextitle=2,subsubsection* ");
Append (Ocaml_variables.ocamldoc_flags, "-latextitle=6,subsection* ");
Append (Ocaml_variables.ocamldoc_flags, "-latextitle=7,subsubsection* ");
]
let html =
[
Add (Ocaml_variables.ocamldoc_backend, "html");
Append (Ocaml_variables.ocamldoc_flags, "-colorize-code ");
]
let man =
[
Add (Ocaml_variables.ocamldoc_backend, "man");
]
let wrap str = (" " ^ str ^ " ")
let make_library_modifier library directory =
@ -82,4 +107,7 @@ let _ =
register_modifiers "str" str;
register_modifiers "ocamlcommon" ocamlcommon;
register_modifiers "systhreads" systhreads;
register_modifiers "latex" latex;
register_modifiers "html" html;
register_modifiers "man" man;
()

View File

@ -22,3 +22,7 @@ val testing : Environments.modifiers
val unix : Environments.modifiers
val str : Environments.modifiers
val latex: Environments.modifiers
val man: Environments.modifiers
val html: Environments.modifiers

View File

@ -88,6 +88,23 @@ let expect =
]
}
let ocamldoc =
{
test_name = "ocamldoc";
test_run_by_default = false;
test_actions =
if Ocamltest_config.ocamldoc then
[
shared_libraries;
setup_ocamldoc_build_env;
run_ocamldoc;
check_program_output;
check_ocamldoc_output
]
else
[ skip ]
}
let _ =
List.iter register
[
@ -95,4 +112,5 @@ let _ =
native;
toplevel;
expect;
ocamldoc;
]

View File

@ -22,3 +22,5 @@ val native : Tests.t
val toplevel : Tests.t
val expect : Tests.t
val ocamldoc : Tests.t

View File

@ -49,3 +49,23 @@ end
let expected_exit_status env tool =
Actions_helpers.exit_status_of_variable env tool#exit_status_variable
let ocamldoc =
object inherit
tool
~name:Ocaml_files.ocamldoc
~family:"doc"
~flags:""
~directory:"ocamldoc"
~exit_status_variable:Ocaml_variables.ocamldoc_exit_status
~reference_variable:Ocaml_variables.ocamldoc_reference
~output_variable:Ocaml_variables.ocamldoc_output
method ! reference_filename_suffix env =
let backend =
Environments.safe_lookup Ocaml_variables.ocamldoc_backend env in
if backend = "" then
".reference"
else "." ^ backend ^ ".reference"
end

View File

@ -36,3 +36,5 @@ object
end
val expected_exit_status : Environments.t -> tool -> int
val ocamldoc: tool

View File

@ -137,6 +137,27 @@ let ocamlsrcdir = make ("ocamlsrcdir",
let os_type = make ("os_type",
"The OS we are running on")
let ocamldoc_flags = Variables.make ("ocamldoc_flags",
"ocamldoc flags")
let ocamldoc_backend = Variables.make ("ocamldoc_backend",
"ocamldoc backend (html, latex, man, ... )")
let ocamldoc_exit_status =
Variables.make ( "ocamldoc_exit_status", "expected ocamldoc exit status")
let ocamldoc_output =
Variables.make ( "ocamldoc_output", "Where to log ocamldoc output")
let ocamldoc_reference =
Variables.make ( "ocamldoc_reference",
"Where to find expected ocamldoc output")
let plugins =
Variables.make ( "plugins", "plugins for ocamlc,ocamlopt or ocamldoc" )
let _ = List.iter register_variable
[
all_modules;
@ -167,4 +188,10 @@ let _ = List.iter register_variable
os_type;
ocamllex_flags;
ocamlyacc_flags;
ocamldoc_flags;
ocamldoc_backend;
ocamldoc_output;
ocamldoc_reference;
ocamldoc_exit_status;
plugins
]

View File

@ -74,3 +74,11 @@ val ocamlrunparam : Variables.t
val ocamlsrcdir : Variables.t
val os_type : Variables.t
val ocamldoc_flags : Variables.t
val ocamldoc_backend : Variables.t
val ocamldoc_exit_status : Variables.t
val ocamldoc_output : Variables.t
val ocamldoc_reference : Variables.t
val plugins: Variables.t

View File

@ -39,3 +39,5 @@ let ocamlopt_default_flags = "@@OCAMLOPTDEFAULTFLAGS@@"
let safe_string = @@FORCE_SAFE_STRING@@
let flat_float_array = @@FLAT_FLOAT_ARRAY@@
let ocamldoc = @@OCAMLDOC@@

View File

@ -53,3 +53,6 @@ val safe_string : bool
val flat_float_array : bool
(* Whether the compiler was configured with -flat-float-array *)
val ocamldoc: bool
(** Whether ocamldoc has been enabled at configure time *)