Skip to content

Commit

Permalink
test: Add tests for index generation and aggregation
Browse files Browse the repository at this point in the history
We use a mock binary in tests

Signed-off-by: Ulysse Gérard <[email protected]>
  • Loading branch information
voodoos committed May 7, 2024
1 parent 5ff8b93 commit a8fe370
Show file tree
Hide file tree
Showing 40 changed files with 250 additions and 1 deletion.
3 changes: 2 additions & 1 deletion test/blackbox-tests/test-cases/dune
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@
../utils/melc_stdlib_prefix.exe
../utils/refmt.exe
../utils/webserver_oneshot.exe
../utils/sherlodoc.exe)))
../utils/sherlodoc.exe
../utils/ocaml_index.exe)))

(cram
(applies_to pp-cwd)
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 3.5)
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
$ mkdir bin
$ cp $(which ocaml_index) bin/ocaml-index
$ export PATH=bin:$PATH

Building from the workspace folder creates all three indexes:
$ dune build @ocaml-index
$ find . -name '*.ocaml-index' | sort
./_build/default/sub-project/bin/.main.eobjs/cctx.ocaml-index
./_build/default/sub-project/lib/.subprojectlib.objs/cctx.ocaml-index
./_build/default/sub-project2/lib/.subprojectlib2.objs/cctx.ocaml-index

$ dune clean

Building from one of the sub-projects folder also creates all three indexes:
$ cd sub-project
$ export PATH=../bin:$PATH
$ dune build --workspace=../dune-workspace --root=.. @sub-project/ocaml-index
Entering directory '..'
Leaving directory '..'
$ cd ..

$ find . -name '*.ocaml-index' | sort
./_build/default/sub-project/bin/.main.eobjs/cctx.ocaml-index
./_build/default/sub-project/lib/.subprojectlib.objs/cctx.ocaml-index
./_build/default/sub-project2/lib/.subprojectlib2.objs/cctx.ocaml-index
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(executable
(name main)
(public_name main)
(libraries subprojectlib subprojectlib2))
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
print_int Subprojectlib2.subproject_value;
print_endline "test"
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(lang dune 3.5)

Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(library
(name subprojectlib)
(public_name subprojectlib))
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
let subproject_value = 42
let () = print_int subproject_value
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(lang dune 3.5)

Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(library
(name subprojectlib2)
(public_name subprojectlib2))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let subproject_value = 42
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/ocaml-index/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(cram
(applies_to :whole_subtree)
(deps %{bin:ocaml_index}))
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(executable
(name main)
(libraries otherlib vendored_lib pmodlib))
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(lang dune 3.5)
(implicit_transitive_deps false)

Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 3.5)
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(library
(name imp_lib))
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
let imp_x = 42
type t
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(library
(name otherlib)
(libraries imp_lib))
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
type u = Imp_lib.t

let fromotherlib = 36
let do_something () = ignore fromotherlib

include Imp_lib
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
val do_something : unit -> unit
val fromotherlib : int


include (module type of Imp_lib)
type u = Imp_lib.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
print_int Othermod.(other + Otherlib.fromotherlib + Otherlib.imp_x);;
print_int Vendored_lib.value;;
print_int Pmodlib.x;;
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
let y = 36
let other = 42 + y
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(library
(name pmodlib)
(private_modules pmod ))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let x = 42
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
include Pmod
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
$ mkdir bin
$ cp $(which ocaml_index) bin/ocaml-index
$ export PATH=bin:$PATH

$ dune exec ./main.exe
1564242

The @check alias does not build indexes:
(it might at some point if the process becomes fast-enough)

$ dune build @check

$ find . -name '*.ocaml-index' | sort

The @ocaml-index indexes the entire workspace, including librairies that might
not be directly used and thus usually not built by @check:

$ dune build @ocaml-index

$ find . -name '*.ocaml-index' | sort
./_build/default/.main.eobjs/cctx.ocaml-index
./_build/default/implicit-lib/.imp_lib.objs/cctx.ocaml-index
./_build/default/lib/.otherlib.objs/cctx.ocaml-index
./_build/default/private-module/.pmodlib.objs/cctx.ocaml-index
./_build/default/sub-project/.subprojectlib.objs/cctx.ocaml-index
./_build/default/vendor/otherproject/.private_lib.objs/cctx.ocaml-index
./_build/default/vendor/otherproject/.vendored_lib.objs/cctx.ocaml-index


