Skip to content

Commit

Permalink
Represent env_nodes using a record rather than a list
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Jul 30, 2018
1 parent 613ca71 commit 7cb7502
Show file tree
Hide file tree
Showing 3 changed files with 25 additions and 14 deletions.
22 changes: 13 additions & 9 deletions src/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,13 @@ module Kind = struct
])
end

module Env_nodes = struct
type t =
{ context: Dune_env.Stanza.t option
; workspace: Dune_env.Stanza.t option
}
end

type t =
{ name : string
; kind : Kind.t
Expand All @@ -26,7 +33,7 @@ type t =
; for_host : t option
; implicit : bool
; build_dir : Path.t
; env_nodes : Dune_env.Stanza.t list
; env_nodes : Env_nodes.t
; path : Path.t list
; toplevel_path : Path.t option
; ocaml_bin : Path.t
Expand Down Expand Up @@ -456,14 +463,11 @@ let create_for_opam ?root ~env ~env_nodes ~targets ~profile ~switch ~name
~name ~merlin ()

let create ?merlin ?workspace_env ~env def =
let env_nodes =
match workspace_env with
| None -> Option.to_list
| Some s ->
begin function
| None -> [s]
| Some x -> [x; s]
end
let env_nodes context =
{ Env_nodes.
context
; workspace = workspace_env
}
in
match (def : Workspace.Context.t) with
| Default { targets; profile; env = env_node ; loc = _ } ->
Expand Down
9 changes: 8 additions & 1 deletion src/context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,13 @@ module Kind : sig
type t = Default | Opam of Opam.t
end

module Env_nodes : sig
type t =
{ context: Dune_env.Stanza.t option
; workspace: Dune_env.Stanza.t option
}
end

type t =
{ name : string
; kind : Kind.t
Expand All @@ -51,7 +58,7 @@ type t =
build_dir : Path.t

; (** env node that this context was initialized with *)
env_nodes : Dune_env.Stanza.t list
env_nodes : Env_nodes.t

; (** [PATH] *)
path : Path.t list
Expand Down
8 changes: 4 additions & 4 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -622,14 +622,14 @@ let create
}
in
match context.env_nodes with
| [] ->
| { context = None; workspace = None } ->
make ~config:{ loc = Loc.none; rules = [] } ~inherit_from:None
| [config] ->
| { context = Some config; workspace = None }
| { context = None; workspace = Some config } ->
make ~config ~inherit_from:None
| [context; workspace] ->
| { context = Some context ; workspace = Some workspace } ->
make ~config:context
~inherit_from:(Some (lazy (make ~inherit_from:None ~config:workspace)))
| _::_::_::_ -> assert false
) in
List.iter stanzas
~f:(fun { Dir_with_jbuild. ctx_dir; scope; stanzas; _ } ->
Expand Down

0 comments on commit 7cb7502

Please sign in to comment.