fixing warnings and errors

This commit is contained in:
Roland Hollós 2023-02-08 09:20:36 +01:00
commit 4eb1e65c8b
27 changed files with 437 additions and 37 deletions

View File

@ -39,9 +39,12 @@ Imports:
tcltk,
Boruta,
rpart,
plotly,
rpart.plot
Maintainer: Roland Hollo's <hollorol@gmail.com>
Suggests: knitr,
rmarkdown,
VignetteBuilder: knitr
ByteCompile: true
RoxygenNote: 7.2.3
Encoding: UTF-8

View File

@ -11,6 +11,7 @@ export(copyMusoExampleTo)
export(corrigMuso)
export(createSoilFile)
export(flatMuso)
export(genEpc)
export(getAnnualOutputList)
export(getConstMatrix)
export(getDailyOutputList)
@ -19,7 +20,9 @@ export(getFilesFromIni)
export(getyearlycum)
export(getyearlymax)
export(multiSiteCalib)
export(musoCompareFiles)
export(musoDate)
export(musoGetValues)
export(musoGlue)
export(musoMapping)
export(musoMappingFind)
@ -40,6 +43,9 @@ export(saveAllMusoPlots)
export(setupMuso)
export(spinupMuso)
export(supportedMuso)
export(tuneMuso)
export(tuneMusoServer)
export(tuneMusoUI)
export(updateMusoMapping)
import(ggplot2)
import(utils)
@ -84,12 +90,38 @@ importFrom(lubridate,leap_year)
importFrom(magrittr,'%<>%')
importFrom(magrittr,'%>%')
importFrom(openxlsx,read.xlsx)
importFrom(plotly,add_trace)
importFrom(plotly,plot_ly)
importFrom(plotly,plotlyOutput)
importFrom(plotly,renderPlotly)
importFrom(rmarkdown,pandoc_version)
importFrom(rmarkdown,render)
importFrom(rpart,rpart)
importFrom(rpart,rpart.control)
importFrom(rpart.plot,rpart.plot)
importFrom(scales,percent)
importFrom(shiny,HTML)
importFrom(shiny,actionButton)
importFrom(shiny,checkboxInput)
importFrom(shiny,fluidPage)
importFrom(shiny,getShinyOption)
importFrom(shiny,isolate)
importFrom(shiny,mainPanel)
importFrom(shiny,numericInput)
importFrom(shiny,observeEvent)
importFrom(shiny,radioButtons)
importFrom(shiny,reactiveValues)
importFrom(shiny,selectInput)
importFrom(shiny,shinyApp)
importFrom(shiny,shinyOptions)
importFrom(shiny,sidebarLayout)
importFrom(shiny,sidebarPanel)
importFrom(shiny,tabPanel)
importFrom(shiny,tabsetPanel)
importFrom(shiny,tagList)
importFrom(shiny,tags)
importFrom(shiny,textAreaInput)
importFrom(shiny,titlePanel)
importFrom(stats,approx)
importFrom(tcltk,tk_choose.files)
importFrom(tibble,rownames_to_column)

View File

