From 05add08a296f1fa0adcde64d91a5aa22c4abe7fc Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Mon, 16 Mar 2020 17:39:27 +0100 Subject: [PATCH] Remove support for old versioning system MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse GĂ©rard --- src/dune/action_plugin.ml | 2 +- src/dune/cinaps.ml | 2 +- src/dune/dune_file.ml | 7 ++- src/dune/format_config.ml | 2 +- src/dune/mdx.ml | 2 +- src/dune/menhir_stanza.ml | 2 +- src/dune/ocaml_stdlib.ml | 2 +- src/dune/stanza.ml | 2 +- src/dune_lang/syntax.ml | 85 ++++++++++----------------------- src/dune_lang/syntax.mli | 10 ++-- src/dune_lang/versioned_file.ml | 5 +- 11 files changed, 41 insertions(+), 80 deletions(-) diff --git a/src/dune/action_plugin.ml b/src/dune/action_plugin.ml index d633eec4d235..5dd882edb2b6 100644 --- a/src/dune/action_plugin.ml +++ b/src/dune/action_plugin.ml @@ -1,3 +1,3 @@ let syntax = - Dune_lang.Syntax.createn ~name:"action-plugin" ~desc:"action plugin extension" + Dune_lang.Syntax.create ~name:"action-plugin" ~desc:"action plugin extension" [ ((0, 1), `Since (2, 0)) ] diff --git a/src/dune/cinaps.ml b/src/dune/cinaps.ml index 8129d2da34c0..40f19b0df82b 100644 --- a/src/dune/cinaps.ml +++ b/src/dune/cinaps.ml @@ -16,7 +16,7 @@ let name = "cinaps" type Stanza.t += T of t let syntax = - Dune_lang.Syntax.createn ~name ~desc:"the cinaps extension" + Dune_lang.Syntax.create ~name ~desc:"the cinaps extension" [ ((1, 0), `Since (1, 11)) ] let alias = Alias.make (Alias.Name.of_string name) diff --git a/src/dune/dune_file.ml b/src/dune/dune_file.ml index 75b55851340a..767ad04c8d5a 100644 --- a/src/dune/dune_file.ml +++ b/src/dune/dune_file.ml @@ -21,7 +21,7 @@ let relative_file = let library_variants = let syntax = - Dune_lang.Syntax.createn ~name:"library_variants" + Dune_lang.Syntax.create ~name:"library_variants" ~desc:"the experimental library variants feature." [ ((0, 1), `Since (1, 9)); ((0, 2), `Since (1, 11)) ] in @@ -1538,7 +1538,7 @@ module Executables = struct let bootstrap_info_extension = let syntax = - Dune_lang.Syntax.createn ~name:"dune-bootstrap-info" + Dune_lang.Syntax.create ~name:"dune-bootstrap-info" ~desc:"private extension to handle Dune bootstrap" [ ((0, 1), `Since (2, 0)) ] in @@ -1991,8 +1991,7 @@ module Coq = struct } let syntax = - Dune_lang.Syntax.createn ~name:"coq" - ~desc:"the coq extension (experimental)" + Dune_lang.Syntax.create ~name:"coq" ~desc:"the coq extension (experimental)" [ ((0, 1), `Since (1, 9)) ] let coq_public_decode = diff --git a/src/dune/format_config.ml b/src/dune/format_config.ml index 059e70671563..f7dcb0c4b6e6 100644 --- a/src/dune/format_config.ml +++ b/src/dune/format_config.ml @@ -3,7 +3,7 @@ open Import open Dune_lang.Decoder let syntax = - Dune_lang.Syntax.createn ~name:"fmt" + Dune_lang.Syntax.create ~name:"fmt" ~desc:"integration with automatic formatters" [ ((1, 0), `Since (1, 4)) ; ((1, 1), `Since (1, 7)) diff --git a/src/dune/mdx.ml b/src/dune/mdx.ml index 590672559a9c..79ba12eb99ef 100644 --- a/src/dune/mdx.ml +++ b/src/dune/mdx.ml @@ -149,7 +149,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.createn ~name ~desc [ ((0, 1), `Since (2, 4)) ] + 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 diff --git a/src/dune/menhir_stanza.ml b/src/dune/menhir_stanza.ml index 11f7b2d9d50e..a7b8a9241520 100644 --- a/src/dune/menhir_stanza.ml +++ b/src/dune/menhir_stanza.ml @@ -1,5 +1,5 @@ let syntax = - Dune_lang.Syntax.createn ~name:"menhir" ~desc:"the menhir extension" + Dune_lang.Syntax.create ~name:"menhir" ~desc:"the menhir extension" [ ((1, 0), `Since (1, 0)) ; ((1, 1), `Since (1, 4)) ; ((2, 0), `Since (1, 4)) diff --git a/src/dune/ocaml_stdlib.ml b/src/dune/ocaml_stdlib.ml index 953c4611eb6f..b94ee8bf5a66 100644 --- a/src/dune/ocaml_stdlib.ml +++ b/src/dune/ocaml_stdlib.ml @@ -6,7 +6,7 @@ type t = let syntax = let syntax = - Dune_lang.Syntax.createn + Dune_lang.Syntax.create ~name:"experimental_building_ocaml_compiler_with_dune" ~desc:"experimental feature for building the compiler with dune" [ ((0, 1), `Since (1, 3)) ] diff --git a/src/dune/stanza.ml b/src/dune/stanza.ml index 1f925c6b10fe..afb92f269cfb 100644 --- a/src/dune/stanza.ml +++ b/src/dune/stanza.ml @@ -14,5 +14,5 @@ let all_minors (major, minor) = List.init (minor + 1) ~f:(fun i -> since (major, i)) let syntax = - Dune_lang.Syntax.createn ~name:"dune" ~desc:"the dune language" + Dune_lang.Syntax.create ~name:"dune" ~desc:"the dune language" (all_minors (1, 12) @ all_minors latest_version) diff --git a/src/dune_lang/syntax.ml b/src/dune_lang/syntax.ml index caa8f440addc..111d629cd4e3 100644 --- a/src/dune_lang/syntax.ml +++ b/src/dune_lang/syntax.ml @@ -47,31 +47,16 @@ module Supported_versions = struct (* The extension supported versions are declared using an explicit list of all versions but stored as a map from major versions to maps from minor version to dune_lang required versions *) - type t = - [ `Old of int Int.Map.t - | `New of Version.t Int.Map.t Int.Map.t - ] + type t = Version.t Int.Map.t Int.Map.t - let to_dyn t = - match t with - | `Old t -> Int.Map.to_dyn Int.to_dyn t - | `New t -> Int.Map.to_dyn (Int.Map.to_dyn Version.to_dyn) t - - let _print t = - Int.Map.iteri t ~f:(fun k m -> - Printf.eprintf "Major: %i" k; - Int.Map.iteri m ~f:(fun k dlv -> - Printf.eprintf " (Minor: %i DLV: %s)" k (Version.to_string dlv)); - Printf.eprintf "\n") - - let make v : t = `Old (Int.Map.of_list_exn v) + let to_dyn t = Int.Map.to_dyn (Int.Map.to_dyn Version.to_dyn) t (* We convert the exposed extension version type: `(Version.t * [ `Since of Version.t ]) list` which is a list of fully qualified versions paired with the corresponding dune_lang version. To the internal representation: `(Version.t Int.Map.t) Int.Map.t` which is a list of major versions paired with lists of minor versions paires with a dune_lang version. *) - let maken (versions : (Version.t * [ `Since of Version.t ]) list) : t = + let make (versions : (Version.t * [ `Since of Version.t ]) list) : t = let v = List.fold_left versions ~init:(Int.Map.empty : Version.t Int.Map.t Int.Map.t) @@ -87,7 +72,7 @@ module Supported_versions = struct | Some _minor_map -> Some minor_map | None -> Some minor_map)) in - `New v + v let remove_uncompatible_versions lang_ver = Int.Map.filter_map ~f:(fun minors -> @@ -101,52 +86,37 @@ module Supported_versions = struct let rec greatest_supported_version ?lang_ver t = let open Option.O in - match (t, lang_ver) with - | `Old t, _ -> Int.Map.max_binding t - | `New t, Some lang_ver -> + match lang_ver with + | Some lang_ver -> let compat = remove_uncompatible_versions lang_ver t in - greatest_supported_version (`New compat) - | `New t, None -> + greatest_supported_version compat + | None -> let* major, minors = Int.Map.max_binding t in let* minor, _ = Int.Map.max_binding minors in Some (major, minor) let get_min_lang_ver t (major, minor) = - match t with - | `New t -> - let open Option.O in - let* minors = Int.Map.find t major in - Int.Map.find minors minor - | `Old _ -> None + let open Option.O in + let* minors = Int.Map.find t major in + Int.Map.find minors minor let is_supported t (major, minor) lang_ver = - match t with - | `Old t -> ( - match Int.Map.find t major with - | Some minor' -> minor' >= minor - | None -> false ) - | `New t -> ( - match Int.Map.find t major with - | Some t -> ( - match Int.Map.find t minor with - | Some min_lang_ver -> lang_ver >= min_lang_ver - | None -> false ) + match Int.Map.find t major with + | Some t -> ( + match Int.Map.find t minor with + | Some min_lang_ver -> lang_ver >= min_lang_ver | None -> false ) + | None -> false let supported_ranges lang_ver (t : t) = - match t with - | `Old t -> - Int.Map.to_list t - |> List.map ~f:(fun (major, minor) -> ((major, 0), (major, minor))) - | `New t -> - let compat = remove_uncompatible_versions lang_ver t in - Int.Map.to_list compat - |> List.map ~f:(fun (major, minors) -> - let max_minor, _ = Option.value_exn (Int.Map.max_binding minors) in - if major > 0 then - ((major, 0), (major, max_minor)) - else - ((major, 1), (major, max_minor))) + let compat = remove_uncompatible_versions lang_ver t in + Int.Map.to_list compat + |> List.map ~f:(fun (major, minors) -> + let max_minor, _ = Option.value_exn (Int.Map.max_binding minors) in + if major > 0 then + ((major, 0), (major, max_minor)) + else + ((major, 1), (major, max_minor))) end type t = @@ -210,13 +180,6 @@ let create ~name ~desc supported_versions = ; supported_versions = Supported_versions.make supported_versions } -let createn ~name ~desc supported_versions = - { name - ; desc - ; key = Univ_map.Key.create ~name Version.to_dyn - ; supported_versions = Supported_versions.maken supported_versions - } - let name t = t.name let check_supported ~lang_ver t (loc, ver) = diff --git a/src/dune_lang/syntax.mli b/src/dune_lang/syntax.mli index abd614b07e71..0f7d7a82c8b3 100644 --- a/src/dune_lang/syntax.mli +++ b/src/dune_lang/syntax.mli @@ -58,12 +58,10 @@ module Warning : sig end (** [create ~name ~desc supported_versions] defines a new syntax. - [supported_version] is the list of the last minor version of each supported - major version. [desc] is used to describe what this syntax represent in - error messages. *) -val create : name:string -> desc:string -> Version.t list -> t - -val createn : + [supported_version] is the list of all the supported versions paired with + the versions of the dune lang in which they where introduced. [desc] is used + to describe what this syntax represent in error messages. *) +val create : name:string -> desc:string -> (Version.t * [ `Since of Version.t ]) list -> t (** Return the name of the syntax. *) diff --git a/src/dune_lang/versioned_file.ml b/src/dune_lang/versioned_file.ml index c78b659d400d..d88a18f43d3b 100644 --- a/src/dune_lang/versioned_file.ml +++ b/src/dune_lang/versioned_file.ml @@ -72,8 +72,9 @@ struct Syntax.check_supported ~lang_ver t.syntax (ver_loc, lang_ver); { syntax = t.syntax; data = t.data; version = lang_ver } - (* TODO get_exn is only called with "dune" so far, but greatest_supported_version may return None for extensions - which are not supported under the specified dune_lang version *) + (* TODO get_exn is only called with "dune" so far, but + greatest_supported_version may return None for extensions which are not + supported under the specified dune_lang version *) let get_exn name : Instance.t = let t = Table.find_exn langs name in { syntax = t.syntax