Skip to content

Commit

Permalink
Misc. tweaks to interface
Browse files Browse the repository at this point in the history
  • Loading branch information
ppernot committed Mar 23, 2023
1 parent ff8af0d commit e81de28
Show file tree
Hide file tree
Showing 10 changed files with 92 additions and 48 deletions.
9 changes: 5 additions & 4 deletions R/graphFuncs.R
Original file line number Diff line number Diff line change
Expand Up @@ -1036,16 +1036,17 @@ plotMS <- function(
text.cex = 1) {

plot(x, y, type = 'n',
xlim = xlim, xlab = xlab, cex.axis=0.75,
xlim = xlim, xlab = xlab, cex.axis=0.75, xaxt = 'n',
ylim = ylim, ylab = 'Mole fraction', yaxs ='i',
main = main)

# Axis
if(diff(range(xlim)) <= 20)
if(diff(range(xlim)) <= 20) {
step = 1
else
} else {
step = 5
ti = seq(floor(xlim[1]), ceiling(xlim[2]), by = step)
}
ti = seq(floor(xlim[1]/step)*step, ceiling(xlim[2]/step)*step, by = step)
axis(side = 1, at = ti, labels = ti, cex.axis=0.75)
grid()

Expand Down
2 changes: 2 additions & 0 deletions global.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
version = 1.5

# Options ####
Sys.setlocale(
category = "LC_NUMERIC",
Expand Down
21 changes: 11 additions & 10 deletions server_files/analysis.R
Original file line number Diff line number Diff line change
Expand Up @@ -381,7 +381,8 @@ generateCategories = function(species) {
radic[is.na(radic)] = 0

## Define species groups according to composition
grp = rep('Misc.',length(species))
lnk = '.'
grp = rep('Dummy',length(species))
sel = colSums(compo) != 0
ns = sum(sel)
elt = elements[sel]
Expand All @@ -398,7 +399,7 @@ generateCategories = function(species) {
e2 = elt[j]
sel = cop[,i] & cop[,j]
if(any(sel))
grp[sel] = paste0(e1,'&',e2)
grp[sel] = paste0(e1,lnk,e2)
}
}
if(ns >= 3)
Expand All @@ -410,7 +411,7 @@ generateCategories = function(species) {
e3 = elt[k]
sel = cop[,i] & cop[,j] & cop[,k]
if(any(sel))
grp[sel] = paste0(e1,'&',e2,'&',e3)
grp[sel] = paste0(e1,lnk,e2,lnk,e3)
}
}
}
Expand All @@ -425,23 +426,23 @@ generateCategories = function(species) {
e4 = elt[l]
sel = cop[,i] & cop[,j] & cop[,k] & cop[,l]
if(any(sel))
grp[sel] = paste0(e1,'&',e2,'&',e3,'&',e4)
grp[sel] = paste0(e1,lnk,e2,lnk,e3,lnk,e4)
}
}
}
}

