diff --git a/plotting/datasheet.R b/plotting/datasheet.R index d8ae947504f20c291ed74ff2dd188336b1e55160..1c34cf2aee01ec686e9b6676a46679158307711e 100644 --- a/plotting/datasheet.R +++ b/plotting/datasheet.R @@ -34,7 +34,7 @@ source('processing/analyse.R', encoding='UTF-8') # Manages datasheets creations for all stations. Makes the call to # the different headers, trend analysis graphs and realises arranging # every plots. -datasheet_panel = function (list_df2plot, df_meta, trend_period, info_header, time_header, foot_note, layout_matrix, info_ratio, time_ratio, var_ratio, foot_height, resources_path, AEAGlogo_file, INRAElogo_file, FRlogo_file, outdirTmp) { +datasheet_panel = function (list_df2plot, df_meta, trend_period, info_header, time_header, foot_note, layout_matrix, info_ratio, time_ratio, var_ratio, foot_height, resources_path, AEAGlogo_file, INRAElogo_file, FRlogo_file, outdirTmp, df_page=NULL) { # The percentage of augmentation and diminution of the min # and max limits for y axis @@ -432,12 +432,28 @@ datasheet_panel = function (list_df2plot, df_meta, trend_period, info_header, ti P[[i+nbh]] = p } - foot = foot_panel('fiche station', k, nCode, resources_path, - AEAGlogo_file, INRAElogo_file, - FRlogo_file, foot_height) - - P[[nbg]] = foot - + if (!is.null(df_page)) { + section = 'fiche station' + subsection = code + n_page = df_page$n[nrow(df_page)] + 1 + df_page = bind_rows( + df_page, + tibble(section=section, + subsection=subsection, + n=n_page)) + } + + if (foot_note) { + footName = 'fiche station' + if (is.null(df_page)) { + n_page = k + } + + foot = foot_panel(footName, n_page, resources_path, + AEAGlogo_file, INRAElogo_file, + FRlogo_file, foot_height) + P[[nbg]] = foot + } # Convert the 'layout_matrix' to a matrix if it is not already layout_matrix = as.matrix(layout_matrix) @@ -517,6 +533,7 @@ datasheet_panel = function (list_df2plot, df_meta, trend_period, info_header, ti width=width, height=height, units='cm', dpi=100) } + return (df_page) } diff --git a/plotting/layout.R b/plotting/layout.R index a31cdd89c9e8e25e70a5d7593cebf45585a5b734..4fb5889e2246cfe15e884dbcf2eda2b8bfc26e44 100644 --- a/plotting/layout.R +++ b/plotting/layout.R @@ -242,35 +242,74 @@ datasheet_layout = function (df_data, df_meta, layout_matrix, list_df2plot[[i]] = df2plot } - # If datasheets needs to be plot - if ('datasheet' %in% toplot) { - - datasheet_panel(list_df2plot, df_meta, trend_period, info_header=info_header, time_header=time_header, foot_note=foot_note, layout_matrix=layout_matrix, info_ratio=info_ratio, time_ratio=time_ratio, var_ratio=var_ratio, foot_height=foot_height, resources_path=resources_path, AEAGlogo_file=AEAGlogo_file, INRAElogo_file=INRAElogo_file, FRlogo_file=FRlogo_file, outdirTmp=outdirTmp) - + df_page = tibble(section='sommaire', subsection=NA, n=1) + + # If map needs to be plot + if ('map' %in% toplot) { + df_page = map_panel(list_df2plot, + df_meta, + idPer_trend=length(trend_period), + mean_period=mean_period, + df_shapefile=df_shapefile, + foot_note=foot_note, + foot_height=foot_height, + resources_path=resources_path, + AEAGlogo_file=AEAGlogo_file, + INRAElogo_file=INRAElogo_file, + FRlogo_file=FRlogo_file, + outdirTmp=outdirTmp, + df_page=df_page) } # If summarize matrix needs to be plot if ('matrix' %in% toplot) { - matrix_panel(list_df2plot, df_meta, trend_period, mean_period, - slice=19, outdirTmp=outdirTmp, A3=TRUE, - foot_note=foot_note, foot_height=foot_height, resources_path=resources_path, AEAGlogo_file=AEAGlogo_file, INRAElogo_file=INRAElogo_file, FRlogo_file=FRlogo_file,) + df_page = matrix_panel(list_df2plot, + df_meta, + trend_period, + mean_period, + slice=19, + outdirTmp=outdirTmp, + A3=TRUE, + foot_note=foot_note, + foot_height=foot_height, + resources_path=resources_path, + AEAGlogo_file=AEAGlogo_file, + INRAElogo_file=INRAElogo_file, + FRlogo_file=FRlogo_file, + df_page=df_page) } - # If map needs to be plot - if ('map' %in% toplot) { - map_panel(list_df2plot, - df_meta, - idPer_trend=length(trend_period), - mean_period=mean_period, - df_shapefile=df_shapefile, - foot_note=foot_note, - foot_height=foot_height, - resources_path=resources_path, - AEAGlogo_file=AEAGlogo_file, - INRAElogo_file=INRAElogo_file, - FRlogo_file=FRlogo_file, - outdirTmp=outdirTmp) + # If datasheets needs to be plot + if ('datasheet' %in% toplot) { + df_page = datasheet_panel(list_df2plot, + df_meta, + trend_period, + info_header=info_header, + time_header=time_header, + foot_note=foot_note, + layout_matrix=layout_matrix, + info_ratio=info_ratio, + time_ratio=time_ratio, + var_ratio=var_ratio, + foot_height=foot_height, + resources_path=resources_path, + AEAGlogo_file=AEAGlogo_file, + INRAElogo_file=INRAElogo_file, + FRlogo_file=FRlogo_file, + outdirTmp=outdirTmp, + df_page=df_page) } + + print(df_page) + + summary_panel(df_page, + foot_note, + foot_height, + resources_path, + AEAGlogo_file, + INRAElogo_file, + FRlogo_file, + outdirTmp) # Combine independant pages into one PDF details = file.info(list.files(outdirTmp, full.names=TRUE)) @@ -444,11 +483,128 @@ palette_tester = function (n=256) { } +### Summary panel +summary_panel = function (df_page, foot_note, foot_height, resources_path, AEAGlogo_file, INRAElogo_file, FRlogo_file, outdirTmp) { + + text_title = paste( + "<b> Analyse de stationnarité </b>", + sep='') + + Sec_name = rle(df_page$section)$values + nSec = length(Sec_name) + + text_sum = '' + for (idS in 1:nSec) { + sec_name = Sec_name[idS] + subSec_name = rle(df_page$subsection[df_page$section == sec_name])$values + n_page = df_page$n[df_page$section == sec_name][1] + + text_sum = paste(text_sum, + idS, ". ", "<b>", sec_name, "</b>", + ' ', 'p.', n_page, "<br>", + sep='') + + nSSec = length(subSec_name) + for (idSS in 1:nSSec) { + subsec_name = subSec_name[idSS] + if (!is.na(subsec_name)) { + n_page = df_page$n[df_page$section == sec_name & + df_page$subsection == subsec_name][1] + + text_sum = paste(text_sum, + idS, ".", idSS, ". ", subsec_name, + ' ', 'p.', n_page, "<br>", + sep='') + } + } + } + + text_sum = gsub('<ol>', '', text_sum) + + text_sum = "1. <b>sommaire</b><br>2. <b>carte des tendances observées</b><br>2.1. QA p.2<br>2.2. QMNA p.3<br>2.3. VCN10 p.4<br>2.4. DEB p.5<br>2.5. CEN p.6<br>3. <b>carte des écarts observés</b><br>3.1. QA p.7<br>3.2. QMNA p.8<br>3.3. VCN10 p.9<br>3.4. DEB p.10<br>3.5. CEN p.11<br>4. <b>tableau récapitulatif de saisonnalité</b><br>4.1. Adour p.12<br>5. <b>tableau récapitulatif de sévérité</b><br>5.1. Adour p.13<br>6. <b>fiche station</b><br>6.1. Q7002910 p.14<br>" + + print(text_title) + print(text_sum) + + # text_sum = 'test<br>test<br><b>test</b>' + + # Converts all texts to graphical object in the right position + gtitle = richtext_grob(text_title, + x=0, y=1, + margin=unit(c(t=0, r=0, b=0, l=0), "mm"), + hjust=0, vjust=1, + gp=gpar(col="#00A3A8", fontsize=20)) + + gsum = richtext_grob(text_sum, + x=0, y=1, + margin=unit(c(t=0, r=0, b=0, l=0), "mm"), + hjust=0, vjust=1, + gp=gpar(col="#00A3A8", fontsize=10)) + + # If there is a foot note + if (foot_note) { + footName = 'sommaire' + foot = foot_panel(footName, + 1, resources_path, + AEAGlogo_file, INRAElogo_file, + FRlogo_file, foot_height) + + P = list(gtitle, gsum, foot) + LM = matrix(c(1, + 2, + 3), + nrow=3, byrow=TRUE) + } else { + foot_height = 0 + P = list(gtitle, gsum) + LM = matrix(c(1, + 2), + nrow=2, byrow=TRUE) + } + id_foot = 2 + + LMcol = ncol(LM) + LMrow = nrow(LM) + + LM = rbind(rep(99, times=LMcol), LM, rep(99, times=LMcol)) + LMrow = nrow(LM) + LM = cbind(rep(99, times=LMrow), LM, rep(99, times=LMrow)) + LMcol = ncol(LM) + + margin_height = 0.5 + height = 29.7 + width = 21 + + row_height = (height - 2*margin_height - foot_height) / (LMrow - 3) + + Hcut = LM[, 2] + heightLM = rep(row_height, times=LMrow) + heightLM[Hcut == id_foot] = foot_height + heightLM[Hcut == 99] = margin_height + + col_width = (width - 2*margin_height) / (LMcol - 2) + + Wcut = LM[(nrow(LM)-1),] + widthLM = rep(col_width, times=LMcol) + widthLM[Wcut == 99] = margin_height + + # Arranges the graphical object + plot = grid.arrange(grobs=P, layout_matrix=LM, + heights=heightLM, widths=widthLM) + + # Saves the plot + ggsave(plot=plot, + path=outdirTmp, + filename=paste('sommaire', '.pdf', sep=''), + width=width, height=height, units='cm', dpi=100) +} + + ### Foot note panel -foot_panel = function (name, n_page, N_page, resources_path, AEAGlogo_file, INRAElogo_file, FRlogo_file, foot_height) { +foot_panel = function (name, n_page, resources_path, AEAGlogo_file, INRAElogo_file, FRlogo_file, foot_height) { text_page = paste( - name, " <b>p. ", n_page, "/", N_page, "</b>", + name, " <b>p. ", n_page, "</b>", sep='') text_date = paste ( diff --git a/plotting/map.R b/plotting/map.R index 5c4dcf9b556b4fd5dfa2a88b08f767f6c35e279f..5403fc0ae98ba8b75b9090865b2991143bee9dfe 100644 --- a/plotting/map.R +++ b/plotting/map.R @@ -34,7 +34,7 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, foot_note=FALSE, foot_height=0, resources_path=NULL, AEAGlogo_file=NULL, INRAElogo_file=NULL, - FRlogo_file=NULL, + FRlogo_file=NULL, df_page=NULL, verbose=TRUE) { # Extract shapefiles @@ -325,13 +325,20 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, outname = paste('map_', var, sep='') } - n_page = i + nbp*(j-1) - N_page = nbp*nPeriod_mean + n_loop = i + nbp*(j-1) + N_loop = nbp*nPeriod_mean # If there is the verbose option if (verbose) { + if (j > 1) { + mapName = 'difference' + } else { + mapName = 'tendence' + } # Prints the name of the map - print(paste('Map for variable : ', var, - " (", round(n_page/N_page*100, 0), " %)", + print(paste('Map of ', mapName, ' for : ', var, + " (", + round(n_loop/N_loop*100, 0), + " %)", sep='')) } @@ -641,11 +648,11 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, # If it is a flow variable if (type == 'sévérité') { # Formatting of label in pourcent - labTick = as.character(round(labTick*100, 2)) + labTick = as.character(signif(labTick*100, 2)) # If it is a date variable } else if (type == 'saisonnalité') { # Formatting of label - labTick = as.character(round(labTick, 2)) + labTick = as.character(signif(labTick, 2)) } # X position of ticks all similar @@ -686,7 +693,7 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, color='white', fill=colTick) if (j > 1) { - ValueName = "Écarts observées" + ValueName = "Écarts observés" # If it is a flow variable if (type == 'sévérité') { unit = bquote(bold("(%)")) @@ -794,7 +801,7 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, yValue = yValue[alpha_Ok] # Histogram distribution - # Computes the histogram of the trend + # Computes the histogram of values res_hist = hist(yValue, breaks=ytick, plot=FALSE) # Extracts the number of counts per cells counts = res_hist$counts @@ -808,15 +815,27 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, xValue = c() yValue = c() # Start X position of the distribution - start_hist = 1.25 + start_hist = 1 + # X separation bewteen point hist_sep = 0.15 + + # Gets the maximun number of point of the distribution + maxCount = max(counts, na.rm=TRUE) + # Limit of the histogram + lim_hist = 2 + # If the number of point will exceed the limit + if (maxCount * hist_sep > lim_hist) { + # Computes the right amount of space between points + hist_sep = lim_hist / maxCount + } + # For all cells of the histogram for (ii in 1:length(mids)) { # If the count in the current cell is not zero if (counts[ii] != 0) { - # Stores the X positions of points of the distribution - # for the current cell + # Stores the X positions of points of the + # distribution for the current cell xValue = c(xValue, seq(start_hist, start_hist+(counts[ii]-1)*hist_sep, @@ -827,16 +846,16 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, yValue = c(yValue, rep(mids[ii], times=counts[ii])) } - # Makes a tibble to plot the trend distribution + # Makes a tibble to plot the distribution plot_value = tibble(xValue=xValue, yValue=yValue) pal = pal + - # Plots the point of the trend distribution + # Plots the point of the distribution geom_point(data=plot_value, aes(x=xValue, y=yValue), - # shape=21, size=1, - # color="grey20", fill="grey20") - alpha=0.4) + shape=21, color='white', + fill='grey50', stroke=0.4, + alpha=1) if (type == 'sévérité') { labelArrow = 'Plus sévère' @@ -844,6 +863,7 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, labelArrow = 'Plus tôt' } + # Position of the arrow xArrow = 3.2 pal = pal + @@ -870,16 +890,35 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, # Margin of the colorbar theme(plot.margin=margin(t=0, r=0, b=0, l=0, unit="mm")) - if (j > 1) { - footName = 'carte des écarts observés' - } else { - footName = 'carte des tendances observées' + if (!is.null(df_page)) { + if (j > 1) { + section = 'carte des écarts observés' + } else { + section = 'carte des tendances observées' + } + subsection = var + n_page = df_page$n[nrow(df_page)] + 1 + df_page = bind_rows( + df_page, + tibble(section=section, + subsection=subsection, + n=n_page)) } # If there is a foot note if (foot_note) { + if (j > 1) { + footName = 'carte des écarts observés' + } else { + footName = 'carte des tendances observées' + } + + if (is.null(df_page)) { + n_page = n_loop + } + foot = foot_panel(footName, - n_page, N_page, resources_path, + n_page, resources_path, AEAGlogo_file, INRAElogo_file, FRlogo_file, foot_height) @@ -929,7 +968,8 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, heights=heightLM, widths=widthLM) - # If there is no specified station code to highlight (mini map) + # If there is no specified station code to highlight + # (mini map) if (is.null(codeLight)) { # Saving matrix plot ggsave(plot=plot, @@ -939,7 +979,13 @@ map_panel = function (list_df2plot, df_meta, df_shapefile, idPer_trend=1, } } } + # If there is no specified station code to highlight + # (mini map) + if (is.null(codeLight)) { + return (df_page) # Returns the map object - return (map) + } else { + return (map) + } } diff --git a/plotting/matrix.R b/plotting/matrix.R index 679482fd716badb97e441763ba6a5b43f6302403..65ce7c9e43f34c1f71e6198a6455b8044ca464c7 100644 --- a/plotting/matrix.R +++ b/plotting/matrix.R @@ -32,7 +32,7 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice foot_note=FALSE, foot_height=0, resources_path=NULL, AEAGlogo_file=NULL, INRAElogo_file=NULL, - FRlogo_file=NULL) { + FRlogo_file=NULL, df_page=NULL) { # Number of variable/plot nbp = length(list_df2plot) @@ -207,7 +207,7 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice Var_trend = c() Type_trend = c() Code_trend = c() - Pthresold_trend = c() + Alpha_trend = c() TrendValue_trend = c() DataMean_trend = c() Fill_trend = c() @@ -282,12 +282,12 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice # table cells fill = color_res color = 'white' - Pthresold = p_thresold + Alpha = TRUE # Otherwise it is not significative } else { fill = 'white' color = 'grey85' - Pthresold = NA + Alpha = FALSE } # Stores info needed to plot @@ -296,7 +296,7 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice Var_trend = append(Var_trend, var) Type_trend = append(Type_trend, type) Code_trend = append(Code_trend, code) - Pthresold_trend = append(Pthresold_trend, Pthresold) + Alpha_trend = append(Alpha_trend, Alpha) TrendValue_trend = append(TrendValue_trend, trendValue) DataMean_trend = append(DataMean_trend, dataMean) Fill_trend = append(Fill_trend, fill) @@ -463,6 +463,33 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice # Gets all the different type of plots Type = levels(factor(allType)) nbType = length(Type) + + # Number of pages + N_loop = 0 + # For all the type of plots + for (itype in 1:nbType) { + # Gets the type + type = Type[itype] + # Extracts each possibilities of first letter of station code + firstLetter = levels(factor(substr(Code, 1, 1))) + # Number of different first letters + nfL = length(firstLetter) + # For all the available first letter + for (ifL in 1:nfL) { + # Gets the first letter + fL = firstLetter[ifL] + + # Get only station code with the same first letter + subCodefL = Code[substr(Code, 1, 1) == fL] + # Counts the number of station in it + nsubCodefL = length(subCodefL) + # Computes the number of pages needed to plot all stations + nMat = as.integer(nsubCodefL/slice) + 1 + # Counts the number of pages + N_loop = N_loop + nMat + } + } + # For all the type of plots for (itype in 1:nbType) { # Gets the type @@ -485,15 +512,15 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice nMat = as.integer(nsubCodefL/slice) + 1 # For all the pages for (iMat in 1:nMat) { - n_page = ifL + nfL*(itype-1) - N_page = nfL*2 + n_loop = ifL + nfL*(itype-1) + (iMat-1) + # N_loop = nfL*nbType # Print the matrix name print(paste('Matrix ', iMat, '/', nMat, ' of ', type, ' for region : ', fL, " (", - round(n_page / N_page * 100, + round(n_loop / N_loop * 100, 0), " %)", sep='')) @@ -517,7 +544,7 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice subVar_trend = Var_trend[CodefL_trend] subType_trend = Type_trend[CodefL_trend] subCode_trend = Code_trend[CodefL_trend] - subPthresold_trend = Pthresold_trend[CodefL_trend] + subAlpha_trend = Alpha_trend[CodefL_trend] subTrendValue_trend = TrendValue_trend[CodefL_trend] subDataMean_trend = DataMean_trend[CodefL_trend] subFill_trend = Fill_trend[CodefL_trend] @@ -599,8 +626,8 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice subType_trend[subNPeriod_trend == j] Code_trend_per = subCode_trend[subNPeriod_trend == j] - Pthresold_trend_per = - subPthresold_trend[subNPeriod_trend == j] + Alpha_trend_per = + subAlpha_trend[subNPeriod_trend == j] TrendValue_trend_per = subTrendValue_trend[subNPeriod_trend == j] DataMean_trend_per = @@ -696,7 +723,7 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice } # If it is significative - if (!is.na(Pthresold_trend_per[i])) { + if (Alpha_trend_per[i]) { # The text color is white Tcolor = 'white' # Otherwise @@ -1113,22 +1140,43 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice dpi = 100 } + if (!is.null(df_page)) { + section = paste('tableau récapitulatif de ', + type, sep='') + subsection = title + n_page = df_page$n[nrow(df_page)] + 1 + df_page = bind_rows( + df_page, + tibble(section=section, + subsection=subsection, + n=n_page)) + } + # If there is a foot note if (foot_note) { - foot = foot_panel('tableau récapitulatif', - n_page, N_page, + footName = paste('tableau récapitulatif de ', + type, sep='') + + if (is.null(df_page)) { + n_page = n_loop + } + + foot = foot_panel(footName, + n_page, resources_path, AEAGlogo_file, INRAElogo_file, FRlogo_file, foot_height) - # Stores the map, the title and the colorbar in a list + # Stores the map, the title and the colorbar + # in a list P = list(mat, foot) LM = matrix(c(1, 2), nrow=2, byrow=TRUE) } else { foot_height = 0 - # Stores the map, the title and the colorbar in a list + # Stores the map, the title and the colorbar + # in a list P = list(mat) LM = matrix(c(1), nrow=1, byrow=TRUE) @@ -1177,4 +1225,5 @@ matrix_panel = function (list_df2plot, df_meta, trend_period, mean_period, slice } } } + return (df_page) } diff --git a/processing/analyse.R b/processing/analyse.R index 8bc6530a716b3358fb2109c3febbf6507f77d318..b0b841a7b6826cedd55d8a2822b0d22ffa72c5a9 100644 --- a/processing/analyse.R +++ b/processing/analyse.R @@ -97,7 +97,7 @@ get_intercept = function (df_Xtrend, df_Xlist, unit2day=365.25) { ### 1.1. QA # Realise the trend analysis of the average annual flow (QA) # hydrological variable -get_QAtrend = function (df_data, df_meta, period, p_thresold) { +get_QAtrend = function (df_data, df_meta, period, alpha) { # Removes incomplete data from time series df_data = remove_incomplete_data(df_data, df_meta, @@ -125,7 +125,7 @@ get_QAtrend = function (df_data, df_meta, period, p_thresold) { na.rm=TRUE) # Compute the trend analysis df_QAtrend = Estimate.stats(data.extract=df_QAEx, - level=p_thresold) + level=alpha) # Get the associated time interval I = interval(per[1], per[2]) @@ -150,7 +150,7 @@ get_QAtrend = function (df_data, df_meta, period, p_thresold) { ### 1.2. QMNA # Realise the trend analysis of the monthly minimum flow in the # year (QMNA) hydrological variable -get_QMNAtrend = function (df_data, df_meta, period, p_thresold, sampleSpan) { +get_QMNAtrend = function (df_data, df_meta, period, alpha, sampleSpan) { # Removes incomplete data from time series df_data = remove_incomplete_data(df_data, df_meta, @@ -192,7 +192,7 @@ get_QMNAtrend = function (df_data, df_meta, period, p_thresold, sampleSpan) { na.rm=TRUE) # Compute the trend analysis df_QMNAtrend = Estimate.stats(data.extract=df_QMNAEx, - level=p_thresold) + level=alpha) # Get the associated time interval I = interval(per[1], per[2]) @@ -219,7 +219,7 @@ get_QMNAtrend = function (df_data, df_meta, period, p_thresold, sampleSpan) { ### 1.3. VCN10 # Realises the trend analysis of the minimum 10 day average flow # over the year (VCN10) hydrological variable -get_VCN10trend = function (df_data, df_meta, period, p_thresold, sampleSpan) { +get_VCN10trend = function (df_data, df_meta, period, alpha, sampleSpan) { # Removes incomplete data from time series df_data = remove_incomplete_data(df_data, df_meta, @@ -268,7 +268,7 @@ get_VCN10trend = function (df_data, df_meta, period, p_thresold, sampleSpan) { na.rm=TRUE) # Compute the trend analysis df_VCN10trend = Estimate.stats(data.extract=df_VCN10Ex, - level=p_thresold) + level=alpha) # Get the associated time interval I = interval(per[1], per[2]) @@ -327,7 +327,7 @@ which_underfirst = function (L, UpLim, select_longest=TRUE) { return (id) } -get_DEBtrend = function (df_data, df_meta, period, p_thresold, sampleSpan, thresold_type='VCN10', select_longest=TRUE) { +get_DEBtrend = function (df_data, df_meta, period, alpha, sampleSpan, thresold_type='VCN10', select_longest=TRUE) { # Get all different stations code Code = levels(factor(df_meta$code)) @@ -455,7 +455,7 @@ get_DEBtrend = function (df_data, df_meta, period, p_thresold, sampleSpan, thres # Compute the trend analysis df_DEBtrend = Estimate.stats(data.extract=df_DEBEx, - level=p_thresold) + level=alpha) # Get the associated time interval I = interval(per[1], per[2]) @@ -481,7 +481,7 @@ get_DEBtrend = function (df_data, df_meta, period, p_thresold, sampleSpan, thres ### 1.5. CEN date # Realises the trend analysis of the date of the minimum 10 day # average flow over the year (VCN10) hydrological variable -get_CENtrend = function (df_data, df_meta, period, p_thresold, sampleSpan) { +get_CENtrend = function (df_data, df_meta, period, alpha, sampleSpan) { # Get all different stations code Code = levels(factor(df_meta$code)) @@ -533,7 +533,7 @@ get_CENtrend = function (df_data, df_meta, period, p_thresold, sampleSpan) { # Compute the trend analysis df_CENtrend = Estimate.stats(data.extract=df_CENEx, - level=p_thresold) + level=alpha) # Get the associated time interval I = interval(per[1], per[2]) @@ -690,7 +690,7 @@ get_hydrograph = function (df_data, period=NULL, df_meta=NULL) { ### 2.2. Break date # Compute the break date of the flow data by station -get_break = function (df_data, df_meta, p_thresold=0.05) { +get_break = function (df_data, df_meta, alpha=0.05) { # Get all different stations code Code = levels(factor(df_meta$code)) @@ -719,7 +719,7 @@ get_break = function (df_data, df_meta, p_thresold=0.05) { ibreak = res_break$estimate # If the p value results is under the thresold - if (p_value <= p_thresold) { + if (p_value <= alpha) { # Get the mean of the index break if there is several ibreak = round(mean(ibreak), 0) # Store the date break with its associated code diff --git a/script.R b/script.R index 99f6c6777004e9f8e9a236a3fd8dcc506bd831e3..f4550cdf600b9f2fa52f30ba3e8863af0e389d9a 100644 --- a/script.R +++ b/script.R @@ -55,19 +55,19 @@ filedir = # Name of the file that will be analysed from the BH directory # (if 'all', all the file of the directory will be chosen) filename = - "" - # c( + # "" + c( # "S2235610_HYDRO_QJM.txt", # "P1712910_HYDRO_QJM.txt", # "P0885010_HYDRO_QJM.txt", # "O5055010_HYDRO_QJM.txt", # "O0384010_HYDRO_QJM.txt", # "S4214010_HYDRO_QJM.txt", - # "Q7002910_HYDRO_QJM.txt" + "Q7002910_HYDRO_QJM.txt" # "O3035210_HYDRO_QJM.txt" # "O0554010_HYDRO_QJM.txt", # "O1584610_HYDRO_QJM.txt" - # ) + ) ## AGENCE EAU ADOUR GARONNE SELECTION @@ -77,8 +77,8 @@ AGlistdir = "" AGlistname = - # "" - "Liste-station_RRSE.docx" + "" + # "Liste-station_RRSE.docx" ## NIVALE SELECTION @@ -236,37 +236,37 @@ df_meta = get_lacune(df_data, df_meta) df_meta = get_hydrograph(df_data, df_meta, period=mean_period[[1]])$meta ### 3.2. Trend analysis -# # QA trend -# res_QAtrend = get_QAtrend(df_data, df_meta, -# period=trend_period, -# alpha=alpha) - -# # QMNA tend -# res_QMNAtrend = get_QMNAtrend(df_data, df_meta, -# period=trend_period, -# alpha=alpha, -# sampleSpan=sampleSpan) - -# # VCN10 trend -# res_VCN10trend = get_VCN10trend(df_data, df_meta, -# period=trend_period, -# alpha=alpha, -# sampleSpan=sampleSpan) - -# # Start date for low water trend -# res_DEBtrend = get_DEBtrend(df_data, df_meta, -# period=trend_period, -# alpha=alpha, -# sampleSpan=sampleSpan, -# thresold_type='VCN10', -# select_longest=TRUE) -# # res_DEBtrend = read_listofdf(resdir, 'res_DEBtrend') - -# # Center date for low water trend -# res_CENtrend = get_CENtrend(df_data, df_meta, -# period=trend_period, -# alpha=alpha, -# sampleSpan=sampleSpan) +# QA trend +res_QAtrend = get_QAtrend(df_data, df_meta, + period=trend_period, + alpha=alpha) + +# QMNA tend +res_QMNAtrend = get_QMNAtrend(df_data, df_meta, + period=trend_period, + alpha=alpha, + sampleSpan=sampleSpan) + +# VCN10 trend +res_VCN10trend = get_VCN10trend(df_data, df_meta, + period=trend_period, + alpha=alpha, + sampleSpan=sampleSpan) + +# Start date for low water trend +res_DEBtrend = get_DEBtrend(df_data, df_meta, + period=trend_period, + alpha=alpha, + sampleSpan=sampleSpan, + thresold_type='VCN10', + select_longest=TRUE) +# res_DEBtrend = read_listofdf(resdir, 'res_DEBtrend') + +# Center date for low water trend +res_CENtrend = get_CENtrend(df_data, df_meta, + period=trend_period, + alpha=alpha, + sampleSpan=sampleSpan) ### 3.3. Break analysis # df_break = get_break(res_QAtrend$data, df_meta) @@ -286,7 +286,7 @@ df_shapefile = ini_shapefile(computer_data_path, fr_shpdir, fr_shpname, bs_shpdir, bs_shpname, sbs_shpdir, sbs_shpname, - rv_shpdir, rv_shpname, riv=TRUE) + rv_shpdir, rv_shpname, riv=FALSE) ### 4.1. Simple time panel to criticize station data # Plot time panel of debit by stations