Chelsyx has uploaded a new change for review. ( 
https://gerrit.wikimedia.org/r/327877 )

Change subject: Add sparklines for KPIs: - KPI Summary Page - Monthly Metrics 
Page
......................................................................

Add sparklines for KPIs:
- KPI Summary Page
- Monthly Metrics Page

Bug: T150215
Change-Id: I4b64830a3db7f734977b19de695fdf7b0ae7ee12
---
M server.R
M ui.R
2 files changed, 142 insertions(+), 18 deletions(-)


  git pull ssh://gerrit.wikimedia.org:29418/wikimedia/discovery/rainbow 
refs/changes/77/327877/1

diff --git a/server.R b/server.R
index 3f980c6..c2481db 100644
--- a/server.R
+++ b/server.R
@@ -1,6 +1,9 @@
 library(shiny)
 library(shinydashboard)
 library(dygraphs)
+library(sparkline)
+library(DT)
+library(data.table)
 
 source("utils.R")
 
@@ -559,6 +562,84 @@
     return(polloi::na_box("User engagement (data problem)"))
   })
 
+  ## KPI Sparklines
+  output$sparkline_load_time <- sparkline:::renderSparkline({
+    if(input$kpi_summary_date_range_selector == "all"){
+      output_sl <- list(desktop_load_data, mobile_load_data, 
android_load_data, ios_load_data)
+    } else{
+      output_sl <- list(desktop_load_data, mobile_load_data, 
android_load_data, ios_load_data) %>%
+        lapply(polloi::subset_by_date_range, from = Sys.Date() - 91, to = 
Sys.Date() - 1)
+    }
+    output_sl <- output_sl %>%
+      lapply(function(platform_load_data) {
+        platform_load_data[, c("date", "Median")]
+      }) %>%
+      dplyr::bind_rows(.id = "platform") %>%
+      dplyr::group_by(date) %>%
+      dplyr::summarize(Median = median(Median)) %>%
+      dplyr::ungroup() %>%
+      dplyr::select(Median) %>%
+      unlist(use.names = FALSE) %>%
+      round(2)
+    sparkline::sparkline(values = output_sl, type = "line",
+                         height = 50, width = '100%',
+                         lineColor = 'black', fillColor = '#ccc',
+                         highlightLineColor = 'orange', highlightSpotColor = 
'orange')
+  })
+  output$sparkline_zero_results <- sparkline:::renderSparkline({
+    if(input$kpi_summary_date_range_selector == "all"){
+      output_sl <- failure_data_with_automata
+    } else{
+      output_sl <- failure_data_with_automata %>%
+        polloi::subset_by_date_range(from = Sys.Date() - 91, to = Sys.Date() - 
1)
+    }
+    output_sl <- output_sl %>%
+      dplyr::select(rate) %>%
+      unlist(use.names = FALSE) %>%
+      round(2)
+    sparkline::sparkline(values = output_sl, type = "line",
+                         height = 50, width = '100%',
+                         lineColor = 'black', fillColor = '#ccc',
+                         highlightLineColor = 'orange', highlightSpotColor = 
'orange')
+  })
+  output$sparkline_api_usage <- sparkline:::renderSparkline({
+    if(input$kpi_summary_date_range_selector == "all"){
+      output_sl <- split_dataset
+    } else{
+      output_sl <- split_dataset %>%
+        lapply(polloi::subset_by_date_range, from = Sys.Date() - 91, to = 
Sys.Date() - 1)
+    }
+    output_sl <- output_sl %>%
+      lapply(function(platform_load_data) {
+        platform_load_data[, c("date", "events")]
+      }) %>%
+      dplyr::bind_rows(.id = "api") %>%
+      dplyr::group_by(date) %>%
+      dplyr::summarize(total = sum(events)) %>%
+      dplyr::select(total) %>%
+      unlist(use.names = FALSE)
+    sparkline::sparkline(values = output_sl, type = "line",
+                         height = 50, width = '100%',
+                         lineColor = 'black', fillColor = '#ccc',
+                         highlightLineColor = 'orange', highlightSpotColor = 
'orange')
+  })
+  output$sparkline_augmented_clickthroughs <- sparkline:::renderSparkline({
+    if(input$kpi_summary_date_range_selector == "all"){
+      output_sl <- augmented_clickthroughs
+    } else{
+      output_sl <- augmented_clickthroughs %>%
+        polloi::subset_by_date_range(from = Sys.Date() - 91, to = Sys.Date() - 
1)
+    }
+    output_sl <- output_sl %>%
+      dplyr::select(user_engagement) %>%
+      unlist(use.names = FALSE) %>%
+      round(2)
+    sparkline::sparkline(values = output_sl, type = "line",
+                         height = 50, width = '100%',
+                         lineColor = 'black', fillColor = '#ccc',
+                         highlightLineColor = 'orange', highlightSpotColor = 
'orange')
+  })
+
   ## KPI Modules
   output$kpi_load_time_series <- renderDygraph({
     smooth_level <- input$smoothing_kpi_load_time
@@ -722,8 +803,9 @@
       dyEvent(as.Date("2016-07-12"), "A (schema switch)", labelLoc = "bottom")
   })
 
