Skip to content

Commit 186c886

Browse files
committed
Enable bisect_ppx via dune-workspace
Signed-off-by: Stephanie You <[email protected]>
1 parent b1a42f6 commit 186c886

34 files changed

+194
-22
lines changed

.travis-ci.sh

+2-1
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,8 @@ opam_install_test_deps () {
3030
ocaml-migrate-parsetree \
3131
result.1.4 \
3232
utop.2.4.2 \
33-
mdx.1.6.0
33+
mdx.1.6.0 \
34+
bisect_ppx
3435
# We install Coq separatedly as to be more resistant w.r.t. the 10
3536
# minutes Travis timeout; the travis_wait hack doesn't work well
3637
# with Dune's current setup. Note that Travis caching should help

src/dune/context.ml

+10-5
Original file line numberDiff line numberDiff line change
@@ -250,7 +250,7 @@ let write_dot_dune_dir ~build_dir ~ocamlc ~ocaml_config_vars =
250250

251251
let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
252252
~host_context ~host_toolchain ~profile ~fdo_target_exe
253-
~dynamically_linked_foreign_archives =
253+
~dynamically_linked_foreign_archives ~bisect_enabled =
254254
let prog_not_found_in_path prog =
255255
Utils.program_not_found prog ~context:name ~loc:None
256256
in
@@ -485,6 +485,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
485485
; ccomp_type = Ocaml_config.ccomp_type ocfg
486486
; profile
487487
; ocaml_version = Ocaml_config.version_string ocfg
488+
; bisect_enabled
488489
}
489490
in
490491
if Option.is_some fdo_target_exe then
@@ -597,10 +598,10 @@ let extend_paths t ~env =
597598
Env.extend ~vars env
598599

599600
let default ~merlin ~env_nodes ~env ~targets ~fdo_target_exe
600-
~dynamically_linked_foreign_archives =
601+
~dynamically_linked_foreign_archives ~bisect_enabled =
601602
let path = Env.path env in
602603
create ~kind:Default ~path ~env ~env_nodes ~merlin ~targets ~fdo_target_exe
603-
~dynamically_linked_foreign_archives
604+
~dynamically_linked_foreign_archives ~bisect_enabled
604605

605606
let opam_version =
606607
let f opam =
@@ -631,7 +632,7 @@ let opam_version =
631632

632633
let create_for_opam ~root ~env ~env_nodes ~targets ~profile ~switch ~name
633634
~merlin ~host_context ~host_toolchain ~fdo_target_exe
634-
~dynamically_linked_foreign_archives =
635+
~dynamically_linked_foreign_archives ~bisect_enabled =
635636
let opam =
636637
match Memo.Lazy.force opam with
637638
| None -> Utils.program_not_found "opam" ~loc:None
@@ -682,6 +683,7 @@ let create_for_opam ~root ~env ~env_nodes ~targets ~profile ~switch ~name
682683
~kind:(Opam { root; switch })
683684
~profile ~targets ~path ~env ~env_nodes ~name ~merlin ~host_context
684685
~host_toolchain ~fdo_target_exe ~dynamically_linked_foreign_archives
686+
~bisect_enabled
685687

