diff --git a/arbetsdag.R b/arbetsdag.R new file mode 100644 index 0000000..0ea727a --- /dev/null +++ b/arbetsdag.R @@ -0,0 +1,16 @@ +workingdays <- function(begins, ends, key) { + result <- c() + for (i in seq(length.out=length(begins))) { + # working days + WD_URL = "http://api.arbetsdag.se/v2/dagar.json" + WD_QUERY = paste0("?fran=", as.Date(begins[i]), + "&till=", as.Date(ends[i]), + "&key=", key, + "&id=1234") + url = paste0(WD_URL, WD_QUERY) + + WD <- fromJSON(url) + result[i] <- WD$antal_vardagar + } + return(result) +} diff --git a/data-helpers.R b/data-helpers.R index 50f2278..2f987af 100644 --- a/data-helpers.R +++ b/data-helpers.R @@ -1,6 +1,9 @@ # A set of generic functions that operate on the "aggregated" data # to produce data formatted for the plots +# get workingdays +source("arbetsdag.R") + gen.user.data <- function(data, id) { user.data <- subset(data, team == id) %>% group_by(date, user, key) %>% @@ -58,7 +61,7 @@ gen.team.summary <- function(summary) { return(team.summary) } -gen.user.delta <- function(data, id) { +gen.user.delta <- function(data, id, daily.hours, api.key) { user.delta <- subset(data, team == id) %>% group_by(user) %>% summarise( @@ -68,8 +71,8 @@ gen.user.delta <- function(data, id) { billable = sum(billable) ) - if (! is.null(working.hours)) { - user.delta <- merge(user.delta, working.hours, by = "user") + if (! is.null(daily.hours)) { + user.delta <- merge(user.delta, daily.hours, by = "user") } else { if (TEMPO_DAILY == '') { TEMPO_DAILY = 8 @@ -83,7 +86,7 @@ gen.user.delta <- function(data, id) { user.delta <- user.delta %>% group_by(user) %>% mutate( - expected = daily * workingdays(start, end), + expected = daily * workingdays(start, end, api.key), delta = hours - expected, fraction = 100 * billable / expected ) diff --git a/ggplot-helpers.R b/ggplot-helpers.R new file mode 100644 index 0000000..71b7ddf --- /dev/null +++ b/ggplot-helpers.R @@ -0,0 +1,146 @@ +# ggplot-helpers + +tempo.daily.plot <- function(data, id) { + # returns + # a column plot with the daily logs for each + # user in the team, colors follow the project keys + # + # data is the aggregated data for all teams + # id is the team.id for one team + # + plot <- ggplot(data = subset(data, team == id)) + + geom_col(aes(x = date, y = hours, fill = key)) + + facet_wrap(~user) + scale_fill_hue(l = 45) + + scale_y_continuous( + breaks = c(0,2,4,6,8,10), + name = "Daily", + sec.axis = dup_axis()) + + scale_x_date(name = NULL) + + theme(legend.position = "top", + axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + + ggtitle("Daily logs") + + return(plot) +} + +tempo.detailed.plot <- function(data, id) { + # returns + # a detailed column plot with the daily logs for each + # user in the team, colors follow the project tasks + # limited to the last 14 days + # + # data is the aggregated data for all teams + # id is the team.id for one team + # + plot <- ggplot(data = subset(data, team == id)) + + geom_col(aes(x = date, y = hours, fill = issue.key), show.legend = FALSE) + + facet_wrap(~user) + scale_fill_hue(l = 45) + + scale_y_continuous( + breaks = c(0,2,4,6,8,10), + name = "Daily", + sec.axis = dup_axis()) + + scale_x_date(name = NULL) + + theme(legend.position = "top", + axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + + coord_cartesian(xlim = c(Sys.Date() - 14, Sys.Date())) + + ggtitle("Detailed logs, last 14 days") + + return(plot) +} + +tempo.billable.plot <- function(data) { + # returns a scatter plot of the billable tasks + # + # data is user.detail + # + plot <- ggplot(data = subset(data, billable > 0)) + + geom_point(aes(x = reorder(issue.key, -hours), + y = hours, + color = issue.key, + fill = issue.key), show.legend = FALSE) + + facet_wrap(~user) + scale_fill_hue(l = 45) + + scale_x_discrete(name = NULL) + + scale_y_log10( + name = "Logged hours [h]", + sec.axis = dup_axis()) + + theme(legend.position = "top", + legend.title = element_blank(), + axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + + ggtitle("Billable tasks") + + return(plot) +} + +tempo.unbillable.plot <- function(data) { + # returns a detailed scatter plot for the unbillable tasks + # + # + plot <- ggplot(data = subset(data, billable == 0)) + + geom_point(aes(x = reorder(issue.key, -hours), + y = hours, + color = issue.key, + fill = issue.key), show.legend = FALSE) + + facet_wrap(~user) + scale_fill_hue(l = 45) + + scale_x_discrete(name = NULL) + + scale_y_log10( + name = "Logged hours [h]", + sec.axis = dup_axis()) + + theme(legend.position = "top", + axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + + ggtitle("Unbillable tasks") + + return(plot) +} + +team.plot <- function(data) { + plot <- ggplot(data = data) + + geom_point(aes(x = date, y = average.7.hours), color = "Gray50", shape = 1) + + geom_point(aes(x = date, y = average.30.hours), color = "Dark Blue") + + geom_smooth(aes(x = date, y = average.30.hours), color = "Dark Blue") + + geom_point(aes(x = date, y = average.7.billable), color = "Gray75", shape = 1) + + geom_point(aes(x = date, y = average.30.billable), color = "Dark Green") + + geom_smooth(aes(x = date, y = average.30.billable), color = "Dark Green") + + scale_color_hue(l = 45) + scale_fill_hue(l = 45) + + scale_y_continuous( + breaks = c(0,8,16,24,32,40, 48,56), + name = "Weekly", + sec.axis = dup_axis()) + + scale_x_date(name = NULL) + + theme(legend.position = "top", + legend.title = element_blank(), + axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + + return(plot) +} + +rolling.plot <- function(data) { + plot <- ggplot(data = data) + + geom_point(aes(x = date, y = roll.7.hours), color = "Gray50", shape = 1) + + geom_point(aes(x = date, y = roll.7.billable), color = "Gray75", shape = 1) + + geom_point(aes(x = date, y = roll.30.hours), color = "Dark Blue") + + geom_line(aes(x = date, y = roll.30.hours), color = "Dark Blue") + + geom_point(aes(x = date, y = roll.30.billable), color = "Dark Green") + + geom_line(aes(x = date, y = roll.30.billable), color = "Dark Green") + + facet_wrap(~user) + scale_fill_hue(l = 45) + scale_color_hue(l = 45) + + scale_y_continuous( + breaks = c(0,8,16,24,32,40, 48), + name = "Rolling Weekly [h]", + sec.axis = dup_axis()) + + scale_x_date(name = NULL) + + theme(legend.position = "top", legend.title = element_blank(), + axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + + return(plot) +} + +accumulated.plot <- function(data) { + plot <- ggplot(data = data) + + geom_col(aes(x = user, y = delta, fill = user), show.legend = FALSE) + + scale_fill_hue(l = 45) + + scale_x_discrete(name = NULL) + + scale_y_continuous( + name = "Delta hours [h]", + sec.axis = dup_axis()) + + return(plot) +} diff --git a/shiny-tempo.Rmd b/shiny-tempo.Rmd new file mode 100644 index 0000000..06a59e8 --- /dev/null +++ b/shiny-tempo.Rmd @@ -0,0 +1,263 @@ +--- +title: "tempo report" +author: "`r Sys.getenv('USER')`" +date: "`r Sys.Date()`" +output: html_document +runtime: shiny +--- + +```{r setup, include=FALSE} +knitr::opts_chunk$set(echo = TRUE) +``` + + +This is an R Markdown document. For more details on using R Markdown see . + +When you click the **Knit** button to generate the document. + +```{r functions, echo = FALSE} + +source("r-helpers.R") + +``` + +### Environment variables + +For this to work, these needs to be set in **$HOME/.Renviron** + +```{r environment, echo = TRUE} +TEMPO_KEY <- Sys.getenv("TEMPO_KEY") +check.if.empty(TEMPO_KEY, "TEMPO_KEY") +TEMPO_START <- Sys.getenv("TEMPO_START") +check.if.empty(TEMPO_START, "TEMPO_START") +TEMPO_DAILY <- Sys.getenv("TEMPO_DAILY") +# No checking for this, can be set this way, or through a config/workinghours.csv file +# TEMPO_DAILY is the needed working ours per day, assuming a 5 day work week +TEMPO_DETAILS <- Sys.getenv("TEMPO_DETAILS") +# No checking for this, used to filter how much details are plotted +TEMPO_TEAM <- Sys.getenv("TEMPO_TEAM") +# No check, does not have to be set +WD_KEY <- Sys.getenv("ARBETSDAGAR_KEY") +check.if.empty(WD_KEY, "WD_KEY") +``` + +where TEMPO_KEY is the api key and TEMPO_START is the date you started using tempo. WD_KEY is the api key for "arbetsdagar.se", you will have to register, at least, a free account to use the service. + +```{r libraries, echo = FALSE, warning = TRUE, message = TRUE} + +packages <- c("tidyverse", "jsonlite", "httr", "stringr", "slider", "lubridate") +check.packages(packages) + +library(tidyverse) +library(dplyr) +library(httr) +library(jsonlite) +library(stringr) +library(slider) +library(lubridate) +``` + +```{r fetch-helpers, echo = FALSE, message = FALSE} +TEMPO_URL <- "https://api.tempo.io/core/3/" + +fetch.tempo <- function(url, query, key) { + url <- paste0(url, query) + header <- paste0("Bearer ", key) + message(url) + httpResponse <- GET(url, + add_headers("Authorization" = header), + accept_json(), + timeout(20)) + + return(fromJSON(content(httpResponse, "text"))) +} + +fetch.tempo.teams <- function(url, key) { + query <- "teams" + data <- fetch.tempo(url, query, key) + # print(paste("Found", data$metadata, "teams")) + return(data$result) +} + +fetch.tempo.data <- function(key, begins, ends, team = 0) { + offset <- 0 + count <- 100 + TEMPO_LIMIT <- count + + while (count == TEMPO_LIMIT) { + TEAM_QUERY <- "worklogs" + if (team != 0) { + TEAM_QUERY <- paste0(TEAM_QUERY,"/team/", team) + } + TEMPO_QUERY <- paste0(TEAM_QUERY, + "?from=", begins, + "&to=", ends, + "&offset=", offset, + "&limit=", TEMPO_LIMIT) + results <- fetch.tempo(TEMPO_URL, TEMPO_QUERY, key) + count <- results$metadata$count + if (offset == 0) { + data <- results$results + } else { + data <- bind_rows(data, results$results) + + } + offset <- offset + TEMPO_LIMIT + } + return(data) +} + +``` + +```{r working-hours, echo = FALSE} +workinghours <- function(file = "config/workinghours.csv") { + result <- c() + + if (file.exists(file)) { + result <- read.csv(file) + } else { + print(paste("No such file:", file)) + } + + return(result) +} + +``` + +```{r aggregate-data, echo = FALSE, warning = FALSE, message = FALSE} + +working.hours <- workinghours() + +team.data <- fetch.tempo.teams(TEMPO_URL, TEMPO_KEY) +team.data <- subset(team.data, select = c(id, name)) +knitr::kable(team.data, caption = "Teams", + col.names = capwords(names(team.data))) + +if (TEMPO_TEAM != '') { + teams <- c(TEMPO_TEAM) +} else { + teams <- team.data$id +} + +aggregated.data <- tibble() + +for (team in teams) { + tempo.data <- fetch.tempo.data(TEMPO_KEY, TEMPO_START, Sys.Date(), team) + + aggregated.team.data <- tibble() + + if (length(tempo.data) > 0) { + + aggregated.team.data <- tempo.data %>% + mutate( + user = author$displayName, + hours = timeSpentSeconds/(60*60), + billable = billableSeconds/(60*60), + date = as.Date(startDate), + key = str_replace(issue$key, "-.*", ""), + issue.key = issue$key, + team = team + ) + aggregated.data <- bind_rows(aggregated.data, aggregated.team.data) + } +} + +if ( ! length(aggregated.data) > 0) { + stop("Could not fetch any data") +} + +``` + +```{r data-generators, echo = FALSE} +# +source("data-helpers.R") +``` + +```{r ggplot-helpers, echo = FALSE} +# +source("ggplot-helpers.R") +``` + +```{r, echo = FALSE, warning = FALSE, message = FALSE, results = "asis"} + +teams.with.data <- levels(factor(aggregated.data$team)) +``` + +```{r input, echo = FALSE} +library(shiny) +inputPanel( + selectInput("team.id", label = "Team Id: ", choices = c("", teams.with.data), selected = NA) +) +``` + +```{r echo = FALSE} + +renderTable({ + if ( input$team.id != "" ) { + user.delta <- gen.user.delta(aggregated.data, input$team.id, working.hours, WD_KEY) + } +}) + +renderPlot({ + if ( input$team.id != "" ) { + user.delta <- gen.user.delta(aggregated.data, input$team.id, working.hours, WD_KEY) + accumulated <- accumulated.plot(user.delta) + plot(accumulated) + } +}) + +renderPlot({ + if ( input$team.id != "" ) { + user.summary <- gen.user.summary(aggregated.data, input$team.id) + team.summary <- gen.team.summary(user.summary) + team <- team.plot(team.summary) + plot(team) + } +}) + +if (TEMPO_DETAILS != '') { + renderPlot({ + if ( input$team.id != "" ) { + user.summary <- gen.user.summary(aggregated.data, input$team.id) + rolling <- rolling.plot(user.summary) + plot(rolling) + } + }) +} + +if (TEMPO_DETAILS != '') { + renderPlot({ + if ( input$team.id != "" ) { + tempo <- tempo.daily.plot(aggregated.data, input$team.id) + plot(tempo) + } + }) +} + +renderPlot({ + if ( input$team.id != "" ) { + tempo.detailed <- tempo.detailed.plot(aggregated.data, input$team.id) + plot(tempo.detailed) + } +}) + +if (TEMPO_DETAILS != '') { + renderPlot({ + if ( input$team.id != "" ) { + user.detail <- gen.user.detail(aggregated.data, input$team.id) + tempo.billable <- tempo.billable.plot(user.detail) + plot(tempo.billable) + } + }) +} + +if (TEMPO_DETAILS != '') { + renderPlot({ + if ( input$team.id != "" ) { + user.detail <- gen.user.detail(aggregated.data, input$team.id) + tempo.unbillable <- tempo.unbillable.plot(user.detail) + plot(tempo.unbillable) + } + }) +} +``` diff --git a/tempo.Rmd b/tempo.Rmd index 4296088..b0adff2 100644 --- a/tempo.Rmd +++ b/tempo.Rmd @@ -188,6 +188,11 @@ if ( ! length(aggregated.data) > 0) { source("data-helpers.R") ``` +```{r ggplot-helpers, echo = FALSE} +# +source("ggplot-helpers.R") +``` + ```{r, echo = FALSE, warning = FALSE, message = FALSE, results = "asis"} teams.with.data <- levels(factor(aggregated.data$team)) @@ -204,103 +209,21 @@ for (team.id in teams.with.data) { team.summary <- gen.team.summary(user.summary) - user.delta <- gen.user.delta(aggregated.data, team.id) - - tempo <- ggplot(data = subset(aggregated.data, team == team.id)) + - geom_col(aes(x = date, y = hours, fill = key)) + - facet_wrap(~user) + scale_fill_hue(l = 45) + - scale_y_continuous( - breaks = c(0,2,4,6,8,10), - name = "Daily", - sec.axis = dup_axis()) + - scale_x_date(name = NULL) + - theme(legend.position = "top", - axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + - ggtitle("Daily logs") - - tempo.detailed <- ggplot(data = subset(aggregated.data, team == team.id)) + - geom_col(aes(x = date, y = hours, fill = issue.key), show.legend = FALSE) + - facet_wrap(~user) + scale_fill_hue(l = 45) + - scale_y_continuous( - breaks = c(0,2,4,6,8,10), - name = "Daily", - sec.axis = dup_axis()) + - scale_x_date(name = NULL) + - theme(legend.position = "top", - axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + - coord_cartesian(xlim = c(Sys.Date() - 14, Sys.Date())) + - ggtitle("Detailed logs, last 14 days") - - tempo.billable <- ggplot(data = subset(user.detail, billable > 0)) + - geom_point(aes(x = reorder(issue.key, -hours), - y = hours, - color = issue.key, - fill = issue.key), show.legend = FALSE) + - facet_wrap(~user) + scale_fill_hue(l = 45) + - scale_x_discrete(name = NULL) + - scale_y_log10( - name = "Logged hours [h]", - sec.axis = dup_axis()) + - theme(legend.position = "top", - legend.title = element_blank(), - axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + - ggtitle("Billable tasks") + user.delta <- gen.user.delta(aggregated.data, team.id, working.hours, WD_KEY) + + tempo <- tempo.daily.plot(aggregated.data, team.id) + tempo.detailed <- tempo.detailed.plot(aggregated.data, team.id) - tempo.unbillable <- ggplot(data = subset(user.detail, billable == 0)) + - geom_point(aes(x = reorder(issue.key, -hours), - y = hours, - color = issue.key, - fill = issue.key), show.legend = FALSE) + - facet_wrap(~user) + scale_fill_hue(l = 45) + - scale_x_discrete(name = NULL) + - scale_y_log10( - name = "Logged hours [h]", - sec.axis = dup_axis()) + - theme(legend.position = "top", - axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + - ggtitle("Unbillable tasks") + tempo.billable <- tempo.billable.plot(user.detail) - team <- ggplot(data = team.summary) + - geom_point(aes(x = date, y = average.7.hours), color = "Gray50", shape = 1) + - geom_point(aes(x = date, y = average.30.hours), color = "Dark Blue") + - geom_smooth(aes(x = date, y = average.30.hours), color = "Dark Blue") + - geom_point(aes(x = date, y = average.7.billable), color = "Gray75", shape = 1) + - geom_point(aes(x = date, y = average.30.billable), color = "Dark Green") + - geom_smooth(aes(x = date, y = average.30.billable), color = "Dark Green") + - scale_color_hue(l = 45) + scale_fill_hue(l = 45) + - scale_y_continuous( - breaks = c(0,8,16,24,32,40, 48,56), - name = "Weekly", - sec.axis = dup_axis()) + - scale_x_date(name = NULL) + - theme(legend.position = "top", - legend.title = element_blank(), - axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + tempo.unbillable <- tempo.unbillable.plot(user.detail) - rolling <- ggplot(data = user.summary) + - geom_point(aes(x = date, y = roll.7.hours), color = "Gray50", shape = 1) + - geom_point(aes(x = date, y = roll.7.billable), color = "Gray75", shape = 1) + - geom_point(aes(x = date, y = roll.30.hours), color = "Dark Blue") + - geom_line(aes(x = date, y = roll.30.hours), color = "Dark Blue") + - geom_point(aes(x = date, y = roll.30.billable), color = "Dark Green") + - geom_line(aes(x = date, y = roll.30.billable), color = "Dark Green") + - facet_wrap(~user) + scale_fill_hue(l = 45) + scale_color_hue(l = 45) + - scale_y_continuous( - breaks = c(0,8,16,24,32,40, 48), - name = "Rolling Weekly [h]", - sec.axis = dup_axis()) + - scale_x_date(name = NULL) + - theme(legend.position = "top", legend.title = element_blank(), - axis.text.x = element_text(size = 6, angle = 45, hjust = 1)) + team <- team.plot(team.summary) + + rolling <- rolling.plot(user.summary) - accumulated <- ggplot(data = user.delta) + - geom_col(aes(x = user, y = delta, fill = user), show.legend = FALSE) + - scale_fill_hue(l = 45) + - scale_x_discrete(name = NULL) + - scale_y_continuous( - name = "Delta hours [h]", - sec.axis = dup_axis()) + accumulated <- accumulated.plot(user.delta) print(knitr::kable(user.delta, caption = subset(team.data, id == team.id)$name,