Skip to content

Commit

Permalink
refactor: remove [Merlin_ident.t] from compile info (#11079)
Browse files Browse the repository at this point in the history
This field wasn't used sometimes and it's just as easy to generate it
when needed without passing it around.

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Nov 2, 2024
1 parent c91926c commit b0cc44c
Show file tree
Hide file tree
Showing 11 changed files with 8 additions and 40 deletions.
4 changes: 0 additions & 4 deletions src/dune_rules/artifacts_db.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,6 @@ let available_exes ~dir (exes : Executables.t) =
|> Resolve.Memo.read_memo
>>| Preprocess.Per_module.pps
in
let merlin_ident =
Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd exes.names)
in
Lib.DB.resolve_user_written_deps
libs
(`Exe exes.names)
Expand All @@ -30,7 +27,6 @@ let available_exes ~dir (exes : Executables.t) =
~dune_version
~forbidden_libraries:exes.forbidden_libraries
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
~merlin_ident
in
let open Memo.O in
let+ available = Lib.Compile.direct_requires compile_info in
Expand Down
2 changes: 0 additions & 2 deletions src/dune_rules/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -155,15 +155,13 @@ let gen_rules sctx t ~dir ~scope =
in
let dune_version = Scope.project scope |> Dune_project.dune_version in
let names = Nonempty_list.[ t.loc, name ] in
let merlin_ident = Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd names) in
let compile_info =
Lib.DB.resolve_user_written_deps
(Scope.libs scope)
(`Exe names)
(Lib_dep.Direct (loc, Lib_name.of_string "cinaps.runtime") :: t.libraries)
~pps:(Preprocess.Per_module.pps t.preprocess)
~dune_version
~merlin_ident
~allow_overlaps:false
~forbidden_libraries:[]
in
Expand Down
6 changes: 2 additions & 4 deletions src/dune_rules/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -291,7 +291,7 @@ let executables_rules
~preprocess:
(Preprocess.Per_module.without_instrumentation exes.buildable.preprocess)
~dialects:(Dune_project.dialects (Scope.project scope))
~ident:(Lib.Compile.merlin_ident compile_info)
~ident:(Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd exes.names))
~modes:`Exe )
;;

Expand All @@ -305,7 +305,6 @@ let compile_info ~scope (exes : Executables.t) =
~instrumentation_backend:(Lib.DB.instrumentation_backend (Scope.libs scope)))
>>| Preprocess.Per_module.pps
in
let merlin_ident = Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd exes.names) in
Lib.DB.resolve_user_written_deps
(Scope.libs scope)
(`Exe exes.names)
Expand All @@ -314,7 +313,6 @@ let compile_info ~scope (exes : Executables.t) =
~dune_version
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
~forbidden_libraries:exes.forbidden_libraries
~merlin_ident
;;

let rules ~sctx ~dir ~dir_contents ~scope ~expander (exes : Executables.t) =
Expand All @@ -335,6 +333,6 @@ let rules ~sctx ~dir ~dir_contents ~scope ~expander (exes : Executables.t) =
let requires_link = Lib.Compile.requires_link compile_info in
Bootstrap_info.gen_rules sctx exes ~dir ~requires_link
in
let merlin_ident = Lib.Compile.merlin_ident compile_info in
let merlin_ident = Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd exes.names) in
Buildable_rules.with_lib_deps (Super_context.context sctx) merlin_ident ~dir ~f
;;
4 changes: 0 additions & 4 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -383,9 +383,6 @@ end = struct
|> Resolve.Memo.read_memo
>>| Preprocess.Per_module.pps
in
let merlin_ident =
Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd exes.names)
in
Lib.DB.resolve_user_written_deps
(Scope.libs scope)
~forbidden_libraries:[]
Expand All @@ -394,7 +391,6 @@ end = struct
~pps
~dune_version
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
~merlin_ident
in
let+ requires = Lib.Compile.direct_requires compile_info in
Resolve.is_ok requires)
Expand Down
6 changes: 0 additions & 6 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1826,7 +1826,6 @@ module Compile = struct
; pps : t list Resolve.Memo.t
; resolved_selects : Resolved_select.t list Resolve.Memo.t
; sub_systems : Sub_system0.Instance.t Memo.Lazy.t Sub_system_name.Map.t
; merlin_ident : Merlin_ident.t
}

