Skip to content

Commit

Permalink
revert the inside_dune hack for overriding supported versions
Browse files Browse the repository at this point in the history
Signed-off-by: Arseniy Alekseyev <aalekseyev@janestreet.com>
  • Loading branch information
aalekseyev committed Oct 30, 2019
1 parent ee2bc8a commit 0033f6a
Show file tree
Hide file tree
Showing 3 changed files with 1 addition and 7 deletions.
2 changes: 0 additions & 2 deletions src/dune/config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,6 @@ let inside_emacs = Option.is_some (Env.get Env.initial "INSIDE_EMACS")

let inside_dune = Option.is_some (Env.get Env.initial "INSIDE_DUNE")

let () = Dune_lang.Syntax.inside_dune := inside_dune

let inside_ci = Option.is_some (Env.get Env.initial "CI")

let show_full_command_on_error () =
Expand Down
4 changes: 1 addition & 3 deletions src/dune_lang/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,6 @@ module Version = struct
parser_major = data_major && parser_minor >= data_minor
end

let inside_dune = ref false

module Supported_versions = struct
type t = int Int.Map.t

Expand All @@ -56,7 +54,7 @@ module Supported_versions = struct

let is_supported t (major, minor) =
match Int.Map.find t major with
| Some minor' -> minor' >= minor || !inside_dune
| Some minor' -> minor' >= minor
| None -> false

let supported_ranges t =
Expand Down
2 changes: 0 additions & 2 deletions src/dune_lang/syntax.mli
Original file line number Diff line number Diff line change
Expand Up @@ -101,5 +101,3 @@ val set : t -> Version.t -> ('a, 'k) Decoder.parser -> ('a, 'k) Decoder.parser
val get_exn : t -> (Version.t, 'k) Decoder.parser

val key : t -> Version.t Univ_map.Key.t

val inside_dune : bool ref

0 comments on commit 0033f6a

Please sign in to comment.