Skip to content

Commit

Permalink
Remove wrong validation for switch names
Browse files Browse the repository at this point in the history
Previously, switch names were validated to be valid context names. This
is wrong as it prevent us from using local switches which are in fact
specified by their path. We remove this unnecessary validation and now
we can use local switches to define contexts.

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Mar 15, 2020
1 parent d9c34d1 commit e6a1965
Show file tree
Hide file tree
Showing 5 changed files with 23 additions and 17 deletions.
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
Unreleased
----------

- Allow contexts to be defined with local switches in workspace files (#3265,
fix #3264, @rgrinberg)

2.4.0 (06/03/2020)
------------------

Expand Down
9 changes: 3 additions & 6 deletions src/dune/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Kind = struct
module Opam = struct
type t =
{ root : string option
; switch : Context_name.t
; switch : string
}
end

Expand All @@ -18,10 +18,7 @@ module Kind = struct
| Default -> Dyn.Encoder.string "default"
| Opam o ->
Dyn.Encoder.(
record
[ ("root", option string o.root)
; ("switch", Context_name.to_dyn o.switch)
])
record [ ("root", option string o.root); ("switch", string o.switch) ])
end

module Env_nodes = struct
Expand Down Expand Up @@ -643,7 +640,7 @@ let create_for_opam ~root ~env ~env_nodes ~targets ~profile ~switch ~name
; ( match root with
| None -> []
| Some root -> [ "--root"; root ] )
; [ "--switch"; Context_name.to_string switch; "--sexp" ]
; [ "--switch"; switch; "--sexp" ]
; ( if version < (2, 0, 0) then
[]
else
Expand Down
2 changes: 1 addition & 1 deletion src/dune/context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module Kind : sig
module Opam : sig
type t =
{ root : string option
; switch : Context_name.t
; switch : string
}
end

Expand Down
19 changes: 10 additions & 9 deletions src/dune/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -156,7 +156,7 @@ module Context = struct
module Opam = struct
type t =
{ base : Common.t
; switch : Context_name.t
; switch : string
; root : string option
; merlin : bool
}
Expand All @@ -165,29 +165,30 @@ module Context = struct
let open Dyn.Encoder in
record
[ ("base", Common.to_dyn base)
; ("switch", Context_name.to_dyn switch)
; ("switch", string switch)
; ("root", option string root)
; ("merlin", bool merlin)
]

let equal { base; switch; root; merlin } t =
Common.equal base t.base
&& Context_name.equal switch t.switch
&& String.equal switch t.switch
&& Option.equal String.equal root t.root
&& Bool.equal merlin t.merlin

let t ~profile ~x =
let+ switch = field "switch" Context_name.decode
let+ loc_switch, switch = field "switch" (located string)
and+ name = field_o "name" Context_name.decode
and+ root = field_o "root" string
and+ merlin = field_b "merlin"
and+ base = Common.t ~profile in
let default =
(* TODO this needs proper error handling with locations *)
let name = Context_name.to_string switch ^ Common.fdo_suffix base in
Context_name.parse_string_exn (Loc.none, name)
let name =
match name with
| Some s -> s
| None ->
let name = Filename.basename switch ^ Common.fdo_suffix base in
Context_name.parse_string_exn (loc_switch, name)
in
let name = Option.value ~default name in
let base = { base with targets = Target.add base.targets x; name } in
{ base; switch; root; merlin }
end
Expand Down
4 changes: 3 additions & 1 deletion src/dune/workspace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,9 @@ module Context : sig
module Opam : sig
type t =
{ base : Common.t
; switch : Context_name.t
(** Either a switch name or a path to a local switch. This argument
is left opaque as we leave to opam to interpret it. *)
; switch : string
; root : string option
; merlin : bool
}
Expand Down

0 comments on commit e6a1965

Please sign in to comment.