Skip to content

Commit 68238a3

Browse files
Julowjonludlam
authored andcommitted
Fix generators test handling internal files
The generators tests were complaining about the '.formatted' directory created by Dune. This commit refactor the handling of input files to avoid this.
1 parent da5986d commit 68238a3

File tree

2 files changed

+117
-117
lines changed

2 files changed

+117
-117
lines changed

test/generators/gen_rules/gen_rules.ml

Lines changed: 56 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,7 @@
1+
let die s =
2+
prerr_endline s;
3+
exit 1
4+
15
let html_target_rule path : Gen_rules_lib.sexp =
26
List
37
[
@@ -63,40 +67,70 @@ let man_target_rule path : Gen_rules_lib.sexp =
6367
];
6468
]
6569

66-
let read_file_from_dir dir =
67-
let filenames =
68-
let arr = Sys.readdir dir in
69-
Array.sort String.compare arr;
70-
Array.to_list arr
71-
in
72-
let dir = Fpath.v dir in
73-
List.map (Fpath.( / ) dir) filenames
70+
(** Returns filenames, not paths. *)
71+
let read_files_from_dir dir =
72+
let arr = Sys.readdir (Fpath.to_string dir) in
73+
Array.sort String.compare arr;
74+
Array.to_list arr
7475

7576
let constraints =
7677
let open Gen_rules_lib in
7778
[
78-
(Fpath.v "stop_dead_link_doc.mli", Min "4.04");
79-
(Fpath.v "bugs_post_406.mli", Min "4.06");
80-
(Fpath.v "ocamlary.mli", Min "4.07");
81-
(Fpath.v "recent.mli", Min "4.09");
82-
(Fpath.v "labels.mli", Min "4.09");
83-
(Fpath.v "recent_impl.ml", Min "4.09");
84-
(Fpath.v "bugs_pre_410.ml", Max "4.09");
85-
(Fpath.v "module_type_subst.mli", Min "4.13");
79+
("stop_dead_link_doc.mli", Min "4.04");
80+
("bugs_post_406.mli", Min "4.06");
81+
("ocamlary.mli", Min "4.07");
82+
("recent.mli", Min "4.09");
83+
("labels.mli", Min "4.09");
84+
("recent_impl.ml", Min "4.09");
85+
("bugs_pre_410.ml", Max "4.09");
86+
("module_type_subst.mli", Min "4.13");
8687
]
8788

