@@ -22,23 +22,34 @@ let ws = [' ' '\t']+
2222let hash = ['0' - '9' 'a' - 'z' '-' ]+
2323let name = ['A' - 'Z' ] ['A' - 'Z' 'a' - 'z' '0' - '9' '_' ]*
2424
25- rule ocamlobjinfo acc = parse
26- | " Interfaces imported:" newline { intfs acc lexbuf }
27- | " Implementations imported:" newline { impls acc lexbuf }
28- | _ { ocamlobjinfo acc lexbuf }
25+ rule ocamlobjinfo acc_units acc = parse
26+ | " Interfaces imported:" newline { intfs acc_units acc lexbuf }
27+ | " Implementations imported:" newline { impls acc_units acc lexbuf }
28+ | _ { ocamlobjinfo acc_units acc lexbuf }
29+ | eof { acc :: acc_units }
30+ and intfs acc_units acc = parse
31+ | ws hash ws (name as name) newline { intfs acc_units (add_intf acc name) lexbuf }
32+ | " Implementations imported:" newline { impls acc_units acc lexbuf }
33+ | " File " [^ '\n' ]+ newline { ocamlobjinfo (acc :: acc_units) empty lexbuf }
34+ | _ | eof { acc :: acc_units }
35+ and impls acc_units acc = parse
36+ | ws hash ws (name as name) newline { impls acc_units (add_impl acc name) lexbuf }
37+ | " File " [^ '\n' ]+ newline { ocamlobjinfo (acc :: acc_units) empty lexbuf }
38+ | _ | eof { acc :: acc_units }
39+
40+ and archive acc = parse
41+ | " Unit name:" ws (name as name) { archive (Module_name.Unique.Set. add acc (Module_name.Unique. of_string name)) lexbuf }
42+ | _ { archive acc lexbuf }
2943 | eof { acc }
30- and intfs acc = parse
31- | ws hash ws (name as name) newline { intfs (add_intf acc name) lexbuf }
32- | " Implementations imported:" newline { impls acc lexbuf }
33- | _ | eof { acc }
34- and impls acc = parse
35- | ws hash ws (name as name) newline { impls (add_impl acc name) lexbuf }
36- | _ | eof { acc }
3744
3845{
39- let parse s = ocamlobjinfo empty (Lexing. from_string s)
46+ let parse s = Lexing. from_string s |> ocamlobjinfo [] empty |> List. rev
47+
48+ let parse_archive s =
49+ Lexing. from_string s
50+ |> archive Module_name.Unique.Set. empty
4051
41- let rules (ocaml : Ocaml_toolchain.t ) ~dir ~sandbox ~unit =
52+ let rules (ocaml : Ocaml_toolchain.t ) ~dir ~sandbox ~units =
4253 let no_approx =
4354 if Ocaml.Version. ooi_supports_no_approx ocaml.version then
4455 [Command.Args. A " -no-approx" ]
@@ -52,7 +63,9 @@ let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
5263 []
5364 in
5465 let observing_facts =
55- Dep.Facts. singleton (Dep. file unit ) (Dep.Fact. nothing)
66+ List. map units ~f: (fun unit ->
67+ Dep.Facts. singleton (Dep. file unit ) (Dep.Fact. nothing))
68+ |> Dep.Facts. union_all
5669 in
5770 let open Action_builder.O in
5871 let * action =
@@ -61,7 +74,7 @@ let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
6174 (List. concat
6275 [ no_approx
6376 ; no_code
64- ; [ Dep unit ]
77+ ; [ Deps units ]
6578 ])
6679 in
6780 (Dune_engine.Build_system. execute_action_stdout
@@ -73,4 +86,24 @@ let rules (ocaml : Ocaml_toolchain.t) ~dir ~sandbox ~unit =
7386 }
7487 |> Action_builder. of_memo)
7588 >> | parse
89+
90+ let archive_rules (ocaml : Ocaml_toolchain.t ) ~dir ~sandbox ~archive =
91+ let observing_facts =
92+ Dep.Facts. singleton (Dep. file archive) (Dep.Fact. nothing)
93+ in
94+ let open Action_builder.O in
95+ let * action =
96+ Command. run' ?sandbox
97+ ~dir: (Path. build dir) ocaml.ocamlobjinfo
98+ [ Dep archive ]
99+ in
100+ (Dune_engine.Build_system. execute_action_stdout
101+ ~observing_facts
102+ { Rule.Anonymous_action. action
103+ ; loc = Loc. none
104+ ; dir
105+ ; alias = None
106+ }
107+ |> Action_builder. of_memo)
108+ >> | parse_archive
76109}
0 commit comments