commit 72b6b096b832fc07e9f5980a955c6be11fe37278
parent c569479026157b3ae685165335892f8efe231187
Author: Ivan Gankevich <igankevich@ya.ru>
Date: Thu, 11 May 2017 12:09:02 +0300
Read more field from logs.
Diffstat:
R/common.R | | | 67 | +++++++++++++++++++++++++++++++++++++++++++++++++++++++++---------- |
1 file changed, 57 insertions(+), 10 deletions(-)
diff --git a/R/common.R b/R/common.R
@@ -2,13 +2,24 @@ load_log_file_as_data_frame <- function (prefix, pattern) {
runtime <- data.frame()
dirs <- sort(list.files(prefix))
rownum <- 1
+ run <- 1
for (d in dirs) {
files <- sort(list.files(file.path(prefix, d), pattern=pattern))
for (f in files) {
lines <- readLines(file.path(prefix, d, f))
t <- lines[grepl("^prfl.*=.*$", lines, perl=TRUE)]
- t <- gsub("^prfl\\s+.*=\\s*([0-9]+)us$", "\\1", t, perl=TRUE)
- t <- sum(as.numeric(t))
+ routine <- gsub(
+ "^prfl\\s+([a-zA-Z0-9_]+).*=\\s*([0-9]+)us$",
+ "\\1",
+ t,
+ perl=TRUE
+ )
+ t <- gsub(
+ "^prfl\\s+([a-zA-Z0-9_]+).*=\\s*([0-9]+)us$",
+ "\\2",
+ t,
+ perl=TRUE
+ )
s <- lines[grepl("^Output grid size", lines, perl=TRUE)]
s <- gsub(
"Output grid size\\s*=\\s*\\([0-9]+,([0-9]+),[0-9]+\\)",
@@ -18,21 +29,35 @@ load_log_file_as_data_frame <- function (prefix, pattern) {
)
s <- as.numeric(s)
# add new column if needed
+ if (!("run" %in% colnames(runtime))) {
+ runtime[, "run"] <- rep(NA, nrow(runtime))
+ }
if (!("t" %in% colnames(runtime))) {
runtime[, "t"] <- rep(NA, nrow(runtime))
}
if (!("size" %in% colnames(runtime))) {
runtime[, "size"] <- rep(NA, nrow(runtime))
}
+ if (!("routine" %in% colnames(runtime))) {
+ runtime[, "routine"] <- rep(NA, nrow(runtime))
+ }
# add new row if needed
-# r <- paste(d, s, sep="-")
- r <- rownum
- if (!(r %in% rownames(runtime))) {
- runtime[r, ] <- rep(NA, ncol(runtime))
+ for (i in seq(1, length(t))) {
+ if (!(rownum %in% rownames(runtime))) {
+ runtime[rownum, ] <- rep(NA, ncol(runtime))
+ }
+ runtime[rownum, "run"] <- run
+ runtime[rownum, "t"] <- as.numeric(t[[i]])
+ runtime[rownum, "size"] <- s
+ runtime[rownum, "routine"] <- routine[[i]]
+# runtime[rownum, ] <- c(as.numeric(t[[i]]), s, routine[[i]])
+ rownum <- rownum + 1
}
- runtime[r, ] <- c(t, s)
- rownum <- rownum + 1
+ #t <- sum(as.numeric(t))
+ #runtime[r, ] <- c(t, s, routine)
+ #rownum <- rownum + 1
}
+ run <- run + 1
}
runtime
}
@@ -40,8 +65,30 @@ load_log_file_as_data_frame <- function (prefix, pattern) {
arma.plot_cpu_gpu <- function () {
data1 <- load_log_file_as_data_frame("data", "^linear.*\\.log$")
data2 <- load_log_file_as_data_frame("data", "^high_amplitude_realtime.*\\.log$")
- data1 <- aggregate(data1$t*1e-6, by=list(size=data1$size), FUN=mean)
- data2 <- aggregate(data2$t*1e-6, by=list(size=data2$size), FUN=mean)
+ first_size <- data1[1, "size"]
+ data1 <- aggregate(
+ data1$t,
+ by=list(run=data1$run, size=data1$size),
+ FUN=sum
+ )
+ names(data1) <- c("run", "size", "t")
+ data2 <- aggregate(
+ data2$t,
+ by=list(run=data2$run, size=data2$size),
+ FUN=sum
+ )
+ names(data2) <- c("run", "size", "t")
+ #print(data2)
+ data1 <- aggregate(
+ data1$t*1e-6,
+ by=list(size=data1$size),
+ FUN=mean
+ )
+ data2 <- aggregate(
+ data2$t*1e-6,
+ by=list(size=data2$size),
+ FUN=mean
+ )
plot.new()
plot.window(
xlim=range(data1$size),