Skip to content

Commit

Permalink
refactor: move cram stanza definition (#6800)
Browse files Browse the repository at this point in the history
From Dune_file.Cram to Cram_stanza.T

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Dec 28, 2022
1 parent aaa7880 commit 72f25ed
Show file tree
Hide file tree
Showing 5 changed files with 6 additions and 4 deletions.
2 changes: 1 addition & 1 deletion src/dune_rules/cram_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ let rules ~sctx ~expander ~dir tests =
| None -> []
| Some (d : Dune_file.t) ->
List.filter_map d.stanzas ~f:(function
| Dune_file.Cram c -> Option.some_if (f c) (dir, c)
| Cram_stanza.T c -> Option.some_if (f c) (dir, c)
| _ -> None)
in
let rec collect_whole_subtree acc dir =
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/cram_stanza.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,8 @@ type t =
; package : Package.t option
}

type Stanza.t += T of t

let decode =
fields
(let+ loc = loc
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/cram_stanza.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,4 +14,6 @@ type t =
; package : Package.t option
}

type Stanza.t += T of t

val decode : t Dune_lang.Decoder.t
3 changes: 1 addition & 2 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2245,7 +2245,6 @@ type Stanza.t +=
| Toplevel of Toplevel.t
| Library_redirect of Library_redirect.Local.t
| Deprecated_library_name of Deprecated_library_name.t
| Cram of Cram_stanza.t
| Plugin of Plugin.t

module Stanzas = struct
Expand Down Expand Up @@ -2354,7 +2353,7 @@ module Stanzas = struct
"You can enable cram tests by adding (cram enable) to your \
dune-project file."
];
[ Cram t ] )
[ Cram_stanza.T t ] )
; ( "generate_sites_module"
, let+ () = Dune_lang.Syntax.since Section.dune_site_syntax (0, 1)
and+ t = Generate_sites_module_stanza.decode in
Expand Down
1 change: 0 additions & 1 deletion src/dune_rules/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -464,7 +464,6 @@ type Stanza.t +=
| Toplevel of Toplevel.t
| Library_redirect of Library_redirect.Local.t
| Deprecated_library_name of Deprecated_library_name.t
| Cram of Cram_stanza.t
| Plugin of Plugin.t

val stanza_package : Stanza.t -> Package.t option
Expand Down

0 comments on commit 72f25ed

Please sign in to comment.