-  output$monthly_metrics_tbl <- renderUI({
-    temp <- data.frame(
+  output$monthly_metrics_tbl <- DT::renderDataTable(
+    {
+      temp <- data.frame(
       KPI = c("Load time", "Zero results rate", "API Usage", "User 
engagement"),
       Units = c("ms", "%", "", "%")
     )
@@ -795,28 +877,64 @@
     # Sanitize:
     temp[temp == "NA%" | temp == "NANA%" | temp == "NANA"] <- "--"
     temp$KPI <- paste0('<a id="mm_', temp$Anchors, '">', temp$KPI, '</a>')
-    cols_to_keep <- c(1, 5, 4, 3, 7, 8)
+    # sparkline
+    median_load_times <- list(Desktop = desktop_load_data,
+                              Mobile = mobile_load_data,
+                              Android = android_load_data,
+                              iOS = ios_load_data) %>%
+      lapply(function(platform_load_data) {
+        platform_load_data[, c("date", "Median")]
+      }) %>%
+      dplyr::bind_rows(.id = "platform") %>%
+      dplyr::group_by(date) %>%
+      dplyr::summarize(Median = median(Median)) %>%
+      dplyr::mutate(month = as.yearmon(date)) %>%
+      dplyr::group_by(month) %>%
+      dplyr::summarise(monthly_median = round(median(Median), 2))
+    median_zrr <- failure_data_with_automata %>%
+      dplyr::mutate(month = as.yearmon(date)) %>%
+      dplyr::group_by(month) %>%
+      dplyr::summarise(monthly_median = round(median(rate), 2))
+    median_api <- split_dataset %>%
+      lapply(function(platform_load_data) {
+        platform_load_data[, c("date", "events")]
+      }) %>%
+      dplyr::bind_rows(.id = "api") %>%
+      dplyr::group_by(date) %>%
+      dplyr::summarize(total = sum(events)) %>%
+      dplyr::mutate(month = as.yearmon(date)) %>%
+      dplyr::group_by(month) %>%
+      dplyr::summarise(monthly_median = median(total))
+    median_engagement <- augmented_clickthroughs %>%
+      dplyr::mutate(month = as.yearmon(date)) %>%
+      dplyr::group_by(month) %>%
+      dplyr::summarise(monthly_median = round(median(user_engagement),2))
+    temp$`Monthly Median` <- c(paste(median_load_times$monthly_median, 
collapse = ","),
+                     paste(median_zrr$monthly_median, collapse = ","),
+                     paste(median_api$monthly_median, collapse = ","),
+                     paste(median_engagement$monthly_median, collapse = ","))
+    cols_to_keep <- c(1, 5, 4, 3, 7, 8, 9)
     if (!input$monthly_metrics_prev_month) {
       cols_to_keep <- base::setdiff(cols_to_keep, 4)
     }
     if (!input$monthly_metrics_prev_year) {
       cols_to_keep <- base::setdiff(cols_to_keep, 5)
     }
-    return(HTML(
-      knitr::kable(temp[, cols_to_keep], format = "html", table.attr = 
"class=\"table table-striped spacing-s\"", escape = FALSE),
-      "<!-- JS for clicking on the KPIs in the table -->
-      <script type = 'text/javascript'>
-      // Enables clicking on a kpi in the monthly metrics table:
+    column_def <- list(list(targets = length(cols_to_keep)-1, render = 
JS("function(data, type, full){ return '<span class=sparkSeries>' + data + 
'</span>' }")))
+    line_string <- "type: 'line', lineColor: 'black', fillColor: '#ccc', 
highlightLineColor: 'orange', highlightSpotColor: 'orange'"
+    callback_fnc <- JS(paste0("function (oSettings, json) {
+      $('.sparkSeries:not(:has(canvas))').sparkline('html', { ", line_string, 
" });
       $('a[id^=mm_kpi_]').click(function(){
-        var target = $(this).attr('id').replace('mm_', '');
-        $('a[data-value=\"'+target+'\"]').click();
-      });
-      // Visual feedback that the kpi in the monthly metrics table is 
clickable:
-      $('a[id^=mm_kpi_]').hover(function() {
-        $(this).css('cursor','pointer');
-      });</script>"
-    ))
-  })
+      var target = $(this).attr('id').replace('mm_', '');
+      $('a[data-value=\"'+target+'\"]').click();});
+      $('a[id^=mm_kpi_]').hover(function() 
{$(this).css('cursor','pointer');});\n}"), collapse = "")
+    mm_dt <- datatable(data.table(temp[, cols_to_keep]), rownames = FALSE,
+      options = list(searching = F, paging = F, info = F, ordering = F,
+                     columnDefs = column_def, fnDrawCallback = callback_fnc), 
escape=F)
+    mm_dt$dependencies <- append(mm_dt$dependencies, 
htmlwidgets:::getDependency("sparkline"))
+    mm_dt
+    }
+  )
 
   # Check datasets for missing data and notify user which datasets are missing 
data (if any)
   output$message_menu <- renderMenu({
diff --git a/ui.R b/ui.R
index 9219483..5961c93 100644
--- a/ui.R
+++ b/ui.R
@@ -86,6 +86,12 @@
                          valueBoxOutput("kpi_summary_box_zero_results", width 
= 3),
                          valueBoxOutput("kpi_summary_box_api_usage", width = 
3),
                          
valueBoxOutput("kpi_summary_box_augmented_clickthroughs", width = 3)),
+                fluidRow(
+                  box(sparkline:::sparklineOutput('sparkline_load_time'), 
width=3, background="light-blue"),
+                  box(sparkline:::sparklineOutput('sparkline_zero_results'), 
width=3, background="light-blue"),
+                  box(sparkline:::sparklineOutput('sparkline_api_usage'), 
width=3, background="light-blue"),
+                  
box(sparkline:::sparklineOutput('sparkline_augmented_clickthroughs'), width=3, 
background="light-blue")
+                  ),
                 includeMarkdown("./tab_documentation/kpis_summary.md")),
         tabItem(tabName = "monthly_metrics",
                 fluidRow(
@@ -110,7 +116,7 @@
                   checkboxInput("monthly_metrics_prev_year",
                                 "Show previous year", TRUE),
                   width = 4),
-                  column(htmlOutput("monthly_metrics_tbl"), width = 8)
+                  column(DT::dataTableOutput("monthly_metrics_tbl"), width = 8)
                 ),
                 includeMarkdown("./tab_documentation/monthly_metrics.md")),
         tabItem(tabName = "kpi_load_time",

-- 
To view, visit https://gerrit.wikimedia.org/r/327877
To unsubscribe, visit https://gerrit.wikimedia.org/r/settings

Gerrit-MessageType: newchange
Gerrit-Change-Id: I4b64830a3db7f734977b19de695fdf7b0ae7ee12
Gerrit-PatchSet: 1
Gerrit-Project: wikimedia/discovery/rainbow
Gerrit-Branch: master
Gerrit-Owner: Chelsyx <c...@wikimedia.org>

_______________________________________________
MediaWiki-commits mailing list
MediaWiki-commits@lists.wikimedia.org
https://lists.wikimedia.org/mailman/listinfo/mediawiki-commits

Reply via email to