Skip to content

Commit 1927730

Browse files
Drop support for upgrading jbuilder projects (#4473)
Signed-off-by: Jeremie Dimino <jeremie@dimino.org>
1 parent d9377e8 commit 1927730

File tree

35 files changed

+109
-1200
lines changed

35 files changed

+109
-1200
lines changed

CHANGES.md

+2
Original file line numberDiff line numberDiff line change
@@ -95,6 +95,8 @@ Unreleased
9595
- Allow dune-file as an alternative file name for dune files (needs to be
9696
enabled in the dune-project file) (#4428, @nojb)
9797

98+
- Drop support for upgrading jbuilder projects (#...., @jeremiedimino)
99+
98100
2.8.5 (28/03/2021)
99101
------------------
100102

bin/common.ml

+2-3
Original file line numberDiff line numberDiff line change
@@ -128,7 +128,7 @@ let print_entering_message c =
128128
in
129129
Console.print [ Pp.verbatim (sprintf "Entering directory '%s'" dir) ]
130130

131-
let init ?log_file ?(recognize_jbuilder_projects = false) c =
131+
let init ?log_file c =
132132
if c.root.dir <> Filename.current_dir_name then Sys.chdir c.root.dir;
133133
Path.set_root (normalize_path (Path.External.cwd ()));
134134
Path.Build.set_build_dir (Path.Build.Kind.of_string c.build_dir);
@@ -156,8 +156,7 @@ let init ?log_file ?(recognize_jbuilder_projects = false) c =
156156
|> S.set_ancestor_vcs c.root.ancestor_vcs
157157
|> S.set_execution_parameters
158158
(Dune_engine.Execution_parameters.builtin_default
159-
|> Dune_rules.Workspace.update_execution_parameters w)
160-
|> S.set_recognize_jbuilder_projects recognize_jbuilder_projects);
159+
|> Dune_rules.Workspace.update_execution_parameters w));
161160
Dune_rules.Global.init ~capture_outputs:c.capture_outputs;
162161
(* CR-soon amokhov: Right now, types [Dune_config.Caching.Duplication.t] and
163162
[Dune_cache_storage.Mode.t] are the same. They will be unified after

bin/common.mli

+1-5
Original file line numberDiff line numberDiff line change
@@ -22,11 +22,7 @@ val prefix_target : t -> string -> string
2222
2323
Return the final configuration, which is the same as the one returned in the
2424
[config] field of [Dune_rules.Workspace.workspace ()]) *)
25-
val init :
26-
?log_file:Dune_util.Log.File.t
27-
-> ?recognize_jbuilder_projects:bool
28-
-> t
29-
-> Dune_config.t
25+
val init : ?log_file:Dune_util.Log.File.t -> t -> Dune_config.t
3026

