Skip to content

Commit 513d902

Browse files
committed
refactor: add Tests variant to Ml_sources.Origin.t
Signed-off-by: Ali Caglayan <[email protected]>
1 parent eef3831 commit 513d902

File tree

3 files changed

+54
-18
lines changed

3 files changed

+54
-18
lines changed

src/dune_rules/ml_sources.ml

Lines changed: 52 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -5,23 +5,27 @@ module Origin = struct
55
type t =
66
| Library of Library.t
77
| Executables of Executables.t
8+
| Tests of Tests.t
89
| Melange of Melange_stanzas.Emit.t
910

1011
let loc = function
1112
| Library l -> l.buildable.loc
1213
| Executables e -> e.buildable.loc
14+
| Tests t -> t.exes.buildable.loc
1315
| Melange mel -> mel.loc
1416
;;
1517

1618
let preprocess = function
1719
| Library l -> l.buildable.preprocess
1820
| Executables e -> e.buildable.preprocess
21+
| Tests t -> t.exes.buildable.preprocess
1922
| Melange mel -> mel.preprocess
2023
;;
2124

2225
let to_dyn = function
2326
| Library _ -> Dyn.variant "Library" [ Dyn.Opaque ]
2427
| Executables _ -> Dyn.variant "Executables" [ Dyn.Opaque ]
28+
| Tests _ -> Dyn.variant "Tests" [ Dyn.Opaque ]
2529
| Melange _ -> Dyn.variant "Melange" [ Dyn.Opaque ]
2630
;;
2731
end
@@ -58,10 +62,11 @@ module Per_stanza = struct
5862
type groups =
5963
{ libraries : Library.t group_part list
6064
; executables : Executables.t group_part list
65+
; tests : Tests.t group_part list
6166
; melange_emits : Melange_stanzas.Emit.t group_part list
6267
}
6368

