Skip to content

Commit f489068

Browse files
committed
[Opam] Don't generate the dune-site build part when not needed
Fixes #4849 Signed-off-by: François Bobot <[email protected]>
1 parent 6b69c61 commit f489068

File tree

5 files changed

+74
-27
lines changed

5 files changed

+74
-27
lines changed

otherlibs/site/test/run.t

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -150,11 +150,10 @@ Test with an opam like installation
150150
name
151151
"-j"
152152
jobs
153-
"--promote-install-files"
154-
"false"
155153
"@install"
156154
"@runtest" {with-test}
157155
"@doc" {with-doc}
156+
"--promote-install-files=false"
158157
]
159158
["dune" "install" "-p" name "--create-install-files" name]
160159
]

src/dune_engine/dune_project.ml

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -293,12 +293,15 @@ module Extension = struct
293293
let register_deleted ~name ~deleted_in =
294294
Table.add_exn extensions name (Deleted_in deleted_in)
295295

296-
let register_simple syntax stanzas =
296+
let register_unit syntax stanzas =
297297
let unit_stanzas =
298298
let+ r = stanzas in
299299
((), r)
300300
in
301-
let (_ : unit t) = register syntax unit_stanzas Unit.to_dyn in
301+
register syntax unit_stanzas Unit.to_dyn
302+
303+
let register_simple syntax stanzas =
304+
let (_ : unit t) = register_unit syntax stanzas in
302305
()
303306

304307
let instantiate ~dune_lang_ver ~loc ~parse_args (name_loc, name) (ver_loc, ver)
@@ -841,10 +844,10 @@ let executables_implicit_empty_intf t = t.executables_implicit_empty_intf
841844

842845
let accept_alternative_dune_file_name t = t.accept_alternative_dune_file_name
843846

844-
let () =
845-
let open Dune_lang.Decoder in
846-
Extension.register_simple Action_plugin.syntax (return []);
847-
Extension.register_simple Section.dune_site_syntax (return [])
847+
let () = Extension.register_simple Action_plugin.syntax (return [])
848+
849+
let dune_site_extension =
850+
Extension.register_unit Section.dune_site_syntax (return [])
848851

849852
let strict_package_deps t = t.strict_package_deps
850853

src/dune_engine/dune_project.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -175,3 +175,5 @@ val info : t -> Package.Info.t
175175
[dune-project] file. *)
176176
val update_execution_parameters :
177177
t -> Execution_parameters.t -> Execution_parameters.t
178+
179+
val dune_site_extension : unit Extension.t

src/dune_rules/opam_create.ml

Lines changed: 38 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -43,31 +43,50 @@ let default_build_command =
4343
]
4444
|}))
4545
and from_2_9 =
46-
lazy
47-
(Opam_file.parse_value
48-
(Lexbuf.from_string ~fname:"<internal>"
49-
{|
50-
[
51-
[ "dune" "subst" ] {dev}
52-
[ "dune" "build" "-p" name "-j" jobs "--promote-install-files" "false"
46+
let fname = "<internal>" in
47+
let parse s = lazy (Opam_file.parse_value (Lexbuf.from_string ~fname s)) in
48+
let subst = parse {| [ "dune" "subst" ] {dev} |} in
49+
let build =
50+
parse
51+
{|
52+
[ "dune" "build" "-p" name "-j" jobs
5353
"@install"
5454
"@runtest" {with-test}
5555
"@doc" {with-doc}
5656
]
57-
[ "dune" "install" "-p" name "--create-install-files" name ]
58-
]
59-
|}))
57+
|}
58+
in
59+
let install =
60+
parse {| [ "dune" "install" "-p" name "--create-install-files" name ] |}
61+
in
62+
fun ~with_sites ->
63+
let dumb_pos = (fname, 0, 0) in
64+
if with_sites then
65+
let build =
66+
match Lazy.force build with
67+
| OpamParserTypes.List (op, l) ->
68+
OpamParserTypes.List
69+
(op, l @ [ String (op, "--promote-install-files=false") ])
70+
| _ -> assert false
71+
in
72+
OpamParserTypes.List
73+
(dumb_pos, [ Lazy.force subst; build; Lazy.force install ])
74+
else
75+
OpamParserTypes.List (dumb_pos, [ Lazy.force subst; Lazy.force build ])
6076
in
6177
fun project ->
62-
Lazy.force
63-
(if Dune_project.dune_version project < (1, 11) then
64-
before_1_11
65-
else if Dune_project.dune_version project < (2, 7) then
66-
from_1_11_before_2_7
67-
else if Dune_project.dune_version project < (2, 9) then
68-
from_2_7
69-
else
70-
from_2_9)
78+
if Dune_project.dune_version project < (1, 11) then
79+
Lazy.force before_1_11
80+
else if Dune_project.dune_version project < (2, 7) then
81+
Lazy.force from_1_11_before_2_7
82+
else if Dune_project.dune_version project < (2, 9) then
83+
Lazy.force from_2_7
84+
else
85+
from_2_9
86+
~with_sites:
87+
(Option.is_some
88+
(Dune_project.find_extension_args project
89+
Dune_project.dune_site_extension))
7190

7291
let package_fields
7392
{ Package.synopsis

test/blackbox-tests/test-cases/dune-project-meta/main.t/run.t

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -517,3 +517,27 @@ the doc dependencies:
517517
"something"
518518
"odoc" {with-doc}
519519
]
520+
521+
$ cat > dune-project <<EOF
522+
> (lang dune 2.9)
523+
> (name foo)
524+
> (generate_opam_files true)
525+
> (package (name foo))
526+
> EOF
527+
528+
$ dune build foo.opam
529+
$ grep -A15 ^build: foo.opam
530+
build: [
531+
["dune" "subst"] {dev}
532+
[
533+
"dune"
534+
"build"
535+
"-p"
536+
name
537+
"-j"
538+
jobs
539+
"@install"
540+
"@runtest" {with-test}
541+
"@doc" {with-doc}
542+
]
543+
]

0 commit comments

Comments
 (0)