From 7bc064d054a95f8d9570dcd51cd6f615a343a342 Mon Sep 17 00:00:00 2001
From: "louis.heraut" <louis.heraut@inrae.fr>
Date: Tue, 23 Nov 2021 11:24:24 +0100
Subject: [PATCH] Plot modularity

---
 plotting/panel.R | 93 +++++++++++++++++++++++++++++++++++-------------
 script.R         | 42 ++++++++++++++--------
 2 files changed, 96 insertions(+), 39 deletions(-)

diff --git a/plotting/panel.R b/plotting/panel.R
index 8c08653..195652b 100644
--- a/plotting/panel.R
+++ b/plotting/panel.R
@@ -9,7 +9,7 @@ library(grid)
 
 
 # Time panel
-panel = function (df_data, df_meta, figdir, filedir_opt='', filename_opt='', variable='', df_trend=NULL, p_threshold=0.1, unit2day=365.25, type='', missRect=FALSE) {
+panel = function (df_data, df_meta, layout_matrix, figdir='', filedir_opt='', filename_opt='', variable='', df_trend=NULL, p_threshold=0.1, unit2day=365.25, type='', missRect=FALSE, time_header=NULL, info_header=TRUE, header_ratio=2) {
     
     if (all(class(df_data) != 'list')) {
         df_data = list(df_data)
@@ -47,12 +47,6 @@ panel = function (df_data, df_meta, figdir, filedir_opt='', filename_opt='', var
             missRect = replicate(nbp, missRect)
         }}
 
-    # print(df_data)
-    # print(df_trend)
-    # print(p_threshold)
-    # print(unit2day)
-    # print(missRect)
-
     list_df2plot = vector(mode='list', length=nbp)
 
     for (i in 1:nbp) {
@@ -67,7 +61,6 @@ panel = function (df_data, df_meta, figdir, filedir_opt='', filename_opt='', var
         list_df2plot[[i]] = df2plot
     }
 
-    # print(list_df2plot)
 
     outfile = "Panels"
     if (filename_opt != '') {
@@ -94,15 +87,23 @@ panel = function (df_data, df_meta, figdir, filedir_opt='', filename_opt='', var
         # Print code of the station for the current plotting
         print(paste("Plotting for sation :", code))
         
-        nbg = nbp+1
+        nbh = as.numeric(info_header) + as.numeric(!is.null(time_header))
+        nbg = nbp + nbh
+
         P = vector(mode='list', length=nbg)
-        # P = as.list(rep(void, nbp))
-        # print(nbp)
-        # print(P)
-        
-        gtext = text_panel(code, df_meta)
-        P[[1]] = gtext
-        
+
+        if (info_header) {
+            Htext = text_panel(code, df_meta)
+            P[[1]] = Htext
+        }
+
+        if (!is.null(time_header)) {
+            Htime = time_panel(code, time_header, df_trend=NULL,
+                               missRect=TRUE, unit2day=365.25,
+                               type='time')
+            P[[2]] = Htime
+        }
+
         for (i in 1:nbp) {
             df_data = list_df2plot[[i]]$data
             df_trend = list_df2plot[[i]]$trend
@@ -114,18 +115,59 @@ panel = function (df_data, df_meta, figdir, filedir_opt='', filename_opt='', var
             p = time_panel(code, df_data, df_trend, missRect,
                            p_threshold, unit2day, type)
 
-            P[[i+1]] = p
+            P[[i+nbh]] = p
 
         }
+        
+        layout_matrix_H = as.matrix(layout_matrix + nbh)
+
+        print(layout_matrix_H)
+
+        LM = c()
+        LMcol = ncol(layout_matrix_H)
+        LMrow = nrow(layout_matrix_H)
+        for (i in 1:(LMrow+nbh)) {
+            
+            print(i)
+
+            if (i <= nbh) {
+                LM = rbind(LM, rep(i, times=LMcol))
+            } else {
+                LM = rbind(LM, 
+                           matrix(rep(layout_matrix_H[i-nbh,],
+                                      times=header_ratio),
+                                  ncol=LMcol, byrow=TRUE))
+            }
+        }
+
+        print(nbg)
+        print(LM)
+
+        plot = grid.arrange(grobs=P, layout_matrix=LM)
+
 
-        # plot = grid.arrange(gtext, P[[1]], P[[2]], P[[3]], P[[4]],
-                            # heights=c(1/8, 1/8, 2/8, 2/8, 2/8), 
-                            # ncol=1, nrow=5)
+        # if (nbnh <= 4) {
+        #     plot = grid.arrange(grobs=P,
+        #                         heights=c(rep(1/(nbnh*ratio + nbh), 
+        #                                       nbh),
+        #                                   rep(ratio/(nbnh*ratio + nbh),
+        #                                       nbnh)),
+        #                         ncol=1, nrow=nbg)
 
-        plot = grid.arrange(grobs=P,
-                            heights=c(rep(1/((nbg-2)*2+2), 2),
-                                      rep(2/((nbg-2)*2+2), nbg-2)), 
-                            ncol=1, nrow=nbg)
+        # } else if (nbnh > 4) {
+        #     P[[(length(P)+1):8]] = void
+        #     plot = grid.arrange(grobs=P, 
+        #                         heights=c(rep(1/((nbg-2)*2+2), 1),
+        #                                   rep(2/((nbg-2)*2+2), nbg-2)), 
+        #                         ncol=1, nrow=nbg)
+
+        # }
+
+            # } else if (nbg-2 <= 6 & nbg-2 > 3) {
+            #     
+
+            # }
+        
 
         # Saving
         ggsave(plot=plot, 
@@ -228,10 +270,11 @@ time_panel = function (code, df_data, df_trend, missRect, p_threshold, unit2day,
                                 expand=c(0, 0))
     }
 
+    # if 
     p = p +
         theme(
             panel.background=element_rect(fill="white"),
-            plot.margin=margin(0, 5, 0, 5, unit="mm"))
+            plot.margin=margin(0.25, 5, 0.25, 5, unit="mm"))
 
     return(p)
 }
diff --git a/script.R b/script.R
index f897507..10ed233 100644
--- a/script.R
+++ b/script.R
@@ -59,7 +59,7 @@ NVlistname =
 
 ### TREND ANALYSIS ###
 # Time period to analyse
-period = c("1960-01-01","2019-12-31")
+period = c("1980-01-01","2019-12-31")
 # period = c("1960-01-01","2020-01-01")
 
 
@@ -72,11 +72,11 @@ period = c("1960-01-01","2019-12-31")
 setwd(computer_work_path)
 
 # Sourcing R file
-source('processing/extractBH.R')
-source('processing/extractNV.R')
-source('processing/format.R')
-source('processing/analyse.R')
-source('plotting/panel.R')
+source('processing/extractBH.R', encoding='latin1')
+source('processing/extractNV.R', encoding='latin1')
+source('processing/format.R', encoding='latin1')
+source('processing/analyse.R', encoding='latin1')
+source('plotting/panel.R', encoding='latin1')
 # source('plotting/layout.R')
 
 # Usefull library
@@ -147,7 +147,7 @@ df_meta = df_join$meta
 res_QAtrend = get_QAtrend(df_data, period)
 
 # QMNA TREND #
-res_QMNAtrend = get_QMNAtrend(df_data, period)
+# res_QMNAtrend = get_QMNAtrend(df_data, period)
 
 # VCN10 TREND #
 res_VCN10trend = get_VCN10trend(df_data, df_meta, period)
@@ -155,17 +155,31 @@ res_VCN10trend = get_VCN10trend(df_data, df_meta, period)
 
 # TIME PANEL #
 # Plot time panel of debit by stations
-panel(list(df_data, res_QAtrend$data, res_QMNAtrend$data,
+# panel(list(df_data, df_data),
+#       layout_matrix=c(1, 2),
+#       df_meta=df_meta,
+#       missRect=list(TRUE, TRUE), 
+#       type=list('time', 'sqrt'), 
+#       info_header=TRUE,
+#       time_header=NULL,
+#       header_ratio=3,
+#       figdir=figdir,
+#       filename_opt='time')
+
+panel(list(res_QAtrend$data, res_QMNAtrend$data,
            res_VCN10trend$data), 
+      layout_matrix=matrix(c(1, 2, 3, 3), ncol=2, byrow=TRUE),
       df_meta=df_meta, 
-      figdir=figdir,
-      df_trend=list(NULL, res_QAtrend$trend, res_QMNAtrend$trend,
+      df_trend=list(res_QAtrend$trend, res_QMNAtrend$trend,
                     res_VCN10trend$trend), 
-      type=list('time', '', '', ''),
-      missRect=list(TRUE, TRUE, TRUE, TRUE),
-      )
+      type=list('', '', ''),
+      missRect=list(TRUE, TRUE, TRUE),
+      info_header=TRUE,
+      time_header=df_data,
+      header_ratio=2,
+      figdir=figdir,
+      filename_opt='')
 
-# panel(df_data, df_meta=df_meta, figdir=figdir, missRect=TRUE, type='sqrt')
 ### /!\ Removed 185 row(s) containing missing values (geom_path) -> remove NA ###
 
 
-- 
GitLab