Changeset - 4a904127877a
[Not reviewed]
0 10 0
Hannes Muehleisen - 9 years ago 2015-07-08 11:08:30
hannes@muehleisen.org
new ops exp and pqr
10 files changed with 38 insertions and 46 deletions:
identity.pdf
bin+mod
operators.pdf
bin+mod
parallel.pdf
bin+mod
pushdown.pdf
bin+mod
recycling.pdf
bin+mod
run.sh
2
1
survey.pdf
bin+mod
0 comments (0 inline, 0 general)
harness.R
Show inline comments
 
@@ -7,7 +7,6 @@ conf <- arg[[1]]
 
sm <- as.integer(arg[[2]])
 

	
 
sys <- ifelse(R.Version()$major == 2L, "Renjin", "GNU R")
 

	
 
log.result <- function(...) {
 
	con <- file("results.tsv", open="at")
 
	writeLines(paste(c(...), collapse="\t"), con=con)
identity.pdf
Show inline comments
 
binary diff not shown
makeplots.R
Show inline comments
 
@@ -29,12 +29,41 @@ se <- function(x) sqrt(var(x)/length(x))
 

	
 

	
 

	
 
# operators
 
d <- all %>% filter(exp=="operators", s > 5) %>% group_by(exp, sys, s, conf) %>% 
 
	summarize(meant=mean(timesec), se=se(timesec)) %>% 
 
	mutate(conf=ifelse(conf=="opt"," + Vectorization",""), tool=paste(sys,conf,sep=""), datasize=10^as.integer(s))
 

	
 
print(d)
 

	
 
limits <- aes(ymax = meant + se, ymin=meant - se, width=2)
 

	
 
pdf("operators.pdf",width=10,height=7)
 
p <- ggplot(d,aes(datasize,meant,group=tool)) + 
 
  geom_point(size=4) + geom_line(size=1.5, aes(group=tool, linetype=tool)) +
 
  geom_pointrange(limits) +
 
   # scale_y_log10(breaks=ybreaks, labels=ylabels) +
 
    scale_x_log10(breaks=xbreaks, labels=xlabels, limits=c(NA, 10^9.1)) +
 

	
 
	xlab("Dataset Size (elements, log scale)") + ylab("Execution Time (s)") + theme +
 

	
 
	annotate("text", x=10^7.8, y=-1, label="GNU R", family="serif", size=10)+
 
	annotate("text", x=10^8.55, y=39, label="Renjin ", family="serif", size=10)+
 
	annotate("text", x=10^8.8, y=8, label="Renjin + Vec.", family="serif", size=10)
 

	
 
	#annotate("text", x=700000, y=6, label="Renjin", family="serif", size=10)+
 
	#annotate("text", x=20000000, y=2, label="Renjin + Recycling", family="serif", size=10)
 

	
 

	
 
print(p)
 
dev.off()
 

	
 
# survey
 
d <- all %>% filter(exp=="survey") %>% group_by(sys, s, conf) %>% 
 
	summarize(meant=mean(timesec), se=se(timesec)) %>% 
 
	mutate(tool=paste(sys,conf), 
 
		datasize=sapply(s, switch, alabama=47512, california=1060060, acs3yr=9093077)) %>% 
 
	filter(tool %in% c("Renjin jitopt", "Renjin none", "Renjin 1t") | sys == "GNU R")
 
	filter(tool %in% c("Renjin jitopt", "Renjin none", "Renjin 1t") | sys  =="GNU R" | conf == "pqr")
 

	
 
print(d)
 

	
 
@@ -48,7 +77,9 @@ ggplot(d,aes(datasize,meant,group=tool)) +
 
    scale_x_log10(breaks=c(47512,1060060,9093077)) +
 

	
 
	xlab("Dataset Size (elements, log scale)") + ylab("Execution Time (s)") + theme +
 
	annotate("text", x=10^6.6, y=45, label="GNU R", family="serif", size=10)+
 
	annotate("text", x=10^6.7, y=45, label="pqR", family="serif", size=10)+
 
	annotate("text", x=10^6.9, y=30, label="GNU R", family="serif", size=10)+
 

	
 
	annotate("text", x=10^6.4, y=100, label="Renjin -opt", family="serif", size=10)+
 
	annotate("text", x=10^6.8, y=-1, label="Renjin", family="serif", size=10)+
 
	annotate("text", x=10^6.8, y=20, label="Renjin 1t", family="serif", size=10)
 
@@ -188,35 +219,6 @@ dev.off()
 

	
 

	
 

	
 
# operators
 
d <- all %>% filter(exp=="operators", s > 5) %>% group_by(exp, sys, s, conf) %>% 
 
	summarize(meant=mean(timesec), se=se(timesec)) %>% 
 
	mutate(conf=ifelse(conf=="opt"," + Vectorization",""), tool=paste(sys,conf,sep=""), datasize=10^as.integer(s))
 

	
 
print(d)
 

	
 
limits <- aes(ymax = meant + se, ymin=meant - se, width=2)
 

	
 
pdf("operators.pdf",width=10,height=7)
 
p <- ggplot(d,aes(datasize,meant,group=tool)) + 
 
  geom_point(size=4) + geom_line(size=1.5, aes(group=tool, linetype=tool)) +
 
  geom_pointrange(limits) +
 
   # scale_y_log10(breaks=ybreaks, labels=ylabels) +
 
    scale_x_log10(breaks=xbreaks, labels=xlabels, limits=c(NA, 10^8.1)) +
 

	
 
	xlab("Dataset Size (elements, log scale)") + ylab("Execution Time (log)") + theme +
 

	
 
	annotate("text", x=10^7.8, y=4, label="GNU R", family="serif", size=10)+
 
	annotate("text", x=40000000, y=19, label="Renjin ", family="serif", size=10)+
 
	annotate("text", x=10^7.95, y=14, label="Renjin + V.", family="serif", size=10)
 

	
 
	#annotate("text", x=700000, y=6, label="Renjin", family="serif", size=10)+
 
	#annotate("text", x=20000000, y=2, label="Renjin + Recycling", family="serif", size=10)
 

	
 

	
 
print(p)
 
dev.off()
 

	
 

	
 
# # print some latex for the paper
 
# selection$timesec <- selection$timesec/1000
operators.R
Show inline comments
 
source("harness.R")
 

	
 
dd <- function() {as.integer(runif(10^s, 1, 100))}
 

	
 
for (s in 4:sm) {
 
	a <- list(dd(), dd(), dd(), dd(), dd(), dd(), dd(), dd(), dd(), dd())
 
	x <- dd()
 
	dim(x) <- c(length(x),1)
 
	attr(a, "row.names") <- 1:length(a[[1]])
 
  	class(a) <- "data.frame"
 

	
 
	x <- runif(10^s, 1, 100)
 
	y <- seq(1:10^s)
 
	for (r in 1:5) {
 
		timing <- system.time({
 
			m <- matrix(data=as.numeric(NA), ncol=1, nrow=ncol(a))
 
			for(i in 1:ncol(a)){
 
				m[i,]<-t(colSums(a[,i]*x)/sum(a[,i]))
 
			}
 
			print(m)
 
			print(sum(sqrt(x+1)-y*x))
 
		})[[3]]
 
		log.result("operators", sys, conf, s, r, timing)
 
		clearResultRecycler()
operators.pdf
Show inline comments
 
binary diff not shown
parallel.pdf
Show inline comments
 
binary diff not shown
pushdown.pdf
Show inline comments
 
binary diff not shown
recycling.pdf
Show inline comments
 
binary diff not shown
run.sh
Show inline comments
 
@@ -40,7 +40,7 @@ export RENJIN_OPTS="-Xmx200G -Drenjin.vp.threads=32"
 
renjin -f parallel.R --args 32 $PDPAR
 

	
 
# vectorized/jitted operators
 
PDOPT=8
 
PDOPT=9
 
export RENJIN_OPTS="-Xmx16G -Drenjin.vp.threads=1"                            
 
renjin -f operators.R --args opt $PDOPT
 
export RENJIN_OPTS="-Xmx16G -Drenjin.vp.threads=1 -Drenjin.vp.disablejit=true"                            
 
@@ -51,6 +51,7 @@ R -f operators.R --args none $PDOPT
 
#NOTE: Need to install MonetDB and load ACS dataset to run this
 
#R -f sqlsurvey.R   --args laptop 42
 
R -f survey.R      --args laptop 42
 
pqR -f -f survey.R --args pqr 42
 

	
 
export RENJIN_OPTS="-Xmx200G"         
 
renjin -f survey.R --args jitopt 42
survey.pdf
Show inline comments
 
binary diff not shown
0 comments (0 inline, 0 general)