Skip to content

Commit

Permalink
refactor: use and improve [Dune_project.is_extension_set] (#6985)
Browse files Browse the repository at this point in the history
* Implement it with Univ_map.mem
* Use is consistently everywhere

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Feb 3, 2023
1 parent 9f2b230 commit eb53793
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 8 deletions.
2 changes: 1 addition & 1 deletion src/dune_engine/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ let to_dyn

let find_extension_args t key = Univ_map.find t.extension_args key

let is_extension_set t key = Option.is_some (find_extension_args t key)
let is_extension_set t key = Univ_map.mem t.extension_args key

include Dune_lang.Versioned_file.Make (struct
type t = Stanza.Parser.t list
Expand Down
10 changes: 3 additions & 7 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1577,9 +1577,7 @@ module Executables = struct
(let+ loc = loc
and+ fname = filename
and+ project = Dune_project.get_exn () in
if
Option.is_none
(Dune_project.find_extension_args project bootstrap_info_extension)
if not (Dune_project.is_extension_set project bootstrap_info_extension)
then
User_error.raise ~loc
[ Pp.text "This field is reserved for Dune itself" ];
Expand Down Expand Up @@ -1750,8 +1748,7 @@ module Rule = struct
in
let* project = Dune_project.get_exn () in
let allow_directory_targets =
Option.is_some
(Dune_project.find_extension_args project directory_targets_extension)
Dune_project.is_extension_set project directory_targets_extension
in
String_with_vars.add_user_vars_to_decoding_env (Bindings.var_names deps)
(let+ loc = loc
Expand Down Expand Up @@ -2317,8 +2314,7 @@ module Stanzas = struct
let+ () = Dune_lang.Syntax.since Stanza.syntax (1, 1)
and+ t =
let enable_qualified =
Option.is_some
(Dune_project.find_extension_args project Coq_stanza.key)
Dune_project.is_extension_set project Coq_stanza.key
in
Include_subdirs.decode ~enable_qualified
and+ loc = loc in
Expand Down

0 comments on commit eb53793

Please sign in to comment.