Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 3 additions & 0 deletions doc/changes/added/12623.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
- Introduce an `unused-libs` alias to detect unused libraries. To disable the
check for a particular library, add it to the `allowed_unused_libraries` field.
(#12623, fixes #650, @rgrinberg)
1 change: 1 addition & 0 deletions doc/reference/aliases.rst
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,7 @@ Some aliases are defined and managed by Dune itself:
aliases/runtest
aliases/fmt
aliases/lint
aliases/unused-libs

.. grid-item::

Expand Down
5 changes: 5 additions & 0 deletions doc/reference/aliases/unused-libs.rst
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
@unused-libs
============

This alias is used to detect unused entries in the libraries field of
executables and stanzas.
1 change: 1 addition & 0 deletions src/dune_rules/alias0.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ let install = standard "install"
let pkg_install = Alias.Name.of_string "pkg-install"
let ocaml_index = standard "ocaml-index"
let runtest = standard "runtest"
let unused_libs = standard "unused-libs"
let all = standard "all"
let default = standard "default"
let empty = standard "empty"
1 change: 1 addition & 0 deletions src/dune_rules/alias0.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ val ocaml_index : Name.t
val install : Name.t
val pkg_install : Name.t
val runtest : Name.t
val unused_libs : Name.t
val empty : Name.t
val all : Name.t
val default : Name.t
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/artifacts_db.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ let available_exes ~dir (exes : Executables.t) =
libs
(`Exe exes.names)
exes.buildable.libraries
~allow_unused_libraries:exes.buildable.allow_unused_libraries
~pps
~dune_version
~forbidden_libraries:exes.forbidden_libraries
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -140,6 +140,7 @@ let gen_rules sctx t ~dir ~scope =
(Scope.libs scope)
(`Exe names)
(Lib_dep.Direct (loc, Lib_name.of_string "cinaps.runtime") :: t.libraries)
~allow_unused_libraries:[]
~pps:(Preprocess.Per_module.pps t.preprocess)
~dune_version
~allow_overlaps:false
Expand Down
5 changes: 4 additions & 1 deletion src/dune_rules/dep_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,10 @@ let ooi_deps
let ctx = Super_context.context sctx in
Context.ocaml ctx
in
Ocamlobjinfo.rules ocaml ~sandbox ~dir ~unit
Ocamlobjinfo.rules ocaml ~sandbox ~dir ~units:[ unit ]
|> Action_builder.map ~f:(function
| [ x ] -> x
| [] | _ :: _ -> assert false)
in
let add_rule = Super_context.add_rule sctx ~dir in
let read =
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/dune_package.ml
Original file line number Diff line number Diff line change
Expand Up @@ -289,6 +289,7 @@ module Lib = struct
~plugins
~archives
~ppx_runtime_deps
~allow_unused_libraries:[]
~foreign_archives
~native_archives:(Files native_archives)
~foreign_dll_files
Expand Down
15 changes: 15 additions & 0 deletions src/dune_rules/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -208,6 +208,20 @@ let executables_rules
in
let lib_config = ocaml.lib_config in
let* requires_compile = Compilation_context.requires_compile cctx in
let* () =
let toolchain = Compilation_context.ocaml cctx in
let direct_requires = Lib.Compile.direct_requires compile_info in
let allow_unused_libraries = Lib.Compile.allow_unused_libraries compile_info in
Unused_libs_rules.gen_rules
sctx
toolchain
exes.buildable.loc
~obj_dir
~modules
~dir
~direct_requires
~allow_unused_libraries
in
let* () =
let* dep_graphs =
(* Building an archive for foreign stubs, we link the corresponding object
Expand Down Expand Up @@ -328,6 +342,7 @@ let compile_info ~scope (exes : Executables.t) =
(Scope.libs scope)
(`Exe exes.names)
exes.buildable.libraries
~allow_unused_libraries:exes.buildable.allow_unused_libraries
~pps
~dune_version
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -260,6 +260,7 @@ let to_dune_library (t : Findlib.Package.t) ~dir_contents ~ext_lib ~external_loc
~plugins
~archives
~ppx_runtime_deps
~allow_unused_libraries:[]
~foreign_archives
~native_archives:(Files native_archives)
~foreign_dll_files:[]
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -427,6 +427,7 @@ end = struct
~forbidden_libraries:[]
(`Exe exes.names)
exes.buildable.libraries
~allow_unused_libraries:exes.buildable.allow_unused_libraries
~pps
~dune_version
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
Expand Down
13 changes: 13 additions & 0 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -362,6 +362,7 @@ module T = struct
; pps : t list Resolve.t
; resolved_selects : Resolved_select.t list Resolve.t
; parameters : t list Resolve.t
; allow_unused_libraries : t list Resolve.t
; implements : t Resolve.t option
; project : Dune_project.t option
; (* these fields cannot be forced until the library is instantiated *)
Expand Down Expand Up @@ -1106,6 +1107,9 @@ end = struct
let* ppx_runtime_deps =
Lib_info.ppx_runtime_deps info |> resolve_simple_deps db ~private_deps
in
let* allow_unused_libraries =
Lib_info.allow_unused_libraries info |> resolve_simple_deps db ~private_deps
in
let src_dir = Lib_info.src_dir info in
let map_error x =
Resolve.push_stack_frame x ~human_readable_description:(fun () ->
Expand Down Expand Up @@ -1138,6 +1142,7 @@ end = struct
; re_exports
; implements
; parameters
; allow_unused_libraries
; default_implementation
; project
; sub_systems =
Expand Down Expand Up @@ -1906,6 +1911,7 @@ module Compile = struct
; requires_link : t list Resolve.t Memo.Lazy.t
; pps : t list Resolve.Memo.t
; resolved_selects : Resolved_select.t list Resolve.Memo.t
; allow_unused_libraries : t list Resolve.Memo.t
; sub_systems : Sub_system0.Instance.t Memo.Lazy.t Sub_system_name.Map.t
}

Expand Down Expand Up @@ -1934,6 +1940,7 @@ module Compile = struct
; requires_link
; resolved_selects = Memo.return t.resolved_selects
; pps = Memo.return t.pps
; allow_unused_libraries = Memo.return t.allow_unused_libraries
; sub_systems = t.sub_systems
}
;;
Expand All @@ -1942,6 +1949,7 @@ module Compile = struct
let requires_link t = t.requires_link
let resolved_selects t = t.resolved_selects
let pps t = t.pps
let allow_unused_libraries t = t.allow_unused_libraries

let sub_systems t =
Sub_system_name.Map.values t.sub_systems
Expand Down Expand Up @@ -2134,6 +2142,7 @@ module DB = struct
~allow_overlaps
~forbidden_libraries
deps
~allow_unused_libraries
~pps
~dune_version
=
Expand Down Expand Up @@ -2201,10 +2210,14 @@ module DB = struct
let+ resolved = Memo.Lazy.force resolved in
resolved.selects
in
let allow_unused_libraries =
Resolve_names.resolve_simple_deps t ~private_deps:Allow_all allow_unused_libraries
in
{ Compile.direct_requires
; requires_link
; pps
; resolved_selects = resolved_selects |> Memo.map ~f:Resolve.return
; allow_unused_libraries
; sub_systems = Sub_system_name.Map.empty
}
;;
Expand Down
4 changes: 4 additions & 0 deletions src/dune_rules/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -77,6 +77,9 @@ module Compile : sig
(** Transitive closure of all used ppx rewriters *)
val pps : t -> lib list Resolve.Memo.t

(** Libraries allowed to be unused *)
val allow_unused_libraries : t -> lib list Resolve.Memo.t

(** Sub-systems used in this compilation context *)
val sub_systems : t -> sub_system list Memo.t
end
Expand Down Expand Up @@ -155,6 +158,7 @@ module DB : sig
-> allow_overlaps:bool
-> forbidden_libraries:(Loc.t * Lib_name.t) list
-> Lib_dep.t list
-> allow_unused_libraries:(Loc.t * Lib_name.t) list
-> pps:(Loc.t * Lib_name.t) list
-> dune_version:Dune_lang.Syntax.Version.t
-> Compile.t
Expand Down
5 changes: 5 additions & 0 deletions src/dune_rules/lib_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -320,6 +320,7 @@ type 'path t =
; requires : Lib_dep.t list
; parameters : (Loc.t * Lib_name.t) list
; ppx_runtime_deps : (Loc.t * Lib_name.t) list
; allow_unused_libraries : (Loc.t * Lib_name.t) list
; preprocess : Preprocess.With_instrumentation.t Preprocess.Per_module.t
; enabled : Enabled_status.t Memo.t
; virtual_deps : (Loc.t * Lib_name.t) list
Expand Down Expand Up @@ -349,6 +350,7 @@ let requires t = t.requires
let parameters t = t.parameters
let preprocess t = t.preprocess
let ppx_runtime_deps t = t.ppx_runtime_deps
let allow_unused_libraries t = t.allow_unused_libraries
let sub_systems t = t.sub_systems
let modes t = t.modes
let modules t = t.modules
Expand Down Expand Up @@ -412,6 +414,7 @@ let create
~plugins
~archives
~ppx_runtime_deps
~allow_unused_libraries
~foreign_archives
~native_archives
~foreign_dll_files
Expand Down Expand Up @@ -451,6 +454,7 @@ let create
; plugins
; archives
; ppx_runtime_deps
; allow_unused_libraries
; foreign_archives
; native_archives
; foreign_dll_files
Expand Down Expand Up @@ -548,6 +552,7 @@ let to_dyn
; plugins
; archives
; ppx_runtime_deps
; allow_unused_libraries = _
; foreign_archives
; native_archives
; foreign_dll_files
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/lib_info.mli
Original file line number Diff line number Diff line change
Expand Up @@ -151,6 +151,7 @@ val implements : _ t -> (Loc.t * Lib_name.t) option
val requires : _ t -> Lib_dep.t list
val parameters : _ t -> (Loc.t * Lib_name.t) list
val ppx_runtime_deps : _ t -> (Loc.t * Lib_name.t) list
val allow_unused_libraries : _ t -> (Loc.t * Lib_name.t) list
val preprocess : _ t -> Preprocess.With_instrumentation.t Preprocess.Per_module.t
val sub_systems : _ t -> Sub_system_info.t Sub_system_name.Map.t
val enabled : _ t -> Enabled_status.t Memo.t
Expand Down Expand Up @@ -211,6 +212,7 @@ val create
-> plugins:'a list Mode.Dict.t
-> archives:'a list Mode.Dict.t
-> ppx_runtime_deps:(Loc.t * Lib_name.t) list
-> allow_unused_libraries:(Loc.t * Lib_name.t) list
-> foreign_archives:'a Mode.Map.Multi.t
-> native_archives:'a native_archives
-> foreign_dll_files:'a list
Expand Down
13 changes: 13 additions & 0 deletions src/dune_rules/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -621,6 +621,19 @@ let library_rules
in
Sub_system.gen_rules
{ super_context = sctx; dir; stanza = lib; scope; source_modules; compile_info }
and+ () =
let toolchain = Compilation_context.ocaml cctx in
let direct_requires = Lib.Compile.direct_requires compile_info in
let allow_unused_libraries = Lib.Compile.allow_unused_libraries compile_info in
Unused_libs_rules.gen_rules
sctx
toolchain
lib.buildable.loc
~obj_dir
~modules
~dir
~direct_requires
~allow_unused_libraries
and+ merlin =
let+ requires_hidden = Compilation_context.requires_hidden cctx
and+ parameters = Compilation_context.parameters cctx in
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/mdx.ml
Original file line number Diff line number Diff line change
Expand Up @@ -457,6 +457,7 @@ let mdx_prog_gen t ~sctx ~dir ~scope ~mdx_prog =
~allow_overlaps:false
~forbidden_libraries:[]
(lib "mdx.test" :: lib "mdx.top" :: t.libraries)
~allow_unused_libraries:[]
~pps:[]
~dune_version
in
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/melange/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -181,6 +181,7 @@ let compile_info ~scope (mel : Melange_stanzas.Emit.t) =
~allow_overlaps:mel.allow_overlapping_dependencies
~forbidden_libraries:[]
libraries
~allow_unused_libraries:[]
~pps
~dune_version
;;
Expand Down
17 changes: 14 additions & 3 deletions src/dune_rules/ocamlobjinfo.mli
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,19 @@ val rules
: Ocaml_toolchain.t
-> dir:Path.Build.t
-> sandbox:Sandbox_config.t option
-> unit:Path.t
-> t Action_builder.t
-> units:Path.t list
-> t list Action_builder.t

(** Run ocamlobjinfo on an archive to extract module names defined in it *)
val archive_rules
: Ocaml_toolchain.t
-> dir:Path.Build.t
-> sandbox:Sandbox_config.t option
-> archive:Path.t
-> Module_name.Unique.Set.t Action_builder.t

(** For testing only *)
val parse : string -> t
val parse : string -> t list

(** Parse archive output to extract module names defined in the archive *)
val parse_archive : string -> Module_name.Unique.Set.t
Loading
Loading