@ -270,10 +270,14 @@ musoGlue <- function(presCalFile, w, delta = 0.17, settings=setupMuso(), paramet
par(pari)
dev.off()
maxParValues <- preservedCalibtop5[which.max(preservedCalibtop5$combined),]
maxParValues <- unlist(preservedCalibtop5[which.max(preservedCalibtop5$combined),])[1:length(paramIndex)]
maxParIndexes <- paramIndex
write.csv(cbind.data.frame(calibrationPar=maxParValues,parameters=maxParIndexes),"maxLikelihood.csv")
maxLikelihoodParameters <- data.frame(parameter_index=maxParIndexes,parameter_value=maxParValues)
write.csv(cbind.data.frame(parameters=maxParIndexes, calibrationPar=maxParValues),
"maxlikelihood_parameters.csv")
cat("\n\n- A file containing the parameters with the maximum likelihood (maxlikelihood_parameters.csv) has been created.\n")
write.csv(optRanges,"optRanges.csv")
cat("- GLUE interval values have been written into optRanges.csv\n")
# browser()
# There are some serious problems with this implementation. The uncertainity bouns are not for the parameters, but for the output values. The median is pointwise median for all simulation.
# And the 95 and 5 percentile also.

View File

@ -5,7 +5,7 @@
#' @author Roland Hollos
#' @export
changemulline <- function(filePaths, calibrationPar, contents, src, outFiles=filePaths){
changemulline <- function(filePaths, calibrationPar, contents, src=NULL, outFiles=filePaths){
# browser()
if(is.null(src)){
src <- filePaths
@ -31,3 +31,38 @@ changeByIndex <- function (rowIndex, parameter, fileStringVector){
fileStringVector[i] <- changeNth(fileStringVector[i], h, parameter)
fileStringVector
}
#' musoGetValues
#'
#' Get values from a musofile by supplying muso indices
#'
#' @param filename The name of the musofile we want the value from (e.g. epc file)
#' @param indices muso indices
#' @usage musoGetValues(filename, indices)
#' @export
musoGetValues <- function(filename, indices){
sapply(indices, function(index){
colIndex <- round((index*100) %% 10) + 1
rowIndex <- as.integer(index)
as.numeric(unlist(strsplit(readLines(filename)[rowIndex],split="\\s+"))[colIndex])
})
}
#' musoCompareFiles
#'
#' A simple wrapper function based on musoGetValues where you can get multiple values from multiple files
#' using the supplied indices. It is useful for comparing files.
#'
#' @param filenames The name of the files where you can get the data from
#' @param indices muso indices
#' @usage musoCompareFiles(filenames, indices)
#' @export
musoCompareFiles <- function(filenames, indices){
sapply(filenames, function(fn){
musoGetValues(fn,indices)
})
}

View File

@ -29,7 +29,22 @@ randEpc <- function(parameterFile = "parameters.csv", location = "./epcDir",
for(i in seq(iterations)){
epcOut <- gsub("\\.",paste0("-",i,"."),basename(sourceEpc))
changemulline(filePaths = basename(sourceEpc), calibrationPar = randVals[[1]],
contents = randVals[[2]][i,],fileOut = epcOut, fileToChange = "epc")
contents = randVals[[2]][i,],outFiles = epcOut)
}
setwd(currDir)
}
#' genEpc
#'
#' randEpc is a random epc creator based on musoMonte
#' @author Roland HOLLOS
#' @param sourceEpc the original epc file-the template
#' @param parameters dataframe where in the first column there are the indices and the second column the values
#' @param location output location directory
#' @export
genEpc <- function (sourceEpc, targetEpc, parameters) {
changemulline(filePaths=sourceEpc,outFiles=targetEpc,
calibrationPar=parameters[,1],contents=parameters[,2])
}

View File

@ -590,7 +590,7 @@ agroLikelihood <- function(modVector,measured){
#' compareCalibratedWithOriginal
#'
#' This functions compareses the likelihood and the RMSE values of the simulations and the measurements
#' @param key
#' @param key keyword
compareCalibratedWithOriginal <- function(key, modOld, modNew, mes,
likelihoods, alignIndexes, musoCodeToIndex, nameGroupTable,
groupFun){

View File

@ -2,12 +2,12 @@
#'
#' This function generates MuSo compatibla dates for the data
#' @author Roland HOLLOS
#' @param startYear
#' @param numYears
#' @param timestep
#' @param combined
#' @param corrigated
#' @param format
#' @param startYear Start year of the simulations
#' @param numYears Number of the years of the simulation
#' @param timestep timestep of date creation
#' @param combined using separate y m d columns or not?
#' @param corrigated If leapyear ...
#' @param format "the date format"
#' @importFrom lubridate leap_year
#' @export

View File

@ -90,9 +90,9 @@ normalMuso<- function(settings=NULL,parameters=NULL,timee="d",debugging=FALSE,lo
if(!is.null(parameters)){
switch(fileToChange,
"epc" = tryCatch(changemulline(filename = epc[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R)
"epc" = tryCatch(changemulline(epc[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R)
error = function (e) {stop("Cannot change the epc file")}),
"ini" = tryCatch(changemulline(filename = iniInput[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R)
"ini" = tryCatch(changemulline(iniInput[1],calibrationPar,parameters), #(:DONE: trycatch :INSIDE: changeMuso.R)
error = function (e) {stop("Cannot change the ini file")}),
"both" = (stop("This option is not implemented yet, please choose epc or ini"))
)

View File

@ -68,9 +68,9 @@ plotMuso <- function(settings = NULL, variable = "all",
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})
colnames(Reva) <- unlist(settings$outputVars[[1]])
rownames(Reva) <- NULL
musoData <- cbind(musoDate(startYear = startYear,numYears = numberOfYears,combined = TRUE,corrigated=FALSE),
musoData <- cbind(musoDate(startYear = startYear,numYears = numberOfYears,combined = TRUE),
rep(1:365,numberOfYears),
musoDate(startYear = startYear,numYears = numberOfYears,combined = FALSE,corrigated=FALSE),as.data.frame(Reva))
musoDate(startYear = startYear,numYears = numberOfYears,combined = FALSE),as.data.frame(Reva))
colnames(musoData)[1:5]<-c("date","yearDay","year","day","month")
musoData <-musoData %>%
mutate(date=as.Date(as.character(date),"%d.%m.%Y"))
@ -275,28 +275,29 @@ plotMusoWithData <- function(mdata, plotName=NULL,
modellSettings = settings,
startDate = startDate,
endDate = endDate, leapYear = leapYearHandling, continious = continious),envir=environment())
mesData <- numeric(settings$numYears*365)
k <- 1
for(i in seq(mesData)){
if(i %in% modIndex){
mesData[i] <- measuredData[k]
k <- k + 1
} else {
mesData[i] <- NA
}
}
rm(k)
# mesData <- numeric(settings$numYears*365)
# k <- 1
# for(i in seq(mesData)){
# if(i %in% modIndex){
# mesData[i] <- measuredData[k]
# k <- k + 1
# } else {
# mesData[i] <- NA
# }
# }
# rm(k)
# modIndex and measuredData are created.
## measuredData is created
## baseData <- calibMuso(settings = settings, silent = silent, prettyOut = TRUE)[modIndex,]
baseData <- calibMuso(settings = settings, silent = silent, prettyOut = TRUE)
baseData <- calibMuso(settings = settings, silent = silent, prettyOut = TRUE)[modIndex,]
baseData[,1] <- as.Date(baseData[,1],format = "%d.%m.%Y")
selVarName <- colnames(baseData)[selVar]
if(!all.equal(colnames(baseData),unique(colnames(baseData)))){
notUnique <- setdiff((unlist(settings$dailyVarCodes)),unique(unlist(settings$dailyVarCodes)))
stop(paste0("Error: daily output variable list in the ini file must contain unique numbers. Check your ini files! Not unique codes: ",notUnique))
}
mesData<-cbind.data.frame(baseData[,1],mesData)
# mesData<-cbind.data.frame(baseData[,1],mesData)
mesData<-cbind.data.frame(baseData[,1],measuredData)
colnames(mesData) <- c("date", "measured")
p <- baseData %>%
ggplot(aes_string("date",selVarName)) +

View File

@ -254,7 +254,7 @@ rungetMuso <- function(settings, timee="d", debugging=FALSE, logfilename=NULL, k
Reva <- corrigMuso(settings,Reva)
rownames(Reva) <- musoDate(settings$startYear, settings$numYears)
} else {
rownames(Reva) <- musoDate(settings$startYear, settings$numYears, corrigated=FALSE)
rownames(Reva) <- musoDate(settings$startYear, settings$numYears) # TODO: Need fix
}
if(export!=FALSE){

View File

@ -52,9 +52,9 @@ spinupMuso <- function(settings=NULL, parameters=NULL, debugging=FALSE, logfilen
if(!is.null(parameters)){
switch(fileToChange,
"epc" = tryCatch(changemulline(filename = epc[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R)
"epc" = tryCatch(changemulline(filePaths = epc[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R)
error = function (e) {stop("Cannot change the epc file")}),
"ini" = tryCatch(changemulline(filename = iniInput[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R)
"ini" = tryCatch(changemulline(filePaths = iniInput[1],calibrationPar,parameters), #(:INSIDE: changeMuso.R)
error = function (e) {stop("Cannot change the ini file")}),
"both" = (stop("This option is not implemented yet, please choose epc or ini"))
)

173
RBBGCMuso/R/tuner.R Normal file
View File

@ -0,0 +1,173 @@
#' tuneMusoUI
#'
#' This is a simple parameter tuner function which works great in a flat directory systemj
#'
#' @param parameterFile optional, the parameter csv file
#' @importFrom plotly plotlyOutput
#' @importFrom shiny tags actionButton numericInput HTML checkboxInput titlePanel radioButtons textAreaInput fluidPage sidebarLayout sidebarPanel mainPanel getShinyOption tabsetPanel tabPanel tagList selectInput
#' @usage ...
#' @export
tuneMusoUI <- function(parameterFile = NULL, ...){
setwd(getShinyOption("musoRoot"))
dir.create("bck",showWarnings = FALSE)
file.copy("n.ini","bck/n.ini", overwrite=FALSE)
if(is.null(parameterFile)){
parameterFile <- "parameters.csv"
}
parameters <- read.csv(parameterFile, stringsAsFactors=FALSE)
settings <- setupMuso(...)
defaultValues <- musoGetValues(settings$epcInput[2],parameters[,2])
fluidPage(
# tags$head(tags$style(HTML("#iniContainer {width: 80vw;}"))),
tags$head(tags$style(HTML("#contolp {height: 80vh;overflow-y:scroll;}"))),
titlePanel("Biome-BGCMuSo parameter tuner"),
sidebarLayout(
sidebarPanel(tabsetPanel(type="tabs",
tabPanel("params",
checkboxInput("autoupdate","Automatic update"),
tags$div(id="controlp",selectInput("ovar",
label="Select output Variable",
choices=settings$dailyOutputTable$name,
width="40%"
),
do.call(tagList,lapply(1:nrow(parameters),function(x){
numericInput(paste0("param_",x),
parameters[x,1],
defaultValues[x],
step=defaultValues[x]/10,
width="40%"
)
}))),
tags$div(actionButton(inputId="runModel","Run MuSo"),
radioButtons(inputId="destination",
label="reference or modified",
choiceValues=c("auto","prev","next"),
choiceNames=c("automatic","reference","modified")))),
tabPanel("ini",tags$div(id="iniContainer",
textAreaInput("inifile","Normal Ini file",
value=paste(readLines(settings$iniInput[2]),
collapse="\n"))),
actionButton(inputId="getOriginalIni", "Load original"),
actionButton(inputId="overwriteIni", "overwrite")
)
)),
mainPanel(plotlyOutput(outputId="Result"))
)
)
}
#' tuneMusoServer
#'
#' Server program for tumeMuso
#'
#' @param input shiny input
#' @param output shiny output
#' @param session dinamic session management for shiny
#' @importFrom shiny reactiveValues isolate observeEvent
#' @importFrom plotly renderPlotly plot_ly add_trace
#' @usage ...
#' @export
tuneMusoServer <- function(input, output, session){
settings <- setupMuso()
dates <- as.Date(musoDate(settings$startYear, numYears=settings$numYears),"%d.%m.%Y")
parameters <- read.csv("parameters.csv", stringsAsFactors=FALSE)
outputList <- vector(mode = "list", length = 2)
outputList <- reactiveValues()
outputList[['prev']] <- character(0)
outputList[['next']] <- character(0)
observeEvent(input$runModel,{
paramVal <- sapply(1:nrow(parameters),function(x){
input[[paste0("param_", x)]]
})
if(isolate(input$destination) == "auto"){
outputList[['prev']] <- isolate(outputList[['next']])
outputList[['next']] <- calibMuso(settings = settings,
calibrationPar = parameters[,2],
parameters = paramVal)
} else {
outputList[[isolate(input$destination)]] <- calibMuso(settings = settings,
calibrationPar = parameters[,2],
parameters = paramVal)
}
})
observe({
if(input$autoupdate){
paramVal <- sapply(1:nrow(parameters),function(x){
input[[paste0("param_", x)]]
})
if(isolate(input$destination) == "auto"){
outputList[['prev']] <- isolate(outputList[['next']])
outputList[['next']] <- calibMuso(settings = settings,
calibrationPar = parameters[,2],
parameters = paramVal)
} else {
outputList[[isolate(input$destination)]] <- calibMuso(settings = settings,
calibrationPar = parameters[,2],
parameters = paramVal)
}
}
})
observe({
if(length(outputList[['next']])!=0){
output$Result <- renderPlotly(
{
p <- plot_ly()
if(length(outputList[['prev']])!=0){
p <- add_trace(p, x=dates, y=outputList[['prev']][,input$ovar], type='scatter',
mode='lines')
}
add_trace(p, x=dates, y=outputList[['next']][,input$ovar], color="red", type='scatter',
mode='lines')
}
)
}
})
observeEvent(input$getOriginalIni,{
updateTextAreaInput(session, "inifile", value=paste(readLines("bck/n.ini"),
collapse="\n") )
})
}
#' tuneMuso
#'
#' launchApp launch the shiny app
#' @param ... Other parameters for shinyApp function
#' @importFrom shiny shinyApp shinyOptions
#' @export
tuneMuso <- function(directory = NULL,...){
shinyOptions(workdir = getwd())
if(is.null(directory)){
shinyOptions(musoRoot = ".")
} else {
shinyOptions(musoRoot = normalizePath(directory))
}
shinyApp(ui = tuneMusoUI(), server = tuneMusoServer, options = list(...))
}

View File

@ -24,7 +24,7 @@ calibrateMuso(
naVal = NULL,
postProcString = NULL,
thread_prefix = "thread",
numCores = (parallel::detectCores() - 1),
numCores = max(c(parallel::detectCores() - 1, 1)),
pb = txtProgressBar(min = 0, max = iterations, style = 3),
maxLikelihoodEpc = TRUE,
pbUpdate = setTxtProgressBar,

View File

@ -4,7 +4,13 @@
\alias{changemulline}
\title{changemulline}
\usage{
changemulline(filePaths, calibrationPar, contents, src, outFiles = filePaths)
changemulline(
filePaths,
calibrationPar,
contents,
src = NULL,
outFiles = filePaths
)
}
\description{
The function uses the previous changspecline function to operate.

View File

@ -16,6 +16,9 @@ compareCalibratedWithOriginal(
groupFun
)
}
\arguments{
\item{key}{keyword}
}
\description{
This functions compareses the likelihood and the RMSE values of the simulations and the measurements
}

View File

@ -3,6 +3,16 @@
\name{createSoilFile}
\alias{createSoilFile}
\title{createSoilFile}
\usage{
createSoilFile(
lat,
lon,
outputFile = "recent.soi",
method = "constant",
apiURL,
template = system.file("examples/hhs/hhs.soi", package = "RBBGCMuso")
)
}
\description{
This function collects soil data from a given restapi, de default is soilGrid
}

21
RBBGCMuso/man/genEpc.Rd Normal file
View File

@ -0,0 +1,21 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/genEpc.R
\name{genEpc}
\alias{genEpc}
\title{genEpc}
\usage{
genEpc(sourceEpc, targetEpc, parameters)
}
\arguments{
\item{sourceEpc}{the original epc file-the template}
\item{parameters}{dataframe where in the first column there are the indices and the second column the values}
\item{location}{output location directory}
}
\description{
randEpc is a random epc creator based on musoMonte
}
\author{
Roland HOLLOS
}

View File

@ -3,6 +3,9 @@
\name{getSoilDataFull}
\alias{getSoilDataFull}
\title{getSoilDataFull}
\usage{
getSoilDataFull(lat, lon, apiURL)
}
\description{
This function collects soil data from a given restapi, de default is soilGrid
}

View File

@ -0,0 +1,17 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/changeMuso.R
\name{musoCompareFiles}
\alias{musoCompareFiles}
\title{musoCompareFiles}
\usage{
musoCompareFiles(filenames, indices)
}
\arguments{
\item{filenames}{The name of the files where you can get the data from}
\item{indices}{muso indices}
}
\description{
A simple wrapper function based on musoGetValues where you can get multiple values from multiple files
using the supplied indices. It is useful for comparing files.
}

View File

@ -13,6 +13,19 @@ musoDate(
prettyOut = FALSE
)
}
\arguments{
\item{startYear}{Start year of the simulations}
\item{numYears}{Number of the years of the simulation}
\item{combined}{using separate y m d columns or not?}
\item{timestep}{timestep of date creation}
\item{corrigated}{If leapyear ...}
\item{format}{"the date format"}
}
\description{
This function generates MuSo compatibla dates for the data
}

View File

@ -0,0 +1,16 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/changeMuso.R
\name{musoGetValues}
\alias{musoGetValues}
\title{musoGetValues}
\usage{
musoGetValues(filename, indices)
}
\arguments{
\item{filename}{The name of the musofile we want the value from (e.g. epc file)}
\item{indices}{muso indices}
}
\description{
Get values from a musofile by supplying muso indices
}

View File

@ -11,7 +11,9 @@ readObservedData(
leapYearHandling = TRUE,
convert.var = NULL,
convert.scalar = 1,
convert.fun = (function(x) { x * convert.scalar }),
convert.fun = (function(x) {
x * convert.scalar
}),
convert.file = NULL,
filterCol = NULL,
filterVal = 1,

View File

@ -42,7 +42,7 @@ nitInput=NULL, iniInput=NULL, epcInput=NULL)
\item{plougInput}{Via the plougInput parameter, the user can specify the location of the file that contains the ploughing information. By default the package reads this information from the INI files.}
\item{fertInput}{Via the fertInput parameter, ythe user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files.}
\item{fertInput}{Via the fertInput parameter, the user can specify the location of the file that contains the fertilizing information. By default the package reads this information from the INI files.}
\item{irrInput}{Via the irrInput parameter, the user can specify the location of the file that contains the irrigation information. By default the package reads this information from the INI files.}

14
RBBGCMuso/man/tuneMuso.Rd Normal file
View File

@ -0,0 +1,14 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/tuner.R
\name{tuneMuso}
\alias{tuneMuso}
\title{tuneMuso}
\usage{
tuneMuso(directory = NULL, ...)
}
\arguments{
\item{...}{Other parameters for shinyApp function}
}
\description{
launchApp launch the shiny app
}

View File

@ -0,0 +1,18 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/tuner.R
\name{tuneMusoServer}
\alias{tuneMusoServer}
\title{tuneMusoServer}
\usage{
...
}
\arguments{
\item{input}{shiny input}
\item{output}{shiny output}
\item{session}{dinamic session management for shiny}
}
\description{
Server program for tumeMuso
}

View File

@ -0,0 +1,14 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/tuner.R
\name{tuneMusoUI}
\alias{tuneMusoUI}
\title{tuneMusoUI}
\usage{
...
}
\arguments{
\item{parameterFile}{optional, the parameter csv file}
}
\description{
This is a simple parameter tuner function which works great in a flat directory systemj
}

View File

@ -7,13 +7,13 @@
updateMusoMapping(excelName, dest = "./", version = getOption("RMuso_version"))
}
\arguments{
\item{excelName}{Name of the excelfile which contains the parameters}
\item{excelName}{Name of the Excel file which contains the parameters}
}
\value{
The output code-variable matrix, and also the function changes the global variable
}
\description{
This function updates the Biome-BGCMuSo output code-variable matrix (creates a json file that is used internally by RBBGCMuso). Within Biome-BGCMuSo the output state variablesare marked by integer numbers (see the User's Guide). In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is handled by this function. The input Excel file must have the following column order: name, index, units, description (plus other optional columns line group). name refers to the abbreviation of the variable; index is the integer number of the output variable; unit is the unit of the variable; description is a meaningful text to explain the variable. The script will NOT work with other column order!
This function updates the Biome-BGCMuSo output code-variable matrix (creates a json file that is used internally by RBBGCMuso). Within Biome-BGCMuSo the output state variables are marked by integer numbers (see the User's Guide). In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is handled by this function. The input Excel file must have the following column order: name, index, units, description (plus other optional columns line group). name refers to the abbreviation of the variable; index is the integer number of the output variable; unit is the unit of the variable; description is a meaningful text to explain the variable. The script will NOT work with other column order!
}
\author{
Roland HOLLOS