Skip to content

Commit

Permalink
Tighter type of Super_context.Deps.interpret. (#2162)
Browse files Browse the repository at this point in the history
The returned paths are actually unused.

Also add to comments.

Signed-off-by: Arseniy Alekseyev <[email protected]>
  • Loading branch information
aalekseyev authored May 16, 2019
1 parent 6166600 commit c4b7311
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 5 deletions.
2 changes: 1 addition & 1 deletion src/preprocessing.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ val make
-> dep_kind:Lib_deps_info.Kind.t
-> lint:Dune_file.Preprocess_map.t
-> preprocess:Dune_file.Preprocess_map.t
-> preprocessor_deps:(unit, Path.t list) Build.t
-> preprocessor_deps:(unit, unit) Build.t
-> lib_name:Lib_name.Local.t option
-> scope:Scope.t
-> dir_kind:Dune_lang.File_syntax.t
Expand Down
4 changes: 3 additions & 1 deletion src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -597,7 +597,9 @@ module Deps = struct
(Build.path_set (Expander.Resolved_forms.sdeps forms))
>>^ (fun (deps, _, _, _) -> deps)

let interpret = make_interpreter ~f:dep
let interpret t ~expander l =
make_interpreter ~f:dep t ~expander l
>>^ (fun _paths -> ())

let interpret_named =
make_interpreter ~f:(fun t expander -> function
Expand Down
15 changes: 12 additions & 3 deletions src/super_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -146,13 +146,19 @@ end

(** Interpret dependencies written in jbuild files *)
module Deps : sig
(** Evaluates to the actual list of dependencies, ignoring aliases *)

(** Evaluates to the actual list of dependencies, ignoring aliases,
and registers them as the action dependencies. *)
val interpret
: t
-> expander:Expander.t
-> Dep_conf.t list
-> (unit, Path.t list) Build.t
-> (unit, unit) Build.t

(** Evaluates to the actual list of dependencies, ignoring aliases,
and registers them as the action dependencies.
It returns bindings that are later used for action expansion. *)
val interpret_named
: t
-> expander:Expander.t
Expand All @@ -162,7 +168,10 @@ end

(** Interpret action written in jbuild files *)
module Action : sig
(** The arrow takes as input the list of actual dependencies *)

(** The arrow takes as input the list of dependencies written by user, which
is used for action expansion. These must be registered with the build
arrow before calling [run]. *)
val run
: t
-> loc:Loc.t
Expand Down

0 comments on commit c4b7311

Please sign in to comment.