Skip to content

Commit

Permalink
Extensions versioning (#3270)
Browse files Browse the repository at this point in the history
Improve and check extensions versioning.

Signed-off-by: Ulysse Gérard <thevoodoos@gmail.com>

Co-authored-by: Jeremie Dimino <jeremie@dimino.org>
  • Loading branch information
voodoos and jeremiedimino authored Mar 24, 2020
1 parent 704c492 commit 1825241
Show file tree
Hide file tree
Showing 41 changed files with 296 additions and 102 deletions.
5 changes: 5 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,11 @@ Unreleased

- [coq] Support for theory dependencies and compositional builds using
new field `(theories ...)` (#2053, @ejgallego, @rgrinberg)

- From now on, each version of a syntax extension must be explicitely tied to a
minimum version of the dune language. Inconsistent versions in a
`dune-project` will trigger a warning for version <=2.4 and an error for
versions >2.4 of the dune language. (#3270, fixes #2957, @voodoos)

2.4.0 (06/03/2020)
------------------
Expand Down
6 changes: 3 additions & 3 deletions doc/dune-files.rst
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ like:

.. code:: scheme
(lang dune 2.4)
(lang dune 2.5)
Additionally, they can contains the following stanzas.

Expand Down Expand Up @@ -1696,7 +1696,7 @@ a typical ``dune-workspace`` file looks like:

.. code:: scheme
(lang dune 2.4)
(lang dune 2.5)
(context (opam (switch 4.02.3)))
(context (opam (switch 4.03.0)))
(context (opam (switch 4.04.0)))
Expand All @@ -1708,7 +1708,7 @@ containing exactly:

.. code:: scheme
(lang dune 2.4)
(lang dune 2.5)
(context default)
This allows you to use an empty ``dune-workspace`` file to mark the root of your
Expand Down
2 changes: 1 addition & 1 deletion doc/opam.rst
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ configuration will tell ``dune`` to generate two opam files: ``cohttp.opam`` and

.. code:: scheme
(lang dune 2.4)
(lang dune 2.5)
(name cohttp)
(generate_opam_files true)
Expand Down
2 changes: 1 addition & 1 deletion src/dune/action_plugin.ml
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
let syntax =
Dune_lang.Syntax.create ~name:"action-plugin" ~desc:"action plugin extension"
[ (0, 1) ]
[ ((0, 1), `Since (2, 0)) ]
3 changes: 2 additions & 1 deletion src/dune/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,8 @@ let name = "cinaps"
type Stanza.t += T of t

let syntax =
Dune_lang.Syntax.create ~name ~desc:"the cinaps extension" [ (1, 0) ]
Dune_lang.Syntax.create ~name ~desc:"the cinaps extension"
[ ((1, 0), `Since (1, 11)) ]

let alias = Alias.make (Alias.Name.of_string name)

Expand Down
8 changes: 5 additions & 3 deletions src/dune/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ let relative_file =
let library_variants =
let syntax =
Dune_lang.Syntax.create ~name:"library_variants"
~desc:"the experimental library variants feature." [ (0, 2) ]
~desc:"the experimental library variants feature."
[ ((0, 1), `Since (1, 9)); ((0, 2), `Since (1, 11)) ]
in
Dune_project.Extension.register_simple ~experimental:true syntax
(Dune_lang.Decoder.return []);
Expand Down Expand Up @@ -1538,7 +1539,8 @@ module Executables = struct
let bootstrap_info_extension =
let syntax =
Dune_lang.Syntax.create ~name:"dune-bootstrap-info"
~desc:"private extension to handle Dune bootstrap" [ (0, 1) ]
~desc:"private extension to handle Dune bootstrap"
[ ((0, 1), `Since (2, 0)) ]
in
Dune_project.Extension.register syntax (return ((), [])) Dyn.Encoder.unit

Expand Down Expand Up @@ -1992,7 +1994,7 @@ module Coq = struct

let syntax =
Dune_lang.Syntax.create ~name:"coq" ~desc:"the coq extension (experimental)"
[ (0, 1) ]
[ ((0, 1), `Since (1, 9)) ]

let coq_public_decode =
map_validate
Expand Down
81 changes: 45 additions & 36 deletions src/dune/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -247,7 +247,9 @@ include Dune_lang.Versioned_file.Make (struct
end)

let default_dune_language_version =
ref (Dune_lang.Syntax.greatest_supported_version Stanza.syntax)
ref
(Option.value_exn
(Dune_lang.Syntax.greatest_supported_version Stanza.syntax))

let get_dune_lang () =
{ (Lang.get_exn "dune") with version = !default_dune_language_version }
Expand Down Expand Up @@ -370,58 +372,64 @@ module Extension = struct
let (_ : unit t) = register ?experimental syntax unit_stanzas Unit.to_dyn in
()

let instantiate ~loc ~parse_args (name_loc, name) (ver_loc, ver) =
let instantiate ~dune_lang_ver ~loc ~parse_args (name_loc, name) (ver_loc, ver)
=
match Table.find extensions name with
| None ->
User_error.raise ~loc:name_loc
[ Pp.textf "Unknown extension %S." name ]
~hints:
(User_message.did_you_mean name ~candidates:(Table.keys extensions))
| Some t ->
Dune_lang.Syntax.check_supported (syntax t) (ver_loc, ver);
Dune_lang.Syntax.check_supported ~dune_lang_ver (syntax t) (ver_loc, ver);
{ extension = t; version = ver; loc; parse_args }

(* Extensions that are not selected in the dune-project file are automatically
available at their latest version. When used, dune will automatically edit
the dune-project file. *)
let automatic ~project_file ~f =
let automatic ~lang ~project_file ~f =
Table.foldi extensions ~init:[] ~f:(fun name extension acc ->
if f name then
let version =
if is_experimental extension then
(0, 0)
Some (0, 0)
else
Dune_lang.Syntax.greatest_supported_version (syntax extension)
let dune_lang_ver = lang.Lang.Instance.version in
Dune_lang.Syntax.greatest_supported_version ~dune_lang_ver
(syntax extension)
in
let parse_args p =
let open Dune_lang.Decoder in
let dune_project_edited = ref false in
let arg, stanzas =
parse (enter p) Univ_map.empty (List (Loc.of_pos __POS__, []))
match version with
| Some version ->
let parse_args p =
let open Dune_lang.Decoder in
let dune_project_edited = ref false in
let arg, stanzas =
parse (enter p) Univ_map.empty (List (Loc.of_pos __POS__, []))
in
let result_stanzas =
List.map stanzas ~f:(fun (name, p) ->
( name
, let* () = return () in
if not !dune_project_edited then (
dune_project_edited := true;
ignore
( Project_file_edit.append project_file
(Dune_lang.to_string
(List
[ Dune_lang.atom "using"
; Dune_lang.atom name
; Dune_lang.atom
(Dune_lang.Syntax.Version.to_string
version)
]))
: created_or_already_exist )
);
p ))
in
(arg, result_stanzas)
in
let result_stanzas =
List.map stanzas ~f:(fun (name, p) ->
( name
, let* () = return () in
if not !dune_project_edited then (
dune_project_edited := true;
ignore
( Project_file_edit.append project_file
(Dune_lang.to_string
(List
[ Dune_lang.atom "using"
; Dune_lang.atom name
; Dune_lang.atom
(Dune_lang.Syntax.Version.to_string
version)
]))
: created_or_already_exist )
);
p ))
in
(arg, result_stanzas)
in
{ extension; version; loc = Loc.none; parse_args } :: acc
{ extension; version; loc = Loc.none; parse_args } :: acc
| None -> acc
else
acc)
end
Expand All @@ -438,7 +446,7 @@ let interpret_lang_and_extensions ~(lang : Lang.Instance.t) ~explicit_extensions
[ Pp.textf "Extension %S specified for the second time." name ]
| Ok map ->
let implicit_extensions =
Extension.automatic ~project_file ~f:(fun name ->
Extension.automatic ~lang ~project_file ~f:(fun name ->
not (String.Map.mem map name))
in
let extensions =
Expand Down Expand Up @@ -583,7 +591,8 @@ let parse ~dir ~lang ~opam_packages ~file =
and+ parse_args = capture in
(* We don't parse the arguments quite yet as we want to set the
version of extensions before parsing them. *)
Extension.instantiate ~loc ~parse_args name ver)
Extension.instantiate ~dune_lang_ver:lang.Lang.Instance.version ~loc
~parse_args name ver)
and+ implicit_transitive_deps =
field_o_b "implicit_transitive_deps"
~check:(Dune_lang.Syntax.since Stanza.syntax (1, 7))
Expand Down
6 changes: 5 additions & 1 deletion src/dune/format_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,11 @@ open Dune_lang.Decoder

let syntax =
Dune_lang.Syntax.create ~name:"fmt"
~desc:"integration with automatic formatters" [ (1, 2) ]
~desc:"integration with automatic formatters"
[ ((1, 0), `Since (1, 4))
; ((1, 1), `Since (1, 7))
; ((1, 2), `Since (1, 11))
]

module Language = struct
type t =
Expand Down
2 changes: 1 addition & 1 deletion src/dune/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -295,7 +295,7 @@ let gen_dune_package sctx pkg =
let meta_template = Package_paths.meta_template ctx pkg in
let name = pkg.name in
let dune_version =
Dune_lang.Syntax.greatest_supported_version Stanza.syntax
Option.value_exn (Dune_lang.Syntax.greatest_supported_version Stanza.syntax)
in
let lib_entries = Super_context.lib_entries_of_package sctx pkg.name in
let deprecated_dune_packages =
Expand Down
2 changes: 1 addition & 1 deletion src/dune/mdx.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ type Stanza.t += T of t
let syntax =
let name = "mdx" in
let desc = "mdx extension to verify code blocks in .md files" in
Dune_lang.Syntax.create ~name ~desc [ (0, 1) ]
Dune_lang.Syntax.create ~name ~desc [ ((0, 1), `Since (2, 4)) ]

let default_files =
let has_extention ext s = String.equal ext (Filename.extension s) in
Expand Down
6 changes: 5 additions & 1 deletion src/dune/menhir_stanza.ml
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
let syntax =
Dune_lang.Syntax.create ~name:"menhir" ~desc:"the menhir extension"
[ (1, 1); (2, 1) ]
[ ((1, 0), `Since (1, 0))
; ((1, 1), `Since (1, 4))
; ((2, 0), `Since (1, 4))
; ((2, 1), `Since (2, 2))
]
2 changes: 1 addition & 1 deletion src/dune/ocaml_stdlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ let syntax =
Dune_lang.Syntax.create
~name:"experimental_building_ocaml_compiler_with_dune"
~desc:"experimental feature for building the compiler with dune"
[ (0, 1) ]
[ ((0, 1), `Since (1, 3)) ]
in
Dune_project.Extension.register_simple ~experimental:true syntax
(Dune_lang.Decoder.return []);
Expand Down
9 changes: 7 additions & 2 deletions src/dune/stanza.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,13 @@ module Parser = struct
type nonrec t = string * t list Dune_lang.Decoder.t
end

let latest_version = (2, 4)
let latest_version = (2, 5)

let since v = (v, `Since v)

let all_minors (major, minor) =
List.init (minor + 1) ~f:(fun i -> since (major, i))

let syntax =
Dune_lang.Syntax.create ~name:"dune" ~desc:"the dune language"
[ (1, 12); latest_version ]
(all_minors (1, 12) @ all_minors latest_version)
Loading

0 comments on commit 1825241

Please sign in to comment.