Skip to content

Commit

Permalink
Use Syntax.deleted_in for error
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Nov 5, 2019
1 parent a157986 commit 047afc7
Show file tree
Hide file tree
Showing 3 changed files with 14 additions and 15 deletions.
19 changes: 7 additions & 12 deletions src/dune/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1993,18 +1993,13 @@ module Alias_conf = struct
and+ package = field_o "package" Pkg.decode
and+ action =
field_o "action"
(let* syntax_version = Dune_lang.Syntax.get_exn Stanza.syntax
and+ loc = loc in
let deleted_in_version = (2, 0) in
if syntax_version < deleted_in_version then
located Action_dune_lang.decode
else
let what = "action field" in
let repl =
[ Pp.text "Use a rule stanza with the alias field instead" ]
in
Dune_lang.Syntax.Error.deleted_in loc Stanza.syntax
deleted_in_version ~what ~repl)
(let repl =
[ Pp.text "Use a rule stanza with the alias field instead" ]
in
let* () =
Dune_lang.Syntax.deleted_in ~repl Stanza.syntax (2, 0)
in
located Action_dune_lang.decode)
and+ loc = loc
and+ locks = field "locks" (repeat String_with_vars.decode) ~default:[]
and+ deps =
Expand Down
4 changes: 2 additions & 2 deletions src/dune_lang/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -170,14 +170,14 @@ let desc () =
| Values (loc, Some s) -> (loc, sprintf "'%s'" s)
| Fields (loc, Some s) -> (loc, sprintf "Field '%s'" s)

let deleted_in ?(extra_info = "") t ver =
let deleted_in ?(extra_info = "") ?repl t ver =
let open Version.Infix in
let* current_ver = get_exn t in
if current_ver < ver then
return ()
else
let* loc, what = desc () in
Error.deleted_in ~extra_info loc t ver ~what
Error.deleted_in ?repl ~extra_info loc t ver ~what

let deprecated_in ?(extra_info = "") t ver =
let open Version.Infix in
Expand Down
6 changes: 5 additions & 1 deletion src/dune_lang/syntax.mli
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,11 @@ val greatest_supported_version : t -> Version.t
(** Indicate the field/constructor being parsed was deleted in the given
version *)
val deleted_in :
?extra_info:string -> t -> Version.t -> (unit, _) Decoder.parser
?extra_info:string
-> ?repl:User_message.Style.t Pp.t list
-> t
-> Version.t
-> (unit, _) Decoder.parser

(** Indicate the field/constructor being parsed was deprecated in the given
version *)
Expand Down

0 comments on commit 047afc7

Please sign in to comment.