88-
let () =
89-
let paths = read_file_from_dir (Fpath.filename Gen_rules_lib.cases) in
90-
let paths =
91-
List.filter (fun p -> not (Gen_rules_lib.is_dot_ocamlformat p)) paths
89+
let test_cases_dir = Fpath.v "cases"
90+
91+
(** Make a test cases or return the empty list if the given file should be
92+
ignored. Might abort the program with an error. *)
93+
let make_test_case case_name =
94+
let input = Fpath.(/) test_cases_dir case_name in
95+
let mk odoc_prefix cmt_suffix =
96+
let base_out_path = Fpath.v (odoc_prefix ^ case_name) in
97+
let cmt =
98+
match cmt_suffix with
99+
| Some suf -> Some (Fpath.set_ext suf base_out_path)
100+
| None -> None
101+
in
102+
let odoc = Fpath.set_ext ".odoc" base_out_path in
103+
let odocl = Fpath.set_ext ".odocl" base_out_path in
104+
let enabledif =
105+
try Some (List.assoc case_name constraints) with Not_found -> None
106+
in
107+
{ Gen_rules_lib.input; cmt; odoc; odocl; enabledif }
92108
in
109+
match Fpath.get_ext input with
110+
| ".ml" -> [ mk "" (Some ".cmt") ]
111+
| ".mli" -> [ mk "" (Some ".cmti") ]
112+
| ".mld" -> [ mk "page-" None ]
113+
(* Dune creates directories starting with a dot, which result in an empty
114+
extension with Fpath. Also, there's [.ocamlformat]. *)
115+
| "" -> []
116+
| ext ->
117+
die
118+
(Format.asprintf
119+
"Don't know what to do with %a because of unrecognized %s extension."
120+
Fpath.pp input ext)
121+
122+
let read_test_cases () =
123+
read_files_from_dir test_cases_dir |> List.map make_test_case |> List.concat
124+
125+
let () =
126+
let cases = read_test_cases () in
93127
let stanzas =
94-
Gen_rules_lib.gen_rule constraints
128+
Gen_rules_lib.gen_rule
95129
[
96130
(html_target_rule, Fpath.v "html", Some "--flat");
97131
(latex_target_rule, Fpath.v "latex", None);
98132
(man_target_rule, Fpath.v "man", None);
99133
]
100-
paths
134+
cases
101135
in
102136
List.iter (Sexplib0.Sexp.pp Format.std_formatter) stanzas

test/generators/gen_rules_lib.ml

Lines changed: 61 additions & 95 deletions
Original file line numberDiff line numberDiff line change
@@ -2,11 +2,51 @@ type sexp = Sexplib0.Sexp.t = Atom of string | List of sexp list
22

33
type enabledif = Min of string | Max of string | MinMax of string * string
44

5+
type test_case = {
6+
input : Fpath.t;
7+
cmt : Fpath.t option; (** [None] for mld files. *)
8+
odoc : Fpath.t;
9+
odocl : Fpath.t;
10+
enabledif : enabledif option;
11+
}
12+
13+
let render_enabledif = function
14+
| Some (Min v) ->
15+
[
16+
List
17+
[
18+
Atom "enabled_if";
19+
List [ Atom ">="; Atom "%{ocaml_version}"; Atom v ];
20+
];
21+
]
22+
| Some (Max v) ->
23+
[
24+
List
25+
[
26+
Atom "enabled_if";
27+
List [ Atom "<="; Atom "%{ocaml_version}"; Atom v ];
28+
];
29+
]
30+
| Some (MinMax (min, max)) ->
31+
[
32+
List
33+
[
34+
Atom "enabled_if";
35+
List
36+
[
37+
Atom "and";
38+
List [ Atom ">="; Atom "%{ocaml_version}"; Atom min ];
39+
List [ Atom "<="; Atom "%{ocaml_version}"; Atom max ];
40+
];
41+
];
42+
]
43+
| None -> []
44+
545
let cu_target_rule enabledif dep_path target_path =
646
List
747
([
848
Atom "rule";
9-
List [ Atom "target"; Atom target_path ];
49+
List [ Atom "target"; Atom (Fpath.to_string target_path) ];
1050
List [ Atom "deps"; Atom (Fpath.to_string dep_path) ];
1151
List
1252
[
@@ -91,52 +131,29 @@ let mld_odoc_target_rule enabledif dep_path target_path =
91131
]
92132
@ enabledif)
93133

94-
let set_odocl_ext = Fpath.set_ext ".odocl"
95-
96-
let set_odoc_ext = Fpath.set_ext ".odoc"
97-
98-
let file_rule enabledif path ext =
99-
let cm_file = Fpath.set_ext ext path in
100-
let odoc_file = set_odoc_ext path in
101-
let odocl_file = set_odocl_ext path in
134+
let file_rule { input; odoc; odocl; enabledif; _ } cmt =
135+
let enabledif = render_enabledif enabledif in
102136
[
103-
cu_target_rule enabledif path (Fpath.basename cm_file);
104-
odoc_target_rule enabledif cm_file odoc_file;
105-
odocl_target_rule enabledif odoc_file odocl_file;
137+
cu_target_rule enabledif input cmt;
138+
odoc_target_rule enabledif cmt odoc;
139+
odocl_target_rule enabledif odoc odocl;
106140
]
107141

108-
let mld_file_rule enabledif path =
109-
let path' = Fpath.(v ("page-" ^ basename path)) in
110-
let odoc_file = set_odoc_ext path' in
111-
let odocl_file = set_odocl_ext path' in
142+
let mld_file_rule { input; odoc; odocl; enabledif; _ } =
143+
let enabledif = render_enabledif enabledif in
112144
[
113-
mld_odoc_target_rule enabledif path odoc_file;
114-
odocl_target_rule enabledif odoc_file odocl_file;
145+
mld_odoc_target_rule enabledif input odoc;
146+
odocl_target_rule enabledif odoc odocl;
115147
]
116148

117-
let die s =
118-
prerr_endline s;
119-
exit 1
120-
121149
let path' () f = Filename.quote (Fpath.to_string f)
122150

123151
let ext' () f = Filename.quote (Fpath.get_ext f)
124152

125-
let cases = Fpath.v "cases"
126-
127-
let is_dot_ocamlformat p = Fpath.filename p = ".ocamlformat"
128-
129-
let gen_rule_for_source_file enabledif path =
130-
let ext = Fpath.get_ext path in
131-
match ext with
132-
| ".ml" -> file_rule enabledif path ".cmt"
133-
| ".mli" -> file_rule enabledif path ".cmti"
134-
| ".mld" -> mld_file_rule enabledif path
135-
| _ ->
136-
die
137-
(Printf.sprintf
138-
"Don't know what to do with %a because of unrecognized %a extension."
139-
path' path ext' path)
153+
let gen_rule_for_source_file case =
154+
match case.cmt with
155+
| Some cmt -> file_rule case cmt
156+
| None -> mld_file_rule case
140157

141158
let odocls backend p =
142159
let path = Fpath.relativize ~root:backend p in
@@ -308,66 +325,15 @@ let gen_backend_rule enabledif backend_target_rules path =
308325
backend_target_rules
309326
|> List.flatten
310327

311-
let gen_rule enabledif backend_target_rules paths =
312-
let enabledif v =
313-
match List.assoc v enabledif with
314-
| exception Not_found -> []
315-
| Min v ->
316-
[
317-
List
318-
[
319-
Atom "enabled_if";
320-
List [ Atom ">="; Atom "%{ocaml_version}"; Atom v ];
321-
];
322-
]
323-
| Max v ->
324-
[
325-
List
326-
[
327-
Atom "enabled_if";
328-
List [ Atom "<="; Atom "%{ocaml_version}"; Atom v ];
329-
];
330-
]
331-
| MinMax (min, max) ->
332-
[
333-
List
334-
[
335-
Atom "enabled_if";
336-
List
337-
[
338-
Atom "and";
339-
List [ Atom ">="; Atom "%{ocaml_version}"; Atom min ];
340-
List [ Atom "<="; Atom "%{ocaml_version}"; Atom max ];
341-
];
342-
];
343-
]
344-
in
345-
let paths' =
346-
List.map
347-
(fun origp ->
348-
let path = Fpath.relativize ~root:cases origp in
349-
match path with
350-
| Some p ->
351-
let odocl =
352-
if Fpath.get_ext p = ".mld" then
353-
set_odocl_ext Fpath.(parent p / ("page-" ^ filename p))
354-
else set_odocl_ext Fpath.(parent p / filename p)
355-
in
356-
(origp, odocl, enabledif p)
357-
| None -> assert false)
358-
paths
359-
in
328+
let gen_rule backend_target_rules test_cases =
360329
List.concat
361330
[
362-
List.(
363-
concat
364-
(map
365-
(fun (path, _, enabledif) ->
366-
gen_rule_for_source_file enabledif path)
367-
paths'));
331+
List.(concat (map gen_rule_for_source_file test_cases));
368332
List.map
369-
(fun (_, p, enabledif) ->
370-
gen_backend_rule enabledif backend_target_rules p)
371-
paths'
333+
(fun case ->
334+
gen_backend_rule
335+
(render_enabledif case.enabledif)
336+
backend_target_rules case.odocl)
337+
test_cases
372338
|> List.flatten;
373339
]

0 commit comments

Comments
 (0)