let for_lib ~allow_overlaps db (t : lib) =
Expand All @@ -1850,21 +1849,18 @@ module Compile = struct
db
~forbidden_libraries:Map.empty)
in
let merlin_ident = Merlin_ident.for_lib t.name in
{ direct_requires = requires
; requires_link
; resolved_selects = Memo.return t.resolved_selects
; pps = Memo.return t.pps
; sub_systems = t.sub_systems
; merlin_ident
}
;;

let direct_requires t = t.direct_requires
let requires_link t = t.requires_link
let resolved_selects t = t.resolved_selects
let pps t = t.pps
let merlin_ident t = t.merlin_ident

let sub_systems t =
Sub_system_name.Map.values t.sub_systems
Expand Down Expand Up @@ -2050,7 +2046,6 @@ module DB = struct
deps
~pps
~dune_version
~merlin_ident
=
let resolved =
Memo.lazy_ (fun () ->
Expand Down Expand Up @@ -2120,7 +2115,6 @@ module DB = struct
; pps
; resolved_selects = resolved_selects |> Memo.map ~f:Resolve.return
; sub_systems = Sub_system_name.Map.empty
; merlin_ident
}
;;

Expand Down
3 changes: 0 additions & 3 deletions src/dune_rules/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -77,8 +77,6 @@ module Compile : sig
(** Transitive closure of all used ppx rewriters *)
val pps : t -> lib list Resolve.Memo.t

val merlin_ident : t -> Merlin_ident.t

(** Sub-systems used in this compilation context *)
val sub_systems : t -> sub_system list Memo.t
end
Expand Down Expand Up @@ -153,7 +151,6 @@ module DB : sig
-> Lib_dep.t list
-> pps:(Loc.t * Lib_name.t) list
-> dune_version:Dune_lang.Syntax.Version.t
-> merlin_ident:Merlin_ident.t
-> Compile.t

