Skip to content

Commit

Permalink
give user settings a major facelift
Browse files Browse the repository at this point in the history
  • Loading branch information
ncullen93 committed May 12, 2023
1 parent 8fb4e2e commit a505468
Show file tree
Hide file tree
Showing 3 changed files with 47 additions and 131 deletions.
3 changes: 1 addition & 2 deletions components/app/R/ui.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ app_ui <- function() {
#-------------------------------------------------------
## Build USERMENU
#-------------------------------------------------------
user.tab <- tabView(title = "Settings", id="user", UserInputs("user"), UserUI("user"))

upgrade.tab <- NULL
if(opt$AUTHENTICATION == "firebase") {
Expand Down Expand Up @@ -339,7 +338,7 @@ app_ui <- function() {
##"User",
shiny::textOutput("current_user", inline = TRUE),
bigdash::navbarDropdownTab(
"Settings",
"Profile",
"userSettings"
),
upgrade.tab,
Expand Down
92 changes: 0 additions & 92 deletions components/board.user/R/user_server.R
Original file line number Diff line number Diff line change
Expand Up @@ -23,31 +23,6 @@ UserBoard <- function(id, user) {
)
})

output$description <- renderUI({
user.name <- user$name()
user.level <- user$level()
user.email <- user$email()
dbg("[UserBoard::description] names(user) = ", names(user))
dbg("[UserBoard::description] user.name = ", user.name)
dbg("[UserBoard::description] user.email = ", user.email)
dbg("[UserBoard::description] user.level = ", user.level)

if (is.null(user.name)) user.name <- ""
if (is.null(user.email)) user.email <- ""
user <- user.email
if (user == "" || is.na(user)) user <- user.name

description <- "Signed in as<h2><b>NAME</b></h2><h4>EMAIL</h4><br><h4>LEVEL</h4>"
description <- "Signed in as<h2><b>NAME</b></h2><h4>EMAIL</h4>"
description <- "Signed in as<h4>USER</h4>"
## description = "Signed in as<h4><b>EMAIL<b></h4>"
description <- sub("EMAIL", as.character(user.email), description)
description <- sub("NAME", as.character(user.name), description)
description <- sub("LEVEL", as.character(user.level), description)
description <- sub("USER", as.character(user), description)
shiny::HTML(description)
})

output$plan <- renderUI({
plan_class <- "info"
if (user$level() == "premium") {
Expand Down Expand Up @@ -107,73 +82,6 @@ UserBoard <- function(id, user) {
HTML(news)
})

## ---------------------------------------------------------------
## --------------------- modules for UsersMap --------------------
## ---------------------------------------------------------------

# usersmap.RENDER <- shiny::reactive({

# df <- ACCESS.LOG$visitors
# ## sPDF <- rworldmap::getMap()
# ## rworldmap::mapCountryData(sPDF, nameColumnToPlot='continent')
# sPDF <- rworldmap::joinCountryData2Map(
# df,
# joinCode = "ISO2",
# nameJoinColumn = "country_code")

# par(mai=c(0,0.4,0.2,1),xaxs="i",yaxs="i")
# mapParams <- rworldmap::mapCountryData(
# sPDF, nameColumnToPlot="count",
# ##mapTitle = "Number of unique IPs",
# mapTitle = "", addLegend='FALSE',
# colourPalette = RColorBrewer::brewer.pal(9,"Blues"),
# numCats=9, catMethod="logFixedWidth")

# ##add a modified legend using the same initial parameters as mapCountryData
# do.call( rworldmap::addMapLegend,
# c(mapParams, labelFontSize = 0.85, legendWidth = 1.2, legendShrink = 0.5,
# legendMar = 4, horizontal = FALSE, legendArgs = NULL, tcl = -0.5,
# sigFigs = 4, digits = 3)
# )

# })

# usersmap_info = "<strong>Visitors map.</strong> The world map shows the number of users visiting this site by unique IP."

# shiny::callModule(
# plotModule,
# id = "usersmap",
# plotlib = "baseplot",
# func = usersmap.RENDER,
# func2 = usersmap.RENDER,
# info.text = usersmap_info,
# ##options = usersmap_options,
# pdf.width=12, pdf.height=7, pdf.pointsize=13,
# height = c(450,600), width = c('auto',1000), res=72,
# ##datacsv = enrich_getWordFreq,
# title = "Number of visitors by country",
# add.watermark = WATERMARK
# )

# ##usersmap_caption = "<b>(a)</b> <b>Geo locate.</b>"
# output$usersmapInfo <- shiny::renderUI({

# u <- ACCESS.LOG
# df <- u$visitors
# rownames(df) <- df$country_name
# tot.users <- sum(df$count)
# freq <- df$count
# names(freq) <- df$country_name
# top.countries <- head(sort(freq,dec=TRUE),10)
# top.countriesTT <- paste("<li>",names(top.countries),top.countries,collapse=" ")

# shiny::HTML(
# "<b>Total visitors:</b>",tot.users,"<br><br>",
# "<b>Top 10 countries:</b><br><ol>",top.countriesTT,"</ol><br>",
# "<b>Period:</b><br>",u$period,"<br><br>"
# )
# })

## ------------------------------------------------
## Board return object
## ------------------------------------------------
Expand Down
83 changes: 46 additions & 37 deletions components/board.user/R/user_ui.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,48 +5,57 @@

UserInputs <- function(id) {
ns <- shiny::NS(id)
bigdash::tabSettings(
shiny::uiOutput(ns("description"))
)
bigdash::tabSettings()
}

UserUI <- function(id) {
ns <- shiny::NS(id) ## namespace
shiny::fillCol(
height = 750,
shiny::tabsetPanel(
id = ns("tabs"),
shiny::tabPanel(
"User settings",
fillRow(
flex = c(0.8, 0.2, 1, 0.2, 1),
tagList(
shiny::h4("News"),
shiny::htmlOutput(ns("news"))
), br(),
tagList(
shiny::h4("Personal"),
uiOutput(ns("plan")),
shiny::tableOutput(ns("userdata"))
), br(),
tagList(
shiny::h4("Settings"),
shinyWidgets::prettySwitch(ns("enable_beta"), "enable beta features")

div(
class = "row",
boardHeader(title = "Profile", info_link = ns("board_info")),
div(
class = "col-md-7",
shiny::tabsetPanel(
id = ns("tabs1"),
shiny::tabPanel(
"App Settings",
bslib::layout_column_wrap(
height = "calc(100vh - 183px)",
width = 1,
tagList(
shinyWidgets::prettySwitch(ns("enable_beta"), "enable beta features")
)
)
),
shiny::tabPanel(
"Subscription",
bslib::layout_column_wrap(
height = "calc(100vh - 183px)",
width = 1,
tagList(
shiny::h4("Personal"),
uiOutput(ns("plan")),
shiny::tableOutput(ns("userdata"))
)
)
)
)
),
div(
class = "col-md-5",
shiny::tabsetPanel(
id = ns("tabs2"),
shiny::tabPanel(
"News",
bslib::layout_column_wrap(
height = "calc(100vh - 183px)",
width = 1,
shiny::htmlOutput(ns("news"))
)
)
)
)
)
# Currently not used Stefan 22.03.22
# shiny::tabPanel("Visitors map",
# shiny::fillCol(
# height = 600,
# shiny::fillRow(
# flex = c(1,4.5),
# shiny::wellPanel( shiny::uiOutput(ns("usersmapInfo"))),
# plotWidget(ns("usersmap"))
# )
# )
# )
# shiny::tabPanel("Community forum",uiOutput(ns("forum_UI")))
)
)

}

0 comments on commit a505468

Please sign in to comment.