Skip to content

Commit c185847

Browse files
committed
Driver: add a counter for compiling assets
1 parent 3f69941 commit c185847

File tree

3 files changed

+24
-9
lines changed

3 files changed

+24
-9
lines changed

src/driver/compile.ml

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -11,29 +11,34 @@ let mk_byhash (pkgs : Odoc_unit.t list) =
1111
Util.StringMap.empty pkgs
1212

1313
let init_stats (units : Odoc_unit.t list) =
14-
let total, total_impl, non_hidden, mlds, indexes =
14+
let total, total_impl, non_hidden, mlds, assets, indexes =
1515
List.fold_left
16-
(fun (total, total_impl, non_hidden, mlds, indexes) (unit : Odoc_unit.t) ->
16+
(fun (total, total_impl, non_hidden, mlds, assets, indexes)
17+
(unit : Odoc_unit.t) ->
1718
let total = match unit.kind with `Intf _ -> total + 1 | _ -> total in
1819
let total_impl =
1920
match unit.kind with `Impl _ -> total_impl + 1 | _ -> total_impl
2021
in
22+
let assets =
23+
match unit.kind with `Asset -> assets + 1 | _ -> assets
24+
in
2125
let indexes = Fpath.Set.add unit.index.output_file indexes in
2226
let non_hidden =
2327
match unit.kind with
2428
| `Intf { hidden = false; _ } -> non_hidden + 1
2529
| _ -> non_hidden
2630
in
2731
let mlds = match unit.kind with `Mld -> mlds + 1 | _ -> mlds in
28-
(total, total_impl, non_hidden, mlds, indexes))
29-
(0, 0, 0, 0, Fpath.Set.empty)
32+
(total, total_impl, non_hidden, mlds, assets, indexes))
33+
(0, 0, 0, 0, 0, Fpath.Set.empty)
3034
units
3135
in
3236

3337
Atomic.set Stats.stats.total_units total;
3438
Atomic.set Stats.stats.total_impls total_impl;
3539
Atomic.set Stats.stats.non_hidden_units non_hidden;
3640
Atomic.set Stats.stats.total_mlds mlds;
41+
Atomic.set Stats.stats.total_assets assets;
3742
Atomic.set Stats.stats.total_indexes (Fpath.Set.cardinal indexes)
3843

3944
open Eio.Std
@@ -155,6 +160,7 @@ let compile ?partial ~partial_dir ?linked_dir:_ (all : Odoc_unit.t list) =
155160
| `Asset ->
156161
Odoc.compile_asset ~output_dir:unit.output_dir ~parent_id:unit.parent_id
157162
~name:(Fpath.filename unit.input_file);
163+
Atomic.incr Stats.stats.compiled_assets;
158164
Ok unit
159165
| `Mld ->
160166
let includes = Fpath.Set.of_list unit.include_dirs in
@@ -199,7 +205,7 @@ let link : compiled list -> _ =
199205
(match c.kind with
200206
| `Intf _ -> Atomic.incr Stats.stats.linked_units
201207
| `Mld -> Atomic.incr Stats.stats.linked_mlds
202-
| `Asset -> () (* TODO *)
208+
| `Asset -> ()
203209
| `Impl _ -> Atomic.incr Stats.stats.linked_impls);
204210
c
205211
in

src/driver/odoc_driver.ml

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -451,6 +451,7 @@ let render_stats env nprocs =
451451
let total = Atomic.get Stats.stats.total_units in
452452
let total_impls = Atomic.get Stats.stats.total_impls in
453453
let total_mlds = Atomic.get Stats.stats.total_mlds in
454+
let total_assets = Atomic.get Stats.stats.total_assets in
454455
let total_indexes = Atomic.get Stats.stats.total_indexes in
455456
let bar message total =
456457
let open Progress.Line in
@@ -474,19 +475,22 @@ let render_stats env nprocs =
474475
dline "Compiling" total
475476
++ dline "Compiling impls" total_impls
476477
++ dline "Compiling pages" total_mlds
478+
++ dline "Compiling assets" total_assets
477479
++ dline "Linking" non_hidden
478480
++ dline "Linking impls" total_impls
479481
++ dline "Linking mlds" total_mlds
480482
++ dline "Indexes" total_indexes
481483
++ dline "HTML" (total_impls + non_hidden + total_mlds)
482484
++ line (procs nprocs)
483485
++ descriptions)
484-
(fun comp compimpl compmld link linkimpl linkmld indexes html procs descr ->
485-
let rec inner (a, b, c, d, e, f, i, g, h) =
486+
(fun comp compimpl compmld compassets link linkimpl linkmld indexes html
487+
procs descr ->
488+
let rec inner (a, b, c, j, d, e, f, i, g, h) =
486489
Eio.Time.sleep clock 0.1;
487490
let a' = Atomic.get Stats.stats.compiled_units in
488491
let b' = Atomic.get Stats.stats.compiled_impls in
489492
let c' = Atomic.get Stats.stats.compiled_mlds in
493+
let j' = Atomic.get Stats.stats.compiled_assets in
490494
let d' = Atomic.get Stats.stats.linked_units in
491495
let e' = Atomic.get Stats.stats.linked_impls in
492496
let f' = Atomic.get Stats.stats.linked_mlds in
@@ -499,16 +503,17 @@ let render_stats env nprocs =
499503
comp (a' - a);
500504
compimpl (b' - b);
501505
compmld (c' - c);
506+
compassets (j' - j);
502507
link (d' - d);
503508
linkimpl (e' - e);
504509
linkmld (f' - f);
505510
indexes (i' - i);
506511
html (g' - g);
507512
procs (h' - h);
508513
if g' < non_hidden + total_impls + total_mlds then
509-
inner (a', b', c', d', e', f', i', g', h')
514+
inner (a', b', c', j', d', e', f', i', g', h')
510515
in
511-
inner (0, 0, 0, 0, 0, 0, 0, 0, 0))
516+
inner (0, 0, 0, 0, 0, 0, 0, 0, 0, 0))
512517

513518
let run libs verbose packages_dir odoc_dir odocl_dir html_dir stats nb_workers
514519
odoc_bin voodoo package_name blessed dune_style =

src/driver/stats.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,11 +6,13 @@ type stats = {
66
mutable total_units : int Atomic.t;
77
mutable total_impls : int Atomic.t;
88
mutable total_mlds : int Atomic.t;
9+
mutable total_assets : int Atomic.t;
910
mutable total_indexes : int Atomic.t;
1011
mutable non_hidden_units : int Atomic.t;
1112
mutable compiled_units : int Atomic.t;
1213
mutable compiled_impls : int Atomic.t;
1314
mutable compiled_mlds : int Atomic.t;
15+
mutable compiled_assets : int Atomic.t;
1416
mutable linked_units : int Atomic.t;
1517
mutable linked_impls : int Atomic.t;
1618
mutable linked_mlds : int Atomic.t;
@@ -25,11 +27,13 @@ let stats =
2527
total_units = Atomic.make 0;
2628
total_impls = Atomic.make 0;
2729
total_mlds = Atomic.make 0;
30+
total_assets = Atomic.make 0;
2831
total_indexes = Atomic.make 0;
2932
non_hidden_units = Atomic.make 0;
3033
compiled_units = Atomic.make 0;
3134
compiled_impls = Atomic.make 0;
3235
compiled_mlds = Atomic.make 0;
36+
compiled_assets = Atomic.make 0;
3337
linked_units = Atomic.make 0;
3438
linked_impls = Atomic.make 0;
3539
linked_mlds = Atomic.make 0;

0 commit comments

Comments
 (0)