3127
(** [examples \[("description", "dune cmd foo"); ...\]] is an [EXAMPLES] manpage
3228
section of enumerated examples illustrating how to run the documented

bin/ocaml_merlin.ml

+2-6
Original file line numberDiff line numberDiff line change
@@ -29,9 +29,7 @@ let term =
2929
ouptut.")
3030
in
3131
let common = Common.set_print_directory common false in
32-
let config =
33-
Common.init common ~log_file:No_log_file ~recognize_jbuilder_projects:true
34-
in
32+
let config = Common.init common ~log_file:No_log_file in
3533
Scheduler.go ~common ~config (fun () ->
3634
match dump_config with
3735
| Some s -> Dune_rules.Merlin_server.dump s
@@ -66,9 +64,7 @@ module Dump_dot_merlin = struct
6664
"The path to the folder of which the configuration should be \
6765
printed. Defaults to the current directory.")
6866
in
69-
let config =
70-
Common.init common ~log_file:No_log_file ~recognize_jbuilder_projects:true
71-
in
67+
let config = Common.init common ~log_file:No_log_file in
7268
Scheduler.go ~common ~config (fun () ->
7369
match path with
7470
| Some s -> Dune_rules.Merlin_server.dump_dot_merlin s

bin/upgrade.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ let info = Term.info "upgrade" ~doc ~man
1515

1616
let term =
1717
let+ common = Common.term in
18-
let config = Common.init common ~recognize_jbuilder_projects:true in
18+
let config = Common.init common in
1919
Scheduler.go ~common ~config (fun () -> Dune_upgrader.upgrade ())
2020

2121
let command = (term, info)

boot/libs.ml

-1
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,6 @@ let local_libraries =
2929
; ("src/section", Some "Dune_section", false, None)
3030
; ("vendor/build_path_prefix_map/src", Some "Build_path_prefix_map", false,
3131
None)
32-
; ("src/jbuild_support", Some "Jbuild_support", false, None)
3332
; ("otherlibs/dune-rpc/private", Some "Dune_rpc_private", false, None)
3433
; ("src/dune_rpc_server", Some "Dune_rpc_server", false, None)
3534
; ("src/csexp_rpc", Some "Csexp_rpc", false, None)

src/dune_engine/action_builder.ml

+1-2
Original file line numberDiff line numberDiff line change
@@ -147,8 +147,7 @@ let strings p =
147147

148148
let read_sexp p =
149149
let+ s = contents p in
150-
Dune_lang.Parser.parse_string s ~lexer:Dune_lang.Lexer.token
151-
~fname:(Path.to_string p) ~mode:Single
150+
Dune_lang.Parser.parse_string s ~fname:(Path.to_string p) ~mode:Single
152151

153152
let if_file_exists p ~then_ ~else_ = If_file_exists (p, then_, else_)
154153

src/dune_engine/dune

-1
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,6 @@
2020
ocaml_config
2121
chrome_trace
2222
stats
23-
jbuild_support
2423
dune_action_plugin
2524
dune_util
2625
build_path_prefix_map

src/dune_engine/include_stanza.ml

+1-4
Original file line numberDiff line numberDiff line change
@@ -45,8 +45,5 @@ let load_sexps ~context:{ current_file; include_stack } (loc, fn) =
4545
Path.Source.equal f current_file)
4646
then
4747
error { current_file; include_stack };
48-
let sexps =
49-
Dune_lang.Parser.load ~lexer:Dune_lang.Lexer.token
50-
(Path.source current_file) ~mode:Many
51-
in
48+
let sexps = Dune_lang.Parser.load (Path.source current_file) ~mode:Many in
5249
(sexps, { current_file; include_stack })

src/dune_engine/source_tree.ml

+3-34
Original file line numberDiff line numberDiff line change
@@ -54,8 +54,6 @@ module Dune_file = struct
5454

5555
let alternative_fname = "dune-file"
5656

57-
let jbuild_fname = "jbuild"
58-
5957
type kind =
6058
| Plain
6159
| Ocaml_script
@@ -358,21 +356,16 @@ end
358356
module Settings = struct
359357
type t =
360358
{ ancestor_vcs : Vcs.t option
361-
; recognize_jbuilder_projects : bool
362359
; execution_parameters : Execution_parameters.t
363360
}
364361

365362
let builtin_default =
366363
{ ancestor_vcs = None
367-
; recognize_jbuilder_projects = false
368364
; execution_parameters = Execution_parameters.builtin_default
369365
}
370366

371367
let set_ancestor_vcs x t = { t with ancestor_vcs = x }
372368

373-
let set_recognize_jbuilder_projects x t =
374-
{ t with recognize_jbuilder_projects = x }
375-
376369
let set_execution_parameters x t = { t with execution_parameters = x }
377370

378371
let t : t Memo.Build.t Fdecl.t = Fdecl.create Dyn.Encoder.opaque
@@ -464,26 +457,10 @@ end = struct
464457
(visited, init)
465458
end
466459

467-
let dune_file ~(dir_status : Sub_dirs.Status.t) ~recognize_jbuilder_projects
468-
~path ~files ~project =
460+
let dune_file ~(dir_status : Sub_dirs.Status.t) ~path ~files ~project =
469461
let file_exists =
470462
if dir_status = Data_only then
471463
None
472-
else if
473-
(not recognize_jbuilder_projects)
474-
&& String.Set.mem files Dune_file.jbuild_fname
475-
then
476-
User_error.raise
477-
~loc:
478-
(Loc.in_file
479-
(Path.source (Path.Source.relative path Dune_file.jbuild_fname)))
480-
[ Pp.text
481-
"jbuild files are no longer supported, please convert this file \
482-
to a dune file instead."
483-
; Pp.text
484-
"Note: You can use \"dune upgrade\" to convert your project to \
485-
dune."
486-
]
487464
else if
488465
Dune_project.accept_alternative_dune_file_name project
489466
&& String.Set.mem files Dune_file.alternative_fname
@@ -524,13 +501,7 @@ end = struct
524501

525502
let contents { Readdir.dirs; files } ~dirs_visited ~project ~path
526503
~(dir_status : Sub_dirs.Status.t) =
527-
let* recognize_jbuilder_projects =
528-
let+ settings = Settings.get () in
529-
settings.recognize_jbuilder_projects
530-
in
531-
let+ dune_file =
532-
dune_file ~dir_status ~recognize_jbuilder_projects ~files ~project ~path
533-
in
504+
let+ dune_file = dune_file ~dir_status ~files ~project ~path in
534505
let sub_dirs = Dune_file.sub_dirs dune_file in
535506
let dirs_visited, sub_dirs =
536507
Get_subdir.all ~dirs_visited ~dirs ~sub_dirs ~parent_status:dir_status
@@ -613,7 +584,6 @@ end = struct
613584
| None -> Memo.Build.return None
614585
| Some (parent_dir, dirs_visited, dir_status, virtual_) ->
615586
let dirs_visited = Dirs_visited.Per_fn.find dirs_visited path in
616-
let* settings = Settings.get () in
617587
let readdir =
618588
if virtual_ then
619589
Readdir.empty
@@ -628,8 +598,7 @@ end = struct
628598
else
629599
Option.value
630600
(Dune_project.load ~dir:path ~files:readdir.files
631-
~infer_from_opam_files:settings.recognize_jbuilder_projects
632-
~dir_status)
601+
~infer_from_opam_files:false ~dir_status)
633602
~default:parent_dir.project
634603
in
635604
let vcs = get_vcs ~default:parent_dir.vcs ~readdir ~path in

src/dune_engine/source_tree.mli

-6
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,6 @@ module Dune_file : sig
88

99
val alternative_fname : string
1010

11-
val jbuild_fname : string
12-
1311
type kind = private
1412
| Plain
1513
| Ocaml_script
@@ -82,10 +80,6 @@ module Settings : sig
8280
this is the vcs that will be used for the root. *)
8381
val set_ancestor_vcs : Vcs.t option -> t -> t
8482

85-
(** Whether we recognise jbuilder projects. This is only set to [true] by the
86-
upgrader. *)
87-
val set_recognize_jbuilder_projects : bool -> t -> t
88-
8983
(** The default execution parameters. *)
9084
val set_execution_parameters : Execution_parameters.t -> t -> t
9185
end

src/jbuild_support/atom.ml

-32
This file was deleted.

src/jbuild_support/atom.mli

-1
This file was deleted.

src/jbuild_support/dune

-6
This file was deleted.

src/jbuild_support/lexer.mli

-1
This file was deleted.

0 commit comments

Comments
 (0)