Skip to content

Commit

Permalink
Make dune look for dune-workspace rather than jbuild-workspace
Browse files Browse the repository at this point in the history
  • Loading branch information
Jeremie Dimino committed Apr 26, 2018
1 parent a983787 commit 75370cf
Show file tree
Hide file tree
Showing 4 changed files with 24 additions and 12 deletions.
19 changes: 14 additions & 5 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,11 @@ module Make(M : sig val which : which end) = struct
| Jbuilder -> "jbuilder"
| Dune -> "dune"

let workspace_file =
match M.which with
| Jbuilder -> "jbuild-workspace"
| Dune -> "dune-workspace"

type common =
{ debug_dep_path : bool
; debug_findlib : bool
Expand Down Expand Up @@ -83,7 +88,11 @@ module Make(M : sig val which : which end) = struct
let setup ~log ?external_lib_deps_mode common =
setup
~log
?workspace_file:(Option.map ~f:Path.of_string common.workspace_file)
~workspace_file:(
Path.of_string (
match common.workspace_file with
| Some fn -> fn
| None -> workspace_file))
?only_packages:common.only_packages
?external_lib_deps_mode
?x:common.x
Expand Down Expand Up @@ -145,13 +154,13 @@ module Make(M : sig val which : which end) = struct
let cwd = Sys.getcwd () in
let rec loop counter ~candidates ~to_cwd dir =
let files = Sys.readdir dir |> Array.to_list |> String.Set.of_list in
if String.Set.mem files "jbuild-workspace" then
if String.Set.mem files workspace_file then
cont counter ~candidates:((0, dir, to_cwd) :: candidates) dir ~to_cwd
else if M.which = Jbuilder &&
String.Set.exists files ~f:(fun fn ->
String.is_prefix fn ~prefix:"jbuild-workspace") then
String.is_prefix fn ~prefix:workspace_file) then
cont counter ~candidates:((1, dir, to_cwd) :: candidates) dir ~to_cwd
else if String.Set.mem files "dune-project" then
else if String.Set.mem files Dune_project.filename then
cont counter ~candidates:((2, dir, to_cwd) :: candidates) dir ~to_cwd
else
cont counter ~candidates dir ~to_cwd
Expand Down Expand Up @@ -479,7 +488,7 @@ module Make(M : sig val which : which end) = struct
else
[]
; (match config_file with
| This fn -> ["--config-file"; fn]
| This fn -> ["--config-file"; Path.to_string fn]
| No_config -> ["--no-config"]
| Default -> [])
]
Expand Down
6 changes: 3 additions & 3 deletions src/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,8 @@ module Acc = struct
end

let load ~dir =
let fname = Path.to_string (Path.relative dir filename) in
let sexps = Sexp.load ~fname ~mode:Many in
let fname = Path.relative dir filename in
let sexps = Io.Sexp.load fname ~mode:Many in
let langs, sexps =
List.partition_map sexps ~f:(function
| List (loc, Atom (_, A "lang") :: _) as sexp ->
Expand All @@ -45,7 +45,7 @@ let load ~dir =
let _lang =
match langs with
| [] ->
Loc.fail (Loc.in_file fname)
Loc.fail (Loc.in_file (Path.to_string fname))
"language not specified, you need to add (lang dune 0.1)"
| [(v, _)] -> v
| _ :: (_, loc) :: _ ->
Expand Down
2 changes: 2 additions & 0 deletions src/dune_project.mli
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
(** dune-project files *)

open Import

type t =
{ name : string
}
Expand Down
9 changes: 5 additions & 4 deletions src/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ let setup_env ~capture_outputs =

let setup ?(log=Log.no_log)
?external_lib_deps_mode
?workspace ?(workspace_file=Path.of_string "jbuild-workspace")
?workspace ?workspace_file
?only_packages
?extra_ignored_subtrees
?x
Expand All @@ -55,9 +55,10 @@ let setup ?(log=Log.no_log)
match workspace with
| Some w -> w
| None ->
if Path.exists workspace_file then
Workspace.load ?x workspace_file
else
match workspace_file with
| Some p when Path.exists p ->
Workspace.load ?x p
| _ ->
{ merlin_context = Some "default"
; contexts = [Default [
match x with
Expand Down

0 comments on commit 75370cf

Please sign in to comment.