Skip to content

Commit

Permalink
Additional cleaning up of opinionated renamings
Browse files Browse the repository at this point in the history
Signed-off-by: Ambre Austen Suhamy <[email protected]>
  • Loading branch information
ElectreAAS committed Jan 10, 2025
1 parent 78bf86f commit d1f860c
Show file tree
Hide file tree
Showing 14 changed files with 27 additions and 49 deletions.
4 changes: 2 additions & 2 deletions bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -223,15 +223,15 @@ let get_path_and_build_if_necessary sctx ~no_rebuild ~dir ~prog =
| Ok p -> build_prog ~no_rebuild ~prog p)
| Relative_to_current_dir ->
let path = Path.relative_to_source_in_build_or_external ~dir prog in
Build_system.path_exists path
Build_system.file_exists path
>>= (function
| true -> Memo.return (Some path)
| false ->
if not (Filename.check_suffix prog ".exe")
then Memo.return None
else (
let path = Path.extend_basename path ~suffix:".exe" in
Build_system.path_exists path
Build_system.file_exists path
>>| function
| true -> Some path
| false -> None))
Expand Down
2 changes: 1 addition & 1 deletion bin/ocaml/utop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ let term =
let utop_target = Filename.concat dir Utop.utop_exe in
Path.build (Path.Build.relative (Context.build_dir context) utop_target)
in
Build_system.path_exists utop_target
Build_system.file_exists utop_target
>>= function
| false ->
User_error.raise
Expand Down
10 changes: 3 additions & 7 deletions src/dune_cache/local.ml
Original file line number Diff line number Diff line change
Expand Up @@ -85,9 +85,7 @@ module Artifacts = struct
=
let entries =
Targets.Produced.foldi artifacts ~init:[] ~f:(fun target digest entries ->
let entry : Metadata_entry.t =
{ file_path = Path.Local.to_string target; digest }
in
let entry : Metadata_entry.t = { path = Path.Local.to_string target; digest } in
entry :: entries)
|> List.rev
in
Expand Down Expand Up @@ -302,10 +300,8 @@ module Artifacts = struct
let restore ~mode ~rule_digest ~target_dir =
Restore_result.bind (list ~rule_digest) ~f:(fun (entries : Metadata_entry.t list) ->
let artifacts =
Path.Local.Map.of_list_map_exn
entries
~f:(fun { Metadata_entry.file_path; digest } ->
Path.Local.of_string file_path, digest)
Path.Local.Map.of_list_map_exn entries ~f:(fun { Metadata_entry.path; digest } ->
Path.Local.of_string path, digest)
|> Targets.Produced.of_files target_dir
in
try
Expand Down
12 changes: 4 additions & 8 deletions src/dune_cache/shared.ml
Original file line number Diff line number Diff line change
Expand Up @@ -121,13 +121,10 @@ struct
]
in
let update_cached_digests ~targets_and_digests =
Targets.Produced.iteri
targets_and_digests
~f:(fun path digest ->
Cached_digest.set (Path.Build.append_local targets_and_digests.root path) digest)
~d:(fun _path -> ())
Targets.Produced.iter_files targets_and_digests ~f:(fun path digest ->
Cached_digest.set (Path.Build.append_local targets_and_digests.root path) digest)
in
let map_res =
match
Targets.Produced.map_with_errors
~f:(fun target ->
(* All of this monad boilerplate seems unnecessary since we don't care about errors... *)
Expand All @@ -140,8 +137,7 @@ struct
| None -> Error ())
~all_errors:false
produced_targets
in
match map_res with
with
| Error _ -> Fiber.return None
| Ok targets ->
let compute_digest ~executable path =
Expand Down
14 changes: 6 additions & 8 deletions src/dune_cache_storage/dune_cache_storage.ml
Original file line number Diff line number Diff line change
Expand Up @@ -215,23 +215,21 @@ end
module Artifacts = struct
module Metadata_entry = struct
type t =
{ file_path : string
(* This digest is always present in case [file_path] points to a file, and absent when it's a directory. *)
{ path : string (** Can have more than one component for directory targets *)
; digest : Digest.t option
(** This digest is always present in case [file_path] points to a file, and absent when it's a directory. *)
}

let equal x y =
String.equal x.file_path y.file_path && Option.equal Digest.equal x.digest y.digest
String.equal x.path y.path && Option.equal Digest.equal x.digest y.digest
;;

let digest_to_sexp = function
| None -> Sexp.Atom "<dir>"
| Some digest -> Sexp.Atom (Digest.to_string digest)
;;

let to_sexp { file_path; digest } =
Sexp.List [ Atom file_path; digest_to_sexp digest ]
;;
let to_sexp { path; digest } = Sexp.List [ Atom path; digest_to_sexp digest ]

let digest_of_sexp = function
| "<dir>" -> Ok None
Expand All @@ -245,9 +243,9 @@ module Artifacts = struct
;;

let of_sexp = function
| Sexp.List [ Atom file_path; Atom digest ] ->
| Sexp.List [ Atom path; Atom digest ] ->
(match digest_of_sexp digest with
| Ok digest -> Ok { file_path; digest }
| Ok digest -> Ok { path; digest }
| Error e -> Error e)
| _ -> Error (Failure "Cannot parse cache metadata entry")
;;
Expand Down
2 changes: 1 addition & 1 deletion src/dune_cache_storage/dune_cache_storage.mli
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ end
module Artifacts : sig
module Metadata_entry : sig
type t =
{ file_path : string (** Can have more than one component for directory targets *)
{ path : string (** Can have more than one component for directory targets *)
; digest : Digest.t option
(** This digest is always present in case [file_path] points to a file, and absent when it's a directory. *)
}
Expand Down
3 changes: 2 additions & 1 deletion src/dune_engine/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1049,7 +1049,7 @@ include Exported
when executing the very same [Action_builder.t] with [Action_builder.exec] --
the results of both [Action_builder.static_deps] and [Action_builder.exec]
are cached. *)
let path_exists fn =
let file_exists fn =
Load_rules.load_dir ~dir:(Path.parent_exn fn)
>>= function
| Source { filenames } | External { filenames } ->
Expand All @@ -1059,6 +1059,7 @@ let path_exists fn =
(Path.Build.Map.mem rules_here.by_file_targets (Path.as_in_build_dir_exn fn))
| Build_under_directory_target { directory_target_ancestor } ->
let+ path_map = build_dir (Path.build directory_target_ancestor) in
(* Note that in the case of directory targets, we also check if directories exist. *)
Targets.Produced.mem_any path_map (Path.as_in_build_dir_exn fn)
;;

Expand Down
6 changes: 3 additions & 3 deletions src/dune_engine/build_system.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,8 @@ val with_file : Path.t -> f:(Path.t -> 'a) -> 'a Memo.t
(** Build a file and read its contents. Like [with_file ~f:Io.read_file] but memoized. *)
val read_file : Path.t -> string Memo.t

(** Return [true] if a file exists or is buildable *)
val path_exists : Path.t -> bool Memo.t
(** Return [true] if a file or directory exists or is buildable. *)
val file_exists : Path.t -> bool Memo.t

(** Build a set of dependencies and return learned facts about them. *)
val build_deps : Dep.Set.t -> Dep.Facts.t Memo.t
Expand All @@ -29,7 +29,7 @@ val record_deps : Dep.Set.t -> unit Action_builder.t
This function does the minimum amount of work necessary to produce the result, and may
do some building (e.g., if [glob] points inside a directory target). To force building
the files you need, use [build]. *)
the files you need, use [build_file]. *)
val eval_pred : File_selector.t -> Filename_set.t Memo.t

(** Same as [eval_pred] with [Predicate.true_] as predicate. *)
Expand Down
2 changes: 1 addition & 1 deletion src/dune_engine/rule_cache.ml
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,7 @@ module Workspace_local = struct
(match
Targets.Produced.map_with_errors
~all_errors:false
~f:(fun target -> Cached_digest.build_file ~allow_dirs:true target)
~f:(Cached_digest.build_file ~allow_dirs:true)
targets
with
| Ok produced_targets -> Dune_cache.Hit_or_miss.Hit produced_targets
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/action_builder.ml
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@ let progn ts =
;;

let if_file_exists p ~then_ ~else_ =
let* exists = of_memo (Build_system.path_exists p) in
let* exists = of_memo (Build_system.file_exists p) in
if exists then then_ else else_
;;

Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -668,7 +668,7 @@ let expand_pform_macro
(Without
(let open Memo.O in
let path = relative ~source dir s in
let+ available = Build_system.path_exists path in
let+ available = Build_system.file_exists path in
available |> string_of_bool |> string))
| Read -> expand_read_macro ~dir ~source s ~read:string
| Read_lines ->
Expand Down
12 changes: 0 additions & 12 deletions src/dune_targets/dune_targets.ml
Original file line number Diff line number Diff line change
Expand Up @@ -63,18 +63,6 @@ module Validated = struct
; dirs : Filename.Set.t
}

let pp { root; files; dirs } =
let open Pp.O in
Pp.hovbox
(Pp.textf "Validated: root=%S, files=[" (Path.Build.to_string root)
++ Pp.concat
~sep:(Pp.text "; ")
(Filename.Set.to_list_map files ~f:(Pp.textf "%S"))
++ Pp.text "], dirs=["
++ Pp.concat ~sep:(Pp.text "; ") (Filename.Set.to_list_map dirs ~f:(Pp.textf "%S"))
++ Pp.char ']')
;;

let iter { root; files; dirs } ~file ~dir =
Filename.Set.iter files ~f:(fun fn -> file (Path.Build.relative root fn));
Filename.Set.iter dirs ~f:(fun dn -> dir (Path.Build.relative root dn))
Expand Down
1 change: 0 additions & 1 deletion src/dune_targets/dune_targets.mli
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,6 @@ module Validated : sig
; dirs : Filename.Set.t
}

val pp : t -> _ Pp.t
val iter : t -> file:(Path.Build.t -> unit) -> dir:(Path.Build.t -> unit) -> unit

val fold
Expand Down
4 changes: 2 additions & 2 deletions src/fs/fs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ let dir_contents (dir : Path.t) =
;;

let exists path kind =
Build_system.path_exists path
Build_system.file_exists path
>>= function
| false -> Memo.return false
| true ->
Expand All @@ -45,7 +45,7 @@ let dir_exists dir =
| `Inside _ ->
(* CR-rgrinberg: unfortunately, [Build_system.file_exists] always returns
false for directories. *)
(* CR-ElectreAAS: sike! [path_exists] now takes both into account! *)
(* CR-ElectreAAS: sike! [exists] now takes both into account! *)
exists dir Unix.S_DIR
;;

Expand Down

0 comments on commit d1f860c

Please sign in to comment.