Skip to content

Commit

Permalink
refactor: drop [~distribute] in [is_useful_to] (#9058)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Oct 31, 2023
1 parent 93a7699 commit 59ecf4b
Show file tree
Hide file tree
Showing 8 changed files with 17 additions and 17 deletions.
14 changes: 7 additions & 7 deletions src/dune_engine/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -287,7 +287,7 @@ type is_useful =
| Clearly_not
| Maybe

let is_useful_to distribute memoize =
let is_useful_to memoize =
let rec loop t =
match t with
| Chdir (_, t) -> loop t
Expand All @@ -301,26 +301,26 @@ let is_useful_to distribute memoize =
| Copy _ -> memoize
| Symlink _ -> false
| Hardlink _ -> false
| Write_file _ -> distribute
| Write_file _ -> true
| Rename _ -> memoize
| Remove_tree _ -> false
| Diff _ -> distribute
| Diff _ -> true
| Mkdir _ -> false
| Merge_files_into _ -> distribute
| Merge_files_into _ -> true
| Run _ -> true
| Dynamic_run _ -> true
| System _ -> true
| Bash _ -> true
| Extension (module A) -> A.Spec.is_useful_to ~distribute ~memoize
| Extension (module A) -> A.Spec.is_useful_to ~memoize
in
fun t ->
match loop t with
| true -> Maybe
| false -> Clearly_not
;;

let is_useful_to_distribute = is_useful_to true false
let is_useful_to_memoize = is_useful_to true true
let is_useful_to_distribute = is_useful_to false
let is_useful_to_memoize = is_useful_to true

module Full = struct
module T = struct
Expand Down
2 changes: 1 addition & 1 deletion src/dune_engine/action_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ module Ext = struct

val name : string
val version : int
val is_useful_to : distribute:bool -> memoize:bool -> bool
val is_useful_to : memoize:bool -> bool
val encode : ('p, 't) t -> ('p -> Dune_sexp.t) -> ('t -> Dune_sexp.t) -> Dune_sexp.t
val bimap : ('a, 'b) t -> ('a -> 'x) -> ('b -> 'y) -> ('x, 'y) t

Expand Down
2 changes: 1 addition & 1 deletion src/dune_patch/dune_patch.ml
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ module Spec = struct
let name = "patch"
let version = 1
let bimap patch f _ = f patch
let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode patch input _ : Dune_lang.t =
List [ Dune_lang.atom_or_quoted_string name; input patch ]
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/copy_line_directive.ml
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ module Spec = struct
let name = "copy-line-directive"
let version = 1
let bimap (src, dst, merlin) f g = f src, g dst, merlin
let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode (src, dst, merlin) path target : Dune_lang.t =
List
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/cram/cram_exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -452,7 +452,7 @@ module Spec = struct
let name = "cram"
let version = 1
let bimap path f _ = f path
let is_useful_to ~distribute:_ ~memoize:_ = true
let is_useful_to ~memoize:_ = true

let encode script path _ : Dune_lang.t =
List [ Dune_lang.atom_or_quoted_string "cram"; path script ]
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/format_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ let action =
let name = "format-dune-file"
let version = 1
let bimap (ver, src, dst) f g = ver, f src, g dst
let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode (version, src, dst) path target : Dune_lang.t =
List
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1078,7 +1078,7 @@ include (
let name = "gen-install-file"
let version = 1
let bimap (entries, dst) _ g = entries, g dst
let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode (_entries, dst) _path target : Dune_lang.t =
List [ Dune_lang.atom_or_quoted_string name; target dst ]
Expand Down
8 changes: 4 additions & 4 deletions src/dune_rules/pkg_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -387,7 +387,7 @@ module Substitute = struct
let name = "substitute"
let version = 1
let bimap (e, s, i, o) f g = e, s, f i, g o
let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode (e, s, i, o) input output : Dune_lang.t =
let e =
Expand Down Expand Up @@ -973,7 +973,7 @@ module Install_action = struct
}
;;

let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode
{ install_file; config_file; target_dir; install_action; package }
Expand Down Expand Up @@ -1225,7 +1225,7 @@ module Fetch = struct
let name = "source-fetch"
let version = 1
let bimap t _ g = { t with target_dir = g t.target_dir }
let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode_loc f (loc, x) =
Dune_lang.List
Expand Down Expand Up @@ -1303,7 +1303,7 @@ module Copy_tree = struct
let name = "copy-tree"
let version = 1
let bimap (src, dst) f g = f src, g dst
let is_useful_to ~distribute:_ ~memoize = memoize
let is_useful_to ~memoize = memoize

let encode (src, dst) dep target : Dune_lang.t =
List [ Dune_lang.atom_or_quoted_string name; dep src; target dst ]
Expand Down

0 comments on commit 59ecf4b

Please sign in to comment.