686688
let instantiate_context env (workspace : Workspace.t)
687689
~(context : Workspace.Context.t) ~host_context =
@@ -701,6 +703,7 @@ let instantiate_context env (workspace : Workspace.t)
701703
; loc = _
702704
; fdo_target_exe
703705
; dynamically_linked_foreign_archives
706+
; bisect_enabled
704707
} ->
705708
let merlin =
706709
workspace.merlin_context = Some (Workspace.Context.name context)
@@ -716,6 +719,7 @@ let instantiate_context env (workspace : Workspace.t)
716719
let env = extend_paths ~env paths in
717720
default ~env ~env_nodes ~profile ~targets ~name ~merlin ~host_context
718721
~host_toolchain ~fdo_target_exe ~dynamically_linked_foreign_archives
722+
~bisect_enabled
719723
| Opam
720724
{ base =
721725
{ targets
@@ -728,6 +732,7 @@ let instantiate_context env (workspace : Workspace.t)
728732
; loc = _
729733
; fdo_target_exe
730734
; dynamically_linked_foreign_archives
735+
; bisect_enabled
731736
}
732737
; switch
733738
; root
@@ -736,7 +741,7 @@ let instantiate_context env (workspace : Workspace.t)
736741
let env = extend_paths ~env paths in
737742
create_for_opam ~root ~env_nodes ~env ~profile ~switch ~name ~merlin
738743
~targets ~host_context ~host_toolchain:toolchain ~fdo_target_exe
739-
~dynamically_linked_foreign_archives
744+
~dynamically_linked_foreign_archives ~bisect_enabled
740745

741746
module Create = struct
742747
module Output = struct

src/dune/dune_file.ml

+39-1
Original file line numberDiff line numberDiff line change
@@ -214,6 +214,24 @@ module Preprocess_map = struct
214214
List.fold_left (Preprocess.pps pp) ~init:acc ~f:(fun acc (loc, pp) ->
215215
Lib_name.Map.set acc pp loc))
216216
|> Lib_name.Map.foldi ~init:[] ~f:(fun pp loc acc -> (loc, pp) :: acc)
217+
218+
let add_bisect t =
219+
let bisect_ppx =
220+
let bisect_name = Lib_name.parse_string_exn (Loc.none, "bisect_ppx") in
221+
(Loc.none, bisect_name)
222+
in
223+
Per_module.map t ~f:(fun pp ->
224+
match pp with
225+
| Preprocess.No_preprocessing ->
226+
let loc = Loc.none in
227+
let pps = [ bisect_ppx ] in
228+
let flags = [] in
229+
let staged = false in
230+
Preprocess.Pps { loc; pps; flags; staged }
231+
| Preprocess.Pps { loc; pps; flags; staged } ->
232+
let pps = bisect_ppx :: pps in
233+
Preprocess.Pps { loc; pps; flags; staged }
234+
| _ -> pp (* TODO: decide if this is the correct behavior *) )
217235
end
218236

219237
module Lint = struct
@@ -359,6 +377,7 @@ module Buildable = struct
359377
; flags : Ocaml_flags.Spec.t
360378
; js_of_ocaml : Js_of_ocaml.t
361379
; allow_overlapping_dependencies : bool
380+
; bisect_ppx : bool
362381
}
363382

364383
let decode ~in_library ~allow_re_export =
@@ -424,6 +443,8 @@ module Buildable = struct
424443
field "js_of_ocaml" Js_of_ocaml.decode ~default:Js_of_ocaml.default
425444
and+ allow_overlapping_dependencies =
426445
field_b "allow_overlapping_dependencies"
446+
and+ bisect_ppx =
447+
field_b "bisect_ppx" ~check:(Dune_lang.Syntax.since Stanza.syntax (2, 5))
427448
and+ version = Dune_lang.Syntax.get_exn Stanza.syntax in
428449
let foreign_stubs =
429450
foreign_stubs
@@ -468,6 +489,7 @@ module Buildable = struct
468489
; flags
469490
; js_of_ocaml
470491
; allow_overlapping_dependencies
492+
; bisect_ppx
471493
}
472494

473495
let has_foreign t =
@@ -481,6 +503,12 @@ module Buildable = struct
481503
Per_module.get t.preprocess dummy_name
482504
else
483505
Preprocess.No_preprocessing
506+
507+
let preprocess t ~(lib_config: Lib_config.t) =
508+
if t.bisect_ppx && lib_config.bisect_enabled then
509+
Preprocess_map.add_bisect t.preprocess
510+
else
511+
t.preprocess
484512
end
485513

