[Author Prev][Author Next][Thread Prev][Thread Next][Author Index][Thread Index]
[or-cvs] [metrics-db/master] Stop pre-generating graphs.
Author: Karsten Loesing <karsten.loesing@xxxxxxx>
Date: Tue, 19 Oct 2010 15:20:08 +0200
Subject: Stop pre-generating graphs.
Commit: 373eeeab95f64aefaeb2d581df2a3a4388b11452
The next step is to have metrics-web generate .csv files on demand, so
that we can get rid of the R cronjob in metrics-db completely.
---
R/bridge-stats.R | 156 ------------------------------------------
R/consensus-stats.R | 146 ----------------------------------------
R/consensus.R | 29 --------
R/descriptor-stats.R | 136 -------------------------------------
R/dirreq-stats.R | 182 +-------------------------------------------------
R/gettor.R | 23 ------
R/graphs.R | 1 -
R/torperf.R | 57 ----------------
build.xml | 7 --
9 files changed, 1 insertions(+), 736 deletions(-)
delete mode 100755 R/consensus.R
delete mode 100644 R/descriptor-stats.R
diff --git a/R/bridge-stats.R b/R/bridge-stats.R
index 84bfb65..6e40e1f 100644
--- a/R/bridge-stats.R
+++ b/R/bridge-stats.R
@@ -1,164 +1,8 @@
-options(warn = -1)
-suppressPackageStartupMessages(library("ggplot2"))
-
-plot_bridges <- function(filename, title, limits, code) {
- c <- data.frame(date = bridge$date, users = bridge[[code]])
- ggplot(c, aes(x = as.Date(date, "%Y-%m-%d"), y = users)) +
- geom_line() + scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/",
- limits = limits) +
- scale_y_continuous(name = "", limits = c(0, max(bridge[[code]],
- na.rm = TRUE))) +
- opts(title = title)
- ggsave(filename = paste("website/graphs/bridge-users/", filename,
- sep = ""), width = 8, height = 5, dpi = 72)
-}
-
-plot_alldata <- function(countries) {
- end <- Sys.Date()
- start <- as.Date(bridge$date[1])
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_bridges(paste(filename, "-bridges-all.png", sep = ""),
- paste(people, "Tor users via bridges (all data)\n"),
- c(start, end), code)
- }
- plot_bridges(paste("total-bridges-all.png", sep = ""),
- paste("Total Tor users via bridges (all data)\n"),
- c(start, end), "all")
-}
-
-plot_pastdays <- function(days, countries) {
- for (day in days) {
- end <- Sys.Date()
- start <- seq(from = end, length = 2, by = paste("-", day, " days",
- sep = ""))[2]
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_bridges(paste(filename, "-bridges-", day, "d.png", sep = ""),
- paste(people, "Tor users via bridges (past", day, "days)\n"),
- c(start, end), code)
- }
- plot_bridges(paste("total-bridges-", day, "d.png", sep = ""),
- paste("Total Tor users via bridges (past", day, "days)\n"),
- c(start, end), "all")
- }
-}
-
-plot_years <- function(years, countries) {
- for (year in years) {
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_bridges(paste(filename, "-bridges-", year, ".png", sep = ""),
- paste(people, " Tor users via bridges (", year, ")\n", sep = ""),
- as.Date(c(paste(year, "-01-01", sep = ""), paste(year, "-12-31",
- sep = ""))), code)
- }
- plot_bridges(paste("total-bridges-", year, ".png", sep = ""),
- paste("Total Tor users via bridges (", year, ")\n", sep = ""),
- as.Date(c(paste(year, "-01-01", sep = ""), paste(year, "-12-31",
- sep = ""))), "all")
- }
-}
-
-plot_quarters <- function(years, quarters, countries) {
- for (year in years) {
- for (quarter in quarters) {
- start <- as.Date(paste(year, "-", (quarter - 1) * 3 + 1, "-01",
- sep = ""))
- end <- seq(seq(start, length = 2, by = "3 months")[2], length = 2,
- by = "-1 day")[2]
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_bridges(paste(filename, "-bridges-", year, "-q", quarter,
- ".png", sep = ""), paste(people, " Tor users via bridges (Q",
- quarter, " ", year, ")\n", sep = ""), c(start, end), code)
- }
- plot_bridges(paste("total-bridges-", year, "-q", quarter, ".png",
- sep = ""), paste("Total Tor users via bridges (Q", quarter, " ",
- year, ")\n", sep = ""), c(start, end), "all")
- }
- }
-}
-
-plot_months <- function(years, months, countries) {
- for (year in years) {
- for (month in months) {
- start <- as.Date(paste(year, "-", month, "-01", sep = ""))
- end <- seq(seq(start, length = 2, by = "1 month")[2], length = 2,
- by = "-1 day")[2]
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_bridges(paste(filename, "-bridges-", year, "-",
- format(start, "%m"), ".png", sep = ""), paste(people,
- " Tor users via bridges (", format(start, "%B"), " ", year,
- ")\n", sep = ""), c(start, end), code)
- }
- plot_bridges(paste("total-bridges-", year, "-", format(start, "%m"),
- ".png", sep = ""), paste("Total Tor users via bridges (",
- format(start, "%B"), " ", year, ")\n", sep = ""), c(start, end),
- "all")
- }
- }
-}
-
-plot_current <- function(countries) {
- plot_alldata(countries)
- plot_pastdays(c(30, 90, 180), countries)
- today <- as.POSIXct(Sys.Date(), tz = "GMT")
- one_week_ago <- seq(from = today, length = 2, by = "-7 days")[2]
- year_today <- format(today, "%Y")
- year_one_week_ago <- format(one_week_ago, "%Y")
- quarter_today <- 1 + floor((as.numeric(format(today, "%m")) - 1) / 3)
- quarter_one_week_ago <- 1 + floor((as.numeric(format(one_week_ago,
- "%m")) - 1) / 3)
- month_today <- as.numeric(format(today, "%m"))
- month_one_week_ago <- as.numeric(format(one_week_ago, "%m"))
- plot_years(union(year_today, year_one_week_ago), countries)
- if (year_today == year_one_week_ago) {
- plot_quarters(year_today, union(quarter_today, quarter_one_week_ago),
- countries)
- } else {
- plot_quarters(year_today, quarter_today, countries)
- plot_quarters(year_one_week_ago, quarter_one_week_ago, countries)
- }
- if (year_today == year_one_week_ago) {
- plot_months(year_today, union(month_today, month_one_week_ago),
- countries)
- } else {
- plot_months(year_today, month_today, countries)
- plot_months(year_one_week_ago, month_one_week_ago, countries)
- }
-}
-
-countries <- data.frame(code = c("au", "bh", "br", "ca", "cn", "cu", "de",
- "et", "fr", "gb", "ir", "it", "jp", "kr", "mm", "pl", "ru", "sa", "se",
- "sy", "tn", "tm", "us", "uz", "vn", "ye"), people = c("Australian",
- "Bahraini", "Brazilian", "Canadian", "Chinese", "Cuban", "German",
- "Ethiopian", "French", "U.K.", "Iranian", "Italian", "Japanese",
- "South Korean", "Burmese", "Polish", "Russian", "Saudi", "Swedish",
- "Syrian", "Tunisian", "Turkmen", "U.S.", "Uzbek", "Vietnamese",
- "Yemeni"), filename = c("australia", "bahrain", "brazil", "canada",
- "china", "cuba", "germany", "ethiopia", "france", "uk", "iran", "italy",
- "japan", "southkorea", "burma", "poland", "russia", "saudi", "sweden",
- "syria", "tunisia", "turkmenistan", "usa", "uzbekistan", "vietnam",
- "yemen"), stringsAsFactors = FALSE)
-
if (file.exists("stats/bridge-stats")) {
bridge <- read.csv("stats/bridge-stats", header = TRUE,
stringsAsFactors = FALSE)
bridge <- bridge[1:length(bridge$date)-1,]
write.csv(bridge, "website/csv/bridge-users.csv", quote = FALSE,
row.names = FALSE)
- plot_current(countries)
}
diff --git a/R/consensus-stats.R b/R/consensus-stats.R
index 70c28a5..b40f634 100644
--- a/R/consensus-stats.R
+++ b/R/consensus-stats.R
@@ -1,27 +1,3 @@
-options(warn = -1)
-suppressPackageStartupMessages(library("ggplot2"))
-
-if (file.exists("stats/consensus-stats-raw")) {
- relaysDay <- read.csv("stats/consensus-stats-raw",
- stringsAsFactors = FALSE)
- to <- Sys.time()
- from <- seq(from = to, length = 2, by = "-3 days")[2]
- relaysDay <- subset(relaysDay, as.POSIXct(datetime, tz = "GMT") >= from)
- if (length(relaysDay$datetime) > 0) {
- m <- melt(relaysDay[,c(1, 5, 2)], id = "datetime")
- ggplot(m, aes(x = as.POSIXct(datetime, tz = "GMT"), y = value,
- colour = variable)) + geom_point() +
- scale_x_datetime(name = "\nThe Tor Project - https://metrics.torproject.org/",
- limits = c(from, to)) +
- scale_y_continuous(name = "") +
- scale_colour_hue("", breaks = c("running", "exit"),
- labels = c("All relays", "Exit relays")) +
- opts(title = "Number of exit relays (past 72 hours)\n")
- ggsave(filename = "website/graphs/exit/exit-72h.png",
- width = 8, height = 5, dpi = 72)
- }
-}
-
if (file.exists("stats/consensus-stats")) {
consensuses <- read.csv("stats/consensus-stats", header = TRUE,
stringsAsFactors = FALSE);
@@ -34,125 +10,3 @@ if (file.exists("stats/consensus-stats")) {
"website/csv/exit.csv", quote = FALSE, row.names = FALSE)
}
-plot_consensus <- function(directory, filename, title, limits, rows, breaks,
- labels) {
- c <- melt(consensuses[rows], id = "date")
- ggplot(c, aes(x = as.Date(date, "%Y-%m-%d"), y = value,
- colour = variable)) + geom_line() + #stat_smooth() +
- scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/",
- limits = limits) +
- #paste("\nhttp://metrics.torproject.org/ -- last updated:",
- # date(), "UTC"),
- scale_y_continuous(name = "",
- limits = c(0, max(c$value, na.rm = TRUE))) +
- scale_colour_hue("", breaks = breaks, labels = labels) +
- opts(title = title)
- ggsave(filename = paste(directory, filename, sep = ""),
- width = 8, height = 5, dpi = 72)
-}
-
-plot_pastdays <- function(directory, filenamePart, titlePart, days, rows,
- breaks, labels) {
- for (day in days) {
- end <- Sys.Date()
- start <- seq(from = end, length = 2, by = paste("-", day, " days",
- sep = ""))[2]
- plot_consensus(directory, paste(filenamePart, "-", day, "d.png",
- sep = ""), paste(titlePart, "(past", day, "days)\n"), c(start, end),
- rows, breaks, labels)
- }
-}
-
-plot_years <- function(directory, filenamePart, titlePart, years, rows,
- breaks, labels) {
- for (year in years) {
- plot_consensus(directory, paste(filenamePart, "-", year, ".png",
- sep = ""), paste(titlePart, " (", year, ")\n", sep = ""),
- as.Date(c(paste(year, "-01-01", sep = ""),
- paste(year, "-12-31", sep = ""))), rows, breaks, labels)
- }
-}
-
-plot_quarters <- function(directory, filenamePart, titlePart, years,
- quarters, rows, breaks, labels) {
- for (year in years) {
- for (quarter in quarters) {
- start <- as.Date(paste(year, "-", (quarter - 1) * 3 + 1, "-01",
- sep = ""))
- end <- seq(seq(start, length = 2, by = "3 months")[2], length = 2,
- by = "-1 day")[2]
- plot_consensus(directory, paste(filenamePart, "-", year, "-q",
- quarter, ".png",
- sep = ""), paste(titlePart, " (Q", quarter, " ", year, ")\n",
- sep = ""), c(start, end), rows, breaks, labels)
- }
- }
-}
-
-plot_months <- function(directory, filenamePart, titlePart, years, months,
- rows, breaks, labels) {
- for (year in years) {
- for (month in months) {
- start <- as.Date(paste(year, "-", month, "-01", sep = ""))
- end <- seq(seq(start, length = 2, by = "1 month")[2], length = 2,
- by = "-1 day")[2]
- plot_consensus(directory, paste(filenamePart, "-", year, "-",
- format(start, "%m"), ".png", sep = ""), paste(titlePart,
- " (", format(start, "%B"), " ", year, ")\n", sep = ""),
- c(start, end), rows, breaks, labels)
- }
- }
-}
-
-plot_all <- function(directory, filenamePart, titlePart, rows, breaks,
- labels) {
- plot_consensus(directory, paste(filenamePart, "-all.png", sep = ""),
- paste(titlePart, " (all data)\n", sep = ""),
- as.Date(c(min(consensuses$date), max(consensuses$date))), rows,
- breaks, labels)
-}
-
-plot_current <- function(directory, filenamePart, titlePart, rows, breaks,
- labels) {
- plot_pastdays(directory, filenamePart, titlePart, c(30, 90, 180), rows,
- breaks, labels)
- today <- as.POSIXct(Sys.Date(), tz = "GMT")
- one_week_ago <- seq(from = today, length = 2, by = "-7 days")[2]
- year_today <- format(today, "%Y")
- year_one_week_ago <- format(one_week_ago, "%Y")
- quarter_today <- 1 + floor((as.numeric(format(today, "%m")) - 1) / 3)
- quarter_one_week_ago <- 1 + floor((as.numeric(format(one_week_ago,
- "%m")) - 1) / 3)
- month_today <- as.numeric(format(today, "%m"))
- month_one_week_ago <- as.numeric(format(one_week_ago, "%m"))
- plot_years(directory, filenamePart, titlePart, union(year_today,
- year_one_week_ago), rows, breaks, labels)
- if (year_today == year_one_week_ago) {
- plot_quarters(directory, filenamePart, titlePart, year_today,
- union(quarter_today, quarter_one_week_ago), rows, breaks, labels)
- } else {
- plot_quarters(directory, filenamePart, titlePart, year_today,
- quarter_today, rows, breaks, labels)
- plot_quarters(directory, filenamePart, titlePart, year_one_week_ago,
- quarter_one_week_ago, rows, breaks, labels)
- }
- if (year_today == year_one_week_ago) {
- plot_months(directory, filenamePart, titlePart, year_today,
- union(month_today, month_one_week_ago), rows, breaks, labels)
- } else {
- plot_months(directory, filenamePart, titlePart, year_today, month_today,
- rows, breaks, labels)
- plot_months(directory, filenamePart, titlePart, year_one_week_ago,
- month_one_week_ago, rows, breaks, labels)
- }
- plot_all(directory, filenamePart, titlePart, rows, breaks, labels)
-}
-
-if (file.exists("stats/consensus-stats")) {
- plot_current("website/graphs/networksize/", "networksize",
- "Number of relays and bridges", c(1, 5, 7),
- c("running", "brunning"), c("Relays", "Bridges"))
- plot_current("website/graphs/exit/", "exit", "Number of exit relays",
- c(1, 5, 2), c("running", "exit"), c("All relays", "Exit relays"))
-}
-
diff --git a/R/consensus.R b/R/consensus.R
deleted file mode 100755
index 6b57dc8..0000000
--- a/R/consensus.R
+++ /dev/null
@@ -1,29 +0,0 @@
-options(warn = -1)
-suppressPackageStartupMessages(library("ggplot2"))
-
-args <- commandArgs()
-days <- args[4]
-fname <- args[5]
-
-c <- read.csv("/tmp/consensus-stats", header = TRUE,
- stringsAsFactors = FALSE);
-c <- c[1:length(c$date)-1,c("date", "running", "brunning")]
-c <- melt(c, id = "date")
-
-day <- as.numeric(days)
-end <- Sys.Date()
-start <- seq(from = end, length = 2, by = paste("-", day, " days",
- sep = ""))[2]
-limits <- c(start, end)
-png(filename = fname, unit = "in", width = 8, height = 5, res = 72)
-ggplot(c, aes(x = as.Date(date, "%Y-%m-%d"), y = value,
- colour = variable)) + geom_line() +
- scale_x_date(name = "", limits = limits) +
- scale_y_continuous(name = "",
- limits = c(0, max(c$value, na.rm = TRUE))) +
- scale_colour_hue("", breaks = c("running", "brunning"),
- labels = c("Relays", "Bridges")) +
- opts(title = paste("Number of relays and bridges (past", day,
- "days)\n"))
-invisible(dev.off())
-
diff --git a/R/descriptor-stats.R b/R/descriptor-stats.R
deleted file mode 100644
index 159eb28..0000000
--- a/R/descriptor-stats.R
+++ /dev/null
@@ -1,136 +0,0 @@
-# R script to plot relay versions, platforms, and advertised bandwidth.
-# Run from ERNIE's base directory as "R --slave < R/descriptor.stats.R".
-
-# Suppress all warnings, so that only errors are written to stdout. This
-# is useful when executing this script from cron and having it mail out a
-# notification only when there's an actual problem.
-options(warn = -1)
-
-# Import library ggplot2 that is used for plotting. Suppress package
-# startup messages for the same reason as suppressing warnings.
-suppressPackageStartupMessages(library("ggplot2"))
-
-# Define a function to plot relay versions. Right now, there are no
-# parameters for this function. In the future, a possible parameter would
-# be the time interval to be plotted on the x axis.
-plot_versions <- function() {
-
- # Transform data frame versions into a data frame that can be processed
- # by ggplot2. In particular, versions has one row per date and multiple
- # columns for the number of relays running a particular Tor version at
- # that date. What we need for plotting is a single data point per row
- # with additional columns for classification, e.g., which version this
- # date point belongs to. Add commands "print(versions)" and "print(v)"
- # for an example.
- v <- melt(versions, id = "date")
-
- # Start plotting the data in data frame v.
- ggplot(v,
-
- # Tell ggplot2 how to understand the data in data frame v. The date
- # shall be plotted on the x axis, the value on the y axis, and the
- # row called variable shall be used to distinguish data sets by color.
- aes(x = date, y = value, colour = variable)) +
-
- # So far, ggplot2 only knows how to understand the data, but not how
- # to visualize them. Draw a line from the data with line size 1.
- geom_line(size = 1) +
-
- # Override the default x axis which would display a label "date" with
- # an x axis that has no label. This line can be commented out.
- scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/") +
-
- # Override the default y axis with label "value" with one that has no
- # label and that starts at the origin. Note that the max() function is
- # told to remove NA values. These lines can be commented out.
- scale_y_continuous(name = "",
- limits = c(0, max(v$value, na.rm = TRUE))) +
-
- # Override the categorization by relay version to use a different
- # color scheme (brewer instead of hue), have a different legend title
- # ("Tor versions" instead of "variable") and display custom legend
- # labels ("0.2.2" instead of "X0.2.2"). These lines can be commented
- # out.
- scale_colour_brewer(name = "Tor version",
- breaks = rev(names(versions)[2:length(names(versions))]),
- labels = c("other",
- substr(rev(names(versions)[2:(length(names(versions)) - 1)]),
- 2, 6))) +
-
- # Add a graph title. This line can be commented out together with the
- # '+' character in the last non-comment line.
- opts(title = "Relay versions\n")
-
- # Save the generated graph to the following path with given width,
- # height, and resolution.
- ggsave(filename = "website/graphs/descriptors/versions.png",
- width = 8, height = 5, dpi = 72)
-}
-
-# Define a function to plot relay platforms. See the similar function
-# plot_versions() for details.
-plot_platforms <- function() {
- p <- melt(platforms, id = "date")
- ggplot(p, aes(x = date, y = value, colour = variable)) +
- geom_line(size = 1) +
- scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/") +
- scale_y_continuous(name = "",
- limits = c(0, max(p$value, na.rm = TRUE))) +
- scale_colour_brewer(name = "Platform",
- breaks = rev(names(platforms)[2:length(names(platforms))]),
- labels = rev(names(platforms)[2:length(names(platforms))])) +
- opts(title = "Relay platforms\n")
- ggsave(filename = "website/graphs/descriptors/platforms.png",
- width = 8, height = 5, dpi = 72)
-}
-
-# Define a function to plot advertised bandwidth. See the similar function
-# plot_versions() for details.
-plot_bandwidth <- function() {
- ggplot(bandwidth, aes(x = date, y = advbw / 1024)) + geom_line() +
- scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/") +
- scale_y_continuous(name = "Bandwidth (MiB/s)",
- limits = c(0, max(bandwidth$advbw / 1024, na.rm = TRUE))) +
- opts(title = "Total advertised bandwidth\n")
- ggsave(filename = "website/graphs/descriptors/bandwidth.png",
- width = 8, height = 5, dpi = 72)
-}
-
-# If a CSV file with version data exists, ...
-if (file.exists("stats/version-stats")) {
-
- # Read in the file, declare that the first line has the column names,
- # and define the type of the first column as Date.
- versions <- read.csv("stats/version-stats", header = TRUE,
- colClasses = c(date = "Date"))
-
- # Write the same data to disk without putting in quotes around strings
- # and without adding row numbers. This file can be downloaded by others
- # to run their own evaluations.
- write.csv(versions, "website/csv/versions.csv", quote = FALSE,
- row.names = FALSE)
-
- # Call the function defined above to plot relay versions.
- plot_versions()
-}
-
-# If a CSV file with platform data exists, read it, copy it to the
-# website, and plot a platform graph.
-if (file.exists("stats/platform-stats")) {
- platforms <- read.csv("stats/platform-stats", header = TRUE,
- colClasses = c(date = "Date"))
- write.csv(platforms, "website/csv/platforms.csv", quote = FALSE,
- row.names = FALSE)
- plot_platforms()
-}
-
-# If a CSV file with bandwidth data exists, read it, copy it to the
-# website, and plot a bandwidth graph.
-if (file.exists("stats/bandwidth-stats")) {
- bandwidth <- read.csv("stats/bandwidth-stats", header = TRUE,
- colClasses = c(date = "Date"))
- write.csv(bandwidth, "website/csv/bandwidth.csv", quote = FALSE,
- row.names = FALSE)
- plot_bandwidth()
-}
-
diff --git a/R/dirreq-stats.R b/R/dirreq-stats.R
index 34e2a43..1871b5d 100644
--- a/R/dirreq-stats.R
+++ b/R/dirreq-stats.R
@@ -1,178 +1,3 @@
-options(warn = -1)
-suppressPackageStartupMessages(library("ggplot2"))
-
-formatter <- function(x, ...) {
- format(x, scientific = FALSE, ...)
-}
-
-plot_dirreq <- function(directory, filename, title, limits, data, code) {
- c <- data.frame(date = data$date, users = data[[code]])
- ggplot(c, aes(x = as.Date(date, "%Y-%m-%d"), y = users)) +
- geom_line() +
- scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/",
- limits = limits) +
- scale_y_continuous(name = "", formatter = formatter,
- limits = c(0, max(c$users, na.rm = TRUE))) +
- opts(title = title)
- ggsave(filename = paste(directory, filename, sep = ""),
- width = 8, height = 5, dpi = 72)
-}
-
-plot_alldata <- function(directory, filenamePart, titlePart, data,
- countries) {
- end <- Sys.Date()
- start <- as.Date(data$date[1])
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_dirreq(directory, paste(filename, filenamePart, "-all.png",
- sep = ""), paste(titlePart, people, "Tor users (all data)\n"),
- c(start, end), data, code)
- }
- plot_dirreq(directory, paste("total", filenamePart, "-all.png",
- sep = ""), paste("Total", tolower(titlePart),
- "Tor users (all data)\n"), c(start, end), data, "all")
-}
-
-plot_pastdays <- function(directory, filenamePart, titlePart, days, data,
- countries) {
- for (day in days) {
- end <- Sys.Date()
- start <- seq(from = end, length = 2, by = paste("-", day, " days",
- sep = ""))[2]
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_dirreq(directory, paste(filename, filenamePart, "-", day,
- "d.png", sep = ""), paste(titlePart, people, "Tor users (past",
- day, "days)\n"), c(start, end), data, code)
- }
- plot_dirreq(directory, paste("total", filenamePart, "-", day,
- "d.png", sep = ""), paste("Total", tolower(titlePart),
- "Tor users (past", day, "days)\n"), c(start, end), data, "all")
- }
-}
-
-plot_years <- function(directory, filenamePart, titlePart, years, data,
- countries) {
- for (year in years) {
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_dirreq(directory, paste(filename, filenamePart, "-", year,
- ".png", sep = ""), paste(titlePart, " ", people, " Tor users (",
- year, ")\n", sep = ""), as.Date(c(paste(year, "-01-01", sep = ""),
- paste(year, "-12-31", sep = ""))), data, code)
- }
- plot_dirreq(directory, paste("total", filenamePart, "-", year,
- ".png", sep = ""), paste("Total ", tolower(titlePart),
- " Tor users (", year, ")\n", sep = ""),
- as.Date(c(paste(year, "-01-01", sep = ""),
- paste(year, "-12-31", sep = ""))), data, "all")
- }
-}
-
-plot_quarters <- function(directory, filenamePart, titlePart, years,
- quarters, data, countries) {
- for (year in years) {
- for (quarter in quarters) {
- start <- as.Date(paste(year, "-", (quarter - 1) * 3 + 1, "-01",
- sep = ""))
- end <- seq(seq(start, length = 2, by = "3 months")[2], length = 2,
- by = "-1 day")[2]
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_dirreq(directory, paste(filename, filenamePart, "-", year,
- "-q", quarter, ".png", sep = ""), paste(titlePart, " ", people,
- " Tor users (Q", quarter, " ", year, ")\n", sep = ""),
- c(start, end), data, code)
- }
- plot_dirreq(directory, paste("total", filenamePart, "-", year,
- "-q", quarter, ".png", sep = ""), paste("Total ",
- tolower(titlePart), " Tor users (Q", quarter, " ", year, ")\n",
- sep = ""), c(start, end), data, "all")
- }
- }
-}
-
-plot_months <- function(directory, filenamePart, titlePart, years, months,
- data, countries) {
- for (year in years) {
- for (month in months) {
- start <- as.Date(paste(year, "-", month, "-01", sep = ""))
- end <- seq(seq(start, length = 2, by = "1 month")[2], length = 2,
- by = "-1 day")[2]
- for (country in 1:length(countries$code)) {
- code <- countries[country, 1]
- people <- countries[country, 2]
- filename <- countries[country, 3]
- plot_dirreq(directory, paste(filename, filenamePart, "-", year,
- "-", format(start, "%m"), ".png", sep = ""), paste(titlePart,
- " ", people, " Tor users (", format(start, "%B"), " ", year,
- ")\n", sep = ""), c(start, end), data, code)
- }
- plot_dirreq(directory, paste("total", filenamePart, "-", year, "-",
- format(start, "%m"), ".png", sep = ""), paste("Total ",
- tolower(titlePart), " Tor users (", format(start, "%B"), " ",
- year, ")\n", sep = ""), c(start, end), data, "all")
- }
- }
-}
-
-plot_current <- function(directory, filenamePart, titlePart, data,
- countries) {
- plot_alldata(directory, filenamePart, titlePart, data, countries)
- plot_pastdays(directory, filenamePart, titlePart, c(30, 90, 180), data,
- countries)
- today <- as.POSIXct(Sys.Date(), tz = "GMT")
- one_week_ago <- seq(from = today, length = 2, by = "-7 days")[2]
- year_today <- format(today, "%Y")
- year_one_week_ago <- format(one_week_ago, "%Y")
- quarter_today <- 1 + floor((as.numeric(format(today, "%m")) - 1) / 3)
- quarter_one_week_ago <- 1 + floor((as.numeric(format(one_week_ago,
- "%m")) - 1) / 3)
- month_today <- as.numeric(format(today, "%m"))
- month_one_week_ago <- as.numeric(format(one_week_ago, "%m"))
- plot_years(directory, filenamePart, titlePart, union(year_today,
- year_one_week_ago), data, countries)
- if (year_today == year_one_week_ago) {
- plot_quarters(directory, filenamePart, titlePart, year_today,
- union(quarter_today, quarter_one_week_ago), data, countries)
- } else {
- plot_quarters(directory, filenamePart, titlePart, year_today,
- quarter_today, data, countries)
- plot_quarters(directory, filenamePart, titlePart, year_one_week_ago,
- quarter_one_week_ago, data, countries)
- }
- if (year_today == year_one_week_ago) {
- plot_months(directory, filenamePart, titlePart, year_today,
- union(month_today, month_one_week_ago), data, countries)
- } else {
- plot_months(directory, filenamePart, titlePart, year_today,
- month_today, data, countries)
- plot_months(directory, filenamePart, titlePart, year_one_week_ago,
- month_one_week_ago, data, countries)
- }
-}
-
-countries <- data.frame(code = c("au", "bh", "br", "ca", "cn", "cu", "de",
- "et", "fr", "gb", "ir", "it", "jp", "kr", "mm", "pl", "ru", "sa", "se",
- "sy", "tn", "tm", "us", "uz", "vn", "ye"), people = c("Australian",
- "Bahraini", "Brazilian", "Canadian", "Chinese", "Cuban", "German",
- "Ethiopian", "French", "U.K.", "Iranian", "Italian", "Japanese",
- "South Korean", "Burmese", "Polish", "Russian", "Saudi", "Swedish",
- "Syrian", "Tunisian", "Turkmen", "U.S.", "Uzbek", "Vietnamese",
- "Yemeni"), filename = c("australia", "bahrain", "brazil", "canada",
- "china", "cuba", "germany", "ethiopia", "france", "uk", "iran", "italy",
- "japan", "southkorea", "burma", "poland", "russia", "saudi", "sweden",
- "syria", "tunisia", "turkmenistan", "usa", "uzbekistan", "vietnam",
- "yemen"), stringsAsFactors = FALSE)
-
if (file.exists("stats/dirreq-stats")) {
dirreq <- read.csv("stats/dirreq-stats", header = TRUE,
stringsAsFactors = FALSE)
@@ -193,12 +18,7 @@ if (file.exists("stats/dirreq-stats")) {
write.csv(gabelmoo, "website/csv/new-users.csv", quote = FALSE,
row.names = FALSE)
- write.csv(trusted, "website/csv/recurring-users.csv", quote = FALSE,
+ write.csv(trusted, "website/csv/direct-users.csv", quote = FALSE,
row.names = FALSE)
-
- plot_current("website/graphs/new-users/", "-new",
- "New or returning, directly connecting", gabelmoo, countries)
- plot_current("website/graphs/direct-users/", "-direct",
- "Recurring, directly connecting", trusted, countries)
}
diff --git a/R/gettor.R b/R/gettor.R
index 6ed7a91..30e7f34 100644
--- a/R/gettor.R
+++ b/R/gettor.R
@@ -1,6 +1,3 @@
-options(warn = -1)
-suppressPackageStartupMessages(library("ggplot2"))
-
if (file.exists("stats/gettor-stats")) {
gettor <- read.csv("stats/gettor-stats", header = TRUE,
stringsAsFactors = FALSE);
@@ -23,25 +20,5 @@ if (file.exists("stats/gettor-stats")) {
gettor$tor.im.browser.bundle_zh_cn,
fa = gettor$tor.browser.bundle_fa + gettor$tor.im.browser.bundle_fa),
"website/csv/gettor.csv", quote = FALSE, row.names = FALSE)
-
- plot_packages <- function(filename, title, data) {
- ggplot(data, aes(x = as.Date(date, "%Y-%m-%d"), y = packages)) + geom_line() +
- scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/",
- limits = c(start, end)) +
- scale_y_continuous(name = "",
- limits = c(0, max(data$packages, na.rm = TRUE))) +
- opts(title = paste(title, "\n", sep = ""))
- ggsave(filename = paste("website/graphs/gettor/", filename, sep = ""),
- width = 8, height = 5, dpi = 72)
- }
-
- plot_packages("gettor-total.png",
- "Total packages requested from GetTor per day", total)
- plot_packages("gettor-en.png",
- "Tor Browser Bundles (en) requested from GetTor per day", en)
- plot_packages("gettor-zh_cn.png",
- "Tor Browser Bundles (zh_CN) requested from GetTor per day", zh_cn)
- plot_packages("gettor-fa.png",
- "Tor Browser Bundles (fa) requested from GetTor per day", fa)
}
diff --git a/R/graphs.R b/R/graphs.R
index bcf6b3a..bfb65cc 100644
--- a/R/graphs.R
+++ b/R/graphs.R
@@ -1,7 +1,6 @@
source("R/consensus-stats.R");
source("R/dirreq-stats.R");
source("R/bridge-stats.R");
-source("R/descriptor-stats.R");
source("R/torperf.R");
source("R/gettor.R");
source("R/monthly-users.R");
diff --git a/R/torperf.R b/R/torperf.R
index 51ba985..9c38235 100644
--- a/R/torperf.R
+++ b/R/torperf.R
@@ -1,63 +1,6 @@
-options(warn = -1)
-suppressPackageStartupMessages(library("ggplot2"))
-
if (file.exists("stats/torperf-stats")) {
-
t <- read.csv("stats/torperf-stats", colClasses = c("character", "Date",
"integer", "integer", "integer"))
write.csv(t, "website/csv/torperf.csv", quote = FALSE, row.names = FALSE)
-
- intervals <- c("12m", "6m", "2w")
- intervalsStr <- c("-12 months", "-6 months", "-2 weeks")
-
- for (intervalInd in 1:length(intervals)) {
- interval <- intervals[intervalInd]
- intervalStr <- intervalsStr[intervalInd]
-
- end <- seq(from = Sys.Date(), length = 2, by = "-1 day")[2]
- start <- seq(seq(from = end, length = 2,
- by=intervalStr)[2], length=2, by="1 day")[2]
-
- dates <- seq(from = start, to = end, by="1 day")
-
- sources <- c("siv", "moria", "torperf")
- colors <- c("#0000EE", "#EE0000", "#00CD00")
- sizes <- c("5mb", "1mb", "50kb")
- sizePrint <- c("5 MiB", "1 MiB", "50 KiB")
-
- for (sizeInd in 1:length(sizes)) {
- size <- sizes[sizeInd]
- sizePr <- sizePrint[sizeInd]
- for (sourceInd in 1:length(sources)) {
- sourceStr <- paste(sources[sourceInd], size, sep = "-")
- sourceName <- sources[sourceInd]
-
- u <- t[t$source == sourceStr & t$date >= start & t$date <= end, 2:5]
- missing <- setdiff(dates, u$date)
- if (length(missing) > 0) {
- u <- rbind(u, data.frame(date = as.Date(missing, origin = "1970-01-01"),
- q1 = NA, md = NA, q3 = NA))
- }
- maxy <- max(t[t$source %in% paste(sources, "-", size, sep = "") &
- t$date >= start & t$date <= end, 5], na.rm = TRUE)
- ggplot(u, aes(x = as.Date(date), y = md/1e3, fill = "line")) +
- geom_line(colour = colors[sourceInd], size = 0.75) +
- geom_ribbon(data = u, aes(x = date, ymin = q1/1e3,
- ymax = q3/1e3, fill = "ribbon")) +
- scale_x_date(name = "\nThe Tor Project - https://metrics.torproject.org/") +
- scale_y_continuous(name = "", limits = c(0, maxy / 1e3)) +
- coord_cartesian(ylim = c(0, 0.8 * maxy / 1e3)) +
- scale_fill_manual(name = paste("Measured times on",
- sources[sourceInd], "per day"),
- breaks = c("line", "ribbon"),
- labels = c("Median", "1st to 3rd quartile"),
- values = paste(colors[sourceInd], c("", "66"), sep = "")) +
- opts(title = paste("Time in seconds to complete", sizePr, "request"), legend.position = "top")
- ggsave(filename = paste("website/graphs/torperf/torperf-", size, "-",
- sourceName, "-", interval, ".png", sep = ""), width = 8, height = 5,
- dpi = 72)
- }
- }
- }
}
diff --git a/build.xml b/build.xml
index bddac1d..39c74b2 100644
--- a/build.xml
+++ b/build.xml
@@ -23,13 +23,6 @@
<target name="init">
<mkdir dir="${classes}"/>
<mkdir dir="website/csv"/>
- <mkdir dir="website/graphs/descriptors"/>
- <mkdir dir="website/graphs/direct-users"/>
- <mkdir dir="website/graphs/exit"/>
- <mkdir dir="website/graphs/gettor"/>
- <mkdir dir="website/graphs/networksize"/>
- <mkdir dir="website/graphs/new-users"/>
- <mkdir dir="website/graphs/torperf"/>
</target>
<target name="compile" depends="init">
<javac srcdir="${sources}"
--
1.7.1