From 7e2b3fc2238bf43e5d2440e91b0a08252c4e66ea Mon Sep 17 00:00:00 2001
From: "louis.heraut" <louis.heraut@inrae.fr>
Date: Tue, 14 Dec 2021 16:31:24 +0100
Subject: [PATCH] Mini map

---
 plotting/layout.R |  67 +++++++--
 plotting/panel.R  | 372 +++++++++++++++++++++++++++++-----------------
 script.R          |  13 +-
 3 files changed, 294 insertions(+), 158 deletions(-)

diff --git a/plotting/layout.R b/plotting/layout.R
index c9cbee5..0e5fa15 100644
--- a/plotting/layout.R
+++ b/plotting/layout.R
@@ -14,7 +14,7 @@ library(RColorBrewer)
 source('plotting/panel.R', encoding='latin1')
 
 
-panels_layout = function (df_data, df_meta, layout_matrix, figdir='', filedir_opt='', filename_opt='', variable='', df_trend=NULL, p_threshold=0.1, unit2day=365.25, type='', trend_period=NULL, mean_period=NULL, axis_xlim=NULL, missRect=FALSE, time_header=NULL, info_header=TRUE, time_ratio=2, var_ratio=3, fr_shpdir=NULL, fr_shpname=NULL,  bs_shpdir=NULL, bs_shpname=NULL, rv_shpdir=NULL, rv_shpname=NULL, computer_data_path=NULL) {
+panels_layout = function (df_data, df_meta, layout_matrix, figdir='', filedir_opt='', filename_opt='', variable='', df_trend=NULL, p_threshold=0.1, unit2day=365.25, type='', trend_period=NULL, mean_period=NULL, axis_xlim=NULL, missRect=FALSE, time_header=NULL, info_header=TRUE, info_ratio=1, time_ratio=2, var_ratio=3, fr_shpdir=NULL, fr_shpname=NULL,  bs_shpdir=NULL, bs_shpname=NULL, rv_shpdir=NULL, rv_shpname=NULL, computer_data_path=NULL) {
     
     outfile = "Panels"
     if (filename_opt != '') {
@@ -206,13 +206,22 @@ panels_layout = function (df_data, df_meta, layout_matrix, figdir='', filedir_op
         print(paste("Plotting for station :", code))
         
         nbh = as.numeric(info_header) + as.numeric(!is.null(time_header))
-        nbg = nbp + nbh
+        nbg = nbp + nbh 
 
         P = vector(mode='list', length=nbg)
 
         if (info_header) {
-            Htext = text_panel(code, df_meta)
-            P[[1]] = Htext
+            Hinfo = info_panel(list_df2plot, 
+                               df_meta,
+                               computer_data_path=computer_data_path,
+                               fr_shpdir=fr_shpdir,
+                               fr_shpname=fr_shpname,
+                               bs_shpdir=bs_shpdir,
+                               bs_shpname=bs_shpname,
+                               rv_shpdir=rv_shpdir,
+                               rv_shpname=rv_shpname,
+                               codeLight=code)
+            P[[1]] = Hinfo
         }
 
         if (!is.null(time_header)) {
@@ -227,8 +236,9 @@ panels_layout = function (df_data, df_meta, layout_matrix, figdir='', filedir_op
 
             P[[2]] = Htime
         }
-
-
+        
+        # map = map_panel()
+        
         nbcol = ncol(as.matrix(layout_matrix))
         for (i in 1:nbp) {
             df_data = list_df2plot[[i]]$data
@@ -294,10 +304,9 @@ panels_layout = function (df_data, df_meta, layout_matrix, figdir='', filedir_op
                            unit2day=unit2day, last=(i > nbp-nbcol),
                            color=color)
             
-            P[[i+nbh]] = p
+            P[[i+nbh]] = p 
+        }   
 
-        }
-        
         layout_matrix = as.matrix(layout_matrix)
         nel = nrow(layout_matrix)*ncol(layout_matrix)
 
@@ -310,23 +319,57 @@ panels_layout = function (df_data, df_meta, layout_matrix, figdir='', filedir_op
         layout_matrix_H = layout_matrix + nbh
 
 
+        info_ratio_scale = info_ratio
+        time_ratio_scale = time_ratio
+        var_ratio_scale = var_ratio
+
+        ndec_info = 0
+        ndec_time = 0
+        ndec_var = 0
+
+        if (info_ratio_scale != round(info_ratio_scale)) {
+            ndec_info = nchar(gsub('^[0-9]+.', '',
+                                   as.character(info_ratio_scale)))
+        }
+
+        if (time_ratio_scale != round(time_ratio_scale)) {
+            ndec_time = nchar(gsub('^[0-9]+.', '',
+                                   as.character(time_ratio_scale)))
+        }
+        
+        if (var_ratio_scale != round(var_ratio_scale)) {
+            ndec_var = nchar(gsub('^[0-9]+.', '',
+                                  as.character(var_ratio_scale)))
+        }
+        
+        ndec = max(c(ndec_info, ndec_time, ndec_var))
+        
+        info_ratio_scale = info_ratio_scale * 10^ndec
+        time_ratio_scale = time_ratio_scale * 10^ndec
+        var_ratio_scale = var_ratio_scale * 10^ndec
+        
         LM = c()
         LMcol = ncol(layout_matrix_H)
         LMrow = nrow(layout_matrix_H)
         for (i in 1:(LMrow+nbh)) {
 
             if (info_header & i == 1) {
-                LM = rbind(LM, rep(i, times=LMcol))
+                # LM = rbind(LM, rep(i, times=LMcol))
+                LM = rbind(LM,
+                           matrix(rep(rep(i, times=LMcol),
+                                      times=info_ratio_scale),
+                                  ncol=LMcol, byrow=TRUE))
+                
             } else if (!is.null(time_header) & i == 2) {
                 LM = rbind(LM,
                            matrix(rep(rep(i, times=LMcol),
-                                      times=time_ratio),
+                                      times=time_ratio_scale),
                                   ncol=LMcol, byrow=TRUE))
 
             } else {
                 LM = rbind(LM, 
                            matrix(rep(layout_matrix_H[i-nbh,],
-                                      times=var_ratio),
+                                      times=var_ratio_scale),
                                   ncol=LMcol, byrow=TRUE))
             }}
 
diff --git a/plotting/panel.R b/plotting/panel.R
index 98c1040..aaabd49 100644
--- a/plotting/panel.R
+++ b/plotting/panel.R
@@ -1101,7 +1101,7 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, slice=NULL, outdi
 
 
 
-map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdir, fr_shpname, bs_shpdir=bs_shpdir, bs_shpname=bs_shpname, rv_shpdir, rv_shpname, outdirTmp) {
+map_panel = function (list_df2plot, df_meta, computer_data_path, fr_shpdir, fr_shpname, bs_shpdir, bs_shpname, rv_shpdir, rv_shpname, idPer=1, outdirTmp='', codeLight=NULL, margin=TRUE) {
     
     fr_shppath = file.path(computer_data_path, fr_shpdir, fr_shpname)
     rv_shppath = file.path(computer_data_path, rv_shpdir, rv_shpname)
@@ -1235,6 +1235,10 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
     
     for (i in 1:nbp) {
         
+        if (i > 1 & !is.null(codeLight)) {
+            break
+        }
+        
         outname = paste('map_', i, sep='')
         print(paste('map :', outname))
 
@@ -1242,8 +1246,13 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
         
         map = ggplot() + theme_ash +
             
-            theme(panel.border = element_blank()) +
-        
+            theme(
+                # panel.border=element_blank(),
+                  axis.text.x=element_blank(),
+                  axis.text.y=element_blank(),
+                  axis.ticks.x=element_blank(),
+                  axis.ticks.y=element_blank()) +
+            
             coord_fixed() +
             
             geom_polygon(data=df_france,
@@ -1251,8 +1260,8 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
                          color=NA, fill="grey97") +
             
             # geom_path(data=df_river,
-            # aes(x=lon, y=lat, group=group),
-            # color="grey85", size=0.15) +
+                      # aes(x=long, y=lat, group=group),
+                      # color="grey85", size=0.3) +
             
             geom_polygon(data=df_bassin,
                          aes(x=long, y=lat, group=group),
@@ -1261,19 +1270,55 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
             geom_polygon(data=df_france,
                          aes(x=long, y=lat, group=group),
                          color="grey40", fill=NA, size=0.2)
+        
+        xlim = c(280000, 790000)
+        ylim = c(6110000, 6600000)
+        
 
-        map = map +
-                        
-            coord_sf(xlim=c(280000, 790000),
-                     ylim=c(6110000, 6600000),
+        if (is.null(codeLight)) {
+            xmin = gpct(7, xlim, shift=TRUE)
+            xint = c(0, 10*1E3, 50*1E3, 100*1E3)
+            ymin = gpct(5, ylim, shift=TRUE)
+            ymax = ymin + gpct(1, ylim)
+            
+            map = map +
+                
+                geom_line(aes(x=c(xmin, max(xint)+xmin),
+                              y=c(ymin, ymin)),
+                          color="grey40", size=0.2) +
+                annotate("text",
+                         x=max(xint)+xmin+gpct(1, xlim), y=ymin,
+                         vjust=0, hjust=0, label="km",
+                         color="grey40", size=3)
+
+            for (x in xint) {
+                map = map +
+                    annotate("segment",
+                             x=x+xmin, xend=x+xmin, y=ymin, yend=ymax,
+                             color="grey40", size=0.2) +
+                    annotate("text",
+                             x=x+xmin, y=ymax+gpct(0.5, ylim),
+                             vjust=0, hjust=0.5, label=x/1E3,
+                             color="grey40", size=3)
+            }
+        }
+        
+        map = map +          
+            coord_sf(xlim=xlim, ylim=ylim,
                      expand=FALSE)
 
-        map = map +
-            theme(plot.margin=margin(t=5, r=0, b=5, l=5, unit="mm"))
-
+        if (margin) {
+            map = map +
+                theme(plot.margin=margin(t=5, r=0, b=5, l=5, unit="mm"))
+        } else {
+            map = map +
+                theme(plot.margin=margin(t=0, r=0, b=0, l=0, unit="mm"))
+        }
+        
         lon = c()
         lat = c()
         fill = c()
+        shape = c()
         
         for (code in Code) {
             
@@ -1302,20 +1347,29 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
             
             dataMean = mean(df_data_code_per$Qm3s, na.rm=TRUE)
             trendMean = df_trend_code_per$trend / dataMean
-            
-            if (df_trend_code_per$p <= p_threshold){
-                color_res = get_color(trendMean, 
+
+            color_res = get_color(trendMean, 
                                       minTrendMean[idPer, i],
                                       maxTrendMean[idPer, i],
                                       palette_name='perso',
                                       reverse=TRUE,
                                       ncolor=ncolor,
-                                      nbTick=nbTick)
+                                  nbTick=nbTick)
+            
+            if (df_trend_code_per$p <= p_threshold){
+                filltmp = color_res$color
+                palette = color_res$palette
+
+                if (trendMean >= 0) {
+                    shapetmp = 24
+                } else {
+                    shapetmp = 25
+                }
                 
+            } else {                
                 filltmp = color_res$color
                 palette = color_res$palette
-            } else { 
-                filltmp = 'grey97'
+                shapetmp = 21
             }
 
             lontmp =
@@ -1326,32 +1380,51 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
             lon = c(lon, lontmp)
             lat = c(lat, lattmp)
             fill = c(fill, filltmp)
-
-            plot_map = tibble(lon=lon, lat=lat, fill=fill)
+            shape = c(shape, shapetmp)
 
         }
+        
+        plot_map = tibble(lon=lon, lat=lat, fill=fill,
+                          shape=shape, code=Code)
 
-        for (k in nCode) {
+        if (is.null(codeLight)) {
             map = map +
                 geom_point(data=plot_map,
                            aes(x=lon, y=lat),
-                           shape=21, size=5, stroke=1,
+                           shape=shape, size=5, stroke=1,
                            color='grey50', fill=fill)
+        } else {
+            plot_map_codeNo = plot_map[plot_map$code != codeLight,]
+            plot_map_code = plot_map[plot_map$code == codeLight,]
+            
+            map = map +
+                
+                geom_point(data=plot_map_codeNo,
+                           aes(x=lon, y=lat),
+                           shape=21, size=1, stroke=1,
+                           color='grey70', fill='grey70') +
+                
+                geom_point(data=plot_map_code,
+                           aes(x=lon, y=lat),
+                           shape=21, size=2, stroke=1,
+                           color='#00A3A8', fill='#00A3A8')
         }
-
-
+                
         idTick = color_res$idTick
         labTick = color_res$labTick
         colTick = color_res$colTick
-        ncolorShow = length(color_res$palette)
+        
+        nbTickmod = length(idTick)
 
-        labTick = as.character(round(labTick*100, 2))
+        valNorm = nbTickmod * 10
+        ytick = idTick / max(idTick) * valNorm
         
-        xtick = rep(0, times=nbTick)
+        labTick = as.character(round(labTick*100, 2))
+       
+        xtick = rep(0, times=nbTickmod)
 
-        plot_palette = tibble(xtick=xtick, ytick=idTick,
+        plot_palette = tibble(xtick=xtick, ytick=ytick,
                               colTick=colTick, labTick=labTick)
-
         
         title = ggplot() + theme_void() +
             
@@ -1361,8 +1434,8 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
                      hjust=0, vjust=0,
                      size=10, color="#00A3A8") +
             
-            geom_line(aes(x=c(-0.3, 3), y=c(0.05, 0.05)),
-                      size=0.5, color="#00A3A8") +
+            geom_line(aes(x=c(-0.3, 3.3), y=c(0.05, 0.05)),
+                      size=0.6, color="#00A3A8") +
             
             scale_x_continuous(limits=c(-1, 1 + 3),
                                expand=c(0, 0)) +
@@ -1378,12 +1451,26 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
             geom_point(data=plot_palette,
                        aes(x=xtick, y=ytick),
                        shape=21, size=5, stroke=1,
-                       color='grey50', fill=colTick)
+                       color='white', fill=colTick)
 
-        for (j in 1:nbTick) {
+        pal = pal +
+            
+            annotate('text',
+                     x=-0.3, y= valNorm + 23,
+                     label="Tendance",
+                     hjust=0, vjust=0.5,
+                     size=6, color='grey40') +
+            
+            annotate('text',
+                     x=-0.2, y= valNorm + 13,
+                     label=bquote(bold("% par an")),
+                     hjust=0, vjust=0.5,
+                     size=4, color='grey40')
+
+        for (j in 1:nbTickmod) {
             pal = pal +
                 annotate('text', x=xtick[j]+0.3,
-                         y=idTick[j],
+                         y=ytick[j],
                          label=bquote(bold(.(labTick[j]))),
                          hjust=0, vjust=0.7, 
                          size=3, color='grey40')
@@ -1392,35 +1479,46 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
         pal = pal +
             
             geom_point(aes(x=0, y=-20),
-                       shape=21, size=5, stroke=1,
+                       shape=24, size=4, stroke=1,
                        color='grey50', fill='grey97') +
             
             annotate('text',
                      x=0.3, y=-20,
-                     label=bquote(bold("non significatif à 10%")),
-                     hjust=0, vjust=0.7,
+                     label=bquote(bold("Hausse significative à 10%")),
+                     hjust=0, vjust=0.5,
                      size=3, color='grey40')
 
         pal = pal +
             
+            geom_point(aes(x=0, y=-29),
+                       shape=21, size=4, stroke=1,
+                       color='grey50', fill='grey97') +
+            
             annotate('text',
-                     x=-0.3, y=ncolorShow + 29,
-                     label="Tendance",
-                     hjust=0, vjust=0.5,
-                     size=6, color='grey40') +
+                     x=0.3, y=-29,
+                     label=bquote(bold("Non significatif à 10%")),
+                     hjust=0, vjust=0.7,
+                     size=3, color='grey40')
+
+        pal = pal +
+            
+            geom_point(aes(x=0, y=-40),
+                       shape=25, size=4, stroke=1,
+                       color='grey50', fill='grey97') +
             
             annotate('text',
-                     x=-0.2, y=ncolorShow + 16,
-                     label=bquote(bold("% par an")),
+                     x=0.3, y=-40,
+                     label=bquote(bold("Baisse significative à 10%")),
                      hjust=0, vjust=0.5,
-                     size=4, color='grey40')
+                     size=3, color='grey40')
+       
             
         pal = pal +
             
             scale_x_continuous(limits=c(-1, 1 + 3),
                                expand=c(0, 0)) +
             
-            scale_y_continuous(limits=c(-55, ncolorShow + 45),
+            scale_y_continuous(limits=c(-60, valNorm + 35),
                                expand=c(0, 0)) +
             
             theme(plot.margin=margin(t=0, r=5, b=5, l=0, unit="mm"))
@@ -1432,23 +1530,39 @@ map_panel = function (list_df2plot, df_meta, idPer, computer_data_path, fr_shpdi
                                            matrix(c(1, 1, 1, 2,
                                                     1, 1, 1, 3),
                                                   nrow=2, byrow=TRUE))
-        
-        # Saving matrix plot
-        ggsave(plot=plot,
-               path=outdirTmp,
-               filename=paste(outname, '.pdf', sep=''),
-               width=29.7, height=21, units='cm', dpi=100)
+
+        if (is.null(codeLight)) {
+            # Saving matrix plot
+            ggsave(plot=plot,
+                   path=outdirTmp,
+                   filename=paste(outname, '.pdf', sep=''),
+                   width=29.7, height=21, units='cm', dpi=100)
+        }
     }
+    return (map)
 }
 
 
 
 
-text_panel = function(code, df_meta) {
-    df_meta_code = df_meta[df_meta$code == code,]
+info_panel = function(list_df2plot, df_meta, computer_data_path, fr_shpdir, fr_shpname, bs_shpdir, bs_shpname, rv_shpdir, rv_shpname, codeLight) {
+
+    map =  map_panel(list_df2plot, 
+                     df_meta,
+                     computer_data_path=computer_data_path,
+                     fr_shpdir=fr_shpdir,
+                     fr_shpname=fr_shpname,
+                     bs_shpdir=bs_shpdir,
+                     bs_shpname=bs_shpname,
+                     rv_shpdir=rv_shpdir,
+                     rv_shpname=rv_shpname,
+                     codeLight=codeLight,
+                     margin=FALSE)
+    
+    df_meta_code = df_meta[df_meta$code == codeLight,]
 
     text1 = paste(
-        "<b>", code, '</b>  -  ', df_meta_code$nom, ' &#40;',
+        "<b>", codeLight, '</b>  -  ', df_meta_code$nom, ' &#40;',
         df_meta_code$region_hydro, '&#41;', 
         sep='')
 
@@ -1472,31 +1586,6 @@ text_panel = function(code, df_meta) {
         "</b>",
         sep='')
 
-    # text3 = paste(
-    #     "<b>",
-    #     "Superficie : ", df_meta_code$surface_km2_IN, 
-    #     ' (', df_meta_code$surface_km2_BH, ')', "  [km<sup>2</sup>] <br>",
-    #     "X = ", df_meta_code$L93X_m_IN, 
-    #     ' (', df_meta_code$L93X_m_BH, ')', "  [m ; Lambert 93]", 
-    #     "</b>",
-    #     sep='')
-        
-    # text4 = paste(
-    #     "<b>",
-    #     "Altitude : ", df_meta_code$altitude_m_IN, 
-    #     ' (', df_meta_code$altitude_m_BH, ')', "  [m]<br>",
-    #     "Y = ", df_meta_code$L93Y_m_IN, 
-    #     ' (', df_meta_code$L93Y_m_BH, ')', "  [m ; Lambert 93]",
-    #     "</b>",
-    #     sep='')
-
-    # text5 = paste(
-    #     "<b>",
-    #     "INRAE (Banque Hydro)<br>",
-    #     "INRAE (Banque Hydro)",
-    #     "</b>",
-    #     sep='')
-
     gtext1 = richtext_grob(text1,
                            x=0, y=1,
                            margin=unit(c(t=5, r=5, b=0, l=5), "mm"),
@@ -1521,20 +1610,17 @@ text_panel = function(code, df_meta) {
                            hjust=0, vjust=1,
                            gp=gpar(col="grey20", fontsize=9))
 
-    # gtext5 = richtext_grob(text5,
-                           # x=0, y=1,
-                           # margin=unit(c(t=0, r=5, b=5, l=5), "mm"),
-                           # hjust=0, vjust=1,
-                           # gp=gpar(col="grey20", fontsize=9))
+    P = list(gtext1, gtext2, gtext3, gtext4, map)
     
-    gtext_merge = grid.arrange(grobs=list(gtext1, gtext2, gtext3, 
-                                          gtext4),#, gtext5), 
-                               layout_matrix=matrix(c(1, 1, 1,
-                                                      2, 2, 2,
-                                                      3, 4, 5),
-                                                    nrow=3, 
-                                                    byrow=TRUE))
-    return(gtext_merge)
+    plot = grid.arrange(grobs=P,
+                        layout_matrix=matrix(c(1, 1, 1,
+                                               2, 2, 5,
+                                               2, 2, 5,
+                                               3, 4, 5,
+                                               3, 4, 5),
+                                             nrow=5, 
+                                             byrow=TRUE))
+    return(plot)
 }
 
 
@@ -1666,77 +1752,83 @@ cumulative = function (data_bin, df_meta, dyear=10, figdir='', filedir_opt='') {
 get_color = function (value, min, max, ncolor=256, palette_name='perso', reverse=FALSE, nbTick=10) {
     
     if (palette_name == 'perso') {
-        palette = colorRampPalette(c(
-            # '#1a4157',
-            # '#00af9d',
-            # '#fbdd7e',
-            # '#fdb147',
-            # '#fd4659'
-
-            '#0f3b57',
-            '#1d7881',
-            '#80c4a9',
-            '#e2dac6', #mid
-            '#fadfad',
-            '#d08363',
-            '#7e392f'
-
-            # '#193830',
-            # '#2A6863',
-            # '#449C93',
-            # '#7ACEB9',
-            # '#BCE6DB',
-            # '#EFE0B0',
-            # '#D4B86A',
-            # '#B3762A',
-            # '#7F4A23',
-            # '#452C1A'
-
-        ))(ncolor)
-        
+        colorList = c('#0f3b57',
+                      '#1d7881',
+                      '#80c4a9',
+                      '#e2dac6', #mid
+                      '#fadfad',
+                      '#d08363',
+                      '#7e392f')
     } else {
-        palette = colorRampPalette(brewer.pal(11, palette_name))(ncolor)
+        colorList = brewer.pal(11, palette_name)
     }
+    
+    nSample = length(colorList)
+    
+    palette = colorRampPalette(colorList)(ncolor)
+    Sample_hot = 1:(as.integer(nSample/2)+1)
+    Sample_cold = (as.integer(nSample/2)+1):nSample
+
+    palette_hot = colorRampPalette(colorList[Sample_hot])(ncolor)
+    palette_cold = colorRampPalette(colorList[Sample_cold])(ncolor)
 
     if (reverse) {
         palette = rev(palette)
+        palette_hot = rev(palette_hot)
+        palette_cold = rev(palette_cold)
     }
-    
-    palette_cold = palette[1:as.integer(ncolor/2)]
-    palette_hot = palette[(as.integer(ncolor/2)+1):ncolor]
-
-    ncolor_cold = length(palette_cold)
-    ncolor_hot = length(palette_hot)
 
     if (value < 0) {
         idNorm = (value - min) / (0 - min)
-        id = round(idNorm*(ncolor_cold - 1) + 1, 0)
+        id = round(idNorm*(ncolor - 1) + 1, 0)
         color = palette_cold[id]
     } else {
         idNorm = (value - 0) / (max - 0)
-        id = round(idNorm*(ncolor_hot - 1) + 1, 0)
+        id = round(idNorm*(ncolor - 1) + 1, 0)
         color = palette_hot[id]
     }    
 
     if (min < 0 & max < 0) {
         paletteShow = palette_cold
+        idTick = c()
+        for (i in 1:nbTick) {
+            id = round((ncolor-1)/(nbTick-1)*(i-1)) + 1
+            idTick = c(idTick, id)
+        }
+        labTick = seq(min, max, length.out=nbTick)
+        colTick = paletteShow[idTick]
+        
     } else if (min > 0 & max > 0) {
         paletteShow = palette_hot
+        idTick = c()
+        for (i in 1:nbTick) {
+            id = round((ncolor-1)/(nbTick-1)*(i-1)) + 1
+            idTick = c(idTick, id)
+        }
+        labTick = seq(min, max, length.out=nbTick)
+        colTick = paletteShow[idTick]
+        
     } else {
         paletteShow = palette
-    }
+        nbSemiTick = round(nbTick/2) + 1
 
-    ncolorShow = length(paletteShow)
-    
-    idTick = c()
-    for (i in 1:nbTick) {
-        id = round((ncolorShow-1)/(nbTick-1)*(i-1)) + 1
-        idTick = c(idTick, id)
+        idSemiTick = c()
+        for (i in 1:nbSemiTick) {
+            id = round((ncolor-1)/(nbSemiTick-1)*(i-1)) + 1
+            idSemiTick = c(idSemiTick, id)
+        }
+        
+        labTick_hot = seq(0, max, length.out=nbSemiTick)
+        labTick_cold = seq(min, 0, length.out=nbSemiTick)
+
+        colTick_hot = palette_hot[idSemiTick]
+        colTick_cold = palette_cold[idSemiTick]
+
+        idTick = as.integer(seq(1, ncolor, length.out=nbTick+1))
+        labTick = c(labTick_cold, labTick_hot[-1])
+        colTick = c(colTick_cold, colTick_hot[-1])
     }
-    
-    labTick = seq(min, max, length.out=nbTick)
-    colTick = paletteShow[idTick]
-    
+ 
     return(list(color=color, palette=paletteShow,
                 idTick=idTick, labTick=labTick, colTick=colTick))
 }
diff --git a/script.R b/script.R
index fd979cb..210bcd2 100644
--- a/script.R
+++ b/script.R
@@ -22,7 +22,7 @@ filedir =
 ### MANUAL SELECTION ###
 # Name of the file that will be analysed from the AG directory
 filename =
-    ""
+    # ""
 
     # c(
       # "S2235610_HYDRO_QJM.txt", 
@@ -32,9 +32,9 @@ filename =
       # "A2250310_HYDRO_QJM.txt"
       # )
 
-    # c("S4214010_HYDRO_QJM.txt",
-      # "Q6332510_HYDRO_QJM.txt",
-      # "Q7002910_HYDRO_QJM.txt")
+    c("S4214010_HYDRO_QJM.txt",
+      "O0384010_HYDRO_QJM.txt",
+      "Q7002910_HYDRO_QJM.txt")
 
 
 
@@ -44,8 +44,8 @@ AGlistdir =
     ""
 
 AGlistname = 
-    # ""
-    "Liste-station_RRSE.docx" 
+    ""
+    # "Liste-station_RRSE.docx" 
 
 
 ### NIVALE SELECTION ###
@@ -246,6 +246,7 @@ panels_layout(list(res_QAtrend$data, res_QMNAtrend$data,
               mean_period=mean_period,
               info_header=TRUE,
               time_header=df_data,
+              info_ratio=2, 
               time_ratio=2, 
               var_ratio=3,
               computer_data_path=computer_data_path,
-- 
GitLab