An error occurred while loading the file. Please try again.
-
Heraut Louis authored93790e80
# \\\
# Copyright 2021-2022 Louis Héraut*1
#
# *1 INRAE, France
# louis.heraut@inrae.fr
#
# This file is part of ash R toolbox.
#
# ash R toolbox is free software: you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation, either version 3 of the License, or (at
# your option) any later version.
#
# ash R toolbox is distributed in the hope that it will be useful, but
# WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
# General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with ash R toolbox. If not, see <https://www.gnu.org/licenses/>.
# ///
#
#
# plotting/layout.R
#
# Regroups general parameters about plotting like the theme used ang
# color management. It mainly deals with the calling to specific
# plotting functions and the organisation of each plot for the
# generation of the PDF.
# Usefull library
library(ggplot2)
library(scales)
library(qpdf)
library(gridExtra)
library(gridtext)
library(dplyr)
library(grid)
library(ggh4x)
library(RColorBrewer)
library(rgdal)
library(shadowtext)
library(png)
# Sourcing R file
source('plotting/datasheet.R', encoding='UTF-8')
source('plotting/map.R', encoding='UTF-8')
source('plotting/matrix.R', encoding='UTF-8')
source('plotting/break.R', encoding='UTF-8')
source('plotting/tools.R', encoding='UTF-8')
## 1. PERSONALISATION ________________________________________________
### 1.1. Personal theme ______________________________________________
theme_ash =
theme(
# White background
panel.background=element_rect(fill='white'),
# Font
text=element_text(family='sans'),
# Border of plot
panel.border = element_rect(color="grey85",
fill=NA,
size=0.7),
# Grid
panel.grid.major.x=element_blank(),
panel.grid.major.y=element_blank(),
# Ticks marker
7172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140
axis.ticks.x=element_line(color='grey75', size=0.3),
axis.ticks.y=element_line(color='grey75', size=0.3),
# Ticks label
axis.text.x=element_text(color='grey40'),
axis.text.y=element_text(color='grey40'),
# Ticks length
axis.ticks.length=unit(1.5, 'mm'),
# Ticks minor
ggh4x.axis.ticks.length.minor=rel(0.5),
# Title
plot.title=element_blank(),
# Axis title
axis.title.x=element_blank(),
axis.title.y=element_text(size=9, vjust=1.2,
hjust=0.5, color='grey20'),
# Axis line
axis.line.x=element_blank(),
axis.line.y=element_blank(),
)
### 1.2. Color palette _______________________________________________
palette_perso = c('#0f3b57', # cold
'#1d7881',
'#80c4a9',
'#e2dac6', # mid
'#fadfad',
'#d08363',
'#7e392f') # hot
## 2. USEFUL GENERICAL PLOT __________________________________________
### 2.1. Void plot ___________________________________________________
# A plot completly blank
void = ggplot() + geom_blank(aes(1,1)) +
theme(
plot.background = element_blank(),
panel.grid.major = element_blank(),
panel.grid.minor = element_blank(),
panel.border = element_blank(),
panel.background = element_blank(),
axis.title.x = element_blank(),
axis.title.y = element_blank(),
axis.text.x = element_blank(),
axis.text.y = element_blank(),
axis.ticks = element_blank(),
axis.line = element_blank()
)
### 2.2. Contour void plot ___________________________________________
# A plot completly blank with a contour
contour = void +
theme(plot.background=element_rect(fill=NA, color="#EC4899"),
plot.margin=margin(t=0, r=0, b=0, l=0, unit="mm"))
## 3. LAYOUT _________________________________________________________
# Generates a PDF that gather datasheets, map and summarize matrix about the trend analyses realised on selected stations
layout_panel = function (df_data, df_meta, layout_matrix,
what_plot=c('datasheet', 'matrix', 'map'),
figdir='', filedir_opt='', filename_opt='',
variable='', df_trend=NULL,
alpha=0.1, unit2day=365.25, var='',
type='', glose=NULL, trend_period=NULL,
mean_period=NULL, colorForce=FALSE,
axis_xlim=NULL,
missRect=TRUE, time_header=NULL,
info_header=NULL, foot_note=TRUE,
info_height=2.8, time_ratio=2,
var_ratio=3, foot_height=1.25,
df_shapefile=NULL,
141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210
resources_path=NULL,
logo_dir=NULL,
AEAGlogo_file=NULL,
INRAElogo_file=NULL,
FRlogo_file=NULL) {
# Name of the document
outfile = "Panels"
# If there is an option to mention in the filename it adds it
if (filename_opt != '') {
outfile = paste(outfile, '_', filename_opt, sep='')
}
# Add the 'pdf' extensionto the name
outfile = paste(outfile, '.pdf', sep='')
# If there is not a dedicated figure directory it creats one
outdir = file.path(figdir, filedir_opt, sep='')
if (!(file.exists(outdir))) {
dir.create(outdir)
}
# Names of a temporary directory to store all the independent pages
outdirTmp = file.path(outdir, 'tmp')
# Creates it if it does not exist
if (!(file.exists(outdirTmp))) {
dir.create(outdirTmp)
# If it already exists it deletes the pre-existent directory
# and recreates one
} else {
unlink(outdirTmp, recursive=TRUE)
dir.create(outdirTmp)
}
# Number of type/variable
nbp = length(df_data)
# Convert data tibble to list of tibble if it is not the case
if (all(class(df_data) != 'list')) {
df_data = list(df_data)
}
if (all(class(df_trend) != 'list')) {
df_trend = list(df_trend)
if (length(df_trend) == 1) {
df_trend = replicate(nbp, df_trend)
}}
if (all(class(alpha) != 'list')) {
alpha = list(alpha)
# If there is only one value
if (length(alpha) == 1) {
# Replicates the value the number of times that there
# is of studied variables
alpha = replicate(nbp, alpha)
}}
# Same
if (all(class(unit2day) != 'list')) {
unit2day = list(unit2day)
if (length(unit2day) == 1) {
unit2day = replicate(nbp, unit2day)
}}
if (all(class(var) != 'list')) {
var = list(var)
if (length(var) == 1) {
var = replicate(nbp, var)
}}
211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280
if (all(class(glose) != 'list')) {
glose = list(glose)
if (length(glose) == 1) {
glose = replicate(nbp, glose)
}}
if (all(class(type) != 'list')) {
type = list(type)
if (length(type) == 1) {
type = replicate(nbp, type)
}}
if (all(class(missRect) != 'list')) {
missRect = list(missRect)
if (length(missRect) == 1) {
missRect = replicate(nbp, missRect)
}}
# Creates a blank list to store all the data of each type of plot
list_df2plot = vector(mode='list', length=nbp)
# For all the type of graph / number of studied variables
for (i in 1:nbp) {
# Creates a list that gather all the info for one type of graph
df2plot = list(data=df_data[[i]],
trend=df_trend[[i]],
alpha=alpha[[i]],
unit2day=unit2day[[i]],
var=var[[i]], type=type[[i]],
glose=glose[[i]],
missRect=missRect[[i]])
# Stores it
list_df2plot[[i]] = df2plot
}
df_page = tibble(section='Sommaire', subsection=NA, n=1)
# If map needs to be plot
if ('map' %in% what_plot) {
df_page = map_panel(list_df2plot,
df_meta,
idPer_trend=length(trend_period),
trend_period=trend_period,
mean_period=mean_period,
colorForce=colorForce,
df_shapefile=df_shapefile,
foot_note=foot_note,
foot_height=foot_height,
resources_path=resources_path,
logo_dir=logo_dir,
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% what_plot) {
df_page = matrix_panel(list_df2plot,
df_meta,
trend_period,
mean_period,
colorForce=colorForce,
slice=19,
outdirTmp=outdirTmp,
A3=TRUE,
foot_note=foot_note,
foot_height=foot_height,
resources_path=resources_path,
281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350
logo_dir=logo_dir,
AEAGlogo_file=AEAGlogo_file,
INRAElogo_file=INRAElogo_file,
FRlogo_file=FRlogo_file,
df_page=df_page)
}
# If datasheets needs to be plot
if ('datasheet' %in% what_plot) {
df_page = datasheet_panel(list_df2plot,
df_meta,
trend_period=trend_period,
mean_period=mean_period,
axis_xlim=axis_xlim,
colorForce=colorForce,
info_header=info_header,
time_header=time_header,
foot_note=foot_note,
layout_matrix=layout_matrix,
info_height=info_height,
time_ratio=time_ratio,
var_ratio=var_ratio,
foot_height=foot_height,
resources_path=resources_path,
logo_dir=logo_dir,
AEAGlogo_file=AEAGlogo_file,
INRAElogo_file=INRAElogo_file,
FRlogo_file=FRlogo_file,
outdirTmp=outdirTmp,
df_page=df_page)
}
summary_panel(df_page,
foot_note,
foot_height,
resources_path,
logo_dir=logo_dir,
AEAGlogo_file,
INRAElogo_file,
FRlogo_file,
outdirTmp)
# Combine independant pages into one PDF
details = file.info(list.files(outdirTmp, full.names=TRUE))
details = details[with(details, order(as.POSIXct(mtime))),]
listfile_path = rownames(details)
summary_path = listfile_path[length(listfile_path)]
listfile_path = listfile_path[-length(listfile_path)]
listfile_path = c(summary_path, listfile_path)
pdf_combine(input=listfile_path,
output=file.path(outdir, outfile))
}
## 4. PDF ORGANISATION PANEL _________________________________________
### 4.1. Summary _____________________________________________________
summary_panel = function (df_page, foot_note, foot_height, resources_path, logo_dir, AEAGlogo_file, INRAElogo_file, FRlogo_file, outdirTmp) {
text_title = paste(
"<b>Analyse de Stationnarité Hydrologique</b>",
sep='')
text_subtitle = paste(
"Bassin Adour-Garonnne",
sep='')
Sec_name = rle(df_page$section)$values
nSec = length(Sec_name)
351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420
text_sum1 = ''
text_page1 = ''
text_sum2 = ''
text_page2 = ''
nline = 0
nline_max = 58
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]
line = paste("<b>", idS, ". ", sec_name, "</b>", "<br>", sep='')
page = paste("<b>p.", n_page, "</b><br>", sep='')
if (nline <= nline_max) {
text_sum1 = paste(text_sum1, line, sep='')
text_page1 = paste(text_page1, page, sep='')
} else {
text_sum2 = paste(text_sum2, line, sep='')
text_page2 = paste(text_page2, page, sep='')
}
nline = nline + 1
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]
line = paste("<b>", idS, ".", idSS, ".</b> ",
subsec_name, "<br>", sep='')
page = paste("p.", n_page, "<br>", sep='')
if (nline <= nline_max) {
text_sum1 = paste(text_sum1, line, sep='')
text_page1 = paste(text_page1, page, sep='')
} else {
text_sum2 = paste(text_sum2, line, sep='')
text_page2 = paste(text_page2, page, sep='')
}
nline = nline + 1
}
}
if (nline <= nline_max) {
text_sum1 = paste(text_sum1, "<br>", sep='')
text_page1 = paste(text_page1, "<br>", sep='')
} else {
text_sum2 = paste(text_sum2, "<br>", sep='')
text_page2 = paste(text_page2, "<br>", sep='')
}
nline = nline + 1
}
# text_sum1 = gsub(" ", "<span style='color:white'>_</span>",
# text_sum1)
text_sum1 = gsub('[.]', '.', text_sum1)
text_page1 = gsub('[.]', '.', text_page1)
# text_sum2 = gsub(" ", "<span style='color:white'>_</span>",
# text_sum2)
text_sum2 = gsub('[.]', '.', text_sum2)
text_page2 = gsub('[.]', '.', text_page2)
# Converts all texts to graphical object in the right position
421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490
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))
gsubtitle = richtext_grob(text_subtitle,
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=15))
gsum1 = richtext_grob(text_sum1,
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))
gpage1 = richtext_grob(text_page1,
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))
gsum2 = richtext_grob(text_sum2,
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))
gpage2 = richtext_grob(text_page2,
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,
logo_dir,
AEAGlogo_file, INRAElogo_file,
FRlogo_file, foot_height)
P = list(gtitle, gsubtitle, gsum1, gpage1, gsum2, gpage2, foot)
LM = matrix(c(1, 1, 1, 1,
2, 2, 2, 2,
3, 4, 5, 6,
7, 7, 7, 7),
nrow=4, byrow=TRUE)
} else {
foot_height = 0
P = list(gtitle, gsubtitle, gsum1, gpage1, gsum2, gpage2)
LM = matrix(c(1, 1, 1, 1,
2, 2, 2, 2,
3, 4, 5, 6),
nrow=3, byrow=TRUE)
}
id_title = 1
id_subtitle = 2
id_page1 = 4
id_page2 = 6
id_foot = 7
LMcol = ncol(LM)
LMrow = nrow(LM)
LM = rbind(rep(99, times=LMcol), LM, rep(99, times=LMcol))
491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560
LMrow = nrow(LM)
LM = cbind(rep(99, times=LMrow), LM, rep(99, times=LMrow))
LMcol = ncol(LM)
title_height = 0.75
subtitle_height = 1.25
margin_size = 0.5
page_width = 2
height = 29.7
width = 21
row_height = (height - 2*margin_size - foot_height - title_height - subtitle_height) / (LMrow - 5)
Hcut = LM[, 2]
heightLM = rep(row_height, times=LMrow)
heightLM[Hcut == id_title] = title_height
heightLM[Hcut == id_subtitle] = subtitle_height
heightLM[Hcut == id_foot] = foot_height
heightLM[Hcut == 99] = margin_size
col_width = (width - 2*margin_size - 2*page_width) / (LMcol - 4)
Wcut = LM[4,]
widthLM = rep(col_width, times=LMcol)
widthLM[Wcut == id_page1 | Wcut == id_page2] = page_width
widthLM[Wcut == 99] = margin_size
# 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)
}
### 4.2. Foot note panel______________________________________________
foot_panel = function (name, n_page, resources_path, logo_dir, AEAGlogo_file, INRAElogo_file, FRlogo_file, foot_height) {
text_page = paste(
name, " <b>p. ", n_page, "</b>",
sep='')
text_date = paste (
format(Sys.Date(), "%B %Y"),
sep='')
# Converts all texts to graphical object in the right position
gtext_page = richtext_grob(text_page,
x=1, y=0,
margin=unit(c(t=0, r=0, b=0, l=0), "mm"),
hjust=1, vjust=0.5,
gp=gpar(col="#00A3A8", fontsize=8))
gtext_date = richtext_grob(text_date,
x=1, y=0.55,
margin=unit(c(t=0, r=0, b=0, l=0), "mm"),
hjust=1, vjust=0.5,
gp=gpar(col="#00A3A8", fontsize=6))
AEAGlogo_path = file.path(resources_path, logo_dir, AEAGlogo_file)
INRAElogo_path = file.path(resources_path, logo_dir, INRAElogo_file)
FRlogo_path = file.path(resources_path, logo_dir, FRlogo_file)
AEAGlogo_img = readPNG(AEAGlogo_path)
AEAGlogo_grob = rasterGrob(AEAGlogo_img,
y=0.49,
vjust=0.5,
561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599
width=unit(0.7*foot_height, "cm"))
INRAElogo_img = readPNG(INRAElogo_path)
INRAElogo_grob = rasterGrob(INRAElogo_img,
y=0.565,
vjust=0.5,
width=unit(1.08*foot_height, "cm"))
FRlogo_img = readPNG(FRlogo_path)
FRlogo_grob = rasterGrob(FRlogo_img,
x=0, hjust=0,
width=unit(1*foot_height, "cm"))
P = list(void,
FRlogo_grob, INRAElogo_grob, AEAGlogo_grob,
gtext_page, gtext_date)
# Creates the matrix layout
LM = matrix(c(1, 2, 3, 4, 5,
1, 2, 3, 4, 6),
nrow=2,
byrow=TRUE)
# And sets the relative width of each plot
widths = rep(1, times=ncol(LM))
widths[2] = 0.2
widths[3] = 0.25
widths[4] = 0.2
# Arranges all the graphical objetcs
plot = grid.arrange(grobs=P,
layout_matrix=LM,
widths=widths)
# Return the plot object
return (plot)
}