diff --git a/inst/ShinyApp/server.R b/inst/ShinyApp/server.R
index 55b4552af9596e852ec5863f4fa739ea056b44e5..d7bca876a42ba9e56ebf96d255c3512c185830e7 100644
--- a/inst/ShinyApp/server.R
+++ b/inst/ShinyApp/server.R
@@ -1,11 +1,24 @@
 server <- function(input, output, session){
 
 
+  ##--------------------------------------------
+  ##  Hide all inputs excepted actionButtons  --
+  ##--------------------------------------------
+  output$hide_pop_size <- eventReactive({
+    input$button_pop_size
+  },{
+    if(input$button_pop_size%%2 == 1) TRUE else FALSE
+  }, ignoreInit = TRUE)
+
+  outputOptions(output, "hide_pop_size", suspendWhenHidden = FALSE)
+
+
   ##--------------------------------------------
   ##  Hide all inputs excepted actionButtons  --
   ##--------------------------------------------
   observe({
-    shinyjs::hide("fatal_constant")
+
+    #shinyjs::hide("fatal_constant")
     shinyjs::hide("fatalities_input_type")
     shinyjs::hide("fatalities_mean")
     shinyjs::hide("fatalities_se")
@@ -13,16 +26,19 @@ server <- function(input, output, session){
     shinyjs::hide("fatalities_run_expert")
     shinyjs::hide("farm_number_cumulated")
     shinyjs::hide("fatalities_mat_cumulated")
-    shinyjs::hide("pop_size_type")
+
+    #shinyjs::hide("pop_size_unit")
     shinyjs::hide("pop_size_input_type")
     shinyjs::hide("pop_size_mean")
     shinyjs::hide("pop_size_se")
     shinyjs::hide("pop_size_mat_expert")
     shinyjs::hide("pop_size_run_expert")
+
     shinyjs::hide("carrying_cap_input_type")
     shinyjs::hide("carrying_capacity")
     shinyjs::hide("carrying_cap_mat_expert")
     shinyjs::hide("carrying_cap_run_expert")
+
     shinyjs::hide("pop_growth_input_type")
     shinyjs::hide("pop_growth_mean")
     shinyjs::hide("pop_growth_se")
@@ -30,17 +46,20 @@ server <- function(input, output, session){
     shinyjs::hide("pop_growth_run_expert")
     shinyjs::hide("pop_trend")
     shinyjs::hide("pop_trend_strength")
+
     shinyjs::hide("mat_fill_vr")
 
+
     # Show fatalities part
 
     if(input$button_fatalities%%2 == 1){
-      shinyjs::show("fatal_constant")
+      #shinyjs::show("fatal_constant")
 
       # Show inputs for none cumulated impacts scenario
 
       if(input$analysis_choice == "scenario"){
         shinyjs::show("fatalities_input_type")
+
         if(input$fatalities_input_type == "val"){
           shinyjs::show("fatalities_mean")
           shinyjs::show("fatalities_se")
@@ -63,7 +82,7 @@ server <- function(input, output, session){
     # Show inputs for population size part
 
     if(input$button_pop_size%%2 == 1){
-      shinyjs::show("pop_size_type")
+      #shinyjs::show("pop_size_unit")
       shinyjs::show("pop_size_input_type")
       if(input$pop_size_input_type == "val"){
         shinyjs::show("pop_size_mean")
@@ -109,7 +128,7 @@ server <- function(input, output, session){
     # Show inputs vital rates part
 
     if(input$button_vital_rates%%2 == 1){
-        shinyjs::show("mat_fill_vr")
+      shinyjs::show("mat_fill_vr")
     }
 
   }) # en observe show/hide
@@ -144,7 +163,7 @@ server <- function(input, output, session){
 
                           pop_size_mean = NULL,
                           pop_size_se = NULL,
-                          pop_size_type = NULL,
+                          pop_size_unit = NULL,
 
                           pop_growth_mean = NULL,
                           pop_growth_se = NULL,
@@ -168,7 +187,7 @@ server <- function(input, output, session){
                           pop_size_eli_result = NULL,
                           pop_growth_eli_result = NULL,
                           carrying_cap_eli_result = NULL
-                          )
+  )
   ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
 
@@ -187,7 +206,7 @@ server <- function(input, output, session){
     param$time_horzion = time_horzion
     param$coeff_var_environ = coeff_var_environ
 
-    }) # end observe
+  }) # end observe
   ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
 
@@ -220,7 +239,7 @@ server <- function(input, output, session){
   observeEvent({
     input$fatalities_input_type
   },{
-  output$fatalities_distri_plot <- renderPlot({ plot_gamma(mu = input$fatalities_mean, se = input$fatalities_se) })
+    output$fatalities_distri_plot <- renderPlot({ plot_gamma(mu = input$fatalities_mean, se = input$fatalities_se) })
   })
 
   ## Population size ###~~~~~~~~~~~~~~~~~~~~~~~~~~###
@@ -321,7 +340,7 @@ server <- function(input, output, session){
       ## run elicitation analysis
       output$carrying_cap_distri_plot <- renderPlot({
         plot_expert(param$carrying_cap_eli_result$out, show_se = FALSE)
-        })
+      })
 
     } else {
       print("missing value")
@@ -395,12 +414,12 @@ server <- function(input, output, session){
         print("Erreur: Vous n'avez pas lancer l'analyse 'valeurs experts'")
       }
 
-    # Case 2 : Values directly provided (i.e., not from expert elicitation)
+      # Case 2 : Values directly provided (i.e., not from expert elicitation)
     } else {
       param$pop_size_mean <- input$pop_size_mean
       param$pop_size_se <- input$pop_size_se
     }
-    param$pop_size_type <- input$pop_size_type
+    param$pop_size_unit <- input$pop_size_unit
   })
 
 
@@ -430,7 +449,7 @@ server <- function(input, output, session){
         print("Erreur: Vous n'avez pas lancer l'analyse 'valeurs experts'")
       }
 
-    # Case 2 : Trend information
+      # Case 2 : Trend information
     } else if(input$pop_growth_input_type == "trend"){
 
       if(input$pop_trend == "Croissance") {
@@ -454,7 +473,7 @@ server <- function(input, output, session){
       }
       param$pop_growth_se <- 0.03
 
-    # Case 3 : Values directly provided (i.e., not from expert elicitation)
+      # Case 3 : Values directly provided (i.e., not from expert elicitation)
     } else {
       param$pop_growth_mean <- round(min(1 + param$rMAX_species, input$pop_growth_mean), 2)
       param$pop_growth_se <- input$pop_growth_se
@@ -475,7 +494,9 @@ server <- function(input, output, session){
 
 
   # Observe carrying capacity
-  observeEvent({input$run}, {
+  observeEvent({
+    input$run
+  }, {
     if(input$carrying_cap_input_type == "eli_exp"){
       if(!(is.null(param$carrying_cap_eli_result))){
         param$carrying_capacity <- round(param$carrying_cap_eli_result$mean)
@@ -487,7 +508,9 @@ server <- function(input, output, session){
     }
   })
 
-  observeEvent({input$run}, {
+  observeEvent({
+    input$run
+  }, {
     print(param$pop_growth_mean)
     print(param$pop_growth_se)
   })
@@ -511,7 +534,7 @@ server <- function(input, output, session){
 
                                   pop_size_mean = param$pop_size_mean,
                                   pop_size_se = param$pop_size_se,
-                                  pop_size_type = param$pop_size_type,
+                                  pop_size_type = param$pop_size_unit,
 
                                   pop_growth_mean = param$pop_growth_mean,
                                   pop_growth_se = param$pop_growth_se,
@@ -557,7 +580,7 @@ server <- function(input, output, session){
   ##  Display General information             --
   ##--------------------------------------------
 
-  output$species_name <- renderText({ paste0("Espèce : ", as.character(input$species_choice)) })
+  #output$species_name <- renderText({ paste0("Espèce : ", as.character(input$species_choice)) })
 
 
   ## Fatalities
@@ -590,18 +613,10 @@ server <- function(input, output, session){
   })
 
 
-
-
-
-
-
-
-
-
   ## Poplutation size
 
-  output$pop_size_type_info <- renderText({
-    if(input$pop_size_type == "Npair"){
+  output$pop_size_unit_info <- renderText({
+    if(input$pop_size_unit == "Npair"){
       paste0("Nombre de couple")
     } else {
       paste0("Effectif total")
@@ -635,48 +650,56 @@ server <- function(input, output, session){
   ## Carrying capacity
 
   output$carrying_capacity_info <- renderText({
+
+    # N type
+    if(input$pop_size_unit == "Npair"){
+      info1 <- paste0("Nombre de couple : ")
+    } else {
+      info1 <- paste0("Effectif total : ")
+    }
+
+    # value of K
     if(input$carrying_cap_input_type == "eli_exp"){
       if(!(is.null(param$carrying_cap_eli_result))){
-        info <- round(param$carrying_cap_eli_result$mean)
+        info2 <- round(param$carrying_cap_eli_result$mean)
       } else {info <- NA}
     }
     else {
-      info <- input$carrying_capacity
+      info2 <- input$carrying_capacity
     }
-    paste0("Valeur : ", info)
+
+    # paste for printing
+    paste0(info1, info2)
   })
 
   ## Population growth
-
-  output$pop_trend_type_info <- renderText({paste0("Type de Tendance de pop : ", input$pop_growth_input_type)})
-
   output$pop_growth_mean_info <- renderText({
     if(input$pop_growth_input_type == "eli_exp"){
       if(!(is.null(param$pop_growth_eli_result))){
         info <- round(param$pop_growth_eli_result$mean, 2)
       } else {info <- NA}
     } else if(input$pop_growth_input_type == "trend"){
-        if(input$pop_trend == "Croissance") {
-          if(input$pop_trend_strength == "Faible") {
-            info <- 1.01
-          } else if(input$pop_trend_strength == "Moyen"){
-            info <- 1.03
-          } else {
-            info <- 1.06
-          }
-        } else if(input$pop_trend == "Déclin"){
-          if(input$pop_trend_strength == "Faible") {
-            info <- 0.99
-          } else if(input$pop_trend_strength == "Moyen"){
-            info <- 0.97
-          } else {
-            info <- 0.94
-          }
+      if(input$pop_trend == "Croissance") {
+        if(input$pop_trend_strength == "Faible") {
+          info <- 1.01
+        } else if(input$pop_trend_strength == "Moyen"){
+          info <- 1.03
+        } else {
+          info <- 1.06
+        }
+      } else if(input$pop_trend == "Déclin"){
+        if(input$pop_trend_strength == "Faible") {
+          info <- 0.99
+        } else if(input$pop_trend_strength == "Moyen"){
+          info <- 0.97
         } else {
-          info <- 1.00
+          info <- 0.94
         }
+      } else {
+        info <- 1.00
+      }
     } else {
-        info <- input$pop_growth_mean
+      info <- input$pop_growth_mean
     }
     paste0("Moyenne : ", info)
   })
@@ -697,12 +720,9 @@ server <- function(input, output, session){
 
 
   ## Vital rates
-
   output$vital_rates_info <- renderTable({
     input$mat_fill_vr
-    }, rownames = TRUE)
-
-  # End genral informations output
+  }, rownames = TRUE)
 
 
 
@@ -737,7 +757,7 @@ server <- function(input, output, session){
   }
 
 
-## Update the vital rate matrix when changing species in the list
+  ## Update the vital rate matrix when changing species in the list
   observeEvent({input$species_choice}, {
 
     if(input$species_choice == "Espèce générique") {} else {
@@ -768,6 +788,6 @@ server <- function(input, output, session){
   }) # end observeEvent species_list
 
 
-###################################################################################
+  ###################################################################################
 } # End server
 
diff --git a/inst/ShinyApp/ui.R b/inst/ShinyApp/ui.R
index 6d38db5081d70a06ad7f96400a8b0f53ddd3e261..d0a5a247c3ffbc1c61a1056a673cd89793ecb7d6 100644
--- a/inst/ShinyApp/ui.R
+++ b/inst/ShinyApp/ui.R
@@ -1,353 +1,382 @@
 rm(list = ls(all.names = TRUE))
 
-## Load libraries
-library(shiny)
-library(shinyjs)
-library(shinyMatrix)
-library(tidyverse)
-library(eolpop)
-
-
-## Load species list
-species_data <- read.csv("./inst/ShinyApp/species_list.csv", sep = ",")
-species_list <- unique(as.character(species_data$NomEspece))
-
-## Load survival and fecundities data
-data_sf <- read.csv("./inst/ShinyApp/survivals_fecundities_species.csv", sep = ",")#, encoding = "UTF-8")
-(data_sf)
-
-# Fixed parameters (for now)
-nsim = 10
-coeff_var_environ = 0.10
-time_horzion = 30
-theta = 1 # DD parameter theta
-
-#####################
-### Pre-fill data ###
-#####################
-
-## Data elicitation pre-fill data
-# fatalities
-eli_fatalities <- c(1.0, 2, 5, 8,  0.80,
-                    0.2, 0, 3, 6,  0.90,
-                    0.2, 2, 4, 10, 0.90,
-                    0.1, 1, 3, 7,  0.70)
-
-# population size
-eli_pop_size <-   c(1.0, 150, 200, 250, 0.80,
-                    0.5, 120, 180, 240, 0.90,
-                    0.8, 170, 250, 310, 0.90,
-                    0.3, 180, 200, 230, 0.70)
-
-# carrying capacity
-eli_carrying_cap <- c(1.0, 500, 700, 1000, 0.80,
-                      0.5, 1000, 1500, 2000, 0.90,
-                      0.8, 800, 1200, 1600, 0.90,
-                      0.3, 100, 1200, 1500, 0.70)
-
-# population growth rate
-eli_pop_growth <- c(1 , 0.95, 0.98, 1.00, 0.95,
-                    0.2, 0.97, 1.00, 1.01, 0.90,
-                    0.5, 0.92, 0.96, 0.99, 0.90,
-                    0.3, 0.90, 0.95, 0.98, 0.70)
-
-## Other pre-fill data
-# fatalities for several wind farms (cumulated impacts)
-init_cumul <- c(10, 5, 8,
-                0.05, 0.05, 0.05,
-                2010, 2015, 2018)
-
-init_cumul_add <- c(3, 0.05, 2020)
-
-###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
+#~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+# Initial stuff
+{
+  ## Load libraries
+  library(shiny)
+  library(shinyjs)
+  library(shinyMatrix)
+  library(tidyverse)
+  library(eolpop)
+
+  ## Load species list
+  species_data <- read.csv("./inst/ShinyApp/species_list.csv", sep = ",")
+  species_list <- unique(as.character(species_data$NomEspece))
+
+  ## Load survival and fecundities data
+  data_sf <- read.csv("./inst/ShinyApp/survivals_fecundities_species.csv", sep = ",")#, encoding = "UTF-8")
+  (data_sf)
+
+  # Fixed parameters (for now)
+  nsim = 10
+  coeff_var_environ = 0.10
+  time_horzion = 30
+  theta = 1 # DD parameter theta
+}
+#~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
+
+#~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+# Pre-fill data
+{
+  ## Data elicitation pre-fill data
+  # fatalities
+  eli_fatalities <- c(1.0, 2, 5, 8,  0.80,
+                      0.2, 0, 3, 6,  0.90,
+                      0.2, 2, 4, 10, 0.90,
+                      0.1, 1, 3, 7,  0.70)
+
+  # population size
+  eli_pop_size <-   c(1.0, 150, 200, 250, 0.80,
+                      0.5, 120, 180, 240, 0.90,
+                      0.8, 170, 250, 310, 0.90,
+                      0.3, 180, 200, 230, 0.70)
+
+  # carrying capacity
+  eli_carrying_cap <- c(1.0, 500, 700, 1000, 0.80,
+                        0.5, 1000, 1500, 2000, 0.90,
+                        0.8, 800, 1200, 1600, 0.90,
+                        0.3, 100, 1200, 1500, 0.70)
+
+  # population growth rate
+  eli_pop_growth <- c(1 , 0.95, 0.98, 1.00, 0.95,
+                      0.2, 0.97, 1.00, 1.01, 0.90,
+                      0.5, 0.92, 0.96, 0.99, 0.90,
+                      0.3, 0.90, 0.95, 0.98, 0.70)
+
+  ## Other pre-fill data
+  # fatalities for several wind farms (cumulated impacts)
+  init_cumul <- c(10, 5, 8,
+                  0.05, 0.05, 0.05,
+                  2010, 2015, 2018)
+
+  init_cumul_add <- c(3, 0.05, 2020)
+}
+#~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
 
 
 ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
-##--------------------------------------------
-##  User Interface                          --
-##--------------------------------------------
+##  User Interface
 ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
-ui <- fluidPage(
+# fluidPage
+{ui <- fluidPage(
+
   useShinyjs(),
   titlePanel("eolpop : Impact demographique des éoliennes"),
 
 
-  # Creation of the first page (select species, analysis type choice)
-  wellPanel(
-
-    selectInput(inputId = "species_choice", selected = 1,
-                h4(strong("Sélectionner une espèce")),
-                choices = species_list),
-
-    radioButtons(inputId = "analysis_choice",
-                 h4(strong("Sélectionner un type d'analyse")),
-                 choices = c("Impacts non cumulés" = "scenario", "Impacts cumulés" = "cumulated"))
-
-  ), # End wellPanel
-
-
-  ##--------------------------------------------
-  ##  General information                     --
-  ##--------------------------------------------
-
-  wellPanel(
-    h2("Valeurs actuelles"),
-
-    fluidRow(
-      column(width = 4,
-        div( textOutput(outputId = "species_name") ,
-             style="color:black; font-size:18px; font-weight: bold", align = "left"),
-      )
-    ),
-
-    fluidRow(
-      column(width = 4,
-
-             br(),
-             h3("Mortalités"),
-             textOutput(outputId = "fatalities_mean_info"),
-             textOutput(outputId = "fatalities_se_info"),
-
-             br(),
-             h3("Taille de la population"),
-             textOutput(outputId = "pop_size_type_info"),
-             textOutput(outputId = "pop_size_mean_info"),
-             textOutput(outputId = "pop_size_se_info")),
-
-        column(width = 4,
-
-               br(),
-               h3("Capacité de charge"),
-               textOutput(outputId = "carrying_capacity_info"),
-
-               br(),
-               h3("Tendance de la population"),
-               textOutput(outputId = "pop_trend_type_info"),
-               textOutput(outputId = "pop_growth_mean_info"),
-               textOutput(outputId = "pop_growth_se_info")),
-
-          column(width = 4,
+  ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
+  # Head Panel 1 : type of analysis and species
+  {wellPanel(
+    {fluidRow(
+
+      # Select type of analysis : cumulated impacted or not
+      {column(width = 4,
+              radioButtons(inputId = "analysis_choice",
+                           h4(strong("Sélectionner un type d'analyse")),
+                           choices = c("Impacts non cumulés" = "scenario", "Impacts cumulés" = "cumulated")),
+
+              selectInput(inputId = "species_choice",
+                          selected = 1, width = '80%',
+                          label = h4(strong("Sélectionner une espèce")),
+                          choices = species_list),
+      )}, # close column
+
+      # Show vital rate values
+      {column(width = 4,
+              fluidRow(
+                h4(strong("Paramètres démographiques")),
+                tableOutput(outputId = "vital_rates_info"),
+              ),
+      )}, # close column
+
+
+      ## Modify vital rates (if needed)
+      {column(width = 4,
+              tags$style(HTML('#button_vital_rates{background-color:#C2C8D3}')),
+              actionButton(inputId = "button_vital_rates",
+                           label = tags$span("Modifier les paramètres démographiques",
+                                             style = "font-weight: bold; font-size: 18px;")
+              ),
+
+              br(),
+              matrixInput(inputId = "mat_fill_vr",
+                          label = "",
+                          value = matrix(data = NA, 3, 2,
+                                         dimnames = list(c("Juv 1", "Juv 2", "Adulte"), c("Survie", "Fécondité"))),
+                          class = "numeric",
+                          rows = list(names = TRUE),
+                          cols = list(names = TRUE)
+              )
+
+      )}, # close column
+
+    )}, # End fluidRow
+  )}, # End wellPanel
+  ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
-                 br(),
-                 h3("Paramètres démographiques"),
-                 tableOutput(outputId = "vital_rates_info"))
 
-    ) # # End wellPanel
-  ), # End fluidRow
   ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
+  # Head Panel 2 : Model parameters
+  {wellPanel(
+
+    #h2("Saisie des paramètres"),
+    p("Saisie des paramètres", style="font-size:28px"),
+
+    {fluidRow(
+
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      ##  1. Fatalities
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      {column(width = 3,
+
+              tags$style(HTML('#button_fatalities{background-color:#C2C8D3}')),
+              actionButton(inputId = "button_fatalities",
+                           label = tags$span("Mortalités annuelles", style = "font-weight: bold; font-size: 18px;")
+              ),
+
+              br(""),
+
+              ### Part for non-cumulated impacts
+              # Input type
+              radioButtons(inputId = "fatalities_input_type",
+                           label = "Type de saisie",
+                           choices = c("Valeurs" = "val", "Elicitation d'expert" = "eli_exp")),
+
+              # Values
+              numericInput(inputId = "fatalities_mean",
+                           label = "Moyenne des mortalités annuelles",
+                           value = 5,
+                           min = 0, max = Inf, step = 0.5),
+              numericInput(inputId = "fatalities_se",
+                           label = "Erreur-type des mortalités annuelles",
+                           value = 0.05,
+                           min = 0, max = Inf, step = 0.1),
+
+              # Matrix for expert elicitation
+              matrixInput(inputId = "fatalities_mat_expert",
+                          value = matrix(data = eli_fatalities, nrow = 4, ncol = 5,
+                                         dimnames = list(c("#1", "#2", "#3", "#4"),
+                                                         c("Poids", "Min", "Best", "Max", "% IC" )),
+                                         byrow = TRUE),
+                          class = "numeric",
+                          rows = list(names = TRUE),
+                          cols = list(names = TRUE)),
+
+              actionButton(inputId = "fatalities_run_expert", label = "Utiliser valeurs experts"),
+
+              ### Part for cumulated impacts
+
+              numericInput(inputId = "farm_number_cumulated",
+                           label = "Nombre de parcs éoliens",
+                           value = 3, min = 2, max = Inf, step = 1),
+
+              matrixInput(inputId = "fatalities_mat_cumulated",
+                          value = matrix(init_cumul, 3, 3,
+                                         dimnames = list(c(paste0("Parc n°", c(1:3))),
+                                                         c("Moyenne",
+                                                           "Erreur-type",
+                                                           "Année de mise en service du parc"))),
+                          class = "numeric",
+                          rows = list(names = TRUE),
+                          cols = list(names = TRUE)),
+
+      )}, # end column "mortalité"
 
+      ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
 
-  ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
-  ##--------------------------------------------
-  ##  Paramter Inputs                         --
-  ##--------------------------------------------
-  sidebarLayout(
-    sidebarPanel(
-
-      h2("Modifier les paramètres"),
-
-      br(" "),
-      ##--------------------------------------------
-      ##  1. Fatalities                           --
-      ##--------------------------------------------
-      tags$style(HTML('#button_fatalities{background-color:#C2C8D3}')),
-      actionButton(inputId = "button_fatalities",
-                   label = tags$span("Mortalités annuelles", style = "font-weight: bold; font-size: 18px;")
-      ),
-
-      radioButtons(inputId = "fatal_constant",
-                   label = h4("Modélisation"),
-                   choices = c("Taux de mortalités (h) constant" = "h",
-                               "Nombre de mortalités (M) constant" = "M")),
-
-      ### Part for non-cumulated impacts
-      # Input type
-      radioButtons(inputId = "fatalities_input_type",
-                   label = h4("Type de saisie"),
-                   choices = c("Valeurs" = "val", "Elicitation d'expert" = "eli_exp")),
-
-      # Values
-      numericInput(inputId = "fatalities_mean",
-                   label = "Moyenne des mortalités annuelles",
-                   value = 5,
-                   min = 0, max = Inf, step = 0.5),
-      numericInput(inputId = "fatalities_se",
-                   label = "Erreur-type des mortalités annuelles",
-                   value = 0.05,
-                   min = 0, max = Inf, step = 0.1),
-
-      # Matrix for expert elicitation
-      matrixInput(inputId = "fatalities_mat_expert",
-                  value = matrix(data = eli_fatalities, nrow = 4, ncol = 5,
-                                 dimnames = list(c("#1", "#2", "#3", "#4"),
-                                                 c("Poids", "Min", "Best", "Max", "% IC" )),
-                                 byrow = TRUE),
-                  class = "numeric",
-                  rows = list(names = TRUE),
-                  cols = list(names = TRUE)),
-
-      actionButton(inputId = "fatalities_run_expert", label = "Utiliser valeurs experts"),
-
-      ### Part for cumulated impacts
-
-      numericInput(inputId = "farm_number_cumulated",
-                   label = "Nombre de parcs éoliens",
-                   value = 3, min = 2, max = Inf, step = 1),
-
-      matrixInput(inputId = "fatalities_mat_cumulated",
-                  value = matrix(init_cumul, 3, 3,
-                                 dimnames = list(c(paste0("Parc n°", c(1:3))),
-                                                 c("Moyenne",
-                                                   "Erreur-type",
-                                                   "Année de mise en service du parc"))),
-                  class = "numeric",
-                  rows = list(names = TRUE),
-                  cols = list(names = TRUE)),
-
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      ##  2. Population Size
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      {column(width = 3,
+
+              tags$style(HTML('#button_pop_size{background-color:#C2C8D3}')),
+              actionButton(inputId = "button_pop_size",
+                           label = tags$span("Taille de la population", style = "font-weight: bold; font-size: 18px;")
+              ),
+
+              br(""),
+
+              conditionalPanel("output.hide_pop_size",
+                               wellPanel(style = "background:#FFF8DC",
+                                 radioButtons(inputId = "pop_size_unit", inline = TRUE,
+                                              label = "Unité",
+                                              choices = c("Nombre de couple" = "Npair", "Effectif total" = "Ntotal"),
+                                              selected = "Ntotal"),
+                               ),
+              ),
+
+              radioButtons(inputId = "pop_size_input_type",
+                           label = "Type de saisie",
+                           choices = c("Valeurs" = "val", "Elicitation d'expert" = "eli_exp")),
+
+              numericInput(inputId = "pop_size_mean",
+                           label = "Moyenne de la taille de la population",
+                           value = 200,
+                           min = 0, max = Inf, step = 50),
+
+              numericInput(inputId = "pop_size_se",
+                           label = "Erreur-type de la taille de la population",
+                           value = 25,
+                           min = 0, max = Inf, step = 1),
+
+              matrixInput(inputId = "pop_size_mat_expert",
+                          value = matrix(data = eli_pop_size, nrow = 4, ncol = 5,
+                                         dimnames = list(c("#1", "#2", "#3", "#4"),
+                                                         c("Poids", "Min", "Best", "Max", "% IC" )),
+                                         byrow = TRUE),
+                          class = "numeric",
+                          rows = list(names = TRUE),
+                          cols = list(names = TRUE)),
+
+              actionButton(inputId = "pop_size_run_expert", label = "Utiliser valeurs experts"),
+
+      )}, # end column "mortalité"
       ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
-      hr(),
-      ##--------------------------------------------
-      ##  2. Population Size                      --
-      ##--------------------------------------------
-      tags$style(HTML('#button_pop_size{background-color:#C2C8D3}')),
-      actionButton(inputId = "button_pop_size",
-                   label = tags$span("Taille de la population", style = "font-weight: bold; font-size: 18px;")
-      ),
-
-      radioButtons(inputId = "pop_size_type",
-                   label = h4("Unité"),
-                   choices = c("Nombre de couple" = "Npair", "Effectif total" = "Ntotal"),
-                   selected = "Ntotal"),
-
-      radioButtons(inputId = "pop_size_input_type",
-                   label = h4("Type de saisie"),
-                   choices = c("Valeurs" = "val", "Elicitation d'expert" = "eli_exp")),
-
-      numericInput(inputId = "pop_size_mean",
-                   label = "Moyenne de la taille de la population",
-                   value = 200,
-                   min = 0, max = Inf, step = 50),
-
-      numericInput(inputId = "pop_size_se",
-                   label = "Erreur-type de la taille de la population",
-                   value = 25,
-                   min = 0, max = Inf, step = 1),
-
-      matrixInput(inputId = "pop_size_mat_expert",
-                  value = matrix(data = eli_pop_size, nrow = 4, ncol = 5,
-                                 dimnames = list(c("#1", "#2", "#3", "#4"),
-                                                 c("Poids", "Min", "Best", "Max", "% IC" )),
-                                 byrow = TRUE),
-                  class = "numeric",
-                  rows = list(names = TRUE),
-                  cols = list(names = TRUE)),
-
-      actionButton(inputId = "pop_size_run_expert", label = "Utiliser valeurs experts"),
+
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      ##  3. Population Growth
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      {column(width = 3,
+
+              tags$style(HTML('#button_pop_trend{background-color:#C2C8D3}')),
+              actionButton(inputId = "button_pop_trend",
+                           label = tags$span("Tendance de la population", style = "font-weight: bold; font-size: 18px;")
+              ),
+
+              br(""),
+              radioButtons(inputId = "pop_growth_input_type",
+                           label = "Type de saisie",
+                           choices = c("Taux de croissance" = "val",
+                                       "Elicitation d'expert" = "eli_exp",
+                                       "Tendance locale ou régionale" = "trend")),
+
+              numericInput(inputId = "pop_growth_mean",
+                           label = "Moyenne de la croissance de la population",
+                           value = 1.1,
+                           min = 0, max = Inf, step = 0.01),
+
+              numericInput(inputId = "pop_growth_se",
+                           label = "Erreur-type de la croissance de la population",
+                           value = 0.01,
+                           min = 0, max = Inf, step = 0.01),
+
+              matrixInput(inputId = "pop_growth_mat_expert",
+                          value = matrix(data = eli_pop_growth, nrow = 4, ncol = 5,
+                                         dimnames = list(c("#1", "#2", "#3", "#4"),
+                                                         c("Poids", "Min", "Best", "Max", "% IC" )),
+                                         byrow = TRUE),
+                          class = "numeric",
+                          rows = list(names = TRUE),
+                          cols = list(names = TRUE)),
+
+              actionButton(inputId = "pop_growth_run_expert", label = "Utiliser valeurs experts"),
+
+              radioButtons(inputId = "pop_trend",
+                           label = NULL,
+                           choices = c("Croissance", "Stable", "Déclin")),
+
+              radioButtons(inputId = "pop_trend_strength",
+                           label = NULL,
+                           choices = c("Faible", "Moyen", "Fort")),
+      )}, # end column "mortalité"
       ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
 
-      hr(),
-      ##--------------------------------------------
-      ##  3. Population Growth                    --
-      ##--------------------------------------------
-      tags$style(HTML('#button_pop_trend{background-color:#C2C8D3}')),
-      actionButton(inputId = "button_pop_trend",
-                   label = tags$span("Tendance de la population", style = "font-weight: bold; font-size: 18px;")
-                   ),
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      ##  4. Carrying capacity
+      ##~~~~~~~~~~~~~~~~~~~~~~~~~
+      {column(width = 3,
 
-      radioButtons(inputId = "pop_growth_input_type",
-                   label = h4("Type de saisie"),
-                   choices = c("Taux de croissance" = "val",
-                               "Elicitation d'expert" = "eli_exp",
-                               "Tendance locale ou régionale" = "trend")),
+              tags$style(HTML('#button_carrying_cap{background-color:#C2C8D3}')),
+              actionButton(inputId = "button_carrying_cap",
+                           label = tags$span("Capacité de charge", style = "font-weight: bold; font-size: 18px;")
+              ),
 
-      numericInput(inputId = "pop_growth_mean",
-                   label = "Moyenne de la croissance de la population",
-                   value = 1.1,
-                   min = 0, max = Inf, step = 0.01),
+              br(""),
+              radioButtons(inputId = "carrying_cap_input_type",
+                           label = "Type de saisie",
+                           choices = c("Valeurs" = "val", "Elicitation d'expert" = "eli_exp")),
 
-      numericInput(inputId = "pop_growth_se",
-                   label = "Erreur-type de la croissance de la population",
-                   value = 0.01,
-                   min = 0, max = Inf, step = 0.01),
+              numericInput(inputId = "carrying_capacity",
+                           label = "Capacité de charge",
+                           value = 500,
+                           min = 0, max = Inf, step = 100),
 
-      matrixInput(inputId = "pop_growth_mat_expert",
-                  value = matrix(data = eli_pop_growth, nrow = 4, ncol = 5,
-                                 dimnames = list(c("#1", "#2", "#3", "#4"),
-                                                 c("Poids", "Min", "Best", "Max", "% IC" )),
-                                 byrow = TRUE),
-                  class = "numeric",
-                  rows = list(names = TRUE),
-                  cols = list(names = TRUE)),
+              matrixInput(inputId = "carrying_cap_mat_expert",
+                          value = matrix(data = eli_carrying_cap, nrow = 4, ncol = 5,
+                                         dimnames = list(c("#1", "#2", "#3", "#4"),
+                                                         c("Poids", "Min", "Best", "Max", "% IC" )),
+                                         byrow = TRUE),
+                          class = "numeric",
+                          rows = list(names = TRUE),
+                          cols = list(names = TRUE)),
 
-      actionButton(inputId = "pop_growth_run_expert", label = "Utiliser valeurs experts"),
+              actionButton(inputId = "carrying_cap_run_expert", label = "Utiliser valeurs experts"),
 
-      radioButtons(inputId = "pop_trend",
-                   label = NULL,
-                   choices = c("Croissance", "Stable", "Déclin")),
+      )}, # end column "mortalité"
+      ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
-      radioButtons(inputId = "pop_trend_strength",
-                   label = NULL,
-                   choices = c("Faible", "Moyen", "Fort")),
 
+    )}, # # End fluidRow
 
-      ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
+  )}, # # End wellPanel
+  ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
 
-      hr(),
-      ##--------------------------------------------
-      ##  4. Carrying capacity                    --
-      ##--------------------------------------------
-      tags$style(HTML('#button_carrying_cap{background-color:#C2C8D3}')),
-      actionButton(inputId = "button_carrying_cap",
-                   label = tags$span("Capacité de charge", style = "font-weight: bold; font-size: 18px;")
-      ),
 
-      radioButtons(inputId = "carrying_cap_input_type",
-                   label = h4("Type de saisie"),
-                   choices = c("Valeurs" = "val", "Elicitation d'expert" = "eli_exp")),
+  ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
+  ##  Side Panel : Parameter information
+  {sidebarLayout(
+    {sidebarPanel(
 
-      numericInput(inputId = "carrying_capacity",
-                   label = "Capacité de charge",
-                   value = 500,
-                   min = 0, max = Inf, step = 100),
+      p("Valeurs saisies", style="font-size:28px"),
 
-      matrixInput(inputId = "carrying_cap_mat_expert",
-                  value = matrix(data = eli_carrying_cap, nrow = 4, ncol = 5,
-                                 dimnames = list(c("#1", "#2", "#3", "#4"),
-                                                 c("Poids", "Min", "Best", "Max", "% IC" )),
-                                 byrow = TRUE),
-                  class = "numeric",
-                  rows = list(names = TRUE),
-                  cols = list(names = TRUE)),
+      # Mortalités annuelles
+      {wellPanel(style = "background:#DCDCDC",
+                 p("Mortalités annuelles", style="font-size:20px; font-weight: bold"),
+                 span(textOutput(outputId = "fatalities_mean_info"), style="font-size:16px"),
+                 span(textOutput(outputId = "fatalities_se_info"), style="font-size:16px"),
+      )},
 
-      actionButton(inputId = "carrying_cap_run_expert", label = "Utiliser valeurs experts"),
+      # Taille de population
+      {wellPanel(style = "background:#DCDCDC",
+                 p("Taille de la population", style="font-size:20px; font-weight: bold"),
+                 shiny::tags$u(textOutput(outputId = "pop_size_unit_info"), style="font-size:16px"),
+                 p(""),
+                 span(textOutput(outputId = "pop_size_mean_info"), style="font-size:16px"),
+                 span(textOutput(outputId = "pop_size_se_info"), style="font-size:16px"),
 
-      ###~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
+      )},
 
+      # Tendance de la population
+      {wellPanel(style = "background:#DCDCDC",
+                 p("Tendance de la population", style="font-size:20px; font-weight: bold"),
+                 span(textOutput(outputId = "pop_growth_mean_info"), style="font-size:16px"),
+                 span(textOutput(outputId = "pop_growth_se_info"), style="font-size:16px"),
+      )},
 
-      hr(),
-      ##--------------------------------------------
-      ##  5. Vital rates                         --
-      ##--------------------------------------------
-      tags$style(HTML('#button_vital_rates{background-color:#C2C8D3}')),
-      actionButton(inputId = "button_vital_rates",
-                   label = tags$span("Paramètres démographiques", style = "font-weight: bold; font-size: 18px;")
-      ),
+      # Capacité de charge
+      {wellPanel(style = "background:#DCDCDC",
+                 p("Capacité de charge", style="font-size:20px; font-weight: bold"),
+                 span(textOutput(outputId = "carrying_capacity_info"), style="font-size:16px"),
+      )},
 
-      br(),
-      matrixInput(inputId = "mat_fill_vr",
-                  label = "",
-                  value = matrix(data = NA, 3, 2,
-                                 dimnames = list(c("Juv 1", "Juv 2", "Adulte"), c("Survie", "Fécondité"))),
-                  class = "numeric",
-                  rows = list(names = TRUE),
-                  cols = list(names = TRUE))
 
-    ), # End sidebarPanel
+    )}, # End sidebarPanel
 
 
     #~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -356,7 +385,7 @@ ui <- fluidPage(
 
     # Creation of outputs parts
 
-    mainPanel(
+    {mainPanel(
       tabsetPanel(
         tabPanel(title = "Distribution paramètres",
                  br(),
@@ -384,11 +413,22 @@ ui <- fluidPage(
 
 
         tabPanel(title = "Impact population",
-                 strong(span(textOutput("message"), style="color:blue; font-size:24px", align = "center")),
-                 br(),
+
                  numericInput(inputId = "nsim", label = "Nombre de simulations",
                               value = 50, min = 0, max = Inf, step = 10),
+
+                 ###### A DEPLACER #############
+                 radioButtons(inputId = "fatal_constant",
+                              label = h4("Modélisation"),
+                              choices = c("Taux de mortalités (h) constant" = "h",
+                                          "Nombre de mortalités (M) constant" = "M")),
+                 ###############################
+
+                 br(),
+
+                 strong(span(textOutput("message"), style="color:blue; font-size:24px", align = "center")),
                  br(),
+
                  actionButton(inputId = "run", label = "Lancer l'analyse"),
                  hr(),
                  h4("Graphique : Impact relatif de chaque scénario", align = "center"),
@@ -417,9 +457,11 @@ ui <- fluidPage(
         ) # End tabPanel
 
       ) # End tabSetPanel
-    ) # End mainPanel
+    )} # End mainPanel
+
+  )} # sidebarLayout
+
+)} # FluidPage
 
-  ) # sidebarLayout
-) # FluidPage
+# End UI #~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~###
 
-# End UI