$ FILE=$PWD/main.ml
$ printf "(4:File%d:%s)" ${#FILE} $FILE | dune ocaml-merlin |
> sed -E "s/[[:digit:]]+:/\?:/g" | tr '(' '\n' | grep ":INDEX?"
?:INDEX?:$TESTCASE_ROOT/_build/default/.main.eobjs/cctx.ocaml-index)
?:INDEX?:$TESTCASE_ROOT/_build/default/implicit-lib/.imp_lib.objs/cctx.ocaml-index)
?:INDEX?:$TESTCASE_ROOT/_build/default/lib/.otherlib.objs/cctx.ocaml-index)
?:INDEX?:$TESTCASE_ROOT/_build/default/private-module/.pmodlib.objs/cctx.ocaml-index)
?:INDEX?:$TESTCASE_ROOT/_build/default/sub-project/.subprojectlib.objs/cctx.ocaml-index)
?:INDEX?:$TESTCASE_ROOT/_build/default/vendor/otherproject/.private_lib.objs/cctx.ocaml-index)
?:INDEX?:$TESTCASE_ROOT/_build/default/vendor/otherproject/.vendored_lib.objs/cctx.ocaml-index)
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(library
(name subprojectlib)
(public_name subprojectlib))
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(lang dune 3.5)

Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
let subproject_value = 42
let () = print_int subproject_value
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(vendored_dirs *)
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
(library
(name vendored_lib)
(public_name vendored_lib)
(modules vendored_lib))

(library
(name private_lib) ; This private lib is not built when vendored
(modules private_lib))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 2.0)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let more = "less"
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let value = 42
5 changes: 5 additions & 0 deletions test/blackbox-tests/utils/dune
Original file line number Diff line number Diff line change
Expand Up @@ -33,3 +33,8 @@
(name sherlodoc)
(modules sherlodoc)
(libraries stdune))

(executable
(modules ocaml_index)
(name ocaml_index)
(libraries cmdliner))
101 changes: 101 additions & 0 deletions test/blackbox-tests/utils/ocaml_index.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,101 @@
(** Mock ocaml-index real CLI *)

open Cmdliner

let touch file =
let chan = open_out file in
close_out chan
;;

module Common = struct
let set_log_level _ _ = ()

let verbose =
let doc = "increase log verbosity" in
Arg.(value & flag & info [ "v"; "verbose" ] ~doc)
;;

let debug =
let doc = "set maximum log verbosity" in
Arg.(value & flag & info [ "debug" ] ~doc)
;;

let with_log = Term.(const set_log_level $ debug $ verbose)

let output_file =
let doc = "name of the generated index" in
Arg.(value & opt string "project.ocaml-index" & info [ "o"; "output-file" ] ~doc)
;;
end

module Aggregate = struct
let from_files _ _ output_file _ _ () = touch output_file

let root =
let doc = "if provided all locations will be appended to that path" in
Arg.(value & opt (some string) None & info [ "root" ] ~doc)
;;

let files =
let doc = "the files to index" in
Arg.(value & pos_all string [] & info [] ~doc)
;;

let build_path =
let doc = "an extra directory to add to the load path" in
Arg.(value & opt_all string [] & info [ "I" ] ~doc)
;;

let store_shapes =
let doc = "aggregate input-indexes shapes and store them in the new index" in
Arg.(value & flag & info [ "store-shapes" ] ~doc)
;;

let term =
Term.(
const from_files
$ store_shapes
$ root
$ Common.output_file
$ build_path
$ files
$ Common.with_log)
;;

let cmd =
let info =
let doc = "builds the index for a single $(i, .cmt) file" in
Cmd.info "aggregate" ~doc
in
Cmd.v info term
;;
end

module Dump = struct
let dump file () = Printf.printf "Dump %s" file

let file =
let doc = "the file to dump" in
Arg.(required & pos 0 (some string) None & info [] ~doc)
;;

let term = Term.(const dump $ file $ Common.with_log)

let cmd =
let info =
let doc = "print the content of an index file to stdout" in
Cmd.info "dump" ~doc
in
Cmd.v info term
;;
end

let subcommands =
let info =
let doc = "An indexer for OCaml's artifacts" in
Cmd.info "ocaml-index" ~doc
in
Cmd.group info ~default:Aggregate.term [ Aggregate.cmd; Dump.cmd ]
;;

let () = exit (Cmd.eval subcommands)

0 comments on commit a8fe370

Please sign in to comment.