diff --git a/plotting/layout.R b/plotting/layout.R index 08267e73cd621889da2b3643637356fc02b40e06..d90002c041d8471e48fa2b6dca7d78db8a1f7dcf 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, 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) { +panels_layout = function (df_data, df_meta, layout_matrix, isplot=c('datasheet', 'matrix', 'map'), 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 != '') { @@ -121,291 +121,296 @@ panels_layout = function (df_data, df_meta, layout_matrix, figdir='', filedir_op list_df2plot[[i]] = df2plot } - Start_code = vector(mode='list', length=nCode) - End_code = vector(mode='list', length=nCode) - Code_code = vector(mode='list', length=nCode) - Periods_code = vector(mode='list', length=nCode) - for (j in 1:nCode) { - - code = Code[j] - - df_trend_code = df_trendtmp[df_trendtmp$code == code,] - - Start = df_trend_code$period_start - UStart = levels(factor(Start)) - - End = df_trend_code$period_end - UEnd = levels(factor(End)) - - nPeriod = max(length(UStart), length(UEnd)) + if ('datasheet' %in% isplot) { - Periods = c() - - for (i in 1:nPeriod_max) { - Periods = append(Periods, - paste(substr(Start[i], 1, 4), - substr(End[i], 1, 4), - sep=' / ')) - } - Start_code[[j]] = Start - End_code[[j]] = End - Code_code[[j]] = code - Periods_code[[j]] = Periods - } + Start_code = vector(mode='list', length=nCode) + End_code = vector(mode='list', length=nCode) + Code_code = vector(mode='list', length=nCode) + Periods_code = vector(mode='list', length=nCode) - TrendMean_code = array(rep(1, nPeriod_max*nbp*nCode), - dim=c(nPeriod_max, nbp, nCode)) + for (j in 1:nCode) { + + code = Code[j] - for (j in 1:nPeriod_max) { + df_trend_code = df_trendtmp[df_trendtmp$code == code,] - for (k in 1:nCode) { + Start = df_trend_code$period_start + UStart = levels(factor(Start)) - code = Code[k] + End = df_trend_code$period_end + UEnd = levels(factor(End)) - for (i in 1:nbp) { - - df_data = list_df2plot[[i]]$data - df_trend = list_df2plot[[i]]$trend - p_threshold = list_df2plot[[i]]$p_threshold - - df_data_code = df_data[df_data$code == code,] - df_trend_code = df_trend[df_trend$code == code,] - - Start = Start_code[Code_code == code][[1]][j] - End = End_code[Code_code == code][[1]][j] - Periods = Periods_code[Code_code == code][[1]][j] - - df_data_code_per = - df_data_code[df_data_code$Date >= Start - & df_data_code$Date <= End,] + nPeriod = max(length(UStart), length(UEnd)) - df_trend_code_per = - df_trend_code[df_trend_code$period_start == Start - & df_trend_code$period_end == End,] - - Ntrend = nrow(df_trend_code_per) - if (Ntrend > 1) { - df_trend_code_per = df_trend_code_per[1,] - } - - dataMean = mean(df_data_code_per$Qm3s, na.rm=TRUE) - trendMean = df_trend_code_per$trend / dataMean + Periods = c() - TrendMean_code[j, i, k] = trendMean + for (i in 1:nPeriod_max) { + Periods = append(Periods, + paste(substr(Start[i], 1, 4), + substr(End[i], 1, 4), + sep=' / ')) } + Start_code[[j]] = Start + End_code[[j]] = End + Code_code[[j]] = code + Periods_code[[j]] = Periods } - } - minTrendMean = apply(TrendMean_code, c(1, 2), min, na.rm=TRUE) - maxTrendMean = apply(TrendMean_code, c(1, 2), max, na.rm=TRUE) - - for (code in Code) { - - # Print code of the station for the current plotting - print(paste("Plotting for station :", code)) - - nbh = as.numeric(info_header) + as.numeric(!is.null(time_header)) - nbg = nbp + nbh - - P = vector(mode='list', length=nbg) + TrendMean_code = array(rep(1, nPeriod_max*nbp*nCode), + dim=c(nPeriod_max, nbp, nCode)) - if (info_header) { - time_header_code = time_header[time_header$code == code,] - - 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, - df_data_code=time_header_code) - P[[1]] = Hinfo - } + for (j in 1:nPeriod_max) { - if (!is.null(time_header)) { + for (k in 1:nCode) { + + code = Code[k] + + for (i in 1:nbp) { + + df_data = list_df2plot[[i]]$data + df_trend = list_df2plot[[i]]$trend + p_threshold = list_df2plot[[i]]$p_threshold - time_header_code = time_header[time_header$code == code,] - axis_xlim = c(min(time_header_code$Date), - max(time_header_code$Date)) - - Htime = time_panel(time_header_code, df_trend_code=NULL, - trend_period=trend_period, missRect=TRUE, - unit2day=365.25, type='Q', first=FALSE) + df_data_code = df_data[df_data$code == code,] + df_trend_code = df_trend[df_trend$code == code,] - P[[2]] = Htime - } - - # map = map_panel() - - nbcol = ncol(as.matrix(layout_matrix)) - for (i in 1:nbp) { - df_data = list_df2plot[[i]]$data - df_trend = list_df2plot[[i]]$trend - p_threshold = list_df2plot[[i]]$p_threshold - unit2day = list_df2plot[[i]]$unit2day - missRect = list_df2plot[[i]]$missRect - type = list_df2plot[[i]]$type - - df_data_code = df_data[df_data$code == code,] - df_trend_code = df_trend[df_trend$code == code,] - - color = c() - # for (j in 1:nrow(df_trend_code)) { - grey = 85 - for (j in 1:nPeriod_max) { - if (df_trend_code$p[j] <= p_threshold){ - # color_res = get_color(df_trend_code$trend[j], - # minTrend[i], - # maxTrend[i], - # palette_name='perso', - # reverse=TRUE) - Start = Start_code[Code_code == code][[1]][j] End = End_code[Code_code == code][[1]][j] Periods = Periods_code[Code_code == code][[1]][j] - + df_data_code_per = df_data_code[df_data_code$Date >= Start & df_data_code$Date <= End,] - + df_trend_code_per = df_trend_code[df_trend_code$period_start == Start & df_trend_code$period_end == End,] - + Ntrend = nrow(df_trend_code_per) if (Ntrend > 1) { df_trend_code_per = df_trend_code_per[1,] } - dataMean = mean(df_data_code$Qm3s, na.rm=TRUE) + dataMean = mean(df_data_code_per$Qm3s, na.rm=TRUE) trendMean = df_trend_code_per$trend / dataMean - - color_res = get_color(trendMean, - minTrendMean[j, i], - maxTrendMean[j, i], - palette_name='perso', - reverse=TRUE) - - colortmp = color_res - } else { - colortmp = paste('grey', grey, sep='') - grey = grey - 10 + + TrendMean_code[j, i, k] = trendMean } + } + } + + minTrendMean = apply(TrendMean_code, c(1, 2), min, na.rm=TRUE) + maxTrendMean = apply(TrendMean_code, c(1, 2), max, na.rm=TRUE) + + for (code in Code) { + + # Print code of the station for the current plotting + print(paste("Plotting for station :", code)) + + nbh = as.numeric(info_header) + as.numeric(!is.null(time_header)) + nbg = nbp + nbh + + P = vector(mode='list', length=nbg) - color = append(color, colortmp) + if (info_header) { + time_header_code = time_header[time_header$code == code,] + + 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, + df_data_code=time_header_code) + P[[1]] = Hinfo + } + + if (!is.null(time_header)) { + + time_header_code = time_header[time_header$code == code,] + axis_xlim = c(min(time_header_code$Date), + max(time_header_code$Date)) + + Htime = time_panel(time_header_code, df_trend_code=NULL, + trend_period=trend_period, missRect=TRUE, + unit2day=365.25, type='Q', first=FALSE) + + P[[2]] = Htime } - - p = time_panel(df_data_code, df_trend_code, type=type, - p_threshold=p_threshold, missRect=missRect, - trend_period=trend_period, - mean_period=mean_period, axis_xlim=axis_xlim, - unit2day=unit2day, last=(i > nbp-nbcol), - color=color) - P[[i+nbh]] = p - } + # map = map_panel() + + nbcol = ncol(as.matrix(layout_matrix)) + for (i in 1:nbp) { + df_data = list_df2plot[[i]]$data + df_trend = list_df2plot[[i]]$trend + p_threshold = list_df2plot[[i]]$p_threshold + unit2day = list_df2plot[[i]]$unit2day + missRect = list_df2plot[[i]]$missRect + type = list_df2plot[[i]]$type - layout_matrix = as.matrix(layout_matrix) - nel = nrow(layout_matrix)*ncol(layout_matrix) + df_data_code = df_data[df_data$code == code,] + df_trend_code = df_trend[df_trend$code == code,] - idNA = which(is.na(layout_matrix), arr.ind=TRUE) + color = c() + # for (j in 1:nrow(df_trend_code)) { + grey = 85 + for (j in 1:nPeriod_max) { + if (df_trend_code$p[j] <= p_threshold){ + # color_res = get_color(df_trend_code$trend[j], + # minTrend[i], + # maxTrend[i], + # palette_name='perso', + # reverse=TRUE) + + Start = Start_code[Code_code == code][[1]][j] + End = End_code[Code_code == code][[1]][j] + Periods = Periods_code[Code_code == code][[1]][j] + + df_data_code_per = + df_data_code[df_data_code$Date >= Start + & df_data_code$Date <= End,] + + df_trend_code_per = + df_trend_code[df_trend_code$period_start == Start + & df_trend_code$period_end == End,] + + Ntrend = nrow(df_trend_code_per) + if (Ntrend > 1) { + df_trend_code_per = df_trend_code_per[1,] + } + + dataMean = mean(df_data_code$Qm3s, na.rm=TRUE) + trendMean = df_trend_code_per$trend / dataMean + + color_res = get_color(trendMean, + minTrendMean[j, i], + maxTrendMean[j, i], + palette_name='perso', + reverse=TRUE) + + colortmp = color_res + } else { + colortmp = paste('grey', grey, sep='') + grey = grey - 10 + } - layout_matrix[idNA] = seq(max(layout_matrix, na.rm=TRUE) + 1, - max(layout_matrix, na.rm=TRUE) + 1 + - nel) + color = append(color, colortmp) + } + + p = time_panel(df_data_code, df_trend_code, type=type, + p_threshold=p_threshold, missRect=missRect, + trend_period=trend_period, + mean_period=mean_period, axis_xlim=axis_xlim, + unit2day=unit2day, last=(i > nbp-nbcol), + color=color) + + P[[i+nbh]] = p + } - layout_matrix_H = layout_matrix + nbh + layout_matrix = as.matrix(layout_matrix) + nel = nrow(layout_matrix)*ncol(layout_matrix) + idNA = which(is.na(layout_matrix), arr.ind=TRUE) - info_ratio_scale = info_ratio - time_ratio_scale = time_ratio - var_ratio_scale = var_ratio + layout_matrix[idNA] = seq(max(layout_matrix, na.rm=TRUE) + 1, + max(layout_matrix, na.rm=TRUE) + 1 + + nel) - ndec_info = 0 - ndec_time = 0 - ndec_var = 0 + layout_matrix_H = layout_matrix + nbh - 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, - 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_scale), - ncol=LMcol, byrow=TRUE)) - - } else { - LM = rbind(LM, - matrix(rep(layout_matrix_H[i-nbh,], - times=var_ratio_scale), - ncol=LMcol, byrow=TRUE)) - }} - - plot = grid.arrange(grobs=P, layout_matrix=LM) - - # plot = grid.arrange(rbind(cbind(ggplotGrob(P[[2]]), ggplotGrob(P[[2]])), cbind(ggplotGrob(P[[3]]), ggplotGrob(P[[3]]))), heights=c(1/3, 2/3)) - + info_ratio_scale = info_ratio + time_ratio_scale = time_ratio + var_ratio_scale = var_ratio - # Saving - ggsave(plot=plot, - path=outdirTmp, - filename=paste(as.character(code), '.pdf', sep=''), - width=21, height=29.7, units='cm', dpi=100) + 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))) + } - matrice_panel(list_df2plot, df_meta, trend_period, mean_period, - slice=12, outdirTmp=outdirTmp, A3=TRUE) + 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, + 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_scale), + ncol=LMcol, byrow=TRUE)) + + } else { + LM = rbind(LM, + matrix(rep(layout_matrix_H[i-nbh,], + times=var_ratio_scale), + ncol=LMcol, byrow=TRUE)) + }} + + plot = grid.arrange(grobs=P, layout_matrix=LM) + + # plot = grid.arrange(rbind(cbind(ggplotGrob(P[[2]]), ggplotGrob(P[[2]])), cbind(ggplotGrob(P[[3]]), ggplotGrob(P[[3]]))), heights=c(1/3, 2/3)) + - - map_panel(list_df2plot, - df_meta, - idPer=length(trend_period), - 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, - outdirTmp=outdirTmp, - margin=margin(t=5, r=0, b=5, l=5, unit="mm")) + # Saving + ggsave(plot=plot, + path=outdirTmp, + filename=paste(as.character(code), '.pdf', sep=''), + width=21, height=29.7, units='cm', dpi=100) + + } + } + if ('matrix' %in% isplot) { + matrice_panel(list_df2plot, df_meta, trend_period, mean_period, + slice=12, outdirTmp=outdirTmp, A3=TRUE) + } + if ('map' %in% isplot) { + map_panel(list_df2plot, + df_meta, + idPer=length(trend_period), + 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, + outdirTmp=outdirTmp, + margin=margin(t=5, r=0, b=5, l=5, unit="mm")) + } # PDF combine pdf_combine(input=file.path(outdirTmp, list.files(outdirTmp)), diff --git a/plotting/panel.R b/plotting/panel.R index 09934555857811e143c601e5d2ef22cd1333f0ed..f52008299b1042f687827ed01a91477438416346 100644 --- a/plotting/panel.R +++ b/plotting/panel.R @@ -724,7 +724,10 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic if (nPeriod > nPeriod_max) { nPeriod_max = nPeriod } - } + } + + # print(nPeriod_trend) + # print(nPeriod_max) Start_code = vector(mode='list', length=nCode) End_code = vector(mode='list', length=nCode) @@ -1014,51 +1017,46 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic nMat = as.integer(nsubCodefL/slice) + 1 + print(nMat) + for (imat in 1:nMat) { subCode = subCodefL[(slice*(imat-1)+1):(slice*imat)] subCode = subCode[!is.na(subCode)] + + # print('aaa') + # print(subCode) nsubCode = length(subCode) + + CodefL_trend = substr(Code_trend, 1, 1) == fL - subPeriods_trend = Periods_trend[substr(Code_trend, 1, 1) - == fL] - subNPeriod_trend = NPeriod_trend[substr(Code_trend, 1, 1) - == fL] - subType_trend = Type_trend[substr(Code_trend, 1, 1) - == fL] - subCode_trend = Code_trend[substr(Code_trend, 1, 1) - == fL] - subPthresold_trend = Pthresold_trend[substr(Code_trend, 1, 1) - == fL] - subTrendMean_trend = TrendMean_trend[substr(Code_trend, 1, 1) - == fL] - subDataMean_trend = DataMean_trend[substr(Code_trend, 1, 1) - == fL] - subFill_trend = Fill_trend[substr(Code_trend, 1, 1) - == fL] - subColor_trend = Color_trend[substr(Code_trend, 1, 1) - == fL] + subPeriods_trend = Periods_trend[CodefL_trend] + subNPeriod_trend = NPeriod_trend[CodefL_trend] + subType_trend = Type_trend[CodefL_trend] + subCode_trend = Code_trend[CodefL_trend] + subPthresold_trend = Pthresold_trend[CodefL_trend] + subTrendMean_trend = TrendMean_trend[CodefL_trend] + subDataMean_trend = DataMean_trend[CodefL_trend] + subFill_trend = Fill_trend[CodefL_trend] + subColor_trend = Color_trend[CodefL_trend] + + # print(subNPeriod_trend) - subPeriods_mean = Periods_mean[substr(Code_mean, 1, 1) - == fL] - subNPeriod_mean = NPeriod_mean[substr(Code_mean, 1, 1) - == fL] - subType_mean = Type_mean[substr(Code_mean, 1, 1) - == fL] - subCode_mean = Code_mean[substr(Code_mean, 1, 1) - == fL] - subDataMean_mean = DataMean_mean[substr(Code_mean, 1, 1) - == fL] - subBreakMean_mean = BreakMean_mean[substr(Code_mean, 1, 1) - == fL] - subFill_mean = Fill_mean[substr(Code_mean, 1, 1) - == fL] - subColor_mean = Color_mean[substr(Code_mean, 1, 1) - == fL] + CodefL_mean = substr(Code_mean, 1, 1) == fL - title = df_meta[df_meta$code == subCode[1],]$region_hydro + subPeriods_mean = Periods_mean[CodefL_mean] + subNPeriod_mean = NPeriod_mean[CodefL_mean] + subType_mean = Type_mean[CodefL_mean] + subCode_mean = Code_mean[CodefL_mean] + subDataMean_mean = DataMean_mean[CodefL_mean] + subBreakMean_mean = BreakMean_mean[CodefL_mean] + subFill_mean = Fill_mean[CodefL_mean] + subColor_mean = Color_mean[CodefL_mean] + title = df_meta[df_meta$code == subCode[1],]$region_hydro + + # print('bbb') ### Plot ### height = length(subCode) @@ -1089,6 +1087,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic size=6, color="#00A3A8") + # print('ccc') + ### Trend ### for (j in 1:nPeriod_trend) { @@ -1097,7 +1097,7 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic Code_trend_per = subCode_trend[subNPeriod_trend == j] Pthresold_trend_per = - subPthresold_trend[NPeriod_trend == j] + subPthresold_trend[subNPeriod_trend == j] TrendMean_trend_per = subTrendMean_trend[subNPeriod_trend == j] DataMean_trend_per = @@ -1106,7 +1106,7 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic subFill_trend[subNPeriod_trend == j] Color_trend_per = subColor_trend[subNPeriod_trend == j] - + Xtmp = as.integer(factor(as.character(Type_trend_per))) Xc = j + (j - 1)*nbp*2 @@ -1151,7 +1151,7 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic gg_circle(r=0.45, xc=Xc, yc=Y[i], fill='white', color='grey40') } - + for (i in 1:length(TrendMean_trend_per)) { trendMean = TrendMean_trend_per[i] trendC = signif(trendMean*100, 2) @@ -1222,6 +1222,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic } } + # print('ddd') + ### Mean ### for (j in 1:nPeriod_mean) { @@ -1239,6 +1241,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic Color_mean_per = subColor_mean[subNPeriod_mean == j] + # print('ddd1') + Xtmp_mean = as.integer(factor(as.character(Type_mean_per))) Xc_mean = j + (j - 1)*nbp + X[length(X)] @@ -1269,6 +1273,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic label=periodName, hjust=0, vjust=0.5, size=3, color='grey40') + + # print('ddd2') if (j > 1) { x = Xr_mean[1] - 0.4 @@ -1288,6 +1294,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic hjust=0, vjust=0.5, size=3, color='grey40') } + + # print('ddd3') for (i in 1:length(Xm_mean)) { mat = mat + @@ -1306,8 +1314,12 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic } } + # print('ddd4') + for (i in 1:length(DataMean_mean_per)) { dataMean = signif(DataMean_mean_per[i], 2) + + # print(i) mat = mat + annotate('text', x=Xm_mean[i], y=Y[i], @@ -1318,6 +1330,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic if (j > 1) { BreakMean = BreakMean_mean_per[i] BreakC = signif(BreakMean*100, 2) + + # print(BreakMean) mat = mat + annotate('text', x=Xr_mean[i], y=Y[i], @@ -1326,6 +1340,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic size=3, color='white') } } + + # print('ddd5') mat = mat + annotate('text', x=Xc_mean, y=max(Y) + 0.85, @@ -1338,6 +1354,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic hjust=0.5, vjust=0.5, size=3, color='grey20') + + # print('ddd6') for (i in 1:nbp) { type = list_df2plot[[i]]$type @@ -1356,6 +1374,8 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic } } + # print('ddd7') + for (k in 1:nsubCode) { code = subCode[k] label = Periods_mean[NPeriod_mean == j @@ -1376,6 +1396,7 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic } } + # print('eee') ### Code ### for (k in 1:nsubCode) { @@ -1398,7 +1419,9 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic hjust=1, vjust=0.5, size=3.5, color="#00A3A8") } - + + + # print('fff') ### Environment ### @@ -1424,12 +1447,16 @@ matrice_panel = function (list_df2plot, df_meta, trend_period, mean_period, slic height = 21 dpi = 100 } + + # print('ggg') ggsave(plot=mat, path=outdirTmp, filename=paste(outnameTmp, '_', fL, imat, '.pdf', sep=''), width=width, height=height, units='cm', dpi=dpi) + + # print('hhh') } } diff --git a/script.R b/script.R index 323c222d3d7088623eefe9e44133e60a04145d60..09c9e59bf323698bda0917c7fdbe243403189a22 100644 --- a/script.R +++ b/script.R @@ -142,7 +142,7 @@ if (AGlistname != ""){ filename = df_selec_AG[df_selec_AG$ok,]$filename ##### - # filename = filename[(1+30):(16+30)] + filename = filename[(1):(25)] ##### # Extract metadata about selected stations @@ -234,7 +234,8 @@ res_VCN10trend = get_VCN10trend(df_data, df_meta, # figdir=figdir, # filename_opt='time') -panels_layout(list(res_QAtrend$data, res_QMNAtrend$data, +panels_layout(isplot=c('matrix'), + df_data=list(res_QAtrend$data, res_QMNAtrend$data, res_VCN10trend$data), layout_matrix=c(1, 2, 3), df_meta=df_meta,