486514
module Public_lib = struct
@@ -1031,7 +1059,17 @@ module Library = struct
10311059
let synopsis = conf.synopsis in
10321060
let sub_systems = conf.sub_systems in
10331061
let ppx_runtime_deps = conf.ppx_runtime_libraries in
1034-
let pps = Preprocess_map.pps conf.buildable.preprocess in
1062+
let pps =
1063+
let pps_without_bisect = Preprocess_map.pps conf.buildable.preprocess in
1064+
if lib_config.bisect_enabled && conf.buildable.bisect_ppx then
1065+
let bisect_ppx =
1066+
let bisect_name = Lib_name.parse_string_exn (Loc.none, "bisect_ppx") in
1067+
(Loc.none, bisect_name)
1068+
in
1069+
bisect_ppx :: pps_without_bisect
1070+
else
1071+
pps_without_bisect
1072+
in
10351073
let virtual_deps = conf.virtual_deps in
10361074
let dune_version = Some conf.dune_version in
10371075
let implements = conf.implements in

src/dune/dune_file.mli

+4
Original file line numberDiff line numberDiff line change
@@ -98,13 +98,17 @@ module Buildable : sig
9898
; flags : Ocaml_flags.Spec.t
9999
; js_of_ocaml : Js_of_ocaml.t
100100
; allow_overlapping_dependencies : bool
101+
; bisect_ppx : bool
101102
}
102103

103104
(** Check if the buildable has any foreign stubs or archives. *)
104105
val has_foreign : t -> bool
105106

106107
(** Preprocessing specification used by all modules or [No_preprocessing] *)
107108
val single_preprocess : t -> Preprocess.t
109+
110+
(** Includes bisect_ppx if specified by [lib_config] *)
111+
val preprocess : t -> lib_config:Lib_config.t -> Preprocess_map.t
108112
end
109113

110114
module Public_lib : sig

src/dune/exe_rules.ml

+11-5
Original file line numberDiff line numberDiff line change
@@ -15,9 +15,13 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
1515
let ml_sources = Dir_contents.ocaml dir_contents in
1616
Ml_sources.modules_of_executables ml_sources ~first_exe ~obj_dir
1717
in
18+
let ctx = SC.context sctx in
19+
let preprocess =
20+
Dune_file.Buildable.preprocess exes.buildable ~lib_config:ctx.lib_config
21+
in
1822
let pp =
1923
Preprocessing.make sctx ~dir ~dep_kind:Required ~scope ~expander
20-
~preprocess:exes.buildable.preprocess
24+
~preprocess
2125
~preprocessor_deps:exes.buildable.preprocessor_deps
2226
~lint:exes.buildable.lint ~lib_name:None
2327
in
@@ -44,7 +48,6 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
4448
(Module_name.to_string mod_name)
4549
])
4650
in
47-
let ctx = SC.context sctx in
4851
let explicit_js_mode = Dune_project.explicit_js_mode (Scope.project scope) in
4952
let linkages =
5053
let module L = Dune_file.Executables.Link_mode in
@@ -170,11 +173,14 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
170173
let rules ~sctx ~dir ~dir_contents ~scope ~expander
171174
(exes : Dune_file.Executables.t) =
172175
let dune_version = Scope.project scope |> Dune_project.dune_version in
176+
let ctx = SC.context sctx in
177+
let pps =
178+
Dune_file.Preprocess_map.pps
179+
(Dune_file.Buildable.preprocess exes.buildable ~lib_config:ctx.lib_config)
180+
in
173181
let compile_info =
174182
Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) exes.names
175-
exes.buildable.libraries
176-
~pps:(Dune_file.Preprocess_map.pps exes.buildable.preprocess)
177-
~dune_version
183+
exes.buildable.libraries ~pps ~dune_version
178184
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
179185
~variants:exes.variants ~optional:exes.optional
180186
~forbidden_libraries:exes.forbidden_libraries

src/dune/install_rules.ml