val resolve_pps : t -> (Loc.t * Lib_name.t) list -> lib list Resolve.Memo.t
Expand Down
4 changes: 2 additions & 2 deletions src/dune_rules/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -637,7 +637,7 @@ let library_rules
~libname:(Some (snd lib.name))
~obj_dir
~dialects:(Dune_project.dialects (Scope.project scope))
~ident:(Lib.Compile.merlin_ident compile_info)
~ident:(Merlin_ident.for_lib (Library.best_name lib))
~modes:(`Lib (Lib_info.modes lib_info)) )
;;

Expand Down Expand Up @@ -675,6 +675,6 @@ let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope =
~ctx_dir:dir
in
let* () = Buildable_rules.gen_select_rules sctx compile_info ~dir in
let merlin_ident = Lib.Compile.merlin_ident compile_info in
let merlin_ident = Merlin_ident.for_lib (Library.best_name lib) in
Buildable_rules.with_lib_deps (Super_context.context sctx) merlin_ident ~dir ~f
;;
5 changes: 1 addition & 4 deletions src/dune_rules/mdx.ml
Original file line number Diff line number Diff line change
Expand Up @@ -453,17 +453,14 @@ let mdx_prog_gen t ~sctx ~dir ~scope ~mdx_prog =
let lib name = Lib_dep.Direct (loc, Lib_name.of_string name) in
let* cctx =
let compile_info =
let names = Nonempty_list.[ t.loc, name ] in
let merlin_ident = Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd names) in
Lib.DB.resolve_user_written_deps
(Scope.libs scope)
(`Exe names)
(`Exe Nonempty_list.[ t.loc, name ])
~allow_overlaps:false
~forbidden_libraries:[]
(lib "mdx.test" :: lib "mdx.top" :: t.libraries)
~pps:[]
~dune_version
~merlin_ident
in
let requires_compile = Lib.Compile.direct_requires compile_info
and requires_link = Lib.Compile.requires_link compile_info in
Expand Down
8 changes: 3 additions & 5 deletions src/dune_rules/melange/melange_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -136,13 +136,12 @@ let compile_info ~scope (mel : Melange_stanzas.Emit.t) =
~instrumentation_backend:(Lib.DB.instrumentation_backend (Scope.libs scope)))
>>| Preprocess.Per_module.pps
in
let merlin_ident = Merlin_ident.for_melange ~target:mel.target in
let libraries =
match mel.emit_stdlib with
| false -> mel.libraries
| true ->
let builtin_melange_dep = Lib_dep.Direct (mel.loc, Lib_name.of_string "melange") in
builtin_melange_dep :: mel.libraries
| false -> mel.libraries
in
Lib.DB.resolve_user_written_deps
(Scope.libs scope)
Expand All @@ -152,7 +151,6 @@ let compile_info ~scope (mel : Melange_stanzas.Emit.t) =
libraries
~pps
~dune_version
~merlin_ident
;;

let js_targets_of_modules modules ~module_systems ~output =
Expand Down Expand Up @@ -271,6 +269,7 @@ let setup_emit_cmj_rules
=
let* compile_info = compile_info ~scope mel in
let ctx = Super_context.context sctx in
let merlin_ident = Merlin_ident.for_melange ~target:mel.target in
let f () =
let* modules, obj_dir =
Dir_contents.ocaml dir_contents
Expand Down Expand Up @@ -363,12 +362,11 @@ let setup_emit_cmj_rules
~libname:None
~preprocess:(Preprocess.Per_module.without_instrumentation mel.preprocess)
~obj_dir
~ident:(Lib.Compile.merlin_ident compile_info)
~ident:merlin_ident
~dialects:(Dune_project.dialects (Scope.project scope))
~modes:`Melange_emit )
in
let* () = Buildable_rules.gen_select_rules sctx compile_info ~dir in
let merlin_ident = Lib.Compile.merlin_ident compile_info in
Buildable_rules.with_lib_deps ctx merlin_ident ~dir ~f
;;

Expand Down
2 changes: 0 additions & 2 deletions src/dune_rules/toplevel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -204,7 +204,6 @@ module Stanza = struct
Lib_name.parse_string_exn (source.loc, "compiler-libs.toplevel")
in
let names = Nonempty_list.[ source.loc, source.name ] in
let merlin_ident = Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd names) in
Lib.DB.resolve_user_written_deps
(Scope.libs scope)
(`Exe names)
Expand All @@ -214,7 +213,6 @@ module Stanza = struct
~pps
~dune_version
~allow_overlaps:false
~merlin_ident
in
let requires_compile = Lib.Compile.direct_requires compile_info in
let requires_link = Lib.Compile.requires_link compile_info in
Expand Down
4 changes: 0 additions & 4 deletions src/dune_rules/utop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -79,9 +79,6 @@ let add_stanza db ~dir (acc, pps) stanza =
(Lib.DB.instrumentation_backend (Scope.libs scope)))
>>| Preprocess.Per_module.pps
in
let merlin_ident =
Merlin_ident.for_exes ~names:(Nonempty_list.map ~f:snd exes.names)
in
Lib.DB.resolve_user_written_deps
db
(`Exe exes.names)
Expand All @@ -90,7 +87,6 @@ let add_stanza db ~dir (acc, pps) stanza =
~dune_version
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
~forbidden_libraries:exes.forbidden_libraries
~merlin_ident
in
let+ available = Lib.Compile.direct_requires compile_info in
Resolve.peek available
Expand Down

0 comments on commit b0cc44c

Please sign in to comment.