Skip to content

Commit

Permalink
UI design of shiny App
Browse files Browse the repository at this point in the history
  • Loading branch information
gaospecial committed Dec 27, 2023
1 parent aa5cedd commit 623a542
Show file tree
Hide file tree
Showing 2 changed files with 195 additions and 29 deletions.
187 changes: 158 additions & 29 deletions inst/shiny/shinyApp.R
Original file line number Diff line number Diff line change
@@ -1,45 +1,155 @@
library(shiny)
library(ggVennDiagram)
devtools::load_all(path = rprojroot::find_root("DESCRIPTION"))
library(ggplot2)
library(shinyjs)
library(bslib)
library(htmltools)

# SMALL HTML ELEMENTS -------------------------------------------------------------


## Basic Elements of Sidebar ---------------------------------------------

### Venn plot primary control --------
venn_plot_primary_ctrl = accordion_panel(
"Primary controls",
# Set number
sliderInput(
inputId = 'nsets',
label = "No. of Sets:",
value = 4,
min = 2,
max = 10,
step = 1
),

hr(),

# dynamic inputs
uiOutput("text_inputs")
)

venn_plot_other_ctrl = accordion_panel(
"Other controls",
"Other controls go here"
)

# PAGE COMPONENTS ------

## Venn plot sidebar -----

venn_plot_card_sidebar = sidebar(
width = "25em",
accordion(
venn_plot_primary_ctrl,
venn_plot_other_ctrl
),
actionButton("plot_btn", "Plot Now!")
)

# PAGE LAYOUT-----

## Navset card UI
ui_navset_card_tab = navset_card_tab(
height = 700,
full_screen = TRUE,
title = "Draw a Venn diagram or Upset plot",

# Venn plot card
nav_panel( # for Venn plot
"Venn Diagram",
card_title("A plotly plot"),
layout_sidebar(
sidebar = venn_plot_card_sidebar,

# others
uiOutput('plot_note'),

# plot
plotOutput("plot"),

# download button
conditionalPanel(
condition = "output.plot",
downloadButton("download_png", "Download as PNG"),
downloadButton("download_pdf", "Download as PDF")
)
)
),

# Upset plot card
nav_panel( # for Upset plot
"Upset Plot",
card_title("A leaflet plot"),
markdown("leaflet_widget")
),

# Help card
nav_panel( # for help
shiny::icon("circle-info"),
markdown("Learn more about [htmlwidgets](http://www.htmlwidgets.org/)")
)
)


ui_page_sidebar = page_sidebar(
title = "Penguins dashboard",
sidebar = venn_plot_card_sidebar,
navset_card_underline(
title = "Histograms by species",
nav_panel("Bill Length", plotOutput("bill_length")),
nav_panel("Bill Depth", plotOutput("bill_depth")),
nav_panel("Body Mass", plotOutput("body_mass"))
)
)

# THEME -----
bs_theme = bs_theme(version = 5)
bs_theme = bs_theme |>
bs_add_rules(xfun::read_utf8(xfun::magic_path("shinyApp.css")) |> paste(collapse = "\n"))

# NATIVE SHINY UI ------------------------------------------------------------------

ui = fluidPage(
titlePanel("Draw a Venn diagram or Upset plot"),
theme = bs_theme,
titlePanel("ggVennDiagram Shiny App"),
sidebarLayout(
sidebarPanel(
# Set number
sliderInput(
inputId = 'nsets',
label = "No. of Sets:",
label = "Number of Sets: ",
value = 4,
min = 2,
max = 10,
max = 8,
step = 1
),

# Increase or decrease set number
actionButton(
inputId = "decrease_btn",
label = "decrease the no. of set",
icon = icon("caret-down")
),
actionButton(
inputId = "increase_btn",
label = "increase the no. of set",
icon = icon("caret-up"),
align = "right"
),

hr(),
p("Set name and members:"),

# dynamic inputs
uiOutput("text_inputs"),
hr(),

# type of plot
checkboxInput(
inputId = "force_upset",
label = "Upset Plot"
accordion(
open = FALSE,
accordion_panel(
"Other Controls",
selectInput("label-geom", 'label-geom', c("text", "label"))
)),


fluidRow(
# type of plot
column(4,
checkboxInput(
inputId = "force_upset",
label = "Upset"
)),
column(8,
checkboxInput(
"show_intersect",
"Show Intersects"
))
),

# 画图按钮
Expand All @@ -65,7 +175,11 @@ ui = fluidPage(
)


server = function(input, output, session){

# SERVER SIDE FUNCTIONS ---------------------------------------------------


server = function(input, output, session) {
# 监听按钮的点击事件,更新 slider 的值
observeEvent(input$increase_btn, {
updateSliderInput(session, "nsets", value = input$nsets + 1)
Expand All @@ -79,9 +193,15 @@ server = function(input, output, session){
output$text_inputs = renderUI({
# 生成 nsets 个文本输入框
text_inputs = lapply(1:input$nsets, function(i) {
textAreaInput(paste0("set_", i),
label = paste0("Set_", i),
value = paste0(sample(letters, sample(3:10, 1)), collapse = ","))
div(
class = "form-control my-2 p-2",
fluidRow(
column(textInput(paste0("setname_",i), NULL, paste("Set", i, sep = "_")), width = 10),
column(colourInput(paste0("setcolor_",i), NULL, value = "black", showColour = "background"), width = 2),
),
textAreaInput(paste0("set_", i),
label = "",
value = paste0(sample(letters, sample(3:10, 1)), collapse = ",")))
})

# 返回生成的文本输入框列表
Expand All @@ -102,10 +222,17 @@ server = function(input, output, session){
# 绘图的逻辑
drawPlot <- function(){
x = vector("list", length = input$nsets)
for (i in 1:input$nsets){
category_names = vector("list", length = input$nsets)
set_color = vector("list", length = input$nsets)
for (i in 1:input$nsets) {
x[[i]] = input[[paste0("set_", i)]] |> strsplit(split = ",") |> unlist()
category_names[[i]] = input[[paste0("setname_",i)]]
set_color[[i]] = input[[paste0("setcolor_", i)]]
}
return(ggVennDiagram(x, force_upset = input$force_upset))
return(ggVennDiagram(x,
category.names = category_names,
set_color = unlist(set_color),
force_upset = input$force_upset))
}

# 监听画图按钮的点击事件
Expand Down Expand Up @@ -136,4 +263,6 @@ server = function(input, output, session){
}


# RUN shinyApp() ----------------------------------------------------------

shinyApp(ui, server)
37 changes: 37 additions & 0 deletions inst/shiny/shinyApp.css
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
.form-control {
padding: 0rem;
}

.form-control .control-label {
display: none;
}

.form-group {
margin-top: 0.3rem;
margin-bottom: 0.3rem;
}

.shiny-input-text, .shiny-input-textarea {
border-color: whitesmoke;
padding: 0.1rem;
}

.shiny-input-text {
font-weight: bold;
}

/* move button to right */
form {
overflow: hidden;
}

.action-button {
float: right;
margin-top: 1rem;
}
/* move button to right */


.inline .form-group {
display: table-row;
}

0 comments on commit 623a542

Please sign in to comment.