[tor-commits] [metrics-web/release] Make all graph data available as CSV.

karsten at torproject.org karsten at torproject.org
Wed May 30 13:45:11 UTC 2018


commit b75358eace4e8e0a75c60fe0ea1814aa479ecb9f
Author: Karsten Loesing <karsten.loesing at gmx.net>
Date:   Wed Feb 28 20:55:10 2018 +0100

    Make all graph data available as CSV.
    
    Previously, we provided links to CSV files that graphs are based on.
    But in some cases it would require some data wrangling to obtain the
    data in the graph, which is less usable than it could be. Now we're
    generating CSV files based on the graph and selected parameters. This
    will enable users to quickly obtain the data in a graph and further
    process it using tools of their choice.
    
    Implements #25382.
---
 src/main/R/rserver/graphs.R                        | 562 +++++++++++++++++----
 .../torproject/metrics/web/GraphImageServlet.java  |   3 +-
 .../org/torproject/metrics/web/GraphServlet.java   |   1 -
 .../org/torproject/metrics/web/LinkServlet.java    |   1 -
 .../java/org/torproject/metrics/web/Metric.java    |   6 -
 .../org/torproject/metrics/web/MetricServlet.java  |   5 -
 .../torproject/metrics/web/RObjectGenerator.java   |   9 +-
 .../org/torproject/metrics/web/TableServlet.java   |   1 -
 src/main/resources/web.xml                         |  35 +-
 src/main/resources/web/json/metrics.json           | 149 +-----
 src/main/resources/web/jsps/graph.jsp              |  10 +-
 src/main/resources/web/jsps/table.jsp              |   9 -
 12 files changed, 533 insertions(+), 258 deletions(-)

diff --git a/src/main/R/rserver/graphs.R b/src/main/R/rserver/graphs.R
index ab1a60d..fd5201d 100644
--- a/src/main/R/rserver/graphs.R
+++ b/src/main/R/rserver/graphs.R
@@ -328,7 +328,7 @@ stats_dir = "/srv/metrics.torproject.org/metrics/shared/stats/"
 
 rdata_dir = "/srv/metrics.torproject.org/metrics/shared/RData/"
 
