Skip to content

Commit 848e13e

Browse files
committed
feature: unused-libs alias
Introduce an alias to detect unused libraries in libraries and executable stanzas. This stanza relies on information extracted using ocamlobjinfo to detect which modules are actually used Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 5bfb106 commit 848e13e

File tree

18 files changed

+627
-149
lines changed

18 files changed

+627
-149
lines changed

doc/changes/added/12623.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
- Introduce an `unused-libs` stanza to detect unused libraries (#12623, fixes
2+
#650, @rgrinberg)

doc/reference/aliases.rst

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -82,6 +82,7 @@ Some aliases are defined and managed by Dune itself:
8282
aliases/runtest
8383
aliases/fmt
8484
aliases/lint
85+
aliases/unused-libs
8586

8687
.. grid-item::
8788

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
@unused-libs
2+
============
3+
4+
This alias is used to detect unused entries in the libraries field of
5+
executables and stanzas.

src/dune_rules/alias0.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ let install = standard "install"
2626
let pkg_install = Alias.Name.of_string "pkg-install"
2727
let ocaml_index = standard "ocaml-index"
2828
let runtest = standard "runtest"
29+
let unused_libs = standard "unused-libs"
2930
let all = standard "all"
3031
let default = standard "default"
3132
let empty = standard "empty"

src/dune_rules/alias0.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ val ocaml_index : Name.t
1515
val install : Name.t
1616
val pkg_install : Name.t
1717
val runtest : Name.t
18+
val unused_libs : Name.t
1819
val empty : Name.t
1920
val all : Name.t
2021
val default : Name.t

src/dune_rules/dep_rules.ml

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,10 @@ let ooi_deps
3636
let ctx = Super_context.context sctx in
3737
Context.ocaml ctx
3838
in
39-
Ocamlobjinfo.rules ocaml ~sandbox ~dir ~unit
39+
Ocamlobjinfo.rules ocaml ~sandbox ~dir ~units:[ unit ]
40+
|> Action_builder.map ~f:(function
41+
| [ x ] -> x
42+
| [] | _ :: _ -> assert false)
4043
in
4144
let add_rule = Super_context.add_rule sctx ~dir in
4245
let read =

src/dune_rules/exe_rules.ml

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -208,6 +208,18 @@ let executables_rules
208208
in
209209
let lib_config = ocaml.lib_config in
210210
let* requires_compile = Compilation_context.requires_compile cctx in
211+
let* () =
212+
let toolchain = Compilation_context.ocaml cctx in
213+
let direct_requires = Lib.Compile.direct_requires compile_info in
214+
Unused_libs_rules.gen_rules
215+
sctx
216+
toolchain
217+
exes.buildable.loc
218+
~obj_dir
219+
~modules
220+
~dir
221+
~direct_requires
222+
in
211223
let* () =
212224
let* dep_graphs =
213225
(* Building an archive for foreign stubs, we link the corresponding object

src/dune_rules/lib_rules.ml

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -621,6 +621,17 @@ let library_rules
621621
in
622622
Sub_system.gen_rules
623623
{ super_context = sctx; dir; stanza = lib; scope; source_modules; compile_info }
624+
and+ () =
625+
let toolchain = Compilation_context.ocaml cctx in
626+
let direct_requires = Lib.Compile.direct_requires compile_info in
627+
Unused_libs_rules.gen_rules
628+
sctx
629+
toolchain
630+
lib.buildable.loc
631+
~obj_dir
632+
~modules
633+
~dir
634+
~direct_requires
624635
and+ merlin =
625636
let+ requires_hidden = Compilation_context.requires_hidden cctx
626637
and+ parameters = Compilation_context.parameters cctx in

src/dune_rules/ocamlobjinfo.mli

Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,19 @@ val rules
1010
: Ocaml_toolchain.t
1111
-> dir:Path.Build.t
1212
-> sandbox:Sandbox_config.t option
13-
-> unit:Path.t
14-
-> t Action_builder.t
13+
-> units:Path.t list
14+
-> t list Action_builder.t
15+
16+
(** Run ocamlobjinfo on an archive to extract module names defined in it *)
17+
val archive_rules
18+
: Ocaml_toolchain.t
19+
-> dir:Path.Build.t
20+
-> sandbox:Sandbox_config.t option
21+
-> archive:Path.t
22+
-> Module_name.Unique.Set.t Action_builder.t
1523

1624
(** For testing only *)
17-
val parse : string -> t
25+
val parse : string -> t list
26+
27+
(** Parse archive output to extract module names defined in the archive *)
28+
val parse_archive : string -> Module_name.Unique.Set.t

src/dune_rules/ocamlobjinfo.mll

Lines changed: 48 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -22,23 +22,34 @@ let ws = [' ' '\t']+
2222
let hash = ['0'-'9' 'a'-'z' '-']+
2323
let name = ['A'-'Z'] ['A'-'Z' 'a'-'z' '0'-'9' '_']*
2424

25-
rule ocamlobjinfo acc = parse
26-
| "Interfaces imported:" newline { intfs acc lexbuf }
27-
| "Implementations imported:" newline { impls acc lexbuf }
28-
| _ { ocamlobjinfo acc lexbuf }
25+
rule ocamlobjinfo acc_units acc = parse
26+
| "Interfaces imported:" newline { intfs acc_units acc lexbuf }
27+
| "Implementations imported:" newline { impls acc_units acc lexbuf }
28+
| _ { ocamlobjinfo acc_units acc lexbuf }
29+
| eof { acc :: acc_units }
30+
and intfs acc_units acc = parse
31+
| ws hash ws (name as name) newline { intfs acc_units (add_intf acc name) lexbuf }
32+
| "Implementations imported:" newline { impls acc_units acc lexbuf }
33+
| "File " [^ '\n']+ newline { ocamlobjinfo (acc :: acc_units) empty lexbuf }
34+
| _ | eof { acc :: acc_units }
35+
and impls acc_units acc = parse
36+
| ws hash ws (name as name) newline { impls acc_units (add_impl acc name) lexbuf }
37+
| "File " [^ '\n']+ newline { ocamlobjinfo (acc :: acc_units) empty lexbuf }
38+
| _ | eof { acc :: acc_units }
39+
40+
and archive acc = parse
41+
| "Unit name:" ws (name as name) { archive (Module_name.Unique.Set.add acc (Module_name.Unique.of_string name)) lexbuf }
42+
| _ { archive acc lexbuf }
2943
| eof { acc }
30-
and intfs acc = parse
31-
| ws hash ws (name as name) newline { intfs (add_intf acc name) lexbuf }
32-
| "Implementations imported:" newline { impls acc lexbuf }
33-
| _ | eof { acc }
34-
and impls acc = parse
35-
| ws hash ws (name as name) newline { impls (add_impl acc name) lexbuf }
36-
| _ | eof { acc }
3744

3845
{
39-
let parse s = ocamlobjinfo empty (Lexing.from_string s)
46+
let parse s = Lexing.from_string s |> ocamlobjinfo [] empty |> List.rev
47+
48+
let parse_archive s =
49+
Lexing.from_string s
50+
|> archive Module_name.Unique.Set.empty
4051

41-
let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
52+
let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~units =
4253
let no_approx =
4354
if Ocaml.Version.ooi_supports_no_approx ocaml.version then
4455
[Command.Args.A "-no-approx"]
@@ -52,7 +63,9 @@ let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
5263
[]
5364
in
5465
let observing_facts =
55-
Dep.Facts.singleton (Dep.file unit) (Dep.Fact.nothing)
66+
List.map units ~f:(fun unit ->
67+
Dep.Facts.singleton (Dep.file unit) (Dep.Fact.nothing))
68+
|> Dep.Facts.union_all
5669
in
5770
let open Action_builder.O in
5871
let* action =
@@ -61,7 +74,7 @@ let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
6174
(List.concat
6275
[ no_approx
6376
; no_code
64-
; [ Dep unit ]
77+
; [ Deps units ]
6578
])
6679
in
6780
(Dune_engine.Build_system.execute_action_stdout
@@ -73,4 +86,24 @@ let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
7386
}
7487
|> Action_builder.of_memo)
7588
>>| parse
89+
90+
let archive_rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~archive =
91+
let observing_facts =
92+
Dep.Facts.singleton (Dep.file archive) (Dep.Fact.nothing)
93+
in
94+
let open Action_builder.O in
95+
let* action =
96+
Command.run' ?sandbox
97+
~dir:(Path.build dir) ocaml.ocamlobjinfo
98+
[ Dep archive ]
99+
in
100+
(Dune_engine.Build_system.execute_action_stdout
101+
~observing_facts
102+
{ Rule.Anonymous_action.action
103+
; loc = Loc.none
104+
; dir
105+
; alias = None
106+
}
107+
|> Action_builder.of_memo)
108+
>>| parse_archive
76109
}

0 commit comments

Comments
 (0)