Skip to content

Commit

Permalink
remove Kind_db
Browse files Browse the repository at this point in the history
Signed-off-by: Alpha DIALLO <[email protected]>
  • Loading branch information
moyodiallo committed Oct 10, 2022
1 parent 2ca2962 commit db3b493
Show file tree
Hide file tree
Showing 3 changed files with 3 additions and 21 deletions.
12 changes: 1 addition & 11 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -369,20 +369,12 @@ module Status = struct
| Found t -> variant "Found" [ to_dyn t ]
end

module Kind_db = struct
type t =
| Installed_libs
| Public_libs
| Project_libs
end

type db =
{ parent : db option
; resolve : Lib_name.t -> resolve_result Memo.t
; all : Lib_name.t list Memo.Lazy.t
; lib_config : Lib_config.t
; instrument_with : Lib_name.t list
; kind : Kind_db.t
}

and resolve_result =
Expand Down Expand Up @@ -1740,13 +1732,12 @@ module DB = struct

type t = db

let create ~parent ~resolve ~all ~lib_config ~kind () =
let create ~parent ~resolve ~all ~lib_config () =
{ parent
; resolve
; all = Memo.lazy_ all
; lib_config
; instrument_with = lib_config.Lib_config.instrument_with
; kind
}

let parent t = t.parent
Expand All @@ -1768,7 +1759,6 @@ module DB = struct
~all:(fun () ->
let open Memo.O in
Findlib.all_packages findlib >>| List.map ~f:Dune_package.Entry.name)
~kind:Kind_db.Installed_libs

let installed (context : Context.t) =
let open Memo.O in
Expand Down
8 changes: 0 additions & 8 deletions src/dune_rules/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -41,13 +41,6 @@ val hash : t -> int

val project : t -> Dune_project.t option

module Kind_db : sig
type t =
| Installed_libs
| Public_libs
| Project_libs
end

(** Operations on list of libraries *)
module L : sig
val top_closure :
Expand Down Expand Up @@ -133,7 +126,6 @@ module DB : sig
-> resolve:(Lib_name.t -> Resolve_result.t Memo.t)
-> all:(unit -> Lib_name.t list Memo.t)
-> lib_config:Lib_config.t
-> kind:Kind_db.t
-> unit
-> t

Expand Down
4 changes: 2 additions & 2 deletions src/dune_rules/scope.ml
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,7 @@ module DB = struct
| Some (Redirect lib) -> Lib.DB.Resolve_result.redirect None lib
| Some (Found lib) -> Lib.DB.Resolve_result.found lib))
~all:(fun () -> Lib_name.Map.keys map |> Memo.return)
~lib_config ~kind:Lib.Kind_db.Project_libs
~lib_config

type redirect_to =
| Project of Dune_project.t
Expand Down Expand Up @@ -187,7 +187,7 @@ module DB = struct
let resolve lib = Memo.return (resolve t public_libs lib) in
Lib.DB.create ~parent:(Some installed_libs) ~resolve
~all:(fun () -> Lib_name.Map.keys public_libs |> Memo.return)
~lib_config () ~kind:Lib.Kind_db.Public_libs
~lib_config ()

module Path_source_map_traversals = Memo.Make_map_traversals (Path.Source.Map)

Expand Down

0 comments on commit db3b493

Please sign in to comment.