64-
let make { libraries = libs; executables = exes; melange_emits = emits } =
69+
let make { libraries = libs; executables = exes; tests; melange_emits = emits } =
6570
let libraries, libraries_by_obj_dir =
6671
List.fold_left
6772
libs
@@ -84,17 +89,29 @@ module Per_stanza = struct
8489
by_id, by_obj_dir)
8590
in
8691
let executables =
87-
match
88-
String.Map.of_list_map exes ~f:(fun (part : Executables.t group_part) ->
89-
let first_exe = snd (Nonempty_list.hd part.stanza.names) in
90-
let origin : Origin.t = Executables part.stanza in
91-
first_exe, (origin, part.modules, part.obj_dir))
92-
with
93-
| Ok x -> x
94-
| Error (name, _, part) ->
92+
let entries =
93+
List.concat
94+
[ List.map exes ~f:(fun (part : Executables.t group_part) ->
95+
let first_exe = snd (Nonempty_list.hd part.stanza.names) in
96+
let origin : Origin.t = Executables part.stanza in
97+
first_exe, (origin, part.modules, part.obj_dir, part.stanza.buildable.loc))
98+
; List.map tests ~f:(fun (part : Tests.t group_part) ->
99+
let first_exe = snd (Nonempty_list.hd part.stanza.exes.names) in
100+
let origin : Origin.t = Tests part.stanza in
101+
( first_exe
102+
, (origin, part.modules, part.obj_dir, part.stanza.exes.buildable.loc) ))
103+
]
104+
in
105+
match String.Map.of_list entries with
106+
| Ok map ->
107+
String.Map.map map ~f:(fun (origin, modules, obj_dir, _loc) ->
108+
origin, modules, obj_dir)
109+
| Error (name, (_, _, _, loc1), (_, _, _, loc2)) ->
95110
User_error.raise
96-
~loc:part.stanza.buildable.loc
97-
[ Pp.textf "Executable %S appears for the second time in this directory" name ]
111+
~loc:loc1
112+
[ Pp.textf "Executable %S appears for the second time in this directory" name
113+
; Pp.textf "Already defined at %s" (Loc.to_file_colon_line loc2)
114+
]
98115
in
99116
let melange_emits =
100117
match
@@ -118,6 +135,8 @@ module Per_stanza = struct
118135
by_path (Library part.stanza, part.dir) part.sources)
119136
; List.rev_concat_map exes ~f:(fun part ->
120137
by_path (Executables part.stanza, part.dir) part.sources)
138+
; List.rev_concat_map tests ~f:(fun part ->
139+
by_path (Tests part.stanza, part.dir) part.sources)
121140
; List.rev_concat_map emits ~f:(fun part ->
122141
by_path (Melange part.stanza, part.dir) part.sources)
123142
]
@@ -252,7 +271,7 @@ let find_origin (t : t) ~libs path =
252271
| Some origins ->
253272
Memo.List.filter_map origins ~f:(fun (origin, dir) ->
254273
match origin with
255-
| Executables _ | Melange _ -> Memo.return (Some origin)
274+
| Executables _ | Tests _ | Melange _ -> Memo.return (Some origin)
256275
| Library lib ->
257276
let src_dir = Path.drop_optional_build_context_src_exn (Path.build dir) in
258277
Lib.DB.available_by_lib_id libs (Local (Library.to_lib_id ~src_dir lib))
@@ -461,14 +480,18 @@ let modules_of_stanzas =
461480
| `Skip -> loop l acc
462481
| `Library y -> loop l { acc with libraries = y :: acc.libraries }
463482
| `Executables y -> loop l { acc with executables = y :: acc.executables }
483+
| `Tests y -> loop l { acc with tests = y :: acc.tests }
464484
| `Melange_emit y -> loop l { acc with melange_emits = y :: acc.melange_emits })
465485
in
466-
fun l -> loop l { libraries = []; executables = []; melange_emits = [] }
486+
fun l -> loop l { libraries = []; executables = []; tests = []; melange_emits = [] }
467487
in
468488
fun l ->
469-
let { Per_stanza.libraries; executables; melange_emits } = rev_filter_partition l in
489+
let { Per_stanza.libraries; executables; tests; melange_emits } =
490+
rev_filter_partition l
491+
in
470492
{ Per_stanza.libraries = List.rev libraries
471493
; executables = List.rev executables
494+
; tests = List.rev tests
472495
; melange_emits = List.rev melange_emits
473496
}
474497
in
@@ -496,6 +519,12 @@ let modules_of_stanzas =
496519
in
497520
`Executables { Per_stanza.stanza = exes; sources; modules; obj_dir; dir }
498521
in
522+
let make_tests ~dir ~expander ~modules ~project tests =
523+
let+ result = make_executables ~dir ~expander ~modules ~project tests.Tests.exes in
524+
match result with
525+
| `Executables group_part -> `Tests { group_part with stanza = tests }
526+
| _ -> assert false
527+
in
499528
fun stanzas ~expander ~project ~dir ~libs ~lookup_vlib ~modules ~include_subdirs ->
500529
Memo.parallel_map stanzas ~f:(fun stanza ->
501530
let enabled_if =
@@ -532,7 +561,7 @@ let modules_of_stanzas =
532561
let obj_dir = Library.obj_dir lib ~dir in
533562
`Library { Per_stanza.stanza = lib; sources; modules; dir; obj_dir }
534563
| Executables.T exes -> make_executables ~dir ~expander ~modules ~project exes
535-
| Tests.T { exes; _ } -> make_executables ~dir ~expander ~modules ~project exes
564+
| Tests.T tests -> make_tests ~dir ~expander ~modules ~project tests
536565
| Melange_stanzas.Emit.T mel ->
537566
let obj_dir = Obj_dir.make_melange_emit ~dir ~name:mel.target in
538567
let+ sources, modules =
@@ -652,9 +681,14 @@ let make
652681
part.stanza, part.modules, part.obj_dir)
653682
in
654683
let exes =
655-
List.map
656-
modules_of_stanzas.executables
657-
~f:(fun (part : _ Per_stanza.group_part) -> part.modules, part.obj_dir)
684+
List.concat
685+
[ List.map
686+
modules_of_stanzas.executables
687+
~f:(fun { Per_stanza.modules; obj_dir; _ } -> modules, obj_dir)
688+
; List.map
689+
modules_of_stanzas.tests
690+
~f:(fun { Per_stanza.modules; obj_dir; _ } -> modules, obj_dir)
691+
]
658692
in
659693
Artifacts_obj.make
660694
~dir

src/dune_rules/ml_sources.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Origin : sig
88
type t =
99
| Library of Library.t
1010
| Executables of Executables.t
11+
| Tests of Tests.t
1112
| Melange of Melange_stanzas.Emit.t
1213

1314
val preprocess : t -> Preprocess.With_instrumentation.t Preprocess.Per_module.t

src/dune_rules/top_module.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ let find_module sctx src =
4242
@@ fun () ->
4343
match origin with
4444
| Executables exes -> Exe_rules.rules ~sctx ~dir_contents ~scope ~expander exes
45+
| Tests tests -> Exe_rules.rules ~sctx ~dir_contents ~scope ~expander tests.exes
4546
| Library lib -> Lib_rules.rules lib ~sctx ~dir_contents ~expander ~scope
4647
| Melange mel ->
4748
Melange_rules.setup_emit_cmj_rules ~sctx ~dir_contents ~expander ~scope mel

0 commit comments

Comments
 (0)