## Mass
mass = apply(compo, 1, massFormula)
if(any(species %in% spDummy)){
dummyMass = round(max(mass,na.rm=TRUE) + 2 )
if (any(species %in% spDummy)) {
dummyMass = round(max(mass, na.rm = TRUE) + 2)
mass[species %in% spDummy] = dummyMass
}

## Nb of heavy atoms
nbh = nbHeavyAtoms(species)
if(any(species %in% spDummy))
nbh[species %in% spDummy] = max(nbh) + 1
if (any(species %in% spDummy))
nbh[species %in% spDummy] = max(nbh, na.rm = TRUE) + 2
# nbh[is.na(nbh)] = 0

list(
Expand Down Expand Up @@ -636,7 +637,7 @@ output$categsPlot <- renderUI({
ui = list(
br(),
strong("Selection"),
hr(style="border-color: #666;")
hr()
)
ii = 3

Expand Down Expand Up @@ -837,7 +838,7 @@ req(speciesCategories())
ui = list(
br(),
strong("Selection"),
hr(style="border-color: #666;")
hr()
)
ii = 3

Expand Down
14 changes: 8 additions & 6 deletions server_files/model.R
Original file line number Diff line number Diff line change
Expand Up @@ -510,7 +510,8 @@ setGroups = function(species, netColoring, vlpI) {

} else if (netColoring == 'compo') {
# Define species groups according to composition
grp = rep('Misc.',length(species))
lnk = '.'
grp = rep('Dummy',length(species))
sel = colSums(compo) != 0
ns = sum(sel)
elt = elements[sel]
Expand All @@ -527,7 +528,7 @@ setGroups = function(species, netColoring, vlpI) {
e2 = elt[j]
sel = cop[,i] & cop[,j]
if(any(sel))
grp[sel] = paste0(e1,'&',e2)
grp[sel] = paste0(e1,lnk,e2)
}
}
if(ns >= 3)
Expand All @@ -539,7 +540,7 @@ setGroups = function(species, netColoring, vlpI) {
e3 = elt[k]
sel = cop[,i] & cop[,j] & cop[,k]
if(any(sel))
grp[sel] = paste0(e1,'&',e2,'&',e3)
grp[sel] = paste0(e1,lnk,e2,lnk,e3)
}
}
}
Expand All @@ -554,16 +555,17 @@ setGroups = function(species, netColoring, vlpI) {
e4 = elt[l]
sel = cop[,i] & cop[,j] & cop[,k] & cop[,l]
if(any(sel))
grp[sel] = paste0(e1,'&',e2,'&',e3,'&',e4)
grp[sel] = paste0(e1,lnk,e2,lnk,e3,lnk,e4)
}
}
}
}

} else if (netColoring == 'mass') {
nbh = nbHeavyAtoms(species)
nbh[is.na(nbh)] = 0
grp = paste0('C',nbh)
nbh[species %in% spDummy] = max(nbh, na.rm = TRUE) + 2
# nbh[is.na(nbh)] = 0
grp = nbh

}
return(grp)
Expand Down
17 changes: 12 additions & 5 deletions ui.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,13 @@ function(request) {
theme = shinythemes::shinytheme(
c("cosmo", "cerulean", "spacelab", "yeti")[3]
),
tags$head(tags$style(HTML("
hr {
height: 1px;
margin-top: 0.0em;
background: #666;
}"
))),
tabPanel(
title = "Project",
source_ui("project.R")
Expand All @@ -30,14 +37,14 @@ function(request) {
tabPanel(
title = "Fluxes",
source_ui("fluxes.R")
),
)#,
# tabPanel(
# title = "Downloads",
# source_ui("downloads.R")
# ),
tabPanel(
title = "About",
source_ui("about.R")
)
# tabPanel(
# title = "About",
# source_ui("about.R")
# )
)
}
File renamed without changes.
51 changes: 32 additions & 19 deletions ui_files/analysis.R
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,11 @@ sidebarLayout(
column(
width = 3,
wellPanel(
uiOutput(
"categsPlot"
),
strong("Plot"),
hr(),
checkboxInput(
"mcPlot",
"Show error bands",
Expand All @@ -87,9 +92,6 @@ sidebarLayout(
"ppscale",
"Draw PPM scale",
value = FALSE
),
uiOutput(
"categsPlot"
)
)
),
Expand Down Expand Up @@ -117,6 +119,11 @@ sidebarLayout(
column(
width = 3,
wellPanel(
uiOutput(
"categsPlotMS"
),
strong("Plot"),
hr(),
checkboxInput(
"mcPlotMS",
"Show error bars",
Expand All @@ -127,9 +134,6 @@ sidebarLayout(
"Draw PPM scale",
value = FALSE
),
uiOutput(
"categsPlotMS"
),
sliderInput(
"timeMS",
"Log sampling time",
Expand Down Expand Up @@ -183,6 +187,28 @@ sidebarLayout(
column(
width = 3,
wellPanel(
fluidRow(
column(6,
textInput(
"SASpecies",
"Target",
width = "100%",
value = NULL,
placeholder = "Species"
)
),
column(6,
actionButton(
'doSA',
'Run SA',
icon = icon('gear')
),
tags$style(
type = 'text/css',
"#doSA { width:100%; margin-top: 27px;}"
)
)
),
radioButtons(
"anaType",
"Sensitivity indices",
Expand All @@ -192,19 +218,6 @@ sidebarLayout(
"dHSIC" = "hsic"
)
),
textInput(
"SASpecies",
"Choose species",
width = "50%",
value = NULL,
placeholder = "Type species"
),
actionButton(
'doSA',
'Run SA',
icon = icon('gear')
),
hr(),
radioButtons(
"SAPlotType",
"Plot Type",
Expand Down
4 changes: 2 additions & 2 deletions ui_files/model.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ sidebarLayout(
sidebarPanel(
width = sideWidth,
h4("Model control"),
hr( style="border-color: #666;"),
# hr( style="border-color: #666;"),
verbatimTextOutput("contentsNmlMsg")
),
mainPanel(
Expand Down Expand Up @@ -84,7 +84,7 @@ sidebarLayout(
'netColoring',
'Color scheme',
choiceNames = list(
'Volpert','Charge','Radicals','Composition','Mass'
'Volpert','Charge','Radicals','Composition','Heavy atoms'
),
choiceValues = list(
'volpert','charge','radicals','compo','mass'
Expand Down
20 changes: 19 additions & 1 deletion ui_files/project.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,25 @@ sidebarLayout(
'Save Project',
icon = icon('gear')
)

),
br(),br(),br(),
wellPanel(
h4("About"),
hr(),
h5("Author : P. Pernot"),
h5("Affiliation : ",a(href="https://www.cnrs.fr/","CNRS")),
h5(paste0("Version : ",version)),
# h5("Date : 2022/09/19"),
br(),
a(href="https://github.com/ppernot/ReactorUI","How to cite..."),
br(),
a(href="https://github.com/ppernot/ReactorUI","code@github"),
br(),
a(href="https://github.com/ppernot/ReactorUI/issues",
"Bugs report, Features request"),
br(),
a(href="https://ppernot.github.io/ReactorUI",
"User's manual")
)
)
),
Expand Down
2 changes: 1 addition & 1 deletion ui_files/run.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ sidebarLayout(
sidebarPanel(
width = sideWidth,
h4("Run Reactor"),
hr( style="border-color: #666;"),
hr(),
uiOutput("nMCRunSelect"),
tabsetPanel(
tabPanel(
Expand Down

0 comments on commit e81de28

Please sign in to comment.