-plot_networksize <- function(start, end, path) {
+prepare_networksize <- function(start, end) {
   s <- read.csv(paste(stats_dir, "servers.csv", sep = ""),
     stringsAsFactors = FALSE)
   s <- s[s$date >= start & s$date <= end & s$flag == '' &
@@ -336,6 +336,11 @@ plot_networksize <- function(start, end, path) {
          s$ec2bridge == '', ]
   s <- data.frame(date = as.Date(s$date, "%Y-%m-%d"), relays = s$relays,
                   bridges = s$bridges)
+  s
+}
+
+plot_networksize <- function(start, end, path) {
+  s <- prepare_networksize(start, end)
   dates <- seq(from = as.Date(start, "%Y-%m-%d"),
       to = as.Date(end, "%Y-%m-%d"), by="1 day")
   missing <- setdiff(dates, as.Date(s$date, origin = "1970-01-01"))
@@ -356,7 +361,12 @@ plot_networksize <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_versions <- function(start, end, path) {
+write_networksize <- function(start, end, path) {
+  prepare_networksize(start, end) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_versions <- function(start, end) {
   s <- read.csv(paste(stats_dir, "servers.csv", sep = ""),
     stringsAsFactors = FALSE)
   s <- s[s$date >= start & s$date <= end & s$flag == '' &
@@ -364,6 +374,11 @@ plot_versions <- function(start, end, path) {
          s$ec2bridge == '', ]
   s <- data.frame(date = as.Date(s$date, "%Y-%m-%d"), version = s$version,
                   relays = s$relays)
+  s
+}
+
+plot_versions <- function(start, end, path) {
+  s <- prepare_versions(start, end)
   known_versions <- c("Other", "0.1.0", "0.1.1", "0.1.2", "0.2.0",
         "0.2.1", "0.2.2", "0.2.3", "0.2.4", "0.2.5", "0.2.6", "0.2.7",
         "0.2.8", "0.2.9", "0.3.0", "0.3.1", "0.3.2", "0.3.3")
@@ -388,14 +403,26 @@ plot_versions <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_platforms <- function(start, end, path) {
+write_versions <- function(start, end, path) {
+  prepare_versions(start, end) %>%
+    spread(key = "version", value = "relays", fill = 0) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_platforms <- function(start, end) {
   s <- read.csv(paste(stats_dir, "servers.csv", sep = ""),
     stringsAsFactors = FALSE)
   s <- s[s$date >= start & s$date <= end & s$flag == '' &
          s$country == '' & s$version == '' & s$platform != '' &
          s$ec2bridge == '', ]
   platforms <- data.frame(date = as.Date(s$date, "%Y-%m-%d"),
-                  variable = s$platform, value = s$relays)
+      variable = ifelse(s$platform == "Darwin", "macOS", s$platform),
+      value = s$relays)
+  platforms
+}
+
+plot_platforms <- function(start, end, path) {
+  platforms <- prepare_platforms(start, end)
   ggplot(platforms, aes(x = as.Date(date, "%Y-%m-%d"), y = value,
       colour = variable)) +
     geom_line() +
@@ -403,25 +430,35 @@ plot_platforms <- function(start, end, path) {
       labels = custom_labels, minor_breaks = custom_minor_breaks) +
     scale_y_continuous(name = "", labels = formatter, limits = c(0, NA)) +
     scale_colour_manual(name = "Platform",
-      breaks = c("Linux", "Darwin", "BSD", "Windows", "Other"),
-      labels = c("Linux", "macOS", "BSD", "Windows", "Other"),
+      breaks = c("Linux", "macOS", "BSD", "Windows", "Other"),
       values = c("#E69F00", "#56B4E9", "#009E73", "#0072B2", "#333333")) +
     ggtitle("Relay platforms") +
     labs(caption = copyright_notice)
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_bandwidth <- function(start, end, path) {
+write_platforms <- function(start, end, path) {
+  prepare_platforms(start, end) %>%
+    spread(variable, value) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_bandwidth <- function(start, end) {
   b <- read.csv(paste(stats_dir, "bandwidth.csv", sep = ""),
     stringsAsFactors = FALSE)
   b <- b[b$date >= start & b$date <= end & b$isexit == '' &
          b$isguard == '', ]
   b <- data.frame(date = as.Date(b$date, "%Y-%m-%d"),
-                  bwadv = b$advbw,
-                  bwhist = (b$bwread + b$bwwrite) / 2)
+                  bwadv = b$advbw * 8 / 1e9,
+                  bwhist = (b$bwread + b$bwwrite) * 8 / 2e9)
+  b
+}
+
+plot_bandwidth <- function(start, end, path) {
+  b <- prepare_bandwidth(start, end)
   bandwidth <- melt(b, id = "date")
   ggplot(bandwidth, aes(x = as.Date(date, "%Y-%m-%d"),
-      y = value * 8 / 1e9, colour = variable)) +
+      y = value, colour = variable)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
       labels = custom_labels, minor_breaks = custom_minor_breaks) +
@@ -436,7 +473,12 @@ plot_bandwidth <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_bwhist_flags <- function(start, end, path) {
+write_bandwidth <- function(start, end, path) {
+  prepare_bandwidth(start, end) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_bwhist_flags <- function(start, end) {
   b <- read.csv(paste(stats_dir, "bandwidth.csv", sep = ""),
     stringsAsFactors = FALSE)
   b <- b[b$date >= start & b$date <= end & b$isexit != '' &
@@ -458,10 +500,15 @@ plot_bwhist_flags <- function(start, end, path) {
         data.frame(date = as.Date(missing, origin = "1970-01-01"),
         isexit = TRUE, isguard = TRUE, read = NA, written = NA))
   bw <- data.frame(date = bw$date, variable = ifelse(bw$isexit,
-        ifelse(bw$isguard, "Guard & Exit", "Exit only"),
-        ifelse(bw$isguard, "Guard only", "Middle only")),
-        value = (bw$read + bw$written) / 2)
-  ggplot(bw, aes(x = as.Date(date, "%Y-%m-%d"), y = value * 8 / 1e9,
+        ifelse(bw$isguard, "guard_and_exit", "exit_only"),
+        ifelse(bw$isguard, "guard_only", "middle_only")),
+        value = (bw$read + bw$written) * 8 / 2e9)
+  bw
+}
+
+plot_bwhist_flags <- function(start, end, path) {
+  bw <- prepare_bwhist_flags(start, end)
+  ggplot(bw, aes(x = as.Date(date, "%Y-%m-%d"), y = value,
       colour = variable)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
@@ -469,22 +516,36 @@ plot_bwhist_flags <- function(start, end, path) {
     scale_y_continuous(name = "", labels = unit_format(unit = "Gbit/s"),
       limits = c(0, NA)) +
     scale_colour_manual(name = "",
-        values = c("#E69F00", "#56B4E9", "#009E73", "#0072B2")) +
+      breaks = c("exit_only", "guard_and_exit", "guard_only", "middle_only"),
+      labels = c("Exit only", "Guard & Exit", "Guard only", "Middle only"),
+      values = c("#E69F00", "#56B4E9", "#009E73", "#0072B2")) +
     ggtitle("Bandwidth history by relay flags") +
     labs(caption = copyright_notice) +
     theme(legend.position = "top")
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_dirbytes <- function(start, end, path) {
+write_bwhist_flags <- function(start, end, path) {
+  prepare_bwhist_flags(start, end) %>%
+    spread(variable, value) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_dirbytes <- function(start, end, path) {
   b <- read.csv(paste(stats_dir, "bandwidth.csv", sep = ""),
     stringsAsFactors = FALSE)
   b <- b[b$date >= start & b$date <= end & b$isexit == '' &
          b$isguard == '', ]
   b <- data.frame(date = as.Date(b$date, "%Y-%m-%d"),
-                  dirread = b$dirread, dirwrite = b$dirwrite)
+                  dirread = b$dirread * 8 / 1e9,
+                  dirwrite = b$dirwrite * 8 / 1e9)
+  b
+}
+
+plot_dirbytes <- function(start, end, path) {
+  b <- prepare_dirbytes(start, end)
   dir <- melt(b, id = "date")
-  ggplot(dir, aes(x = as.Date(date, "%Y-%m-%d"), y = value * 8 / 1e9,
+  ggplot(dir, aes(x = as.Date(date, "%Y-%m-%d"), y = value,
       colour = variable)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
@@ -500,7 +561,12 @@ plot_dirbytes <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_relayflags <- function(start, end, flags, path) {
+write_dirbytes <- function(start, end, path) {
+  prepare_dirbytes(start, end) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_relayflags <- function(start, end, flags) {
   s <- read.csv(paste(stats_dir, "servers.csv", sep = ""),
     stringsAsFactors = FALSE)
   s <- s[s$date >= start & s$date <= end & s$country == '' &
@@ -509,6 +575,11 @@ plot_relayflags <- function(start, end, flags, path) {
                   variable = ifelse(s$flag == '', 'Running', s$flag),
                   value = s$relays)
   networksize <- s[s$variable %in% flags, ]
+  networksize
+}
+
+plot_relayflags <- function(start, end, flags, path) {
+  networksize <- prepare_relayflags(start, end, flags)
   networksize <- rbind(data.frame(
     date = as.Date(end) + 1,
     variable = c("Running", "Exit", "Guard", "Fast", "Stable", "HSDir"),
@@ -534,6 +605,13 @@ plot_relayflags <- function(start, end, flags, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
+write_relayflags <- function(start, end, flags, path) {
+  prepare_relayflags(start, end, flags) %>%
+    mutate(variable = tolower(variable)) %>%
+    spread(variable, value) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
 plot_torperf <- function(start, end, source, server, filesize, path) {
   filesizeVal <- ifelse(filesize == '50kb', 50 * 1024,
           ifelse(filesize == '1mb', 1024 * 1024, 5 * 1024 * 1024))
@@ -580,35 +658,51 @@ plot_torperf <- function(start, end, source, server, filesize, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_torperf_failures <- function(start, end, source, server, filesize, path) {
+# Ideally, this function would share code with plot_torperf by using a
+# common prepare_torperf function. This just turned out to be a bit
+# harder than for other functions, because plot_torperf uses different
+# colours based on which sources exist, unrelated to which source is
+# plotted. Left as future work.
+write_torperf <- function(start, end, source_, server_, filesize_, path) {
+  read.csv(paste(stats_dir, "torperf-1.1.csv", sep = ""),
+    colClasses = c("date" = "Date")) %>%
+    filter(date >= as.Date(start), date <= as.Date(end),
+      filesize == ifelse(filesize_ == '50kb', 50 * 1024,
+        ifelse(filesize_ == '1mb', 1024 * 1024, 5 * 1024 * 1024)),
+      source == ifelse(source_ == 'all', '', source_),
+      server == server_) %>%
+    select(date, q1, md, q3) %>%
+    mutate(q1 = q1 / 1e3, md = md / 1e3, q3 = q3 / 1e3) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_torperf_failures <- function(start, end, source, server, filesize) {
   filesizeVal <- ifelse(filesize == '50kb', 50 * 1024,
           ifelse(filesize == '1mb', 1024 * 1024, 5 * 1024 * 1024))
   t <- read.csv(paste(stats_dir, "torperf-1.1.csv", sep = ""),
     stringsAsFactors = FALSE)
   t <- t[t$date >= start & t$date <= end & t$filesize == filesizeVal &
          t$source == ifelse(source == 'all', '', source) &
-         t$server == server, ]
+         t$server == server & t$requests > 0, ]
   torperf <- data.frame(date = as.Date(t$date, "%Y-%m-%d"),
-                        timeouts = t$timeouts, failures = t$failures,
-                        requests = t$requests)
+                        timeouts = t$timeouts / t$requests,
+                        failures = t$failures / t$requests)
+  torperf
+}
+
+plot_torperf_failures <- function(start, end, source, server, filesize, path) {
+  torperf <- prepare_torperf_failures(start, end, source, server, filesize)
   dates <- seq(from = as.Date(start, "%Y-%m-%d"),
       to = as.Date(end, "%Y-%m-%d"), by="1 day")
   missing <- setdiff(dates, torperf$date)
   if (length(missing) > 0)
     torperf <- rbind(torperf,
         data.frame(date = as.Date(missing, origin = "1970-01-01"),
-        timeouts = NA, failures = NA, requests = NA))
+        timeouts = NA, failures = NA))
+  torperf <- melt(torperf, id = "date")
   filesizes <- data.frame(filesizes = c("5mb", "1mb", "50kb"),
       label = c("5 MiB", "1 MiB", "50 KiB"), stringsAsFactors = FALSE)
   filesizeStr <- filesizes[filesizes$filesize == filesize, "label"]
-  torperf <- rbind(data.frame(date = torperf$date,
-      value = ifelse(torperf$requests > 0,
-                     torperf$timeouts / torperf$requests, 0),
-      variable = "timeouts"),
-    data.frame(date = torperf$date,
-      value = ifelse(torperf$requests > 0,
-                     torperf$failures / torperf$requests, 0),
-      variable = "failures"))
   ggplot(torperf, aes(x = as.Date(date, "%Y-%m-%d"), y = value,
     colour = variable)) +
     geom_point(size = 2) +
@@ -626,7 +720,12 @@ plot_torperf_failures <- function(start, end, source, server, filesize, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_connbidirect <- function(start, end, path) {
+write_torperf_failures <- function(start, end, source, server, filesize, path) {
+  prepare_torperf_failures(start, end, source, server, filesize) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_connbidirect <- function(start, end) {
   c <- read.csv(paste(stats_dir, "connbidirect2.csv", sep = ""),
     stringsAsFactors = FALSE)
   c <- c[c$date >= start & c$date <= end, ]
@@ -636,6 +735,11 @@ plot_connbidirect <- function(start, end, path) {
                   quantile = paste("X", c$quantile, sep = ""),
                   fraction = c$fraction / 100)
   c <- cast(c, date + direction ~ quantile, value = "fraction")
+  c
+}
+
+plot_connbidirect <- function(start, end, path) {
+  c <- prepare_connbidirect(start, end)
   ggplot(c, aes(x = date, y = X0.5, colour = direction)) +
     geom_line(size = 0.75) +
     geom_ribbon(aes(x = date, ymin = X0.25, ymax = X0.75,
@@ -657,28 +761,33 @@ plot_connbidirect <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_bandwidth_flags <- function(start, end, path) {
+write_connbidirect <- function(start, end, path) {
+  prepare_connbidirect(start, end) %>%
+    rename(q1 = X0.25, md = X0.5, q3 = X0.75) %>%
+    gather(variable, value, -(date:direction)) %>%
+    unite(temp, direction, variable) %>%
+    spread(temp, value) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_bandwidth_flags <- function(start, end) {
   b <- read.csv(paste(stats_dir, "bandwidth.csv", sep = ""),
     stringsAsFactors = FALSE)
   b <- b[b$date >= start & b$date <= end & b$isexit != '' &
          b$isguard != '', ]
   b <- data.frame(date = as.Date(b$date, "%Y-%m-%d"),
                   isexit = b$isexit == 't', isguard = b$isguard == 't',
-                  advbw = b$advbw,
-                  bwhist = floor((b$bwread + b$bwwrite) / 2))
+                  advbw = b$advbw * 8 / 1e9,
+                  bwhist = (b$bwread + b$bwwrite) * 8 / 2e9)
   b <- rbind(
-    data.frame(b[b$isguard == TRUE, ], flag = "Guard"),
-    data.frame(b[b$isexit == TRUE, ], flag = "Exit"))
+    data.frame(b[b$isguard == TRUE, ], flag = "guard"),
+    data.frame(b[b$isexit == TRUE, ], flag = "exit"))
   b <- data.frame(date = b$date, advbw = b$advbw, bwhist = b$bwhist,
                   flag = b$flag)
   b <- aggregate(list(advbw = b$advbw, bwhist = b$bwhist),
                  by = list(date = b$date, flag = b$flag), FUN = sum,
                  na.rm = TRUE, na.action = NULL)
-  b <- melt(b, id.vars = c("date", "flag"))
-  b <- data.frame(date = b$date,
-      type = ifelse(b$variable == 'advbw', 'advertised bandwidth',
-                    'bandwidth history'),
-      flag = b$flag, value = b$value)
+  b <- melt(b, id.vars = c("date", "flag"), variable_name = "type")
   bandwidth <- b[b$value > 0, ]
   dates <- seq(from = as.Date(start, "%Y-%m-%d"),
       to = as.Date(end, "%Y-%m-%d"), by = "1 day")
@@ -687,27 +796,35 @@ plot_bandwidth_flags <- function(start, end, path) {
   if (length(missing) > 0) {
     bandwidth <- rbind(bandwidth,
         data.frame(date = as.Date(missing, origin = "1970-01-01"),
-        type = "advertised bandwidth", flag = "Exit", value = NA),
+        type = "advbw", flag = "exit", value = NA),
         data.frame(date = as.Date(missing, origin = "1970-01-01"),
-        type = "bandwidth history", flag = "Exit", value = NA),
+        type = "bwhist", flag = "exit", value = NA),
         data.frame(date = as.Date(missing, origin = "1970-01-01"),
-        type = "advertised bandwidth", flag = "Guard", value = NA),
+        type = "advbw", flag = "guard", value = NA),
         data.frame(date = as.Date(missing, origin = "1970-01-01"),
-        type = "bandwidth history", flag = "Guard", value = NA))
+        type = "bwhist", flag = "guard", value = NA))
   }
   bandwidth <- data.frame(date = bandwidth$date,
-    variable = as.factor(paste(bandwidth$flag, ", ", bandwidth$type,
+    variable = as.factor(paste(bandwidth$flag, "_", bandwidth$type,
     sep = "")), value = bandwidth$value)
   bandwidth$variable <- factor(bandwidth$variable,
     levels = levels(bandwidth$variable)[c(3, 4, 1, 2)])
+  bandwidth
+}
+
+plot_bandwidth_flags <- function(start, end, path) {
+  bandwidth <- prepare_bandwidth_flags(start, end)
   ggplot(bandwidth, aes(x = as.Date(date, "%Y-%m-%d"),
-      y = value * 8 / 1e9, colour = variable)) +
+      y = value, colour = variable)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
       labels = custom_labels, minor_breaks = custom_minor_breaks) +
     scale_y_continuous(name = "", labels = unit_format(unit = "Gbit/s"),
       limits = c(0, NA)) +
     scale_colour_manual(name = "",
+        breaks = c("guard_advbw", "guard_bwhist", "exit_advbw", "exit_bwhist"),
+        labels = c("Guard, advertised bandwidth", "Guard, bandwidth history",
+                   "Exit, advertised bandwidth", "Exit, bandwidth history"),
         values = c("#E69F00", "#D6C827", "#009E73", "#00C34F")) +
     ggtitle(paste("Advertised bandwidth and bandwidth history by",
         "relay flags")) +
@@ -716,6 +833,12 @@ plot_bandwidth_flags <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
+write_bandwidth_flags <- function(start, end, path) {
+  prepare_bandwidth_flags(start, end) %>%
+    spread(variable, value) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
 plot_userstats <- function(start, end, node, variable, value, events,
                            path) {
   load(paste(rdata_dir, "clients-", node, ".RData", sep = ""))
@@ -861,20 +984,96 @@ plot_userstats_bridge_version <- function(start, end, version, path) {
   plot_userstats(start, end, 'bridge', 'version', version, 'off', path)
 }
 
+write_userstats_relay_country <- function(start, end, country_, events,
+    path) {
+  load(paste(rdata_dir, "clients-relay.RData", sep = ""))
+  u <- data %>%
+    filter(date >= as.Date(start), date <= as.Date(end),
+      country == ifelse(country_ == 'all', '', country_), transport == '',
+      version == '')
+  if (country_ != 'all' && events == 'on') {
+    u <- u %>%
+      mutate(downturns = clients < u$lower, upturns = clients > upper) %>%
+      select(date, clients, downturns, upturns, lower, upper)
+  } else if (country_ != 'all' && events != 'off') {
+    u <- u %>%
+      mutate(downturns = clients < u$lower, upturns = clients > upper) %>%
+      select(date, clients, downturns, upturns)
+  } else {
+    u <- u %>%
+      select(date, clients)
+  }
+  u %>%
+    rename(users = clients) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+write_userstats_bridge_country <- function(start, end, country_, path) {
+  load(paste(rdata_dir, "clients-bridge.RData", sep = ""))
+  data %>%
+    filter(date >= as.Date(start), date <= as.Date(end),
+      country == ifelse(country_ == 'all', '', country_), transport == '',
+      version == '') %>%
+    select(date, clients) %>%
+    rename(users = clients) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+write_userstats_bridge_transport <- function(start, end, transports, path) {
+  load(paste(rdata_dir, "clients-bridge.RData", sep = ""))
+  u <- data %>%
+    filter(date >= as.Date(start), date <= as.Date(end),
+      country == '', version == '', transport != '') %>%
+    select(date, transport, clients)
+  if ('!<OR>' %in% transports) {
+    n <- u %>%
+      filter(transport != '<OR>') %>%
+      group_by(date) %>%
+      summarize(clients = sum(clients))
+    u <- rbind(u, data.frame(date = n$date, transport = '!<OR>',
+                             clients = n$clients))
+  }
+  u %>%
+    filter(transport %in% transports) %>%
+    mutate(transport = ifelse(transport == '<OR>', 'default_or_protocol',
+      ifelse(transport == '!<OR>', 'any_pt',
+      ifelse(transport == '<??>', 'unknown_pluggable_transports',
+      transport)))) %>%
+    group_by(date, transport) %>%
+    select(date, transport, clients) %>%
+    spread(transport, clients) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+write_userstats_bridge_version <- function(start, end, version_, path) {
+  load(paste(rdata_dir, "clients-bridge.RData", sep = ""))
+  data %>%
+    filter(date >= as.Date(start), date <= as.Date(end),
+      country == '', transport == '', version == version_) %>%
+    select(date, clients) %>%
+    rename(users = clients) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_userstats_bridge_combined <- function(start, end, country) {
+  top <- 3
+  country <- ifelse(country == "all", NA, country)
+  load(paste(rdata_dir, "userstats-bridge-combined.RData", sep = ""))
+  u <- data
+  u <- u[u$date >= start & u$date <= end
+         & (is.na(country) | u$country == country), ]
+  a <- aggregate(list(mid = (u$high + u$low) / 2),
+                 by = list(transport = u$transport), FUN = sum)
+  a <- a[order(a$mid, decreasing = TRUE)[1:top], ]
+  u <- u[u$transport %in% a$transport, ]
+  u
+}
+
 plot_userstats_bridge_combined <- function(start, end, country, path) {
   if (country == "all") {
     plot_userstats_bridge_country(start, end, country, path)
   } else {
-    top <- 3
-    country <- ifelse(country == "all", NA, country)
-    load(paste(rdata_dir, "userstats-bridge-combined.RData", sep = ""))
-    u <- data
-    u <- u[u$date >= start & u$date <= end
-           & (is.na(country) | u$country == country), ]
-    a <- aggregate(list(mid = (u$high + u$low) / 2),
-                   by = list(transport = u$transport), FUN = sum)
-    a <- a[order(a$mid, decreasing = TRUE)[1:top], ]
-    u <- u[u$transport %in% a$transport, ]
+    u <- prepare_userstats_bridge_combined(start, end, country)
     title <- paste("Bridge users by transport from ",
                    countryname(country), sep = "")
     ggplot(u, aes(x = as.Date(date), ymin = low, ymax = high,
@@ -883,8 +1082,8 @@ plot_userstats_bridge_combined <- function(start, end, country, path) {
     scale_x_date(name = "", breaks = custom_breaks,
       labels = custom_labels, minor_breaks = custom_minor_breaks) +
     scale_y_continuous(name = "", limits = c(0, NA), labels = formatter) +
-    scale_colour_hue(paste("Top-", top, " transports", sep = "")) +
-    scale_fill_hue(paste("Top-", top, " transports", sep = "")) +
+    scale_colour_hue("Top-3 transports") +
+    scale_fill_hue("Top-3 transports") +
     ggtitle(title) +
     labs(caption = copyright_notice) +
     theme(legend.position = "top")
@@ -892,15 +1091,36 @@ plot_userstats_bridge_combined <- function(start, end, country, path) {
   }
 }
 
-plot_advbwdist_perc <- function(start, end, p, path) {
+write_userstats_bridge_combined <- function(start, end, country, path) {
+  if (country == "all") {
+    write_userstats_bridge_country(start, end, country, path)
+  } else {
+    prepare_userstats_bridge_combined(start, end, country) %>%
+      select(date, transport, low, high) %>%
+      mutate(transport = ifelse(transport == '<OR>',
+                                'default_or_protocol', transport)) %>%
+      gather(variable, value, -(date:transport)) %>%
+      unite(temp, transport, variable) %>%
+      spread(temp, value) %>%
+      write.csv(path, quote = FALSE, row.names = FALSE)
+  }
+}
+
+prepare_advbwdist_perc <- function(start, end, p) {
   t <- read.csv(paste(stats_dir,
                 "advbwdist.csv", sep = ""), stringsAsFactors = FALSE)
   t <- t[t$date >= start & t$date <= end &
          t$percentile %in% as.numeric(p), ]
-  t <- data.frame(date = t$date, advbw = t$advbw * 8 / 1e9,
-                  variable = ifelse(t$isexit != "t", "All relays",
-                                    "Exits only"),
-                  percentile = as.factor(t$percentile))
+  t <- data.frame(date = t$date, percentile = as.factor(t$percentile),
+                  variable = ifelse(t$isexit != "t", "all", "exits"),
+                  advbw = t$advbw * 8 / 1e9)
+  t
+}
+
+plot_advbwdist_perc <- function(start, end, p, path) {
+  t <- prepare_advbwdist_perc(start, end, p)
+  t$variable <- ifelse(t$variable == "all", "All relays",
+                       "Exits only")
   ggplot(t, aes(x = as.Date(date), y = advbw, colour = percentile)) +
     facet_grid(variable ~ .) +
     geom_line() +
@@ -915,14 +1135,27 @@ plot_advbwdist_perc <- function(start, end, p, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_advbwdist_relay <- function(start, end, n, path) {
+write_advbwdist_perc <- function(start, end, p, path) {
+  prepare_advbwdist_perc(start, end, p) %>%
+    unite(temp, variable, percentile) %>%
+    spread(temp, advbw) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_advbwdist_relay <- function(start, end, n) {
   t <- read.csv(paste(stats_dir, "advbwdist.csv", sep = ""),
     stringsAsFactors = FALSE)
   t <- t[t$date >= start & t$date <= end & t$relay %in% as.numeric(n), ]
-  t <- data.frame(date = t$date, advbw = t$advbw * 8 / 1e9,
-                  variable = ifelse(t$isexit != "t", "All relays",
-                                    "Exits only"),
-                  relay = as.factor(t$relay))
+  t <- data.frame(date = t$date, relay = as.factor(t$relay),
+                  variable = ifelse(t$isexit != "t", "all", "exits"),
+                  advbw = t$advbw * 8 / 1e9)
+  t
+}
+
+plot_advbwdist_relay <- function(start, end, n, path) {
+  t <- prepare_advbwdist_relay(start, end, n)
+  t$variable <- ifelse(t$variable == "all", "All relays",
+                       "Exits only")
   ggplot(t, aes(x = as.Date(date), y = advbw, colour = relay)) +
     facet_grid(variable ~ .) +
     geom_line() +
@@ -936,14 +1169,25 @@ plot_advbwdist_relay <- function(start, end, n, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_hidserv_dir_onions_seen <- function(start, end, path) {
+write_advbwdist_relay <- function(start, end, n, path) {
+  prepare_advbwdist_relay(start, end, n) %>%
+    unite(temp, variable, relay) %>%
+    spread(temp, advbw) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_hidserv_dir_onions_seen <- function(start, end) {
   h <- read.csv(paste(stats_dir, "hidserv.csv", sep = ""),
     stringsAsFactors = FALSE)
   h <- h[h$date >= start & h$date <= end & h$type == "dir-onions-seen", ]
-  h <- rbind(data.frame(date = NA, wiqm = 0),
-             data.frame(date = as.Date(h$date, "%Y-%m-%d"),
-                        wiqm = ifelse(h$frac >= 0.01, h$wiqm, NA)))
-  ggplot(h, aes(x = as.Date(date, origin = "1970-01-01"), y = wiqm)) +
+  h <- data.frame(date = as.Date(h$date, "%Y-%m-%d"),
+                  onions = ifelse(h$frac >= 0.01, h$wiqm, NA))
+  h
+}
+
+plot_hidserv_dir_onions_seen <- function(start, end, path) {
+  h <- prepare_hidserv_dir_onions_seen(start, end)
+  ggplot(h, aes(x = as.Date(date, origin = "1970-01-01"), y = onions)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
       labels = custom_labels, minor_breaks = custom_minor_breaks) +
@@ -953,16 +1197,25 @@ plot_hidserv_dir_onions_seen <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_hidserv_rend_relayed_cells <- function(start, end, path) {
+write_hidserv_dir_onions_seen <- function(start, end, path) {
+  prepare_hidserv_dir_onions_seen(start, end) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_hidserv_rend_relayed_cells <- function(start, end) {
   h <- read.csv(paste(stats_dir, "hidserv.csv", sep = ""),
     stringsAsFactors = FALSE)
   h <- h[h$date >= start & h$date <= end &
          h$type == "rend-relayed-cells", ]
-  h <- rbind(data.frame(date = NA, wiqm = 0),
-             data.frame(date = as.Date(h$date, "%Y-%m-%d"),
-                        wiqm = ifelse(h$frac >= 0.01, h$wiqm, NA)))
-  ggplot(h, aes(x = as.Date(date, origin = "1970-01-01"),
-      y = wiqm * 8 * 512 / (86400 * 1e9))) +
+  h <- data.frame(date = as.Date(h$date, "%Y-%m-%d"),
+                  relayed = ifelse(h$frac >= 0.01,
+                                   h$wiqm * 8 * 512 / (86400 * 1e9), NA))
+  h
+}
+
+plot_hidserv_rend_relayed_cells <- function(start, end, path) {
+  h <- prepare_hidserv_rend_relayed_cells(start, end)
+  ggplot(h, aes(x = as.Date(date, origin = "1970-01-01"), y = relayed)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
       labels = custom_labels, minor_breaks = custom_minor_breaks) +
@@ -973,15 +1226,22 @@ plot_hidserv_rend_relayed_cells <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_hidserv_frac_reporting <- function(start, end, path) {
+write_hidserv_rend_relayed_cells <- function(start, end, path) {
+  prepare_hidserv_rend_relayed_cells(start, end) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_hidserv_frac_reporting <- function(start, end) {
   h <- read.csv(paste(stats_dir, "hidserv.csv", sep = ""),
     stringsAsFactors = FALSE)
   h <- h[h$date >= start & h$date <= end, ]
-  h <- rbind(data.frame(date = NA, frac = 0,
-                        type = c("rend-relayed-cells",
-                                 "dir-onions-seen")),
-             data.frame(date = as.Date(h$date, "%Y-%m-%d"),
-                        frac = h$frac, type = h$type))
+  h <- data.frame(date = as.Date(h$date, "%Y-%m-%d"),
+                  frac = h$frac, type = h$type)
+  h
+}
+
+plot_hidserv_frac_reporting <- function(start, end, path) {
+  h <- prepare_hidserv_frac_reporting(start, end)
   ggplot(h, aes(x = as.Date(date, origin = "1970-01-01"), y = frac,
       colour = type)) +
     geom_line() +
@@ -1000,11 +1260,23 @@ plot_hidserv_frac_reporting <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_webstats_tb <- function(start, end, path) {
+write_hidserv_frac_reporting <- function(start, end, path) {
+  prepare_hidserv_frac_reporting(start, end) %>%
+    mutate(type = ifelse(type == "dir-onions-seen", "onions", "relayed")) %>%
+    spread(type, frac) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_webstats_tb <- function(start, end) {
   load(paste(rdata_dir, "webstats-tb.RData", sep = ""))
   d <- data
   d <- d[d$log_date >= start & d$log_date <= end, ]
   d$request_type <- factor(d$request_type)
+  d
+}
+
+plot_webstats_tb <- function(start, end, path) {
+  d <- prepare_webstats_tb(start, end)
   levels(d$request_type) <- list(
       'Initial downloads' = 'tbid',
       'Signature downloads' = 'tbsd',
@@ -1024,12 +1296,26 @@ plot_webstats_tb <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_webstats_tb_platform <- function(start, end, path) {
+write_webstats_tb <- function(start, end, path) {
+  prepare_webstats_tb(start, end) %>%
+    rename(date = log_date) %>%
+    spread(request_type, count) %>%
+    rename(initial_downloads = tbid, signature_downloads = tbsd,
+      update_pings = tbup, update_requests = tbur) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_webstats_tb_platform <- function(start, end) {
   d <- read.csv(paste(stats_dir, "webstats.csv", sep = ""),
     stringsAsFactors = FALSE)
   d <- d[d$log_date >= start & d$log_date <= end & d$request_type == 'tbid', ]
   d <- aggregate(list(count = d$count), by = list(log_date = as.Date(d$log_date),
     platform = d$platform), FUN = sum)
+  d
+}
+
+plot_webstats_tb_platform <- function(start, end, path) {
+  d <- prepare_webstats_tb_platform(start, end)
   ggplot(d, aes(x = log_date, y = count, colour = platform)) +
     geom_point() +
     geom_line() +
@@ -1046,6 +1332,14 @@ plot_webstats_tb_platform <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
+write_webstats_tb_platform <- function(start, end, path) {
+  prepare_webstats_tb_platform(start, end) %>%
+    rename(date = log_date) %>%
+    spread(platform, count) %>%
+    rename(linux = l, macos = m, windows = w) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
 plot_webstats_tb_locale <- function(start, end, path) {
   d <- read.csv(paste(stats_dir, "webstats.csv", sep = ""),
     stringsAsFactors = FALSE)
@@ -1072,11 +1366,38 @@ plot_webstats_tb_locale <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_webstats_tm <- function(start, end, path) {
+# Ideally, this function would share code with plot_webstats_tb_locale
+# by using a common prepare_webstats_tb_locale function. This just
+# turned out to be a bit harder than for other functions, because
+# plot_webstats_tb_locale needs the preliminary data frame e for its
+# breaks and labels. Left as future work.
+write_webstats_tb_locale <- function(start, end, path) {
+  d <- read.csv(paste(stats_dir, "webstats.csv", sep = ""),
+    stringsAsFactors = FALSE)
+  d <- d[d$log_date >= start & d$log_date <= end & d$request_type == 'tbid', ]
+  e <- d
+  e <- aggregate(list(count = e$count), by = list(locale = e$locale), FUN = sum)
+  e <- e[order(e$count, decreasing = TRUE), ]
+  e <- e[1:5, ]
+  d <- aggregate(list(count = d$count), by = list(log_date = as.Date(d$log_date),
+    locale = ifelse(d$locale %in% e$locale, d$locale, 'other')), FUN = sum)
+  d %>%
+    mutate(locale = tolower(locale)) %>%
+    rename(date = log_date) %>%
+    spread(locale, count) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_webstats_tm <- function(start, end) {
   load(paste(rdata_dir, "webstats-tm.RData", sep = ""))
   d <- data
   d <- d[d$log_date >= start & d$log_date <= end, ]
   d$request_type <- factor(d$request_type)
+  d
+}
+
+plot_webstats_tm <- function(start, end, path) {
+  d <- prepare_webstats_tm(start, end)
   levels(d$request_type) <- list(
       'Initial downloads' = 'tmid',
       'Update pings' = 'tmup')
@@ -1094,7 +1415,15 @@ plot_webstats_tm <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_relays_ipv6 <- function(start, end, path) {
+write_webstats_tm <- function(start, end, path) {
+  prepare_webstats_tm(start, end) %>%
+    rename(date = log_date) %>%
+    spread(request_type, count) %>%
+    rename(initial_downloads = tmid, update_pings = tmup) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_relays_ipv6 <- function(start, end) {
   read.csv(paste(stats_dir, "ipv6servers.csv", sep = ""),
     colClasses = c("valid_after_date" = "Date")) %>%
     filter(valid_after_date >= as.Date(start),
@@ -1106,7 +1435,11 @@ plot_relays_ipv6 <- function(start, end, path) {
       exiting = sum(server_count_sum_avg[exiting_ipv6_relay == 't'])) %>%
     complete(valid_after_date = full_seq(valid_after_date, period = 1)) %>%
     gather(total, announced, reachable, exiting, key = "category",
-      value = "count") %>%
+      value = "count")
+}
+
+plot_relays_ipv6 <- function(start, end, path) {
+  prepare_relays_ipv6(start, end) %>%
     ggplot(aes(x = valid_after_date, y = count, colour = category)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
@@ -1122,7 +1455,14 @@ plot_relays_ipv6 <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_bridges_ipv6 <- function(start, end, path) {
+write_relays_ipv6 <- function(start, end, path) {
+  prepare_relays_ipv6(start, end) %>%
+    rename(date = valid_after_date) %>%
+    spread(category, count) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_bridges_ipv6 <- function(start, end) {
   read.csv(paste(stats_dir, "ipv6servers.csv", sep = ""),
     colClasses = c("valid_after_date" = "Date")) %>%
     filter(valid_after_date >= as.Date(start),
@@ -1131,7 +1471,11 @@ plot_bridges_ipv6 <- function(start, end, path) {
     summarize(total = sum(server_count_sum_avg),
       announced = sum(server_count_sum_avg[announced_ipv6 == 't'])) %>%
     complete(valid_after_date = full_seq(valid_after_date, period = 1)) %>%
-    gather(total, announced, key = "category", value = "count") %>%
+    gather(total, announced, key = "category", value = "count")
+}
+
+plot_bridges_ipv6 <- function(start, end, path) {
+  prepare_bridges_ipv6(start, end) %>%
     ggplot(aes(x = valid_after_date, y = count, colour = category)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
@@ -1146,7 +1490,14 @@ plot_bridges_ipv6 <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
-plot_advbw_ipv6 <- function(start, end, path) {
+write_bridges_ipv6 <- function(start, end, path) {
+  prepare_bridges_ipv6(start, end) %>%
+    rename(date = valid_after_date) %>%
+    spread(category, count) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
+prepare_advbw_ipv6 <- function(start, end) {
   read.csv(paste(stats_dir, "ipv6servers.csv", sep = ""),
     colClasses = c("valid_after_date" = "Date")) %>%
     filter(valid_after_date >= as.Date(start),
@@ -1163,9 +1514,13 @@ plot_advbw_ipv6 <- function(start, end, path) {
         exiting_ipv6_relay != 'f'])) %>%
     complete(valid_after_date = full_seq(valid_after_date, period = 1)) %>%
     gather(total, total_guard, total_exit, reachable_guard, reachable_exit,
-      exiting, key = "category", value = "count") %>%
-    ggplot(aes(x = valid_after_date, y = (count * 8) / 1e9,
-      colour = category)) +
+      exiting, key = "category", value = "advbw") %>%
+    mutate(advbw = advbw * 8 / 1e9)
+}
+
+plot_advbw_ipv6 <- function(start, end, path) {
+  prepare_advbw_ipv6(start, end) %>%
+    ggplot(aes(x = valid_after_date, y = advbw, colour = category)) +
     geom_line() +
     scale_x_date(name = "", breaks = custom_breaks,
       labels = custom_labels, minor_breaks = custom_minor_breaks) +
@@ -1183,3 +1538,10 @@ plot_advbw_ipv6 <- function(start, end, path) {
   ggsave(filename = path, width = 8, height = 5, dpi = 150)
 }
 
+write_advbw_ipv6 <- function(start, end, path) {
+  prepare_advbw_ipv6(start, end) %>%
+    rename(date = valid_after_date) %>%
+    spread(category, advbw) %>%
+    write.csv(path, quote = FALSE, row.names = FALSE)
+}
+
diff --git a/src/main/java/org/torproject/metrics/web/GraphImageServlet.java b/src/main/java/org/torproject/metrics/web/GraphImageServlet.java
index 0644fa2..f24d698 100644
--- a/src/main/java/org/torproject/metrics/web/GraphImageServlet.java
+++ b/src/main/java/org/torproject/metrics/web/GraphImageServlet.java
@@ -41,7 +41,8 @@ public class GraphImageServlet extends HttpServlet {
     String requestedGraph = request.getRequestURI();
     String fileType = null;
     if (requestedGraph.endsWith(".png")
-        || requestedGraph.endsWith(".pdf")) {
+        || requestedGraph.endsWith(".pdf")
+        || requestedGraph.endsWith(".csv")) {
       fileType = requestedGraph.substring(requestedGraph.length() - 3);
       requestedGraph = requestedGraph.substring(0, requestedGraph.length()
           - 4);
diff --git a/src/main/java/org/torproject/metrics/web/GraphServlet.java b/src/main/java/org/torproject/metrics/web/GraphServlet.java
index 31116b4..2781be0 100644
--- a/src/main/java/org/torproject/metrics/web/GraphServlet.java
+++ b/src/main/java/org/torproject/metrics/web/GraphServlet.java
@@ -151,7 +151,6 @@ public class GraphServlet extends MetricServlet {
     }
     request.setAttribute("description",
         this.descriptions.get(requestedId));
-    request.setAttribute("data", this.data.get(requestedId));
     SimpleDateFormat dateFormat = new SimpleDateFormat("yyyy-MM-dd");
     dateFormat.setTimeZone(TimeZone.getTimeZone("UTC"));
     Date defaultEndDate = new Date();
diff --git a/src/main/java/org/torproject/metrics/web/LinkServlet.java b/src/main/java/org/torproject/metrics/web/LinkServlet.java
index b2687f1..3dcaeb1 100644
--- a/src/main/java/org/torproject/metrics/web/LinkServlet.java
+++ b/src/main/java/org/torproject/metrics/web/LinkServlet.java
@@ -50,7 +50,6 @@ public class LinkServlet extends MetricServlet {
     }
     request.setAttribute("description",
         this.descriptions.get(requestedId));
-    request.setAttribute("data", this.data.get(requestedId));
     request.getRequestDispatcher("WEB-INF/link.jsp").forward(request,
         response);
   }
diff --git a/src/main/java/org/torproject/metrics/web/Metric.java b/src/main/java/org/torproject/metrics/web/Metric.java
index a5604eb..701351f 100644
--- a/src/main/java/org/torproject/metrics/web/Metric.java
+++ b/src/main/java/org/torproject/metrics/web/Metric.java
@@ -21,8 +21,6 @@ public class Metric {
 
   private String[] parameters;
 
-  private String[] data;
-
   private String[] table_headers;
 
   private String[] table_cell_formats;
@@ -75,10 +73,6 @@ public class Metric {
     return this.data_column_spec;
   }
 
-  public String[] getData() {
-    return this.data;
-  }
-
   public boolean getIncludeRelatedEvents() {
     return this.includeRelatedEvents;
   }
diff --git a/src/main/java/org/torproject/metrics/web/MetricServlet.java b/src/main/java/org/torproject/metrics/web/MetricServlet.java
index f5b29dd..b3de046 100644
--- a/src/main/java/org/torproject/metrics/web/MetricServlet.java
+++ b/src/main/java/org/torproject/metrics/web/MetricServlet.java
@@ -31,8 +31,6 @@ public abstract class MetricServlet extends AnyServlet {
 
   protected Map<String, String[]> tableCellFormats = new HashMap<>();
 
-  protected Map<String, String[]> data = new HashMap<>();
-
   protected Map<String, Category> categoriesById = new HashMap<>();
 
   protected Set<String> includeRelatedEvents = new HashSet<>();
@@ -62,9 +60,6 @@ public abstract class MetricServlet extends AnyServlet {
       if (metric.getTableCellFormats() != null) {
         this.tableCellFormats.put(id, metric.getTableCellFormats());
       }
-      if (metric.getData() != null) {
-        this.data.put(id, metric.getData());
-      }
       if (metric.getIncludeRelatedEvents()) {
         this.includeRelatedEvents.add(id);
       }
diff --git a/src/main/java/org/torproject/metrics/web/RObjectGenerator.java b/src/main/java/org/torproject/metrics/web/RObjectGenerator.java
index c7d0041..5d9b29c 100644
--- a/src/main/java/org/torproject/metrics/web/RObjectGenerator.java
+++ b/src/main/java/org/torproject/metrics/web/RObjectGenerator.java
@@ -124,8 +124,13 @@ public class RObjectGenerator implements ServletContextListener {
     if (checkedParameters == null) {
       return null;
     }
-    StringBuilder queryBuilder =
-        new StringBuilder().append(function).append("(");
+    StringBuilder queryBuilder = new StringBuilder();
+    if ("csv".equalsIgnoreCase(fileType)) {
+      queryBuilder.append("write_");
+    } else {
+      queryBuilder.append("plot_");
+    }
+    queryBuilder.append(function).append("(");
     StringBuilder imageFilenameBuilder =
         new StringBuilder(requestedGraph);
     for (Map.Entry<String, String[]> parameter
diff --git a/src/main/java/org/torproject/metrics/web/TableServlet.java b/src/main/java/org/torproject/metrics/web/TableServlet.java
index d37852f..84f46ee 100644
--- a/src/main/java/org/torproject/metrics/web/TableServlet.java
+++ b/src/main/java/org/torproject/metrics/web/TableServlet.java
@@ -62,7 +62,6 @@ public class TableServlet extends MetricServlet {
         this.descriptions.get(requestedId));
     request.setAttribute("tableheader",
         this.tableHeaders.get(requestedId));
-    request.setAttribute("data", this.data.get(requestedId));
     SimpleDateFormat dateFormat = new SimpleDateFormat("yyyy-MM-dd");
     dateFormat.setTimeZone(TimeZone.getTimeZone("UTC"));
     Date defaultEndDate = new Date();
diff --git a/src/main/resources/web.xml b/src/main/resources/web.xml
index 99df1db..a5c3212 100644
--- a/src/main/resources/web.xml
+++ b/src/main/resources/web.xml
@@ -121,62 +121,91 @@
     <servlet-name>GraphImage</servlet-name>
     <url-pattern>/networksize.png</url-pattern>
     <url-pattern>/networksize.pdf</url-pattern>
+    <url-pattern>/networksize.csv</url-pattern>
     <url-pattern>/relaycountries.png</url-pattern>
     <url-pattern>/relaycountries.pdf</url-pattern>
+    <url-pattern>/relaycountries.csv</url-pattern>
     <url-pattern>/relayflags.png</url-pattern>
     <url-pattern>/relayflags.pdf</url-pattern>
+    <url-pattern>/relayflags.csv</url-pattern>
     <url-pattern>/versions.png</url-pattern>
     <url-pattern>/versions.pdf</url-pattern>
+    <url-pattern>/versions.csv</url-pattern>
     <url-pattern>/platforms.png</url-pattern>
     <url-pattern>/platforms.pdf</url-pattern>
+    <url-pattern>/platforms.csv</url-pattern>
     <url-pattern>/bandwidth.png</url-pattern>
     <url-pattern>/bandwidth.pdf</url-pattern>
+    <url-pattern>/bandwidth.csv</url-pattern>
     <url-pattern>/bwhist-flags.png</url-pattern>
     <url-pattern>/bwhist-flags.pdf</url-pattern>
+    <url-pattern>/bwhist-flags.csv</url-pattern>
     <url-pattern>/bandwidth-flags.png</url-pattern>
     <url-pattern>/bandwidth-flags.pdf</url-pattern>
+    <url-pattern>/bandwidth-flags.csv</url-pattern>
     <url-pattern>/dirbytes.png</url-pattern>
     <url-pattern>/dirbytes.pdf</url-pattern>
+    <url-pattern>/dirbytes.csv</url-pattern>
     <url-pattern>/torperf.png</url-pattern>
     <url-pattern>/torperf.pdf</url-pattern>
+    <url-pattern>/torperf.csv</url-pattern>
     <url-pattern>/torperf-failures.png</url-pattern>
     <url-pattern>/torperf-failures.pdf</url-pattern>
+    <url-pattern>/torperf-failures.csv</url-pattern>
     <url-pattern>/connbidirect.png</url-pattern>
     <url-pattern>/connbidirect.pdf</url-pattern>
+    <url-pattern>/connbidirect.csv</url-pattern>
     <url-pattern>/userstats-relay-country.png</url-pattern>
     <url-pattern>/userstats-relay-country.pdf</url-pattern>
+    <url-pattern>/userstats-relay-country.csv</url-pattern>
     <url-pattern>/userstats-bridge-country.png</url-pattern>
     <url-pattern>/userstats-bridge-country.pdf</url-pattern>
+    <url-pattern>/userstats-bridge-country.csv</url-pattern>
     <url-pattern>/userstats-bridge-transport.png</url-pattern>
     <url-pattern>/userstats-bridge-transport.pdf</url-pattern>
+    <url-pattern>/userstats-bridge-transport.csv</url-pattern>
     <url-pattern>/userstats-bridge-combined.png</url-pattern>
     <url-pattern>/userstats-bridge-combined.pdf</url-pattern>
+    <url-pattern>/userstats-bridge-combined.csv</url-pattern>
     <url-pattern>/userstats-bridge-version.png</url-pattern>
     <url-pattern>/userstats-bridge-version.pdf</url-pattern>
+    <url-pattern>/userstats-bridge-version.csv</url-pattern>
     <url-pattern>/advbwdist-perc.png</url-pattern>
     <url-pattern>/advbwdist-perc.pdf</url-pattern>
+    <url-pattern>/advbwdist-perc.csv</url-pattern>
     <url-pattern>/advbwdist-relay.png</url-pattern>
     <url-pattern>/advbwdist-relay.pdf</url-pattern>
+    <url-pattern>/advbwdist-relay.csv</url-pattern>
     <url-pattern>/hidserv-dir-onions-seen.png</url-pattern>
     <url-pattern>/hidserv-dir-onions-seen.pdf</url-pattern>
+    <url-pattern>/hidserv-dir-onions-seen.csv</url-pattern>
     <url-pattern>/hidserv-rend-relayed-cells.png</url-pattern>
     <url-pattern>/hidserv-rend-relayed-cells.pdf</url-pattern>
+    <url-pattern>/hidserv-rend-relayed-cells.csv</url-pattern>
     <url-pattern>/hidserv-frac-reporting.png</url-pattern>
     <url-pattern>/hidserv-frac-reporting.pdf</url-pattern>
+    <url-pattern>/hidserv-frac-reporting.csv</url-pattern>
     <url-pattern>/webstats-tb.png</url-pattern>
     <url-pattern>/webstats-tb.pdf</url-pattern>
+    <url-pattern>/webstats-tb.csv</url-pattern>
     <url-pattern>/webstats-tb-platform.png</url-pattern>
     <url-pattern>/webstats-tb-platform.pdf</url-pattern>
+    <url-pattern>/webstats-tb-platform.csv</url-pattern>
     <url-pattern>/webstats-tb-locale.png</url-pattern>
     <url-pattern>/webstats-tb-locale.pdf</url-pattern>
+    <url-pattern>/webstats-tb-locale.csv</url-pattern>
     <url-pattern>/webstats-tm.png</url-pattern>
     <url-pattern>/webstats-tm.pdf</url-pattern>
-    <url-pattern>/relays-ipv6.pdf</url-pattern>
+    <url-pattern>/webstats-tm.csv</url-pattern>
     <url-pattern>/relays-ipv6.png</url-pattern>
-    <url-pattern>/bridges-ipv6.pdf</url-pattern>
+    <url-pattern>/relays-ipv6.pdf</url-pattern>
+    <url-pattern>/relays-ipv6.csv</url-pattern>
     <url-pattern>/bridges-ipv6.png</url-pattern>
-    <url-pattern>/advbw-ipv6.pdf</url-pattern>
+    <url-pattern>/bridges-ipv6.pdf</url-pattern>
+    <url-pattern>/bridges-ipv6.csv</url-pattern>
     <url-pattern>/advbw-ipv6.png</url-pattern>
+    <url-pattern>/advbw-ipv6.pdf</url-pattern>
+    <url-pattern>/advbw-ipv6.csv</url-pattern>
   </servlet-mapping>
 
   <servlet>
diff --git a/src/main/resources/web/json/metrics.json b/src/main/resources/web/json/metrics.json
index 0b8aca7..0739b88 100644
--- a/src/main/resources/web/json/metrics.json
+++ b/src/main/resources/web/json/metrics.json
@@ -4,13 +4,10 @@
     "title": "Relays and bridges",
     "type": "Graph",
     "description": "<p>This graph shows the number of running <a href=\"glossary.html#relay\">relays</a> and <a href=\"glossary.html#bridge\">bridges</a> in the network.</p>",
-    "function": "plot_networksize",
+    "function": "networksize",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "servers"
     ]
   },
   {
@@ -18,14 +15,11 @@
     "title": "Relays by relay flag",
     "type": "Graph",
     "description": "<p>This graph shows the number of running <a href=\"glossary.html#relay\">relays</a> that have had certain <a href=\"glossary.html#relay-flag\">flags</a> assigned by the <a href=\"glossary.html#directory-authority\">directory authorities</a>.  These flags indicate that a relay should be preferred for either guard (\"Guard\") or exit positions (\"Exit\"), that a relay is suitable for high-bandwidth (\"Fast\") or long-lived circuits (\"Stable\"), or that a relay is considered a onion service directory (\"HSDir\").</p>",
-    "function": "plot_relayflags",
+    "function": "relayflags",
     "parameters": [
       "start",
       "end",
       "flag"
-    ],
-    "data": [
-      "servers"
     ]
   },
   {
@@ -33,13 +27,10 @@
     "title": "Relays by tor version",
     "type": "Graph",
     "description": "<p>This graph shows the number of running <a href=\"glossary.html#relay\">relays</a> by tor software version.  Relays report their tor software version when they announce themselves in the network.  More details on when these versions were declared stable or unstable can be found on the <a href=\"https://www.torproject.org/download/download.html\">download page</a> and in the <a href=\"https://gitweb.torproject.org/tor.git/tree/ChangeLog\">changes file</a>.</p>",
-    "function": "plot_versions",
+    "function": "versions",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "servers"
     ]
   },
   {
@@ -47,13 +38,10 @@
     "title": "Relays by platform",
     "type": "Graph",
     "description": "<p>This graph shows the number of running <a href=\"glossary.html#relay\">relays</a> by operating system.  Relays report their operating system when they announce themselves in the network.</p>",
-    "function": "plot_platforms",
+    "function": "platforms",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "servers"
     ]
   },
   {
@@ -61,13 +49,10 @@
     "title": "Relays by IP version",
     "type": "Graph",
     "description": "<p>This graph shows the number of <a href=\"glossary.html#relay\">relays</a> supporting IPv6 as compared to all relays. A relay can support IPv6 by announcing an IPv6 address and port for the OR protocol, which may then be confirmed as reachable by the <a href=\"glossary.html#directory-authority\">directory authorities</a>, and by permitting exiting to IPv6 targets. These sets are not distinct, because relays can have various combinations of announced/confirmed OR ports and exit policies.</p>",
-    "function": "plot_relays_ipv6",
+    "function": "relays_ipv6",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "ipv6servers"
     ]
   },
   {
@@ -75,13 +60,10 @@
     "title": "Bridges by IP version",
     "type": "Graph",
     "description": "<p>This graph shows the number of <a href=\"glossary.html#bridge\">bridges</a> supporting IPv6 as compared to all bridges. A bridge can support IPv6 by announcing an IPv6 address and port for the OR protocol.</p>",
-    "function": "plot_bridges_ipv6",
+    "function": "bridges_ipv6",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "ipv6servers"
     ]
   },
   {
@@ -89,13 +71,10 @@
     "title": "Total relay bandwidth",
     "type": "Graph",
     "description": "<p>This graph shows the total <a href=\"glossary.html#advertised-bandwidth\">advertised</a> and <a href=\"glossary.html#bandwidth-history\">consumed bandwidth</a> of all <a href=\"glossary.html#relay\">relays</a> in the network.</p>",
-    "function": "plot_bandwidth",
+    "function": "bandwidth",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "bandwidth"
     ]
   },
   {
@@ -103,13 +82,10 @@
     "title": "Consumed bandwidth by Exit/Guard flag combination",
     "type": "Graph",
     "description": "<p>This graph shows the <a href=\"glossary.html#bandwidth-history\">consumed bandwidth</a> reported by relays, subdivided into four distinct subsets by assigned \"Exit\" and/or \"Guard\" <a href=\"glossary.html#relay-flag\">flags</a>.</p>",
-    "function": "plot_bwhist_flags",
+    "function": "bwhist_flags",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "bandwidth"
     ]
   },
   {
@@ -117,13 +93,10 @@
     "title": "Advertised and consumed bandwidth by relay flag",
     "type": "Graph",
     "description": "<p>This graph shows <a href=\"glossary.html#advertised-bandwidth\">advertised</a> and <a href=\"glossary.html#bandwidth-history\">consumed bandwidth</a> of relays with either \"Exit\" or \"Guard\" <a href=\"glossary.html#relay-flag\">flags</a> assigned by the directory authorities.  These sets are not distinct, because a relay that has both the \"Exit\" and \"Guard\" flags assigned will be included in both sets.</p>",
-    "function": "plot_bandwidth_flags",
+    "function": "bandwidth_flags",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "bandwidth"
     ]
   },
   {
@@ -131,13 +104,10 @@
     "title": "Bandwidth spent on answering directory requests",
     "type": "Graph",
     "description": "<p>This graph shows the portion of <a href=\"glossary.html#bandwidth-history\">consumed bandwidth</a> that <a href=\"glossary.html#directory-authority\">directory authorities</a> and <a href=\"glossary.html#directory-mirror\">mirrors</a> have spent on answering directory requests.  Not all directories report these statistics, so the graph shows an estimation of total consumed bandwidth as it would be observed if all directories reported these statistics.</p>",
-    "function": "plot_dirbytes",
+    "function": "dirbytes",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "bandwidth"
     ]
   },
   {
@@ -145,13 +115,10 @@
     "title": "Advertised bandwidth by IP version",
     "type": "Graph",
     "description": "<p>This graph shows total <a href=\"glossary.html#advertised-bandwidth\">advertised bandwidth</a> by relays supporting IPv6 as compared to all relays. A relay can support IPv6 by announcing an IPv6 address and port for the OR protocol, which may then be confirmed as reachable by the <a href=\"glossary.html#directory-authority\">directory authorities</a>, and by permitting exiting to IPv6 targets. In some cases, relay sets are broken down by whether relays got the \"Guard\" and/or \"Exit\" <a href=\"glossary.html#relay-flag\">relay flags</a> indicating their special qualification for the first or last position in a <a href=\"glossary.html#circuit\">circuit</a>. These sets are not distinct, because relays can have various combinations of announced/confirmed OR ports, exit policies, and relay flags.</p>",
-    "function": "plot_advbw_ipv6",
+    "function": "advbw_ipv6",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "ipv6servers"
     ]
   },
   {
@@ -159,14 +126,11 @@
     "title": "Advertised bandwidth distribution",
     "type": "Graph",
     "description": "<p>This graph shows the distribution of the <a href=\"glossary.html#advertised-bandwidth\">advertised bandwidth</a> of relays in the network.  Each percentile represents the advertised bandwidth that a given percentage of relays does not exceed (and that in turn the remaining relays either match or exceed).  For example, 99% of relays advertise at most the bandwidth value shown in the 99th percentile line (and the remaining 1% advertise at least that amount).</p>",
-    "function": "plot_advbwdist_perc",
+    "function": "advbwdist_perc",
     "parameters": [
       "start",
       "end",
       "p"
-    ],
-    "data": [
-      "advbwdist"
     ]
   },
   {
@@ -174,14 +138,11 @@
     "title": "Advertised bandwidth of n-th fastest relays",
     "type": "Graph",
     "description": "<p>This graph shows the <a href=\"glossary.html#advertised-bandwidth\">advertised bandwidth</a> of the n-th fastest relays in the network for different values of n.</p>",
-    "function": "plot_advbwdist_relay",
+    "function": "advbwdist_relay",
     "parameters": [
       "start",
       "end",
       "n"
-    ],
-    "data": [
-      "advbwdist"
     ]
   },
   {
@@ -194,16 +155,13 @@
     "title": "Relay users",
     "type": "Graph",
     "description": "<p>This graph shows the estimated number of directly-connecting <a href=\"glossary.html#client\">clients</a>; that is, it excludes clients connecting via <a href=\"glossary.html#bridge\">bridges</a>.  These estimates are derived from the number of directory requests counted on <a href=\"glossary.html#directory-authority\">directory authorities</a> and <a href=\"glossary.html#directory-mirror\">mirrors</a>.  Relays resolve client IP addresses to country codes, so that graphs are available for most countries.  Furthermore, it is possible to display indications of censorship events as obtained from an anomaly-based censorship-detection system (for more details, see this <a href=\"https://research.torproject.org/techreports/detector-2011-09-09.pdf\">technical report</a>).  For further details see these <a href=\"https://gitweb.torproject.org/metrics-web.git/tree/src/main/resources/doc/users-q-and-a.txt\">questions and answers about user statistics</a>.</p>",
-    "function": "plot_userstats_relay_country",
+    "function": "userstats_relay_country",
     "parameters": [
       "start",
       "end",
       "country",
       "events"
     ],
-    "data": [
-      "clients"
-    ],
     "include_related_events": true
   },
   {
@@ -223,9 +181,6 @@
     "table_cell_formats": [
       "<a href=\"userstats-relay-country.html?graph=userstats-relay-country&country=${cc}\">${country}</a> ",
       "${abs} (${rel} %)"
-    ],
-    "data": [
-      "clients"
     ]
   },
   {
@@ -247,9 +202,6 @@
       "<a href=\"userstats-relay-country.html?graph=userstats-relay-country&country=${cc}&events=on\">${country}</a> ",
       "${downturns}",
       "${upturns}"
-    ],
-    "data": [
-      "clients"
     ]
   },
   {
@@ -257,15 +209,12 @@
     "title": "Bridge users by country",
     "type": "Graph",
     "description": "<p>This graph shows the estimated number of <a href=\"glossary.html#client\">clients</a> connecting via <a href=\"glossary.html#bridge\">bridges</a>.  These numbers are derived from directory requests counted on bridges.  Bridges resolve client IP addresses of incoming directory requests to country codes, so that graphs are available for most countries.  For further details see these <a href=\"https://gitweb.torproject.org/metrics-web.git/tree/src/main/resources/doc/users-q-and-a.txt\">questions and answers about user statistics</a>.</p>",
-    "function": "plot_userstats_bridge_country",
+    "function": "userstats_bridge_country",
     "parameters": [
       "start",
       "end",
       "country"
     ],
-    "data": [
-      "clients"
-    ],
     "include_related_events": true
   },
   {
@@ -285,9 +234,6 @@
     "table_cell_formats": [
       "<a href=\"userstats-bridge-country.html?graph=userstats-bridge-country&country=${cc}\">${country}</a> ",
       "${abs} (${rel} %)"
-    ],
-    "data": [
-      "clients"
     ]
   },
   {
@@ -295,15 +241,12 @@
     "title": "Bridge users by transport",
     "type": "Graph",
     "description": "<p>This graph shows the estimated number of <a href=\"glossary.html#client\">clients</a> connecting via <a href=\"glossary.html#bridge\">bridges</a>.  These numbers are derived from directory requests counted on bridges.  Bridges distinguish connecting clients by transport protocol, which may include <a href=\"glossary.html#pluggable-transport\">pluggable transports</a>, so that graphs are available for different transports.  For further details see these <a href=\"https://gitweb.torproject.org/metrics-web.git/tree/src/main/resources/doc/users-q-and-a.txt\">questions and answers about user statistics</a>.</p>",
-    "function": "plot_userstats_bridge_transport",
+    "function": "userstats_bridge_transport",
     "parameters": [
       "start",
       "end",
       "transport"
     ],
-    "data": [
-      "clients"
-    ],
     "include_related_events": true
   },
   {
@@ -311,15 +254,12 @@
     "title": "Bridge users by country and transport",
     "type": "Graph",
     "description": "<p>This graph shows the estimated number of <a href=\"glossary.html#client\">clients</a> connecting via <a href=\"glossary.html#bridge\">bridges</a>.  These numbers are derived from directory requests counted on bridges.  Bridges resolve client IP addresses of incoming directory requests to country codes, and they distinguish connecting clients by transport protocol, which may include <a href=\"glossary.html#pluggable-transport\">pluggable transports</a>.  Even though bridges don't report a combination of clients by country and transport, it's possible to derive and graph lower and upper bounds from existing usage statistics.  For further details see these <a href=\"https://gitweb.torproject.org/metrics-web.git/tree/src/main/resources/doc/users-q-and-a.txt\">questions and answers about user statistics</a>.</p>",
-    "function": "plot_userstats_bridge_combined",
+    "function": "userstats_bridge_combined",
     "parameters": [
       "start",
       "end",
       "country"
     ],
-    "data": [
-      "userstats-combined"
-    ],
     "include_related_events": true
   },
   {
@@ -327,15 +267,12 @@
     "title": "Bridge users by IP version",
     "type": "Graph",
     "description": "<p>This graph shows the estimated number of <a href=\"glossary.html#client\">clients</a> connecting via <a href=\"glossary.html#bridge\">bridges</a>.  These numbers are derived from directory requests counted on bridges.  Bridges distinguish connecting clients by IP version, so that graphs are available for both IP versions 4 and 6.  For further details see these <a href=\"https://gitweb.torproject.org/metrics-web.git/tree/src/main/resources/doc/users-q-and-a.txt\">questions and answers about user statistics</a>.</p>",
-    "function": "plot_userstats_bridge_version",
+    "function": "userstats_bridge_version",
     "parameters": [
       "start",
       "end",
       "version"
     ],
-    "data": [
-      "clients"
-    ],
     "include_related_events": true
   },
   {
@@ -349,16 +286,13 @@
     "title": "Time to download files over Tor",
     "type": "Graph",
     "description": "<p>This graph shows overall performance when downloading static files of different sizes over Tor, either from a server on the public internet or from a version 2 onion server.  The graph shows the range of measurements from first to third quartile, and highlights the median.  The slowest and fastest quarter of measurements are omitted from the graph.</p>",
-    "function": "plot_torperf",
+    "function": "torperf",
     "parameters": [
       "start",
       "end",
       "source",
       "server",
       "filesize"
-    ],
-    "data": [
-      "torperf-1.1"
     ]
   },
   {
@@ -366,16 +300,13 @@
     "title": "Timeouts and failures of downloading files over Tor",
     "type": "Graph",
     "description": "<p>This graph shows the fraction of timeouts and failures when downloading static files of different sizes over Tor, either from a server on the public internet or from a version 2 onion server.  A timeout occurs when a download does not complete within the scheduled time, in which case it is aborted in order not to overlap with the next scheduled download.  A failure occurs when the download completes, but the response is smaller than expected.</p>",
-    "function": "plot_torperf_failures",
+    "function": "torperf_failures",
     "parameters": [
       "start",
       "end",
       "source",
       "server",
       "filesize"
-    ],
-    "data": [
-      "torperf-1.1"
     ]
   },
   {
@@ -383,13 +314,10 @@
     "title": "Fraction of connections used uni-/bidirectionally",
     "type": "Graph",
     "description": "<p>This graph shows the fraction of direct connections between a <a href=\"glossary.html#relay\">relay</a> and other nodes in the network that are used uni- or bi-directionally.  Every 10 seconds, relays determine for every direct connection whether they read and wrote less than a threshold of 20 KiB.  Connections below this threshold are excluded from the graph.  For the remaining connections, relays determine whether they read/wrote at least 10 times as many bytes as they wrote/read.  If so, they classify a connection as \"Mostly reading\" or \"Mostly writing\", respectively.  All other connections are classified as \"Both reading and writing\".  After classifying connections, read and write counters are reset for the next 10-second interval.  The graph shows daily medians and inter-quartile ranges of reported fractions.</p>",
-    "function": "plot_connbidirect",
+    "function": "connbidirect",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "connbidirect2"
     ]
   },
   {
@@ -397,13 +325,10 @@
     "title": "Unique .onion addresses (version 2 only)",
     "type": "Graph",
     "description": "<p>This graph shows the number of unique .onion addresses for version 2 onion services in the network per day.  These numbers are extrapolated from aggregated statistics on unique version 2 .onion addresses reported by single <a href=\"glossary.html#relay\">relays</a> acting as <a href=\"glossary.html#onion-service\">onion-service</a> directories, if at least 1% of relays reported these statistics.  For more details on the extrapolation algorithm, see <a href=\"https://blog.torproject.org/blog/some-statistics-about-onions\">this blog post</a> and <a href=\"https://research.torproject.org/techreports/extrapolating-hidserv-stats-2015-01-31.pdf\">this technical report</a>.</p>",
-    "function": "plot_hidserv_dir_onions_seen",
+    "function": "hidserv_dir_onions_seen",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "hidserv"
     ]
   },
   {
@@ -411,13 +336,10 @@
     "title": "Onion-service traffic (versions 2 and 3)",
     "type": "Graph",
     "description": "<p>This graph shows the amount of onion-service traffic from version 2 and version 3 onion services in the network per day.  This number is extrapolated from aggregated statistics on onion-service traffic reported by single <a href=\"glossary.html#relay\">relays</a> acting as rendezvous points for version 2 and 3 <a href=\"glossary.html#onion-service\">onion services</a>, if at least 1% of relays reported these statistics.  For more details on the extrapolation algorithm, see <a href=\"https://blog.torproject.org/blog/some-statistics-about-onions\">this blog post</a> and <a href=\"https://research.torproject.org/techreports/extrapolating-hidserv-stats-2015-01-31.pdf\">this technical report</a>.</p>",
-    "function": "plot_hidserv_rend_relayed_cells",
+    "function": "hidserv_rend_relayed_cells",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "hidserv"
     ]
   },
   {
@@ -425,13 +347,10 @@
     "title": "Fraction of relays reporting onion-service statistics",
     "type": "Graph",
     "description": "<p>This graph shows the fraction of <a href=\"glossary.html#relay\">relays</a> that report statistics on <a href=\"glossary.html#onion-service\">onion service</a> usage.  If at least 1% of relays report a statistic, it gets extrapolated towards a network total, where higher fractions are produce more accurate results.  For more details on the extrapolation algorithm, see <a href=\"https://blog.torproject.org/blog/some-statistics-about-onions\">this blog post</a> and <a href=\"https://research.torproject.org/techreports/extrapolating-hidserv-stats-2015-01-31.pdf\">this technical report</a>.</p>",
-    "function": "plot_hidserv_frac_reporting",
+    "function": "hidserv_frac_reporting",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "hidserv"
     ]
   },
   {
@@ -457,13 +376,10 @@
     "title": "Tor Browser downloads and updates",
     "type": "Graph",
     "description": "<p>This graph shows absolute numbers of requests to Tor's web servers related to Tor Browser.  <em>Initial downloads</em> and <em>signature downloads</em> are requests made by the user to download a Tor Browser executable or a corresponding signature file from the Tor website.  <em>Update pings</em> and <em>update requests</em> are requests made by Tor Browser to check whether a newer version is available or to download a newer version.</p>",
-    "function": "plot_webstats_tb",
+    "function": "webstats_tb",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "webstats"
     ]
   },
   {
@@ -471,13 +387,10 @@
     "title": "Tor Browser downloads by platform",
     "type": "Graph",
     "description": "<p>This graph shows absolute numbers of requests to Tor's web servers to download a Tor Browser executable, broken down by platform (Windows, macOS, Linux) of the requested executable.  Note that this graph does <em>not</em> show the platform used to download Tor Browser but the platform that it was downloaded for.</p>",
-    "function": "plot_webstats_tb_platform",
+    "function": "webstats_tb_platform",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "webstats"
     ]
   },
   {
@@ -485,13 +398,10 @@
     "title": "Tor Browser downloads by locale",
     "type": "Graph",
     "description": "<p>This graph shows absolute numbers of requests to Tor's web servers to download a Tor Browser executable, broken down by requested locale.</p>",
-    "function": "plot_webstats_tb_locale",
+    "function": "webstats_tb_locale",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "webstats"
     ]
   },
   {
@@ -499,13 +409,10 @@
     "title": "Tor Messenger downloads and updates",
     "type": "Graph",
     "description": "<p>This graph shows absolute numbers of requests to Tor's web servers related to Tor Messenger.  <em>Initial downloads</em> are requests made by the user to download a Tor Messenger executable from the Tor website.  <em>Update pings</em> are requests made by Tor Messenger to check whether a newer version is available.</p>",
-    "function": "plot_webstats_tm",
+    "function": "webstats_tm",
     "parameters": [
       "start",
       "end"
-    ],
-    "data": [
-      "webstats"
     ]
   }
 ]
diff --git a/src/main/resources/web/jsps/graph.jsp b/src/main/resources/web/jsps/graph.jsp
index 238f6d5..41e751d 100644
--- a/src/main/resources/web/jsps/graph.jsp
+++ b/src/main/resources/web/jsps/graph.jsp
@@ -158,14 +158,8 @@
 <a href="${id}.png${parameters}">PNG</a> or
 <a href="${id}.pdf${parameters}">PDF</a>.</p>
 
-<c:if test="${fn:length(data) > 0}">
-<p>Download underlying data:</p>
-<ul>
-<c:forEach var="row" items="${data}">
-<li><a href="stats/${row}.csv">CSV</a> (<a href="stats.html#${row}">format</a>)</li>
-</c:forEach>
-</ul>
-</c:if>
+<p>Download data as
+<a href="${id}.csv${parameters}">CSV</a>.</p>
 
             </div><!-- col-md-4 -->
           </div><!-- row -->
diff --git a/src/main/resources/web/jsps/table.jsp b/src/main/resources/web/jsps/table.jsp
index cf26ab2..fc8117d 100644
--- a/src/main/resources/web/jsps/table.jsp
+++ b/src/main/resources/web/jsps/table.jsp
@@ -64,15 +64,6 @@
     </p>
 </form>
 
-<c:if test="${fn:length(data) > 0}">
-<p>Download underlying data:</p>
-<ul>
-<c:forEach var="row" items="${data}">
-<li><a href="stats/${row}.csv">CSV</a> (<a href="stats.html#${row}">format</a>)</li>
-</c:forEach>
-</ul>
-</c:if>
-
             </div><!-- col-md-4 -->
           </div><!-- row -->
         </div><!-- tab-pane -->





More information about the tor-commits mailing list