Skip to content

Commit

Permalink
Make (add-to-path) a common (context) field
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Jul 18, 2019
1 parent 4f26858 commit a6aa6aa
Show file tree
Hide file tree
Showing 5 changed files with 27 additions and 34 deletions.
48 changes: 20 additions & 28 deletions src/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,25 +27,6 @@ module Env_nodes = struct
; workspace: Dune_env.Stanza.t option
}

let extra_path ~profile ~cwd env_nodes =
let make_path l =
let open Option.O in
Option.value
~default:[]
(let* stanza = l in
let+ {add_to_path; _} = Dune_env.Stanza.find stanza ~profile
in
List.map ~f:(fun s ->
let s =
if Filename.is_relative s then Filename.concat cwd s
else s
in
Path.of_string s
) add_to_path)
in
make_path env_nodes.context @
make_path env_nodes.workspace

let extra_env ~profile env_nodes =
let make_env l =
let open Option.O in
Expand Down Expand Up @@ -225,8 +206,17 @@ let ocamlfind_printconf_path ~env ~ocamlfind ~toolchain =
let+ l = Process.run_capture_lines ~env Strict ocamlfind args in
List.map l ~f:Path.of_filename_relative_to_initial_cwd

let extra_path ~cwd add_to_path =
List.map ~f:(fun s ->
let s =
if Filename.is_relative s then Filename.concat cwd s
else s
in
Path.of_string s
) add_to_path

let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
~host_context ~host_toolchain ~profile =
~host_context ~host_toolchain ~profile ~add_to_path =
let opam_var_cache = Hashtbl.create 128 in
(match kind with
| Opam { root = Some root; _ } ->
Expand All @@ -236,7 +226,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
Utils.program_not_found prog ~context:name ~loc:None
in
let cwd = Sys.getcwd () in
let extra_path = Env_nodes.extra_path ~profile ~cwd env_nodes in
let extra_path = extra_path ~cwd add_to_path in
let env = List.fold_right ~init:env ~f:(fun dir env -> Env.cons_path env ~dir) extra_path in
let path = extra_path @ path in
let which_cache = Hashtbl.create 128 in
Expand Down Expand Up @@ -565,9 +555,10 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
let opam_config_var t var =
opam_config_var ~env:t.env ~cache:t.opam_var_cache var

let default ~merlin ~env_nodes ~env ~targets =
let default ~merlin ~env_nodes ~env ~targets ~add_to_path =
let path = Env.path Env.initial in
create ~kind:Default ~path ~env ~env_nodes ~merlin ~targets
~add_to_path

let opam_version =
let res = ref None in
Expand All @@ -594,7 +585,8 @@ let opam_version =
Fiber.Future.wait future

let create_for_opam ~root ~env ~env_nodes ~targets ~profile
~switch ~name ~merlin ~host_context ~host_toolchain =
~switch ~name ~merlin ~host_context ~host_toolchain
~add_to_path =
let opam =
match Lazy.force opam with
| None -> Utils.program_not_found "opam" ~loc:None
Expand Down Expand Up @@ -638,7 +630,7 @@ let create_for_opam ~root ~env ~env_nodes ~targets ~profile
in
let env = Env.extend env ~vars in
create ~kind:(Opam { root; switch }) ~profile ~targets ~path ~env ~env_nodes
~name ~merlin ~host_context ~host_toolchain
~name ~merlin ~host_context ~host_toolchain ~add_to_path

let instantiate_context env (workspace : Workspace.t)
~(context : Workspace.Context.t) ~host_context =
Expand All @@ -651,7 +643,7 @@ let instantiate_context env (workspace : Workspace.t)
in
match context with
| Default { targets; name; host_context = _; profile; env = _
; toolchain ; loc = _ } ->
; toolchain ; add_to_path; loc = _ } ->
let merlin =
workspace.merlin_context = Some (Workspace.Context.name context)
in
Expand All @@ -661,12 +653,12 @@ let instantiate_context env (workspace : Workspace.t)
| None -> Env.get env "OCAMLFIND_TOOLCHAIN"
in
default ~env ~env_nodes ~profile ~targets ~name ~merlin ~host_context
~host_toolchain
~host_toolchain ~add_to_path
| Opam { base = { targets; name; host_context = _; profile; env = _
; toolchain; loc = _ }
; toolchain; add_to_path; loc = _ }
; switch; root; merlin } ->
create_for_opam ~root ~env_nodes ~env ~profile ~switch ~name ~merlin
~targets ~host_context ~host_toolchain:toolchain
~targets ~host_context ~host_toolchain:toolchain ~add_to_path

let create ~env (workspace : Workspace.t) =
let rec contexts : t list Fiber.Once.t String.Map.t Lazy.t = lazy (
Expand Down
5 changes: 0 additions & 5 deletions src/dune_env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ module Stanza = struct
; c_flags : Ordered_set_lang.Unexpanded.t C.Kind.Dict.t
; env_vars : Env.t
; binaries : File_binding.Unexpanded.t list
; add_to_path : string list
}

type pattern =
Expand Down Expand Up @@ -50,15 +49,11 @@ module Stanza = struct
and+ binaries = field ~default:[] "binaries"
(Syntax.since Stanza.syntax (1, 6)
>>> File_binding.Unexpanded.L.decode)
and+ add_to_path =
field "add-to-path" ~default:[]
(Syntax.since Stanza.syntax (1, 12) >>> list string)
in
{ flags
; c_flags
; env_vars
; binaries
; add_to_path
}

let rule =
Expand Down
1 change: 0 additions & 1 deletion src/dune_env.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ module Stanza : sig
; c_flags : Ordered_set_lang.Unexpanded.t C.Kind.Dict.t
; env_vars : Env.t
; binaries : File_binding.Unexpanded.t list
; add_to_path : string list
}

type pattern =
Expand Down
6 changes: 6 additions & 0 deletions src/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ module Context = struct
; toolchain : string option
; name : string
; host_context : string option
; add_to_path : string list
}

let t ~profile =
Expand All @@ -64,6 +65,9 @@ module Context = struct
field_o "host" (Syntax.since syntax (1, 10) >>> string)
and+ toolchain =
field_o "toolchain" (Syntax.since syntax (1, 5) >>> string)
and+ add_to_path =
field "add-to-path" ~default:[]
(Syntax.since Stanza.syntax (1, 12) >>> list string)
and+ loc = loc
in
Option.iter
Expand All @@ -81,6 +85,7 @@ module Context = struct
; name = "default"
; host_context
; toolchain
; add_to_path
}
end

Expand Down Expand Up @@ -178,6 +183,7 @@ module Context = struct
; host_context = None
; env = None
; toolchain = None
; add_to_path = []
}
end

Expand Down
1 change: 1 addition & 0 deletions src/workspace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module Context : sig
; toolchain : string option
; name : string
; host_context : string option
; add_to_path : string list
}
end
module Opam : sig
Expand Down

0 comments on commit a6aa6aa

Please sign in to comment.