+8-4
Original file line numberDiff line numberDiff line change
@@ -133,7 +133,7 @@ end = struct
133133
(Some loc, Install.Entry.make Stublibs a))
134134
]
135135

136-
let keep_if ~external_lib_deps_mode expander =
136+
let keep_if ~(ctx : Context.t) ~external_lib_deps_mode expander =
137137
if external_lib_deps_mode then
138138
fun ~scope:_ ->
139139
Option.some
@@ -155,10 +155,14 @@ end = struct
155155
let dune_version =
156156
Scope.project scope |> Dune_project.dune_version
157157
in
158+
let pps =
159+
Dune_file.Preprocess_map.pps
160+
(Dune_file.Buildable.preprocess exes.buildable
161+
~lib_config:ctx.lib_config)
162+
in
158163
Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope)
159164
exes.names exes.buildable.libraries
160-
~pps:(Dune_file.Preprocess_map.pps exes.buildable.preprocess)
161-
~dune_version
165+
~pps ~dune_version
162166
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
163167
~variants:exes.variants ~optional:exes.optional
164168
in
@@ -175,7 +179,7 @@ end = struct
175179
let ctx = Super_context.context sctx in
176180
let stanzas = Super_context.stanzas sctx in
177181
let external_lib_deps_mode = !Clflags.external_lib_deps_mode in
178-
let keep_if = keep_if ~external_lib_deps_mode in
182+
let keep_if = keep_if ~ctx ~external_lib_deps_mode in
179183
let init =
180184
Super_context.packages sctx
181185
|> Package.Name.Map.map ~f:(fun (pkg : Package.t) ->

src/dune/lib_config.ml

+1
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ type t =
1414
; ccomp_type : Ocaml_config.Ccomp_type.t
1515
; profile : Profile.t
1616
; ocaml_version : string
17+
; bisect_enabled : bool
1718
}
1819

1920
let var_map =

src/dune/lib_config.mli

+1
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ type t =
1414
; ccomp_type : Ocaml_config.Ccomp_type.t
1515
; profile : Profile.t
1616
; ocaml_version : string
17+
; bisect_enabled : bool
1718
}
1819

1920
val allowed_in_enabled_if : (string * Dune_lang.Syntax.Version.t) list

src/dune/lib_rules.ml

