diff --git a/.gitignore b/.gitignore index 093f24e..c38a0d4 100644 --- a/.gitignore +++ b/.gitignore @@ -6,21 +6,23 @@ .Rproj.user/ *.Rproj +# Folder readme +FOLDER_INFO.txt # Deployment secrets # Credentials script +create_credentials.R # Constants file constants.R -# Data prep script -data_preparation.R - -# 'data' folder # +# folders to ignrore +admin/ +archive/ data/ - -# infographics folder +drafts/ www/infographics + # Common text files that may contain data # *.[cC][sS][vV] *.[tT][xX][tT] diff --git a/README.md b/README.md index 40bab25..4144e98 100644 --- a/README.md +++ b/README.md @@ -1,2 +1,8 @@ # MHQI-Dashboard The Mental Health Team's repo for the Mental Health Quality Indicators Dashboard + +## Maintaining +This dashboard makes use of a file 'stylesheet.css' (which can be found in the www folder - where it must remain in order to work) to define styling of various elements. This styling overrides the default styling set by the Shiny package and enables styling to be changed once in one place and affect every incidence of that element. As a result, editing aesthetics and certain behaviours of this dashboard should be a much simpler process. + +To edit an element you need to know what 'class(es)' refers to the element. If you need to find out the class(es) of a particular element you can run the app within RStudio and right click on the element you are interested in. Then click "inspect" and it will bring up the developer window with the relevant bits of code. + diff --git a/app.R b/app.R index a98ae23..60b2666 100644 --- a/app.R +++ b/app.R @@ -1,26 +1,43 @@ +### Mental Health Quality Indicators Dashboard + +# Loading packages library(phsstyles) +library(plotly) +library(ggplot2) # adding for testing using this before plotly library(dplyr) -library(purrr) +library(purrr) # for map function to load multiple files +library(stringr) library(shiny) library(shinydashboard) library(fresh) # for customising shinydashboard look library(shinyWidgets) - +library(forcats) # added by mahri for fct_reorder() in graph +library(gotop) # for return to top button +library(shinycssloaders) # for graph loading spinners +library(DT) +library(shinymanager) # password protection # Data import section ---------------------------------------------------- # Source constants used throughout app source("scot_hub_data.R") +source("setup.R") +source("data_preparation.R") + +# 6. sourcing functions created for app (see functions folder) ------------------------------- +list.files("functions") %>% + map(~ source(paste0("functions/", .))) -# # 6. sourcing functions created for app (see functions folder) ------------------------------- -# list.files("functions") %>% -# map(~ source(paste0("functions/", .))) +#* Read in credentials for password-protecting the app ---- +# credentials <- readRDS("admin/credentials.rds") # Un-comment if password protection needed -# Source the ui file ---- +### [ UI section ] ------------------------------------------------------------- -# ui <- source('ui.R', local = TRUE)$value -ui <- dashboardPage( + +ui <- + # secure_app( # Un-comment if password protection is needed. + dashboardPage( dashboardHeader(title = "MH Quality Indicators"), @@ -28,6 +45,7 @@ ui <- dashboardPage( # Define how the various pages of the dashboard look dashboardBody( + ## Source styling for shinydashboard elements # - must be before stylesheet so that it doesn't override the css file source("www/dashboard_style.R", local = TRUE)$value, @@ -35,16 +53,16 @@ ui <- dashboardPage( ## load css stylesheet that defines how things look tags$head(includeCSS("www/stylesheet.css")), - + ## Tabs ---- tabItems( - # [Introduction Tab] ---------------------------------------------------- + # [Introduction Tab] ---- source("modules/introduction_ui.R", local = TRUE)$value, - # [Scotland Hub Tab] ---------------------------------------------------- + # [Scotland Hub Tab] ---- source("modules/scot_hub_ui.R", local = TRUE)$value, - ## Sourcing ui sections for each indicator ------------------------------- + ## Sourcing ui sections for each indicator ---- # [Timely] ---- source("modules/indicators/T1_ui.R", local = TRUE)$value, source("modules/indicators/T2_ui.R", local = TRUE)$value, @@ -81,14 +99,44 @@ ui <- dashboardPage( ) # End of tabItems ) # End of dashboardBody -) # End of UI +) # End of dashboardPage +# ) # End of password-protection wrapper -# Server ---------------------------------------------------- + + +### [ Server ] ----------------------------------------------------------------- server <- function(input, output, session) { + ##* Shinymanager authorisation ---- + # Un-comment this section to password protect the app. + # Re-comment out to remove password protection on launch day. + # res_auth <- secure_server( + # check_credentials = check_credentials(credentials) + # ) + # + # output$auth_output <- renderPrint({ + # reactiveValuesToList(res_auth) + # }) + # Navigation buttons ---- source("modules/nav_buttons_server.R", local = TRUE) + # Indicator servers + source("modules/indicators/E1_server.R", local = TRUE) + source("modules/indicators/EQ1_server.R", local = TRUE) + source("modules/indicators/EF4_server.R", local = TRUE) + + + # Keep dashboard active indefinitely to meet accessibility requirements + # (Keep at the end of server) + auto_invalidate <- reactiveTimer(10000) + observe({ + auto_invalidate() + cat(".") + }) } +# Sets language right at the top of source (required this way for screen readers) +attr(ui, "lang") = "en" + shinyApp(ui, server) diff --git a/data_preparation.R b/data_preparation.R new file mode 100644 index 0000000..a878adb --- /dev/null +++ b/data_preparation.R @@ -0,0 +1,47 @@ +### Data preparation script +# N.B. do not use any direct filepaths, ony relational ones + +### [Indicators] ---- +## E1 ---- +E1_data <- read.csv("data/E1.csv") %>% + rename(dd_bed_days = delayed_discharge_bed_days, + fyear = financial_year) + +E1_area_types <- E1_data %>% + distinct(area_type) %>% pull(area_type) + +# For E1 plot 2: +E1_fyear <- E1_data %>% + distinct(fyear) %>% + pull(fyear) + +## EQ1 ---- +EQ1_data <- read.csv("data/EQ1.csv") + +unique_area_types <- EQ1_data %>% + distinct(area_type) %>% pull(area_type) + +# For EQ1 plot 2: +EQ1_reformatted_data <- read.csv("data/EQ1_Reformatted.csv")%>% + mutate(Rate = round(Rate)) # because values are e.g. "3158.23942548425913" + +unique_area_types_reformatted <- EQ1_reformatted_data %>% + distinct(area_type) %>% pull(area_type) + + +## EF4 ---- +EF4_data <- read.csv("data/EF4.csv") %>% + select(fyear, hb_name, measure, value) + +EF4_fyear <- EF4_data %>% + distinct(fyear) %>% pull(fyear) + +EF4_hb_names <- EF4_data %>% + distinct(hb_name) %>% pull(hb_name) + +EF4_trend_measures <- c('Mental Health Expenditure (%)', 'CAMHS Expenditure (%)') + +# EF4_trend_measures <- EF4_data %>% +# distinct(measure) %>% pull(measure) %>% +# filter(measure = ) + diff --git a/functions/core_functions.R b/functions/core_functions.R new file mode 100644 index 0000000..8fceaeb --- /dev/null +++ b/functions/core_functions.R @@ -0,0 +1,7 @@ +# Load data from shiny_app/data ---- +load_csv_file <- function(csv){ + # Given a .csv file name in shiny_app/data + # this function loads it as a variable with the same name as the + # file apart from the extension + assign(gsub(".csv", "", csv), read.csv(paste0("data/", csv)), envir = .GlobalEnv) +} diff --git a/functions/plot_functions.R b/functions/plot_functions.R new file mode 100755 index 0000000..e9bcda5 --- /dev/null +++ b/functions/plot_functions.R @@ -0,0 +1,70 @@ +### Functions used in plots throughout the app + +## PHS colour spinner ---- + +phs_spinner <- function(plot_name){ + withSpinner( + plotlyOutput(plot_name, width = "100%"), + type = 8, size = 0.7, + color = "#AF69A9", # color.background = "#E1C7DF", + caption = "Loading...", + hide.ui = FALSE + ) +} + +## No Data function ---- +# Function defining what is shown when there is no data to be presented: + +noDataPlot <- function(line_colour){ + + noDataPlot_text <- list( + x = 5, + y = 2, + font = list(color = line_colour, size = 20), + text = paste0("No discharges found for these selections."), + xref = "x", + yref = "y", + showarrow = FALSE +) + +# Visualise an empty graph with the above message in the middle. + +plot_ly() %>% + layout(annotations = noDataPlot_text, + yaxis = list(showline = FALSE, + showticklabels = FALSE, + showgrid = FALSE), + xaxis = list(showline = FALSE, + showticklabels = FALSE, + showgrid = FALSE)) %>% + config(displayModeBar = FALSE, + displaylogo = F, editable = F) + +} + +### Scatter Line Plot Function ---- +# Aesthetic attributes for line graphs + +phs_scatterPlot <- function(plot_data, # Graph reactive ouput + x_var, # variable on x axis + y_var, # variable on y axis + tooltip, # tooltip object name + line_var # line variable name + ) + { + +plotly( + data = plot_data(), + x = ~x_var, y = ~y_var, + text = tooltip, hoverinfo = "text", + color = ~line_var, + colors = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), # line colours + type = 'scatter', mode = 'lines+markers', + # width = 600, height = 300, + line = list(width = 2), + linetype = ~line_var, + linetypes = c("solid", "dash"), + marker = list(size = 8), + name = ~str_wrap(line_var, 19)) + +} diff --git a/indicator_alt_text.R b/indicator_alt_text.R new file mode 100644 index 0000000..f726584 --- /dev/null +++ b/indicator_alt_text.R @@ -0,0 +1,9 @@ +max_year <- 2024 + +EF1 <- read_csv('data/EF1.csv') + +EF1_rate <- EF1$rate %>% + filter(fyear = max_year) + +EF1_lag_rate <- EF1$rate %>% + filter(fyear = (max_year-1)) \ No newline at end of file diff --git a/modules/appendix_ui.R b/modules/appendix_ui.R index 162b143..ff18fb8 100644 --- a/modules/appendix_ui.R +++ b/modules/appendix_ui.R @@ -1,4 +1,4 @@ -tabItem(tabName = appendix_tab, +tabItem(tabName = "appendix_tab", fluidPage( titlePanel(h1("T1 - % of people who commence psychological therapy based treatment within 18 weeks of referral"), diff --git a/modules/indicators/E1_server.R b/modules/indicators/E1_server.R new file mode 100644 index 0000000..fcec46b --- /dev/null +++ b/modules/indicators/E1_server.R @@ -0,0 +1,480 @@ +# PLOT 1 ---- + +## Picker for user selecting HB or CA ---- + +output$E1_plot1_areaType_output <- renderUI({ + shinyWidgets::pickerInput( + "E1_plot1_areaType", + label = "Select type of geography:", + choices = E1_area_types, + selected = "Health board") +}) + +## Picker for user selecting specific geographies ---- + +output$E1_plot1_areaName_output <- renderUI({ + shinyWidgets::pickerInput( + "E1_plot1_areaName", + label = "Select area(s) (Maximum 4):", + choices = sort(unique(as.character( + E1_data$area_name + [E1_data$area_type %in% input$E1_plot1_areaType] + ))), + multiple = TRUE, + options = list("max-options" = 4, + `selected-text-format` = "count > 1"), + selected = "NHS Ayrshire and Arran" + ) +}) + +## Selecting appropriate data for graph 1 ---- +E1_plot1_Data <- reactive({ + E1_data %>% + select(fyear, area_type, area_name, dd_bed_days) %>% + filter(area_type %in% input$E1_plot1_areaType # don't think we really need this first filter but doesn't harm anything? + & area_name %in% input$E1_plot1_areaName) +}) + + +# Create the discharges line chart ---- + + ### Render plotly ---- + +output$E1_plot1 <- renderPlotly({ + + ### Create reactive ggplot graph ---- + + E1_plot1_graph <- reactive({ + + ggplot(data = E1_plot1_Data(), + aes(x = fyear, + y = dd_bed_days, + text = paste0("Financial year: ", + E1_plot1_Data()$fyear, + "
", + "Area of residence: ", + E1_plot1_Data()$area_name, + "
", + "Total number of bed days: ", + E1_plot1_Data()$dd_bed_days))) + # for tooltip in ggplotly - shows values on hover + geom_line() + + geom_point(size = 2.5) + + aes(group = area_name, + linetype = area_name, + color = area_name, # Have to do this outside so that the legends shows and so that there aren't 3 legends + shape = area_name) + + scale_color_discrete_phs(name = "Area name", + palette = "main-blues", + labels = ~ stringr::str_wrap(.x, width = 15)) + + # scale_color_manual(name = "Area name", + # values = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), + # labels = ~ stringr::str_wrap(.x, width = 15)) + + scale_linetype_manual(name = "Area name", + values = c("solid", "dashed", "solid", "dashed"), + labels = ~ stringr::str_wrap(.x, width = 15)) + + scale_shape_manual(name = "Area name", + values = c("circle", "circle", "triangle-up", "triangle-up"), + labels = ~ stringr::str_wrap(.x, width = 15)) + + theme_classic() + # I normally use bw but will see what this looks like (de-clutters graph background) + theme(panel.grid.major.x = element_line(), # Shows vertical grid lines + panel.grid.major.y = element_line(), # Shows horizontal grid lines + axis.title.x = element_text(size = 12, + color = "black", + face = "bold"), + axis.title.y = element_text(size = 12, + color = "black", + face = "bold"), + legend.text = element_text(size = 8, + colour = "black"), + legend.title = element_text(size = 9, + colour = "black", + face = "bold")) + + labs(x = "Financial Year", + y = "Total Number of Days") + + scale_y_continuous(expand = c(0, 0), # Ensures y axis starts from zero (important for Orkney and Shetland HBs which are all zero) + limits = c(0, (max(E1_plot1_Data()$dd_bed_days) + 0.5*max(E1_plot1_Data()$dd_bed_days)))) + + }) + + ### Run graph 1 through plotly ---- + + ggplotly(E1_plot1_graph(), + tooltip = "text")#, # uses text set up in ggplot aes above. + # ### Remove unnecessary buttons from the modebar ---- not working just now + # config(displayModeBar = TRUE, # Remove unnecessary buttons from the modebar + # modeBarButtonsToRemove = bttn_remove, + # displaylogo = F, editable = F)) + +}) + + + + +## X ALL OF THE OLD CODE FOR PLOT 1 ---- + +# # PLOT 1 ---- +# +# output$E1_plot1_areaType_output <- renderUI({ +# shinyWidgets::pickerInput( +# "E1_plot1_areaType", +# label = "Select type of geography:", +# choices = E1_area_types, +# selected = "Health board") +# }) +# +# output$E1_plot1_areaName_output <- renderUI({ +# shinyWidgets::pickerInput( +# "E1_plot1_areaName", +# label = "Select area(s) (Maximum 5):", +# choices = sort(unique(as.character( +# E1_data$area_name +# [E1_data$area_type %in% input$E1_plot1_areaType] +# ))) +# # , +# # multiple = TRUE, +# # options = list("max-options" = 5, +# # `selected-text-format` = "count > 1") +# ) +# }) +# +# E1_plot1_Data <- reactive({ +# E1_data %>% +# select(fyear, area_type, area_name, dd_bed_days) %>% +# filter(area_type %in% input$E1_plot1_areaType +# & area_name %in% input$E1_plot1_areaName) +# }) +# +# # Pull out max bed days value for selected georgraph for using in y-axis range later +# # (Warning error received without this) +# E1_max_bed_days <- reactive({ +# E1_data %>% +# select(fyear, area_type, area_name, dd_bed_days) %>% +# group_by(area_type, area_name) %>% +# filter(area_type %in% input$E1_plot1_areaType +# & area_name %in% input$E1_plot1_areaName) %>% +# slice_max(dd_bed_days) %>% +# ungroup() %>% +# pull(dd_bed_days) +# }) +# +# # Create the discharges line chart. +# +# output$E1_plot1 <- renderPlotly({ +# # +# # # # No data plot +# # # if(sum(E1_plot1_Data()$dd_bed_days) == 0 & +# # # !is.na(sum(E1_plot1_Data()$dd_bed_days))) +# # # +# # # { +# # # noDataPlot(phs_colours("phs-purple")) +# # # } +# # # +# # # else { +# # +# ### 3 - Tooltip creation ---- +# +# tooltip_E1 <- paste0("Financial year: ", +# E1_plot1_Data()$fyear, +# "
", +# "Area of residence: ", +# E1_plot1_Data()$area_name, +# "
", +# "Number of Bed Days: ", +# E1_plot1_Data()$dd_bed_days) +# +# ### 4 - Create the main body of the chart ---- +# +# plot_ly(data = E1_plot1_Data(), +# # Select your variables. +# x = ~fyear, y = ~dd_bed_days, color = ~area_name, +# colors = c("#0080FF"), # line colour - Dark blue for all lines +# text = tooltip_E1, hoverinfo = "text", +# type = 'scatter', mode = 'lines+markers', +# # width = 600, height = 300, +# line = list(width = 3), +# marker = list(size = 12), +# name = ~str_wrap(area_name, 19)) %>% # legend labels +# +# ### 7 - Graph title ---- +# +# # Make the graph title reactive. +# +# layout(title = +# paste0( +# "", +# "Number of Delayed Discharge Bed Days", " by ", +# input$E1_plot1_areaType, ",", +# "
", +# first(as.vector(E1_plot1_Data()$fyear)), +# " to ", +# last(as.vector(E1_plot1_Data()$fyear)), +# "
", +# "
" +# ), +# +# separators = ".", +# +# +# yaxis = list( +# exponentformat = "none", +# separatethousands = TRUE, +# range = c(0, E1_max_bed_days() +# + (E1_max_bed_days() * 0.1)), +# title = paste0(c(rep(" ", 20), +# input$E1_1_input_1, +# rep(" ", 20), +# rep("\n ", 3))), +# showline = TRUE, +# ticks = "outside" +# ), +# +# +# xaxis = list( +# title = paste0(c("
", +# "Financial year", +# collapse = "")), # Don't think it's needed +# showline = TRUE, +# ticks = "outside" +# ), +# +# margin = list(l = 90, r = 60, b = 180, t = 120), +# title = list(size = 15), +# font = list(size = 13), +# # Legend +# showlegend = TRUE, +# legend = list(x = 1, +# y = 1, +# bgcolor = 'rgba(255, 255, 255, 0)', +# bordercolor = 'rgba(255, 255, 255, 0)') +# # legend = list(orientation = "h", # show entries horizontally +# # xanchor = "center", # use center of legend as anchor +# # x = 0.5, y = -0.9) # put legend in center of x-axis +# ) %>% +# +# ### 13 - Remove unnecessary buttons from the modebar ---- +# +# config(displayModeBar = TRUE, +# modeBarButtonsToRemove = bttn_remove, +# displaylogo = F, editable = F) +# +# # } +# +# }) +# +# +# ### 15 - Table below graph creation ---- +# + output$E1_1_table <- renderDataTable({ + datatable(E1_plot1_Data(), + style = 'bootstrap', + class = 'table-bordered table-condensed', + rownames = FALSE, + options = list(pageLength = 16, autoWidth = TRUE, dom = 'tip'), + colnames = c("Financial year", + "Area type", + "Area of Residence", + "Number of Bed Days")) + }) + + + + +# PLOT 2 ---- + +## Picker for user selecting Financial Year ---- + +output$E1_plot2_year_output <- renderUI({ + shinyWidgets::pickerInput( + "E1_plot2_year", + label = "Select financial year:", + choices = E1_fyear, + selected = "2023/24") +}) + +## Selecting appropriate data for graph 2 ---- + +E1_plot2_Data <- reactive({ + E1_data %>% + select(fyear, area_type, area_name, dd_bed_days, rate_per_1000_population) %>% + filter(area_type == "Health board") %>% + filter(fyear %in% input$E1_plot2_year) %>% + mutate(area_name = fct_reorder(area_name, rate_per_1000_population)) %>% # for ordering by most to least bed days + mutate(to_highlight = if_else(area_name == "NHS Scotland", # for highlighting NHS Scotland + "seagreen", "#0080FF")) # changed from "yes" and "no" so that these colours +}) # appear on the graph and don't have a legend using "marker = list(color... )" + + +E1_plot2_Data_download <- reactive({ #Equivalent data for download function, without highlight column. + E1_data %>% + select(fyear, area_type, area_name, dd_bed_days, rate_per_1000_population) %>% + filter(area_type == "Health board") %>% + filter(fyear %in% input$E1_plot2_year) %>% + mutate(area_name = fct_reorder(area_name, rate_per_1000_population)) }) + + +# Create the discharges bar chart ---- + + ### Render plotly ---- + +output$E1_plot2 <- renderPlotly({ + + ### Create reactive ggplot graph ---- + +E1_plot2_graph <- reactive({ + ggplot(E1_plot2_Data(), + aes(x = rate_per_1000_population, + y = area_name, + fill = to_highlight, # colours defined below (highlights NHS Scotland) + text = paste0("Financial year: ", fyear, # for tooltip in ggplotly - shows values on hover + "
", + "Area of residence: ", area_name, + "
", + "Bed days per 1,000 population: ", rate_per_1000_population) + )) + + geom_bar(stat = "identity") + # creates bar graph with bars separated from each other + scale_fill_manual(values = phs_colours(c("phs-blue", "phs-green"))) + # highlights NHS Scotland +# scale_fill_manual(values = c("#0080FF", "seagreen")) + # highlights NHS Scotland + theme_classic() + # I normally use bw but will see what this looks like (de-clutters graph background) + theme(panel.grid.major.x = element_line(), # Shows vertical grid lines + panel.grid.major.y = element_line(), # Shows horizontal grid lines + axis.title.x = element_text(size = 12, + color = "black", + face = "bold"), + axis.title.y = element_blank(), + legend.position = "none") + # removes legend + labs(x = "Number of Days per 1,000 Population", y = NULL) + + scale_x_continuous(limits = c(0, (max(E1_data$rate_per_1000_population) + 9)), # Keeps the x-axis the same length for all graphs, ranges from 0 to the max value plus 9 so that the last tick can be seen + breaks = seq(0, (max(E1_data$rate_per_1000_population) + 9), by = 10)) # x-axis ticks range from 0 to the max value + 9, showing increments of 10 + +}) + ### Run graph 2 through plotly ---- + +ggplotly(E1_plot2_graph(), + tooltip = "text")#, # uses text set up in ggplot aes above. + # ### Remove unnecessary buttons from the modebar ---- not working but will make work + # config(displayModeBar = TRUE, + # modeBarButtonsToRemove = bttn_remove, + # displaylogo = F, editable = F)) + +}) + + +# ### 15 - Table below graph creation ---- +# +output$E1_2_table <- renderDataTable({ + datatable(E1_plot2_Data(), + style = 'bootstrap', + class = 'table-bordered table-condensed', + rownames = FALSE, + options = list(pageLength = 16, autoWidth = TRUE, dom = 'tip', + columnDefs = list(list(visible=FALSE, targets=5))), + colnames = c("Financial year", + "Area type", + "Area of Residence", + "Number of Bed Days", + "Rate per 1000 population", + "Highlight")) +}) + +# Create download buttons that allows users to the download tables in .csv format. +output$E1_1_table_download <- downloadHandler( + filename = 'E1 - Total bed days for chosen area.csv', + content = function(file) { + write.table(E1_plot1_Data(), + file, + #Remove row numbers as the .csv file already has row numbers. + row.names = FALSE, + col.names = c("Financial year", + "Area type", + "Area of Residence", + "Number of Bed Days"), + sep = ",") + } +) + +output$E1_2_table_download <- downloadHandler( + filename = 'E1 - Total bed days for chosen year.csv', + content = function(file) { + write.table(E1_plot2_Data_download(), + file, + #Remove row numbers as the .csv file already has row numbers. + row.names = FALSE, + col.names = c("Financial year", + "Area type", + "Area of Residence", + "Number of Bed Days", + "Rate per 1000 population"), + sep = ",") + } +) + + +## x OLD PLOTLY CODE - PLOT 2 ---- +# output$E1_plot2 <- renderPlotly({ +# + #### Hover Text - Tooltip creation (doesn't quite work) ---- +# +# tooltip_E1_plot2 <- paste0("Area of residence: ", +# E1_plot2_Data()$area_name, +# "
", +# "Number of Bed Days per 1000 population: ", +# E1_plot2_Data()$dd_bed_days) +# + #### Create the main body of the chart ---- +# +# plot_ly(data = E1_plot2_Data(), +# # Select your variables. +# +# x = ~rate_per_1000_population, +# y = ~area_name, +# # fill = ~to_highlight, # highlighting Scotland but this is working with color and colors below +# marker = list(color = ~to_highlight), # This stops the colour legend appearing on the hover. Using color= and colors= below adds the legend +# # color = ~to_highlight, +# # colors = c("#0080FF", "seagreen"), # line colour - Dark blue for all lines. seagreen for test +# #text = tooltip_E1_plot2, # This and hoverinfo = "text" were showing the info when hovering AND permanently on the graph +# # hoverinfo = "text", +# hoverinfo = tooltip_E1_plot2, +# type = 'bar', +# orientation = 'h') %>% +# +# +# + #### Graph layout and titles ----- +# +# layout( +# margin = list(l=0, r=20, b=25, t=50, pad=3), # i only see a difference in the top and the padding, but this adds space around title, axis titles, padding is around graph itself (between axis and values) ("left, right, bottom, top, padding") +# +# title = paste0("", +# "Delayed Discharge Bed Days for the Financial Year: ", input$E1_plot2_year, +# "
", +# "
"), +# # title = list(standoff = 1), # tried lots of ways of doing this but nothing working +# #title = list(size = 12, y = 5, x = 0, xanchor = 'center', yanchor = 'top'), # none of this does anything to change things (no variation of any of them) +# +# separators = ".", +# +# yaxis = list(title =""), +# +# # Re: xasis, I wanted the axis range to be "0:whatever the highest value is across ALL +# # years" for every year's graph. Things I tried, that didn't work, included: +# # rangemode = "tozero" +# # tick0 = 0 +# # range = list(c(0, 300), round(max(E1_data$rate_per_1000_population), 10)), # ensures all graphs have the same range of 0-300 days but the graph wasn't starting at 0 (As bed days are going up each year, "round(...,10)" sets the xaxis as 10 more than whatever the new data shows as the maximum value) +# xaxis = list(title = "Number of Days", +# dtick = 10, # shows a marker for every 10th number of bed days +# # range = c(~min(c(-1, E1_data$rate_per_1000_population)), ~max(c(1, E1_data$rate_per_1000_population))), # I can't work out why this might be better when the below works too +# range = c(~min(0), ~max(c(1, E1_data$rate_per_1000_population))), +# autorange = FALSE), # if it were TRUE then the range would change for each graph +# +# +# font = list(size = 12), +# +# showlegend = FALSE) %>% +# + #### Remove unnecessary buttons from the modebar ---- +# +# config(displayModeBar = TRUE, +# modeBarButtonsToRemove = bttn_remove, +# displaylogo = F, editable = F) +# +# }) \ No newline at end of file diff --git a/modules/indicators/E1_ui.R b/modules/indicators/E1_ui.R index 5e55c2a..a21c98c 100644 --- a/modules/indicators/E1_ui.R +++ b/modules/indicators/E1_ui.R @@ -1,20 +1,278 @@ -tabItem(tabName = E1_tab, +### Beginning of E1 tab ---- + +tabItem(tabName = "E1_tab", fluidPage( - titlePanel(paste0( - "E1 - ")), - mainPanel( - h3("You are on E1"), - fluidRow( - column(4, actionButton(inputId = "E1_scot_hub_button", - label = "Scotland Hub", icon = icon("home"), - class = "navpageButton")), - column(4, actionButton(inputId = "P4_prevButton", - label = "Previous Page", icon = icon("arrow-left"), - class = "navpageButton")), - column(4, actionButton(inputId = "EF1_nextButton", - label = "Next Page", icon = icon("arrow-right"), - class = "navpageButton")) + tags$head( + tags$style( + type = "text/css", + + # Prevent error messages from popping up on the interface. + ".shiny-output-error { visibility: hidden; }", + ".shiny-output-error:before { visibility: hidden; }" + + ), + ), + ## Title for E1 tab ---- + h1(paste0( + "E1 - Delayed Discharges: Number of days people spend in hospital ", + "when they are clinically ready to be discharged (per 1,000 population)") + ), + + + hr(), # page break + + ## First Graph ---- + # Text above graph + fluidRow( + column(12, + box(width = NULL, + p(paste0( + "Below is a graph showing the total number of days spent ", + "in hospital when patients are ready to be discharged over time, ", + "broken down by either council area of residence or health board of treatment. ", + "Use the drop down menus to select which areas you wish to look at.")) + ) + ) + ), # End of fluidRow + + # Drop down menus + fluidRow( + column(6, + box(width = NULL, + uiOutput("E1_plot1_areaType_output")) + ), + column(6, + box(width = NULL, + uiOutput("E1_plot1_areaName_output")) + ), + ), # End of fluidRow + + # Graph 1 output + fluidRow( + box(width = 12, + phs_spinner("E1_plot1") + ) + ), + + hr(), # page break + + # fluidRow( + # column(12, + # box(width = NULL, + # p(paste0( + # "The first graph's data is presented in the table below.")) + # ) + # ) + # ), # End of fluidRow + # Table with graph 1 data + fluidRow( + box(title = "Below is a table showing the data used to create the above graph. + It can be downloaded using the 'Download as .csv' button underneath this section", + width = 12, solidHeader = TRUE, collapsible = TRUE, collapsed = FALSE, + dataTableOutput("E1_1_table") ) - ) - ) -) \ No newline at end of file + ), + + fluidRow( + column(4, + downloadButton(outputId = "E1_1_table_download", + label = "Download as .csv", + class = "E1_1_table_downloadbutton"), + tags$head( + tags$style(".E1_1_table_downloadbutton { background-color: + #3F3685; } + .E1_1_table_downloadbutton { color: #FFFFFF; }") + ) + ) + ), + + + hr(), # page break + + + ## Second Graph ---- + # Text above graph + fluidRow( + column(12, + box(width = NULL, + p(paste0( + "Below is a graph showing the total number of days, per 1,000 population, ", + "spent in hospital when patients are ready to be discharged over time, ", + "broken down by either council area of residence or health board of treatment. ", + "Use the drop down menus to select which areas you wish to look at.")) + ) + ) + ), # End of fluidRow + + # Year Drop down + fluidRow( + column(6, + box(width = NULL, + uiOutput("E1_plot2_year_output")) + ) + ), + # Graph 2 output + fluidRow( + box(width = 12, + phs_spinner("E1_plot2") + ) + ), + + hr(), # page break + + + # hr(), + # + # fluidRow( + # column(12, + # box(width = NULL, + # p(paste0( + # "The second graph's data is presented in the table below.")) + # ) + # ) + # ), # End of fluidRow + # Table with graph 2 data + fluidRow( + box(title = "Below is a table showing the data used to create the above graph. + It can be downloaded using the 'Download as .csv' button underneath this section", + width = 12, solidHeader = TRUE, collapsible = TRUE, collapsed = FALSE, + dataTableOutput("E1_2_table") + ) + ), + + fluidRow( + column(4, + downloadButton(outputId = "E1_2_table_download", + label = "Download as .csv", + class = "E1_2_table_downloadbutton"), + tags$head( + tags$style(".E1_2_table_downloadbutton { background-color: + #3F3685; } + .E1_2_table_downloadbutton { color: #FFFFFF; }") + ) + ) + ), + + + + # fluidRow( + # column(12, + # box(width = NULL, + # p(paste0( + # "The first graph's data is presented in the table below.")) + # ) + # ) + # ), # End of fluidRow + # # Table with graph 1 data + # fluidRow( + # box(width = 12, solidHeader = TRUE, collapsible = TRUE, + # dataTableOutput("E1_1_table") + # ) + # ), + # + # fluidRow( + # column(4, + # downloadButton(outputId = "E1_1_table_download", + # label = "Download as .csv", + # class = "E1_1_table_downloadbutton"), + # tags$head( + # tags$style(".E1_1_table_downloadbutton { background-color: + # #3F3685; } + # .E1_1_table_downloadbutton { color: #FFFFFF; }") + # ) + # ) + # ), + # + # hr(), + # + # fluidRow( + # column(12, + # box(width = NULL, + # p(paste0( + # "The second graph's data is presented in the table below.")) + # ) + # ) + # ), # End of fluidRow + # # Table with graph 2 data + # fluidRow( + # box(width = 12, solidHeader = TRUE, collapsible = TRUE, collapsed = TRUE, + # dataTableOutput("E1_2_table") + # ) + # ), + # + # fluidRow( + # column(4, + # downloadButton(outputId = "E1_2_table_download", + # label = "Download as .csv", + # class = "E1_2_table_downloadbutton"), + # tags$head( + # tags$style(".E1_2_table_downloadbutton { background-color: + # #3F3685; } + # .E1_2_table_downloadbutton { color: #FFFFFF; }") + # ) + # ) + # ), + + + + # mainPanel( + # tags$p("Below is a graph showing the changes over time."), + # + # fluidRow( + # column(6,uiOutput("E1_plot1_areaType_output")), + # column(6,uiOutput("E1_plot1_areaName_output")) + # ), + # + # fluidRow( + # plotlyOutput("E1_plot1" + # # , + # # width = "100%", + # # height = "50%" + # ) + # ), + # br(), + # # dataTableOutput("diagnoses_table"), + # br(), + # br(), + # + # + # tags$p("Below is a graph showing a comparison between health boards and NHS Scotland for your selected financial year."), + # # br(), + # + # fluidRow( + # column(6,uiOutput("E1_plot2_year_output")) + # ), + # + # fluidRow( + # plotlyOutput("E1_plot2" + # # , + # # width = "100%", + # # height = "50%" + # ) + # ), + # br(), + # tags$p("Source: Delayed discharges in NHS Scotland annual publication.", + # br(), + # "Data shown is for ages 18 years and above"), + # # as copied from above -- dataTableOutput("diagnoses_table"), + # br(), + # br(), + + br(), + + ## Navigation Buttons ---- + fluidRow( + column(4, actionButton(inputId = "E1_scot_hub_button", + label = "Scotland Hub", icon = icon("home"), + class = "navpageButton")), + column(4, actionButton(inputId = "P4_prevButton", + label = "Previous Page", icon = icon("arrow-left"), + class = "navpageButton")), + column(4, actionButton(inputId = "EF1_nextButton", + label = "Next Page", icon = icon("arrow-right"), + class = "navpageButton")) + ), + # Insert go to top button + go_2_top_bttn + ) + ) \ No newline at end of file diff --git a/modules/indicators/EF1_ui.R b/modules/indicators/EF1_ui.R index 702ab63..92050d0 100644 --- a/modules/indicators/EF1_ui.R +++ b/modules/indicators/EF1_ui.R @@ -1,7 +1,8 @@ -tabItem(tabName = EF1_tab, +tabItem(tabName = "EF1_tab", fluidPage( - titlePanel("EF1 - Rate of Emergency Bed Days for Adults"), - mainPanel( + h1("EF1 - Rate of Emergency Bed Days for Adults"), + fluidRow( + box(width = 9, img(src='infographics/EF1.png', class = "infographic", alt = paste0( @@ -10,14 +11,18 @@ tabItem(tabName = EF1_tab, "per 100,000 population in Scotland for the year-long period ", "ending 30 September 2021, compared to 19,078 per 100,000 ", "population for the year ending 30 September 2020.")), - br(), + ) + ), + fluidRow( + box(width = 9, p("The data for EF1 is sourced from ", a(href="https://www.nssdiscovery.scot.nhs.uk/", "Discovery"), " using SMR04 data.", a(href="https://publichealthscotland.scot/services/data-management/data-management-in-secondary-care-hospital-activity/scottish-morbidity-records-smr/completeness/", "Data completeness"), - " for SMR04 was around 90% or better when the data was accessed.") + " for SMR04 was around 90% or better when the data was accessed."), + ) ), fluidRow( @@ -30,6 +35,6 @@ tabItem(tabName = EF1_tab, column(4, actionButton(inputId = "EF2_nextButton", label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) - ) - ) # End of fluidPage -) \ No newline at end of file + ) + ) # End of fluidPage + ) diff --git a/modules/indicators/EF2_ui.R b/modules/indicators/EF2_ui.R index d66b28a..cfd820f 100644 --- a/modules/indicators/EF2_ui.R +++ b/modules/indicators/EF2_ui.R @@ -1,9 +1,32 @@ -tabItem(tabName = EF2_tab, +tabItem(tabName = "EF2_tab", fluidPage( - titlePanel("EF2"), - mainPanel( - h3("You are on EF2"), - fluidRow( + h1("EF2 - Readmissions to hospital within 28 days of discharge"), + fluidRow( + box(width = 9, + img(src='infographics/EF2.png', + class = c("infographic", "box"), + alt = paste0( + "The percentage of emergency readmissions within 28 days in ", + "Scotland was 7.3% for the year-long period ending 31 March ", + "2023. This compares with 7.8% for the year ending 31 March ", + "2022 and 9.3% for the year ending 31 March 2021.")) + + + ), + ), + fluidRow( + box(width = 9, + p("The data for EF1 is sourced from ", + a(href="https://www.nssdiscovery.scot.nhs.uk/", + "Discovery"), + " using SMR04 data.", + a(href="https://publichealthscotland.scot/services/data-management/data-management-in-secondary-care-hospital-activity/scottish-morbidity-records-smr/completeness/", + "Data completeness"), + " for SMR04 was around 90% or better when the data was accessed.") + ) + ), + + fluidRow( column(4, actionButton(inputId = "EF2_scot_hub_button", label = "Scotland Hub", icon = icon("home"), class = "navpageButton")), @@ -13,7 +36,6 @@ tabItem(tabName = EF2_tab, column(4, actionButton(inputId = "EF3_nextButton", label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) - ) - ) - ) -) \ No newline at end of file + ) # End of fluidRow + ) # End of fluidPage +) # End of tabItem \ No newline at end of file diff --git a/modules/indicators/EF3_ui.R b/modules/indicators/EF3_ui.R index 695d861..14f0750 100644 --- a/modules/indicators/EF3_ui.R +++ b/modules/indicators/EF3_ui.R @@ -1,9 +1,31 @@ -tabItem(tabName = EF3_tab, +tabItem(tabName = "EF3_tab", fluidPage( - titlePanel("EF3"), - mainPanel( - h3("You are on EF3"), - fluidRow( + h1("EF3 - Total psychiatric inpatient beds per 100,000 population (NRAC adjusted)"), + fluidRow( + box(width = 9, + img(src='infographics/EF3.png', + class = "infographic", + alt = paste0( + "The total number of average available staffed beds per day ", + "for all psychiatric specialties in 2022/23 in Scotland was ", + "3,679 beds (i.e. 66.8 psychiatric beds per 100,000 ", + "population). This is a decrease from 67.5 beds per 100,000 ", + "population in 2021/22 and 68.8 beds per 100,000 population ", + "in 2020/21.")), + ) + ), + fluidRow( + box(width = 9, + p("The numerator for EF3 is sourced from ", + a(href="https://publichealthscotland.scot/publications/acute-hospital-activity-and-nhs-beds-information-annual/", + "the Acute hospital activity and NHS beds information annual release publication, "), + "and the denominator is sourced from ", + a(href="https://www.publichealthscotland.scot/publications/resource-allocation-formula-nrac/resource-allocation-formula-nrac-for-nhsscotland-results-for-financial-year-2024-to-2025/", + "the National Resource Allocation publication.")), + ) + ), + + fluidRow( column(4, actionButton(inputId = "EF3_scot_hub_button", label = "Scotland Hub", icon = icon("home"), class = "navpageButton")), @@ -14,6 +36,6 @@ tabItem(tabName = EF3_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) - ) -) \ No newline at end of file + ) # End of fluidPage + ) + diff --git a/modules/indicators/EF4_server.R b/modules/indicators/EF4_server.R new file mode 100644 index 0000000..9ee718c --- /dev/null +++ b/modules/indicators/EF4_server.R @@ -0,0 +1,271 @@ +### EF4 Trends Plot ---- + +## Health Board selector ---- +output$EF4_trendPlot_hbName_output <- renderUI({ + shinyWidgets::pickerInput( + "EF4_trendPlot_hbName", + label = "Select NHS Health Board:", + choices = EF4_hb_names, + selected = "NHS Scotland") +}) + +## Measure selector ---- +output$EF4_trendPlot_measure_output <- renderUI({ + shinyWidgets::pickerInput( + "EF4_trendPlot_measure", + label = "Select measure(s):", + choices = EF4_trend_measures, + selected = "Mental Health Expenditure (%)", + multiple = TRUE) +}) + +## Graph Data Reactive ---- +# to create graph data based on HB and Measure selection +EF4_trendPlot_data <- reactive({ + EF4_data %>% + filter(hb_name %in% input$EF4_trendPlot_hbName & + measure %in% input$EF4_trendPlot_measure) +}) + + + +# Create the EF4 line chart ---- + + ### Render plotly ---- + + output$EF4_trendPlot <- renderPlotly({ + + ### Create reactive ggplot graph ---- + + EF4_plot_graph <- reactive ({ + + ggplot(data = EF4_trendPlot_data(), + aes(x = fyear, + y = value, + text = paste0("Financial year: ", # for tooltip in ggplotly - shows values on hover + EF4_trendPlot_data()$fyear, + "
", + "Health Board: ", + EF4_trendPlot_data()$hb_name, + "
", + EF4_trendPlot_data()$measure,": ", + EF4_trendPlot_data()$value))) + + geom_line() + + geom_point(size = 2.5) + + aes(group = measure, # Have to do this outside so that the legends shows and so that there aren't 3 legends + linetype = measure, + color = measure, + shape = measure) + + scale_color_discrete_phs(name = "Measure Name", + palette = "main-blues", + labels = ~ stringr::str_wrap(.x, width = 15)) + + # scale_color_manual(name = "Measure Name", + # values = c("#0078D4", "#3393DD"), # colour for lines + # labels = ~ stringr::str_wrap(.x, width = 15)) + + scale_linetype_manual(name = "Measure Name", # have to add it into each one or the legend duplicates + values = c("solid", "dashed"), + labels = ~ stringr::str_wrap(.x, width = 15)) + + scale_shape_manual(name = "Measure Name", + values = c("circle", "triangle-up"), # shape for points + labels = ~ stringr::str_wrap(.x, width = 15)) + + theme_classic()+ + theme(panel.grid.major.x = element_line(), # Shows vertical grid lines + panel.grid.major.y = element_line(), # Shows horizontal grid lines + axis.title.x = element_text(size = 12, + color = "black", + face = "bold"), + axis.title.y = element_text(size = 12, + color = "black", + face = "bold"), + legend.text = element_text(size = 8, + colour = "black"), + legend.title = element_text(size = 9, + colour = "black", + face = "bold")) + + labs(x = "Financial Year", + y = "Percentage (%)") + + scale_y_continuous(expand = c(0, 0), # y axis will always start from zero + limits = c(0, (max(EF4_trendPlot_data()$value) + + 0.5*max(EF4_trendPlot_data()$value)))) # maximum y axis value should always show + + }) + + + ### Run ggplot graph through plotly ---- + + ggplotly(EF4_plot_graph(), + tooltip = "text") # uses text set up in ggplot aes above. + + }) + + + + ### Table below graph ---- + + output$EF4_table <- renderDataTable({ + datatable(EF4_trendPlot_data(), + style = 'bootstrap', + class = 'table-bordered table-condensed', + rownames = FALSE, + options = list(pageLength = 16, autoWidth = TRUE, dom = 'tip'), + colnames = c("Financial year", + "Health Board", + "Measure Name", + "Value")) + }) + + # Create download button that allows users to download tables in .csv format. + output$EF4_table_download <- downloadHandler( + filename = 'EF4 - Mental health spend.csv', + content = function(file) { + write.table(EF4_trendPlot_data(), + file, + #Remove row numbers as the .csv file already has row numbers. + row.names = FALSE, + col.names = c("Financial year", + "Health Board", + "Measure Name", + "Value"), + sep = ",") + } + ) + + + +# X OLD CODE ---- +# +# ## plotly bar chart ---- +# output$EF4_trendPlot <- renderPlotly({ +# # +# # # # No data plot +# # # if(sum(EF4_trendPlot_data()$value) == 0 & +# # # !is.na(sum(EF4_trendPlot_data()$value))) +# # # +# # # { +# # # noDataPlot(phs_colours("phs-purple")) +# # # } +# # # +# # # else { +# # +# ### Tooltip creation ---- +# tooltip_EF4 <- paste0("Financial year: ", +# EF4_trendPlot_data()$fyear, +# "
", +# "Health Board: ", +# EF4_trendPlot_data()$hb_name, +# "
", +# EF4_trendPlot_data()$measure,": ", +# EF4_trendPlot_data()$value) +# +# ## Create the main body of the chart ---- +# +# # phs_scatterPlot(EF4_trendPlot_data, fyear, value, tooltip_EF4, measure) +# +# plot_ly(data = EF4_trendPlot_data(), +# # Select your variables. +# x = ~fyear, y = ~value, color = ~measure, +# text = tooltip_EF4, hoverinfo = "text", +# colors = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), # line colours +# type = 'scatter', mode = 'lines+markers', +# # width = 600, height = 300, +# line = list(width = 2), +# linetype = ~measure, +# linetypes = c("solid", "dash"), +# marker = list(size = 8), +# name = ~str_wrap(measure, 19)) %>% # legend labels +# +# # data = EF4_trendPlot_data(), +# # # Select your variables. +# # x = ~fyear, y = ~value, +# # text = tooltip_EF4, hoverinfo = "text", +# # color = ~measure, +# # colors = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), # line colours +# # type = 'scatter', mode = 'lines+markers', +# # # width = 600, height = 300, +# # line = list(width = 2), +# # linetype = ~measure, +# # linetypes = c("solid", "dash"), +# # marker = list(size = 8), +# # name = ~str_wrap(measure, 19)) %>% # legend labels +# +# ### 7 - Graph title ---- +# layout(title = +# paste0( +# "", +# "Percent (%) of total NHS spend in ", +# input$EF4_trendPlot_hbName_output, ",", +# "
", +# first(as.vector(EF4_trendPlot_data()$fyear)), +# " to ", +# last(as.vector(EF4_trendPlot_data()$fyear)), +# "
", +# "
" +# ), +# +# separators = ".", +# +# yaxis = list( +# exponentformat = "none", +# separatethousands = TRUE, +# range = c(0, max(EF4_trendPlot_data()$value, na.rm = TRUE) +# + (max(EF4_trendPlot_data()$value, na.rm = TRUE)*0.1) +# ), +# # Define Y axis title +# title = paste0(c(rep(" ", 20), +# "Percent", +# rep(" ", 20), +# rep("\n ", 3))), +# showline = TRUE, +# ticks = "outside" +# ), +# +# xaxis = list( +# title = paste0(c("
", "Financial year")), +# showline = TRUE, +# ticks = "outside" +# ), +# +# margin = list(l = 90, r = 60, b = 180, t = 120), +# title = list(size = 15), +# font = list(size = 13), +# # Legend +# showlegend = TRUE, +# legend = list(x = 1, +# y = 1, +# bgcolor = 'rgba(255, 255, 255, 0)', +# bordercolor = 'rgba(255, 255, 255, 0)') +# # legend = list(orientation = "h", # show entries horizontally +# # xanchor = "center", # use center of legend as anchor +# # x = 0.5, y = -0.9) # put legend in center of x-axis +# ) %>% +# +# ### Remove unnecessary buttons from the modebar ---- +# +# config(displayModeBar = TRUE, +# modeBarButtonsToRemove = bttn_remove, +# displaylogo = F, editable = F) +# +# # } +# +# }) +# +# +# ### Table below graph ---- +# +# # output$EF4_1_trend_table <- renderDataTable({ +# # datatable(EF4_trendPlot_data(), +# # style = 'bootstrap', +# # class = 'table-bordered table-condensed', +# # rownames = FALSE, +# # options = list(pageLength = 16, autoWidth = TRUE, dom = 'tip'), +# # colnames = c("Financial year", +# # "Area of Residence", +# # "Number of Bed Days")) +# # }) +# +# +# + + + + diff --git a/modules/indicators/EF4_ui.R b/modules/indicators/EF4_ui.R index 4da7d8d..4f1dff4 100644 --- a/modules/indicators/EF4_ui.R +++ b/modules/indicators/EF4_ui.R @@ -1,9 +1,81 @@ -tabItem(tabName = EF4_tab, +tabItem(tabName = "EF4_tab", fluidPage( - titlePanel("EF4"), - mainPanel( - h3("You are on EF4"), - fluidRow( + # Defining the title + h1("EF4 - Total mental health spend as a % of total spend"), + + hr(), # page break + + ## Text Above Graph ---- + fluidRow( + column(12, + box(width = NULL, + p(paste0( + "Below is a graph showing the percentage (%) of your selected ", + "NHS Health Board's total spend that is attributable to total mental ", + "health spend for each financial year. ", + "Use the drop down menus to select which Health Board and ", + "measure(s) you wish to look at.")) + ) + )), # end of fluidRow + ## Drop down menus ---- + fluidRow( + column(6, + box(width = NULL, + uiOutput("EF4_trendPlot_hbName_output")) + ), + column(6, + box(width = NULL, + uiOutput("EF4_trendPlot_measure_output")) + ), + ), + + ## Graph output ---- + fluidRow( + box(width = 12, + plotlyOutput("EF4_trendPlot", + # height = "50vh", + width = "100%")) + ), + hr(), # page break + + fluidRow( + box(title = "Below is a table showing the data used to create the above graph. + It can be downloaded using the 'Download as .csv' button underneath this section", + width = 12, solidHeader = TRUE, collapsible = TRUE, collapsed = FALSE, + dataTableOutput("EF4_table") + ) + ), + fluidRow( + column(4, + downloadButton(outputId = "EF4_table_download", + label = "Download as .csv", + class = "EF4_table_downloadbutton"), + tags$head( + tags$style(".EF4_table_downloadbutton { background-color: + #3F3685; } + .EF4_table_downloadbutton { color: #FFFFFF; }") + ) + ) + ), + + + hr(), # page break + + + fluidRow( + column(12, + box(width = NULL, + p("These data are sourced from data collected annually by Public Health Scotland (PHS) on expenditure within NHS Scotland, released in an ", + a(href="https://publichealthscotland.scot/media/17844/nhsscotland-mental-health-expenditure.xlsx", + "excel workbook "), + "which also includes data for organisations providing these services (14 territorial NHS Boards and the State Hospital at Carstairs Lanarkshire), as part of the ", + a(href="https://publichealthscotland.scot/publications/scottish-health-service-costs/scottish-health-service-costs-high-level-costs-summary-2021-to-2022/", + "annual release of National Statistics covering expenditure in the financial year 2021/22."))) + ), + + ), + + fluidRow( column(4, actionButton(inputId = "EF4_scot_hub_button", label = "Scotland Hub", icon = icon("home"), class = "navpageButton")), @@ -14,6 +86,6 @@ tabItem(tabName = EF4_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) - ) -) \ No newline at end of file + ) # End of fluidPage +) + \ No newline at end of file diff --git a/modules/indicators/EF5_ui.R b/modules/indicators/EF5_ui.R index 82bbb57..3db532c 100644 --- a/modules/indicators/EF5_ui.R +++ b/modules/indicators/EF5_ui.R @@ -1,9 +1,28 @@ -tabItem(tabName = EF5_tab, +tabItem(tabName = "EF5_tab", fluidPage( - titlePanel("EF5"), - mainPanel( - h3("You are on EF5"), - fluidRow( + h1("EF5 - % of did not attend appointments for community based services of people with mental health problems"), + fluidRow( + box(width = 9, + img(src='infographics/EF5.png', + #width = 250, height = 200, + class = "infographic", + alt = paste0( + "The percentage of people who did not attend their ", + "appointment for mental health problems at community based ", + "services ranged from 8% to 19% for the quarter ending 30 ", + "June 2023.")), + ), + # box(width = 3, + # p("The data for EF5 is sourced is sourced from health board returns, which may be incomplete."), + # ), + ), + + fluidRow( + box(width = 9, + p("The data for EF5 is sourced is sourced from health board returns, which may be incomplete."), + ), + ), + fluidRow( column(4, actionButton(inputId = "EF5_scot_hub_button", label = "Scotland Hub", icon = icon("home"), class = "navpageButton")), @@ -14,6 +33,5 @@ tabItem(tabName = EF5_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) + ) # End of fluidPage ) -) \ No newline at end of file diff --git a/modules/indicators/EQ1_server.R b/modules/indicators/EQ1_server.R new file mode 100644 index 0000000..389572e --- /dev/null +++ b/modules/indicators/EQ1_server.R @@ -0,0 +1,831 @@ +# PLOT 1 ---- + +## Picker for selecting HB or CA ---- + +output$EQ1_plot1_areaType_output <- renderUI({ + shinyWidgets::pickerInput( + "EQ1_plot1_areaType", + label = "Select type of geography:", + choices = unique_area_types, + selected = "Health board" + ) +}) + +## Picker for user selecting specific geographies ---- + +output$EQ1_plot1_areaName_output <- renderUI({ + shinyWidgets::pickerInput( + "EQ1_plot1_areaName", + label = "Select area(s) (Maximum 4):", + choices = sort(unique(as.character( + EQ1_data$area_name + [EQ1_data$area_type %in% input$EQ1_plot1_areaType] + ))) + , + multiple = TRUE, + options = list( + "max-options" = 4, + `selected-text-format` = "count > 1" + ), + selected = "NHS Ayrshire and Arran" + ) +}) + +## Selecting appropriate data for graph 1 ---- + +EQ1_plot1_Data <- reactive({ + EQ1_data %>% + select(Year, + area_type, + area_name, + risk_ratio, + SMR04_Pop_Rate, + General_Pop_Rate) %>% + mutate(risk_ratio = round(risk_ratio, 2)) %>% # because values are e.g., "5.239755" + filter(area_type %in% input$EQ1_plot1_areaType + & area_name %in% input$EQ1_plot1_areaName) +}) + + +# Create the risk ratios line chart ---- + +### Render Plotly ---- + +output$EQ1_plot1 <- renderPlotly({ + ### Create reactive ggplot graph ---- + + EQ1_plot1_graph <- reactive({ + ggplot(data = EQ1_plot1_Data(), + aes( + x = Year, + y = risk_ratio, + text = paste0( + "Financial year: ", + # for tooltip in ggplotly - shows values on hover + EQ1_plot1_Data()$Year, + "
", + "Area of residence: ", + EQ1_plot1_Data()$area_name, + "
", + "Mortality rate: ", + EQ1_plot1_Data()$risk_ratio + ) + )) + + geom_line() + + geom_point(size = 2.5) + + aes( + group = area_name, + linetype = area_name, + # Have to do this outside so that the legends shows and so that there aren't 3 legends + color = area_name, + shape = area_name + ) + + scale_color_discrete_phs( + name = "Area name", + palette = "main-blues", + labels = ~ stringr::str_wrap(.x, width = 15) + ) + + # scale_color_manual(name = "Area name:", + # values = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), # MS 27/09 - keeping this in for now - until spoken about phsstyles + # labels = ~ stringr::str_wrap(.x, width = 15)) + + scale_linetype_manual( + name = "Area name", + values = c("solid", "dashed", "solid", "dashed"), + labels = ~ stringr::str_wrap(.x, width = 15) + ) + + scale_shape_manual( + name = "Area name", + values = c("circle", "circle", "triangle-up", "triangle-up"), + labels = ~ stringr::str_wrap(.x, width = 15) + ) + + theme_classic() + # de-clutters graph background + theme( + panel.grid.major.x = element_line(), + # Shows vertical grid lines + panel.grid.major.y = element_line(), + # Shows horizontal grid lines + axis.title.x = element_text( + size = 12, + color = "black", + face = "bold" + ), + axis.title.y = element_text( + size = 12, + color = "black", + face = "bold" + ), + legend.text = element_text(size = 8, + colour = "black"), + legend.title = element_text( + size = 9, + colour = "black", + face = "bold" + ) + ) + + labs(x = "Year", + y = "Mortality Rate") + + scale_y_continuous(expand = c(0, 0), # Ensures y axis starts from zero + limits = c(0, ( + max(EQ1_plot1_Data()$risk_ratio) + 0.5 * max(EQ1_plot1_Data()$risk_ratio) + ))) + }) + + + ### Run graph 1 through plotly ---- + + ggplotly(EQ1_plot1_graph(), + tooltip = "text")#, # uses text set up in ggplot aes above. + # ### Remove unnecessary buttons from the modebar ---- not working just now + # config(displayModeBar = TRUE, # Remove unnecessary buttons from the modebar + # modeBarButtonsToRemove = bttn_remove, + # displaylogo = F, editable = F)) + +}) + + + +# EQ1 PLOT 2 ---- + +## Picker for user selecting HB or CA ---- + +output$EQ1_plot4_areaType_output <- renderUI({ + shinyWidgets::pickerInput( + "EQ1_plot4_areaType", + label = "Select type of geography:", + choices = unique_area_types, + selected = "Health board" + ) +}) + +## Picker for user selecting specific geographies ---- +output$EQ1_plot4_areaName_output <- renderUI({ + shinyWidgets::pickerInput( + "EQ1_plot4_areaName", + label = "Select area:", + choices = sort(unique( + as.character(EQ1_reformatted_data$area_name + [EQ1_reformatted_data$area_type %in% input$EQ1_plot4_areaType]) + )), + multiple = TRUE, + options = list( + "max-options" = 1, + `selected-text-format` = "count > 1" + ), + selected = "NHS Ayrshire and Arran" + ) +}) + + +## Selecting appropriate data for graph 2 ---- + +EQ1_plot4_Data <- reactive({ + EQ1_reformatted_data %>% + select(Rate_Type, Year, area_type, area_name, Rate) %>% + filter(area_type %in% input$EQ1_plot4_areaType + & area_name %in% input$EQ1_plot4_areaName) +}) + + +# Create the combined general population and MH rates bar chart ---- + +### Render plotly ---- + +output$EQ1_plot4 <- renderPlotly({ + ### Create reactive ggplot bar graph ---- + + EQ1_plot4_graph <- reactive({ + ggplot(data = EQ1_plot4_Data(), + aes( + x = Year, + y = Rate, + fill = Rate_Type, + # colours defined below + text = paste0( + "Financial year: ", + EQ1_plot4_Data()$Year, + "
", + "Area of residence: ", + EQ1_plot4_Data()$area_name, + "
", + "Rate Type: ", + EQ1_plot4_Data()$Rate_Type, + "
", + "Rate: ", + EQ1_plot4_Data()$Rate + ) + )) + + geom_bar(stat = "identity", position = "dodge") + # creates bar graph with bars separated from each other + #scale_fill_manual(values = c("#0078D4", "#B3D7F2")) + # MS 27/09 - keep until phsstyles have been spoken about + scale_fill_manual(values = phs_colours(c("phs-blue", "phs-blue-50"))) + + theme_classic() + + theme( + #legend.position = "bottom", # WHY ISN'T THIS WORKING? + panel.grid.major.x = element_line(), + # Shows vertical grid lines + panel.grid.major.y = element_line(), + # Shows horizontal grid lines + axis.title.x = element_text( + size = 12, + color = "black", + face = "bold" + ), + axis.title.y = element_text( + size = 12, + color = "black", + face = "bold" + ) + ) + + labs(x = "Year", + y = "Mortality Rate", + fill = "Population Group:") + + scale_y_continuous(expand = c(0, 0), # Ensures y axis starts from zero + limits = c(0, ( + max(EQ1_plot4_Data()$Rate) + 0.5 * max(EQ1_plot4_Data()$Rate) + ))) + + }) + + + ### Run graph 2 through plotly ---- + + ggplotly(EQ1_plot4_graph(), + tooltip = "text")#, # uses text set up in ggplot aes above. + # ### Remove unnecessary buttons from the modebar ---- not working but will make work + # config(displayModeBar = TRUE, + # modeBarButtonsToRemove = bttn_remove, + # displaylogo = F, editable = F)) + +}) + + +### Tables below graphs ---- +# Year, area_type, area_name, risk_ratio, SMR04_Pop_Rate, General_Pop_Rate +output$EQ1_1_table <- renderDataTable({ + datatable( + EQ1_plot1_Data(), + style = 'bootstrap', + class = 'table-bordered table-condensed', + rownames = FALSE, + options = list( + pageLength = 16, + autoWidth = TRUE, + dom = 'tip' + ), + colnames = c( + "Financial year", + "Area Type", + "Area Name", + "Risk ratio", + "SMR04 population rate", + "General population rate" + ) + ) +}) +#Rate_Type, Year, area_type, area_name, Rate +output$EQ1_2_table <- renderDataTable({ + datatable( + EQ1_plot4_Data(), + style = 'bootstrap', + class = 'table-bordered table-condensed', + rownames = FALSE, + options = list( + pageLength = 16, + autoWidth = TRUE, + dom = 'tip' + ), + colnames = c("Rate type", + "Financial year", + "Area Type", + "Area Name", + "Rate") + ) +}) + + +# Create download buttons that allows users to the download tables in .csv format. +output$EQ1_1_table_download <- downloadHandler( + filename = 'EQ1 - Mortality rate risk ratio trends.csv', + content = function(file) { + write.table( + EQ1_plot1_Data(), + file, + #Remove row numbers as the .csv file already has row numbers. + row.names = FALSE, + col.names = c( + "Financial year", + "Area Type", + "Area Name", + "Risk ratio", + "SMR04 population rate", + "General population rate" + ), + sep = "," + ) + } +) + +output$EQ1_2_table_download <- downloadHandler( + filename = paste0("EQ1 - Mortality rate trend for chosen area.csv"), + content = function(file) { + write.table( + EQ1_plot4_Data(), + file, + #Remove row numbers as the .csv file already has row numbers. + row.names = FALSE, + col.names = c("Rate type", + "Financial year", + "Area Type", + "Area Name", + "Rate"), + sep = "," + ) + } +) + + +# Table below graph creation ---- + +# output$E1_1_trend_table <- renderDataTable({ +# datatable(E1_plot1_Data(), +# style = 'bootstrap', +# class = 'table-bordered table-condensed', +# rownames = FALSE, +# options = list(pageLength = 16, autoWidth = TRUE, dom = 'tip'), +# colnames = c("Financial year", +# "Area of Residence", +# "Number of Bed Days")) +# }) + + + + + + +# OLD CODE (keeping in case needed for reference) ---- +# +# # +# # +# # # +# # # # # No data plot +# # # # if(sum(E1_plot1_Data()$dd_bed_days) == 0 & +# # # # !is.na(sum(E1_plot1_Data()$dd_bed_days))) +# # # # +# # # # { +# # # # noDataPlot(phs_colours("phs-purple")) +# # # # } +# # # # +# # # # else { +# # # +# # ### 3 - Tooltip creation ---- +# # +# # tooltip_EQ1 <- paste0("Financial year: ", +# # EQ1_plot1_Data()$Year, +# # "
", +# # "Area of residence: ", +# # EQ1_plot1_Data()$area_name, +# # "
", +# # "Mortality rate: ", +# # EQ1_plot1_Data()$risk_ratio) +# # +# # ### 4 - Create the main body of the chart ---- +# # +# # plot_ly(data = EQ1_plot1_Data(), +# # # Select your variables. +# # x = ~as.factor(Year), y = ~risk_ratio, color = ~area_name, +# # colors = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), +# # text = tooltip_EQ1, hoverinfo = "text", +# # type = 'scatter', mode = 'lines+markers', +# # # width = 600, height = 300, +# # line = list(width = 3), +# # linetype = ~area_name, +# # linetypes = c("solid", "dot"), +# # # Select symbols for the health boards, and set their size. +# # symbol = ~area_name, +# # symbols = c("circle", "triangle-up", "circle", "triangle-up"), +# # marker = list(size = 12), +# # name = ~str_wrap(area_name, 19)) %>% # legend labels +# # +# # ### 7 - Graph title ---- +# # +# # # Make the graph title reactive. +# # +# # layout(title = +# # paste0( +# # "", +# # "Mortality rate for persons in contact with MH services", +# # "
", +# # " by ", input$EQ1_plot1_areaType, ", ", first(as.vector(EQ1_plot1_Data()$Year)), +# # " to ", +# # last(as.vector(EQ1_plot1_Data()$Year)), +# # "
", +# # "
" +# # ), +# # +# # separators = ".", +# # +# # yaxis = list( +# # exponentformat = "none", +# # separatethousands = TRUE, +# # range = c(0, max(EQ1_plot1_Data()$risk_ratio, na.rm = TRUE) +# # + (max(EQ1_plot1_Data()$risk_ratio, na.rm = TRUE)*0.1) +# # ), +# # title = paste0(c(rep(" ", 20), +# # input$EQ1_1_input_1, +# # rep(" ", 20), +# # rep("\n ", 3))), +# # showline = TRUE, +# # ticks = "outside" +# # ), +# # +# # xaxis = list( +# # title = paste0(c("
", +# # "Calendar year", +# # collapse = "")), # Don't think it's needed +# # showline = TRUE, +# # ticks = "outside" +# # ), +# # +# # margin = list(l = 90, r = 60, b = 180, t = 120), +# # title = list(size = 15), +# # font = list(size = 13), +# # # Legend +# # showlegend = TRUE, +# # legend = list(x = 1, +# # y = 1, +# # bgcolor = 'rgba(255, 255, 255, 0)', +# # bordercolor = 'rgba(255, 255, 255, 0)') +# # # legend = list(orientation = "h", # show entries horizontally +# # # xanchor = "center", # use center of legend as anchor +# # # x = 0.5, y = -0.9) # put legend in center of x-axis +# # ) %>% +# # +# # ### 13 - Remove unnecessary buttons from the modebar ---- +# # +# # config(displayModeBar = TRUE, +# # modeBarButtonsToRemove = bttn_remove, +# # displaylogo = F, editable = F) +# # +# # # } +# # +# # }) +# +# +# # +# # +# # ####### Create the SMR04 rates bar chart. +# # +# # output$EQ1_plot2 <- renderPlotly({ +# # # +# # # # # No data plot +# # # # if(sum(E1_plot1_Data()$dd_bed_days) == 0 & +# # # # !is.na(sum(E1_plot1_Data()$dd_bed_days))) +# # # # +# # # # { +# # # # noDataPlot(phs_colours("phs-purple")) +# # # # } +# # # # +# # # # else { +# # # +# # ### 3 - Tooltip creation ---- +# # +# # tooltip_EQ1_2 <- paste0("Financial year: ", +# # EQ1_plot1_Data()$Year, +# # "
", +# # "Area of residence: ", +# # EQ1_plot1_Data()$area_name, +# # "
", +# # "Mortality rate: ", +# # EQ1_plot1_Data()$SMR04_Pop_Rate) +# # +# # ### 4 - Create the main body of the chart ---- +# # +# # plot_ly(data = EQ1_plot1_Data(), +# # # Select your variables. +# # x = ~Year, y = ~SMR04_Pop_Rate, type = 'bar', color = ~area_name, +# # #add_trace(p = data, y = ~General_Pop_Rate), +# # colors = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), +# # text = tooltip_EQ1_2, hoverinfo = "text", +# # marker = list(size = 12), +# # name = ~str_wrap(area_name, 19)) %>% # legend labels +# # +# # ### 7 - Graph title ---- +# # +# # # Make the graph title reactive. +# # +# # layout(title = +# # paste0( +# # "", +# # "Mortality rate for persons in contact with MH services", +# # "
", +# # " by ", input$EQ1_plot1_areaType, ", ", first(as.vector(EQ1_plot1_Data()$Year)), +# # " to ", +# # last(as.vector(EQ1_plot1_Data()$Year)), +# # "
", +# # "
" +# # ), +# # +# # separators = ".", +# # +# # yaxis = list( +# # exponentformat = "none", +# # separatethousands = TRUE, +# # range = c(0, max(EQ1_plot1_Data()$SMR04_Pop_Rate, na.rm = TRUE) +# # + (max(EQ1_plot1_Data()$SMR04_Pop_Rate, na.rm = TRUE)*0.1) +# # ), +# # title = paste0(c(rep(" ", 20), +# # input$EQ1_1_input_1, +# # rep(" ", 20), +# # rep("\n ", 3))), +# # showline = TRUE, +# # ticks = "outside" +# # ), +# # +# # xaxis = list( +# # title = paste0(c("
", +# # "Area name", +# # collapse = "")), # Don't think it's needed +# # showline = TRUE, +# # ticks = "outside" +# # ), +# # +# # margin = list(l = 90, r = 60, b = 180, t = 120), +# # title = list(size = 15), +# # font = list(size = 13), +# # # Legend +# # showlegend = TRUE, +# # legend = list(x = 1, +# # y = 1, +# # bgcolor = 'rgba(255, 255, 255, 0)', +# # bordercolor = 'rgba(255, 255, 255, 0)') +# # # legend = list(orientation = "h", # show entries horizontally +# # # xanchor = "center", # use center of legend as anchor +# # # x = 0.5, y = -0.9) # put legend in center of x-axis +# # ) %>% +# # +# # ### 13 - Remove unnecessary buttons from the modebar ---- +# # +# # config(displayModeBar = TRUE, +# # modeBarButtonsToRemove = bttn_remove, +# # displaylogo = F, editable = F) +# # +# # # } +# # +# # }) +# # +# # +# # +# # +# # ####### Create the general population rates bar chart. +# # +# # output$EQ1_plot3 <- renderPlotly({ +# # # +# # # # # No data plot +# # # # if(sum(E1_plot1_Data()$dd_bed_days) == 0 & +# # # # !is.na(sum(E1_plot1_Data()$dd_bed_days))) +# # # # +# # # # { +# # # # noDataPlot(phs_colours("phs-purple")) +# # # # } +# # # # +# # # # else { +# # # +# # ### 3 - Tooltip creation ---- +# # +# # tooltip_EQ1_3 <- paste0("Financial year: ", +# # EQ1_plot1_Data()$Year, +# # "
", +# # "Area of residence: ", +# # EQ1_plot1_Data()$area_name, +# # "
", +# # "Mortality rate: ", +# # EQ1_plot1_Data()$General_Pop_Rate) +# # +# # ### 4 - Create the main body of the chart ---- +# # +# # plot_ly(data = EQ1_plot1_Data(), +# # # Select your variables. +# # x = ~Year, y = ~General_Pop_Rate, type = 'bar', color = ~area_name, +# # #add_trace(p = data, y = ~General_Pop_Rate), +# # colors = c("#0078D4", "#3393DD", "#80BCEA", "#B3D7F2"), +# # text = tooltip_EQ1_3, hoverinfo = "text", +# # marker = list(size = 12), +# # name = ~str_wrap(area_name, 19)) %>% # legend labels +# # +# # ### 7 - Graph title ---- +# # +# # # Make the graph title reactive. +# # +# # layout(title = +# # paste0( +# # "", +# # "Mortality rate for the general population", +# # "
", +# # " by ", input$EQ1_plot1_areaType, ", ", first(as.vector(EQ1_plot1_Data()$Year)), +# # " to ", +# # last(as.vector(EQ1_plot1_Data()$Year)), +# # "
", +# # "
" +# # ), +# # +# # separators = ".", +# # +# # yaxis = list( +# # exponentformat = "none", +# # separatethousands = TRUE, +# # range = c(0, max(EQ1_plot1_Data()$General_Pop_Rate, na.rm = TRUE) +# # + (max(EQ1_plot1_Data()$General_Pop_Rate, na.rm = TRUE)*0.1) +# # ), +# # title = paste0(c(rep(" ", 20), +# # input$EQ1_1_input_1, +# # rep(" ", 20), +# # rep("\n ", 3))), +# # showline = TRUE, +# # ticks = "outside" +# # ), +# # +# # xaxis = list( +# # title = paste0(c("
", +# # "Area name", +# # collapse = "")), # Don't think it's needed +# # showline = TRUE, +# # ticks = "outside" +# # ), +# # +# # margin = list(l = 90, r = 60, b = 180, t = 120), +# # title = list(size = 15), +# # font = list(size = 13), +# # # Legend +# # showlegend = TRUE, +# # legend = list(x = 1, +# # y = 1, +# # bgcolor = 'rgba(255, 255, 255, 0)', +# # bordercolor = 'rgba(255, 255, 255, 0)') +# # # legend = list(orientation = "h", # show entries horizontally +# # # xanchor = "center", # use center of legend as anchor +# # # x = 0.5, y = -0.9) # put legend in center of x-axis +# # ) %>% +# # +# # ### 13 - Remove unnecessary buttons from the modebar ---- +# # +# # config(displayModeBar = TRUE, +# # modeBarButtonsToRemove = bttn_remove, +# # displaylogo = F, editable = F) +# # +# # # } +# # +# # }) +# # +# # +# +# +# +# +# output$EQ1_plot4_areaType_output <- renderUI({ +# shinyWidgets::pickerInput( +# "EQ1_plot4_areaType", +# label = "Select type of geography:", +# choices = unique_area_types, +# selected = "Health board") +# }) +# +# output$EQ1_plot4_areaName_output <- renderUI({ +# shinyWidgets::pickerInput( +# "EQ1_plot4_areaName", +# label = "Select area:", +# choices = sort(unique(as.character( +# EQ1_reformatted_data$area_name +# [EQ1_reformatted_data$area_type %in% input$EQ1_plot4_areaType] +# ))) +# , +# multiple = TRUE, +# options = list("max-options" = 1, +# `selected-text-format` = "count > 1") +# ) +# }) +# +# +# EQ1_plot4_Data <- reactive({ +# EQ1_reformatted_data %>% +# select(Rate_Type, Year, area_type, area_name, Rate) %>% +# filter(area_type %in% input$EQ1_plot4_areaType +# & area_name %in% input$EQ1_plot4_areaName) +# }) +# +# +# ####### Create the combined general population and MH rates bar chart. +# # +# output$EQ1_plot4 <- renderPlotly({ +# # +# # # # No data plot +# # # if(sum(E1_plot1_Data()$dd_bed_days) == 0 & +# # # !is.na(sum(E1_plot1_Data()$dd_bed_days))) +# # # +# # # { +# # # noDataPlot(phs_colours("phs-purple")) +# # # } +# # # +# # # else { +# # +# ### 3 - Tooltip creation ---- +# +# tooltip_EQ1_4 <- paste0("Financial year: ", +# EQ1_plot4_Data()$Year, +# "
", +# "Area of residence: ", +# EQ1_plot4_Data()$area_name, +# "
", +# "Rate Type: ", +# EQ1_plot4_Data()$Rate_Type, +# "
", +# "Rate: ", +# EQ1_plot4_Data()$Rate) +# +# ### 4 - Create the main body of the chart ---- +# +# plot_ly(data = EQ1_plot4_Data(), +# # Select your variables. +# x = ~Year, y = ~Rate, type = 'bar', color = ~Rate_Type, +# colors = c("#0078D4", "#B3D7F2"), +# textposition = "none", +# text = tooltip_EQ1_4, hoverinfo = "text", +# marker = list(size = 12), +# name = ~str_wrap(Rate_Type, 19)) %>% # legend labels +# +# ### 7 - Graph title ---- +# +# # Make the graph title reactive. +# +# layout(title = +# paste0( +# "", +# "Mortality rates for the MH and general population", +# "
", +# " for ", input$EQ1_plot4_areaName, ", ", first(as.vector(EQ1_plot4_Data()$Year)), +# " to ", +# last(as.vector(EQ1_plot4_Data()$Year)), +# "
", +# "
" +# ), +# +# separators = ".", +# +# yaxis = list( +# exponentformat = "none", +# separatethousands = TRUE, +# range = c(0, max(EQ1_plot4_Data()$Rate, na.rm = TRUE) +# + (max(EQ1_plot4_Data()$Rate, na.rm = TRUE)*0.1) +# ), +# title = paste0(c(rep(" ", 20), +# input$EQ1_1_input_1, +# rep(" ", 20), +# rep("\n ", 3))), +# showline = TRUE, +# ticks = "outside" +# ), +# +# xaxis = list( +# title = paste0(c("
", +# "Area name", +# collapse = "")), # Don't think it's needed +# showline = TRUE, +# ticks = "outside" +# ), +# +# margin = list(l = 90, r = 60, b = 180, t = 120), +# title = list(size = 15), +# font = list(size = 13), +# # Legend +# showlegend = TRUE, +# legend = list(x = 1, +# y = 1, +# bgcolor = 'rgba(255, 255, 255, 0)', +# bordercolor = 'rgba(255, 255, 255, 0)') +# # legend = list(orientation = "h", # show entries horizontally +# # xanchor = "center", # use center of legend as anchor +# # x = 0.5, y = -0.9) # put legend in center of x-axis +# ) %>% +# +# ### 13 - Remove unnecessary buttons from the modebar ---- +# +# config(displayModeBar = TRUE, +# modeBarButtonsToRemove = bttn_remove, +# displaylogo = F, editable = F) +# +# # } +# +# }) +# +# +# ### 15 - Table below graph creation ---- +# +# # output$E1_1_trend_table <- renderDataTable({ +# # datatable(E1_plot1_Data(), +# # style = 'bootstrap', +# # class = 'table-bordered table-condensed', +# # rownames = FALSE, +# # options = list(pageLength = 16, autoWidth = TRUE, dom = 'tip'), +# # colnames = c("Financial year", +# # "Area of Residence", +# # "Number of Bed Days")) +# # }) +# diff --git a/modules/indicators/EQ1_ui.R b/modules/indicators/EQ1_ui.R index 2aa832f..6746f37 100644 --- a/modules/indicators/EQ1_ui.R +++ b/modules/indicators/EQ1_ui.R @@ -1,19 +1,232 @@ -tabItem(tabName = EQ1_tab, +# Beginning of EQ1 tab ---- + +tabItem(tabName = "EQ1_tab", fluidPage( - titlePanel("EQ1"), - mainPanel( - h3("You are on EQ1"), - fluidRow( - column(4, actionButton(inputId = "EQ1_scot_hub_button", - label = "Scotland Hub", icon = icon("home"), - class = "navpageButton")), - column(4, actionButton(inputId = "EF5_prevButton", - label = "Previous Page", icon = icon("arrow-left"), - class = "navpageButton")), - column(4, actionButton(inputId = "EQ2_nextButton", - label = "Next Page", icon = icon("arrow-right"), - class = "navpageButton")) + h1("EQ1 - Premature mortality rate = Standardised mortality rate ", + "for persons in contact with mental health services"), + + hr(), # page break + + + # First Graph ---- + # Text above graph + fluidRow( + column(12, + box(width = NULL, + p("Below is a graph showing the changes over time of the ", + "mortality rates for persons in contact with mental health ", + "services. ", + br(), + "This is broken down by either council area or health board of ", + "residence. Please use the drop down menus to select which ", + "areas you wish to look at."))) + ), + + # Geography Drop Down Menus + fluidRow( + column(6, + box(width = NULL, + uiOutput("EQ1_plot1_areaType_output")) + ), + column(6, + box(width = NULL, + uiOutput("EQ1_plot1_areaName_output")) + ), + ), + + # Graph 1 output + fluidRow( + box(width = 12, + phs_spinner("EQ1_plot1")) + ), + hr(), # page break + + fluidRow( + box(title = "Below is a table showing the data used to create the above graph. + It can be downloaded using the 'Download as .csv' button underneath this section", + width = 12, solidHeader = TRUE, collapsible = TRUE, collapsed = FALSE, + dataTableOutput("EQ1_1_table") ) + ), + fluidRow( + column(4, + downloadButton(outputId = "EQ1_1_table_download", + label = "Download as .csv", + class = "EQ1_1_table_downloadbutton"), + tags$head( + tags$style(".EQ1_1_table_downloadbutton { background-color: + #3F3685; } + .EQ1_1_table_downloadbutton { color: #FFFFFF; }") + ) + ) + ), + + hr(), # page break + + + # Second graph ---- + # Text above graph + fluidRow( + column(12, + box(width = NULL, + p("Below is a graph showing the changes over time of the ", + "mortality rates for the general population and the mental ", + "health population for your chosen area.", + br(), + "This is broken down by either council area or health board of ", + "residence. Please use the drop down menus to select which ", + "area you wish to look at."))) + ), + + # Geography Drop Down Menus + fluidRow( + column(6, + box(width = NULL, + uiOutput("EQ1_plot4_areaType_output"))), + column(6, + box(width = NULL, + uiOutput("EQ1_plot4_areaName_output"))), + ), + + # Graph 2 output + fluidRow( + box(width = 12, + phs_spinner("EQ1_plot4")) + ), + hr(), # page break + + fluidRow( + box(title = "Below is a table showing the data used to create the above graph. + It can be downloaded using the 'Download as .csv' button underneath this section", + width = 12, solidHeader = TRUE, collapsible = TRUE, collapsed = FALSE, + dataTableOutput("EQ1_2_table") + ) + ), + fluidRow( + column(4, + downloadButton(outputId = "EQ1_2_table_download", + label = "Download as .csv", + class = "EQ1_2_table_downloadbutton"), + tags$head( + tags$style(".EQ1_2_table_downloadbutton { background-color: + #3F3685; } + .EQ1_2_table_downloadbutton { color: #FFFFFF; }") + ) + ) + ), + br(), + + # Navigation Buttons ---- + go_2_top_bttn, + + br(), + + fluidRow( + column(4, actionButton(inputId = "EQ1_scot_hub_button", + label = "Scotland Hub", icon = icon("home"), + class = "navpageButton")), + column(4, actionButton(inputId = "EF5_prevButton", + label = "Previous Page", icon = icon("arrow-left"), + class = "navpageButton")), + column(4, actionButton(inputId = "EQ2_nextButton", + label = "Next Page", icon = icon("arrow-right"), + class = "navpageButton")) ) - ) -) \ No newline at end of file + + + + + ), # End of fluidPage +) + + +# titlePanel(paste0( +# "EQ1 - Premature mortality rate = Standardised mortality rate ", +# "for persons in contact with mental health services")), + + + + + +# mainPanel( +# tags$p("Below is a graph showing the changes over time."), +# +# fluidRow( +# column(6,uiOutput("EQ1_plot1_areaType_output")), +# column(6,uiOutput("EQ1_plot1_areaName_output")) +# ), +# +# fluidRow( +# plotlyOutput("EQ1_plot1" +# # , +# # width = "100%", +# # height = "50%" +# ) +# ), +# +# br(), +# # br(), +# # fluidRow( +# # plotlyOutput("EQ1_plot2" +# # # , +# # # width = "100%", +# # # height = "50%" +# # ) +# # ), +# # br(), +# # br(), +# # fluidRow( +# # plotlyOutput("EQ1_plot3" +# # # , +# # # width = "100%", +# # # height = "50%" +# # ) +# # ), +# # br(), +# fluidRow( +# column(6,uiOutput("EQ1_plot4_areaType_output")), +# column(6,uiOutput("EQ1_plot4_areaName_output")) +# ), +# br(), +# fluidRow( +# plotlyOutput("EQ1_plot4" +# # , +# # width = "100%", +# # height = "50%" +# ) +# ), +# br(), +# +# +# +# br(), +# +# go_2_top_bttn, +# +# # tags$a(href = '#E1_top', +# # icon("circle-arrow-up", +# # lib = "glyphicon"), +# # "Back to top"), +# br(), +# br(), +# # ), # End of mainPanel +# +# +# +# +# +# fluidRow( +# column(4, actionButton(inputId = "EQ1_scot_hub_button", +# label = "Scotland Hub", icon = icon("home"), +# class = "navpageButton")), +# column(4, actionButton(inputId = "EF5_prevButton", +# label = "Previous Page", icon = icon("arrow-left"), +# class = "navpageButton")), +# column(4, actionButton(inputId = "EQ2_nextButton", +# label = "Next Page", icon = icon("arrow-right"), +# class = "navpageButton")) +# ) +# ) # End of mainPanel +# ) # End of fluidPage +# ) +# diff --git a/modules/indicators/EQ2_ui.R b/modules/indicators/EQ2_ui.R index 7ef7e69..a593b7f 100644 --- a/modules/indicators/EQ2_ui.R +++ b/modules/indicators/EQ2_ui.R @@ -1,8 +1,23 @@ -tabItem(tabName = EQ2_tab, +tabItem(tabName = "EQ2_tab", fluidPage( - titlePanel("EQ2"), - mainPanel( - h3("You are on EQ2"), + h1("EQ2 - Number of emergency detention certificates (EDCs) per 100,000 population"), + fluidRow( + box(width = 9, + img(src='infographics/EQ2.png', + class = "infographic", + alt = paste0( + "In Scotland in 2022/23, the number of emergency detention ", + "certificates per 100,000 population was 60.0. This is a ", + "slight increase from 59.5 in 2021/22.")),) + ), + fluidRow( + box(width = 9, + p("This data is sourced from the ", + a(href="https://www.mwcscot.org.uk/publications?type=44&leg=54", + "Mental Welfare Commission.")), + ) + ), + fluidRow( column(4, actionButton(inputId = "EQ2_scot_hub_button", label = "Scotland Hub", icon = icon("home"), @@ -14,6 +29,6 @@ tabItem(tabName = EQ2_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) - ) -) \ No newline at end of file + ) # End of fluidPage + ) + \ No newline at end of file diff --git a/modules/indicators/EQ4_ui.R b/modules/indicators/EQ4_ui.R index a7c0ccf..5272416 100644 --- a/modules/indicators/EQ4_ui.R +++ b/modules/indicators/EQ4_ui.R @@ -1,8 +1,26 @@ -tabItem(tabName = EQ4_tab, +tabItem(tabName = "EQ4_tab", fluidPage( - titlePanel("EQ4"), - mainPanel( - h3("You are on EQ4"), + h1("EQ4 - % of under 18 year old psychiatric admissions admitted out with NHS specialist Child and Adolescent Mental Health (CAMH) wards"), + fluidRow( + box(width = 9, + img(src='infographics/EQ4.png', + class = "infographic", + alt = paste0( + "30.1% of under 18 year old psychiatric admissions were ", + "admitted outwith NHS specialist CAMH wards during the ", + "year-long period ending 31 March 2023. This compares with ", + "35.5% during the year ending 31 March 2022, and 29.3% ", + "during the year ending 31 March 2021.")), + ) + ), + fluidRow( + box(width = 9, + p("The data for EQ4 is sourced from ", + a(href="https://www.publichealthscotland.scot/services/discovery/#section-1-1", + "Discovery.")), + ) + ), + fluidRow( column(4, actionButton(inputId = "EQ2_prevButton", label = "Previous Page", icon = icon("arrow-left"), @@ -11,6 +29,6 @@ tabItem(tabName = EQ4_tab, label = "Scotland Hub", icon = icon("home"), class = "navpageButton")) ) - ) + ) # End of fluidPage ) -) \ No newline at end of file + \ No newline at end of file diff --git a/modules/indicators/P1_ui.R b/modules/indicators/P1_ui.R index 3b37a3a..bfc6cde 100644 --- a/modules/indicators/P1_ui.R +++ b/modules/indicators/P1_ui.R @@ -1,22 +1,28 @@ -tabItem(tabName = P1_tab, +tabItem(tabName = "P1_tab", fluidPage( - titlePanel(paste0("P1 - % of carers with a mental health condition that ", - "felt supported to continue in their caring role")), - mainPanel( - img(src='infographics/P1.png', - class = "infographic", - alt = paste0( - "In Scotland in 2019/20 27% of carers with a mental health ", - "condition agreed that they felt asupported to continue caring. ", - "This compares with 30% of carers with a mental health condition ", - "in 2017/18")), - br(), - p("Further information can be found in the ", - a(href="https://www.gov.scot/collections/health-and-care-experience-survey/", - "Health and Care Experience Survey"), - ".") - ), - + + h1("P1 - % of carers with a mental health condition that felt supported to continue in their caring role"), + fluidRow( + box(width = 9, + img(src='infographics/P1.png', + class = "infographic", + alt = paste0( + "In Scotland in 2019/20 27% of carers with a mental health ", + "condition agreed that they felt asupported to continue caring. ", + "This compares with 30% of carers with a mental health condition ", + "in 2017/18")), + ), + + ), + + fluidRow( + box(width = 9, + p("Further information can be found in the ", + a(href="https://www.gov.scot/collections/health-and-care-experience-survey/", + "Health and Care Experience Survey"),"."), + ), + ), + fluidRow( column(4, actionButton(inputId = "P1_scot_hub_button", label = "Scotland Hub", icon = icon("home"), @@ -29,4 +35,4 @@ tabItem(tabName = P1_tab, class = "navpageButton")) ) ) # End of fluidPage -) \ No newline at end of file + ) diff --git a/modules/indicators/P2_ui.R b/modules/indicators/P2_ui.R index 45de465..199540d 100644 --- a/modules/indicators/P2_ui.R +++ b/modules/indicators/P2_ui.R @@ -1,22 +1,27 @@ -tabItem(tabName = P2_tab, +tabItem(tabName = "P2_tab", fluidPage( - titlePanel(paste0( - "P2 - % of adults with mental health problems supported at home ", - "who agree that their services and support had an impact in ", - "improving or maintaining their quality of life")), - mainPanel( - img(src='infographics/P2.png', - class = "infographic", - alt = paste0( - "In Scotland in 2019/20 27% of carers with a mental health ", - "condition agreed that they felt asupported to continue caring. ", - "This compares with 30% of carers with a mental health condition ", - "in 2017/18")), - br(), - p("Further information can be found in the ", - a(href="https://www.gov.scot/collections/health-and-care-experience-survey/", - "Health and Care Experience Survey"), - ".") + + h1("P2 - % of adults with mental health problems supported at home who agree that their services and support had an impact in improving or maintaining their quality of life"), + fluidRow( + box(width = 9, + img(src='infographics/P2.png', + class = "infographic", + alt = paste0( + "In Scotland in 2020/21 between 53% and 57% of adults ", + "with mental health problems supported at home agree that ", + "their services and support had an impact in improving ", + "or maintaining their quality of life. This compares with ", + "around 74% of adults with mental health problems in 2019/20.")), + ), + + ), + + fluidRow( + box(width = 9, + p("Further information can be found in the ", + a(href="https://www.gov.scot/collections/health-and-care-experience-survey/", + "Health and Care Experience Survey"),"."), + ), ), fluidRow( @@ -31,5 +36,5 @@ tabItem(tabName = P2_tab, class = "navpageButton")) ) ) # End of fluidPage + ) -) \ No newline at end of file diff --git a/modules/indicators/P3_ui.R b/modules/indicators/P3_ui.R index 00123e2..bb5dd0f 100644 --- a/modules/indicators/P3_ui.R +++ b/modules/indicators/P3_ui.R @@ -1,23 +1,29 @@ -tabItem(tabName = P3_tab, +tabItem(tabName = "P3_tab", fluidPage( - titlePanel(paste0('P3 - % of replies for people with mental health ', - 'problem that agree with statement ', - '"people took account of the things that mattered to me"')), - mainPanel( - img(src='infographics/P3.png', - class = "infographic", - alt = paste0( - "In Scotland in 2019/20 78% of people with a mental health ", - "problem agreed that people took account of the things that ", - "mattered to them, compared to 80% of people with a mental ", - "health problem in 2017/18")), - br(), - p("Further information can be found in the ", - a(href="https://www.gov.scot/collections/health-and-care-experience-survey/", - "Health and Care Experience Survey"), - ".") + + h1("P3 - % of replies for people with mental health problem that agree with statement 'people took account of the things that mattered to me'"), + fluidRow( + box(width = 9, + img(src='infographics/P3.png', + class = "infographic", + alt = paste0( + "In Scotland in 2019/20 78% of people with a mental health ", + "problem agreed that people took account of the things that ", + "mattered to them, compared to 80% of people with a mental ", + "health problem in 2017/18")), + ), + + ), + + fluidRow( + box(width = 9, + p("Further information can be found in the ", + a(href="https://www.gov.scot/collections/health-and-care-experience-survey/", + "Health and Care Experience Survey"),"."), + ), ), + # Navigation buttons fluidRow( column(4, actionButton(inputId = "P3_scot_hub_button", @@ -31,4 +37,4 @@ tabItem(tabName = P3_tab, class = "navpageButton")) ) ) # End of fluidPage -) \ No newline at end of file + ) diff --git a/modules/indicators/P4_ui.R b/modules/indicators/P4_ui.R index 4fad617..77aca28 100644 --- a/modules/indicators/P4_ui.R +++ b/modules/indicators/P4_ui.R @@ -1,12 +1,30 @@ -tabItem(tabName = P4_tab, +tabItem(tabName = "P4_tab", fluidPage( - titlePanel(paste0("P4 - Number of people with advance statements ", - "registered per year with the Mental Welfare ", - "Commission for Scotland")), - mainPanel( - p("This indicator has not been updated since 2021.") + + + h1("P4 - Number of people with advance statements registered per year with the Mental Welfare Commission for Scotland"), + fluidRow( + box(width = 9, + img(src='infographics/P4.png', + class = "infographic", + alt = paste0( + "In Scotland in 2022/23, there were 155 new advanced ", + "statements registered with MWC, this compares with 117 ", + "new statements in 2021/22, 78 in 2020/21 and 257 in 2019/20.")), ), + + ), + fluidRow( + box(width = 9, + p("Further information can be found in the ", + a(href="https://www.gov.scot/collections/health-and-care-experience-survey/", + "Health and Care Experience Survey"),"."), + ), + ), + + + # Navigation buttons fluidRow( column(4, actionButton(inputId = "P4_scot_hub_button", @@ -19,5 +37,5 @@ tabItem(tabName = P4_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) # End of fluidPage -) \ No newline at end of file + ) # End of fluidPage + ) diff --git a/modules/indicators/S1_ui.R b/modules/indicators/S1_ui.R index 007fae1..1347678 100644 --- a/modules/indicators/S1_ui.R +++ b/modules/indicators/S1_ui.R @@ -1,21 +1,30 @@ -tabItem(tabName = S1_tab, +tabItem(tabName = "S1_tab", fluidPage( - titlePanel("S1 - Suicide Rates per 100,000 population"), - mainPanel( - img(src='infographics/S1.png', - class = "infographic", - alt = paste0( - "For the five year period 2016 to 2020, the crude suicide ", - "rate per 100,000 population in Scotand was 13.7 compared to ", - "13.5 for the five year period 2011-2015.")), - br(), - p(paste0( - "Further information can be found in the [THIS LINK IS BROKEN]", - a(href="https://www.scotpho.org.uk/health-wellbeing-and-disease/suicide/key-points/", - "ScotPHO website"), - ".")) + + h1("S1 - Suicide Rates per 100,000 population"), + fluidRow( + box(width = 9, + img(src='infographics/S1.png', + class = "infographic", + alt = paste0( + "For the five year period 2016 to 2020, the crude suicide ", + "rate per 100,000 population in Scotand was 13.7 compared to ", + "13.5 for the five year period 2011-2015.")), + ), + ), + fluidRow( + box(width = 9, + p(paste0( + "Further information can be found in the [THIS LINK IS BROKEN]", + a(href="https://www.scotpho.org.uk/health-wellbeing-and-disease/suicide/key-points/", + "ScotPHO website"), + ".")), + ), + ), + + fluidRow( column(4, actionButton(inputId = "S1_scot_hub_button", label = "Scotland Hub", icon = icon("home"), @@ -27,5 +36,5 @@ tabItem(tabName = S1_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) -) \ No newline at end of file + ) # End of fluidPage + ) diff --git a/modules/indicators/S2_ui.R b/modules/indicators/S2_ui.R index cac62fa..4dd4d2f 100644 --- a/modules/indicators/S2_ui.R +++ b/modules/indicators/S2_ui.R @@ -1,25 +1,32 @@ -tabItem(tabName = S2_tab, +tabItem(tabName = "S2_tab", fluidPage( - titlePanel(paste0("S2 - % of all discharged psychiatric inpatients ", - "followed-up by community mental health services ", - "within 7 calendar days")), - mainPanel( - img(src='infographics/S2.png', - class = "infographic", - alt = paste0( - "For the quarter ending 31 December 2021, the percentage of ", - "discharged psychiatric inpatients followed-up by community ", - "mental health services within 7 calendar days ranged from ", - "17.6% to 88.1%")), - br(), - p(paste0( - "The data for S2 is sourced from board returns, which may be incomplete.")), - br(), - p(paste0( - "Board returns were received from NHS Ayrshire & Arran, NHS Borders, ", - "NHS Fife, NHS Forth Valley, NHS Grampian, NHS Greater Glasgow ", - "& Clyde, NHS Highland, NHS Lothian, NHS Tayside, and NHS Western Isles.")) + + h1("S2 - % of all discharged psychiatric inpatients followed-up by community mental health services within 7 calendar days"), + fluidRow( + box(width = 9, + img(src='infographics/S2.png', + class = "infographic", + alt = paste0( + "For the quarter ending 31 December 2021, the percentage of ", + "discharged psychiatric inpatients followed-up by community ", + "mental health services within 7 calendar days ranged from ", + "17.6% to 88.1%")), + ), + + ), + + fluidRow( + box(width = 9, + p(paste0( + "The data for S2 is sourced from board returns, which may be incomplete.")), + br(), + p(paste0( + "Board returns were received from NHS Ayrshire & Arran, NHS Borders, ", + "NHS Fife, NHS Forth Valley, NHS Grampian, NHS Greater Glasgow ", + "& Clyde, NHS Highland, NHS Lothian, NHS Tayside, and NHS Western Isles.")), ), + ), + fluidRow( column(4, actionButton(inputId = "S2_scot_hub_button", @@ -32,5 +39,5 @@ tabItem(tabName = S2_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) # End of fluidPage -) # End of tabItem \ No newline at end of file + ) # End of fluidPage + ) diff --git a/modules/indicators/S5_ui.R b/modules/indicators/S5_ui.R index b081287..dac1b6e 100644 --- a/modules/indicators/S5_ui.R +++ b/modules/indicators/S5_ui.R @@ -1,27 +1,32 @@ -tabItem(tabName = S5_tab, +tabItem(tabName = "S5_tab", fluidPage( - titlePanel( - paste0( - "S5 - Incidents of physical violence per 1,000 occupied ", - "psychiatric bed days")), - mainPanel( - img(src='infographics/S5.png', - class = "infographic", - alt = paste0( - "The number of incidents of physical violence per 1,000 ", - "occupied psychiatric bed days in Scotland ranged from zero ", - "to 40.3 for the quarter ending 31 December 2021.")), - br(), - p(paste0( - "The data for S5 is sourced from board returns, which may be incomplete.")), - br(), - p(paste0( - "Board returns were received from NHS Ayrshire & Arran, NHS Borders, ", - "NHS Fife, NHS Forth Valley, NHS Grampian, NHS Greater Glasgow ", - "& Clyde, NHS Highland, NHS Lanarkshire, NHS Lothian, NHS Tayside, ", - "and NHS Western Isles.")) + + h1("S5 - Incidents of physical violence per 1,000 occupied psychiatric bed days"), + fluidRow( + box(width = 9, + img(src='infographics/S5.png', + class = "infographic", + alt = paste0( + "The number of incidents of physical violence per 1,000 ", + "occupied psychiatric bed days in Scotland ranged from zero ", + "to 40.3 for the quarter ending 31 December 2021.")), + ), + ), + fluidRow( + box(width = 9, + p(paste0( + "The data for S2 is sourced from board returns, which may be incomplete.")), + br(), + p(paste0( + "Board returns were received from NHS Ayrshire & Arran, NHS Borders, ", + "NHS Fife, NHS Forth Valley, NHS Grampian, NHS Greater Glasgow ", + "& Clyde, NHS Highland, NHS Lanarkshire, NHS Lothian, NHS Tayside, ", + "and NHS Western Isles.")), + ), + ), + fluidRow( column(4, actionButton(inputId = "S5_scot_hub_button", label = "Scotland Hub", icon = icon("home"), @@ -33,5 +38,5 @@ tabItem(tabName = S5_tab, label = "Next Page", icon = icon("arrow-right"), class = "navpageButton")) ) - ) # End of fluidPage -) \ No newline at end of file + ) # End of fluidPage + ) diff --git a/modules/indicators/T1_ui.R b/modules/indicators/T1_ui.R index 9792ebc..538366d 100644 --- a/modules/indicators/T1_ui.R +++ b/modules/indicators/T1_ui.R @@ -1,29 +1,34 @@ -tabItem(tabName = T1_tab, +tabItem(tabName = "T1_tab", fluidPage( - titlePanel(h1("T1 - % of people who commence Psychological therapy - based treatment within 18 weeks of referral"), - h2("Last Updated: Septemberr 2023")), - mainPanel( - img(src='infographics/T1.png', - class = "infographic", - alt = paste0( - "More than four fifths (84.4%) of people started treatment ", - "within 18 weeks of referral in the quarter ending 31 December 2021", - "compared to 87.2% for the previous quarter, and 80% for the ", - "quarter ending 31 December 2020")), - br(), - p("Further information can be found in the ", - a(href="https://publichealthscotland.scot/publications/psychological-therapies-waiting-times/", - "Psychological Therapies Waiting Times publication"), - ".") + h1("T1 - % of people who commence Psychological therapy based treatment within 18 weeks of referral"), + h2("Last Updated: September 2023"), + fluidRow( + box(width = 9, + img(src='infographics/T1.png', + class = "infographic", + alt = paste0( + "More than four fifths (84.4%) of people started treatment ", + "within 18 weeks of referral in the quarter ending 31 December 2021", + "compared to 87.2% for the previous quarter, and 80% for the ", + "quarter ending 31 December 2020")) + ), ), fluidRow( - column(6, actionButton(inputId = "T1_scot_hub_button", - label = "Scotland Hub", icon = icon("home"), - class = "navpageButton")), - column(6, actionButton(inputId = "T2_nextButton", - label = "Next Page - T2", icon = icon("arrow-right"), - class = "navpageButton")) - ) + box(width = 9, + p("Further information can be found in the ", + a(href="https://publichealthscotland.scot/publications/psychological-therapies-waiting-times/", + "Psychological Therapies Waiting Times publication"), + ".") + ), + ), + fluidRow( + column(4, actionButton(inputId = "T1_scot_hub_button", + label = "Scotland Hub", icon = icon("home"), + class = "navpageButton")), + column(4, actionButton(inputId = "T2_nextButton", + label = "Next Page - T2", icon = icon("arrow-right"), + class = "navpageButton")) + ) + ) # End of fluidPage ) # End of tab \ No newline at end of file diff --git a/modules/indicators/T2_ui.R b/modules/indicators/T2_ui.R index 0f71f23..459f643 100644 --- a/modules/indicators/T2_ui.R +++ b/modules/indicators/T2_ui.R @@ -1,10 +1,10 @@ -tabItem(tabName = T2_tab, +tabItem(tabName = "T2_tab", fluidPage( - headerPanel(fluidRow("T2 - % of young people who commence treatment by + h1("T2 - % of young people who commence treatment by specialist Child and Adolescent Mental Health services - within 18 weeks of referral", - "Sub title")), - mainPanel( + within 18 weeks of referral"), + fluidRow( + box(width = 9, img(src='infographics/T2.png', class = "infographic", alt = paste0( @@ -14,13 +14,16 @@ tabItem(tabName = T2_tab, "previous quarter, and 73.1% in the quarter ending 31 December 2020. ", "Half of children and young people started treatment within seven ", "weeks in the quarter ending 31 December 2021")), - br(), + ) + ), + fluidRow( + box(width = 9, p("Further information can be found in the ", a(href="https://publichealthscotland.scot/publications/child-and-adolescent-mental-health-services-camhs-waiting-times/", "Child and Adolescent Mental Health Services in Scotland: Waiting Times publication"), - ".") - ), - + "."), + ) + ), fluidRow( column(4, actionButton(inputId = "T2_scot_hub_button", label = "Scotland Hub", icon = icon("home"), @@ -31,7 +34,6 @@ tabItem(tabName = T2_tab, column(4, actionButton(inputId = "T3_nextButton", label = "Next Page: T3", icon = icon("arrow-right"), class = "navpageButton")) - ) - - ) # End of fluidPage -) \ No newline at end of file + ) + ) # End of fluidPage + ) diff --git a/modules/indicators/T3_ui.R b/modules/indicators/T3_ui.R index 35964c4..4bb0a09 100644 --- a/modules/indicators/T3_ui.R +++ b/modules/indicators/T3_ui.R @@ -1,11 +1,10 @@ -tabItem(tabName = T3_tab, +tabItem(tabName = "T3_tab", fluidPage( - titlePanel( - paste0( - "T3 - % of people who wait less than three weeks from referral ", + h1("T3 - % of people who wait less than three weeks from referral ", "received to appropriate drug or alcohol treatment that supports ", - "their recovery")), - mainPanel( + "their recovery"), + fluidRow( + box(width = 9, img(src='infographics/T3.png', class = "infographic", alt = paste0( @@ -13,23 +12,25 @@ tabItem(tabName = T3_tab, "drug and aclohol treatment services completed in the quarter ", "ending 31 December 2021, 93% involved a wait of three weeks or ", "less. The percentage of referrals completed within three weeks ", - "for drug treatment was 94% and 92% for alcohol treatment.")), - br(), - p(paste0( + "for drug treatment was 94% and 92% for alcohol treatment.")) + ) + ), + fluidRow( + box(width = 9, + p(paste0( "Data from City of Edinburgh Alcohol and Drug Partnership (ADP) ", "have been excluded from this release as the ADP was unable to ", "confirm that their data were accurate and up-to-date within the ", "specified timescale. Amongst the remaining ADPs, 13 services out ", - "of 181 were excluded due to the absence of complete data.") - ), + "of 181 were excluded due to the absence of complete data.")), + ) + ), br(), p("Further information can be found in the ", a(href="https://beta.isdscotland.org/find-publications-and-data/lifestyle-and-behaviours/substance-use/national-drug-and-alcohol-treatment-waiting-times/", "National Drug and Alcohol Treatment Waiting Times publication"), - ".") - ), - - fluidRow( + "."), + fluidRow( column(4, actionButton(inputId = "T3_scot_hub_button", label = "Scotland Hub", icon = icon("home"), class = "navpageButton")), @@ -39,7 +40,6 @@ tabItem(tabName = T3_tab, column(4, actionButton(inputId = "S1_nextButton", label = "Next Page: S1", icon = icon("arrow-right"), class = "navpageButton")) - ) - - ) # End of fluidPage -) \ No newline at end of file + ) + ) # End of fluidPage + ) diff --git a/modules/introduction_ui.R b/modules/introduction_ui.R index ffaac03..1ff0837 100644 --- a/modules/introduction_ui.R +++ b/modules/introduction_ui.R @@ -1,8 +1,8 @@ -tabItem(tabName = intro, +tabItem(tabName = "intro", fluidPage( # titlePanel("Mental Health Quality Indicators Joint Collection Materials"), mainPanel( - h1("Welcome, to the Mental Health Quality Indicators Dashboard"), + h1("Welcome to the Mental Health Quality Indicators Dashboard"), p("This dashbaord covers 19 indicators out of the 32 indicators set out in the "), p("3 of the indicators have been developed into interactive formats diff --git a/modules/scot_hub_ui.R b/modules/scot_hub_ui.R index 609ba3f..e3f105f 100644 --- a/modules/scot_hub_ui.R +++ b/modules/scot_hub_ui.R @@ -1,4 +1,4 @@ -tabItem(tabName = scot_hub, +tabItem(tabName = "scot_hub", ### [Timely] --------------------------- @@ -7,31 +7,35 @@ tabItem(tabName = scot_hub, box(## T1 ---- # Header Text title = tagList(icon("brain"), - paste0( + # N.B. using paste0 for all text blocks rather than writing out the text + # in one go so that there isn't a new line tag inserted when converting R + # to HTML, which screenreaders would read out + paste0( "T1 - % of people who commence psychological ", "therapy based treatment within 18 weeks of referral ", - T1_dateText,":")), - width = 4, solidHeader = TRUE, + T1_ScotlandHub_dateText, ":")), + width = 4, solidHeader = TRUE, # Body text - paste0(T1,"%"), + paste0(T1_ScotlandHub_value,"%"), # Navigation button actionButton(inputId = "T1_button", label = "T1 - Find out more", - class = "navpageButton pull-right") + class = "navpageButton pull-right") + # N.B. pull-right class keeps the actionButton aligned right but within the box boundaries ), box(## T2 ---- # Header Text title = tagList(icon("hourglass-end"), paste0( - "% of young people who commence treatment by ", + "T2 - % of young people who commence treatment by ", "specialist Child and Adolescent Mental Health ", "services within 18 weeks of referral ", - T2_dateText,":")), + T2_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(T2,"%"), - # Navigation button + paste0(T2_ScotlandHub_value,"%"), + # Navigation button actionButton(inputId = "T2_button", label = "T2 - Find out more", class = "navpageButton pull-right") @@ -41,12 +45,13 @@ tabItem(tabName = scot_hub, # Header Text title = tagList(icon("hourglass-end"), paste0( - "T3 - % of people who commence psychological therapy ", - "based treatment within 18 weeks of referral ", - T3_dateText,":")), + "T3 - % of people who wait less than three weeks ", + "from referral received to appropriate drug or ", + "alcohol treatment that supports their recovery ", + T3_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(T3,"%"), + paste0(T3_ScotlandHub_value,"%"), # Navigation button actionButton(inputId = "T3_button", label = "T3 - Find out more", @@ -66,10 +71,10 @@ tabItem(tabName = scot_hub, title = tagList(icon("hourglass-end"), paste0( "S1 - Suicide rates per 100,000 population ", - S1_dateText,":")), + S1_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(S1), + paste0(S1_ScotlandHub_value), # Navigation button actionButton(inputId = "S1_button", label = "S1 - Find out more", @@ -81,10 +86,10 @@ tabItem(tabName = scot_hub, title = tagList(icon("hourglass-end"), paste0("S2 - % of all Discharged Psychiatric Inpatients ", "followed-up by Community Mental Health Services ", - "within 7 Calendar Days ", S2_dateText,":")), + "within 7 Calendar Days ", S2_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(S2_low,"% to ",S2_high,"%"), + paste0(S2_ScotlandHub_value_low,"% to ", S2_ScotlandHub_value_high,"%"), # Navigation button actionButton(inputId = "S2_button", label = "S2 - Find out more", @@ -97,10 +102,10 @@ tabItem(tabName = scot_hub, paste0( "S5 - incidents of Physical Violence per ", "1,000 occupied Psychiatric Bed Days ", - S5_dateText,":")), + S5_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(S5_low," to ",S5_high), + paste0(S5_ScotlandHub_value_low," to ",S2_ScotlandHub_value_high), # Navigation button actionButton(inputId = "S5_button", label = "S5 - Find out more", @@ -119,11 +124,13 @@ tabItem(tabName = scot_hub, # Header Text title = tagList(icon("hourglass-end"), paste0( - "P1 - Suicide rates per 100,000 population ", - P1_dateText,":")), + "P1 - % of carers with a mental health condition that felt ", + "supported to continue in their caring role ", + P1_ScotlandHub_dateText,":")), + width = 4, solidHeader = TRUE, # Body text - paste0(P1,"%"), + paste0(P1_ScotlandHub_value), # Navigation button actionButton(inputId = "P1_button", label = "P1 - Find out more", @@ -137,10 +144,10 @@ tabItem(tabName = scot_hub, paste0( "P2 - % of Adults with MH Problems supported at home who agree ", "their support had an impact on improving or maintaining their ", - "quality of life ", P2_dateText,":")), + "quality of life ", P2_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(P2,"%"), + paste0(P2_ScotlandHub_value), # Navigation button actionButton(inputId = "P2_button", label = "P2 - Find out more", @@ -154,32 +161,26 @@ tabItem(tabName = scot_hub, paste0( 'P3 - % of people with a mental health problem that agree ', 'with the statement "people took account of the things ', - 'that mattered to me" ', P3_dateText,":")), + 'that mattered to me" ', P3_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(P3,"%"), + paste0(P3_ScotlandHub_value), # Navigation button actionButton(inputId = "P3_button", label = "P3 - Find out more", class = "navpageButton pull-right") - ) - ), - - # No br() as the next row is the same category - - ### [Person Centred 2] --------------------------- - - fluidRow( + ), box(## P4 ---- # Header Text title = tagList( - icon("hourglass-end"), + icon("clipboard"), paste0("P4 - number of people with Advance Statements ", - "registered in ", P4_dateText,":")), + "registered with the Mental Welfare Commission for Scotland ", + P4_ScotlandHub_dateText,":")), width = 4, solidHeader = TRUE, # Body text - paste0(P4), + paste0(P4_ScotlandHub_value), # Navigation button actionButton(inputId = "P4_button", label = "P4 - Find out more", @@ -195,15 +196,20 @@ tabItem(tabName = scot_hub, fluidRow( box(## E1 ---- - # Link in title instead of button - title = actionLink("E1_button", - "E1 - Days in hospital when clinically - ready to discharge, per 1,000 population:", - icon = icon("refresh")), + title = tagList( + icon("hourglass-end"), + paste0("E1 - Days in hospital when clinically + ready to discharge, per 1,000 population ", + E1_ScotlandHub_dateText, ":")), width = 4, solidHeader = TRUE, - paste0(E1)) + # Body text + paste0(E1_ScotlandHub_value), + # Navigation button + actionButton(inputId = "E1_button", + label = "E1 - Find out more", + class = "navpageButton pull-right") - ), + )), br(), @@ -215,11 +221,12 @@ tabItem(tabName = scot_hub, box(## EF1 ---- # Header Text title = tagList( - icon("hourglass-end"), - "EF1 - Rate of Emergency Bed Days for Adults:"), + icon("bed"), + "EF1 - Rate of Emergency Bed Days for Adults per 100,000 population ", + EF1_ScotlandHub_dateText, ":"), width = 4, solidHeader = TRUE, # Body text - paste0(EF1," / 100,000"), + paste0(EF1_ScotlandHub_value), # Navigation button actionButton(inputId = "EF1_button", label = "EF1 - Find out more", @@ -229,12 +236,13 @@ tabItem(tabName = scot_hub, box(## EF2 ---- # Header Text title = tagList( - icon("hourglass-end"), - paste0("EF2 - % of Readmissions to hospital within 28 Days of Discharge:") + icon("refresh"), + paste0("EF2 - % of Readmissions to hospital within 28 Days of Discharge ", + EF2_ScotlandHub_dateText, ":") ), width = 4, solidHeader = TRUE, # Body text - paste0(EF2,"%"), + paste0(EF2_ScotlandHub_value, "%"), # Navigation button actionButton(inputId = "EF2_button", label = "EF2 - Find out more", @@ -245,33 +253,28 @@ tabItem(tabName = scot_hub, box( # Header Text title = tagList( - icon("hourglass-end"), - paste0("EF3 - Total Psychiatric Inpatient Beds per 100,000 population:") + icon("bed"), + paste0("EF3 - Total Psychiatric Inpatient Beds per 100,000 population ", + EF3_ScotlandHub_dateText, ":") ), width = 4, solidHeader = TRUE, # Body text - paste0(EF3), + paste0(EF3_ScotlandHub_value), # Navigation button actionButton(inputId = "EF3_button", label = "EF3 - Find out more", class = "navpageButton pull-right") - ) ), - - # No br() as the next row is the same category - - ### [Efficient 2] --------------------------- - - fluidRow( box(# EF4 ---- # Header Text title = tagList( - icon("hourglass-end"), - paste0("EF4 - Total Mental Health Spend as a % of Total Spend:")), + icon("sterling-sign"), + paste0("EF4 - Total Mental Health Spend as a % of Total Spend ", + EF4_ScotlandHub_dateText, ":")), width = 4, solidHeader = TRUE, # Body text - paste0(EF4,"% ", EF4_text), + paste0(EF4_ScotlandHub_value, "%"), # Navigation button actionButton(inputId = "EF4_button", label = "EF4 - Find out more", @@ -282,11 +285,12 @@ tabItem(tabName = scot_hub, # Header Text title = tagList(icon("hourglass-end"), paste0("EF5 - % of Did Not Attend Appointments for ", - "Community based services (Mental Health October - December 2021):") + "Community based services (Mental Health ", + EF5_ScotlandHub_dateText, "):") ), width = 4, solidHeader = TRUE, # Body text - paste0(EF5_low,"% - ",EF5_high, "%"), + paste0(EF5_ScotlandHub_value_low,"% - ",EF5_ScotlandHub_value_high, "%"), # Navigation button actionButton(inputId = "EF5_button", label = "EF5 - Find out more", @@ -306,10 +310,11 @@ tabItem(tabName = scot_hub, # Header Text title = tagList(icon("hourglass-end"), paste0("EQ1 - Premature Mortality rate for Persons ", - "in contact with Mental Health Services (2020/21):")), + "in contact with Mental Health Services ", + EQ1_ScotlandHub_dateText, ":")), width = 4, solidHeader = TRUE, # Body text - paste0(EQ1,"x general"), + paste0(EQ1_ScotlandHub_value,"x general"), # Navigation button actionButton(inputId = "EQ1_button", label = "EQ1 - Find out more", @@ -319,12 +324,12 @@ tabItem(tabName = scot_hub, box(## EQ2 ---- # Header Text - title = tagList(icon("hourglass-end"), + title = tagList(icon("clipboard"), paste0("EQ2 - Number of Emergency Detention Certificates ", - "per 100,000 population (2020/21):")), + "per 100,000 population ", EQ2_ScotlandHub_dateText, ":")), width = 4, solidHeader = TRUE, # Body text - paste0(EQ2), + paste0(EQ2_ScotlandHub_value), # Navigation button actionButton(inputId = "EQ2_button", label = "EQ2 - Find out more", @@ -337,10 +342,11 @@ tabItem(tabName = scot_hub, paste0("EQ3 - % of people with Severe and Enduring ", "Mental Illness and/or Learning Disability ", "who have had an annual health check within ", - "previous 12 months:")), + "previous 12 months ", + EQ3_ScotlandHub_dateText, ":")), width = 4, solidHeader = TRUE, # Body text - paste0("Two NHS Boards advised: ", EQ3,"%"), + paste0("Two NHS Boards advised: ", EQ3_ScotlandHub_value, "%"), # Navigation button actionButton(inputId = "EQ3_button", label = "EQ3 - Find out more", @@ -348,23 +354,16 @@ tabItem(tabName = scot_hub, ), - ), - - # No br() as the next row is the same category - - ### [Equitable 2] --------------------------- - - fluidRow( - box(## EQ4 ---- # Header Text - title = tagList(icon("hourglass-end"), + title = tagList(icon("child"), paste0( "EQ4 - % of under 18 psychiatric admissions ", - "admitted outwith specialist CAMH wards (Sep 2020 - Sep 2021):")), + "admitted outwith specialist CAMH wards ", + EQ4_ScotlandHub_dateText, ":")), width = 4, solidHeader = TRUE, # Body text - paste0(EQ4,"%"), + paste0(EQ4_ScotlandHub_value, "%"), # Navigation button actionButton(inputId = "EQ4_button", label = "EQ4 - Find out more", diff --git a/modules/sidebar_ui.R b/modules/sidebar_ui.R index de497c3..ebae03d 100644 --- a/modules/sidebar_ui.R +++ b/modules/sidebar_ui.R @@ -3,31 +3,33 @@ # link for external source, pic for image from old publication sidebarMenu( + # Enable scrolling of sidebar style = "height:94vh; overflow-y:auto; scrollbar-color: #9F9BC2 #3F3685;" , - # width: 300px;", # Enable scrolling of sidebar + # width: 300px;", + id = "tabs", + menuItem("Introduction", tabName = "intro", icon = icon("home"), selected = TRUE), menuItem("Scotland Hub", tabName = "scot_hub", icon = icon("globe")), br(), - + ## Timely Tabs ---- menuItem("Timely :", icon = icon("clock")), menuItem("T1 - Adult", tabName = "T1_tab", icon = icon("link")), menuItem("T2 - Child and Adolescent", tabName = "T2_tab", icon = icon("up-right-from-square")), menuItem("T3 - Drugs or Alcohol", tabName = "T3_tab", icon = icon("up-right-from-square")), br(), - + ## Safe Tabs ---- menuItem("Safe :"), menuItem("S1 - Suicide", tabName = "S1_tab", icon = icon("image")), - menuItem("S2 - Community Follow-up", tabName = "S2_tab", icon = icon("image"), - badgeLabel = "Updated", badgeColor = "orange"), + menuItem("S2 - Community Follow-up", tabName = "S2_tab", icon = icon("image")), menuItem("S5 - Physical Violence", tabName = "S5_tab", icon = icon("image")), br(), - + ## Person Tabs ---- menuItem("Person Centred :"), menuItem("P1 - Carers", tabName = "P1_tab", icon = icon("image")), menuItem("P2 - At Home Support", tabName = "P2_tab", icon = icon("image")), @@ -35,24 +37,26 @@ sidebarMenu( menuItem("P4 - Advance Statements", tabName = "P4_tab", icon = icon("image")), br(), - + ## Effective Tabs ---- menuItem("Effective :"), menuItem("E1 - Delayed Discharge", tabName = "E1_tab", icon = icon("bar-chart"), - badgeLabel = "New", badgeColor = "green"), + badgeLabel = "Updated", badgeColor = "orange"), br(), - + ## Efficient Tabs ---- menuItem("Efficient :"), menuItem("EF 1 - Emergency Bed Days", tabName = "EF1_tab", icon = icon("image")), menuItem("EF 2 - Readmissions", tabName = "EF2_tab", icon = icon("image")), menuItem("EF 3 - Psychiatric Beds", tabName = "EF3_tab", icon = icon("image")), - menuItem("EF 4 - Mental Health Spend", tabName = "EF4_tab", icon = icon("bar-chart")), + menuItem("EF 4 - Mental Health Spend", tabName = "EF4_tab", icon = icon("bar-chart"), + badgeLabel = "Updated", badgeColor = "orange"), menuItem("EF 5 - Community DNA", tabName = "EF5_tab", icon = icon("image")), br(), - + ## Equitable Tabs ---- menuItem("Equitable :"), - menuItem("EQ 1 - Premature Mortality", tabName = "EQ1_tab", icon = icon("bar-chart")), + menuItem("EQ 1 - Premature Mortality", tabName = "EQ1_tab", icon = icon("bar-chart"), + badgeLabel = "Updated", badgeColor = "orange"), menuItem("EQ 2 - Emergency Detention", tabName = "EQ2_tab", icon = icon("image")), menuItem("EQ 4 - U18 Outwith CAMH Wards", tabName = "EQ4_tab", icon = icon("image")) diff --git a/scot_hub_data.R b/scot_hub_data.R index bcbd02f..4bdd4cb 100755 --- a/scot_hub_data.R +++ b/scot_hub_data.R @@ -1,56 +1,289 @@ -# Constants ---------------------------------------------------- +# NEW CODE (OLD BELOW) ---- + +# Load alt text csv ---- + +alt_text_csv <- read.csv("//PHI_conf/MentalHealth1/Quality Indicators/QI Publication/2024_November/Dashboard Data/Indicator text/WIP_alt_text_for_indicators.csv") + + +# T1 ---- +# % of people who commence Psychological therapy-based treatment within 18 weeks of referral +T1_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "T1_ScotlandHub_dateText") %>% + pull(value) + +T1_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "T1_ScotlandHub_value") %>% + pull(value) + + +# T2 ---- +# % of young people who commence treatment by specialist Child and Adolescent Mental Health +# services within 18 weeks of referral + +T2_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "T2_ScotlandHub_dateText") %>% + pull(value) + +T2_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "T2_ScotlandHub_value") %>% + pull(value) + + +# T3 ---- +# % of people who wait less than three weeks from referral received to appropriate drug or +# alcohol treatment that supports their recovery + +T3_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "T3_ScotlandHub_dateText") %>% + pull(value) + + +T3_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "T3_ScotlandHub_value") %>% + pull(value) + + +# S1 ---- +# Suicide rates per 100,000 population + +S1_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "S1_ScotlandHub_dateText") %>% + pull(value) + +S1_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "S1_ScotlandHub_value") %>% + pull(value) + + + +# S2 - currently no data in folder ---- +# % of all discharged psychiatric inpatients followed-up by community mental health services +# within 7 calendar days +S2_ScotlandHub_dateText <- "(Oct-Dec 2021)" + +S2_ScotlandHub_value_low <- 17.6 + +S2_ScotlandHub_value_high <- 88.1 + + +# S5 - currently no data in folder ---- +# Incidents of physical violence per 1,000 occupied psychiatric bed days + +S5_ScotlandHub_dateText <- "(Oct-Dec 2021)" +S5_ScotlandHub_value_low <- "Zero" +S2_ScotlandHub_value_high <- 40.3 + + +# P1 - update manually ---- +# % of carers with a mental health condition that felt supported to continue in their caring role + +P1_ScotlandHub_dateText <- "(In financial year 2023/24)" + +P1_ScotlandHub_value <- "27%" + + +# P2 - update manually ---- +# % of adults with mental health problems supported at home who agree that their services and +# support had an impact in improving or maintaining their quality of life + +P2_ScotlandHub_dateText <- "(In financial year 2023/24)" + +P2_ScotlandHub_value <- "55%" + +# P3 - update manually ---- +# % of replies for people with a mental health problem that agree with the statement +# "people took account of the things that mattered to me" + +P3_ScotlandHub_dateText <- "(In financial year 2023/24)" + +P3_ScotlandHub_value <- "56%" -# Data for Scot Hub (from previous publication): -T1_dateText <- "(Oct-Dec 2021)" -T1 <- 84.4 -T2_dateText <- "(Oct-Dec 2021)" -T2 <- 70.3 +# P4 ---- +# Number of people with advance statements registered per year with the +# Mental Welfare Commission for Scotland -T3_dateText <- "(Oct-Dec 2021)" -T3 <- 93 +P4_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "P4_ScotlandHub_dateText") %>% + pull(value) +P4_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "P4_ScotlandHub_value") %>% + pull(value) -S1_dateText <- "(2016-2020)" -S1 <- 13.7 -S2_dateText <- "(Oct-Dec 2021)" -S2_low <- 17.6 -S2_high <- 88.1 +# E1 ---- +# Number of days people spend in hospital when they are clinically ready to +# be discharged per 1,000 population -S5_dateText <- "(Oct-Dec 2021)" -S5_low <- "Zero" -S5_high <- 40.3 +E1_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "E1_ScotlandHub_dateText") %>% + pull(value) -P1_dateText <- "(2019/20)" -P1 <- 27 +E1_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "E1_ScotlandHub_value") %>% + pull(value) -P2_dateText <- "(2019/20)" -P2 <- 74 -P3_dateText <- "(2019/20)" -P3 <- 78 +# EF1 ---- +# Rate of emergency bed days for adults (per 100,000 population) -P4_dateText <- "2020/21" -P4 <- 78 - -E1_orig <- 13829462 # [remember to add code to include 000 separarators] -E1 <- format(E1_orig, big.mark = ",") +EF1_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "EF1_ScotlandHub_dateText") %>% + pull(value) -EF1 <- "18,844" -EF2 <- 8.4 -EF3 <- 64.9 +EF1_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "EF1_ScotlandHub_value") %>% + pull(value) -EF4 <- 8.8 -EF4_text <- "(2020/21)" -EF5_low <- 8.2 -EF5_high <- 20.5 +# EF2 ---- +# % Readmissions to hospital within 28 days of discharge -EQ1 <- 2.62 +EF2_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "EF2_ScotlandHub_dateText") %>% + pull(value) -EQ2 <- 60 +EF2_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "EF2_ScotlandHub_value") %>% + pull(value) + + +# EF3 - working on, have half the data ---- +# Total psychiatric inpatient beds per 100,000 population (NRAC adjusted) + +EF3_ScotlandHub_dateText <- "(in EXAMPLE DATE)" + + +EF3_ScotlandHub_value <- 64.9 + + +# EF4 ---- +# Total mental health spend as a % of total spend + +EF4_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "EF4_ScotlandHub_dateText") %>% + pull(value) + + +EF4_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "EF4_ScotlandHub_value") %>% + pull(value) + + +# EF5 - currently no data in folder ---- +# % of did not attend appointments for community based services of people with mental +# health problems + +EF5_ScotlandHub_dateText <- "(EXAMPLE DATE)" + +EF5_ScotlandHub_value_low <- 8.2 +EF5_ScotlandHub_value_high <- 20.5 + + +# EQ1 ---- +# Premature mortality rate = Standardised mortality rate for persons in contact with +# mental health services + +EQ1_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "EQ1_ScotlandHub_dateText") %>% + pull(value) + +EQ1_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "EQ1_ScotlandHub_value") %>% + pull(value) + + +# EQ2 ---- +# Number of emergency detention certificates (EDCs) per 100,000 population + +EQ2_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "EQ2_ScotlandHub_dateText") %>% + pull(value) + +EQ2_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "EQ2_ScotlandHub_value") %>% + pull(value) + + +# EQ3 - new indicator - need to find data ---- +# % of people with Severe and Enduring Mental Illness and/or Learning Disability who have +# had an annual health check within previous 12 months + +EQ3_ScotlandHub_dateText <- "(EXAMPLE DATE)" + +EQ3_ScotlandHub_value <- 6 + + +# EQ4 ---- +# % of under 18 year old psychiatric admissions admitted out with NHS specialist Child and +# Adolescent Mental Health (CAMH) wards + +EQ4_ScotlandHub_dateText <- alt_text_csv %>% + filter(alt_text == "EQ4_ScotlandHub_dateText") %>% + pull(value) + +EQ4_ScotlandHub_value <- alt_text_csv %>% + filter(alt_text == "EQ4_ScotlandHub_value") %>% + pull(value) + + + +# OLD CODE copied out ---- + +# Constants ---------------------------------------------------- + +# Data for Scot Hub (from previous publication): +# T1_dateText <- "(Oct-Dec 2021)" +# T1 <- 84.4 -EQ3 <- 6 - -EQ4 <- 51.3 +# T2_dateText <- "(Oct-Dec 2021)" +# T2 <- 70.3 +# +# T3_dateText <- "(Oct-Dec 2021)" +# T3 <- 93 +# +# +# S1_dateText <- "(2016-2020)" +# S1 <- 13.7 +# +# S2_dateText <- "(Oct-Dec 2021)" +# S2_low <- 17.6 +# S2_high <- 88.1 +# +# S5_dateText <- "(Oct-Dec 2021)" +# S5_low <- "Zero" +# S5_high <- 40.3 +# +# P1_dateText <- "(2019/20)" +# P1 <- 27 +# +# P2_dateText <- "(2019/20)" +# P2 <- 74 +# +# P3_dateText <- "(2019/20)" +# P3 <- 78 +# +# P4_dateText <- "2020/21" +# P4 <- 78 +# +# E1_orig <- 13829462 # [remember to add code to include 000 separarators] +# E1 <- format(E1_orig, big.mark = ",") +# +# EF1 <- "18,844" +# EF2 <- 8.4 +# EF3 <- 64.9 +# +# EF4 <- 8.8 +# EF4_text <- "(2020/21)" +# +# EF5_low <- 8.2 +# EF5_high <- 20.5 +# +# EQ1 <- 2.62 +# +# EQ2 <- 60 +# +# EQ3 <- 6 +# +# EQ4 <- 51.3 \ No newline at end of file diff --git a/setup.R b/setup.R new file mode 100644 index 0000000..dd766ac --- /dev/null +++ b/setup.R @@ -0,0 +1,45 @@ +### Loading required packages ---- + +### Load functions ---- +# source("functions/core_functions.R") +# source("functions/plot_functions.R") + +### Load in data ---- + +# # Load in data to app_data +# # Find all rds files in shiny_app/data +# csv_files <- list.files(path="data/", pattern="*.csv") +# for (csv in csv_files){ +# load_csv_file(csv) +# } + + +### Repeated plotting code ---- + +# Buttons to remove from plotly plots +bttn_remove <- list( + 'select2d', + 'lasso2d', + 'zoomIn2d', + 'zoomOut2d', + 'autoScale2d', + 'toggleSpikelines', + 'hoverCompareCartesian', + 'hoverClosestCartesian' +) + +# Go to top button +go_2_top_bttn <- gotop::use_gotop( + src = "fas fa-chevron-circle-up", # css class from Font Awesome + color = phs_colors('phs-blue'), # color + opacity = 0.8, # transparency + width = 50, # size + appear = 80 # number of pixels before appearance +) + +### 13 - Remove unnecessary buttons from the modebar ---- +# [WARNING, NOT WORKING AT THIS POINT - WILL BREAK DASHBOARD IF UNCOMMENTED] + +# modebar_bttn_rmv <- list(config(displayModeBar = TRUE, +# modeBarButtonsToRemove = bttn_remove, +# displaylogo = F, editable = F)) diff --git a/www/stylesheet.css b/www/stylesheet.css index 71e7e27..b59b38e 100755 --- a/www/stylesheet.css +++ b/www/stylesheet.css @@ -1,6 +1,17 @@ /* MHQI Stylesheet */ /* Sheet has stopped working with phs styles variables for some reason...change to hex codes */ +/* [Page Navigation Buttons] */ +.navpageButton{ + background-color: #9B4393; /* button colour - phs-magenta */ + color: #ECEBF3; /* text colour --phs-purple-10*/ + border: 4px rounded ; + /*word-wrap: normal; /* tell css to wrap the text in buttons */ + /*white-space: normal; /* required for text wrapping to work */ + /*align: right;*/ +} + + /* Main header*/ /*.main-header .navbar { background-color: #ECEBF3; /* Header colour */ @@ -14,6 +25,7 @@ h1 { font-weight: bold; } +/* [Dashboard Skin] */ /* dashboardHeader settings */ .skin-blue .main-header .logo { background-color: #3F3685; @@ -45,48 +57,73 @@ h1 { color: #655E9D; } -/* + +/* [ScotHub styling] */ + /* Defining shinydashboard 'box' element styling */ + +/* Whole Box */ +.col-sm-4{ + min-width: 400px; +} +/* Box border */ +.box{ + border-width: thin; + border-style: solid; + border-color: #C5C3DA; +} + +/* Header */ .box-header{ - background-color: #ECEBF3; /* Header colour */ + background-color: #E9F2F3; /* Header colour */ color: #3F3685; /* Header text colour */ /*font-weight: bold;*/ word-wrap: normal; /* tell css to wrap the text in buttons */ white-space: normal; /* required for text wrapping to work */ - + height: 90px; /* Specifying height of Header area */ + border: thin solid #C5C3DA; } +/* Box Header Text */ .box-header h3{ - /*font-size: 36px;*/ - font-weight: bold; - line-height: 1.8; + /* */ + font-size: 36px; + font-weight: bold; + /*line-height: 3; Doesn't seem to change anything */ } .box-body{ color: #3F3685; - font-size: 24px; /* Change this to your desired font size */ + font-size: 20px; /* Change this to your desired font size */ font-weight: bold; /*word-wrap: normal; /* tell css to wrap the text in buttons */ /*white-space: normal; /* required for text wrapping to work */ } -/* Define buttons styling */ -.navpageButton{ - background-color: #9B4393; /* button colour - phs-magenta */ - color: #ECEBF3; /* text colour --phs-purple-10*/ - border: 4px rounded ; - /*word-wrap: normal; /* tell css to wrap the text in buttons */ - /*white-space: normal; /* required for text wrapping to work */ - /*align: right;*/ -} -.titlePanel h2{ +/**//* Tab styling *//**/ + +/* Tab title */ +.container-fluid h2{ color: #3F3685; + font-size: 20px; font-weight: bold; } +/* Tab content under title */ +.col-sm-8{ + width: auto; +} + +/* Tab text */ +.col-sm-8 p{ + font-size: 14px; +} -/* Defining styling for tabs */ +.mainPanel h2{ + color: #3F3685; + font-weight: bold; +} .infographic{ width: 100%; padding: 10px;