Skip to content

Commit

Permalink
refactor check
Browse files Browse the repository at this point in the history
Signed-off-by: Etienne Millon <[email protected]>
  • Loading branch information
emillon committed Apr 11, 2023
1 parent 978e107 commit 65cca77
Showing 1 changed file with 11 additions and 11 deletions.
22 changes: 11 additions & 11 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1588,6 +1588,7 @@ module Rule = struct
type action_or_field =
| Action
| Field
| Since of Syntax.Version.t * action_or_field

let atom_table =
String.Map.of_list_exn
Expand Down Expand Up @@ -1622,7 +1623,7 @@ module Rule = struct
; ("aliases", Field)
; ("alias", Field)
; ("enabled_if", Field)
; ("package", Field)
; ("package", Since ((3, 8), Field))
]

let short_form =
Expand Down Expand Up @@ -1731,6 +1732,14 @@ module Rule = struct
})

let decode =
let rec interpret atom = function
| Field -> fields long_form
| Action -> short_form
| Since (version, inner) ->
let what = Printf.sprintf "'%s' in short-form 'rule'" atom in
let* () = Dune_lang.Syntax.since ~what Stanza.syntax version in
interpret atom inner
in
peek_exn >>= function
| List (_, Atom (loc, A s) :: _) -> (
match String.Map.find atom_table s with
Expand All @@ -1740,16 +1749,7 @@ module Rule = struct
~hints:
(User_message.did_you_mean s
~candidates:(String.Map.keys atom_table))
| Some Field ->
let* () =
match s with
| "package" ->
Dune_lang.Syntax.since ~what:"'package' in short-form 'rule'"
Stanza.syntax (3, 8)
| _ -> return ()
in
fields long_form
| Some Action -> short_form)
| Some w -> interpret s w)
| sexp ->
User_error.raise ~loc:(Dune_lang.Ast.loc sexp)
[ Pp.textf "S-expression of the form (<atom> ...) expected" ]
Expand Down

0 comments on commit 65cca77

Please sign in to comment.