+5-2
Original file line numberDiff line numberDiff line change
@@ -340,10 +340,14 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope
340340
let flags = Super_context.ocaml_flags sctx ~dir lib.buildable in
341341
let obj_dir = Library.obj_dir ~dir lib in
342342
let vimpl = Virtual_rules.impl sctx ~lib ~scope in
343+
let ctx = Super_context.context sctx in
344+
let preprocess =
345+
Dune_file.Buildable.preprocess lib.buildable ~lib_config:ctx.lib_config
346+
in
343347
(* Preprocess before adding the alias module as it doesn't need preprocessing *)
344348
let pp =
345349
Preprocessing.make sctx ~dir ~dep_kind ~scope
346-
~preprocess:lib.buildable.preprocess ~expander
350+
~preprocess ~expander
347351
~preprocessor_deps:lib.buildable.preprocessor_deps
348352
~lint:lib.buildable.lint
349353
~lib_name:(Some (snd lib.name))
@@ -354,7 +358,6 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope
354358
let modules = Vimpl.impl_modules vimpl modules in
355359
let requires_compile = Lib.Compile.direct_requires compile_info in
356360
let requires_link = Lib.Compile.requires_link compile_info in
357-
let ctx = Super_context.context sctx in
358361
let dynlink =
359362
Dynlink_supported.get lib.dynlink ctx.supports_shared_libraries
360363
in

src/dune/super_context.ml

+6-2
Original file line numberDiff line numberDiff line change
@@ -396,10 +396,14 @@ let get_installed_binaries stanzas ~(context : Context.t) =
396396
let compile_info =
397397
let project = Scope.project d.scope in
398398
let dune_version = Dune_project.dune_version project in
399+
let pps =
400+
Dune_file.Preprocess_map.pps
401+
(Dune_file.Buildable.preprocess exes.buildable
402+
~lib_config:context.lib_config)
403+
in
399404
Lib.DB.resolve_user_written_deps_for_exes (Scope.libs d.scope)
400405
exes.names exes.buildable.libraries
401-
~pps:(Dune_file.Preprocess_map.pps exes.buildable.preprocess)
402-
~dune_version
406+
~pps ~dune_version
403407
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
404408
~variants:exes.variants ~optional:exes.optional
405409
in

src/dune/virtual_rules.ml

+6-2
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,7 @@ let setup_copy_rules_for_impl ~sctx ~dir vimpl =
7474
Modules.iter_no_vlib vlib_modules ~f:(fun m -> copy_objs m)
7575

7676
let impl sctx ~(lib : Dune_file.Library.t) ~scope =
77+
let ctx = Super_context.context sctx in
7778
Option.map lib.implements ~f:(fun (loc, implements) ->
7879
match Lib.DB.find (Scope.libs scope) implements with
7980
| None ->
@@ -108,10 +109,13 @@ let impl sctx ~(lib : Dune_file.Library.t) ~scope =
108109
let dir = Lib_info.src_dir info in
109110
Dir_contents.get sctx ~dir
110111
in
112+
let preprocess =
113+
Dune_file.Buildable.preprocess lib.buildable
114+
~lib_config:ctx.lib_config
115+
in
111116
let modules =
112117
let pp_spec =
113-
Pp_spec.make lib.buildable.preprocess
114-
(Super_context.context sctx).version
118+
Pp_spec.make preprocess (Super_context.context sctx).version
115119
in
116120
Dir_contents.ocaml dir_contents
117121
|> Ml_sources.modules_of_library ~name

src/dune/workspace.ml

+8
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ module Context = struct
4949
; paths : (string * Ordered_set_lang.t) list
5050
; fdo_target_exe : Path.t option
5151
; dynamically_linked_foreign_archives : bool
52+
; bisect_enabled : bool
5253
}
5354

5455
let to_dyn = Dyn.Encoder.opaque
@@ -64,6 +65,7 @@ module Context = struct
6465
; paths
6566
; fdo_target_exe
6667
; dynamically_linked_foreign_archives
68+
; bisect_enabled
6769
} t =
6870
Profile.equal profile t.profile
6971
&& List.equal Target.equal targets t.targets
@@ -77,6 +79,7 @@ module Context = struct
7779
&& Option.equal Path.equal fdo_target_exe t.fdo_target_exe
7880
&& Bool.equal dynamically_linked_foreign_archives
7981
t.dynamically_linked_foreign_archives
82+
&& Bool.equal bisect_enabled t.bisect_enabled
8083

8184
let fdo_suffix t =
8285
match t.fdo_target_exe with
@@ -133,6 +136,9 @@ module Context = struct
133136
field "paths" ~default:[]
134137
( Dune_lang.Syntax.since Stanza.syntax (1, 12)
135138
>>> map ~f (repeat (pair (located string) Ordered_set_lang.decode)) )
139+
and+ bisect_enabled =
140+
field ~default:false "bisect_enabled"
141+
(Dune_lang.Syntax.since syntax (2, 5) >>> bool)
136142
and+ loc = loc in
137143
Option.iter host_context ~f:(fun _ ->
138144
match targets with
@@ -153,6 +159,7 @@ module Context = struct
153159
; paths
154160
; fdo_target_exe
155161
; dynamically_linked_foreign_archives
162+
; bisect_enabled
156163
}
157164
end
158165

@@ -293,6 +300,7 @@ module Context = struct
293300
; paths = []
294301
; fdo_target_exe = None
295302
; dynamically_linked_foreign_archives = true
303+
; bisect_enabled = false
296304
}
297305
end
298306

0 commit comments

Comments
 (0)