OILS / benchmarks / report.R View on Github | oilshell.org

1341 lines, 927 significant
1#!/usr/bin/env Rscript
2#
3# benchmarks/report.R -- Analyze data collected by shell scripts.
4#
5# Usage:
6# benchmarks/report.R OUT_DIR [TIMES_CSV...]
7
8# Suppress warnings about functions masked from 'package:stats' and 'package:base'
9# filter, lag
10# intersect, setdiff, setequal, union
11library(dplyr, warn.conflicts = FALSE)
12library(tidyr) # spread()
13library(stringr)
14
15source('benchmarks/common.R')
16
17options(stringsAsFactors = F)
18
19# For pretty printing
20commas = function(x) {
21 format(x, big.mark=',')
22}
23
24sourceUrl = function(path) {
25 sprintf('https://github.com/oilshell/oil/blob/master/%s', path)
26}
27
28# Takes a filename, not a path.
29sourceUrl2 = function(filename) {
30 sprintf(
31 'https://github.com/oilshell/oil/blob/master/benchmarks/testdata/%s',
32 filename)
33}
34
35mycppUrl = function(name) {
36 sprintf('https://github.com/oilshell/oil/blob/master/mycpp/examples/%s.py', name)
37}
38
39genUrl = function(name) {
40 sprintf('../../_gen/mycpp/examples/%s.mycpp.cc', name)
41}
42
43
44# TODO: Set up cgit because Github links are slow.
45benchmarkDataLink = function(subdir, name, suffix) {
46 #sprintf('../../../../benchmark-data/shell-id/%s', shell_id)
47 sprintf('https://github.com/oilshell/benchmark-data/blob/master/%s/%s%s',
48 subdir, name, suffix)
49}
50
51provenanceLink = function(subdir, name, suffix) {
52 sprintf('../%s/%s%s', subdir, name, suffix)
53}
54
55
56GetOshLabel = function(shell_hash, prov_dir) {
57 ### Given a string, return another string.
58
59 path = sprintf('%s/shell-id/osh-%s/sh-path.txt', prov_dir, shell_hash)
60
61 if (file.exists(path)) {
62 Log('Reading %s', path)
63 lines = readLines(path)
64 if (length(grep('_bin/osh', lines)) > 0) {
65 label = 'osh-ovm'
66 } else if (length(grep('bin/osh', lines)) > 0) {
67 label = 'osh-cpython'
68 } else if (length(grep('_bin/.*/osh', lines)) > 0) {
69 label = 'osh-native'
70 } else {
71 stop("Expected _bin/osh, bin/osh, or _bin/.*/osh")
72 }
73 } else {
74 stop(sprintf("%s doesn't exist", path))
75 }
76 return(label)
77}
78
79opt_suffix1 = '_bin/cxx-opt/osh'
80opt_suffix2 = '_bin/cxx-opt-sh/osh'
81
82ShellLabels = function(shell_name, shell_hash, num_hosts) {
83 ### Given 2 vectors, return a vector of readable labels.
84
85 # TODO: Clean up callers. Some metrics all this function with a
86 # shell/runtime BASENAME, and others a PATH
87 # - e.g. ComputeReport calls this with runtime_name which is actually a PATH
88
89 #Log('name %s', shell_name)
90 #Log('hash %s', shell_hash)
91
92 if (num_hosts == 1) {
93 prov_dir = '_tmp'
94 } else {
95 prov_dir = '../benchmark-data/'
96 }
97
98 labels = c()
99 for (i in 1:length(shell_name)) {
100 sh = shell_name[i]
101 if (sh == 'osh') {
102 label = GetOshLabel(shell_hash[i], prov_dir)
103
104 } else if (endsWith(sh, opt_suffix1) || endsWith(sh, opt_suffix2)) {
105 label = 'opt/osh'
106
107 } else if (endsWith(sh, '_bin/cxx-opt+bumpleak/osh')) {
108 label = 'bumpleak/osh'
109
110 } else {
111 label = sh
112 }
113
114 Log('[%s] [%s]', shell_name[i], label)
115 labels = c(labels, label)
116 }
117
118 return(labels)
119}
120
121# Simple version of the above, used by benchmarks/gc
122ShellLabelFromPath = function(sh_path) {
123 labels = c()
124 for (i in 1:length(sh_path)) {
125 sh = sh_path[i]
126
127 if (endsWith(sh, opt_suffix1) || endsWith(sh, opt_suffix2)) {
128 # the opt binary is osh-native
129 label = 'osh-native'
130
131 } else if (endsWith(sh, '_bin/cxx-opt+bumpleak/osh')) {
132 label = 'bumpleak/osh'
133
134 } else if (endsWith(sh, '_bin/osh')) { # the app bundle
135 label = 'osh-ovm'
136
137 } else if (endsWith(sh, 'bin/osh')) {
138 label = 'osh-cpython'
139
140 } else {
141 label = sh
142 }
143 labels = c(labels, label)
144 }
145 return(labels)
146}
147
148DistinctHosts = function(t) {
149 t %>% distinct(host_name, host_hash) -> distinct_hosts
150 # The label is just the name
151 distinct_hosts$host_label = distinct_hosts$host_name
152 return(distinct_hosts)
153}
154
155DistinctShells = function(t, num_hosts = -1) {
156 t %>% distinct(shell_name, shell_hash) -> distinct_shells
157
158 Log('')
159 Log('Labeling shells')
160
161 # Calculate it if not passed
162 if (num_hosts == -1) {
163 num_hosts = nrow(DistinctHosts(t))
164 }
165
166 distinct_shells$shell_label = ShellLabels(distinct_shells$shell_name,
167 distinct_shells$shell_hash,
168 num_hosts)
169 return(distinct_shells)
170}
171
172ParserReport = function(in_dir, out_dir) {
173 times = read.csv(file.path(in_dir, 'times.csv'))
174 lines = read.csv(file.path(in_dir, 'lines.csv'))
175 raw_data = read.csv(file.path(in_dir, 'raw-data.csv'))
176
177 cachegrind = readTsv(file.path(in_dir, 'cachegrind.tsv'))
178
179 # For joining by filename
180 lines_by_filename = tibble(
181 num_lines = lines$num_lines,
182 filename = basename(lines$path)
183 )
184
185 # Remove failures
186 times %>% filter(status == 0) %>% select(-c(status)) -> times
187 cachegrind %>% filter(status == 0) %>% select(-c(status)) -> cachegrind
188
189 # Add the number of lines, joining on path, and compute lines/ms
190 times %>%
191 left_join(lines, by = c('path')) %>%
192 mutate(filename = basename(path), filename_HREF = sourceUrl(path),
193 max_rss_MB = max_rss_KiB * 1024 / 1e6,
194 elapsed_ms = elapsed_secs * 1000,
195 user_ms = user_secs * 1000,
196 sys_ms = sys_secs * 1000,
197 lines_per_ms = num_lines / elapsed_ms) %>%
198 select(-c(path, max_rss_KiB, elapsed_secs, user_secs, sys_secs)) ->
199 joined_times
200
201 #print(head(times))
202 #print(head(lines))
203 #print(head(vm))
204 #print(head(joined_times))
205
206 print(summary(joined_times))
207
208 #
209 # Find distinct shells and hosts, and label them for readability.
210 #
211
212 distinct_hosts = DistinctHosts(joined_times)
213 Log('')
214 Log('Distinct hosts')
215 print(distinct_hosts)
216
217 distinct_shells = DistinctShells(joined_times)
218 Log('')
219 Log('Distinct shells')
220 print(distinct_shells)
221
222 # Replace name/hash combinations with labels.
223 joined_times %>%
224 left_join(distinct_hosts, by = c('host_name', 'host_hash')) %>%
225 left_join(distinct_shells, by = c('shell_name', 'shell_hash')) %>%
226 select(-c(host_name, host_hash, shell_name, shell_hash)) ->
227 joined_times
228
229 # Like 'times', but do shell_label as one step
230 # Hack: we know benchmarks/auto.sh runs this on one machine
231 distinct_shells_2 = DistinctShells(cachegrind, num_hosts = nrow(distinct_hosts))
232 cachegrind %>%
233 left_join(lines, by = c('path')) %>%
234 select(-c(elapsed_secs, user_secs, sys_secs, max_rss_KiB)) %>%
235 left_join(distinct_shells_2, by = c('shell_name', 'shell_hash')) %>%
236 select(-c(shell_name, shell_hash)) %>%
237 mutate(filename = basename(path), filename_HREF = sourceUrl(path)) %>%
238 select(-c(path)) ->
239 joined_cachegrind
240
241 Log('summary(joined_times):')
242 print(summary(joined_times))
243 Log('head(joined_times):')
244 print(head(joined_times))
245
246 # Summarize rates by platform/shell
247 joined_times %>%
248 mutate(host_label = paste("host", host_label)) %>%
249 group_by(host_label, shell_label) %>%
250 summarize(total_lines = sum(num_lines), total_ms = sum(elapsed_ms)) %>%
251 mutate(lines_per_ms = total_lines / total_ms) %>%
252 select(-c(total_ms)) %>%
253 spread(key = host_label, value = lines_per_ms) ->
254 times_summary
255
256 # Sort by parsing rate on machine 1
257 if ("host hoover" %in% colnames(times_summary)) {
258 times_summary %>% arrange(desc(`host hoover`)) -> times_summary
259 } else {
260 times_summary %>% arrange(desc(`host no-host`)) -> times_summary
261 }
262
263 Log('times_summary:')
264 print(times_summary)
265
266 # Summarize cachegrind by platform/shell
267 # Bug fix: as.numeric(irefs) avoids 32-bit integer overflow!
268 joined_cachegrind %>%
269 group_by(shell_label) %>%
270 summarize(total_lines = sum(num_lines), total_irefs = sum(as.numeric(irefs))) %>%
271 mutate(thousand_irefs_per_line = total_irefs / total_lines / 1000) %>%
272 select(-c(total_irefs)) ->
273 cachegrind_summary
274
275 if ("no-host" %in% distinct_hosts$host_label) {
276
277 # We don't have all the shells
278 elapsed = NULL
279 rate = NULL
280 max_rss = NULL
281 instructions = NULL
282
283 joined_times %>%
284 select(c(shell_label, elapsed_ms, user_ms, sys_ms, max_rss_MB,
285 num_lines, filename, filename_HREF)) %>%
286 arrange(filename, elapsed_ms) ->
287 times_flat
288
289 joined_cachegrind %>%
290 select(c(shell_label, irefs, num_lines, filename, filename_HREF)) %>%
291 arrange(filename, irefs) ->
292 cachegrind_flat
293
294 } else {
295
296 times_flat = NULL
297 cachegrind_flat = NULL
298
299 # Elapsed seconds for each shell by platform and file
300 joined_times %>%
301 select(-c(lines_per_ms, user_ms, sys_ms, max_rss_MB)) %>%
302 spread(key = shell_label, value = elapsed_ms) %>%
303 arrange(host_label, num_lines) %>%
304 mutate(osh_to_bash_ratio = `osh-native` / bash) %>%
305 select(c(host_label, bash, dash, mksh, zsh,
306 `osh-ovm`, `osh-cpython`, `osh-native`,
307 osh_to_bash_ratio, num_lines, filename, filename_HREF)) ->
308 elapsed
309
310 Log('\n')
311 Log('ELAPSED')
312 print(elapsed)
313
314 # Rates by file and shell
315 joined_times %>%
316 select(-c(elapsed_ms, user_ms, sys_ms, max_rss_MB)) %>%
317 spread(key = shell_label, value = lines_per_ms) %>%
318 arrange(host_label, num_lines) %>%
319 select(c(host_label, bash, dash, mksh, zsh,
320 `osh-ovm`, `osh-cpython`, `osh-native`,
321 num_lines, filename, filename_HREF)) ->
322 rate
323
324 Log('\n')
325 Log('RATE')
326 print(rate)
327
328 # Memory usage by file
329 joined_times %>%
330 select(-c(elapsed_ms, lines_per_ms, user_ms, sys_ms)) %>%
331 spread(key = shell_label, value = max_rss_MB) %>%
332 arrange(host_label, num_lines) %>%
333 select(c(host_label, bash, dash, mksh, zsh,
334 `osh-ovm`, `osh-cpython`, `osh-native`,
335 num_lines, filename, filename_HREF)) ->
336 max_rss
337
338 Log('\n')
339 Log('MAX RSS')
340 print(max_rss)
341
342 Log('\n')
343 Log('joined_cachegrind has %d rows', nrow(joined_cachegrind))
344 print(joined_cachegrind)
345 #print(joined_cachegrind %>% filter(path == 'benchmarks/testdata/configure-helper.sh'))
346
347 # Cachegrind instructions by file
348 joined_cachegrind %>%
349 mutate(thousand_irefs_per_line = irefs / num_lines / 1000) %>%
350 select(-c(irefs)) %>%
351 spread(key = shell_label, value = thousand_irefs_per_line) %>%
352 arrange(num_lines) %>%
353 select(c(bash, dash, mksh, `osh-native`,
354 num_lines, filename, filename_HREF)) ->
355 instructions
356
357 Log('\n')
358 Log('instructions has %d rows', nrow(instructions))
359 print(instructions)
360 }
361
362 WriteProvenance(distinct_hosts, distinct_shells, out_dir)
363
364 raw_data_table = tibble(
365 filename = basename(as.character(raw_data$path)),
366 filename_HREF = benchmarkDataLink('osh-parser', filename, '')
367 )
368 #print(raw_data_table)
369
370 writeCsv(raw_data_table, file.path(out_dir, 'raw-data'))
371
372 precision = SamePrecision(0) # lines per ms
373 writeCsv(times_summary, file.path(out_dir, 'summary'), precision)
374
375 precision = ColumnPrecision(list(), default = 1)
376 writeTsv(cachegrind_summary, file.path(out_dir, 'cachegrind_summary'), precision)
377
378 if (!is.null(times_flat)) {
379 precision = SamePrecision(0)
380 writeTsv(times_flat, file.path(out_dir, 'times_flat'), precision)
381 }
382
383 if (!is.null(cachegrind_flat)) {
384 precision = SamePrecision(0)
385 writeTsv(cachegrind_flat, file.path(out_dir, 'cachegrind_flat'), precision)
386 }
387
388 if (!is.null(elapsed)) { # equivalent to no-host
389 # Round to nearest millisecond, but the ratio has a decimal point.
390 precision = ColumnPrecision(list(osh_to_bash_ratio = 1), default = 0)
391 writeCsv(elapsed, file.path(out_dir, 'elapsed'), precision)
392
393 precision = SamePrecision(0)
394 writeCsv(rate, file.path(out_dir, 'rate'), precision)
395
396 writeCsv(max_rss, file.path(out_dir, 'max_rss'))
397
398 precision = SamePrecision(1)
399 writeTsv(instructions, file.path(out_dir, 'instructions'), precision)
400 }
401
402 Log('Wrote %s', out_dir)
403}
404
405WriteProvenance = function(distinct_hosts, distinct_shells, out_dir, tsv = F) {
406
407 num_hosts = nrow(distinct_hosts)
408 if (num_hosts == 1) {
409 linkify = provenanceLink
410 } else {
411 linkify = benchmarkDataLink
412 }
413
414 Log('distinct_hosts')
415 print(distinct_hosts)
416 Log('')
417
418 Log('distinct_shells')
419 print(distinct_shells)
420 Log('')
421
422 # Should be:
423 # host_id_url
424 # And then csv_to_html will be smart enough? It should take --url flag?
425 host_table = tibble(
426 host_label = distinct_hosts$host_label,
427 host_id = paste(distinct_hosts$host_name,
428 distinct_hosts$host_hash, sep='-'),
429 host_id_HREF = linkify('host-id', host_id, '/')
430 )
431 Log('host_table')
432 print(host_table)
433 Log('')
434
435 shell_table = tibble(
436 shell_label = distinct_shells$shell_label,
437 shell_id = paste(distinct_shells$shell_name,
438 distinct_shells$shell_hash, sep='-'),
439 shell_id_HREF = linkify('shell-id', shell_id, '/')
440 )
441
442 Log('shell_table')
443 print(shell_table)
444 Log('')
445
446 if (tsv) {
447 writeTsv(host_table, file.path(out_dir, 'hosts'))
448 writeTsv(shell_table, file.path(out_dir, 'shells'))
449 } else {
450 writeCsv(host_table, file.path(out_dir, 'hosts'))
451 writeCsv(shell_table, file.path(out_dir, 'shells'))
452 }
453}
454
455WriteSimpleProvenance = function(provenance, out_dir) {
456 Log('provenance')
457 print(provenance)
458 Log('')
459
460 # Legacy: add $shell_name, because "$shell_basename-$shell_hash" is what
461 # benchmarks/id.sh publish-shell-id uses
462 provenance %>%
463 mutate(shell_name = basename(sh_path)) %>%
464 distinct(shell_label, shell_name, shell_hash) ->
465 distinct_shells
466
467 Log('distinct_shells')
468 print(distinct_shells)
469 Log('')
470
471 provenance %>% distinct(host_label, host_name, host_hash) -> distinct_hosts
472
473 WriteProvenance(distinct_hosts, distinct_shells, out_dir, tsv = T)
474}
475
476RuntimeReport = function(in_dir, out_dir) {
477 times = readTsv(file.path(in_dir, 'times.tsv'))
478
479 gc_stats = readTsv(file.path(in_dir, 'gc_stats.tsv'))
480 provenance = readTsv(file.path(in_dir, 'provenance.tsv'))
481
482 times %>% filter(status != 0) -> failed
483 if (nrow(failed) != 0) {
484 print(failed)
485 stop('Some osh-runtime tasks failed')
486 }
487
488 # Joins:
489 # times <= sh_path => provenance
490 # times <= join_id, host_name => gc_stats
491
492 # TODO: provenance may have rows from 2 machines. Could validate them and
493 # deduplicate.
494
495 # It should have (host_label, host_name, host_hash)
496 # (shell_label, sh_path, shell_hash)
497 provenance %>%
498 mutate(host_label = host_name, shell_label = ShellLabelFromPath(sh_path)) ->
499 provenance
500
501 provenance %>% distinct(sh_path, shell_label) -> label_lookup
502
503 Log('label_lookup')
504 print(label_lookup)
505
506 # Join with provenance for host label and shell label
507 times %>%
508 select(c(elapsed_secs, user_secs, sys_secs, max_rss_KiB, task_id,
509 host_name, sh_path, workload)) %>%
510 mutate(elapsed_ms = elapsed_secs * 1000,
511 user_ms = user_secs * 1000,
512 sys_ms = sys_secs * 1000,
513 max_rss_MB = max_rss_KiB * 1024 / 1e6) %>%
514 select(-c(elapsed_secs, user_secs, sys_secs, max_rss_KiB)) %>%
515 left_join(label_lookup, by = c('sh_path')) %>%
516 select(-c(sh_path)) %>%
517 # we want to compare workloads on adjacent rows
518 arrange(workload) ->
519 details
520
521 times %>%
522 select(c(task_id, host_name, sh_path, workload, minor_faults, major_faults, swaps, in_block, out_block, signals, voluntary_ctx, involuntary_ctx)) %>%
523 left_join(label_lookup, by = c('sh_path')) %>%
524 select(-c(sh_path)) %>%
525 # we want to compare workloads on adjacent rows
526 arrange(workload) ->
527 details_io
528
529 Log('details')
530 print(details)
531
532 # Elapsed time comparison
533 details %>%
534 select(-c(task_id, user_ms, sys_ms, max_rss_MB)) %>%
535 spread(key = shell_label, value = elapsed_ms) %>%
536 mutate(py_bash_ratio = `osh-cpython` / bash) %>%
537 mutate(native_bash_ratio = `osh-native` / bash) %>%
538 arrange(workload, host_name) %>%
539 select(c(workload, host_name,
540 bash, dash, `osh-cpython`, `osh-native`,
541 py_bash_ratio, native_bash_ratio)) ->
542
543 elapsed
544
545 Log('elapsed')
546 print(elapsed)
547
548 # Minor Page Faults Comparison
549 details_io %>%
550 select(c(host_name, shell_label, workload, minor_faults)) %>%
551 spread(key = shell_label, value = minor_faults) %>%
552 mutate(py_bash_ratio = `osh-cpython` / bash) %>%
553 mutate(native_bash_ratio = `osh-native` / bash) %>%
554 arrange(workload, host_name) %>%
555 select(c(workload, host_name,
556 bash, dash, `osh-cpython`, `osh-native`,
557 py_bash_ratio, native_bash_ratio)) ->
558 page_faults
559
560 Log('page_faults')
561 print(page_faults)
562
563 # Max RSS comparison
564 details %>%
565 select(c(host_name, shell_label, workload, max_rss_MB)) %>%
566 spread(key = shell_label, value = max_rss_MB) %>%
567 mutate(py_bash_ratio = `osh-cpython` / bash) %>%
568 mutate(native_bash_ratio = `osh-native` / bash) %>%
569 arrange(workload, host_name) %>%
570 select(c(workload, host_name,
571 bash, dash, `osh-cpython`, `osh-native`,
572 py_bash_ratio, native_bash_ratio)) ->
573 max_rss
574
575 Log('max rss')
576 print(max_rss)
577
578 details %>%
579 select(c(task_id, host_name, workload, elapsed_ms, max_rss_MB)) %>%
580 mutate(join_id = sprintf("gc-%d", task_id)) %>%
581 select(-c(task_id)) ->
582 gc_details
583
584 Log('GC details')
585 print(gc_details)
586 Log('')
587
588 Log('GC stats')
589 print(gc_stats)
590 Log('')
591
592 gc_stats %>%
593 left_join(gc_details, by = c('join_id', 'host_name')) %>%
594 select(-c(join_id, roots_capacity, objs_capacity)) %>%
595 # Do same transformations as GcReport()
596 mutate(allocated_MB = bytes_allocated / 1e6) %>%
597 select(-c(bytes_allocated)) %>%
598 rename(num_gc_done = num_collections) %>%
599 # Put these columns first
600 relocate(workload, host_name,
601 elapsed_ms, max_gc_millis, total_gc_millis,
602 allocated_MB, max_rss_MB, num_allocated) ->
603 gc_stats
604
605 Log('After GC stats')
606 print(gc_stats)
607 Log('')
608
609 WriteSimpleProvenance(provenance, out_dir)
610
611 # milliseconds don't need decimal digit
612 precision = ColumnPrecision(list(bash = 0, dash = 0, `osh-cpython` = 0,
613 `osh-native` = 0, py_bash_ratio = 2,
614 native_bash_ratio = 2))
615 writeTsv(elapsed, file.path(out_dir, 'elapsed'), precision)
616 writeTsv(page_faults, file.path(out_dir, 'page_faults'), precision)
617
618 precision2 = ColumnPrecision(list(py_bash_ratio = 2, native_bash_ratio = 2))
619 writeTsv(max_rss, file.path(out_dir, 'max_rss'), precision2)
620
621 precision3 = ColumnPrecision(list(max_rss_MB = 1, allocated_MB = 1),
622 default = 0)
623 writeTsv(gc_stats, file.path(out_dir, 'gc_stats'), precision3)
624
625 writeTsv(details, file.path(out_dir, 'details'), precision3)
626 writeTsv(details_io, file.path(out_dir, 'details_io'))
627
628 Log('Wrote %s', out_dir)
629}
630
631VmBaselineReport = function(in_dir, out_dir) {
632 vm = readTsv(file.path(in_dir, 'vm-baseline.tsv'))
633 #print(vm)
634
635 # Not using DistinctHosts() because field host_hash isn't collected
636 num_hosts = nrow(vm %>% distinct(host))
637
638 vm %>%
639 rename(kib = metric_value) %>%
640 mutate(shell_label = ShellLabels(shell_name, shell_hash, num_hosts),
641 megabytes = kib * 1024 / 1e6) %>%
642 select(-c(shell_name, kib)) %>%
643 spread(key = c(metric_name), value = megabytes) %>%
644 rename(VmPeak_MB = VmPeak, VmRSS_MB = VmRSS) %>%
645 select(c(shell_label, shell_hash, host, VmRSS_MB, VmPeak_MB)) %>%
646 arrange(shell_label, shell_hash, host, VmPeak_MB) ->
647 vm
648
649 print(vm)
650
651 writeTsv(vm, file.path(out_dir, 'vm-baseline'))
652}
653
654WriteOvmBuildDetails = function(distinct_hosts, distinct_compilers, out_dir) {
655 host_table = tibble(
656 host_label = distinct_hosts$host_label,
657 host_id = paste(distinct_hosts$host_name,
658 distinct_hosts$host_hash, sep='-'),
659 host_id_HREF = benchmarkDataLink('host-id', host_id, '/')
660 )
661 print(host_table)
662
663 dc = distinct_compilers
664 compiler_table = tibble(
665 compiler_label = dc$compiler_label,
666 compiler_id = paste(dc$compiler_label, dc$compiler_hash, sep='-'),
667 compiler_id_HREF = benchmarkDataLink('compiler-id', compiler_id, '/')
668 )
669 print(compiler_table)
670
671 writeTsv(host_table, file.path(out_dir, 'hosts'))
672 writeTsv(compiler_table, file.path(out_dir, 'compilers'))
673}
674
675OvmBuildReport = function(in_dir, out_dir) {
676 times = readTsv(file.path(in_dir, 'times.tsv'))
677 native_sizes = readTsv(file.path(in_dir, 'native-sizes.tsv'))
678 #raw_data = readTsv(file.path(in_dir, 'raw-data.tsv'))
679
680 times %>% filter(status != 0) -> failed
681 if (nrow(failed) != 0) {
682 print(failed)
683 stop('Some ovm-build tasks failed')
684 }
685
686 times %>% distinct(host_name, host_hash) -> distinct_hosts
687 distinct_hosts$host_label = distinct_hosts$host_name
688
689 times %>% distinct(compiler_path, compiler_hash) -> distinct_compilers
690 distinct_compilers$compiler_label = basename(distinct_compilers$compiler_path)
691
692 #print(distinct_hosts)
693 #print(distinct_compilers)
694
695 WriteOvmBuildDetails(distinct_hosts, distinct_compilers, out_dir)
696
697 times %>%
698 select(-c(status)) %>%
699 left_join(distinct_hosts, by = c('host_name', 'host_hash')) %>%
700 left_join(distinct_compilers, by = c('compiler_path', 'compiler_hash')) %>%
701 select(-c(host_name, host_hash, compiler_path, compiler_hash)) %>%
702 mutate(src_dir = basename(src_dir),
703 host_label = paste("host ", host_label),
704 is_conf = str_detect(action, 'configure'),
705 is_ovm = str_detect(action, 'oil.ovm'),
706 is_dbg = str_detect(action, 'dbg'),
707 ) %>%
708 select(host_label, src_dir, compiler_label, action, is_conf, is_ovm, is_dbg,
709 elapsed_secs) %>%
710 spread(key = c(host_label), value = elapsed_secs) %>%
711 arrange(src_dir, compiler_label, desc(is_conf), is_ovm, desc(is_dbg)) %>%
712 select(-c(is_conf, is_ovm, is_dbg)) ->
713 times
714
715 #print(times)
716
717 # paths look like _tmp/ovm-build/bin/clang/oils_cpp.stripped
718 native_sizes %>%
719 select(c(host_label, path, num_bytes)) %>%
720 mutate(host_label = paste("host ", host_label),
721 binary = basename(path),
722 compiler = basename(dirname(path)),
723 ) %>%
724 select(-c(path)) %>%
725 spread(key = c(host_label), value = num_bytes) %>%
726 arrange(compiler, binary) ->
727 native_sizes
728
729 # NOTE: These don't have the host and compiler.
730 writeTsv(times, file.path(out_dir, 'times'))
731 writeTsv(native_sizes, file.path(out_dir, 'native-sizes'))
732
733 # TODO: I want a size report too
734 #writeCsv(sizes, file.path(out_dir, 'sizes'))
735}
736
737unique_stdout_md5sum = function(t, num_expected) {
738 u = n_distinct(t$stdout_md5sum)
739 if (u != num_expected) {
740 t %>% select(c(host_name, task_name, arg1, arg2, runtime_name, stdout_md5sum)) %>% print()
741 stop(sprintf('Expected %d unique md5sums, got %d', num_expected, u))
742 }
743}
744
745ComputeReport = function(in_dir, out_dir) {
746 # TSV file, not CSV
747 times = read.table(file.path(in_dir, 'times.tsv'), header=T)
748 print(times)
749
750 times %>% filter(status != 0) -> failed
751 if (nrow(failed) != 0) {
752 print(failed)
753 stop('Some compute tasks failed')
754 }
755
756 #
757 # Check correctness
758 #
759
760 times %>% filter(task_name == 'hello') %>% unique_stdout_md5sum(1)
761 times %>% filter(task_name == 'fib') %>% unique_stdout_md5sum(1)
762 times %>% filter(task_name == 'word_freq') %>% unique_stdout_md5sum(1)
763 # 3 different inputs
764 times %>% filter(task_name == 'parse_help') %>% unique_stdout_md5sum(3)
765
766 times %>% filter(task_name == 'bubble_sort') %>% unique_stdout_md5sum(2)
767
768 # TODO:
769 # - oils_cpp doesn't implement unicode LANG=C
770 # - bash behaves differently on your desktop vs. in the container
771 # - might need layer-locales in the image?
772
773 #times %>% filter(task_name == 'palindrome' & arg1 == 'unicode') %>% unique_stdout_md5sum(1)
774 # Ditto here
775 #times %>% filter(task_name == 'palindrome' & arg1 == 'bytes') %>% unique_stdout_md5sum(1)
776
777 #
778 # Find distinct shells and hosts, and label them for readability.
779 #
780
781 # Runtimes are called shells, as a hack for code reuse
782 times %>%
783 mutate(shell_name = runtime_name, shell_hash = runtime_hash) %>%
784 select(c(host_name, host_hash, shell_name, shell_hash)) ->
785 tmp
786
787 distinct_hosts = DistinctHosts(tmp)
788 Log('')
789 Log('Distinct hosts')
790 print(distinct_hosts)
791
792 distinct_shells = DistinctShells(tmp)
793 Log('')
794 Log('Distinct runtimes')
795 print(distinct_shells)
796
797 num_hosts = nrow(distinct_hosts)
798
799 times %>%
800 select(-c(status, stdout_md5sum, stdout_filename, host_hash, runtime_hash)) %>%
801 mutate(runtime_label = ShellLabels(runtime_name, runtime_hash, num_hosts),
802 elapsed_ms = elapsed_secs * 1000,
803 user_ms = user_secs * 1000,
804 sys_ms = sys_secs * 1000,
805 max_rss_MB = max_rss_KiB * 1024 / 1e6) %>%
806 select(-c(runtime_name, elapsed_secs, user_secs, sys_secs, max_rss_KiB)) %>%
807 arrange(host_name, task_name, arg1, arg2, user_ms) ->
808 details
809
810 times %>%
811 mutate(
812 runtime_label = ShellLabels(runtime_name, runtime_hash, num_hosts),
813 stdout_md5sum_HREF = file.path('tmp', task_name, stdout_filename)) %>%
814 select(c(host_name, task_name, arg1, arg2, runtime_label,
815 stdout_md5sum, stdout_md5sum_HREF)) ->
816 stdout_files
817
818 details %>% filter(task_name == 'hello') %>% select(-c(task_name)) -> hello
819 details %>% filter(task_name == 'fib') %>% select(-c(task_name)) -> fib
820 details %>% filter(task_name == 'word_freq') %>% select(-c(task_name)) -> word_freq
821 # There's no arg2
822 details %>% filter(task_name == 'parse_help') %>% select(-c(task_name, arg2)) -> parse_help
823
824 details %>% filter(task_name == 'bubble_sort') %>% select(-c(task_name)) -> bubble_sort
825 details %>% filter(task_name == 'palindrome' & arg1 == 'unicode') %>% select(-c(task_name)) -> palindrome
826
827 precision = ColumnPrecision(list(max_rss_MB = 1), default = 0)
828 writeTsv(details, file.path(out_dir, 'details'), precision)
829
830 writeTsv(stdout_files, file.path(out_dir, 'stdout_files'), precision)
831
832 writeTsv(hello, file.path(out_dir, 'hello'), precision)
833 writeTsv(fib, file.path(out_dir, 'fib'), precision)
834 writeTsv(word_freq, file.path(out_dir, 'word_freq'), precision)
835 writeTsv(parse_help, file.path(out_dir, 'parse_help'), precision)
836
837 writeTsv(bubble_sort, file.path(out_dir, 'bubble_sort'), precision)
838 writeTsv(palindrome, file.path(out_dir, 'palindrome'), precision)
839
840 WriteProvenance(distinct_hosts, distinct_shells, out_dir, tsv = T)
841}
842
843WriteOneTask = function(times, out_dir, task_name, precision) {
844 times %>%
845 filter(task == task_name) %>%
846 select(-c(task)) -> subset
847
848 writeTsv(subset, file.path(out_dir, task_name), precision)
849}
850
851SHELL_ORDER = c('dash',
852 'bash',
853 'zsh',
854 '_bin/cxx-opt+bumpleak/osh',
855 '_bin/cxx-opt+bumproot/osh',
856 '_bin/cxx-opt+bumpsmall/osh',
857 '_bin/cxx-opt/osh',
858 '_bin/cxx-opt+nopool/osh')
859
860GcReport = function(in_dir, out_dir) {
861 times = read.table(file.path(in_dir, 'raw/times.tsv'), header=T)
862 gc_stats = read.table(file.path(in_dir, 'stage1/gc_stats.tsv'), header=T)
863
864 times %>% filter(status != 0) -> failed
865 if (nrow(failed) != 0) {
866 print(failed)
867 stop('Some gc tasks failed')
868 }
869
870 # Change units and order columns
871 times %>%
872 arrange(task, factor(sh_path, levels = SHELL_ORDER)) %>%
873 mutate(elapsed_ms = elapsed_secs * 1000,
874 user_ms = user_secs * 1000,
875 sys_ms = sys_secs * 1000,
876 max_rss_MB = max_rss_KiB * 1024 / 1e6,
877 shell_label = ShellLabelFromPath(sh_path)
878 ) %>%
879 select(c(join_id, task, elapsed_ms, user_ms, sys_ms, max_rss_MB, shell_label,
880 shell_runtime_opts)) ->
881 times
882
883 # Join and order columns
884 gc_stats %>% left_join(times, by = c('join_id')) %>%
885 arrange(desc(task)) %>%
886 mutate(allocated_MB = bytes_allocated / 1e6) %>%
887 # try to make the table skinnier
888 rename(num_gc_done = num_collections) %>%
889 select(task, elapsed_ms, max_gc_millis, total_gc_millis,
890 allocated_MB, max_rss_MB, num_allocated,
891 num_gc_points, num_gc_done, gc_threshold, num_growths, max_survived,
892 shell_label) ->
893 gc_stats
894
895 times %>% select(-c(join_id)) -> times
896
897
898 precision = ColumnPrecision(list(max_rss_MB = 1, allocated_MB = 1),
899 default = 0)
900
901 writeTsv(times, file.path(out_dir, 'times'), precision)
902 writeTsv(gc_stats, file.path(out_dir, 'gc_stats'), precision)
903
904 tasks = c('parse.configure-coreutils',
905 'parse.configure-cpython',
906 'parse.abuild',
907 'ex.compute-fib',
908 'ex.bashcomp-parse-help',
909 'ex.abuild-print-help')
910 # Write out separate rows
911 for (task in tasks) {
912 WriteOneTask(times, out_dir, task, precision)
913 }
914}
915
916GcCachegrindReport = function(in_dir, out_dir) {
917 times = readTsv(file.path(in_dir, 'raw/times.tsv'))
918 counts = readTsv(file.path(in_dir, 'stage1/cachegrind.tsv'))
919
920 times %>% filter(status != 0) -> failed
921 if (nrow(failed) != 0) {
922 print(failed)
923 stop('Some gc tasks failed')
924 }
925
926 print(times)
927 print(counts)
928
929 counts %>% left_join(times, by = c('join_id')) %>%
930 mutate(million_irefs = irefs / 1e6) %>%
931 select(c(million_irefs, task, sh_path, shell_runtime_opts)) %>%
932 arrange(factor(sh_path, levels = SHELL_ORDER)) ->
933 counts
934
935 precision = NULL
936 tasks = c('parse.abuild', 'ex.compute-fib')
937 for (task in tasks) {
938 WriteOneTask(counts, out_dir, task, precision)
939 }
940}
941
942MyCppReport = function(in_dir, out_dir) {
943 times = readTsv(file.path(in_dir, 'benchmark-table.tsv'))
944 print(times)
945
946 times %>% filter(status != 0) -> failed
947 if (nrow(failed) != 0) {
948 print(failed)
949 stop('Some mycpp tasks failed')
950 }
951
952 # Don't care about elapsed and system
953 times %>% select(-c(status, elapsed_secs, bin, task_out)) %>%
954 mutate(example_name_HREF = mycppUrl(example_name),
955 gen = c('gen'),
956 gen_HREF = genUrl(example_name),
957 user_ms = user_secs * 1000,
958 sys_ms = sys_secs * 1000,
959 max_rss_MB = max_rss_KiB * 1024 / 1e6) %>%
960 select(-c(user_secs, sys_secs, max_rss_KiB)) ->
961 details
962
963 details %>% select(-c(sys_ms, max_rss_MB)) %>%
964 spread(key = impl, value = user_ms) %>%
965 mutate(`C++ : C++-souffle : Python` = `C++` / `C++-soufle` / Python) %>%
966 arrange(`C++ : C++-souffle : Python`) ->
967 user_time
968
969 details %>% select(-c(user_ms, max_rss_MB)) %>%
970 spread(key = impl, value = sys_ms) %>%
971 mutate(`C++ : C++-souffle : Python` = `C++` / `C++-soufle` / Python) %>%
972 arrange(`C++ : C++-souffle : Python`) ->
973 sys_time
974
975 details %>% select(-c(user_ms, sys_ms)) %>%
976 spread(key = impl, value = max_rss_MB) %>%
977 mutate(`C++ : C++-souffle : Python` = `C++` / `C++-soufle` / Python) %>%
978 arrange(`C++ : C++-souffle : Python`) ->
979 max_rss
980
981 # Sometimes it speeds up by more than 10x
982 precision1 = ColumnPrecision(list(`C++ : Python` = 3), default = 0)
983 writeTsv(user_time, file.path(out_dir, 'user_time'), precision1)
984 writeTsv(sys_time, file.path(out_dir, 'sys_time'), precision1)
985
986 precision2 = ColumnPrecision(list(`C++ : Python` = 2), default = 1)
987 writeTsv(max_rss, file.path(out_dir, 'max_rss'), precision2)
988
989 writeTsv(details, file.path(out_dir, 'details'))
990}
991
992UftraceTaskReport = function(env, task_name, summaries) {
993 # Need this again after redirect
994 MaybeDisableColor(stdout())
995
996 task_env = env[[task_name]]
997
998 untyped = task_env$untyped
999 typed = task_env$typed
1000 strings = task_env$strings
1001 slabs = task_env$slabs
1002 reserve = task_env$reserve
1003
1004 string_overhead = 17 # GC header (8) + len (4) + hash value (4) + NUL (1)
1005 strings %>% mutate(obj_len = str_len + string_overhead) -> strings
1006
1007 # TODO: Output these totals PER WORKLOAD, e.g. parsing big/small, executing
1008 # big/small
1009 #
1010 # And then zoom in on distributions as well
1011
1012 num_allocs = nrow(untyped)
1013 total_bytes = sum(untyped$obj_len)
1014
1015 untyped %>% group_by(obj_len) %>% count() %>% ungroup() -> untyped_hist
1016 #print(untyped_hist)
1017
1018 untyped_hist %>%
1019 mutate(n_less_than = cumsum(n),
1020 percent = n_less_than * 100.0 / num_allocs) ->
1021 alloc_sizes
1022
1023 a24 = untyped_hist %>% filter(obj_len <= 24)
1024 a48 = untyped_hist %>% filter(obj_len <= 48)
1025 a96 = untyped_hist %>% filter(obj_len <= 96)
1026
1027 allocs_24_bytes_or_less = sum(a24$n) * 100.0 / num_allocs
1028 allocs_48_bytes_or_less = sum(a48$n) * 100.0 / num_allocs
1029 allocs_96_bytes_or_less = sum(a96$n) * 100.0 / num_allocs
1030
1031 Log('Percentage of allocs less than 48 bytes: %.1f', allocs_48_bytes_or_less)
1032
1033 options(tibble.print_min=25)
1034
1035 Log('')
1036 Log('All allocations')
1037 print(alloc_sizes %>% head(22))
1038 print(alloc_sizes %>% tail(5))
1039
1040 Log('')
1041 Log('Common Sizes')
1042 print(untyped_hist %>% arrange(desc(n)) %>% head(8))
1043
1044 Log('')
1045 Log(' %s total allocations, total bytes = %s', commas(num_allocs), commas(total_bytes))
1046 Log('')
1047
1048 Log('Typed allocations')
1049
1050 num_typed = nrow(typed)
1051
1052 typed %>% group_by(func_name) %>% count() %>% ungroup() %>%
1053 mutate(percent = n * 100.0 / num_typed) %>%
1054 arrange(desc(n)) -> most_common_types
1055
1056 print(most_common_types %>% head(20))
1057 print(most_common_types %>% tail(5))
1058
1059 lists = typed %>% filter(str_starts(func_name, ('List<')))
1060 #print(lists)
1061
1062 num_lists = nrow(lists)
1063 total_list_bytes = num_lists * 24 # sizeof List<T> head is hard-coded
1064
1065 Log('')
1066 Log('%s typed allocs, including %s List<T>', commas(num_typed), commas(num_lists))
1067 Log('%.2f%% of allocs are typed', num_typed * 100 / num_allocs)
1068 Log('')
1069
1070 #
1071 # Strings
1072 #
1073
1074 num_strings = nrow(strings)
1075 total_string_bytes = sum(strings$obj_len)
1076
1077 strings %>% group_by(str_len) %>% count() %>% ungroup() %>%
1078 mutate(n_less_than = cumsum(n),
1079 percent = n_less_than * 100.0 / num_strings) ->
1080 string_lengths
1081
1082 strs_6_bytes_or_less = string_lengths %>% filter(str_len == 6) %>% select(percent)
1083 strs_14_bytes_or_less = string_lengths %>% filter(str_len == 14) %>% select(percent)
1084
1085 # Parse workload
1086 # 62% of strings <= 6 bytes
1087 # 84% of strings <= 14 bytes
1088
1089 Log('Str - NewStr() and OverAllocatedStr()')
1090 print(string_lengths %>% head(16))
1091 print(string_lengths %>% tail(5))
1092 Log('')
1093
1094 Log('%s string allocations, total length = %s, total bytes = %s', commas(num_strings),
1095 commas(sum(strings$str_len)), commas(total_string_bytes))
1096 Log('')
1097 Log('%.2f%% of allocs are strings', num_strings * 100 / num_allocs)
1098 Log('%.2f%% of bytes are strings', total_string_bytes * 100 / total_bytes)
1099 Log('')
1100
1101 #
1102 # Slabs
1103 #
1104
1105 Log('NewSlab()')
1106
1107 num_slabs = nrow(slabs)
1108 slabs %>% group_by(slab_len) %>% count() %>% ungroup() %>%
1109 mutate(n_less_than = cumsum(n),
1110 percent = n_less_than * 100.0 / num_slabs) ->
1111 slab_lengths
1112
1113 slabs %>% group_by(func_name) %>% count() %>% ungroup() %>%
1114 arrange(desc(n)) -> slab_types
1115
1116 Log(' Lengths')
1117 print(slab_lengths %>% head())
1118 print(slab_lengths %>% tail(5))
1119 Log('')
1120
1121 Log(' Slab Types')
1122 print(slab_types %>% head())
1123 print(slab_types %>% tail(5))
1124 Log('')
1125
1126 total_slab_items = sum(slabs$slab_len)
1127
1128 Log('%s slabs, total items = %s', commas(num_slabs),
1129 commas(sum(slabs$slab_len)))
1130 Log('%.2f%% of allocs are slabs', num_slabs * 100 / num_allocs)
1131 Log('')
1132
1133 #
1134 # reserve() calls
1135 #
1136
1137 # There should be strictly more List::reserve() calls than NewSlab
1138
1139 Log('::reserve(int n)')
1140 Log('')
1141
1142 num_reserve = nrow(reserve)
1143 reserve %>% group_by(num_items) %>% count() %>% ungroup() %>%
1144 mutate(n_less_than = cumsum(n),
1145 percent = n_less_than * 100.0 / num_reserve) ->
1146 reserve_args
1147
1148 Log(' Num Items')
1149 print(reserve_args %>% head(15))
1150 print(reserve_args %>% tail(5))
1151 Log('')
1152
1153 Log('%s reserve() calls, total items = %s', commas(num_reserve),
1154 commas(sum(reserve$num_items)))
1155 Log('')
1156
1157 # Accounting for all allocations!
1158 Log('Untyped: %s', commas(num_allocs))
1159 Log('Typed + Str + Slab: %s', commas(num_typed + num_strings + num_slabs))
1160 Log('')
1161
1162 num_other_typed = num_typed - num_lists
1163
1164 # Summary table
1165 stats = tibble(task = task_name,
1166 total_bytes_ = commas(total_bytes),
1167 num_allocs_ = commas(num_allocs),
1168 sum_typed_strs_slabs = commas(num_typed + num_strings + num_slabs),
1169 num_reserve_calls = commas(num_reserve),
1170
1171 percent_list_allocs = Percent(num_lists, num_allocs),
1172 percent_slab_allocs = Percent(num_slabs, num_allocs),
1173 percent_string_allocs = Percent(num_strings, num_allocs),
1174 percent_other_typed_allocs = Percent(num_other_typed, num_allocs),
1175
1176 percent_list_bytes = Percent(total_list_bytes, total_bytes),
1177 percent_string_bytes = Percent(total_string_bytes, total_bytes),
1178
1179 allocs_24_bytes_or_less = sprintf('%.1f%%', allocs_24_bytes_or_less),
1180 allocs_48_bytes_or_less = sprintf('%.1f%%', allocs_48_bytes_or_less),
1181 allocs_96_bytes_or_less = sprintf('%.1f%%', allocs_96_bytes_or_less),
1182
1183 strs_6_bytes_or_less = sprintf('%.1f%%', strs_6_bytes_or_less),
1184 strs_14_bytes_or_less = sprintf('%.1f%%', strs_14_bytes_or_less),
1185 )
1186 summaries$stats[[task_name]] = stats
1187
1188 summaries$most_common_types[[task_name]] = most_common_types
1189}
1190
1191LoadUftraceTsv = function(in_dir, env) {
1192 for (task in list.files(in_dir)) {
1193 Log('Loading data for task %s', task)
1194 base_dir = file.path(in_dir, task)
1195
1196 task_env = new.env()
1197 env[[task]] = task_env
1198
1199 # TSV file, not CSV
1200 task_env$untyped = readTsv(file.path(base_dir, 'all-untyped.tsv'))
1201 task_env$typed = readTsv(file.path(base_dir, 'typed.tsv'))
1202 task_env$strings = readTsv(file.path(base_dir, 'strings.tsv'))
1203 task_env$slabs = readTsv(file.path(base_dir, 'slabs.tsv'))
1204 task_env$reserve = readTsv(file.path(base_dir, 'reserve.tsv'))
1205
1206 # median string length is 4, mean is 9.5!
1207 Log('UNTYPED')
1208 print(summary(task_env$untyped))
1209 Log('')
1210
1211 Log('TYPED')
1212 print(summary(task_env$typed))
1213 Log('')
1214
1215 Log('STRINGS')
1216 print(summary(task_env$strings))
1217 Log('')
1218
1219 Log('SLABS')
1220 print(summary(task_env$slabs))
1221 Log('')
1222
1223 Log('RESERVE')
1224 print(summary(task_env$reserve))
1225 Log('')
1226 }
1227}
1228
1229Percent = function(n, total) {
1230 sprintf('%.1f%%', n * 100.0 / total)
1231}
1232
1233PrettyPrintLong = function(d) {
1234 tr = t(d) # transpose
1235
1236 row_names = rownames(tr)
1237
1238 for (i in 1:nrow(tr)) {
1239 row_name = row_names[i]
1240 cat(sprintf('%26s', row_name)) # calculated min width manually
1241 cat(sprintf('%20s', tr[i,]))
1242 cat('\n')
1243
1244 # Extra spacing
1245 if (row_name %in% c('num_reserve_calls',
1246 'percent_string_bytes',
1247 'percent_other_typed_allocs',
1248 'allocs_96_bytes_or_less')) {
1249 cat('\n')
1250 }
1251 }
1252}
1253
1254
1255UftraceReport = function(env, out_dir) {
1256 # summaries$stats should be a list of 1-row data frames
1257 # summaries$top_types should be a list of types
1258 summaries = new.env()
1259
1260 for (task_name in names(env)) {
1261 report_out = file.path(out_dir, paste0(task_name, '.txt'))
1262
1263 Log('Making report for task %s -> %s', task_name, report_out)
1264
1265 sink(file = report_out)
1266 UftraceTaskReport(env, task_name, summaries)
1267 sink() # reset
1268 }
1269 Log('')
1270
1271 # Concate all the data frames added to summary
1272 stats = bind_rows(as.list(summaries$stats))
1273
1274 sink(file = file.path(out_dir, 'summary.txt'))
1275 #print(stats)
1276 #Log('')
1277
1278 PrettyPrintLong(stats)
1279 Log('')
1280
1281 mct = summaries$most_common_types
1282 for (task_name in names(mct)) {
1283 Log('Common types in workload %s', task_name)
1284 Log('')
1285
1286 print(mct[[task_name]] %>% head(5))
1287 Log('')
1288 }
1289 sink()
1290
1291 # For the REPL
1292 return(list(stats = stats))
1293}
1294
1295main = function(argv) {
1296 action = argv[[1]]
1297 in_dir = argv[[2]]
1298 out_dir = argv[[3]]
1299
1300 if (action == 'osh-parser') {
1301 ParserReport(in_dir, out_dir)
1302
1303 } else if (action == 'osh-runtime') {
1304 RuntimeReport(in_dir, out_dir)
1305
1306 } else if (action == 'vm-baseline') {
1307 VmBaselineReport(in_dir, out_dir)
1308
1309 } else if (action == 'ovm-build') {
1310 OvmBuildReport(in_dir, out_dir)
1311
1312 } else if (action == 'compute') {
1313 ComputeReport(in_dir, out_dir)
1314
1315 } else if (action == 'gc') {
1316 GcReport(in_dir, out_dir)
1317
1318 } else if (action == 'gc-cachegrind') {
1319 GcCachegrindReport(in_dir, out_dir)
1320
1321 } else if (action == 'mycpp') {
1322 MyCppReport(in_dir, out_dir)
1323
1324 } else if (action == 'uftrace') {
1325 d = new.env()
1326 LoadUftraceTsv(in_dir, d)
1327 UftraceReport(d, out_dir)
1328
1329 } else {
1330 Log("Invalid action '%s'", action)
1331 quit(status = 1)
1332 }
1333 Log('PID %d done', Sys.getpid())
1334}
1335
1336if (length(sys.frames()) == 0) {
1337 # increase ggplot font size globally
1338 #theme_set(theme_grey(base_size = 20))
1339
1340 main(commandArgs(TRUE))
1341}