Merge pull request #22 from hollorol/version7

Version7
This commit is contained in:
Roland Hollós 2023-06-20 13:18:48 +00:00 committed by GitHub
commit ba579c2cfd
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
238 changed files with 156345 additions and 857 deletions

View File

@ -0,0 +1,18 @@
Package: RBBGCMuso
Title: An R package for BiomeBGC-MuSo ecosystem modelling
Version: 0.7.1
Authors@R: person("Roland", "Hollo's", , "hollorol@gmail.com", role = c("aut", "cre"))
Description: What the package does (one paragraph).
Depends: R (>= 3.3.2)
License: GPL-2
NeedsCompilation: no
Packaged: 2023-02-06 09:42:51 UTC; user
Author: Roland Hollo's [aut, cre]
Imports: grDevices, limSolve, stats, utils, graphics, Rcpp, magrittr,
dplyr, ggplot2, rmarkdown, tibble, tidyr, glue, scales, tcltk,
digest, jsonlite, data.table, gridExtra, lubridate, openxlsx,
ncdf4, future, httr, tcltk, Boruta, rpart, rpart.plot
Maintainer: Roland Hollo's <hollorol@gmail.com>
Suggests: knitr, rmarkdown,
VignetteBuilder: knitr
ByteCompile: true

View File

@ -0,0 +1,97 @@
# Generated by roxygen2: do not edit by hand
export(calibMuso)
export(calibrateMuso)
export(changemulline)
export(checkFileSystem)
export(checkMeteoBGC)
export(cleanupMuso)
export(compareMuso)
export(copyMusoExampleTo)
export(corrigMuso)
export(createSoilFile)
export(flatMuso)
export(getAnnualOutputList)
export(getConstMatrix)
export(getDailyOutputList)
export(getFilePath)
export(getFilesFromIni)
export(getyearlycum)
export(getyearlymax)
export(multiSiteCalib)
export(musoDate)
export(musoGlue)
export(musoMapping)
export(musoMappingFind)
export(musoMonte)
export(musoQuickEffect)
export(musoRand)
export(musoSensi)
export(normalMuso)
export(optiMuso)
export(paramSweep)
export(plotMuso)
export(plotMusoWithData)
export(randEpc)
export(readObservedData)
export(runMuso)
export(rungetMuso)
export(saveAllMusoPlots)
export(setupMuso)
export(spinupMuso)
export(supportedMuso)
export(updateMusoMapping)
import(ggplot2)
import(utils)
importFrom(data.table,':=')
importFrom(data.table,data.table)
importFrom(data.table,fread)
importFrom(digest,digest)
importFrom(dplyr,'%>%')
importFrom(dplyr,filter)
importFrom(dplyr,group_by)
importFrom(dplyr,mutate)
importFrom(dplyr,select)
importFrom(dplyr,summarize)
importFrom(dplyr,tbl_df)
importFrom(future,future)
importFrom(ggplot2,aes)
importFrom(ggplot2,aes_string)
importFrom(ggplot2,element_blank)
importFrom(ggplot2,element_text)
importFrom(ggplot2,facet_wrap)
importFrom(ggplot2,geom_bar)
importFrom(ggplot2,geom_line)
importFrom(ggplot2,geom_point)
importFrom(ggplot2,ggplot)
importFrom(ggplot2,ggsave)
importFrom(ggplot2,ggtitle)
importFrom(ggplot2,labs)
importFrom(ggplot2,scale_y_continuous)
importFrom(ggplot2,theme)
importFrom(ggplot2,theme_classic)
importFrom(ggplot2,xlab)
importFrom(ggplot2,ylab)
importFrom(glue,glue)
importFrom(gridExtra,grid.arrange)
importFrom(httr,GET)
importFrom(httr,config)
importFrom(httr,content)
importFrom(httr,with_config)
importFrom(jsonlite,write_json)
importFrom(limSolve,xsample)
importFrom(lubridate,leap_year)
importFrom(magrittr,'%<>%')
importFrom(magrittr,'%>%')
importFrom(openxlsx,read.xlsx)
importFrom(rmarkdown,pandoc_version)
importFrom(rmarkdown,render)
importFrom(rpart,rpart)
importFrom(rpart,rpart.control)
importFrom(rpart.plot,rpart.plot)
importFrom(scales,percent)
importFrom(stats,approx)
importFrom(tcltk,tk_choose.files)
importFrom(tibble,rownames_to_column)
importFrom(tidyr,gather)
importFrom(tidyr,separate)

View File

@ -0,0 +1,188 @@
#' getLogs
#'
#'This function gives us the muso logfiles with their path
#'
#'@param outputLoc This is the location of the output files.
#'@param outputNames These are the prefixes of the logfiles
#'@return Logfiles with paths
#'@keywords internal
getLogs <- function(outputLoc, outputNames, type = "spinup"){
switch(type,
"spinup" = return(grep(paste0(outputNames[1], ".log"), list.files(outputLoc), value = TRUE)),
"normal" = return(grep(paste0(outputNames[2], ".log"), list.files(outputLoc), value = TRUE)),
"both" = return(sapply(1:2, function (x){grep(paste0(outputNames[x], ".log"), list.files(outputLoc), value = TRUE)})))
}
#' readErrors
#'
#'This function reads the spinup and the normal logfiles and gives back the last line which indicates weather there are any errors during the model execution or not.
#'
#'@param outputLoc This is the location of the output file.
#'@param logfiles These are the names of the logfiles.
#'@return vector with 0 and 1 values, 1, if succed, 0 if not. The first is the spinup run, the second is the normal.
#'@keywords internal
readErrors <- function(outputLoc, logfiles, type = "both"){
if(length(logfiles)==0){
if(type=="normal"){
return(1)
} else {
return(c(0,0))
}
}
switch( type,
"both" = return(
as.numeric(
as.vector(
lapply(paste(outputLoc,logfiles,sep = "/"),
function(x) {
tail(readLines(x,-1),1)
}
)
)
)
),
"spinup" = print("spinup"),
"normal" = return(
abs(as.numeric(tail(readLines(file.path(outputLoc,logfiles),-1),1))-1)
)
)
}
#' getOutFiles
#'
#'This function gives us the muso output files with their paths
#'
#'@param outputLoc This is the location of the output files.
#'@param outputNames These are the prefixes of the logfiles.
#'@return Output files with their paths.
#'@keywords internal
getOutFiles <- function(outputLoc, outputNames){
return(grep("out$", grep(paste(paste0(outputNames, "*"), collapse = "|"), list.files(outputLoc), value=TRUE), value = TRUE))
}
#' stampAndCopy
#'
#'This function gives us the model output files with their paths
#'
#'@param outputLoc This is the location of the output files.
#'@param outputNames These are the prefixes of the logfiles
#'@return Output files with their paths
#'@keywords internal
stampAndDir <- function(outputLoc,names,stampDir, wrongDir, type="output", errorsign, logfiles){
switch(type,
"output" = (
file.copy(file.path(outputLoc,names)
,file.path(stampDir,paste0((stamp(stampDir)+1),"-",names))) ),
"general" = (function (){
stampnum <- stamp(stampDir)
lapply(names,function (x) file.copy(from = x ,to=paste(stampDir,"/",(stampnum+1),"-", basename(x),sep="")))
if(errorsign==1){
lapply(names, function (x) file.copy(from = paste(stampDir,"/",(stampnum+1),"-",basename(x),sep=""), to=wrongDir))}})()
)
}
compareNA <- function(v,a){
compared<- (v==a)
compared[is.na(compared)] <- FALSE
return(compared)
}
#' dynRound
#'
#'This function rounds a sequence (definded by its endpoints and the length) optimally
#'
#'@param x The lower end of the sequence
#'@param y The higher end of the sequence
#' @param seqLen The length of the sequence
#'@return rounded sequence
#'@keywords internal
dynRound <- function(x,y,seqLen){
digitNum <- 2
a <- seq(x,y, length = seqLen)
while(length(a) != length(unique(round(a,digitNum)))){
digitNum <- digitNum +1
}
return(round(a,digitNum))
}
readValuesFromFile <- function(epc, linums){
epcFile <- readLines(epc)
rows <- numeric(2)
values <- sapply(linums, function(x){
rows[1] <- as.integer(x)
rows[2] <- as.integer(round(100*x)) %% 10 + 1
epcFile <- readLines(epc)
selRow <- unlist(strsplit(epcFile[rows[1]], split= "[\t ]"))
selRow <- selRow[selRow!=""]
return(as.numeric(selRow[rows[2]]))
})
return(values)
}
#' readMeasuredMuso
#'
#' MuSo data reader
#' @importFrom data.table fread data.table
#' @export
readObservedData <- function(inFile,
naString = NULL, sep = ",",
leapYearHandling = TRUE,
convert.var = NULL,
convert.scalar = 1,
convert.fun = (function (x) {x * convert.scalar}),
convert.file = NULL,
filterCol = NULL,
filterVal = 1,
selVar = NULL
){
if(!is.null(naString)){
if(is.numeric(naString)){
baseData <- fread(file = inFile, sep=sep)
baseData <- as.data.frame(baseData)
baseData[baseData[,selVar] == naString,selVar] <- NA
} else {
baseData <- fread(file = inFile, sep=sep, na.strings = naString)
baseData <- as.data.frame(baseData)
}
} else {
baseData <- fread(file = inFile, sep=sep)
baseData <- as.data.frame(baseData)
}
if(!is.null(filterCol)){
filterVar<- colnames(baseData)[filterCol]
baseData[(baseData[,filterVar] == filterVal),selVar] <- NA
}
head(baseData)
if(!is.null(selVar)){
baseData[,selVar] <-convert.fun(baseData[,selVar])
}
return(data.table(baseData))
}

View File

@ -0,0 +1,36 @@
.onLoad <- function(libname,pkgname){
RMuso_version <- 7
cat(sprintf("This is RBBGCMuso version 1.0\nDefault Biome-BGCMuSo version: %d",
RMuso_version))
RMuso_constMatrix <- list(epc=NULL,soil=NULL)
RMuso_varTable <- list()
#___________________________
sapply(names(RMuso_constMatrix),function(fType){
sapply(list.files(path=system.file("data",package="RBBGCMuso"),
pattern=sprintf("^%sConstMatrix\\d\\.json$",fType), full.names=TRUE),function(fName){
constMatrix <- jsonlite::read_json(fName,simplifyVector = TRUE)[,c(1,2,3,4,9,5,6,7,8)]
version <- gsub(".*(\\d)\\.json","\\1",fName)
RMuso_constMatrix[[fType]][[version]] <<- constMatrix
})
RMuso_constMatrix
# RMuso_constMatrix <<- RMuso_constMatrix
})
sapply(list.files(path=system.file("data",package="RBBGCMuso"),
pattern="^varTable\\d\\.json$", full.names=TRUE),function(fName){
varTable <- jsonlite::read_json(fName,simplifyVector = TRUE)
version <- gsub(".*(\\d)\\.json","\\1",fName)
RMuso_varTable[[version]] <<- varTable
})
RMuso_depTree<- read.csv(file.path(system.file("data",package="RBBGCMuso"),"depTree.csv"), stringsAsFactors=FALSE)
options(RMuso_version=RMuso_version,
RMuso_constMatrix=RMuso_constMatrix,
RMuso_varTable=RMuso_varTable,
RMuso_depTree=RMuso_depTree
)
# getOption("RMuso_constMatrix")$soil[[as.character(getOption("RMuso_version"))]]
}

View File

@ -0,0 +1,368 @@
#' calibMuso
#'
#' This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a well-structured way.
#'
#' @author Roland Hollos
#' @param settings You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment
#' @param timee The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly. I recommend to use daily data, the yearly and monthly data is not well-tested yet.
#' @param debugging If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles
#' @param keepEpc If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.
#' @param export if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.
#' @param silent If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed.
#' @param aggressive It deletes every possible modell-outputs from the previous modell runs.
#' @param parameters In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4)
#' @param logfilename If you want to set a specific name for your logfiles you can set this via logfile parameter
#' @param leapYear Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.
#' @param keepBinary In default RBBGCMuso to keep working area as clean as possible, deletes all the regular output files. The results are directly printed to the standard output, but you can redirect it, and save it to a variable, or you can export your results to the desired destination in a desired format. Whith this variable you can enable to keep the binary output files. If you want to set the location of the binary output, please take a look at the binaryPlace argument.
#' @param binaryPlace The place of the binary output files.
#' @param fileToChange You can change any line of the epc or the ini file, you just have to specify with this variable which file you van a change. Two options possible: "epc", "ini"
#' @param skipSpinup If TRUE, calibMuso wont do spinup simulation
#' @param prettyOut date ad Date type, separate year, month, day vectors
#' @return No return, outputs are written to file
#' @usage calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL,
#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
#' @import utils
#' @export
calibMuso <- function(settings=setupMuso(), calibrationPar=NULL,
parameters=NULL, outVars = NULL, timee="d",
debugging=FALSE, logfilename=NULL,
keepEpc=FALSE, export=FALSE,
silent=FALSE, aggressive=FALSE,
keepBinary=FALSE,
binaryPlace = "./", fileToChange = "epc",
skipSpinup = TRUE, modifyOriginal = FALSE, prettyOut = FALSE,
postProcString = NULL,
doBackup=TRUE
){ #
########################################################################
###########################Set local variables and places###############
########################################################################
if(doBackup){
file.copy(eval(parse(text = sprintf("settings$%sInput[2]", fileToChange))),file.path(settings$inputLoc),overwrite=FALSE)
}
bck <- file.path(settings$inputLoc, "bck",
basename(eval(parse(text = sprintf("settings$%sInput[2]", fileToChange)))))
if(!silent){
cat("Biome-BGC simulation started\n") # ZOLI
}
Linuxp <-(Sys.info()[1]=="Linux")
##Copy the variables from settings
inputLoc <- settings$inputLoc
outputLoc <- settings$outputLoc
outputNames <- settings$outputNames
executable <- settings$executable
iniInput <- settings$iniInput
epc <- settings$epcInput
if(is.null(calibrationPar)){
calibrationPar <- settings$calibrationPar
}
binaryPlace <- normalizePath(binaryPlace)
whereAmI<-getwd()
## Set the working directory to the inputLoc temporarly.
setwd(inputLoc)
if(debugging){#If debugging option turned on
#If log or ERROR directory does not exists create it!
dirName<-file.path(inputLoc,"LOG")
dirERROR<-file.path(inputLoc,"ERROR")
if(!dir.exists(dirName)){
dir.create(dirName)
}
if(!dir.exists(dirERROR)){
dir.create(dirERROR)
}
}
if(keepEpc) {
epcdir <- dirname(epc[1])
print(epcdir)
WRONGEPC<-file.path(inputLoc,"WRONGEPC")
EPCS<-file.path(inputLoc,"EPCS")
if(!dir.exists(WRONGEPC)){
dir.create(WRONGEPC)
}
if(!dir.exists(EPCS)){
dir.create(EPCS)
}
}
#############################################################
############################spinup run############################
##########################################################
if(aggressive == TRUE){
cleanupMuso(location = outputLoc,deep = TRUE)
}
##change the epc file if and only if there are given parameters
if(!is.null(parameters)){
changemulline(filePaths = epc[2],
calibrationPar = calibrationPar,
contents = parameters,
src = if(file.exists(bck)){
bck
} else {
NULL
})
# fileToChange = fileToChange,)
}
##We change the working directory becase of the model, but we want to avoid sideeffects, so we save the current location and after that we will change everything to it.
if(!skipSpinup) {
##Run the model for the spinup run.
if(silent){#silenc mode
if(Linuxp){
#In this case, in linux machines
tryCatch(system(paste(executable,iniInput[1],"> /dev/null",sep=" ")),
error= function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")})
} else {
#In windows machines there is a show.output.on.console option
tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE),
error= function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")})
}
} else {
system(paste(executable,iniInput[1],sep=" "))
}
logspinup <- getLogs(outputLoc,outputNames,type="spinup")
## logspinup <- grep(paste0(outputNames[1],".log"), list.files(outputLoc),value = TRUE)
## logspinup <- list.files(outputLoc)[grep("log$",list.files(outputLoc))]#load the logfiles
if(length(logspinup)==0){
if(keepEpc){
stampnum<-stamp(EPCS)
lapply(epc,function (x) file.copy(from = x ,to=paste(EPCS,"/",(stampnum+1),"-", basename(x),sep="")))
lapply(epc, function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",basename(x),sep=""), to=WRONGEPC))
setwd(whereAmI)
stop("Modell Failure")
}
setwd(whereAmI)
stop("Modell Failure") #in that case the modell did not create even a logfile
}
if(length(logspinup)>1){
spincrash<-TRUE
} else {
if(identical(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1),character(0))){
spincrash<-TRUE
} else {
spincrash <- (tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)!=1)
}
}
} else {spincrash <- FALSE}
#If the last line in the logfile is 0 There are mistakes so the spinup crashes
if(!spincrash){##If spinup did not crashed, run the normal run.
#####################################################################
###########################normal run#########################
#################################################################
##for the sake of safe we set the location again
setwd(inputLoc)
if(silent){
if(Linuxp){
tryCatch(system(paste(executable,iniInput[2],"> /dev/null",sep=" ")),
error =function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")})
} else {
tryCatch(system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE),
error =function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")} )
}
} else {
tryCatch(system(paste(executable,iniInput[2],sep=" ")),
error =function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")})
}
##read the output
switch(timee,
"d"=(Reva <- tryCatch(getdailyout(settings), #(:INSIDE: getOutput.R )
error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"m"=(Reva <- tryCatch(getmonthlyout(settings), #(:INSIDE: getOutput.R )
error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"y"=(Reva <- tryCatch(getyearlyout(settings), #(:INSIDE: getOutput.R )
error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")}))
)
if(keepBinary){
possibleNames <- tryCatch(getOutFiles(outputLoc = outputLoc,outputNames = outputNames),
error=function (e){
setwd((whereAmI))
stop("Cannot find output files")})
stampAndDir(outputLoc = outputLoc,names = possibleNames,stampDir=binaryPlace,type="output")
}
}
if(skipSpinup){
logfiles <- tryCatch(getLogs(outputLoc,outputNames,type="normal"),
error = function (e){
setwd(whereAmI)
stop("Cannot find log files, something went wrong")})
} else {
logfiles <- tryCatch(getLogs(outputLoc,outputNames,type="both"),
error = function (e){
setwd(whereAmI)
stop("Cannot find log files, something went wrong")})
}
## list.files(outputLoc)[grep("log$",list.files(outputLoc))]#creating a vector for logfilenames
###############################################
#############LOG SECTION#######################
###############################################
if(skipSpinup){
errorsign <- readErrors(outputLoc=outputLoc,logfiles=logfiles,type="normal")
} else {
perror <- readErrors(outputLoc=outputLoc,logfiles=logfiles) #vector of spinup and normalrun error
##if errorsign is 1 there is error, if it is 0 everything ok
perror[is.na(perror)]<-0
if(length(perror)>sum(perror)){
errorsign <- 1
} else {
if(length(perror)==1){
errorsign <- 1
} else {
if(spincrash){
errorsign <- 1
} else {
errorsign <- 0
} }
}
}
if(keepEpc){#if keepepc option turned on
if(length(unique(dirname(epc)))>1){
stop("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?")
} else {
if(skipSpinup){
stampAndDir(stampDir=EPCS, wrongDir=WRONGEPC, names=epc[2], type="general", errorsign=errorsign, logfiles=logfiles)
}
stampAndDir(stampDir=EPCS, wrongDir=WRONGEPC, names=epc, type="general", errorsign=errorsign, logfiles=logfiles)
}
}
if(debugging){ #debugging is boolean
logfiles <- file.path(outputLoc,logfiles)
stampAndDir(stampDir=dirName, wrongDir=dirERROR, names=logfiles, type="general",errorsign=errorsign,logfiles=logfiles)}
#cleanupMuso(location=outputLoc,deep = FALSE)
if(errorsign==1){
stop("Modell Failure")
}
if(timee=="d"){
if(!prettyOut){
colnames(Reva) <- unlist(settings$outputVars[[1]])
} else{
Reva <- cbind.data.frame(
musoDate(startYear = settings$startYear,
numYears = settings$numYears,
combined = FALSE, prettyOut = TRUE),
Reva)
colnames(Reva) <- as.character(c("date","day","month","year",unlist(settings$outputVars[[1]])) )
}
} else {
if(timee=="y")
colnames(Reva) <- unlist(settings$outputVars[[2]])
}
if(!is.null(postProcString)){
Reva <- postProcMuso(Reva,postProcString)
}
## if(leapYear){
## Reva <- corrigMuso(settings,Reva)
## if(!prettyOut){
## rownames(Reva) <- musoDate(settings$startYear,settings$numYears)
## }
## } else {
## if(!prettyOut){
## rownames(Reva) <- musoDate(settings$startYear, settings$numYears)
## }
## }
if(!prettyOut){
rownames(Reva) <- musoDate(settings$startYear, numYears = settings$numYears)
}
if(export!=FALSE){
setwd(whereAmI)
## switch(fextension(export),
## "csv"=(write.csv(Reva,export)),
## "xlsx"=(),
## "odt"=
## )
write.csv(Reva,export)
} else{
setwd(whereAmI)
return(Reva)
}
}

View File

@ -0,0 +1,396 @@
#' calibrateMuso
#'
#' This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution for all selected parameters.
#' @author Roland HOLLOS
#' @importFrom future future
#' @export
calibrateMuso <- function(measuredData, parameters =read.csv("parameters.csv", stringsAsFactor=FALSE), startDate = NULL,
endDate = NULL, formatString = "%Y-%m-%d",
dataVar, outLoc = "./calib",
preTag = "cal-", settings = setupMuso(),
outVars = NULL, iterations = 100,
skipSpinup = TRUE, plotName = "calib.jpg",
modifyOriginal=TRUE, likelihood, uncertainity = NULL,
naVal = NULL, postProcString = NULL,
thread_prefix="thread", numCores = max(c(parallel::detectCores()-1,1)), pb = txtProgressBar(min=0, max=iterations, style=3),
maxLikelihoodEpc=TRUE,
pbUpdate = setTxtProgressBar, outputLoc="./", method="GLUE",lg = FALSE, w=NULL, ...){
future::plan(future::multisession)
file.remove(list.files(path = settings$inputLoc, pattern="progress.txt", recursive = TRUE, full.names=TRUE))
file.remove(list.files(path = settings$inputLoc, pattern="preservedCalib.csv", recursive = TRUE, full.names=TRUE))
unlink(file.path(settings$inputLoc,"thread"),recursive=TRUE)
# ____ _ _ _ _
# / ___|_ __ ___ __ _| |_ ___ | |_| |__ _ __ ___ __ _ __| |___
# | | | '__/ _ \/ _` | __/ _ \ | __| '_ \| '__/ _ \/ _` |/ _` / __|
# | |___| | | __/ (_| | || __/ | |_| | | | | | __/ (_| | (_| \__ \
# \____|_| \___|\__,_|\__\___| \__|_| |_|_| \___|\__,_|\__,_|___/
copyToThreadDirs(thread_prefix, numcores = numCores, runDir = settings$inputLoc)
# ____ _ _ _
# | _ \ _ _ _ __ | |_| |__ _ __ ___ __ _ __| |___
# | |_) | | | | '_ \ | __| '_ \| '__/ _ \/ _` |/ _` / __|
# | _ <| |_| | | | | | |_| | | | | | __/ (_| | (_| \__ \
# |_| \_\\__,_|_| |_| \__|_| |_|_| \___|\__,_|\__,_|___/
threadCount <- distributeCores(iterations, numCores)
fut <- lapply(1:numCores, function(i) {
# browser()
future({
tryCatch(
musoSingleThread(measuredData, parameters, startDate,
endDate, formatString,
dataVar, outLoc,
preTag, settings,
outVars, iterations = threadCount[i],
skipSpinup, plotName,
modifyOriginal, likelihood, uncertainity,
naVal, postProcString, i)
, error = function(e){
writeLines(as.character(iterations),"progress.txt")
})
# musoSingleThread(measuredData, parameters, startDate,
# endDate, formatString,
# dataVar, outLoc,
# preTag, settings,
# outVars, iterations = threadCount[i],
# skipSpinup, plotName,
# modifyOriginal, likelihood, uncertainity,
# naVal, postProcString, i)
})
})
# __ ___ _ _
# \ \ / / |__ __ _| |_ ___| |__ _ __ _ __ ___ ___ ___ ___ ___
# \ \ /\ / /| '_ \ / _` | __/ __| '_ \ | '_ \| '__/ _ \ / __/ _ \/ __/ __|
# \ V V / | | | | (_| | || (__| | | | | |_) | | | (_) | (_| __/\__ \__ \
# \_/\_/ |_| |_|\__,_|\__\___|_| |_| | .__/|_| \___/ \___\___||___/___/
# |_|
getProgress <- function(){
# threadfiles <- list.files(settings$inputLoc, pattern="progress.txt", recursive = TRUE)
threadfiles <- list.files(pattern="progress.txt", recursive = TRUE)
if(length(threadfiles)==0){
return(0)
} else {
sum(sapply(threadfiles, function(x){
partRes <- readLines(x)
if(length(partRes)==0){
return(0)
} else {
return(as.numeric(partRes))
}
}))
}
}
progress <- 0
while(progress < iterations){
Sys.sleep(1)
progress <- tryCatch(getProgress(), error=function(e){progress})
if(is.null(pb)){
pbUpdate(as.numeric(progress))
} else {
pbUpdate(pb,as.numeric(progress))
}
}
if(!is.null(pb)){
close(pb)
}
# ____ _ _
# / ___|___ _ __ ___ | |__ (_)_ __ ___
# | | / _ \| '_ ` _ \| '_ \| | '_ \ / _ \
# | |__| (_) | | | | | | |_) | | | | | __/
# \____\___/|_| |_| |_|_.__/|_|_| |_|\___|
resultFiles <- list.files(pattern="preservedCalib.*csv$",recursive=TRUE)
res0 <- read.csv(grep("thread_1/",resultFiles, value=TRUE),stringsAsFactors=FALSE)
if(numCores==1){
results <- res0
} else {
resultFilesSans0 <- grep("thread_1/", resultFiles, value=TRUE, invert=TRUE)
# results <- do.call(rbind,lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE)}))
resultsSans0 <- lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE, header=FALSE)})
resultsSans0 <- do.call(rbind,resultsSans0)
colnames(resultsSans0) <- colnames(res0)
results <- (rbind(res0,resultsSans0))
}
switch(method,
"GLUE"={
musoGlue(results, parameters=parameters,settings=settings, w=w, lg=lg)
},
"agromo"={
liks <- results[,sprintf("%s_likelihood",names(likelihood))]
epcIndexes <- future::value(fut[[1]], stdout = FALSE, signal=FALSE)
epcVals <- results[which.max(liks),1:length(epcIndexes)]
epcPlace <- file.path(dirname(settings$inputFiles),settings$epc)[2]
changemulline(filePaths= epcPlace, epcIndexes,
epcVals, src =epcPlace,# settings$epcInput[2],
outFiles = file.path(outputLoc, "maxLikelihood_epc.epc"))
names(epcVals) <- epcIndexes
xdate <- as.Date(measuredData$date)
meanM <- measuredData[,sprintf("mean.%s", names(likelihood))]
minsd <- meanM - measuredData[,sprintf("sd.%s", names(likelihood)[1])]
maxsd <- meanM + measuredData[,sprintf("sd.%s", names(likelihood)[1])]
minM <- measuredData[,sprintf("min.%s", names(likelihood)[1])]
maxM <- measuredData[,sprintf("max.%s", names(likelihood)[1])]
plot(xdate, minM, type="l", xlab=NA, ylim=c(min(minM)*0.8, max(maxM)*1.1), ylab = names(likelihood)[1])
lines(xdate, maxM)
polygon(c(xdate,rev(xdate)),c(minM,rev(maxM)), col="gray",border=NA)
lines(xdate, minsd)
lines(xdate, maxsd)
polygon(c(xdate,rev(xdate)),c(minsd,rev(maxsd)), col="gray30",border=NA)
points(xdate,meanM)
varIndex <- match(as.character(dataVar),settings$dailyVarCodes)
apriori <- calibMuso(settings)
modDates <- as.Date(row.names(apriori), format="%d.%m.%Y")
lines(modDates, apriori[,varIndex],col="brown")
calibrated <- calibMuso(settings, calibrationPar = as.numeric(names(epcVals)), parameters=epcVals)
lines(modDates, calibrated[,varIndex],col="blue")
},
stop(sprintf("method: %s not found, please choose from {GLUE, agromo}. See more about this in the documentation of the function!", method))
)
}
copyToThreadDirs <- function(prefix="thread", numcores=parallel::detectCores()-1, runDir="."){
dir.create(file.path(runDir,prefix), showWarnings=TRUE)
fileNames <- grep(".*thread$", list.files(runDir,full.names=TRUE), value=TRUE, invert=TRUE)
invisible(sapply(1:numcores,function(corenum){
threadDir <- file.path(runDir,prefix,paste0(prefix,"_",corenum),"")
dir.create(threadDir, showWarnings=FALSE)
file.copy(from=fileNames,to=threadDir, overwrite=FALSE, recursive=TRUE)
}))
}
musoSingleThread <- function(measuredData, parameters = NULL, startDate = NULL,
endDate = NULL, formatString = "%Y-%m-%d",
dataVar, outLoc = "./calib",
preTag = "cal-", settings = setupMuso(),
outVars = NULL, iterations = 300,
skipSpinup = TRUE, plotName = "calib.jpg",
modifyOriginal=TRUE, likelihood, uncertainity = NULL,
naVal = NULL, postProcString = NULL, threadNumber) {
setwd(paste0(settings$inputLoc, "/thread/thread_", threadNumber))
iniFiles <- file.path(settings$iniInput)
# iniFiles <- list.files(pattern=".*ini")
# if(length(iniFiles)==1){
# iniFiles <- rep(iniFiles, 2)
# }
settings <- setupMuso(iniInput = iniFiles)
# Exanding likelihood
likelihoodFull <- as.list(rep(NA,length(dataVar)))
names(likelihoodFull) <- names(dataVar)
if(!missing(likelihood)) {
lapply(names(likelihood),function(x){
likelihoodFull[[x]] <<- likelihood[[x]]
})
}
defaultLikelihood <- which(is.na(likelihood))
if(length(defaultLikelihood)>0){
likelihoodFull[[defaultLikelihood]] <- (function(x, y){
exp(-sqrt(mean((x-y)^2)))
})
}
mdata <- measuredData
if(is.null(parameters)){
parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) {
stop("You need to specify a path for the parameters.csv, or a matrix.")
})
} else {
if((!is.list(parameters)) & (!is.matrix(parameters))){
parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){
stop("Cannot find neither parameters file neither the parameters matrix")
})
}}
outLoc <- normalizePath(outLoc)
outLocPlain <- basename(outLoc)
currDir <- getwd()
if(!dir.exists(outLoc)){
dir.create(outLoc)
warning(paste(outLoc," is not exists, so it was created"))
}
outLoc <- normalizePath(outLoc)
parameterNames <- parameters[,1]
pretag <- file.path(outLoc,preTag)
##reading the original epc file at the specified
## row numbers
print("optiMuso is randomizing the epc parameters now...",quote = FALSE)
if(iterations < 3000){
randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = 3000)
randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),]
} else {
randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations)
}
origEpc <- readValuesFromFile(settings$epc[2],randVals[[1]])
partialResult <- matrix(ncol=length(randVals[[1]])+2*length(dataVar))
colN <- randVals[[1]]
colN[match(parameters[,2],randVals[[1]])] <- parameters[,1]
colN[match(parameters[,2], randVals[[1]])[!is.na(match(parameters[,2],randVals[[1]]))]] <- parameters[,1]
colnames(partialResult) <- c(colN,sprintf("%s_likelihood",names(dataVar)),
sprintf("%s_rmse",names(dataVar)))
numParameters <- length(colN)
partialResult[1:numParameters] <- origEpc
## Prepare the preservedCalib matrix for the faster
## run.
pretag <- file.path(outLoc,preTag)
musoCodeToIndex <- sapply(dataVar,function(musoCode){
settings$dailyOutputTable[settings$dailyOutputTable$code == musoCode,"index"]
})
resultRange <- (numParameters + 1):(ncol(partialResult))
## Creating function for generating separate
## csv files for each run
settings$iniInput[2] %>%
(function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>%
unlink
randValues <- randVals[[2]]
settings$calibrationPar <- randVals[[1]]
if(!is.null(naVal)){
measuredData <- as.data.frame(measuredData)
measuredData[measuredData == naVal] <- NA
}
alignIndexes <- alignMuso(settings,measuredData)
if(!is.null(uncertainity)){
uncert <- measuredData[alignIndexes$meas,uncertainity]
} else {
uncert <- NULL
}
# browser()
if(threadNumber == 1){
origModellOut <- calibMuso(settings=settings, silent=TRUE, skipSpinup = skipSpinup, postProcString=postProcString, modifyOriginal=modifyOriginal)
partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar,
mod=origModellOut,
mes=measuredData,
likelihoods=likelihood,
alignIndexes=alignIndexes,
musoCodeToIndex = musoCodeToIndex,uncert=uncert)
write.csv(x=origModellOut, file=paste0(pretag, 1, ".csv"))
write.csv(x=partialResult, file="preservedCalib.csv",row.names=FALSE)
}
print("Running the model with the random epc values...", quote = FALSE)
# if(!is.null(postProcString)){
# colNumb <- length(settings$dailyVarCodes) + 1
# }
for(i in 2:(iterations+1)){
tmp <- tryCatch(calibMuso(settings = settings,
parameters = randValues[(i-1),],
silent= TRUE,
skipSpinup = skipSpinup, modifyOriginal=modifyOriginal, postProcString = postProcString), error = function (e) NULL)
if(is.null(tmp)){
partialResult[,resultRange] <- NA
} else {
partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar,
mod=tmp,
mes=measuredData,
likelihoods=likelihood,
alignIndexes=alignIndexes,
musoCodeToIndex = musoCodeToIndex, uncert = uncert)
}
partialResult[1:numParameters] <- randValues[(i-1),]
write.table(x=partialResult, file="preservedCalib.csv", append=TRUE, row.names=FALSE,
sep=",", col.names=FALSE)
write.csv(x=tmp, file=paste0(pretag, (i+1),".csv"))
writeLines(as.character(i-1),"progress.txt")
}
if(threadNumber == 1){
return(randVals[[1]])
}
}
distributeCores <- function(iterations, numCores){
perProcess<- iterations %/% numCores
numSimu <- rep(perProcess,numCores)
gainers <- sample(1:numCores, iterations %% numCores)
numSimu[gainers] <- numSimu[gainers] + 1
numSimu
}
prepareFromAgroMo <- function(fName){
obs <- read.table(fName, stringsAsFactors=FALSE, sep = ";", header=T)
obs <- reshape(obs, timevar="var_id", idvar = "date", direction = "wide")
dateCols <- apply(do.call(rbind,(strsplit(obs$date, split = "-"))),2,as.numeric)
colnames(dateCols) <- c("year", "month", "day")
cbind.data.frame(dateCols, obs)
}
calcLikelihoodsAndRMSE <- function(dataVar, mod, mes, likelihoods, alignIndexes, musoCodeToIndex, uncert){
mes <- as.data.frame(mes)
# NOT COMPATIBLE WITH OLD MEASUREMENT DATA, mes have to be a matrix
likelihoodRMSE <- sapply(names(dataVar),function(key){
modelled <- mod[alignIndexes$mod,musoCodeToIndex[key]]
selected <- grep(sprintf("%s$", key), colnames(mes))
# browser()
measured <- mes[alignIndexes$meas,selected]
if(is.null(dim(measured))){
notNA <- !is.na(measured)
m <- measured <- measured[notNA]
} else {
notNA <- sapply(1:nrow(measured), function(x){!any(is.na(measured[x,]))})
measured <- measured[notNA,]
m <- measured[,grep("^mean", colnames(measured))]
}
modelled <- modelled[notNA]
# uncert <- uncert[!is.na(measured)]
# measured <- measured[!is.na(measured)]
res <- c(likelihoods[[key]](modelled, measured),
sqrt(mean((modelled-m)^2))
)
# browser()
res
})
names(likelihoodRMSE) <- c(sprintf("%s_likelihood",dataVar), sprintf("%s_rmse",dataVar))
return(c(likelihoodRMSE[1,],likelihoodRMSE[2,]))
}
agroLikelihood <- function(modVector,measured){
mu <- measured[,grep("mean", colnames(measured))]
stdev <- measured[,grep("^sd", colnames(measured))]
ndata <- nrow(measured)
sum(sapply(1:ndata, function(x){
dnorm(modVector, mu[x], stdev[x], log = TRUE)
}), na.rm=TRUE)
}
maxLikelihoodAgromo <- function (results, imgPath, varName, ...) {
}

View File

@ -0,0 +1,311 @@
#' optiMuso
#'
#' This function calculates the -users specified- likelihood for random model input.
#'
#' @author Roland HOLLOS
#' @param measuredDataFile a
#' @param parameters b
#' @param sep c
#' @param startDate d
#' @param endDate e
#' @param formatString a
#' @param filterCol a
#' @param filterVal b
#' @param selVar c
#' @param outLoc c
#' @param pretag a
#' @param calPar a
#' @param skipSpinup a
#' @param iterations c
#' @param constrains d
#' @param likelihood d
#' @param settings e
#' @param leapYear b
#' @param plotName u
#' @importFrom ggplot2 ggplot aes_string geom_point ggsave
#' @importFrom magrittr '%>%'
#' @importFrom gridExtra grid.arrange
#' @export
optiMuso <- function(measuredData, parameters = NULL, startDate = NULL,
endDate = NULL, formatString = "%Y-%m-%d",
dataVar, outLoc = "./calib",
preTag = "cal-", settings = setupMuso(),
outVars = NULL, iterations = 30,
skipSpinup = TRUE, plotName = "calib.jpg",
modifyOriginal=TRUE, likelihood, uncertainity = NULL,
naVal = NULL, postProcString = NULL, w=NULL, lg=FALSE, parallel = TRUE) {
# Exanding likelihood
likelihoodFull <- as.list(rep(NA,length(dataVar)))
names(likelihoodFull) <- names(dataVar)
if(!missing(likelihood)) {
lapply(names(likelihood),function(x){
likelihoodFull[[x]] <<- likelihood[[x]]
})
}
defaultLikelihood <- which(is.na(likelihood))
if(length(defaultLikelihood)>0){
likelihoodFull[[defaultLikelihood]] <- (function(x, y){
exp(-sqrt(mean((x-y)^2)))
})
}
mdata <- measuredData
if(is.null(parameters)){
parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) {
stop("You need to specify a path for the parameters.csv, or a matrix.")
})
} else {
if((!is.list(parameters)) & (!is.matrix(parameters))){
parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){
stop("Cannot find neither parameters file neither the parameters matrix")
})
}}
outLoc <- normalizePath(outLoc)
outLocPlain <- basename(outLoc)
currDir <- getwd()
if(!dir.exists(outLoc)){
dir.create(outLoc)
warning(paste(outLoc," is not exists, so it was created"))
}
outLoc <- normalizePath(outLoc)
parameterNames <- parameters[,1]
pretag <- file.path(outLoc,preTag)
##reading the original epc file at the specified
## row numbers
print("optiMuso is randomizing the epc parameters now...",quote = FALSE)
if(iterations < 3000){
randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = 3000)
randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),]
} else {
randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations)
}
origEpc <- readValuesFromFile(settings$epc[2],randVals[[1]])
partialResult <- matrix(ncol=length(randVals[[1]])+2*length(dataVar))
colN <- randVals[[1]]
colN[match(parameters[,2],randVals[[1]])] <- parameters[,1]
colnames(partialResult) <- c(colN,sprintf("%s_likelihood",names(dataVar)),
sprintf("%s_rmse",names(dataVar)))
numParameters <- length(colN)
partialResult[1:numParameters] <- origEpc
## Prepare the preservedCalib matrix for the faster
## run.
pretag <- file.path(outLoc,preTag)
musoCodeToIndex <- sapply(dataVar,function(musoCode){
settings$dailyOutputTable[settings$dailyOutputTable$code == musoCode,"index"]
})
resultRange <- (numParameters + 1):(ncol(partialResult))
## Creating function for generating separate
## csv files for each run
progBar <- txtProgressBar(1,iterations,style=3)
settings$iniInput[2] %>%
(function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>%
unlink
randValues <- randVals[[2]]
settings$calibrationPar <- randVals[[1]]
if(!is.null(naVal)){
measuredData <- as.data.frame(measuredData)
measuredData[measuredData == naVal] <- NA
}
alignIndexes <- alignMuso(settings,measuredData)
if(!is.null(uncertainity)){
uncert <- measuredData[alignIndexes$meas,uncertainity]
} else {
uncert <- NULL
}
# browser()
# browser()
origModellOut <- calibMuso(settings=settings, silent=TRUE, skipSpinup = skipSpinup, postProcString=postProcString, modifyOriginal=modifyOriginal)
partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar,
mod=origModellOut,
mes=measuredData,
likelihoods=likelihood,
alignIndexes=alignIndexes,
musoCodeToIndex = musoCodeToIndex,uncert=uncert)
write.csv(x=origModellOut, file=paste0(pretag, 1, ".csv"))
print("Running the model with the random epc values...", quote = FALSE)
# if(!is.null(postProcString)){
# colNumb <- length(settings$dailyVarCodes) + 1
# }
write.csv(x=partialResult, file="preservedCalib.csv",row.names=FALSE)
for(i in 2:(iterations+1)){
# browser()
tmp <- tryCatch(calibMuso(settings = settings,
parameters = randValues[(i-1),],
silent= TRUE,
skipSpinup = skipSpinup, modifyOriginal=modifyOriginal, postProcString = postProcString), error = function (e) NULL)
if(is.null(tmp)){
partialResult[,resultRange] <- NA
} else {
partialResult[,resultRange] <- calcLikelihoodsAndRMSE(dataVar=dataVar,
mod=tmp,
mes=measuredData,
likelihoods=likelihood,
alignIndexes=alignIndexes,
musoCodeToIndex = musoCodeToIndex, uncert = uncert)
}
partialResult[1:numParameters] <- randValues[(i-1),]
write.table(x=partialResult, file="preservedCalib.csv", append=TRUE, row.names=FALSE,
sep=",", col.names=FALSE)
write.csv(x=tmp, file=paste0(pretag, (i+1),".csv"))
setTxtProgressBar(progBar,i)
}
musoGlue("preservedCalib.csv",w=w, lg = lg)
}
alignMuso <- function (settings,measuredData) {
# Have to fix for other starting points also
modelDates <- seq(from= as.Date(sprintf("%s-01-01",settings$startYear)),
by="days",
to=as.Date(sprintf("%s-12-31",settings$startYear+settings$numYears-1)))
modelDates <- grep("-02-29",modelDates,invert=TRUE, value=TRUE)
measuredDates <- apply(measuredData,1,function(xrow){
sprintf("%s-%s-%s",xrow[1],xrow[2],xrow[3])
})
modIndex <- match(as.Date(measuredDates), as.Date(modelDates))
measIndex <- which(!is.na(modIndex))
modIndex <- modIndex[!is.na(modIndex)]
cbind.data.frame(model=modIndex,meas=measIndex)
}
# calcLikelihoodsAndRMSE <- function(dataVar, mod, mes, likelihoods, alignIndexes, musoCodeToIndex, uncert){
#
# likelihoodRMSE <- sapply(names(dataVar),function(key){
# # browser()
# modelled <- mod[alignIndexes$mod,musoCodeToIndex[key]]
# measured <- mes[alignIndexes$meas,key]
# modelled <- modelled[!is.na(measured)]
# # uncert <- uncert[!is.na(measured)]
# measured <- measured[!is.na(measured)]
# res <- c(likelihoods[[key]](modelled, measured, uncert),
# sqrt(mean((modelled-measured)^2))
# )
# res
# })
# names(likelihoodRMSE) <- c(sprintf("%s_likelihood",dataVar), sprintf("%s_rmse",dataVar))
#
# return(c(likelihoodRMSE[1,],likelihoodRMSE[2,]))
# }
#' musoGlue
#'
#' This function calculates the -users specified- likelihood for random model input.
#'
#' @author Roland HOLLOS
#' @param plotName u
#' @export
musoGlue <- function(presCalFile, w, delta = 0.17, settings=setupMuso(), parameters=read.csv("parameters.csv",
stringsAsFactors=FALSE), lg=FALSE){
if(is.data.frame(presCalFile)){
preservedCalib <- presCalFile
} else {
preservedCalib <- read.csv(presCalFile)
}
paramIndex <- parameters[(match(colnames(preservedCalib),parameters[,1])),2]
paramIndex <- paramIndex[!is.na(paramIndex)]
paramIndex <- c(paramIndex,
as.numeric(gsub("X","",
grep("X[0-9]{1,}",
colnames(preservedCalib),value=TRUE))))
preservedCalib <- preservedCalib[-1,] #original
likeIndexes <- grep("likelihood",colnames(preservedCalib))
if(!is.null(w)){
forCombine<- sapply(names(w),function(n){
grep(sprintf("%s_likelihood",n),colnames(preservedCalib))
})
preservedCalib[["combined"]] <- apply(as.data.frame(Map(function(x,y){
toNormalize <- preservedCalib[,y]
toNormalize <- toNormalize / sqrt(sum(x^2))
toNormalize * x
},w,forCombine)), 1, sum)
} else {
preservedCalib[["combined"]] <- preservedCalib[,grep("likelihood",colnames(preservedCalib),value=TRUE)]
}
parameterIndexes <- 1:(min(likeIndexes)-1)
preservedCalib <- preservedCalib[!is.na(preservedCalib$combined),]
unfilteredLikelihood <- preservedCalib$combined
top5points <- preservedCalib$combined>quantile(preservedCalib$combined,0.95)
preservedCalibtop5 <- preservedCalib[,]
optRanges <-t(apply(preservedCalibtop5,2,function(x) quantile(x,c(0.05,0.5,0.95))))
pdf("dotplot.pdf")
if(lg){
plot(Reduce(min, -(unfilteredLikelihood), accumulate=TRUE),type="l", ylab="-log(likelihood)",xlab="iterations")
} else {
plot(Reduce(min, -log(unfilteredLikelihood), accumulate=TRUE),type="l", ylab="-log(likelihood)",xlab="iterations")
}
pari <- par(mfrow=c(1,2))
for(i in seq_along(colnames(preservedCalib)[parameterIndexes])){
plot(preservedCalib[,i],preservedCalib[,"combined"],pch=19,cex=.1, ylab="likelihood",
main = colnames(preservedCalib)[i], xlab="")
plot(preservedCalibtop5[,i],preservedCalibtop5[,"combined"],pch=19,cex=.1, ylab="likelihood",
main = paste0(colnames(preservedCalibtop5)[i]," (behav.)"), xlab="")
abline(v=optRanges[i,1],col="blue")
abline(v=optRanges[i,2],col="green")
abline(v=optRanges[i,3],col="red")
}
par(pari)
dev.off()
maxParValues <- preservedCalibtop5[which.max(preservedCalibtop5$combined),]
maxParIndexes <- paramIndex
write.csv(cbind.data.frame(calibrationPar=maxParValues,parameters=maxParIndexes),"maxLikelihood.csv")
write.csv(optRanges,"optRanges.csv")
# 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.
# dataVec <- preservedCalibtop5$combined
# closestToMedian <- function (dataVec) {
# match(sort(dataVec)[min(which(sort(dataVec)>=median(dataVec)))], dataVec)
# }
#
# while(is.null(optimalEpc)){
# match(quantile(preservedCalibtop5$combined,0.5), preservedCalibtop5$combined)
# optInterval <-t(apply(preservedCalibtop5,2,function(x) quantile(x,c(0.5-delta,0.5+delta))))
# optParamRange <- cbind.data.frame(rownames(optInterval)[parameterIndexes],as.numeric(paramIndex),optInterval[parameterIndexes,])
# optimalEpc <- tryCatch(musoRand(optParamRange,iterations = 2), error=function(e){NULL})
# delta <- delta*1.05
# if(delta > 0.5){
# delta <- 0.5
# }
# if((delta == 0.5) && is.null(optimalEpc)){
# stop("cannot find optimal value in the given range")
# }
# }
# print("getOptim")
# optimalEpc[[2]] <- optimalEpc[[2]][1,]
# write.csv(as.data.frame(optimalEpc),"epcOptim.csv")
# print(head(optRanges,n=-2))
# calibMuso(calibrationPar=optimalEpc[[1]],parameters=optimalEpc[[2]])
# file.copy(settings$epcInput[2],"epcOptim.epc")
}
generateOptEpc <- function(optRanges,delta, maxLikelihood=FALSE){
if(missing(delta)){
}
}

View File

@ -0,0 +1,33 @@
#' changemulline
#'
#' The function uses the previous changspecline function to operate.
#'
#' @author Roland Hollos
#' @export
changemulline <- function(filePaths, calibrationPar, contents, src, outFiles=filePaths){
# browser()
if(is.null(src)){
src <- filePaths
}
fileStringVector <- readLines(src)
Map(function(index, content){
fileStringVector <<- changeByIndex(index, content, fileStringVector)
}, calibrationPar, contents)
writeLines(fileStringVector, outFiles)
}
changeNth <- function (string,place,replacement) {
trimws(gsub(sprintf("^((.*?\\s+){%s})(.*?\\s+)", place), sprintf("\\1%s ", replacement), paste0(string," "), perl=TRUE),
which="right")
}
changeByIndex <- function (rowIndex, parameter, fileStringVector){
h <- round((rowIndex*100) %% 10)
i <- as.integer(rowIndex)
fileStringVector[i] <- changeNth(fileStringVector[i], h, parameter)
fileStringVector
}

View File

@ -0,0 +1,103 @@
#' checkMeteoBGC
#'
#' This function calculates the daily and yearly statistics for a given meteorology file (mtc43).
#'
#' @author Erzsebet Kristof
#' @param settings The output of setupMuso
#' @param metFileName The name of the meteorology file (mtc43).
#' @param skip Number of header lines in meteorology file.
#' @param numericReport If numericReport is set to FALSE, the function returns with a text report. If numericReport is set to TRUE, the function returns with a numeric report.
#' @param type meteorology for spinup or normal run
#' @return It depends on the numericReport parameter. The function returns with a text report, or with a numeric report.
#' @export
checkMeteoBGC <- function(settings=NULL, skip = 4, numericReport = FALSE,type="normal"){
if(is.null(settings)){
settings <- setupMuso()
}
metFileName <- settings$metInput[type]
intMin <- function(x){
round(min(x,na.rm = TRUE), digits = 1)
}
intMax <- function(x){
round(max(x,na.rm = TRUE), digits = 1)
}
sradAvgShortestDay <- function(x,y){
round(mean(x[na.omit(y) == min(y, na.rm=TRUE)]), digits=1)
}
sradAvgLongestDay <- function(x,y){
round(mean(x[na.omit(y) == max(y, na.rm=TRUE)]), digits=1)
}
metTable <- tryCatch(read.table(metFileName, skip = skip), error = function(e){
stop(sprintf("Cannot read or find meteorology file: %s", metFileName))
})
yearlyPrcpSum <- tapply(metTable$V6,list(metTable$V1), sum)
yearlyTempAvg <- tapply(metTable$V5,list(metTable$V1), mean)
yearlyVpdAvg <- tapply(metTable$V7,list(metTable$V1), mean)
timeFrame <- range(metTable[,1])
if(!numericReport){
cat("Daily and yearly statistics of meteorological data for the time period of",
timeFrame[1], "-", timeFrame[2], ":\n
Precipitation data:
Minimum and maximum of daily sums:",
intMin(metTable$V6), "cm and", intMax(metTable$V6), "cm.
Minimum and maximum of yearly sums:",
intMin(yearlyPrcpSum), "cm and", intMax(yearlyPrcpSum), "cm.\n
Temperature data:
Lowest and highest daily temperatures (Tmin and Tmax):",
intMin(metTable$V4), "deg C and", intMax(metTable$V3), "deg C.
Minimum and maximum of yearly averages (based on Tday):",
intMin(yearlyTempAvg), "deg C and", intMax(yearlyTempAvg), "deg C.\n
Solar radiation data:
Minimum and maximum of daily values:",
intMin(metTable$V8), "W m-2 and", intMax(metTable$V8), "W m-2.
Averages of the shortest and longest days:",
sradAvgShortestDay(metTable$V8, metTable$V9),"W m-2 and",
sradAvgLongestDay(metTable$V8, metTable$V9), "W m-2.\n
Vapour pressure deficit data:
Minimum and maximum of daily values:",
intMin(metTable$V7), "Pa and", intMax(metTable$V7), "Pa.
Minimum and maximum of yearly averages:",
intMin(yearlyVpdAvg), "Pa and", intMax(yearlyVpdAvg), "Pa.\n")
} else {
report <- list()
cat("Numeric report:\n")
report["Precipitation"] <- list(data.frame(minimum = c(daily = intMin(metTable$V6),
yearly = intMin(yearlyPrcpSum)),
maximum = c(daily = intMax(metTable$V6),
yearly = intMax(yearlyPrcpSum))))
report["Temperature"] <- list(data.frame(minimum = c(daily = intMin(metTable$V4),
yearly = intMin(yearlyTempAvg)),
maximum = c(daily = intMax(metTable$V3),
yearly = intMax(yearlyTempAvg))))
report["Solar radiation"] <- list(data.frame(minimum = c(daily = intMin(metTable$V8),
shortest_longest_day = sradAvgShortestDay(metTable$V8, metTable$V9)),
maximum = c(daily = intMax(metTable$V8),
shortest_longest_day = sradAvgLongestDay(metTable$V8, metTable$V9))))
report["Vapour pressure deficit"] <- list(data.frame(minimum = c(daily = intMin(metTable$V7),
yearly = intMin(yearlyVpdAvg)),
maximum = c(daily = intMax(metTable$V7),
yearly = intMax(yearlyVpdAvg))))
return(report)
}
}

View File

@ -0,0 +1,55 @@
#'cleanupMuso
#'
#' cleanupMuso can erase all of the unnecessary log and output files.
#'
#' @author Roland HOLLOS
#' @param location This is the place (directory) where your output files are located.
#' @param simplicity TRUE or FALSE. If TRUE cleanupMuso will erase only the log files from the location
#' @param deep If it is TRUE, it will delete every files from the subdirectories also
#' @usage cleanupMuso(location=NULL, simplicity=TRUE,deep=FALSE)
#' @export
cleanupMuso <- function(location=NULL, simplicity=TRUE,deep=FALSE){
if(is.null(location)){
location<-"./"
}
logDir<-file.path(location,"LOG")
errDir<-file.path(location,"ERROR")
epcDir<-file.path(location,"EPCS")
wroDir<-file.path(location,"WRONGEPC")
if(deep){
if(dir.exists(logDir)){
file.remove(
list.files(logDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE)
)
}
if(dir.exists(errDir)){
file.remove(
list.files(errDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE))
}
if(dir.exists(epcDir)){
file.remove(
list.files(epcDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE))
}
if(dir.exists(wroDir)){
file.remove(
list.files(wroDir,pattern="(out$)|(endpoint$)|(log$)", full.names=TRUE))
}
file.remove(list.files(location, pattern="(out$)|(endpoint$)|(log$)",full.names=TRUE))}
if(!simplicity){
file.remove(list.files(location, pattern="(out$)|(endpoint$)|(log$)",full.names=TRUE))
} else {
file.remove(list.files(location, pattern="log$",full.names=TRUE))}
}

View File

@ -0,0 +1,68 @@
#'rungetMuso
#'
#' This function runs the Biome-BGCMuSo model and reads its outputfile in a well structured way.
#'
#' @author Roland Hollos
#' @keywords internal
#'
## degubMuso <- function(inputloc,outputloc,debugging,errorsign,){
## if((debugging=="stamplog")|(debugging==TRUE)){#If debugging option turned on
## ##If log or ERROR directory does not exists create it!
## dirName<-paste(inputloc,"LOG",sep="")
## dirERROR<-paste(inputloc,"ERROR",sep="")
## if(!dir.exists(dirName)){
## dir.create(dirName)
## }
## if(!dir.exists(dirERROR)){
## dir.create(dirERROR)
## }
## }
## if(debugging=="stamplog"){
## stampnum<-stamp(dirName)
## if(inputloc==outputloc){
## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep=""), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
## } else {
## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep="/"), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
## }
## if(errorsign==1){
## lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",(stampnum+1),"-",x,sep=""), to=dirERROR ))}
## } else { if(debugging){
## if(is.null(logfilename)){
## if(inputloc==outputloc){
## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep=""), to=paste(dirName,"/", x, sep="")))
## } else {
## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep="/"), to=paste(dirName,"/", x, sep="")))
## }
## if(errorsign==1){
## lapply( logfiles, function (x) file.rename(from=paste(dirName,"/", x, sep=""), to=dirERROR))
## }
## } else {
## if(inputloc==outputloc){#These are very ugly solutions for a string problem: inputloc: "./", if outputloc equalent of inputloc, it ends with "/", the string manipulation can not handle this. The better solution is easy, but I dont have enough time(Roland Hollo's)
## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep=""), to=paste(dirName, "/",logfilename,"-",x,sep="")))
## } else {
## lapply( logfiles, function (x) file.rename(from=paste(outputloc,x, sep="/"), to=paste(dirName, "/",logfilename,"-",x,sep="")))
## }
## if(errorsign==1){
## lapply( logfiles, function (x) file.rename(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR))
## }
## }
## }}
## return(errorsign)
## }

View File

@ -0,0 +1,267 @@
getQueue <- function(depTree=options("RMuso_depTree")[[1]], startPoint){
if(length(startPoint) == 0){
return(c())
}
parent <- depTree[depTree[,"name"] == startPoint,"parent"]
c(getQueue(depTree, depTree[depTree[,"child"] == depTree[depTree[,"name"] == startPoint,"parent"],"name"]),parent)
}
isRelative <- function(path){
substr(path,1,1) != '/'
}
#' getFilePath
#'
#' This function reads the ini file and for a chosen fileType it gives you the filePath
#' @param iniName The name of the ini file
#' @param filetype The type of the choosen file. For options see options("RMuso_depTree")[[1]]$name
#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]
#' @export
getFilePath <- function(iniName, fileType, execPath = "./", depTree=options("RMuso_depTree")[[1]]){
if(!file.exists(iniName) || dir.exists(iniName)){
stop(sprintf("Cannot find iniFile: %s", iniName))
}
startPoint <- fileType
startRow <- depTree[depTree[,"name"] == startPoint,]
startExt <- startRow$child
parentFile <- Reduce(function(x,y){
tryCatch(file.path(execPath,gsub(sprintf("\\.%s.*",y),
sprintf("\\.%s",y),
grep(sprintf("\\.%s",y),readLines(x),value=TRUE,perl=TRUE))), error = function(e){
stop(sprintf("Cannot find %s",x))
})
},
getQueue(depTree,startPoint)[-1],
init=iniName)
if(startRow$mod > 0){
tryCatch(
gsub(sprintf("\\.%s.*", startExt),
sprintf("\\.%s", startExt),
grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE,perl=TRUE))[startRow$mod]
,error = function(e){stop(sprintf("Cannot read %s",parentFile))})
} else {
res <- tryCatch(
gsub(sprintf("\\.%s.*", startExt),
sprintf("\\.%s",startExt),
grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE, perl=TRUE))
,error = function(e){stop(sprintf("Cannot read %s", parentFile))})
unique(gsub(".*\\t","",res))
}
}
#' getFilesFromIni
#'
#' This function reads the ini file and gives yout back the path of all file involved in model run
#' @param iniName The name of the ini file
#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]
#' @export
getFilesFromIni <- function(iniName, execPath = "./", depTree=options("RMuso_depTree")[[1]]){
res <- lapply(depTree$name,function(x){
tryCatch(getFilePath(iniName,x,execPath,depTree), error = function(e){
return(NA);
})
})
names(res) <- depTree$name
res
}
#' flatMuso
#'
#' This function reads the ini file and creates a directory (named after the directory argument) with all the files the modell uses with this file. the directory will be flat.
#' @param iniName The name of the ini file
#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]
#' @param directory The destination directory for flattening. At default it will be flatdir
#' @export
flatMuso <- function(iniName, execPath="./", depTree=options("RMuso_depTree")[[1]], directory="flatdir", d=TRUE,outE=TRUE){
dir.create(directory, showWarnings=FALSE, recursive = TRUE)
files <- getFilesFromIni(iniName,execPath,depTree)
files <- sapply(unlist(files)[!is.na(files)], function(x){ifelse(isRelative(x),file.path(execPath,x),x)})
file.copy(unlist(files), directory, overwrite=TRUE)
file.copy(iniName, directory, overwrite=TRUE)
filesByName <- getFilesFromIni(iniName, execPath, depTree)
for(i in seq_along(filesByName)){
fileLines <- readLines(file.path(directory,list.files(directory, pattern = sprintf("*\\.%s", depTree$parent[i])))[1])
sapply(filesByName[[i]],function(origname){
if(!is.na(origname)){
fileLines <<- gsub(origname, basename(origname), fileLines, fixed=TRUE)
}
})
if(!is.na(filesByName[[i]][1])){
writeLines(fileLines, file.path(directory,list.files(directory, pattern = sprintf("*\\.%s", depTree$parent[i])))[1])
}
}
iniLines <- readLines(file.path(directory, basename(iniName)))
outPlace <- grep("OUTPUT_CONTROL", iniLines, perl=TRUE)+1
if(outE){
iniLines[outPlace] <- tools::file_path_sans_ext(basename(iniName))
} else {
iniLines[outPlace] <- basename(strsplit(iniLines[outPlace], split = "\\s+")[[1]][1])
}
if(d){
iniLines[outPlace + 1] <- 1
}
writeLines(iniLines, file.path(directory, basename(iniName)))
}
#' checkFileSystem
#'
#' This function checks the MuSo file system, if it is correct
#' @param iniName The name of the ini file
#' @param depTree The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]
#' @export
checkFileSystem <- function(iniName,root = ".", depTree = options("RMuso_depTree")[[1]]){
recoverAfterEval({
setwd(root)
fileNames <- getFilesFromIni(iniName, depTree)
if(is.na(fileNames$management)){
fileNames[getLeafs("management")] <- NA
}
fileNames <- fileNames[!is.na(fileNames)]
errorFiles <- fileNames[!file.exists(unlist(fileNames))]
})
return(errorFiles)
}
recoverAfterEval <- function(expr){
wd <- getwd()
tryCatch({
eval(expr)
setwd(wd)
}, error=function(e){
setwd(wd)
stop(e)
})
}
getLeafs <- function(name, depTree=options("RMuso_depTree")[[1]]){
if(length(name) == 0){
return(NULL)
}
if(name[1] == "ini"){
return(getLeafs(depTree$name))
}
pname <- depTree[ depTree[,"name"] == name[1] , "child"]
children <- depTree[depTree[,"parent"] == pname,"child"]
if(length(children)==0){
if(length(name) == 1){
return(NULL)
} else{
apname <- depTree[ depTree[,"name"] == name[2] , "child"]
achildren <- depTree[depTree[,"parent"] == apname,"child"]
if(length(achildren)!=0){
return(c(name[1],name[2],getLeafs(name[-1])))
} else{
return(c(name[1], getLeafs(name[-1])))
}
}
}
childrenLogic <-depTree[,"child"] %in% children
parentLogic <- depTree[,"parent"] ==pname
res <- depTree[childrenLogic & parentLogic, "name"]
getChildelem <- depTree[depTree[,"child"] == intersect(depTree[,"parent"], children), "name"]
unique(c(res,getLeafs(getChildelem)))
}
getParent <- function (name, depTree=options("RMuso_depTree")[[1]]) {
parentExt <- depTree[depTree$name == name,"parent"]
# if(length(parentExt) == 0){
# browser()
# }
if(parentExt == "ini"){
return("iniFile")
}
depTree[depTree[,"child"] == parentExt,"name"]
}
getFilePath2 <- function(iniName, fileType, depTree=options("RMuso_depTree")[[1]]){
if(!file.exists(iniName) || dir.exists(iniName)){
stop(sprintf("Cannot find iniFile: %s", iniName))
}
startPoint <- fileType
startRow <- depTree[depTree[,"name"] == startPoint,]
startExt <- startRow$child
parentFile <- Reduce(function(x,y){
tryCatch(gsub(sprintf("\\.%s.*",y),
sprintf("\\.%s",y),
grep(sprintf("\\.%s",y),readLines(x),value=TRUE,perl=TRUE)), error = function(e){
stop(sprintf("Cannot find %s",x))
})
},
getQueue(depTree,startPoint)[-1],
init=iniName)
res <- list()
res["parent"] <- parentFile
if(startRow$mod > 0){
res["children"] <- tryCatch(
gsub(sprintf("\\.%s.*", startExt),
sprintf("\\.%s", startExt),
grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE,perl=TRUE))[startRow$mod]
,error = function(e){stop(sprintf("Cannot read %s",parentFile))})
} else {
rows <- tryCatch(
gsub(sprintf("\\.%s.*", startExt),
sprintf("\\.%s",startExt),
grep(sprintf("\\.%s",startExt),readLines(parentFile),value=TRUE, perl=TRUE))
,error = function(e){stop(sprintf("Cannot read %s", parentFile))})
unique(gsub(".*\\t","",res))
res["children"] <- unique(gsub(".*\\s+(.*\\.epc)","\\1",rows))
}
res
}
getFilesFromIni2 <- function(iniName, depTree=options("RMuso_depTree")[[1]]){
res <- lapply(depTree$name,function(x){
tryCatch(getFilePath2(iniName,x,depTree), error = function(e){
return(NA);
})
})
names(res) <- depTree$name
res
}
checkFileSystemForNotif <- function(iniName,root = ".", depTree = options("RMuso_depTree")[[1]]){
recoverAfterEval({
setwd(root)
fileNames <- suppressWarnings(getFilesFromIni2(iniName, depTree))
if(is.atomic(fileNames$management)){
fileNames[getLeafs("management")] <- NA
}
hasparent <- sapply(fileNames, function(x){
!is.atomic(x)
})
notNA <- ! sapply(fileNames[hasparent], function(x) {is.na(x$children)})
errorIndex <- ! sapply(fileNames[hasparent & notNA], function(x) file.exists(x$children))
})
return(fileNames[hasparent & notNA][errorIndex])
}

View File

@ -0,0 +1,35 @@
#' randEpc
#'
#' randEpc is a random epc creator based on musoMonte
#' @author Roland HOLLOS
#' @param parameterFile parameters.csv file location
#' @param location output location directory
#' @param sourceEpc the original epc file-the template
#' @param iteration the number of iterations
#' @export
randEpc <- function(parameterFile = "parameters.csv", location = "./epcDir",
sourceEpc = "maize.epc", iterations = 1000, constrains = NULL){
if(!dir.exists(location)){
dir.create(location)
}
sourceEpc <- normalizePath(sourceEpc)
currDir <- getwd()
parameters <- read.csv(parameterFile)
if(iterations < 3000){
randVals <- musoRand(parameters = parameters,constrains = constrains, iterations = 3000)
randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),]
} else {
randVals <- musoRand(parameters = parameters,constrains = constrains, iterations = iterations)
}
file.copy(sourceEpc,location,overwrite = TRUE)
setwd(location)
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")
}
setwd(currDir)
}

View File

@ -0,0 +1,33 @@
#' getDailyOutputList
#'
#' bla bla
#' @param settings bla
#' @export
getDailyOutputList <- function(settings=NULL){
if(is.null(settings)){
settings <- setupMuso()
}
varTable <- getOption("RMuso_varTable")$'6'
toPrint <- varTable[match(as.numeric(settings$dailyVarCodes),varTable[,1]),]
toPrint <- cbind.data.frame(index=1:nrow(toPrint),toPrint)
print(toPrint, row.names=FALSE)
}
#' getAnnualOutputList
#'
#' bla bla
#' @param settings bla
#' @export
getAnnualOutputList <- function(settings=NULL){
if(is.null(settings)){
settings<- setupMuso()
}
varTable <- getOption("RMuso_varTable")$'6'
toPrint <- varTable[which(varTable$codes %in% as.numeric(settings$annualVarCodes)),]
toPrint <- cbind.data.frame(index=1:nrow(toPrint),toPrint)
print(toPrint, row.names=FALSE)
}

View File

@ -0,0 +1,44 @@
getthewholedata<-function(settings){
f1<-settings$ininput[2]
filename = paste(settings$inputloc,settings$outputname,"_ann.txt",sep="")
alloutput<-read.table(filename,skip=22, header = FALSE)
return(alloutput)
}
getthespecdata<-function(settings,colnumbers){
filename<-paste(settings$inputloc,settings$outputname,"_ann.txt",sep="")
specoutput<-read.table(filename,skip=22, header = FALSE)[,colnumbers]
return(specoutput)
}
getdailyout<-function(settings){
binaryname<-paste0(settings$outputLoc,"/",settings$outputNames[2],".dayout")
d<-file(binaryname,"rb")
##leapyear is not implemented yet in this function
dayoutput<-matrix(readBin(d,"double",size=8,n=(settings$numData[1])),(settings$numYears*365),byrow=TRUE)
close(d)
return(dayoutput)
}
getmonthlyout<-function(settings){
binaryname<-paste(settings$inputloc,settings$outputname,".monavgout",sep="")
d<-file(binaryname,"rb")
monoutput<-matrix(readBin(d,"double",size=4,n=(settings$numdata[2])),(settings$numyears*12),byrow=TRUE)
close(d)
return(monoutput)
}
getyearlyout<-function(settings){
binaryname<-paste0(settings$inputLoc,"/",settings$outputName[2],".annout")
## d<-file(binaryname,"rb")
## yearoutput<-matrix(readBin(d,"double",size=4,n=(settings$numData[3])),(settings$numYears),byrow=TRUE)
## close(d)
## return(yearoutput)
outPut <- read.table(binaryname,skip = 1)
colnames(outPut) <- c("year", paste0("var_",settings$annualVarCodes))
outPut
}

View File

@ -0,0 +1,640 @@
`%between%` <- function(x, y){
(x <= y[2]) & (x >= y[1])
}
annualAggregate <- function(x, aggFun){
tapply(x, rep(1:(length(x)/365), each=365), aggFun)
}
SELECT <- function(x, selectPart){
if(!is.function(selectPart)){
index <- as.numeric(selectPart)
tapply(x,rep(1:(length(x)/365),each=365), function(y){
y[index]
})
} else {
tapply(x,rep(1:(length(x)/365),each=365), selectPart)
}
}
bVectToInt<- function(bin_vector){
bin_vector <- rev(as.integer(bin_vector))
packBits(as.raw(c(bin_vector,numeric(32-length(bin_vector)))),"integer")
}
constMatToDec <- function(constRes){
tab <- table(apply(constRes,2,function(x){paste(x,collapse=" ")}))
bitvect <- strsplit(names(tab[which.max(tab)]),split=" ")[[1]]
bVectToInt(bitvect)
}
compose <- function(expr){
splt <- strsplit(expr,split="\\|")[[1]]
lhs <- splt[1]
rhs <- splt[2]
penv <- parent.frame()
lhsv <- eval(parse(text=lhs),envir=penv)
penv[["lhsv"]] <- lhsv
place <- regexpr("\\.[^0-9a-zA-Z]",rhs)
if(place != -1){
finalExpression <- paste0(substr(rhs, 1, place -1),"lhsv",
substr(rhs, place + 1, nchar(rhs)))
} else {
finalExpression <- paste0(rhs,"(lhsv)")
}
eval(parse(text=finalExpression),envir=penv)
}
compoVect <- function(mod, constrTable, fileToWrite = "const_results.data"){
with(as.data.frame(mod), {
nexpr <- nrow(constrTable)
filtered <- numeric(nexpr)
vali <- numeric(nexpr)
for(i in 1:nexpr){
val <- compose(constrTable[i,1])
filtered[i] <- (val <= constrTable[i,3]) &&
(val >= constrTable[i,2])
vali[i] <- val
}
write(paste(vali,collapse=","), fileToWrite, append=TRUE)
filtered
})
}
modCont <- function(expr, datf, interval, dumping_factor){
tryCatch({
if((with(datf,eval(parse(text=expr))) %between% interval)){
return(NA)
} else{
return(dumping_factor)
}
},
error = function(e){
stop(sprintf("Cannot find the variable names in the dataframe, detail:\n%s",
e))
})
}
copyToThreadDirs2 <- function(iniSource, thread_prefix = "thread", numCores, execPath="./",
executable = ifelse(Sys.info()[1]=="Linux", file.path(execPath, "muso"),
file.path(execPath,"muso.exe"))){
sapply(iniSource, function(x){
flatMuso(x, execPath,
directory=file.path("tmp", paste0(thread_prefix,"_1"),tools::file_path_sans_ext(basename(x)),""), d =TRUE)
file.copy(executable,
file.path("tmp", paste0(thread_prefix,"_1"),tools::file_path_sans_ext(basename(x))))
tryCatch(file.copy(file.path(execPath,"cygwin1.dll"),
file.path("tmp", paste0(thread_prefix,"_1"),tools::file_path_sans_ext(basename(x)))),
error = function(e){"If you are in Windows..."})
})
sapply(2:numCores,function(thread){
dir.create(sprintf("tmp/%s_%s",thread_prefix,thread), showWarnings=FALSE)
file.copy(list.files(sprintf("tmp/%s_1",thread_prefix),full.names = TRUE),sprintf("tmp/%s_%s/",thread_prefix,thread),
recursive=TRUE, overwrite = TRUE)
})
}
#' multiSiteCalib
#'
#' This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution of the random parameters on convex polytopes.
#' @author Roland HOLLOS
#' @importFrom future future
#' @importFrom rpart rpart rpart.control
#' @importFrom rpart.plot rpart.plot
#' @param measuremets The table which contains the measurements
#' @param calTable A dataframe which contantains the ini file locations and the domains they belongs to
#' @param parameters A dataframe with the name, the minimum, and the maximum value for the parameters used in MonteCarlo experiment
#' @param dataVar A named vector where the elements are the MuSo variable codes and the names are the same as provided in measurements and likelihood
#' @param iterations The number of MonteCarlo experiments to be executed
#' @param burnin Currently not used, altought it is the length of burnin period of the MCMC sampling used to generate random parameters
#' @param likelihood A list of likelihood functions which names are linked to dataVar
#' @param execPath If you are running the calibration from different location than the MuSo executable, you have to provide the path
#' @param thread_prefix The prefix of thread directory names in the tmp directory created during the calibrational process
#' @param numCores The number of processes used during the calibration. At default it uses one less than the number of threads available
#' @param pb The progress bar function. If you use (web-)GUI you can provide a different function
#' @param pbUpdate The update function for pb (progress bar)
#' @param copyThread A boolean, recreate tmp directory for calibration or not (case of repeating the calibration)
#' @param contsraints A dataframe containing the constraints logic the minimum and a maximum value for the calibration.
#' @param th A trashold value for multisite calibration. What percentage of the site should satisfy the constraints.
#' @param treeControl A list which controls (maximal complexity, maximal depth) the details of the decession tree making.
#' @export
multiSiteCalib <- function(measurements,
calTable,
parameters,
dataVar,
iterations = 100,
burnin =ifelse(iterations < 3000, 3000, NULL),
likelihood,
execPath,
thread_prefix="thread",
numCores = (parallel::detectCores()-1),
pb = txtProgressBar(min=0, max=iterations, style=3),
pbUpdate = setTxtProgressBar,
copyThread = TRUE,
constraints=NULL, th = 10, treeControl=rpart.control()
){
future::plan(future::multisession)
# file.remove(list.files(path = "tmp", pattern="progress.txt", recursive = TRUE, full.names=TRUE))
# file.remove(list.files(path = "tmp", pattern="preservedCalib.csv", recursive = TRUE, full.names=TRUE))
# ____ _ _ _ _
# / ___|_ __ ___ __ _| |_ ___ | |_| |__ _ __ ___ __ _ __| |___
# | | | '__/ _ \/ _` | __/ _ \ | __| '_ \| '__/ _ \/ _` |/ _` / __|
# | |___| | | __/ (_| | || __/ | |_| | | | | | __/ (_| | (_| \__ \
# \____|_| \___|\__,_|\__\___| \__|_| |_|_| \___|\__,_|\__,_|___/
if(copyThread){
unlink("tmp",recursive=TRUE)
copyToThreadDirs2(iniSource=calTable$site_id, numCores=numCores, execPath=execPath)
} else {
print("copy skipped")
file.remove(file.path(list.dirs("tmp",recursive=FALSE),"progress.txt"))
file.remove(file.path(list.dirs("tmp", recursive=FALSE), "const_results.data"))
}
# ____ _ _ _
# | _ \ _ _ _ __ | |_| |__ _ __ ___ __ _ __| |___
# | |_) | | | | '_ \ | __| '_ \| '__/ _ \/ _` |/ _` / __|
# | _ <| |_| | | | | | |_| | | | | | __/ (_| | (_| \__ \
# |_| \_\\__,_|_| |_| \__|_| |_|_| \___|\__,_|\__,_|___/
threadCount <- distributeCores(iterations, numCores)
fut <- lapply(1:numCores, function(i) {
future({
tryCatch(
{
result <- multiSiteThread(measuredData = measurements, parameters = parameters, calTable=calTable,
dataVar = dataVar, iterations = threadCount[i],
likelihood = likelihood, threadNumber= i, constraints=constraints, th=th)
# setwd("../../")
# return(result)
}
, error = function(e){
# browser()
sink("error.txt")
print(e)
sink()
saveRDS(e,"error.RDS")
writeLines(as.character(iterations),"progress.txt")
})
})
})
# _ _
# __ ____ _| |_ ___| |__ _ __ _ __ ___ __ _ _ __ ___ ___ ___
# \ \ /\ / / _` | __/ __| '_ \ | '_ \| '__/ _ \ / _` | '__/ _ \/ __/ __|
# \ V V / (_| | || (__| | | | | |_) | | | (_) | (_| | | | __/\__ \__ \
# \_/\_/ \__,_|\__\___|_| |_| | .__/|_| \___/ \__, |_| \___||___/___/
# |_| |___/
getProgress <- function(){
# threadfiles <- list.files(settings$inputLoc, pattern="progress.txt", recursive = TRUE)
threadfiles <- list.files(pattern="progress.txt", recursive = TRUE)
if(length(threadfiles)==0){
return(0)
} else {
sum(sapply(threadfiles, function(x){
partRes <- readLines(x)
if(length(partRes)==0){
return(0)
} else {
return(as.numeric(partRes))
}
}))
}
}
progress <- 0
while(progress < iterations){
Sys.sleep(1)
progress <- tryCatch(getProgress(), error=function(e){progress})
if(is.null(pb)){
pbUpdate(as.numeric(progress))
} else {
pbUpdate(pb,as.numeric(progress))
}
}
if(!is.null(pb)){
close(pb)
}
# ____ _ _
# / ___|___ _ __ ___ | |__ (_)_ __ ___
# | | / _ \| '_ ` _ \| '_ \| | '_ \ / _ \
# | |__| (_) | | | | | | |_) | | | | | __/
# \____\___/|_| |_| |_|_.__/|_|_| |_|\___|
if(!is.null(constraints)){
constRes <- file.path(list.dirs("tmp", recursive=FALSE), "const_results.data")
constRes <- lapply(constRes, function(f){read.csv(f, stringsAsFactors=FALSE, header=FALSE)})
constRes <- do.call(rbind,constRes)
write.csv(constRes, "constRes.csv")
}
resultFiles <- list.files(pattern="preservedCalib.*csv$",recursive=TRUE)
res0 <- read.csv(grep("thread_1/",resultFiles, value=TRUE),stringsAsFactors=FALSE)
resultFilesSans0 <- grep("thread_1/", resultFiles, value=TRUE, invert=TRUE)
# results <- do.call(rbind,lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE)}))
resultsSans0 <- lapply(resultFilesSans0, function(f){read.csv(f, stringsAsFactors=FALSE, header=FALSE)})
resultsSans0 <- do.call(rbind,resultsSans0)
colnames(resultsSans0) <- colnames(res0)
results <- (rbind(res0,resultsSans0))
write.csv(results,"result.csv")
calibrationPar <- future::value(fut[[1]], stdout = FALSE, signal=FALSE)[["calibrationPar"]]
if(!is.null(constraints)){
tryCatch({
notForTree <- c(seq(from = (length(calibrationPar)+1), length.out=3))
notForTree <- c(notForTree,which(sapply(seq_along(calibrationPar),function(i){sd(results[,i])==0})))
treeData <- results[,-notForTree]
treeData["failType"] <- as.factor(results$failType)
if(ncol(treeData) > 4){
rp <- rpart(failType ~ .,data=treeData,control=treeControl)
svg("treeplot.svg")
rpart.plot(rp)
dev.off()
}
}, error = function(e){
print(e)
})
}
origModOut <- future::value(fut[[1]], stdout = FALSE, signal=FALSE)[["origModOut"]]
# Just single objective version TODO:Multiobjective
results <- results[results[,"Const"] == 1,]
if(nrow(results)==0){
stop("No simulation suitable for constraints\n Please see treeplot.png for explanation, if you have more than four parameters.")
}
bestCase <- which.max(results[,length(calibrationPar) + 1])
parameters <- results[bestCase,1:length(calibrationPar)] # the last two column is the (log) likelihood and the rmse
#TODO: Have to put that before multiSiteThread, we should not have to calculate it at every iterations
firstDir <- list.dirs("tmp/thread_1",full.names=TRUE,recursive =FALSE)[1]
epcFile <- list.files(firstDir, pattern = "\\.epc",full.names=TRUE)
settingsProto <- setupMuso(inputLoc = firstDir,
iniInput =rep(list.files(firstDir, pattern = "\\.ini",full.names=TRUE),2))
alignIndexes <- commonIndexes(settingsProto, measurements)
musoCodeToIndex <- sapply(dataVar,function(musoCode){
settingsProto$dailyOutputTable[settingsProto$dailyOutputTable$code == musoCode,"index"]
})
setwd("tmp/thread_1")
aposteriori<- spatialRun(settingsProto, calibrationPar, parameters, calTable)
file.copy(list.files(list.dirs(full.names=TRUE, recursive=FALSE)[1], pattern=".*\\.epc", full.names=TRUE),
"../../multiSiteOptim.epc", overwrite=TRUE)
setwd("../../")
#TODO: Have to put that before multiSiteThread, we should not have to calculate it at every iterations
nameGroupTable <- calTable
nameGroupTable[,1] <- tools::file_path_sans_ext(basename(nameGroupTable[,1]))
res <- list()
res[["calibrationPar"]] <- calibrationPar
res[["parameters"]] <- parameters
# browser()
res[["comparison"]] <- compareCalibratedWithOriginal(key = names(dataVar)[1], modOld=origModOut, modNew=aposteriori, mes=measurements,
likelihoods = likelihood,
alignIndexes = alignIndexes,
musoCodeToIndex = musoCodeToIndex,
nameGroupTable = nameGroupTable, mean)
res[["likelihood"]] <- results[bestCase,ncol(results)-2]
comp <- res$comparison
res[["originalMAE"]] <- mean(abs((comp[,1]-comp[,3])))
res[["MAE"]] <- mean(abs((comp[,2]-comp[,3])))
res[["RMSE"]] <- results[bestCase,ncol(results)-2]
res[["originalRMSE"]] <- sqrt(mean((comp[,1]-comp[,3])^2))
res[["originalR2"]] <- summary(lm(measured ~ original,data=res$comparison))$r.squared
res[["R2"]] <- summary(lm(measured ~ calibrated, data=res$comparison))$r.squared
saveRDS(res,"results.RDS")
png("calibRes.png")
opar <- par(mar=c(5,5,4,2)+0.1, xpd=FALSE)
with(data=res$comparison, {
plot(measured,original,
ylim=c(min(c(measured,original,calibrated)),
max(c(measured,original,calibrated))),
xlim=c(min(c(measured,original,calibrated)),
max(c(measured,original,calibrated))),
xlab=expression("measured "~(kg[DM]~m^-2)),
ylab=expression("simulated "~(kg[DM]~m^-2)),
cex.lab=1.3,
col="red",
pch=19,
pty="s"
)
points(measured,calibrated, pch=19, col="blue")
abline(0,1)
legend(x="top",
pch=c(19,19),
col=c("red","blue"),
inset=c(0,-0.1),
legend=c("original","calibrated"),
ncol=2,
box.lty=0,
xpd=TRUE
)
})
dev.off()
return(res)
}
#' multiSiteThread
#'
#' This is an
#' @author Roland HOLLOS
multiSiteThread <- function(measuredData, parameters = NULL, startDate = NULL,
endDate = NULL, formatString = "%Y-%m-%d", calTable,
dataVar, outLoc = "./calib",
outVars = NULL, iterations = 300,
skipSpinup = TRUE, plotName = "calib.jpg",
modifyOriginal=TRUE, likelihood, uncertainity = NULL, burnin=NULL,
naVal = NULL, postProcString = NULL, threadNumber, constraints=NULL,th=10) {
originalRun <- list()
nameGroupTable <- calTable
nameGroupTable[,1] <- tools::file_path_sans_ext(basename(nameGroupTable[,1]))
setwd(paste0("tmp/thread_",threadNumber))
firstDir <- list.dirs(full.names=FALSE,recursive =FALSE)[1]
epcFile <- list.files(firstDir, pattern = "\\.epc",full.names=TRUE)
settingsProto <- setupMuso(inputLoc = firstDir,
iniInput =rep(list.files(firstDir, pattern = "\\.ini",full.names=TRUE),2))
# Exanding likelihood
likelihoodFull <- as.list(rep(NA,length(dataVar)))
names(likelihoodFull) <- names(dataVar)
if(!missing(likelihood)) {
lapply(names(likelihood),function(x){
likelihoodFull[[x]] <<- likelihood[[x]]
})
}
defaultLikelihood <- which(is.na(likelihood))
if(length(defaultLikelihood)>0){
likelihoodFull[[defaultLikelihood]] <- (function(x, y){
exp(-sqrt(mean((x-y)^2)))
})
}
mdata <- measuredData
if(is.null(parameters)){
parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) {
stop("You need to specify a path for the parameters.csv, or a matrix.")
})
} else {
if((!is.list(parameters)) & (!is.matrix(parameters))){
parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){
stop("Cannot find neither parameters file neither the parameters matrix")
})
}}
print("optiMuso is randomizing the epc parameters now...",quote = FALSE)
randVals <- musoRand(parameters = parameters,constrains = NULL, iterations = iterations)
origEpc <- readValuesFromFile(epcFile, randVals[[1]])
partialResult <- matrix(ncol=length(randVals[[1]])+2*length(dataVar) + 2)
colN <- randVals[[1]]
colN[match(parameters[,2],randVals[[1]])] <- parameters[,1]
colN[match(parameters[,2], randVals[[1]])[!is.na(match(parameters[,2],randVals[[1]]))]] <- parameters[,1]
colnames(partialResult) <- c(colN,sprintf("%s_likelihood",names(dataVar)),
sprintf("%s_rmse",names(dataVar)),"Const", "failType")
numParameters <- length(colN)
partialResult[1:numParameters] <- origEpc
## Prepare the preservedCalib matrix for the faster
## run.
musoCodeToIndex <- sapply(dataVar,function(musoCode){
settingsProto$dailyOutputTable[settingsProto$dailyOutputTable$code == musoCode,"index"]
})
resultRange <- (numParameters + 1):(ncol(partialResult))
randValues <- randVals[[2]]
settingsProto$calibrationPar <- randVals[[1]]
if(!is.null(naVal)){
measuredData <- as.data.frame(measuredData)
measuredData[measuredData == naVal] <- NA
}
resIterate <- 1:nrow(calTable)
names(resIterate) <- tools::file_path_sans_ext(basename(calTable[,1]))
alignIndexes <- commonIndexes(settingsProto, measuredData)
if(threadNumber == 1){
originalRun[["calibrationPar"]] <- randVals[[1]]
origModOut <- lapply(resIterate, function(i){
dirName <- tools::file_path_sans_ext(basename(calTable[i,1]))
setwd(dirName)
settings <- settingsProto
settings$outputLoc <- settings$inputLoc <- "./"
settings$iniInput <- settings$inputFiles <- rep(paste0(dirName,".ini"),2)
settings$outputNames <- rep(dirName,2)
settings$executable <- ifelse(Sys.info()[1]=="Linux","./muso","./muso.exe") # set default exe option at start wold be better
res <- tryCatch(calibMuso(settings=settings,parameters =origEpc, silent = TRUE, skipSpinup = TRUE), error=function(e){NA})
setwd("../")
res
})
originalRun[["origModOut"]] <- origModOut
partialResult[,resultRange] <- calcLikelihoodsForGroups(dataVar=dataVar,
mod=origModOut,
mes=measuredData,
likelihoods=likelihood,
alignIndexes=alignIndexes,
musoCodeToIndex = musoCodeToIndex,nameGroupTable = nameGroupTable, groupFun=mean, constraints=constraints,th=th)
write.csv(x=randVals[[1]],"../randIndexes.csv")
write.csv(x=partialResult, file="preservedCalib.csv",row.names=FALSE)
}
print("Running the model with the random epc values...", quote = FALSE)
for(i in 2:(iterations+1)){
tmp <- lapply(resIterate, function(siteI){
dirName <- tools::file_path_sans_ext(basename(calTable[siteI,1]))
setwd(dirName)
settings <- settingsProto
settings$outputLoc <- settings$inputLoc <- "./"
settings$iniInput <- settings$inputFiles <- rep(paste0(dirName,".ini"),2)
settings$outputNames <- rep(dirName,2)
settings$executable <- ifelse(Sys.info()[1]=="Linux","./muso","./muso.exe") # set default exe option at start wold be better
res <- tryCatch(calibMuso(settings=settings,parameters=randValues[(i-1),], silent = TRUE, skipSpinup = TRUE), error=function(e){NA})
setwd("../")
res
})
if(is.null(tmp)){
partialResult[,resultRange] <- NA
} else {
partialResult[,resultRange] <- calcLikelihoodsForGroups(dataVar=dataVar,
mod=tmp,
mes=measuredData,
likelihoods=likelihood,
alignIndexes=alignIndexes,
musoCodeToIndex = musoCodeToIndex,nameGroupTable = nameGroupTable, groupFun=mean, constraints = constraints, th=th)
partialResult[1:numParameters] <- randValues[(i-1),]
write.table(x=partialResult, file="preservedCalib.csv", append=TRUE, row.names=FALSE,
sep=",", col.names=FALSE)
# write.csv(x=tmp, file=paste0(pretag, (i+1),".csv"))
writeLines(as.character(i-1),"progress.txt") #UNCOMMENT IMPORTANT
}
}
if(threadNumber == 1){
return(originalRun)
}
return(0)
}
distributeCores <- function(iterations, numCores){
perProcess<- iterations %/% numCores
numSimu <- rep(perProcess,numCores)
gainers <- sample(1:numCores, iterations %% numCores)
numSimu[gainers] <- numSimu[gainers] + 1
numSimu
}
prepareFromAgroMo <- function(fName){
obs <- read.table(fName, stringsAsFactors=FALSE, sep = ";", header=T)
obs <- reshape(obs, timevar="var_id", idvar = "date", direction = "wide")
dateCols <- apply(do.call(rbind,(strsplit(obs$date, split = "-"))),2,as.numeric)
colnames(dateCols) <- c("year", "month", "day")
cbind.data.frame(dateCols, obs)
}
calcLikelihoodsForGroups <- function(dataVar, mod, mes,
likelihoods, alignIndexes, musoCodeToIndex,
nameGroupTable, groupFun, constraints,
th = 10){
if(!is.null(constraints)){
constRes<- sapply(mod,function(m){
compoVect(m,constraints)
})
failType <- constMatToDec(constRes)
}
likelihoodRMSE <- sapply(names(dataVar),function(key){
modelled <- as.vector(unlist(sapply(sort(names(alignIndexes)),
function(domain_id){
apply(do.call(cbind,
lapply(nameGroupTable[,1][nameGroupTable[,2] == domain_id],
function(site){mod[[site]][alignIndexes[[domain_id]]$model,musoCodeToIndex[key]]
})),1,groupFun)
})))
measuredGroups <- split(mes,mes$domain_id)
measured <- do.call(rbind.data.frame, lapply(names(measuredGroups), function(domain_id){
measuredGroups[[domain_id]][alignIndexes[[domain_id]]$meas,]
}))
measured <- measured[measured$var_id == key,]
res <- c(likelihoods[[key]](modelled, measured),
sqrt(mean((modelled-measured$mean)^2))
)
print(abs(mean(modelled)-mean(measured$mean)))
res
})
likelihoodRMSE <- c(likelihoodRMSE[1,], likelihoodRMSE[2,],
ifelse((100 * sum(apply(constRes, 2, prod)) / ncol(constRes)) >= th,
1,0), failType)
names(likelihoodRMSE) <- c(sprintf("%s_likelihood",dataVar), sprintf("%s_rmse",dataVar), "Const", "failType")
return(likelihoodRMSE)
}
commonIndexes <- function (settings,measuredData) {
# Have to fix for other starting points also
modelDates <- seq(from= as.Date(sprintf("%s-01-01",settings$startYear)),
by="days",
to=as.Date(sprintf("%s-12-31",settings$startYear+settings$numYears-1)))
modelDates <- grep("-02-29",modelDates,invert=TRUE, value=TRUE)
lapply(split(measuredData,measuredData$domain_id),function(x){
measuredDates <- x$date
modIndex <- match(as.Date(measuredDates), as.Date(modelDates))
measIndex <- which(!is.na(modIndex))
modIndex <- modIndex[!is.na(modIndex)]
cbind.data.frame(model=modIndex,meas=measIndex)
})
}
agroLikelihood <- function(modVector,measured){
mu <- measured[,grep("mean", colnames(measured))]
stdev <- measured[,grep("^sd", colnames(measured))]
ndata <- nrow(measured)
sum(sapply(1:ndata, function(x){
dnorm(modVector, mu[x], stdev[x], log = TRUE)
}), na.rm=TRUE)
}
#' compareCalibratedWithOriginal
#'
#' This functions compareses the likelihood and the RMSE values of the simulations and the measurements
#' @param key
compareCalibratedWithOriginal <- function(key, modOld, modNew, mes,
likelihoods, alignIndexes, musoCodeToIndex, nameGroupTable,
groupFun){
original <- as.vector(unlist(sapply(sort(names(alignIndexes)),
function(domain_id){
apply(do.call(cbind,
lapply(nameGroupTable$site_id[nameGroupTable$domain_id == domain_id],
function(site){
modOld[[site]][alignIndexes[[domain_id]]$model,musoCodeToIndex[key]]
})),1,groupFun)
})))
calibrated <- as.vector(unlist(sapply(sort(names(alignIndexes)),
function(domain_id){
apply(do.call(cbind,
lapply(nameGroupTable$site_id[nameGroupTable$domain_id == domain_id],
function(site){
modNew[[site]][alignIndexes[[domain_id]]$model,musoCodeToIndex[key]]
})),1,groupFun)
})))
measuredGroups <- split(mes,mes$domain_id)
measured <- do.call(rbind.data.frame, lapply(names(measuredGroups), function(domain_id){
measuredGroups[[domain_id]][alignIndexes[[domain_id]]$meas,]
}))
measured <- measured[measured$var_id == key,]
return(data.frame(original = original, calibrated = calibrated,measured=measured$mean))
}
spatialRun <- function(settingsProto,calibrationPar, parameters, calTable){
resIterate <- 1:nrow(calTable)
names(resIterate) <- tools::file_path_sans_ext(basename(calTable[,1]))
modOut <- lapply(resIterate, function(i){
dirName <- tools::file_path_sans_ext(basename(calTable[i,1]))
setwd(dirName)
settings <- settingsProto
settings$outputLoc <- settings$inputLoc <- "./"
settings$iniInput <- settings$inputFiles <- rep(paste0(dirName,".ini"),2)
settings$outputNames <- rep(dirName,2)
settings$calibrationPar <- calibrationPar
settings$executable <- ifelse(Sys.info()[1]=="Linux","./muso","./muso.exe") # set default exe option at start wold be better
res <- tryCatch(calibMuso(settings=settings,parameters =parameters, silent = TRUE, skipSpinup = TRUE), error=function(e){NA})
setwd("../")
res
})
modOut
}

View File

@ -0,0 +1,56 @@
#'copyMusoExampleTo
#'
#'This function enables the user to download a complete, working file set to quickly start using Biome-BGCMuSo through RBBGCMuso (or in standalone mode). The user has to specify the target directory for the files. The file set contains the model executable (muso.exe in Windows), the INI files that drive the model, and other files like meteorology input, ecophysiological constants file (EPC), and other ancillary files (CO2 concentration, parameter range definition file called parameters.csv). Note that we strongly recommend to read the User's Guide of Biome-BGCMuSo to clarify the meaning of the input files. The input files (s.ini, n.ini, maize.epc, meteorology files) are simple text files, so the user can read (and modify) them with his/her favourite text editor (like Editpad Lite, vim, emacs). Note that some files use UNIX/Linux style text which means that the text will not be readable using the Windows Notepad.
#'
#'@param example This is the name of the example file. If it is not set then a simple graphical user interface (tcl/tk menu) will open to select the target dataset (which is typically an experimental site). In the list hhs means the Hegyhatsal eddy covariance site in Hungary.
#'@param destination The destination where the example files will be copied.
#'@export
copyMusoExampleTo <- function(example = NULL, destination = NULL){
WindowsP <- Sys.info()[1] == "Windows"
chooseExample <- function(){
choiceWin <- tcltk::tktoplevel()
tcltk::tclRequire("BWidget")
tcltk::tktitle(choiceWin) <- "Choose an example!"
tcltk::tcl("wm","geometry",choiceWin,"200x50")
tcltk::tcl("wm", "attributes", choiceWin, topmost=TRUE)
choiceValues <- basename(list.dirs(system.file("examples","",package = "RBBGCMuso"),recursive = FALSE))
choices <- tcltk::tkwidget(choiceWin,"ComboBox",
editable = FALSE, values = choiceValues,
textvariable = tcltk::tclVar(choiceValues[1]))
tcltk::tkpack(choices)
choiceValue <- NA
closeSelection <- tcltk::tkwidget(choiceWin,"button",text ="Select", command =function (){
choiceValue <<- tcltk::tclvalue(tcltk::tcl(choices,"get"))
tcltk::tkdestroy(choiceWin)
})
tcltk::tkpack(closeSelection)
while(as.numeric(tcltk::tclvalue(tcltk::tcl("winfo","exists",choiceWin)))){
}
return(choiceValue)
}
if(is.null(example)){
cExample<-paste0(system.file("examples","",package = "RBBGCMuso"),"/",chooseExample())
} else {
cExample <- paste0(system.file("examples","",package = "RBBGCMuso"),"/","hhs")
}
if(is.null(destination)){
destination<-tcltk::tk_choose.dir(getwd(), "Choose folder to copy the examples!")
}
currDir <- getwd()
setwd(cExample)
if(!WindowsP){
file.copy(grep("(exe|dll)$", list.files(), value = TRUE, invert = TRUE),destination)
} else {
file.copy(grep("^muso$", list.files(), value = TRUE, invert = TRUE),destination)
}
setwd(destination)
}

View File

@ -0,0 +1,49 @@
## library(RBBGCMuso)
## library(BayesianTools)
## library(sensitivity)
metMusoGet <- function(metFile,skip=4,namerow=3,saveBackup=TRUE, revert=FALSE){
metData<-read.table(file = metFile,skip=skip)
namesMet <- unlist(read.table(file=metFile,skip = namerow-1,nrows = 1))
colnames(metData)<-namesMet
if(revert){
file.copy(grep(basename(metFile),grep("mbck$",list.files(dirname(metFile)),value=TRUE),value = TRUE), metFile,overwrite = TRUE)
return(cat("Meteorological data is succesfully reverted to backup data"))
}
if(saveBackup){
file.copy(metFile,paste(metFile,"mbck",sep = "-"))
}
return(metData)
}
metMusoSet <- function(metFile,skip=4,namerow=3,saveBackup=TRUE, revert=FALSE,index, changedData){
metData<-read.table(file = metFile,skip=skip)
namesMet <- unlist(read.table(file=metFile,skip = namerow-1,nrows = 1))
colnames(metData)<-namesMet
if(revert){
file.copy(grep("mbck$",list.files(),value=TRUE), metFile)
}
if(saveBackup){
file.copy(metFile,paste(metFile,"mbck",sep = "-"))
}
if(is.vector(changedData)&(length(metData[,index])==length(changedData))){
metData[,index]<-changedData
changedMet<- c(readLines(metFile,-1)[1:skip],apply(metData,1, function (x) paste(x,collapse = " ")))
return(writeLines(changedMet,metFile))
}else {
return(cat("\n\tThe changedData is not a vector or not in a same length"))
}
}

View File

@ -0,0 +1,278 @@
#' musoMonte
#'
#' This function executes the Monte Carlo experiment with Biome-BGCMuSo (musoRand is called by this function). It samples the selected model parameters within user defined ranges from conditional multivariate uniform distribution, and then runs the model for each run.
#' @author Roland HOLLOS
#' @param settings A list of environmental variables for the Monte Carlo experiment. These settings are generated by the setupMuso function. By default the settings parameter is generated automatically.
#' @param parameters This is a dataframe (heterogeneous data-matrix), where the first column is the name of the parameter, the second is a numeric vector of the rownumbers of the given variable in the input EPC file, and the last two columns describe the minimum and the maximum of the parameter (i.e. the parameter ranges), defining the interval for the randomization.
#' @param calibrationPar You might want to change some parameters in your EPC file before you run the modell. You have to select the appropirate model parameters here. You can refer to the parameters by the number of the line in the EPC file where the variables are defined. The indexing of the lines starts at 1, and each line matters (like in any simple text file). You should use a vector for this selection like c(1,5,8)
#' @param inputDir The location of the input directory for the Biome-BGCMuSo model. This directory must contain a viable pack of all input files and the model executable file.
#' @param iterations Number of the Monte Carlo simulations.
#' @param preTag This defines the name of the output files. This tag will be re-used so that the results will be like preTag-1.csv, preTag-2csv...
#' @param outputType This parameter can be "oneCsv", "moreCsv", and "netCDF". If "oneCsv" is chosen the function creates one large csv file for all of the runs. If "moreCsv" is chosen, every model output goes to separate files. If netCDF is selected the output will be stored in a netCDF file. The default value of the outputTypes is "moreCsv". Note that netCDF is not implemented yet.
#' @param fun If you select a variable from the possible outputs (by using the varIndex parameter), you have to provide a function which maps to a subset of real numbers. The most frequent possibilities are: mean, min, max, var, but you can define any function for your needs.
#' @param varIndex This parameter specifies which parameter will be used for the Monte Carlo experiment from the output list of Biome-BGCMuSo (defined by the INI file). You can extract this information from the INI files. At the output parameter specifications, the parameter order will determine this number. For example, if you have set these output parameters: 412, 874, 926, 888, and you want to use 926 for the experiment, you should specify varIndex as 3.
#' @param debugging If you set this parameter, you can save every logfile, and RBBGCMuso will select those which contains errors. This is useful to study why the model crashes with a given parameter set.
#' @param keepEpc If you set keepEpc as TRUE, it will save every selected EPC file, and move the wrong ones into the WRONGEPC directory.
#' @importFrom magrittr '%>%'
#' @export
musoMonte <- function(settings=NULL,
parameters=NULL,
inputDir = "./",
outLoc = "./calib",
iterations = 10,
preTag = "mont-",
outputType = "moreCsv",
fun=mean,
varIndex = 1,
outVars = NULL,
silent = TRUE,
skipSpinup = TRUE,
debugging = FALSE,
keepEpc = FALSE,
constrains = NULL,
skipZero = TRUE,
postProcString=NULL,
modifyOut=TRUE,
...){
readValuesFromEpc <- function(epc, linums){
epcFile <- readLines(epc)
rows <- numeric(2)
values <- sapply(linums, function(x){
rows[1] <- as.integer(x)
rows[2] <- as.integer(round(100*x)) %% 10 + 1
epcFile <- readLines(epc)
selRow <- unlist(strsplit(epcFile[rows[1]], split= "[\t ]"))
selRow <- selRow[selRow!=""]
return(as.numeric(selRow[rows[2]]))
})
return(values)
}
if(is.null(parameters)){
parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) {
stop("You need to specify a path for the parameters.csv, or a matrix.")
})
} else {
if((!is.list(parameters)) & (!is.matrix(parameters))){
parameters <- tryCatch(read.csv(parameters, stringsAsFactor=FALSE), error = function (e){
stop("Cannot find neither parameters file neither the parameters matrix")
})
}}
outLocPlain <- basename(outLoc)
currDir <- getwd()
if(!dir.exists(outLoc)){
dir.create(outLoc)
warning(paste(outLoc," is not exists, so it was created"))
}
outLoc <- normalizePath(outLoc)
if(is.null(settings)){
settings <- setupMuso()
}
if(is.null(outVars)){
numVars <- length(settings$outputVars[[1]])
outVarNames <- settings$outputVars[[1]]
} else {
numVars <- length(outVars)
outVarNames <- sapply(outVars, musoMapping)
}
if(!is.null(postProcString)){
outVarNames <- c(outVarNames,gsub("\\s","",unlist(strsplit(procString,"<-"))[1]))
}
parameterNames <- gsub("([\\s]|\\-epc)","",parameters[,1],perl=TRUE)
# settings$calibrationPar <- A[,1] #:LATER:
pretag <- file.path(outLoc,preTag)
npar <- length(settings$calibrationPar)
##reading the original epc file at the specified
## row numbers
if(iterations < 3000){
randVals <- musoRand(parameters = parameters,fileType="epc", iterations = 3000)
randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),]
} else {
randVals <- musoRand(parameters = parameters,fileType="epc", iterations = iterations)
}
origEpc <- readValuesFromEpc(settings$epc[2],parameters[,2])
## Prepare the preservedEpc matrix for the faster
## run.
pretag <- file.path(outLoc,preTag)
## Creating function for generating separate
## csv files for each run
progBar <- txtProgressBar(1,iterations,style=3)
moreCsv <- function(){
settings$iniInput[2] %>%
(function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>%
unlink
randValues <- randVals[[2]]
settings$calibrationPar <- randVals[[1]]
## randValues <- randValues[,randVals[[1]] %in% parameters[,2]][,rank(parameters[,2])]
modellOut <- matrix(ncol = numVars, nrow = iterations + 1)
origModellOut <- calibMuso(settings=settings,silent=TRUE)
write.csv(x=origModellOut, file=paste0(pretag,1,".csv"))
if(!is.list(fun)){
funct <- rep(list(fun), numVars)
}
tmp2 <- numeric(numVars)
# browser()
for(j in 1:numVars){
tmp2[j]<-funct[[j]](origModellOut[,j])
}
modellOut[1,]<- tmp2
for(i in 2:(iterations+1)){
tmp <- tryCatch(calibMuso(settings = settings,
parameters = randValues[(i-1),],
silent= TRUE,
skipSpinup = skipSpinup,
keepEpc = keepEpc,
debugging = debugging,
modifyOriginal = modifyOut,
outVars = outVars,postProcString=postProcString), error = function (e) NA)
if(length(dim(tmp))>=1){
for(j in 1:numVars){
tmp2[j]<-funct[[j]](tmp[,j])
}
if(skipZero){
if(tmp2[j]==0){
tmp2[j] <- NA
}
}
} else {
for(j in 1:numVars){
tmp2[j]<-NA
}
}
modellOut[i,]<- tmp2
write.csv(x=tmp, file=paste0(pretag,(i+1),".csv"))
setTxtProgressBar(progBar,i)
}
paramLines <- parameters[,2]
paramLines <- order(paramLines)
randInd <- randVals[[1]][(randVals[[1]] %in% parameters[,2])]
randInd <- order(randInd)
# browser()
epcStrip <- rbind(origEpc[order(parameters[,2])],
randValues[,randVals[[1]] %in% parameters[,2]][,randInd])
preservedEpc <- cbind(epcStrip,
modellOut)
colnames(preservedEpc) <- c(parameterNames[paramLines], sapply(outVarNames, function (x) paste0("mod.", x)))
return(preservedEpc)
}
## Creating function for generating one
## csv files for each run
oneCsv <- function () {
# stop("This function is not implemented yet")
settings$iniInput[2] %>%
(function(x) paste0(dirname(x),"/",tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))) %>%
unlink
randValues <- randVals[[2]]
settings$calibrationPar <- randVals[[1]]
## randValues <- randValues[,randVals[[1]] %in% parameters[,2]][,rank(parameters[,2])]
modellOut <- matrix(ncol = numVars, nrow = iterations + 1)
origModellOut <- calibMuso(settings=settings,silent=TRUE)
write.csv(x=origModellOut, file=paste0(pretag,".csv"))
if(!is.list(fun)){
funct <- rep(list(fun), numVars)
}
tmp2 <- numeric(numVars)
for(j in 1:numVars){
tmp2[j]<-funct[[j]](origModellOut[,j])
}
modellOut[1,]<- tmp2
for(i in 2:(iterations+1)){
tmp <- tryCatch(calibMuso(settings = settings,
parameters = randValues[(i-1),],
silent= TRUE,
skipSpinup = skipSpinup,
keepEpc = keepEpc,
debugging = debugging,
outVars = outVars), error = function (e) NA)
if(!is.na(tmp)){
for(j in 1:numVars){
tmp2[j]<-funct[[j]](tmp[,j])
}
} else {
for(j in 1:numVars){
tmp2[j]<-rep(NA,length(settings$outputVars[[1]]))
}
}
modellOut[i,]<- tmp2
write.table(x=tmp, file=paste0(pretag,".csv"), append = TRUE,col.names = FALSE, sep = ",")
setTxtProgressBar(progBar,i)
}
paramLines <- parameters[,2]
paramLines <- order(paramLines)
randInd <- randVals[[1]][(randVals[[1]] %in% parameters[,2])]
randInd <- order(randInd)
epcStrip <- rbind(origEpc[order(parameters[,2])],
randValues[,randVals[[1]] %in% parameters[,2]][,randInd])
preservedEpc <- cbind(epcStrip,
modellOut)
colnames(preservedEpc) <- c(parameterNames[paramLines], sapply(outVarNames, function (x) paste0("mod.", x)))
return(preservedEpc)
}
netCDF <- function () {
stop("This function is not inplemented yet")
}
## Call one function according to the outputType
switch(outputType,
"oneCsv" = (a <- oneCsv()),
"moreCsv" = (a <- moreCsv()),
"netCDF" = (a <- netCDF()))
write.csv(a,"preservedEpc.csv")
setwd(currDir)
return(a)
}

View File

@ -0,0 +1,187 @@
#' musoRand
#'
#' This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution for all selected parameters.
#' @author Roland HOLLOS
#' @param parameters This is a dataframe (heterogeneous data-matrix), where the first column is the name of the parameter, the second is a numeric vector of the rownumbers of the given variable in the input EPC file, and the last two columns describe the minimum and the maximum of the parameter (i.e. the parameter ranges), defining the interval for the randomization.
#' @param constrains This is a matrix wich specify the constrain rules for the sampling. Parameter dependencies are described in the Biome-BGCMuSo User's Guide. Further informations is coming soon.
#' @param iteration The number of samples for the Monte-Carlo experiment. We propose to use at least 3000 iteration because it is generally fast and it can be subsampled later at any time.
#' @importFrom limSolve xsample
#' @export
musoRand <- function(parameters, iterations=3000, fileType="epc", constrains = NULL, burnin = NULL){
if(is.null(constrains)){
constMatrix <- constrains
constMatrix <- getOption("RMuso_constMatrix")[[fileType]][[as.character(getOption("RMuso_version"))]]
} else {
constMatrix <- constrains
}
parameters <- parameters[,-1]
constMatrix <- constMatrix[,-1]
depTableMaker <- function(constMatrix,parameters){
# browser()
parameters <- parameters[order(parameters[,1]),] ## BUG!!!
selectedRows <- constMatrix[,"INDEX"] %in% parameters[,1]
rankList <- rank(constMatrix[selectedRows,2])
constMatrix[selectedRows,c(5,6)] <- parameters[rankList,c(2,3)]
logiConstrain <- (constMatrix[,"GROUP"] %in% constMatrix[constMatrix[,"INDEX"] %in% parameters[,1],"GROUP"] &
(constMatrix[,"GROUP"]!=0)) | ((constMatrix[,"INDEX"] %in% parameters[,1]) & (constMatrix[,"GROUP"] == 0))
constMatrix <- constMatrix[logiConstrain,]
constMatrix <- constMatrix[order(apply(constMatrix[,7:8],1,function(x){x[1]/10+abs(x[2])})),]
constMatrix
}
# browser()
genMat0 <- function(dep){
numberOfVariable <- nrow(dep)
G <- rbind(diag(numberOfVariable), -1*diag(numberOfVariable))
h <- c(dependences[,5], -1*dependences[,6])
return(list(G=G,h=h))
}
genMat1 <- function(dep, N){
## Range <- sapply(list(min,max),function(x){
## x(as.numeric(rownames(dep)))
## }) It is more elegant, more general, but slower
Range <- (function(x){
c(min(x), max(x))
})(as.numeric(dep[,"rowIndex"]))
numberOfVariables <- nrow(dep)
G<- -1*diag(numberOfVariables)
for(i in 1:numberOfVariables){
if(dep[i,4]!=0){
G[i,dep[i,4]] <- 1
}
}
# browser()
G<-G[dep[,4]!=0,]
if(is.null(nrow(G))){
G<-t(as.matrix(G))
}
numRowsInG <- nrow(G)
if(Range[1]==1){
G<-cbind(G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0))
} else{
if(Range[2]==N){
G<-cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G)
} else {
G <- cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0))
}
}
return(list(G=-1*G,h=-1*rep(0,nrow(G))))
}
genMat2 <- function(dep, N){
G <- rep(1,nrow(dep))
Range <- (function(x){
c(min(x), max(x))
})(as.numeric(dep[,"rowIndex"]))
if(Range[1]==1){
G<-c(G, numeric(N-Range[2]))
} else{
if(Range[2]==N){
G<-c(numeric(Range[1]-1), G)
} else {
G <- c(numeric(Range[1]-1), G, numeric(N-Range[2]))
}
}
G <- t(matrix(sign(dep[2,4])*G))
h <- abs(dep[1,4])
if(dep[1,"TYPE"]==2){ # This is not needed, I'll have to remove the if part, and keep the content
G <- G*(-1)
h <- h*(-1)
}
return(list(G=G,h=h))
}
genMat3 <- function(dep, N){
Range <- (function(x){
c(min(x), max(x))
})(as.numeric(dep[,"rowIndex"]))
E <- rep(1,nrow(dep))
if(Range[1]==1){
E<-c(E, numeric(N-Range[2]))
} else{
if(Range[2]==N){
E<-c(numeric(Range[1]-1), E)
} else {
E <- c(numeric(Range[1]-1), E, numeric(N-Range[2]))
}
}
E <- t(matrix(E))
f <- dep[1,4]
return(list(E=E,f=f))
}
applyRandTypeG <- function(dep,N){
type <- unique(dep[,"TYPE"])
minR <- min(dep[,"rowIndex"])
maxR <- max(dep[,"rowIndex"])
switch(type,
invisible(Gh <- genMat1(dep, N)),
invisible(Gh <- genMat2(dep, N)))
return(Gh)
}
applyRandTypeE <- function(dep,N){
type <- unique(dep[,"TYPE"])
minR <- min(dep[,"rowIndex"])
maxR <- max(dep[,"rowIndex"])
switch(-type,
stop("Not implemented yet"),
stop("Not implemented yet"),
invisible(Ef <- genMat3(dep, N)))
return(Ef)
}
dependences <- depTableMaker(constMatrix, parameters)
dependences <- cbind(dependences,1:nrow(dependences))
colnames(dependences)[ncol(dependences)] <- "rowIndex"
# browser()
numberOfVariable <- nrow(dependences)
nonZeroDeps<-dependences[dependences[,"TYPE"]!=0,]
if(nrow(nonZeroDeps)!=0){
splitedDeps<- split(nonZeroDeps,nonZeroDeps[,"GROUP"])
Gh <- list()
Ef <- list()
for(i in 1:length(splitedDeps)){
print(splitedDeps[[i]][1,"TYPE"])
if(splitedDeps[[i]][1,"TYPE"]>0){
Gh[[i]]<-applyRandTypeG(splitedDeps[[i]],nrow(dependences))
} else {
Ef[[i]] <- applyRandTypeE(splitedDeps[[i]],nrow(dependences))
}
}
Gh0<- genMat0(dependences)
G <- do.call(rbind,lapply(Gh,function(x){x$G}))
G<- rbind(Gh0$G,G)
h <- do.call(c,lapply(Gh,function(x){x$h}))
h <- c(Gh0$h,h)
E <- do.call(rbind,lapply(Ef,function(x){x$E}))
f <- do.call(c,lapply(Ef,function(x){x$f}))
# browser()
randVal <- suppressWarnings(limSolve::xsample(G=G,H=h,E=E,F=f,burninlength=burnin, iter = iterations))$X
} else{
Gh0<-genMat0(dependences)
randVal <- suppressWarnings(xsample(G=Gh0$G,H=Gh0$h, iter = iterations))$X
}
results <- list(INDEX =dependences$INDEX, randVal=randVal)
return(results)
}

View File

@ -0,0 +1,121 @@
#' musoSensi
#'
#' This function does regression based sensitivity analysis based on the output of musoMonte.
#' @param settings A list of montecarlos environmental variables. It is generated by the setupMuso() function. In default the settings parameter is generated automatically.
#' @param parameters This is a dataframe (heterogen data-matrix), which first column is the name of the parameters, the second is a numeric vector of the rownumbers of the given variable in the epc-fie, the last two column consist the endpont of the parameter-ranges, where the parameters will be randomized.
#' @param calibrationPar You may want to change some parameters in your epc file, before you run the modell. You have to select the appropirate modell parameters. You can refence to these with the number of the line in the epc file where the variables are. It indexes from one. You should use a vector for this, like: c(1,5,8)
#' @param inputDir The location of the input directory, this directory must content a viable pack of all inputfiles and the executable file.
#' @param iterations number of the monteCarlo run.
#' @param preTag It will be the name of the output files. For example preTag-1.csv, pretag-2csv...
#' @param outputType This parameter can be "oneCsv", "moreCsv", and "netCDF". If "oneCsv" is choosen the function create 1 big csv file for all of the runs, if "moreCsv" is choosen, every modell output goes to separate files, if netCDF is selected the outputs will be put in a netCDF file. The default value of the outputTypes is "moreCsv". netCDF is not implemented yet.
#' @param fun If you select a variable from the possible outputs (with specify the varIndex parameter), you have to provide a function which maps to a subset of real numbers. The most frequent possibilities are: mean, min, max, var, but you can define any function for your need.
#' @param varIndex This parameter specify which parameter of the output will be used. You can extract this information from the ini-files. At the output parameter specifications, the parameters order will determine this number. For example, if you have set these output parameters: 412, 874, 926, 888, and you want to use 926, you should address varIndex with 3.
#' @param skipSpinup With this parameter, you can turn of the spinup phase after the first spinup. I will decrease the time significantly.
#' @importFrom ggplot2 geom_bar ggplot aes theme element_text xlab ylab ggtitle ggsave scale_y_continuous
#' @importFrom scales percent
#' @export
musoSensi <- function(monteCarloFile = NULL,
parameters = NULL,
settings = NULL,
inputDir = "./",
outLoc = "./calib",
outVars = NULL,
iterations = 30,
preTag = "mont-",
outputType = "moreCsv",
fun = mean,
varIndex = 1,
outputFile = "sensitivity.csv",
plotName = "sensitivity.png",
plotTitle = "Sensitivity",
skipSpinup = TRUE,
skipZero = TRUE,
postProcString=NULL,
modifyOut=TRUE,
dpi=300){
if(is.null(parameters)){
parameters <- tryCatch(read.csv("parameters.csv",stringsAsFactor=FALSE), error = function (e) {
stop("You need to specify a path for the parameters.csv, or a matrix.")
})
} else {
if((!is.list(parameters)) & (!is.matrix(parameters))){
parameters <- tryCatch(read.csv(parameters,stringsAsFactor=FALSE), error = function (e){
stop("Cannot find neither parameters file neither the parameters matrix")
})
}}
parameters[,1] <- gsub("([\\s]|\\-epc)","",parameters[,1],perl=TRUE)
doSensi <- function(M){
# browser()
npar <- ncol(M)-1
M <- M[which(!is.na(M[,ncol(M)])),]
M <- M[-1,]
y <- M[,(npar+1)]
colnames(M) <- gsub("\\.epc","-epc",colnames(M))
M <- M[,colnames(M) %in% parameters[,1]]
npar <- ncol(M)
M <- apply(M[,1:npar],2,function(x){x-mean(x)})
varNames<- colnames(M)[1:npar]
w <- lm(y~M)$coefficients[-1]
Sv <- apply(M,2,var)
overalVar <- sum(Sv*w^2,na.rm = TRUE)
S=numeric(npar)
for(i in 1:npar){
S[i] <- ((w[i]^2*Sv[i])/(overalVar))*100
}
S <- round(S,digits=2)
names(S)<-varNames
write.csv(file = outputFile, x = S)
sensiPlot <- ggplot(data.frame(name=varNames,y=S/100),aes(x=name,y=y))+
geom_bar(stat = 'identity')+
theme(axis.text.x = element_text(angle = 45, hjust = 1))+
xlab(NULL)+
ylab(NULL)+
ggtitle("Sensitivity")+
scale_y_continuous(labels = scales::percent,limits=c(0,1))
print(sensiPlot)
ggsave(plotName,dpi=dpi)
return(S)
}
if(is.null(monteCarloFile)){
M <- musoMonte(parameters = parameters,
settings = settings,
inputDir = inputDir,
outLoc = outLoc,
iterations = iterations,
preTag = preTag,
outputType = outputType,
outVars = outVars,
fun = fun,
varIndex = varIndex,
skipSpinup = skipSpinup,
skipZero=skipZero,
postProcString=postProcString,
modifyOut=modifyOut
)
M <- cbind(seq_along(M[,1]),M)
yInd <- grep("mod.", colnames(M))[varIndex]
parNames <- grep("mod.",colnames(M), invert=TRUE, value = TRUE)
M <- M[,c(grep("mod.", colnames(M),invert=TRUE),yInd)]
return(doSensi(M))
} else {
M <- read.csv(monteCarloFile)
yInd <- grep("mod.", colnames(M))[varIndex]
parNames <- grep("mod.",colnames(M), invert=TRUE, value = TRUE)
M <- M[,c(grep("mod.", colnames(M),invert=TRUE),yInd)]
# browser()
return(doSensi(M))
}
}

View File

@ -0,0 +1,116 @@
#' musoDate
#'
#' This function generates MuSo compatibla dates for the data
#' @author Roland HOLLOS
#' @param startYear
#' @param numYears
#' @param timestep
#' @param combined
#' @param corrigated
#' @param format
#' @importFrom lubridate leap_year
#' @export
musoDate <- function(startYear, endYears = NULL, numYears, combined = TRUE, leapYearHandling = FALSE, prettyOut = FALSE){
if(is.null(endYears) & is.null(numYears)){
stop("You should provide endYears or numYears")
}
if(is.null(endYears)){
endYear <- startYear + numYears -1
}
dates <- seq(from = as.Date(paste0(startYear,"01","01"),format = "%Y%m%d"), to = as.Date(paste0(endYear,"12","31"),format = "%Y%m%d"), by = "day")
if(leapYearHandling){
if(prettyOut){
return(cbind(format(dates,"%d.%m.%Y"),
as.numeric(format(dates,"%d")),
as.numeric(format(dates,"%m")),
as.numeric(format(dates,"%Y"))) )
}
if(combined == FALSE){
return(cbind(format(dates,"%d"),format(dates,"%m"),format(dates,"%Y")))
} else {
return(format(dates,"%d.%m.%Y"))
}
} else {
dates <- dates[format(dates,"%m%d")!="0229"]
if(prettyOut){
return(data.frame(date = format(dates,"%d.%m.%Y"),
day = as.numeric(format(dates,"%d")),
month = as.numeric(format(dates,"%m")),
year = as.numeric(format(dates,"%Y"))))
}
if(combined == FALSE){
return(cbind(format(dates,"%d"),format(dates,"%m"),format(dates,"%Y")))
} else {
return(format(dates,"%d.%m.%Y"))
}
}
}
#' alignData
#'
#' This function align the data to the model and the model to the data
#' @importFrom lubridate leap_year
#' @keywords internal
alignData <- function(mdata, dataCol, modellSettings = NULL, startDate=NULL, endDate=NULL, formatString = "%Y-%m-%d", leapYear = TRUE, continious = FALSE){
if(continious){
if((is.null(startDate) | is.null(endDate))){
stop("If your date is continuous, you have to provide both startDate and endDate. ")
}
startDate <- as.Date(startDate, format = formatString)
endDate <- as.Date(endDate, format = formatString)
}
if(is.null(modellSettings)){
modellSettings <- setupMuso()
}
mdata <- as.data.frame(mdata)
if(continious){
dates <- seq(startDate, to = endDate, by= "day")
} else{
dates <- do.call(c,lapply(seq(nrow(mdata)), function(i){ as.Date(paste0(mdata[i,1],sprintf("%02d",mdata[i,2]),mdata[i,3]),format = "%Y%m%d")}))
}
## if(!leapYear){
## casualDays <- which(format(dates,"%m%d") != "0229")
## #mdata <- mdata[casualDays,]
## dates <- dates[casualDays]
## }
mdata <- mdata[dates >= as.Date(paste0(modellSettings$startYear,"01","01"),format = "%Y%m%d"),]
dates <- dates[dates >= as.Date(paste0(modellSettings$startYear,"01","01"),format = "%Y%m%d")]
## goodInd <- which(!(leap_year(dates)&
## (format(dates,"%m") == "12")&
## (format(dates,"%d") == "31")))
if(leapYear){
goodInd <- which(!(leap_year(dates)&
(format(dates,"%m") == "12")&
(format(dates,"%d") == "31")))
} else {
goodInd <-seq_along(dates)
}
realDate <- dates[which(format(dates,"%m%d") != "0229")]
if(leapYear){
mdata <- cbind.data.frame(realDate,mdata[goodInd,])
} else {
mdata <- cbind.data.frame(dates,mdata)
}
modellDates <- as.Date(musoDate(startYear = modellSettings$startYear,numYears = modellSettings$numYears), format = "%d.%m.%Y")
mdata <- mdata[mdata[,1] %in% modellDates,]
nonEmpty <- which(!is.na(mdata[,dataCol+1]))
mdata <- mdata[nonEmpty,]
modIndex <- which(modellDates %in% mdata[,1])
list(measuredData = mdata[,dataCol +1], modIndex = modIndex)
}

View File

@ -0,0 +1,201 @@
#' normalMuso
#'
#' This function optionally changes the EPC file and runs the Biome-BGCMuSo model in normal phase and reads its output file in a well-structured way with debugging features. (Execution of spinup phase is possible with spinupMuso.) Prerequisite of normalMuso is the existence of the endpoint file (which is the result of the spinup phase and contains initial conditions for the simulation).
#'
#' @author Roland HOLLOS
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param timee The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet.
#' @param debugging If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory and stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.
#' @param keepEpc If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.
#' @param export If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv.
#' @param silent If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.
#' @param aggressive It deletes all previous model-outputs from previous model runs.
#' @param parameters Using normalMuso it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).
#' @param logfilename If you would like to set a specific name for your logfiles you can set this via the logfile parameter.
#' @param leapYear Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years.
#' @param keepBinary By default RBBGCMuso keeps the working environment as clean as possible, thus deletes all the regular output files. The results are directly written to the standard output (e.g. to the screen), but you can redirect it and save them to a variable. Alternatively, you can export your results to the desired destination in a desired format. Through the keepBinary parameter you can set RBBGCMuso to keep the binary output files. If you would like to set the location of the binary output, please take a look at the binaryPlace argument.
#' @param binaryPlace The directory for the binary output files (see the keepBinary parameter).
#' @param fileToChange You can change any line of the EPC or the INI file prior to model execution. All you need to do is to specify with this variable which file you want to change. Two options possible: "EPC" or "INI"
#' @return The simulation output matrix, where the columns are the chosen variables and each row is a daily/monthly/annual data.
#' @usage normalMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL,
#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
#' @import utils
#' @export
normalMuso<- function(settings=NULL,parameters=NULL,timee="d",debugging=FALSE,logfilename=NULL,keepEpc=FALSE, export=FALSE,silent=FALSE,aggressive=FALSE,leapYear=FALSE, binaryPlace=NULL,fileToChange="epc", keepBinary=FALSE){
##########################################################################
###########################Set local variables########################
########################################################################
if(is.null(settings)){
settings <- setupMuso() #( :INSIDE: setupMuso.R)
}
# The software works on Linux or Windows, Mac is not implemented yet, so with this simple dichotomy we can determine wich syste is running
Linuxp <-(Sys.info()[1]=="Linux")
##Copy the variables from settings
inputLoc <- settings$inputLoc
outputLoc <- settings$outputLoc
outputNames <- settings$outputNames
executable <- settings$executable
iniInput <- settings$iniInput
epc <- settings$epcInput
calibrationPar <- settings$calibrationPar
## We want to minimize the number of sideeffects so we store the state to restore in the end.
whereAmI<-getwd()
## Optionally the user may want to store the original binary file. At default we set it to the output location.
if(is.null(binaryPlace)){
binaryPlace <- outputLoc
}
## Now we create a directories for the debugging files if these are not exists, and if debugging or keepEpc options are set to true.
if(debugging){ #debugging is boolean, so we dont write debugging == TRUE for the sake of faster model run
#If log or ERROR directory does not exists create it!
dirName<-file.path(inputLoc,"LOG")
dirERROR<-file.path(inputLoc,"ERROR")
if(!dir.exists(dirName)){
dir.create(dirName)
}
if(!dir.exists(dirERROR)){
dir.create(dirERROR)
}
}
if(keepEpc) {#keepEpc is boolean
epcdir <- dirname(epc[1])
print(epcdir)
WRONGEPC<-file.path(inputLoc,"WRONGEPC")
EPCS<-file.path(inputLoc,"EPCS")
if(!dir.exists(WRONGEPC)){
dir.create(WRONGEPC)
}
if(!dir.exists(EPCS)){
dir.create(EPCS)
}
}
if(!is.null(parameters)){
switch(fileToChange,
"epc" = tryCatch(changemulline(filename = 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)
error = function (e) {stop("Cannot change the ini file")}),
"both" = (stop("This option is not implemented yet, please choose epc or ini"))
)
}
#normal run
## if(silent){
## if(Linuxp){
## system(paste(executable,iniInput[2],"> /dev/null",sep=" "))
## } else {
## system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE)
## }
## } else {
## system(paste(executable,iniInput[2],sep=" "))
## }
## system(paste(executable,iniInput[2],sep=" "))
## switch(timee,
## "d"=(Reva<-getdailyout(settings)),
## "m"=(Reva<-getmonthlyout(settings)),
## "y"=(Reva<-getyearlyout(settings))
## )
if(silent){
if(Linuxp){
tryCatch(system(paste(executable,iniInput[2],"> /dev/null",sep=" ")),
error =function (e) {stop("Cannot run the modell-check the executable!")})
} else {
tryCatch(system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE),
error =function (e) {stop("Cannot run the modell-check the executable!")} )
}
} else {
tryCatch(system(paste(executable,iniInput[2],sep=" ")),
error =function (e) {stop("Cannot run the modell-check the executable!")})
}
##read the output
switch(timee,
"d"=(Reva <- tryCatch(getdailyout(settings), #(:INSIDE: getOutput.R )
error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"m"=(Reva <- tryCatch(getmonthlyout(settings), #(:INSIDE: getOutput.R )
error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"y"=(Reva <- tryCatch(getyearlyout(settings), #(:INSIDE: getOutput.R )
error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")}))
)
if(keepBinary){
possibleNames <- getOutFiles(outputLoc = outputLoc,outputNames = outputNames) #(:INSIDE: assistantFunctions.R)
stampAndDir(outputLoc = outputLoc,names = possibleNames,stampDir=binaryPlace,type="output") #(:INSIDE: assistantFunctions.R)
}
logfiles <- getLogs(outputLoc,outputNames,type = "normal") #(:INSIDE: assistantFunctions.R)
#############LOG SECTION#######################
errorsign <- readErrors(outputLoc = outputLoc,logfiles = logfiles,type="normal") #(:INSIDE: assistantFunctions.R)
if(keepEpc){#if keepepc option turned on
if(length(unique(dirname(epc)))>1){
stop("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?")
} else {
stampAndDir(stampDir=EPCS, wrongDir=WRONGEPC, names=epc[2], type="general", errorsign=errorsign, logfiles=logfiles)
}
}
if(debugging){ #debugging is boolean
logfiles <- file.path(outputLoc,logfiles)
stampAndDir(stampDir=dirName, wrongDir=dirERROR, names=logfiles, type="general",errorsign=errorsign,logfiles=logfiles)}
cleanupMuso()
if(errorsign==1){
return("Modell Failure")
}
return(Reva)
}

View File

@ -0,0 +1,185 @@
#' getyearlycum
#'
#' Funtion for getting cumulative yearly data from observations
#' @author Roland Hollos
#' @param daily_observations vector of the daily observations.
#' @return A vector of yearly data
#' @export
getyearlycum<-function(daily_observations){
number_of_years<-length(daily_observations)/365
# daily_observations[is.na(daily_observations)]<-0 # 3+NA=NA
fr<-1
yearlycum<-rep(NA,number_of_years)
for(i in 1:number_of_years){
to<-i*365
yearlycum[i]<-sum(daily_observations[fr:to],na.rm = TRUE)
fr<-i*365+1
}
return(yearlycum)
}
#' getyearlymax
#'
#' Function for getting the maximum values of the years, from daily data
#' @author Roland Hollos
#' @param daily_observations vector of the daily observations
#' @return A vector of yearly data
#' @usage getyearlymax(daily_observations)
#' @export
getyearlymax<-function(daily_observations){
number_of_years<-length(daily_observations)/365
# daily_observations[is.na(daily_observations)]<-0 # 3+NA=NA
fr<-1
yearlycum<-rep(NA,number_of_years)
for(i in 1:number_of_years){
to<-i*365
yearlymax[i]<-max(daily_observations[fr:to],na.rm=TRUE)
fr<-i*365+1
}
return(yearlymax)
}
#' fextension
#'
#' A function for extracting the extension name from the filename string
#' @author Roland Hollos
#' @param filename The string of the filenam
#' @return the extension of the given file
#' @usage fextension(filename)
fextension <- function(filename){
#this function gives back the given filenames extension
fextension <- tail(unlist(strsplit(filename,"\\.")),1)
return(fextension)
}
#'supportedMuso
#'
#' A function for getting the list of the output formats which is supported by RBBGCMuso
#' @author Roland Hollos
#' @param type "outputs" or "message", if you choose "outputs", it gives you a simple vector of the formats, if you choose "message", it gives you a full sentence which contains the same information.
#' @return if you choose "outputs", it gives you a simple vector of the formats, if you choose "message", it gives you a full sentence which contains the same information.
#' @usage supportedMuso(type="outputs")
#' @export
supportedMuso <- function(type="outputs"){
supportedFormats <- c("xls","xlsx","odt","csv","txt")
if(type=="outputs"){
#If you add new format supports, please expand the lists
return(supportedFormats)
}
if(type=="message"){
return(cat("Supported formats are ",supportedFormats,"If your fileformat is something else, we automaticle coerced it to csv.\n"))
}
}
#' corrigMuso
#'
#' This function leapyear-corrigate the output of the modell
#' @author Roland Hollos
#' @param settings This is the output of the setupMuso() function. It contains all of the RBBGCMuso settings
#' @param data the models outputdata
#' @return It returns the modells leapyear-corrigated output data.
#' @export
#' @usage corrigMuso(settings, data)
corrigMuso <- function(settings, data){
insertRow <- function(existingDF, newrow, r){
nr <- nrow(existingDF)
existingDF <- rbind(existingDF,rep(NA,ncol(existingDF)))
existingDF[seq(r+1,nr+1),] <- existingDF[seq(r,nr),]
existingDF[r,] <- newrow
existingDF
}
numdays <- nrow(data)
data <- data
numyears <- settings$numyears
leapyears <- musoLeapYears(settings)
sylvesters <- data[seq(from=365, to=numdays, by=365),]
ind <- 0
for(i in 1:numyears){
if(leapyears[i]){
data <- insertRow(data,sylvesters[i],i*360+ind)
ind <- ind+1
}
}
return(data)
}
## #' file.path2
## #'
## #' It is an extended file.path function, it can concatenate path where the first ends and the second begins with "/", so
## #' there wont be two slash nearby eachother
## #' @author Roland Hollos
## #' @param str1 This is the first path string
## #' @param str2 This is the second path string
## #' @return A concatenated path
## #' @export
## #' @usage file.path2(str1, str2)
## file.path2<-function(str1, str2){
## if(str1==""|str1=="./"){
## return(str2)
## }
## str1<-file.path(dirname(str1),basename(str1))
## if(substring(str2,1,1)=="/"){
## return(paste(str1,str2,sep=""))
## } else{
## return(file.path(str1,str2))
## }
## }
numFactors <- function(x,type="pos"){
x <- as.integer(abs(x))
div <- seq_len(x)
posdiv <- div[x%%div==0L]
negdiv <- posdiv*-1
alldiv <- c(negdiv,posdiv)
switch(type,"pos"=return(posdiv),"neg"=return(negdiv),"all"=return(alldiv))
}
niceMatrixLayoutForPlots <- function(n){
if(n==0){
return(cat("Ther is nothing to do with 0 graph"))
}
n <- as.integer(n)
factors <- numFactors(n)
if(length(factors)==2){
return(n)}
sqrtn <- round(sqrt(n))
num1 <- factors[which(min(abs(factors-sqrtn))==abs(factors-sqrtn))[1]]
num2 <- n/num1
return(c(num1,num2))
}
truncNorm<-function(N,mean, sd, min, max){
n=0
randomNorm<-rep(NA,N)
while(n<=N){
transNorm<-rnorm(1,mean,sd)
if((transNorm>min)&(transNorm<max)){
randomNorm[n]<-transNorm
n<-n+1
}
}
return(randomNorm)
}
#' getConstMatrix
#'
#' getConstMatrix is a function whith wich you can get the default constrain matrix for your choosen type and version.
#' @param filetype It can be "epc" or "soil".
#' @param version The version of the MuSo environment
#' @export
getConstMatrix <- function (filetype="epc", version = as.character(getOption("RMuso_version"))) {
getOption("RMuso_constMatrix")[[filetype]][[version]]
}

View File

@ -0,0 +1,89 @@
#' updateMusoMapping
#'
#' 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!
#' @author Roland HOLLOS
#' @param excelName Name of the excelfile which contains the parameters
#' @importFrom openxlsx read.xlsx
#' @importFrom jsonlite write_json
#' @return The output code-variable matrix, and also the function changes the global variable
#' @export
updateMusoMapping <- function(excelName, dest="./", version=getOption("RMuso_version")){
expandRangeRows <- function (ind) {
toExpand <- excelDF[ind,]
rangeString <- gsub(".*?(\\d*\\-\\d*).*","\\1",toExpand[2])
interval <- as.numeric(strsplit(rangeString,split="-")[[1]])
result <- do.call(rbind,lapply(interval[1]:interval[2],function(x){
toExpand[2] <- x
toExpand[1] <- gsub("\\[.*?\\]",sprintf("_%s",(x-interval[1])),toExpand[1])
toExpand
}))
result <- as.data.frame(result,stringsAsFactors = FALSE)
result[,2] <- as.numeric(result[,2])
colnames(result) <- c("names","codes","units","descriptions")
result[,c(2,1,3,4)]
}
excelDF <- read.xlsx(excelName)
excelDF <- excelDF[!is.na(excelDF[,2]),]
excelDF[,1] <- trimws(excelDF[,1])
excelDF[,2] <- trimws(excelDF[,2])
excelDF[,3] <- trimws(excelDF[,3])
excelDF[,4] <- trimws(excelDF[,4])
rangeRows <- grep("-",excelDF[,2])
nonRangeMatrix <- excelDF[setdiff(1:nrow(excelDF),rangeRows),]
nonRangeMatrix[,2] <- as.numeric(nonRangeMatrix[,2])
nonRangeMatrix[,1] <- trimws(nonRangeMatrix[,1])
names(nonRangeMatrix) <- c("names","codes","units","descriptions")
outMatrix <- rbind.data.frame(do.call(rbind.data.frame,lapply(rangeRows,expandRangeRows)),
nonRangeMatrix[,c(2,1,3,4)])
outMatrix <- outMatrix[order(outMatrix[,1]),]
rownames(outMatrix)<- NULL
write_json(outMatrix, file.path(dest,sprintf("varTable%s.json",version)), pretty=TRUE)
}
#' musoMapping
#'
#' musoMapping can provide the user the name of a Biome-BGCMuSo output code. Within Biome-BGCMuSo the state variables and fluxes are marked by integer numbers. In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is utilized by this function. This function converts variable codes into names musoMappingFind does the opposite.
#' @author Roland HOLLOS
#' @param code the MuSo outputcode
#' @param mapData updateMusomapping generated matrix
#' @return The name of the Biome-BGCMuSo output code (e.g. if code is 3009 this function should return GPP to the user)
#' @export
#' @usage musoMapping(code, mapData=NULL)
musoMapping <- function(code,
mapData=getOption("RMuso_varTable")[[as.character(getOption("RMuso_version"))]]){
if(is.null(mapData)){
return(unlist(tryCatch(mMapping[which(mMapping[,1]==code),2],error = function(e){
stop(sprintf("The code %s in inifile is not valid muso output variable code",code))
}))) #mMapping is package-scoped system variable generated by udateMusoMapping
} else {
return(unlist(mapData[which(mapData[,1]==code),2]))
}
}
#' musoMappingFind
#'
#' musoMappingFind can provide us the code of the Biome-BGCMuSo output variable name. Within Biome-BGCMuSo the state variables and fluxes are marked by integer numbers. In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is utilized by this function. This function converts variable names into codes. musoMapping does the opposite.
#' @author Roland HOLLOS
#' @param variable If this is null, return the whole mapping table. In other cases search for the variable code
#' @return The code of the specific output variable name
#' @export
#' @usage musoMapping(code, mapData=NULL)
musoMappingFind <- function(variable=NULL,
mMapping=getOption("RMuso_varTable")[[as.character(getOption("RMuso_version"))]]){
if(is.null(variable)){
return(mMapping)
} else {
mMapping[grep(variable,mMapping[,2]),]
}
}

View File

@ -0,0 +1,78 @@
#' paramSweep
#'
#' This function is for testing the modell response to change a set of input variables. It generates an html file which contains a set of graphics of the ...
#' @author Roland Hollos
#' @param inputDir The directory which contains the MuSo model's ini files
#' @param parameters A csv file's path which contains the input parameters. The first row must be the name of the parameters, the second is the index of the parameters(row index in the input file), the third is the minimum value of the parameters, the forth is the maximum value of the parameters. If it is not privided, a filebrowser will pop up.
#' @param outputDir The path of the directory where the html file will be generated.
#' @param iterations The number of changes in the parameter
#' @param outVar The name of the output variable to plot, of the MuSo code of it.
#' @param htmlOutName The name of the rendered html file
#' @importFrom rmarkdown render pandoc_version
#' @importFrom digest digest
#' @importFrom tcltk tk_choose.files
#' @export
paramSweep <- function(inputDir="./",
parameters=NULL,
outputDir=NULL,
iterations=10,
outVar="daily_gpp",
htmlOutName = "paramsweep.html"){
if(is.null(pandoc_version())){
stop("In order to use parameterSweep you have to have\n pandoc (1.12.3+) installed or run this function from Rstudio\n
You can download pandoc from here: 'https://pandoc.org/',\n or Rstudio from here: 'https://www.rstudio.com/'")
}
currDir <- getwd()
opSystem <- Sys.info()[[1]]
if(is.character(outVar)){
varNames <- as.data.frame(musoMappingFind(outVar))
if(nrow(varNames)!=1){
warning("There are more than one output variable in conection with ", outVar, ". The first possibility were choosen.")
print(varNames)
outVarIndex <- unlist(varNames[1,1])
varNames <- as.character(unlist(varNames[1,2]))
} else {
outVarIndex <- unlist(varNames[1,1])
varNames <- as.character(unlist(varNames[1,2]))
}
} else {
varNames <- musoMapping(outVar)
outVarIndex<-outVar
}
if(is.null(parameters)){
parameters <- tcltk::tk_choose.files(caption = "Please select a file with the parameters and the ranges")
}
rmdFile <- "---\ntitle: \"ParameterSweep basic\"\n---\n```{r setup, include=FALSE}\nknitr::opts_chunk$set(echo = TRUE)\n```\n```{r, echo=FALSE}\nsuppressWarnings(library(RBBGCMuso))\n```\n```{r, echo=FALSE}\nparameters <- read.csv(\"parameters.csv\")\n```\n```{r,fig.width=10, fig.height=3, echo=FALSE}\nnumPar\nfor(i in 1:numPar){\n suppressWarnings(musoQuickEffect(calibrationPar=parameters[i,2],startVal = parameters[i,3], endVal = parameters[i,4],\nnSteps = 9,\noutVar = \"daily_gpp\",\nparName = parameters[i,1]))\n}\n```"
rmdVec <- unlist(strsplit(rmdFile,"\n"))
rmdVec[11] <- paste0("parameters <- read.csv(\"",parameters,"\", stringsAsFactor = FALSE)")
rmdVec[14] <- "numPar <- nrow(parameters)"
rmdVec[17] <- paste0("nSteps = ", iterations - 1,",")
rmdVec[18] <- paste0("outVar = \"",varNames,"\",")
if(!is.null(outputDir)){
setwd(outputDir)
}
randName <- paste0(digest(date(),"md5"),"-paramsweep.rmd")
writeLines(rmdVec,randName)
render(randName,output_file = htmlOutName)
unlink(randName)
if(opSystem == "Linux"){
system(paste0("xdg-open ",htmlOutName))
} else {
if(opSystem == "Windows"){
shell(paste0("start ",htmlOutName))
} else {
system(paste0("open ",htmlOutName))
}
}
setwd(currDir)
}

View File

@ -0,0 +1,389 @@
#'plot the Biome-BGCMuSo output
#'
#' This function runs the Biome-BGCMuSo model and reads its output file in a well structured way, and after that it plots the results automatically. plotMuso is a convenient and quick method to create nice graphs from Biome-BGCMuSo output which is quite painful in other environments.
#'
#' @author Roland HOLLOS, Dora HIDY
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param timee The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet.
#' @param debugging If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory and stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.
#' @param keepEpc If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.
#' @param export If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv.
#' @param silent If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.
#' @param aggressive It deletes all previous model-outputs from previous model runs.
#' @param variable Column number of the output variable which should be plotted, or "all" if you have less than 10 variables. In this case the function will plot everything in a matrix layout.
#' @param leapYear Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years.
#' @param logfilename If you would like to set a specific name for your logfiles you can set this via the logfile parameter.
#' @param plotType There are two options implemented by now: continuous time series ("cts") or disctrete time series ("dts")
#' @param skipSpinup If TRUE, the function won't perform the spinup simulation. In this case the endpoint file must exist that provides initial conditions for the run.
#' @return It depends on the export parameter. The function returns with a matrix with the model output, or writes this into a file, which is defined previously
#' @usage plotMuso(settings, variable,
#' timee="d", silent=TRUE,
#' debugging=FALSE, keepEpc=FALSE,
#' logfilename=NULL, aggressive=FALSE,
#' leapYear=FALSE, export=FALSE)
#' @importFrom ggplot2 ggplot aes_string geom_line geom_point aes labs theme ggsave element_blank facet_wrap
#' @importFrom dplyr filter group_by summarize mutate '%>%'
#' @importFrom tibble rownames_to_column
#' @importFrom tidyr separate gather
#' @importFrom data.table ':=' data.table
#' @export
plotMuso <- function(settings = NULL, variable = "all",
##compare, ##plotname,
timee = "d", silent = TRUE,
calibrationPar = NULL, parameters = NULL,
debugging = FALSE, keepEpc = FALSE,
fileToChange = "epc", logfilename = NULL,
aggressive = FALSE, leapYear = FALSE,
plotName = NULL, plotType = "cts",
layerPlot = FALSE, colour = "blue",
skipSpinup = TRUE, fromData = FALSE,
timeFrame = "day", selectYear = NULL,
groupFun = mean, separateFile = FALSE, dpi=300, postProcString = NULL){
if( plotType!="cts" && plotType != "dts"){
warning(paste0("The plotType ", plotType," is not implemented, plotType is set to cts"))
plotType <- "cts"
}
if(is.null(settings)){
settings <- setupMuso()
}
numberOfYears <- settings$numYears
startYear <- settings$startYear
dailyVarCodes <- settings$dailyVarCodes
groupByTimeFrame <- function(Data, timeFrame, groupFun){
Data <- data.table(Data)
Data[,c(variable):=groupFun(get(variable)),get(timeFrame)]
Data <- as.data.frame(Data)
Data[,1] <- as.Date(Data[,1],"%d.%m.%Y")
Data
}
if(fromData){
Reva <- tryCatch(getdailyout(settings), #(:INSIDE: getOutput.R )
error = function (e){
setwd((whereAmI))
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),
rep(1:365,numberOfYears),
musoDate(startYear = startYear,numYears = numberOfYears,combined = FALSE,corrigated=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"))
} else {
if(!is.element("cum_yieldC_HRV",unlist(settings$outputVars[[1]]))){
musoData <- calibMuso(postProcString = postProcString,settings,
calibrationPar=calibrationPar,
parameters = parameters,
silent = TRUE,skipSpinup=skipSpinup,prettyOut = TRUE)
if(!is.null(selectYear)){
musoData <- musoData %>% filter(year == get("selectYear"))
}
if(timeFrame!="day"){
musoData <- tryCatch(groupByTimeFrame(Data=musoData, timeFrame = timeFrame, groupFun = groupFun),
error=function(e){stop("The timeFrame or the groupFun is not found")})
}} else {
musoData <- calibMuso(postProcString = postProcString,settings,silent = TRUE,skipSpinup=skipSpinup,parameters = parameters, calibrationPar = calibrationPar,fileToChange = fileToChange) %>%
as.data.frame() %>%
rownames_to_column("date") %>%
mutate(date2=date,date=as.Date(date,"%d.%m.%Y"),
yearDay=rep(1:365,numberOfYears), cum_yieldC_HRV=cum_yieldC_HRV*22.22) %>%
separate(date2,c("day","month","year"),sep="\\.")
if(!is.null(selectYear)){
musoData <- musoData %>% filter(year == get("selectYear"))
}
if(timeFrame!="day"){
musoData <- tryCatch(groupByTimeFrame(data=musoData, timeFrame = timeFrame, groupFun = groupFun),
error=function(e){stop("The timeframe or the gropFun is not found")})
}
}
}
## numVari <- ncol(musoData)
# numVari <- ncol(musoData)-5
numVari <- length(settings$dailyVarCodes)
pointOrLineOrPlot <- function(musoData, variableName, plotType="cts", expandPlot=FALSE, plotName=NULL){
if(!inherits(musoData$date[1], "Date")){
musoData$date<- as.Date(as.character(musoData$date),"%d.%m.%Y")
}
if(!expandPlot){
if(plotType=="cts"){
if(length(variableName)==1){
p <- ggplot(musoData,aes_string("date",variableName,group=1))+geom_line(colour=colour)+theme(axis.title.x=element_blank())
if(!is.null(plotName)){
ggsave(as.character(plotName), plot = p)
p
}
p
} else {
p <- musoData %>%
select(c("date", variableName))%>%
gather(., key= outputs, value = bla, variableName) %>%
# head %>%
ggplot(aes(x=date,y=bla))+
facet_wrap(~ outputs, scales = "free_y",ncol=1) +
geom_line(colour=colour)+
theme(
axis.title.y = element_blank()
)
if(!is.null(plotName)){
ggsave(as.character(plotName), plot = p)
}
p
}
} else {
if(length(variableName)==1){
p <- ggplot(musoData,aes_string("date",variableName))+geom_point(colour=colour)+theme(axis.title.x=element_blank())
if(!is.null(plotName)){
ggsave(as.character(plotName),p)
}
p
} else{
p <- musoData %>%
select(c("date",variableName))%>%
gather(., key= outputs, value = bla,variableName) %>%
# head %>%
ggplot(aes(x=date,y=bla))+
facet_wrap(~ outputs, scales = "free_y",ncol=1) +
geom_line(colour=colour)+
theme(
axis.title.y = element_blank()
)
if(!is.null(plotName)){
ggsave(as.character(plotName),p)
}
p
}
}
} else {
if(!is.null(plotName)){
stop("Cannot save a single plot layer to a graphics device")
}
if(plotType=="cts"){
if(length(variableName)==1){
geom_line(data=musoData, colour=colour, aes_string("date",variableName))
} else {
stop("you cannot add layers for multiple plots")
}
} else {
if(length(variableName)==1){
geom_point(data=musoData, colour=colour, aes_string("date",variableName))
} else{
stop("you cannot add layers for multiple plots")
}
}
}
}
variableName <- as.character(settings$outputVars[[1]])[variable]
if(variable == "all"){
variableName <- as.character(settings$outputVars[[1]])
}
if(is.character(variable)){
if(identical(variable,"all")){
variable <- as.character(settings$outputVars[[1]])
} else {
if(is.element(variable, settings$dailyVarCodes)){
variable <- settings$outputVars[[1]][match(variable,settings$dailyVarCodes)]
}
if(identical(character(0),setdiff(variable,as.character(settings$outputVars[[1]])))){
variableName <- variable
} else {
if(!is.null(postProcString)){
variableName <- variable
} else {
stop("The symmetric difference of the set of the output variables specified in the ini files and the set specified with your variable parameter is not the empty set.")
}
}
}
if(length(variableName)>8){
warning("Too many variables to plot, the output quality can be poor")
}
} else {
if(prod(sapply(variable,function(x){
return(x >= 0 && x <= numVari)
}))){
variableName <- as.character(settings$outputVars[[1]])[variable]
} else {
print(numVari)
stop("Not all members of the variable parameter are among the output variables")
}}
pointOrLineOrPlot(musoData = musoData,
variableName = variableName,
plotType = plotType,
expandPlot = layerPlot,
plotName = plotName)
}
#'plot the Biome-BGCMuSo model output with observation data
#'
#' This function runs the Biome-BGCMuSo model and reads its output file in a well structured way, and after that it plots the results automatically along with a given measurement dataset provided by the user. plotMusoWithData is a convenient and quick method to create nice graphs from Biome-BGCMuSo output which is quite painful in other environments.
#'
#' @author Roland HOLLOS, Dora HIDY
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param sep This is the separator symbol used in the measurement file (that is supposed to be a delimited text file)
#' @param savePlot It it is specified, the plot will be saved in a graphical format specified by the immanent extension. For example, it the savePlot is set to image01.png then a PNG graphics file will be created.
#' @param variable The name of the output variable to plot
#' @param NACHAR This is not implemented yet
#' @param csvFile This specifies the filename of the measurements. It must contain a header. Typically this is a CSV file.
#' @param calibrationPar You might want to change some parameters in your EPC file before running the model. The function offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8)
#' @param parameters Using the function it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).
#' @usage plotMuso(settings, variable,
#' timee="d", silent=TRUE,
#' debugging=FALSE, keepEpc=FALSE,
#' logfilename=NULL, aggressive=FALSE,
#' leapYear=FALSE, export=FALSE)
#' @importFrom ggplot2 ggplot geom_line geom_point aes aes_string labs theme element_blank
#' @export
plotMusoWithData <- function(mdata, plotName=NULL,
startDate = NULL, endDate = NULL,
colour=c("black","blue"), dataVar, modelVar, settings = setupMuso(), silent = TRUE, continious = FALSE, leapYearHandling = FALSE){
if(continious & (is.null(startDate) | is.null(endDate))){
stop("If your date is continuous, you have to provide both startDate and endDate. ")
}
dataCol<- grep(paste0("^",dataVar,"$"), colnames(mdata))
selVar <- grep(modelVar,(settings$dailyVarCodes))+4
list2env(alignData(mdata, dataCol = dataCol,
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)
# 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[,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)
colnames(mesData) <- c("date", "measured")
p <- baseData %>%
ggplot(aes_string("date",selVarName)) +
geom_line(colour=colour[1]) +
geom_point(data = mesData, colour=colour[2], aes(date,measured)) +
labs(y = paste0(selVarName,"_measured"))+
theme(axis.title.x = element_blank())
if(!is.null(plotName)){
ggsave(plotName,p)
return(p)
} else {
return(p)
}
}
#' compareMuso
#'
#' This function runs the model, then changes one of its input data, runs it again, and plots both results in one graph.
#'
#' @author Roland HOLLOS
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param parameters Using this function it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).
#' @param variable The name of the output variable to plot
#' @param calibrationPar You might want to change some parameters in your EPC file before running the model. This function offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8)
#' @param fileToChange You can change any line of the EPC or the INI file. Please choose "EPC", "INI" or "BOTH". This file will be used for the analysis, and the original parameter values will be changed according to the choice of the user.
#' @import ggplot2
#' @export
compareMuso <- function(settings=NULL,parameters, variable=1, calibrationPar=NULL, fileToChange="epc", skipSpinup=TRUE, timeFrame="day"){
if(is.null(settings)){
settings <- setupMuso()
}
p1 <- plotMuso(settings = settings,variable = variable,timeFrame = timeFrame)
p2 <- p1+plotMuso(settings = settings,variable = variable, timeFrame = timeFrame,fileToChange=fileToChange,layerPlot=TRUE)
p2
}
#' saveAllMusoPlots
#'
#' This simple function takes the parameters from the ini files and generates graphics for all output variable.
#'
#' @author Roland HOLLOS
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param plotName The basename for the output plots
#' @param destination The destination for the output plots, it not exits the function will create it.
#' @param silent if true do not suspect for printfs...
#' @importFrom ggplot2 theme_classic ggplot geom_line geom_point theme element_blank geom_bar labs aes_string aes ggsave
#' @export
saveAllMusoPlots <- function(settings=NULL, plotName = ".png",
silent = TRUE, type = "line", outFile = "annual.csv",
colour = "blue", skipSpinup = FALSE){
if(is.null(settings)){
settings <- setupMuso()
}
dailyVarCodes <- settings$dailyVarCodes
annualVarCodes <-settings$annualVarCodes
outputVars <- unlist(settings$outputVars[[1]])
musoData <- calibMuso(settings = settings, prettyOut = TRUE, silent = silent, skipSpinup = skipSpinup)
musoData$date<- as.Date(musoData$date,"%d.%m.%Y")
for(i in seq_along(dailyVarCodes)){
bases <- ggplot(data = musoData, mapping = aes_string(x = "date", y = outputVars[i]))
object <-ifelse(type == "line",paste0("geom_line(colour = '",colour,"')"),
ifelse(type == "point",paste0("geom_line(colour = ",colour,")"),
stop("The")))
outPlot <- bases + eval(parse(text = object)) + theme_classic() + theme(axis.title.x=element_blank())
imName <- paste0("daily-",dailyVarCodes[i],plotName)
cat(sprintf("Saving daily output image of %s as %s\n",outputVars[i],imName))
suppressMessages(ggsave(imName, outPlot))
}
if(settings$normOutputFlags["annual"]!=2){
return("Annual output graphs was not saved (no annual output from the model)")
}
musoYData <- getyearlyout(settings)
write.csv(musoYData,paste0(settings$outputNames[[2]],outFile))
for(i in seq_along(annualVarCodes)){
outPlot <- ggplot(data = musoYData, mapping = aes_string(x = "year", y = paste0("var_",annualVarCodes[i])))+
geom_bar(stat = "identity")+ labs(y = musoMapping(annualVarCodes[i])) + theme_classic() +
theme(axis.title.x=element_blank())
ggsave(paste0("annual-",annualVarCodes[i],plotName),outPlot)
}
}

View File

@ -0,0 +1,10 @@
postProcMuso <- function(modelData, procString){
cNames <- colnames(modelData)
tocalc <- gsub("(@)(\\d)","modelData[,\\2]",procString)
newVarName <- gsub("\\s","",unlist(strsplit(procString,"<-"))[1])
assign(newVarName,eval(parse(text = unlist(strsplit(tocalc,"<-"))[2])))
modelData <- cbind.data.frame(modelData,eval(parse(text = newVarName)))
colnames(modelData) <- c(cNames,newVarName)
modelData
}

View File

@ -0,0 +1,15 @@
#' postProcMuso
#'
#' This is a function wich provides some minimal post processing capabilities
#' @keywords internal
postProcMuso <- function(modelData, procString){
modelDat <- modelData[,-(1:4)]
cNames <- colnames(modelData)
tocalc <- gsub("(@)(\\d)","modelDat[,\\2]",procString)
newVarName <- gsub("\\s","",unlist(strsplit(procString,"<-"))[1])
assign(newVarName,eval(parse(text = unlist(strsplit(tocalc,"<-"))[2])))
modelData <- cbind.data.frame(modelData,eval(parse(text = newVarName)))
colnames(modelData) <- c(cNames,newVarName)
modelData
}

View File

@ -0,0 +1,32 @@
#' putOutVars
#'
#'This function is for adding variables in the inifiles.
#'
#' @author Roland Hollos
#' @param IniFile The name of the normal ini file.
#' @param outputVars List of the output codes
#' @keywords internal
putOutVars <- function(iniFile,outputVars,modifyOriginal = FALSE){
ini <- readLines(iniFile)
numVarsOriginal <- as.numeric(unlist(strsplit(ini[grep("DAILY_OUTPUT",ini)+1],"[\ \t]"))[1])
if(!modifyOriginal){
iniOut <- paste0(tools::file_path_sans_ext(basename(iniFile)),"-tmp.",tools::file_ext(iniFile))
} else {
iniOut <- iniFile
}
outNames <- sapply(outputVars,musoMapping)
partOne <- ini[1:grep("DAILY_OUTPUT",ini)]
partTwo <- ini[grep("ANNUAL_OUTPUT",ini):(length(ini))]
numVars <- length(outputVars)
fileContent <- c(partOne,
as.character(numVars),
sapply(outputVars,function (x) {
paste(as.character(x),musoMapping(x),sep = " ")
}),
"",
partTwo)
writeLines(fileContent,iniOut)
return(list(names=outNames,ratio=numVars/numVarsOriginal))
}

View File

@ -0,0 +1,86 @@
#' musoQuickEffect
#'
#' This function changes a chosen parameter from the INI or from the ecophysiological constants file (EPC) within a predefined range (defined by the user), and visualizes the effect of the change on the selected output variable. The user has to specify the parameter, the interval for the parameter effect test, and the number of steps. This function focuses only on one parameter. The so-called paramSweep function can manipulate multiple INI/EPC parameters and visualize the results.
#' @author Roland HOLLOS
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param startVal The initial value of the given parameter.
#' @param endVal The maximum of the given parameter.
#' @param nSteps Number of steps from startVal to endVal. It equals the number of simulations, and number of curves on the final plot.
#' @param fileTochange Please choose "EPC", "INI" or "BOTH". This file will be used for the analysis, and the original parameter values will be changed according to the choice of the user.
#' @return Graph showing the runs with the selected parameters with color coding. The graph will show data from the last simulation year.
#' @importFrom ggplot2 ggplot aes_string geom_line geom_point aes labs theme ggsave element_blank facet_wrap
#' @importFrom dplyr filter group_by summarize mutate '%>%' tbl_df select
#' @importFrom tibble rownames_to_column
#' @importFrom magrittr '%<>%'
#' @importFrom tidyr separate
#' @export
musoQuickEffect <- function(settings = setupMuso(), calibrationPar = NULL, startVal, endVal, nSteps = 1, fileToChange="epc",modifyOriginal=TRUE, outVar, parName = "parVal", yearNum=1, year=(settings$startYear + yearNum -1)){
if(is.character(outVar)){
varNames <- as.data.frame(musoMappingFind(outVar))
if(nrow(varNames)!=1){
warning("There are more than one output variable in conection with ", outVar, ". The first possibility were choosen.")
print(varNames)
outVarIndex <- unlist(varNames[1,1])
varNames <- as.character(unlist(varNames[1,2]))
} else {
outVarIndex <- unlist(varNames[1,1])
varNames <- as.character(unlist(varNames[1,2]))
}
} else {
varNames <- musoMapping(outVar)
outVarIndex<-outVar
}
if(is.null(calibrationPar)){
calibrationPar <- settings$calibrationPar
}
parVals <- seq(startVal, endVal, length = (nSteps + 1))
parVals <- dynRound(startVal, endVal, seqLen = (nSteps + 1))
a <- do.call(rbind,lapply(parVals, function(parVal){
calResult <- tryCatch(calibMuso(settings = settings,calibrationPar = calibrationPar,
modifyOriginal = modifyOriginal,
parameters = parVal,
outVars = outVarIndex,
silent = TRUE,
fileToChange = fileToChange), error = function(e){NULL})
if(is.null(calResult)){
b <- cbind(rep(NA,365),parVal)
rownames(b) <- musoDate(startYear = year, numYears = 1)
colnames(b)[1] <- varNames
return(b)
} else {
if(yearNum >=0){
m <- as.data.frame(calResult[musoDate(startYear = year, numYears = 1),])
} else{
m <- as.data.frame(calResult)
}
colnames(m) <- colnames(calResult)
return(cbind(m, parVal))
}
}))
a %<>%
tbl_df %>%
mutate(date=as.Date(rownames(a),"%d.%m.%Y")) %>%
select(date,as.character(varNames),parVal)
print(suppressWarnings(ggplot(data = a, aes_string(x= "date", y= varNames))+geom_line(aes(alpha = factor(parVal))) + labs(y=varNames, alpha = parName) + scale_alpha_discrete(range=c(0.25,1))))
}
# calma <- calibMuso(settings = settings,calibrationPar = calibrationPar,
# modifyOriginal = modifyOriginal,
# parameters = parVal,
# outVars = outVarIndex,
# silent = TRUE,
# fileToChange = fileToChange)
# plot(calma[,1])
# calma <- calibMuso(settings = settings,calibrationPar = calibrationPar,
# modifyOriginal = modifyOriginal,
# parameters = parVal,
# silent = TRUE,
# fileToChange = fileToChange)
# calm <- calibMuso(calibrationPar=calibrationPar,parameters=parVal,modifyOriginal=TRUE)
# plot(x=as.Date(musoDate(2015,numYears=1),"%d.%m.%Y"),y=calm[musoDate(2015,numYears=1),"daily_gpp"],type="l")
# calibrationPar
# parVal

View File

@ -0,0 +1,28 @@
#' runMuso
#'
#' This function runs the Biome-BGCMuSo model (with option to change the EPC file), then it reads its output file in a well-structured way. As the result is passed to R, the results can be easily post-processed in R environment.
#'
#' @author Roland HOLL\'{O}S
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param timee The required timesteps in the model output. It can be "d", if it is daily, "m", if it is monthly, "y" if it is yearly. It is recommended to use daily data, as the yearly and monthly data is not well-tested yet.
#' @param debugging If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory to stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.
#' @param keepEpc If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.
#' @param export If it is set to YES or you define a filename here, the function converts the output to the specific file format. For example, if you set export to "example.csv", it converts the output to "csv". If you set it to "example.xls" it converts the output to example.xls with the xlsx package. If the Excel converter package is not installed it gives back a warning message and converts the results to csv.
#' @param silent IIf you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.
#' @param aggressive It deletes all previous model-outputs from previous model runs.
#' @param parameters Using normalMuso it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).
#' @param logfilename If you would like to set a specific name for your logfiles you can set this via the logfile parameter.
#' @param leapYear Should the function do a leapyear correction on the output data? If TRUE, then the result for 31 December will be doubled in leap years which means that the results for the leap year will cover all 366 days. See the model's User's Guide for notes on leap years.
#' @param keepBinary By default RBBGCMuso keeps the working environment as clean as possible, thus deletes all the regular output files. The results are directly written to the standard output (e.g. to the screen), but you can redirect it and save them to a variable. Alternatively, you can export your results to the desired destination in a desired format. Through the keepBinary parameter you can set RBBGCMuso to keep the binary output files. If you would like to set the location of the binary output, please take a look at the binaryPlace argument.
#' @param binaryPlace The directory for the binary output files (see the keepBinary parameter).
#' @param fileToChange You can change any line of the EPC or the INI file prior to model execution. All you need to do is to specify with this variable which file you want to change. Two options possible: "EPC" or "INI"
#' @param skipSpinup If this is set to TRUE, runMuso will not perform the spinup simulation. This is of course means that the endpoint file (initial conditions) must be available for the normal INI file. This option might be extremely useful to speed up multiple model execution. In cropland related simulations due to site history the EPC file used in the normal phase might differ from the one used in the spinup phase, which means that the spinup is the same even if we change the parameterization for the normal phase. In this situation skipSpinup is really useful.
#' @param prettyOut If this parameter is to TRUE then date will provided as the R-style Date type, and separate year, month and day vectors. In typical cases the user should use this option.
#' @return No return, outputs are written to file
#' @usage calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL,
#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
#' @import utils
#' @export
runMuso <- function(...){
calibMuso(...)
}

View File

@ -0,0 +1,278 @@
#'rungetMuso
#'
#' This function runs the BBGC-MuSo model and reads in its outputfile in a very structured way.
#'
#' @author Roland Hollos
#' @param settings You have to run the setupMuso function before rungetMuso. It is its output which contains all of the necessary system variables. It sets the whole environment
#' @param timee The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly
#' @param debugging If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles
#' @param keepEpc If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.
#' @param export if it is yes or you give a filename here, it converts the output to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.
#' @param silent If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed.
#' @param aggressive It deletes every possible modell-outputs from the previous modell runs.
#' @param leapYear Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.
#' @param logfilename If you want to set a specific name for your logfiles you can set this via logfile parameter
#' @return It depends on the export parameter. The function returns with a matrix with the modell output, or writes this in a file, which is given previously
#' @usage rungetMuso(settings, timee="d", debugging=FALSE, logfilename=NULL,
#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
#' @import utils
#' @export
rungetMuso <- function(settings, timee="d", debugging=FALSE, logfilename=NULL, keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE){
##########################################################################
###########################Set local variables########################
########################################################################
Linuxp <-(Sys.info()[1]=="Linux")
##Copy the variables from settings
inputLoc <- settings$inputLoc
outputLoc <- settings$outputLoc
executable <- settings$executable
iniInput <- settings$iniInput
epc <- settings$epcInput
calibrationPar <- settings$calibrationPar
whereAmI<-getwd()
#############################################################
############################spinup run############################
##########################################################
##Sometimes a bug occure due to logfiles and controlfiles in the input loc directory
if(silent!=TRUE){
if(length(grep("(dayout$)|(log$)",list.files(inputLoc)))>0){
cat(" \n \n WARMING: there is a log or dayout file nearby the ini files, that may cause problemes. \n \n If you want to avoid that possible problemes, please copy the log or dayout files into a save place, and after do a cleanupMuso(), or delete these manually, or run the rungetMuso(), with the agressive=TRUE parameter \n \n")
}
}
if(aggressive==TRUE){
cleanupMuso(location=outputLoc, deep=TRUE)
}
##We change the working directory becase of the model, but we want to avoid sideeffects, so we save the current location and after that we will change everything to it.
## Set the working directory to the inputLoc temporary.
setwd(inputLoc)
##Run the model for the spinup run.
if(silent){#silenc mode
if(Linuxp){
#In this case, in linux machines
system(paste(executable,iniInput[1],"> /dev/null",sep=" "))
} else {
#In windows machines there is a show.output.on.console option
system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE)
}
} else {
system(paste(executable,iniInput[1],sep=" "))
}
logspinup<-list.files(outputLoc)[grep("log$",list.files(outputLoc))]#load the logfiles
if(length(logspinup)==0){
return("Modell Failure")#in that case the modell did not create even a logfile
}
if(length(logspinup)>1){
spincrash<-TRUE
} else {
if(identical(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1),character(0))){
spincrash<-TRUE
} else {
spincrash<-(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)!=1)
}
}
if(!spincrash){##If spinup did not crashed, run the normal run.
#####################################################################
###########################normal run#########################
#################################################################
##for the sake of safe we set the location again
setwd(inputLoc)
if(silent){
if(Linuxp){
system(paste(executable,iniInput[2],"> /dev/null",sep=" "))
} else {
system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE)
}
} else {
system(paste(executable,iniInput[2],sep=" "))
}
##read the output
switch(timee,
"d"=(Reva<-getdailyout(settings)),
"m"=(Reva<-getmonthlyout(settings)),
"y"=(Reva<-getyearlyout(settings))
)
}
logfiles <- list.files(outputLoc)[grep("log$",list.files(outputLoc))]#creating a vector for logfilenames
###############################################
#############LOG SECTION#######################
###############################################
perror<-as.numeric(as.vector(lapply(paste(outputLoc,logfiles,sep="/"),function(x) tail(readLines(x,-1),1)))) #vector of spinup and normalrun error
if((debugging=="stamplog")|(debugging==TRUE)){#If debugging option turned on
##If log or ERROR directory does not exists create it!
dirName<-paste(inputLoc,"LOG",sep="")
dirERROR<-paste(inputLoc,"ERROR",sep="")
if(!dir.exists(dirName)){
dir.create(dirName)
}
if(!dir.exists(dirERROR)){
dir.create(dirERROR)
}
}
##if errorsign is 1 there is error, if it is 0 everything ok
if(length(perror)>sum(perror)){
errorsign <- 1
} else {
if(spincrash){
errorsign <- 1
} else {
errorsign <- 0
}
}
if(keepEpc){#if keepepc option tured on
if(length(unique(dirname(epc)))>1){
print("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?")
} else {
epcdir <- dirname(epc[1])
WRONGEPC<-paste(inputLoc,"WRONGEPC",sep="")
EPCS<-paste(inputLoc,"EPCS",sep="")
if(!dir.exists(WRONGEPC)){
dir.create(WRONGEPC)
}
if(!dir.exists(EPCS)){
dir.create(EPCS)
}
epcfiles <- list.files(epcdir)[grep("epc$",list.files(epcdir))]
stampnum<-stamp(EPCS)
lapply(epcfiles,function (x) file.copy(from = paste(epcdir,"/",x,sep=""),to=paste(EPCS,"/",(stampnum+1),"-",x,sep="")))
if(errorsign==1){
lapply(epcfiles,function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",x,sep=""), to=WRONGEPC))
}
}
}
if(debugging=="stamplog"){
stampnum<-stamp(dirName)
if(inputLoc==outputLoc){
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
} else {
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
}
if(errorsign==1){
lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",(stampnum+1),"-",x,sep=""), to=dirERROR ))}
} else { if(debugging){
if(is.null(logfilename)){
if(inputLoc==outputLoc){
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName,"/", x, sep="")))
} else {
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName,"/", x, sep="")))
}
if(errorsign==1){
lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR))
}
} else {
if(inputLoc==outputLoc){#These are very ugly solutions for a string problem: inputLoc: "./", if outputLoc equalent of inputLoc, it ends with "/", the string manipulation can not handle this. The better solution is easy, but I dont have enough time(Roland Hollo's)
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",logfilename,"-",x,sep="")))
} else {
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",logfilename,"-",x,sep="")))
}
if(errorsign==1){
lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR))
}
}
}}
cleanupMuso(location=outputLoc)
if(errorsign==1){
return("Modell Failure")
}
if(timee=="d"){
colnames(Reva) <- unlist(settings$outputVars[[1]])
} else {
if(timee=="y")
colnames(Reva) <- unlist(settings$outputVars[[2]])
}
if(leapYear){
Reva <- corrigMuso(settings,Reva)
rownames(Reva) <- musoDate(settings$startYear, settings$numYears)
} else {
rownames(Reva) <- musoDate(settings$startYear, settings$numYears, corrigated=FALSE)
}
if(export!=FALSE){
setwd(whereAmI)
## switch(fextension(export),
## "csv"=(write.csv(Reva,export)),
## "xlsx"=(),
## "odt"=
## )
write.csv(Reva,export)
} else{
setwd(whereAmI)
return(Reva)}
}

View File

@ -0,0 +1,354 @@
#' setupMuso
#'
#' The setupMuso is fundamental for the Biome-BGCMuSo model related other functions like runMuso, spinupMuso, normalMuso, rungetMuso, as it sets the model's environment. The function reads the INI files from a given directory, analyzes them with error checking, and creates a data structure in R that contains the complete information content for the simulation.
#'
#' @author Roland HOLLOS
#' @param parallel Set this variable to TRUE if you would like to implement parallel execution of the model
#' @param executable This parameter stores the location (directory) of the model-executable file. In normal usage, you don't have to set this parameter, because the RBBGCMuso package always contains the latest model executable. In spite of this, if you would like to use this package for model development or just want to use different model version (for example for comparison), you will find this option useful
#' @param calibrationPar You might want to change some parameters in your EPC file before running the model. setupMuso offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8)
#' @param outputLoc With this parameter the user can specify the directory for the model output. The syntax is simple, for example: outputLoc="/place/of/the/outputs/" or outputLoc="C:/my_model_directory/". Note that this output directory is specified by the user within the INI file, which means that the outputLoc parameter overrides the INI settings if specified.
#' @param inputLoc Usually this is the root (or base) directory where the user stores the INI files for the model. If the working directory is set by the user, this parameter can be skipped.
#' @param metInput Via the metInput parameter the user can specify the location of the input meteorological files. By default the package reads this information from the INI files.
#' @param CO2Input Via the CO2Input parameter the user can specify the location of the CO2 data file. By default the package reads this information from the INI files.
#' @param plantInput Via the plantInput parameter, the user can specify the location of the the file that contains the planting information. By default the package reads this information from the INI files.
#' @param thinInput Via the thinInput parameter,the user can specify the location of the file that contains the thinning information. By default the package reads this information from the INI files.
#' @param mowInput Via the mowInput parameter, the user can specify the location of the file that contains the mowing (i.e. grass cutting) information. By default the package reads this information from the INI files.
#' @param grazInput Via the grazInput parameter, the user can specify the location of the file that contains the grazing information. By default the package reads this information from the INI files.
#' @param harvInput Via the harvInput parameter, the user can specify the location of the file that contains the harvesting information. By default the package reads this information from the INI files.
#' @param 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.
#' @param 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.
#' @param 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.
#' @param nitInput Via the nitInput parameter, the user can specify the location of the file that contains the nitrogen deposition data. By default the package reads this information from the INI files.
#' @param iniInput Via the iniInput parameter, the user can specify the location of the INI files. By default the package reads the INI files from the working directory.
#' @param epcInput Via the epcInput parameter, the user can specify the location of the EPC data file. By default the package reads this information from the INI files.
#' @param modelOutputs This parameter contains the list of the codes that defines the required model output variables. Check the Biome-BGCMuS website for the complete list of possible output variables at http://agromo.agrar.mta.hu/bbgc/download.html
#' @usage setupMuso(executable=NULL, parallel = F, calibrationPar =c(1),
#' outputLoc=NULL, inputLoc=NULL,
#' metInput=NULL, CO2Input=NULL,
#' plantInput=NULL, thinInput=NULL,
#' mowInput=NULL, grazInput=NULL,
#' harvInput=NULL, plougInput=NULL,
#' fertInput=NULL, irrInput=NULL,
#' nitInput=NULL, iniInput=NULL, epcInput=NULL)
#' @return The output is a the model settings list wich contains the following elements:
#' executable, calibrationPar, outputLoc, outputName, inputLoc, iniInput, metInput, epcInput,thinInput,CO2Input, mowInput, grazInput, harvInput, plougInput, fertInput,rrInput, nitInput, inputFiles, numData, startyear, numYears, outputVars
#' @export
setupMuso <- function(executable=NULL,
parallel = F,
calibrationPar =c(1),
outputLoc=NULL,
modelOutputs=NULL,
inputLoc=NULL,
metInput=NULL,
CO2Input=NULL,
plantInput=NULL,
thinInput=NULL,
mowInput=NULL,
grazInput=NULL,
harvInput=NULL,
plougInput=NULL,
fertInput=NULL,
irrInput=NULL,
nitInput=NULL,
iniInput=NULL,
epcInput=NULL,
mapData=NULL,
leapYear=FALSE,
version=6,
doCopy=TRUE
){
Linuxp <-(Sys.info()[1]=="Linux")
writep <- 0
# if(is.null(mapData)&version==4){
# mData <- mMapping4
# }
#
inputParser <- function(string,fileName,counter,value=TRUE){
unlist(strsplit(grep(string,fileName,value=TRUE, perl = TRUE),"[\ \t]", useBytes = TRUE))[counter]
}
# outMaker <- function(inputVar,grepString,filep){
# tempVar <- eval(parse(text=inputVar))
# if(is.null(tempVar)){
# writep <<- writep+1
# if(filep)
# {
# tempVar["spinup"] <- file.path(inputLoc,inputParser(string=grepString,fileName=iniFiles$spinup,counter=1,value=TRUE))
# tempVar["normal"] <- file.path(inputLoc,inputParser(string=grepString,fileName=iniFiles$normal,counter=1,value=TRUE))
# } else {
# tempVar["spinup"] <- inputParser(string=grepString,fileName=iniFiles$spinup,counter=1,value=TRUE)
# tempVar["normal"] <- inputParser(string=grepString,fileName=iniFiles$normal,counter=1,value=TRUE)
#
# }
#
# } else {
# iniFiles$spinup[grep(grepString,iniFiles$spinup)] <<- paste0(tempVar[1],"\t ",grepString)
#
# if(length(tempVar)==2){
# iniFiles$normal[grep(" grepString",iniFiles$normal)] <<- paste0(tempVar[2],"\t ",grepString)
# }
# }
# return(tempVar)
# }
if(is.null(inputLoc)){
inputLoc<- normalizePath("./")
} else{
inputLoc <- normalizePath(inputLoc)
}
#iniChangedp <- FALSE
if(is.null(iniInput)){
spinups<-grep("s.ini$",list.files(inputLoc),value=TRUE, perl = TRUE)
normals<-grep("n.ini$",list.files(inputLoc),value=TRUE, perl = TRUE)
if(length(spinups)==1){
iniInput[1] <- file.path(inputLoc,spinups)
} else {
iniInput[1] <- "no spinup"
# stop("There are multiple or no spinup ini files, please choose")
}
if(length(normals)==1){
iniInput[2]<-file.path(inputLoc,normals)
} else {stop("There are multiple or no normal ini files, please choose")}
}
##read the ini files for the further changes
iniFiles<-lapply(iniInput, function (x) readLines(x,-1))
iniFiles[[1]] <- gsub("\\\\","/", iniFiles[[1]], perl = TRUE) #replacing \ to /
iniFiles[[2]] <- gsub("\\\\","/", iniFiles[[2]], perl = TRUE) #replacing \ to /
names(iniFiles) <- c("spinup","normal")
# inputs <- lapply(1:nrow(grepHelper), function (x) {
#
# outMaker(grepHelper[x,1],grepHelper[x,2],grepHelper[x,3])
#
# })
# names(inputs) <- grepHelper$inputVar
## grepHelper is in sysdata.rda it is a table like this:
##
## inputVar string isFile
## 1 epcInput EPC file name TRUE
## 2 metInput met file name TRUE
## 3 CO2Input CO2 file TRUE
## 4 nitInput N-dep file TRUE
## 5 thinInput do THINNING FALSE
## 6 plantInput do PLANTING FALSE
## 7 mowInput do MOWING FALSE
## 8 grazInput do GRAZING FALSE
## 9 harvInput do HARVESTING FALSE
## 10 plougInput do PLOUGHING FALSE
## 11 fertInput do FERTILIZING FALSE
## 12 irrInput do IRRIGATION FALSE
# return(inputs) debug element
# if(is.null(mapData)){
#
outIndex<-grep("DAILY_OUTPUT",iniFiles[[2]], perl = TRUE)+1
numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][outIndex],"[\ \t]", useBytes = TRUE))[1])
dailyVarCodes<-tryCatch(iniFiles[[2]][(outIndex+1):(outIndex+numVar)],
error = function(e){
stop("Cannot read indexes of output variables from the normal ini file, please make sure you have not skiped a line after the flag: \"DAILY_OUTPUT\"")
})
dailyVarCodes<-unlist(lapply(dailyVarCodes, function(x) unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1]))
dailyVarnames<-unlist(lapply(dailyVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1])))
outIndex<-grep("ANNUAL_OUTPUT",iniFiles[[2]], perl = TRUE)+1
numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][outIndex],"[\ \t]", useBytes = TRUE))[1])
annualVarCodes<-iniFiles[[2]][(outIndex+1):(outIndex+numVar)]
annualVarCodes<-unlist(lapply(annualVarCodes, function(x) unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1]))
annualVarnames<-unlist(lapply(annualVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]", useBytes = TRUE))[1])))
outputVars<-list(dailyVarnames,annualVarnames)
# browser()
# } else {
#
# c<-grep("DAILY_OUTPUT",iniFiles[[2]])+1
# numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1])
# dailyVarCodes<-iniFiles[[2]][(c+1):(c+numVar)]
# dailyVarnames<-lapply(dailyVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1],mapData))
#
# c<-grep("ANNUAL_OUTPUT",iniFiles[[2]])+1
# numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1])
# annualVarCodes<-iniFiles[[2]][(c+1):(c+numVar)]
# annualVarnames<-lapply(annualVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1],mapData))
# outputVars<-list(dailyVarnames,annualVarnames)
#
#
#
# }
if(is.null(executable)){
if(Linuxp){
executable<-file.path(inputLoc,"muso")
} else {
executable<-file.path(inputLoc,"muso.exe")
}
} else {
if(doCopy){
file.copy(executable,inputLoc)
}
}
outputName <- character(2)
outputName[1] <- basename(unlist(strsplit(iniFiles[[1]][grep("OUTPUT_CONTROL",iniFiles[[1]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1])
outputName[2] <- basename(unlist(strsplit(iniFiles[[2]][grep("OUTPUT_CONTROL",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1])
## outputName <- unlist(strsplit(grep("output",grep("prefix",iniFiles[[2]],value=TRUE),value=TRUE),"[\ \t]"))[1]
##THIS IS AN UGLY SOLUTION, WHICH NEEDS AN UPGRADE!!! FiXED (2017.09.11)
## outputName <- unlist(strsplit(grep("prefix for output files",iniFiles[[2]],value=TRUE),"[\ \t]"))[1]
if(is.null(outputName)){
stop("I cannot find outputName in your default ini file \n Please make sure that the line wich contains the name also contains the prefix and the output keywords!")
}
## outputName<-unlist(read.table(iniInput[2],skip=93,nrows = 1))[1]
if(is.null(outputLoc)){
## outputLoc<-paste((rev(rev(unlist(strsplit(outputName,"/")))[-1])),collapse="/")
outputLoc <- dirname(unlist(strsplit(iniFiles[[2]][grep("OUTPUT_CONTROL",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1])
if(substr(outputLoc,start = 1,stop = 1)!="/"){
##if the outputName is not absolute path make it absolute
outputLoc <- file.path(inputLoc,outputLoc)
}
} else {
outputLoc <- normalizePath(outputLoc)
}
inputFiles<-c(iniInput,epcInput,metInput)
numData<-rep(NA,3)
numYears <- as.numeric(unlist(strsplit(iniFiles[[2]][grep("TIME_DEFINE",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1])
## numYears<-unlist(read.table(iniInput[2],skip = 14,nrows = 1)[1])
numValues <- as.numeric(unlist(strsplit(iniFiles[[2]][grep("DAILY_OUTPUT",iniFiles[[2]], perl = TRUE)+1],"[\ \t]", useBytes = TRUE))[1])
## numValues will be replaced to numVar
## numValues<-unlist(read.table(iniInput[2],skip=102,nrows = 1)[1])
startYear <- as.numeric(unlist(strsplit(iniFiles[[2]][grep("TIME_DEFINE",iniFiles[[2]], perl = TRUE)+2],"[\ \t]", useBytes = TRUE))[1])
numData[1] <- numValues * numYears * 365 # Have to corrigate leapyears
numData[2] <- numYears * numValues*12
numData[3] <- numYears * numValues
##Writing out changed ini-file
writeLines(iniFiles[[1]],iniInput[1])
writeLines(iniFiles[[2]],iniInput[2])
if(!is.null(modelOutputs)){
outVarChanges <- putOutVars(iniFile = iniInput[2],outputVars = modelOutputs, modifyOriginal = TRUE)
numData <- round(numDate*outVarChanges[[2]])
outputVars[[1]] <-outVarChanges[[1]]
}
suppressWarnings(file.remove(paste0(file.path(outputLoc,outputName[1]),".log")))
## I use file.path additionally because We do not know if outputLoc ends or not to "/"
suppressWarnings(file.remove(paste0(file.path(outputLoc,outputName[2]),".log")))
searchBellow <- function(inFile, key, stringP = TRUE, n=1, management = FALSE){
if(stringP){
unlist(strsplit(inFile[grep(key,inFile, perl=TRUE)+n],split = "\\s+", useBytes = TRUE))[1]
} else {
as.numeric(unlist(strsplit(inFile[grep(key,inFile,perl=TRUE)+n],split = "\\s+", useBytes = TRUE))[1])
}
}
normOutputFlags <- c(
daily=searchBellow(iniFiles[[2]], "OUTPUT_CONTROL",stringP=FALSE,n=2),
annual=searchBellow(iniFiles[[2]], "OUTPUT_CONTROL",stringP=FALSE,n=5))
if(normOutputFlags[1]!=1){
warning("You should set your daily output flag to 1 (binary) RBBRMuso work only with binary output...")
}
searchBellow(iniFiles[[2]], "OUTPUT_CONTROL",stringP=FALSE,n=5)
soilFile <- NULL
if(version >=6){
soilFiles <- tryCatch(sapply(iniFiles,function(x){(searchBellow(x,"SOIL_FILE"))}),error = function(e){""})
}
epcFiles <- tryCatch(sapply(iniFiles,function(x){(searchBellow(x,"EPC_FILE"))}),error = function(e){""})
metInput <- tryCatch(sapply(iniFiles,function(x){(searchBellow(x,"MET_INPUT"))}),error = function(e){""})
dailyOutputTable <- cbind.data.frame(seq_along(dailyVarCodes),dailyVarCodes,outputVars[[1]])
colnames(dailyOutputTable) <- c("index","code","name")
annualOutputTable <- cbind.data.frame(seq_along(annualVarCodes),annualVarCodes,outputVars[[2]])
colnames(annualOutputTable) <- c("index","code","name")
settings = list(executable = executable,
calibrationPar = calibrationPar,
outputLoc=outputLoc,
outputNames=outputName,
inputLoc=inputLoc,
iniInput=iniInput,
metInput=metInput,
epcInput=epcFiles,
# thinInput=inputs$thinInput,
# CO2Input=inputs$CO2Input,
# mowInput=inputs$mowInput,
# grazInput=inputs$grazInput,
# harvInput=inputs$harvInput,
# plougInput=inputs$plougInput,
# fertInput=inputs$fertInput,
# irrInput=inputs$irrInput,
# nitInput=inputs$nitInput,
inputFiles=inputFiles,
numData=numData,
startYear=startYear,
numYears=numYears,
outputVars=outputVars,
soilFile=soilFiles,
dailyVarCodes= gsub("\\s.*","",dailyVarCodes),
annualVarCodes = gsub("\\s.*","",annualVarCodes),
dailyOutputTable=dailyOutputTable,
annualOutputTable=annualOutputTable,
normOutputFlags=normOutputFlags
)
# if(getOption("RMuso_version")==6){
# manFile <- scan(iniInput[2],what="",n=1,skip=44,sep=" ") # HARDCODED -> UNTIL JSON VERSION
# mgm <- readLines(manFile)
# mgmConn <- file(manFile,open="r")
# manTypes <- c("planting","thinning","mowing","grazing","harvesting","ploughing","fertilizing","irrigating")
# mgmFiles <- rep("none",length(manTypes))
# if(scan(mgmConn,skip=3,n=1,what=integer())==1){
# mgmFiles[1] <- scan(mgmConn,skip=1,n=1,what="", sep = " ")
# }
# for(i in 2:length(mgmFiles)){
# if(scan(mgmConn,skip=2,n=1,what=integer())==1){
# mgmFiles[i] <- scan(mgmConn,skip=1,n=1,what="", sep =" " )
# } else {
# blackhole<-scan(mgmConn,skip =1, n=1,what="")
# }
# }
# names(mgmFiles) <- manTypes
# settings[["management"]] <- mgmFiles
# close(manConn)
# }
# if(writep!=nrow(grepHelper)){
# writeLines(iniFiles[[1]],iniInput[[1]])
# if(inputs$epcInput[1]!=inputs$epc$Input[2]){ #Change need here
# writeLines(iniFiles[[2]],iniInput[[2]])
# }
# }
suppressWarnings(dir.create(file.path(inputLoc,"bck")))
# sapply(iniFiles,epc)
return(settings)
}

View File

@ -0,0 +1,47 @@
## #' setupMuso6
## #'
## #' This is the setup function for MuSo version: 6
## #'
## #' @author Roland HOLLOS
## #' @param setupFile
## #' @export
## setupMuso6<- function(setupFile){
## }
## ini <- readLines("./hhs_apriori_MuSo6_normal.ini")
## flags <- c("MET_INPUT",
## "RESTART",
## "TIME_DEFINE",
## "CO2_CONTROL",
## "NDEP_CONTROL",
## "SITE",
## "SOILPROP_FILE",
## "EPC_FILE",
## "MANAGEMENT_FILE",
## "SIMULATION_CONTROL",
## "W_STATE",
## "CN_STATE",
## "CLIM_CHANGE",
## "CONDITIONAL_MANAGEMENT_STRATEGIES",
## "OUTPUT_CONTROL",
## "DAILY_OUTPUT",
## "ANNUAL_OUTPUT",
## "END_INIT")
## getSegments <- function(ini, flags){
## output <- list()
## flagIterator <- 1:(length(flags)-1)
## for(i in flagIterator){
## output[[flags[i]]] <- lapply(ini[(grep(flags[i],ini)+1):(grep(flags[i+1],ini)-2)], function(x){
## unlist(strsplit(x,split = "\\["))[1]
## })
## }
## output
## }
## getSegments(ini,flags)
## gsub("(.*\\[\\|)([a-zA-Z1-9_]*)","",ini)
## stringi::stri_trim_right("rexamine.com/", "\\[r\\]")
## stri_extract("asdfasdf [|Ezat|]",regex = "\\[\\|*\\]")
## lapply(ini,function(x) gsub("\\s","",(strsplit(x,split= "T]"))[[1]][2]))

View File

@ -0,0 +1,73 @@
#' getSoilDataFull
#'
#' This function collects soil data from a given restapi, de default is soilGrid
#'
#' @author Roland HOLLÓS
#' @name getSoilDataFull
#' @importFrom glue glue
#' @importFrom httr config with_config GET content
getSoilDataFull <- function(lat, lon, apiURL) {
if(missing(apiURL)){
apiURL <- "https://81.169.232.36"
}
apiString <- glue("{apiURL}/query?lon={lon}&lat={lat}")
soilREST <- #with_config(config(ssl_verifypeer=0L, ssl_verifyhost=0L),
GET(apiString) # ) # This is temporary solution ssl_verification wont bypass
content(soilREST)
}
#' createSoilFile
#'
#' This function collects soil data from a given restapi, de default is soilGrid
#'
#' @author Roland HOLLOS
#' @name createSoilFile
#' @importFrom glue glue
#' @importFrom stats approx
#' @importFrom magrittr '%>%'
#' @export
createSoilFile <- function(lat,lon,
outputFile="recent.soi",
method="constant",apiURL,
template=system.file("examples/hhs/hhs.soi",package="RBBGCMuso")) {
if(missing(apiURL)){
apiURL <- "https://rest.soilgrids.org/soilgrids/v2.0/properties"
}
outFile <- suppressWarnings(readLines(template))
outFile[1] <- sprintf("SOILPROP FILE - lat: %s, lon: %s, created in: %s",lat,lon,date())
musoCenters <- c(1.5,6.5,20.0,45.0,75.0,105.0,135.0,175.0,300.0,700.0)
# soilGridDepths <- c(0,5,15,30,60,100,200)
soilGridDepths <- c(2.5, 10, 22.5, 45, 80, 150)
Reduce(function(x,y){(y-x)/2+x},soilGridDepths,accumulate=TRUE)
rest<- getSoilDataFull(lat,lon, apiURL)
createMusoLayers <- function(values,depths=soilGridDepths,centers=musoCenters,intMethod=method){
approx(x=depths,y=values, xout = centers, method=intMethod,rule=2)$y %>%
paste(.,collapse="\t") %>% paste0(.," ")
}
soilDepth <- tryCatch(getMeanSoil(rest,"bdod")/100,error=function(e){stop("There is no data for the given coordinates")})
outFile[55] <- sprintf("%s (%%) percentage of sand by volume in rock free soil",
paste(createMusoLayers(getMeanSoil(rest,"sand")/10), collapse="\t"))
outFile[56] <- sprintf("%s (%%) percentage of silt by volume in rock free soil",
paste(createMusoLayers(getMeanSoil(rest,"silt")/10), collapse="\t"))
outFile[57] <- sprintf("%s (dimless) soil PH",
paste(createMusoLayers(getMeanSoil(rest,"phh2o")/10), collapse="\t"))
# outFile[58] <- sprintf("%s (%%) bulk density",paste(createMusoLayers(soilDepth),collapse="\t"))
writeLines(outFile,outputFile)
}
# createSoilFile(60,50)
getMeanSoil <- function(rest, name){
sapply(
rest$properties$layers[sapply(rest$properties$layers,function(x){
x$name == name
})][[1]]$depths,
function(s){
s$values$mean
}
)
}

View File

@ -0,0 +1,136 @@
#' Runs the Biome-BGCMuSo model in spinup phase (execution of normal phase is possible with normalMuso) with debugging features.
#'
#' This function runs the Biome-BGCMuSo model in spinup phase.
#'
#' @author Roland HOLLOS
#' @param settings RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.
#' @param debugging If debugging is set to TRUE, after model execution the function copies the Biome-BGCMuSo log file into a LOG directory to stores it for further processing. If debugging is set to STAMPLOG instead of TRUE, it concatenates a number before the logfile, which is one plus the maximum of those present in the LOG directory. In each case the log files will be saved.
#' @param keepEpc If keepEpc is set to TRUE, the function keeps the EPC file and stamps it, and then copies it to the EPCS directory. If debugging is set to TRUE, it copies the wrong EPC files to the wrong epc directory.
#' @param silent If you set the silent parameter to TRUE, all of the model's output normally written to the screen will be suppressed. This option can be useful to increase the speed of the model execution.
#' @param aggressive It deletes all previous model-outputs from previous model runs.
#' @param parameters |||| In the parameters variable you have set the row indices of the variables that you wish to change. In this parameter you can provide an exact value for them in a vector form like c(1,2,3,4)
#' @param logfilename If you would like to set a specific name for the logfiles you can set this via the logfilename parameter
#' @return No return, outputs are written to file
#' @usage spinupMuso(settings, parameters=NULL, debugging=FALSE,
#' logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE)
#' @export
spinupMuso <- function(settings=NULL, parameters=NULL, debugging=FALSE, logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE, fileToChange="epc"){
##########################################################################
###########################Set local variables########################
########################################################################
if(is.null(settings)){
settings <- setupMuso() #(:INSIDE: setupMuso.R)
}
# The software works on Linux or Windows, Mac is not implemented yet, so with this simple dichotomy we can determine wich system is running
Linuxp <-(Sys.info()[1]=="Linux")
##Copy the variables from settings for the sake of easy
inputLoc <- settings$inputLoc
outputLoc <- settings$outputLoc
outputNames <- settings$outputNames
executable <- settings$executable
iniInput <- settings$iniInput
epc <- settings$epcInput
calibrationPar <- settings$calibrationPar
## We want to minimize the number of sideeffects so we store the state to restore in the end.
whereAmI<-getwd()
#############################################################
############################spinup run############################
##########################################################
## obsolete feature, but there can be cases in wich this option is helpfull
if(aggressive==TRUE){
cleanupMuso(location=outputLoc,deep=TRUE)} #(:INSIDE: cleanup.R)
## If parameters given, use changemulline, else leave this steps
if(!is.null(parameters)){
switch(fileToChange,
"epc" = tryCatch(changemulline(filename = 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)
error = function (e) {stop("Cannot change the ini file")}),
"both" = (stop("This option is not implemented yet, please choose epc or ini"))
)
}
## Set the working directory to the inputLoc temporary.
setwd(inputLoc)
##Run the spinup modell
if(silent){#silenc mode
if(Linuxp){
#In this case, in linux machines
tryCatch(system(paste(executable,iniInput[1],"> /dev/null",sep=" ")),
error= function (e){stop("Cannot run the modell-check the executable!")})
} else {
#In windows machines there is a show.output.on.console option
tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE),
error= function (e){stop("Cannot run the modell-check the executable!")})
}} else {
system(paste(executable,iniInput[1],sep=" "))
}
###############################################
#############LOG SECTION#######################
###############################################
logspinup <- getLogs(outputLoc,outputNames,type="spinup") #(:INSIDE: assistantFunctions.R)
if(length(logspinup)==0){
if(keepEpc){
stampnum<-stamp(EPCS)
lapply(epc,function (x) file.copy(from = x ,to=paste(EPCS,"/",(stampnum+1),"-", basename(x),sep="")))
lapply(epc, function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",basename(x),sep=""), to=WRONGEPC))
setwd(whereAmI)
stop("Modell Failure")
}
setwd(whereAmI)
stop("Modell Failure") #in that case the modell did not create even a logfile
}
if(length(logspinup)>1){
spincrash<-TRUE
} else {
if(identical(tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1),character(0))){
spincrash<-TRUE
} else {
spincrash <- (tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)!=1)
}
}
dirName<-normalizePath(paste(inputLoc,"/LOG",sep=""))
dirERROR<-paste0(inputLoc,"/ERROR")
if(!dir.exists(dirName)){
dir.create(dirName)}
if(!dir.exists(dirERROR)){
dir.create(dirERROR)}
if(spincrash){
errorsign <- 1
} else {
errorsign <- 0}
if(debugging==TRUE){
stampAndDir(outputLoc=outputLoc,stampDir=dirName, names=logspinup, type="output") #(:INSIDE: assistantFunctions.R)
}
if(errorsign==1){
stop("Modell Failure")
}
}

View File

@ -0,0 +1,33 @@
#' This function returns only the starting numbers of a string
#'
#' This function returns only the starting numbers of a string
#' @author Roland Hollos
#' @keywords internal
numcut<-function(string){
#This function returns only the starting numbers of a string
unlist(strsplit(grep("^[0-9]",string,value = TRUE),"[aAzZ-]"))[1]
}
#' numcutall
#'
#' apply numcut for all elements of a string vector
#' @author Roland Hollos
#' @keywords internal
numcutall<-function(vector){
#numcall apply numcut for all elements of a string vector
as.numeric(unlist(apply(as.matrix(vector),1,numcut)))
}
#' It gives back a stamp wich is the maximum number of the output numcall
#'
#' It gives back a stamp wich is the maximum number of the output numcall
#' @author Roland Hollos
#' @keywords internal
stamp<-function(path="./"){
#It gives back a stamp wich is the maximum number of the output numcall
numbers<-numcutall(list.files(path))
if(length(numbers)==0){
return (0)} else {
return(max(numbers))}
}

File diff suppressed because one or more lines are too long

View File

@ -0,0 +1,190 @@
[
{"X": "1", "NAME": "yearday to start new growth", "INDEX": "9", "UNIT": "yday", "MIN": "0", "MAX": "364", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "2", "NAME": "yearday to end new growth", "INDEX": "10", "UNIT": "yday", "MIN": "0", "MAX": "364", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "3", "NAME": "transfer growth period as fraction of growing season", "INDEX": "11", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "4", "NAME": "litterfall as fraction of growing season", "INDEX": "12", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "5", "NAME": "base temperature", "INDEX": "13", "UNIT": "Celsius", "MIN": "0", "MAX": "12", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "6", "NAME": "minimum temperature for growth displayed on current day", "INDEX": "14", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "0", "GROUP": "1", "TYPE": "1"},
{"X": "7", "NAME": "optimal1 temperature for growth displayed on current day", "INDEX": "15", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "1", "GROUP": "1", "TYPE": "1"},
{"X": "8", "NAME": "optimal2 temperature for growth displayed on current day", "INDEX": "16", "UNIT": "Celsius", "MIN": "20", "MAX": "40", "DEPENDENCE": "2", "GROUP": "1", "TYPE": "1"},
{"X": "9", "NAME": "maxmimum temperature for growth displayed on current day", "INDEX": "17", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "3", "GROUP": "1", "TYPE": "1"},
{"X": "10", "NAME": "minimum temperature for carbon assimilation displayed on current day", "INDEX": "18", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "0", "GROUP": "2", "TYPE": "1"},
{"X": "11", "NAME": "optimal1 temperature for carbon assimilation displayed on current day", "INDEX": "19", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "1", "GROUP": "2", "TYPE": "1"},
{"X": "12", "NAME": "optimal2 temperature for carbon assimilation displayed on current day", "INDEX": "20", "UNIT": "Celsius", "MIN": "20", "MAX": "40", "DEPENDENCE": "2", "GROUP": "2", "TYPE": "1"},
{"X": "13", "NAME": "maxmimum temperature for carbon assimilation displayed on current day", "INDEX": "21", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "3", "GROUP": "2", "TYPE": "1"},
{"X": "14", "NAME": "annual leaf and fine root turnover fraction", "INDEX": "22", "UNIT": "1/yr", "MIN": "0.1", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "15", "NAME": "annual live wood turnover fraction", "INDEX": "23", "UNIT": "1/yr", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "16", "NAME": "annual fire mortality fraction", "INDEX": "24", "UNIT": "1/yr", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "17", "NAME": "whole-plant mortality paramter for vegetation period", "INDEX": "25", "UNIT": "1/vegper", "MIN": "0", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "18", "NAME": "C:N of leaves", "INDEX": "26", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "100", "DEPENDENCE": "0", "GROUP": "3", "TYPE": "1"},
{"X": "19", "NAME": "C:N of leaf litter", "INDEX": "27", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"},
{"X": "20", "NAME": "C:N of fine roots", "INDEX": "28", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"},
{"X": "21", "NAME": "C:N of fruit", "INDEX": "29", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"},
{"X": "22", "NAME": "C:N of softstem", "INDEX": "30", "UNIT": "kgC/kgN", "MIN": "10", "MAX": "60", "DEPENDENCE": "1", "GROUP": "3", "TYPE": "1"},
{"X": "23", "NAME": "C:N of live wood", "INDEX": "31", "UNIT": "kgC/kgN", "MIN": "50", "MAX": "100", "DEPENDENCE": "0", "GROUP": "4", "TYPE": "1"},
{"X": "24", "NAME": "C:N of dead wood", "INDEX": "32", "UNIT": "kgC/kgN", "MIN": "300", "MAX": "800", "DEPENDENCE": "1", "GROUP": "4", "TYPE": "1"},
{"X": "25", "NAME": "dry matter content of leaves", "INDEX": "33", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "26", "NAME": "dry matter content of leaf litter", "INDEX": "34", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "27", "NAME": "dry matter content of fine roots", "INDEX": "35", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "28", "NAME": "dry matter content of fruit", "INDEX": "36", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "29", "NAME": "dry matter content of softstem", "INDEX": "37", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "30", "NAME": "dry matter content of live wood", "INDEX": "38", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "31", "NAME": "dry matter content of dead wood", "INDEX": "39", "UNIT": "kgC/kgDM", "MIN": "0.2", "MAX": "0.6", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "32", "NAME": "leaf litter labile proportion", "INDEX": "40", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "5", "TYPE": "2"},
{"X": "33", "NAME": "leaf litter cellulose proportion", "INDEX": "41", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "5", "TYPE": "2"},
{"X": "34", "NAME": "fine root labile proportion", "INDEX": "42", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "6", "TYPE": "2"},
{"X": "35", "NAME": "fine root cellulose proportion", "INDEX": "43", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "6", "TYPE": "2"},
{"X": "36", "NAME": "fruit labile proportion", "INDEX": "44", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "7", "TYPE": "2"},
{"X": "37", "NAME": "fruit cellulose proportion", "INDEX": "45", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "7", "TYPE": "2"},
{"X": "38", "NAME": "softstem labile proportion", "INDEX": "46", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "8", "TYPE": "2"},
{"X": "39", "NAME": "softstem cellulose proportion", "INDEX": "47", "UNIT": "prop", "MIN": "0.1", "MAX": "0.6", "DEPENDENCE": "1", "GROUP": "8", "TYPE": "2"},
{"X": "40", "NAME": "dead wood cellulose proportion", "INDEX": "48", "UNIT": "prop", "MIN": "0.5", "MAX": "0.9", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "41", "NAME": "canopy water interception coefficient", "INDEX": "49", "UNIT": "1/LAI/d", "MIN": "0.01", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "42", "NAME": "canopy light extinction coefficient", "INDEX": "50", "UNIT": "dimless", "MIN": "0.2", "MAX": "0.8", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "43", "NAME": "potential radiation use efficiency", "INDEX": "51", "UNIT": "g/MJ", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "44", "NAME": "radiation parameter1 (Jiang et al.2015)", "INDEX": "52", "UNIT": "dimless", "MIN": "0.781", "MAX": "0.781", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "45", "NAME": "radiation parameter1 (Jiang et al.2015)", "INDEX": "53", "UNIT": "dimless", "MIN": "-13.596", "MAX": "-13.596", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "46", "NAME": "all-sided to projected leaf area ratio", "INDEX": "54", "UNIT": "dimless", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "47", "NAME": "ratio of shaded SLA:sunlit SLA", "INDEX": "55", "UNIT": "dimless", "MIN": "2", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "48", "NAME": "fraction of leaf N in Rubisco", "INDEX": "56", "UNIT": "dimless", "MIN": "0.01", "MAX": "0.2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "49", "NAME": "fraction of leaf N in PeP", "INDEX": "57", "UNIT": "dimless", "MIN": "0.0424", "MAX": "0.0424", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "50", "NAME": "maximum stomatal conductance", "INDEX": "58", "UNIT": "m/s", "MIN": "0.001", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "51", "NAME": "cuticular conductance", "INDEX": "59", "UNIT": "m/s", "MIN": "1E-05", "MAX": "0.0001", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "52", "NAME": "boundary layer conductance", "INDEX": "60", "UNIT": "m/s", "MIN": "0.01", "MAX": "0.09", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "53", "NAME": "maximum height of plant", "INDEX": "61", "UNIT": "m", "MIN": "0.1", "MAX": "10", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "54", "NAME": "stem weight corresponding to maximum height", "INDEX": "62", "UNIT": "kgC", "MIN": "0.1", "MAX": "100", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "55", "NAME": "plant height function shape parameter (slope)", "INDEX": "63", "UNIT": "dimless", "MIN": "0.5", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "56", "NAME": "maximum depth of rooting zone", "INDEX": "64", "UNIT": "m", "MIN": "0.1", "MAX": "10", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "57", "NAME": "root distribution parameter", "INDEX": "65", "UNIT": "prop", "MIN": "3.67", "MAX": "3.67", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "58", "NAME": "root weight corresponding to max root depth", "INDEX": "66", "UNIT": "kgC/m2", "MIN": "0.4", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "59", "NAME": "root depth function shape parameter (slope)", "INDEX": "67", "UNIT": "prop", "MIN": "0.5", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "60", "NAME": "root weight to rooth length conversion factor", "INDEX": "68", "UNIT": "m/kg", "MIN": "1000", "MAX": "1000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "61", "NAME": "growth resp per unit of C grown", "INDEX": "69", "UNIT": "prop", "MIN": "0.1", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "62", "NAME": "maintenance respiration in kgC/day per kg of tissue N", "INDEX": "70", "UNIT": "kgC/kgN/d", "MIN": "0.1", "MAX": "0.5", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "63", "NAME": "theoretical maximum prop. of non-structural and structural carbohydrates", "INDEX": "71", "UNIT": "dimless", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "64", "NAME": "prop. of non-structural carbohydrates available for maintanance resp", "INDEX": "72", "UNIT": "dimless", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "65", "NAME": "symbiotic+asymbiotic fixation of N", "INDEX": "73", "UNIT": "kgN/m2/yr", "MIN": "0", "MAX": "0.001", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "66", "NAME": "time delay for temperature in photosynthesis acclimation", "INDEX": "74", "UNIT": "day", "MIN": "0", "MAX": "50", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "67", "NAME": "critical VWCratio (prop. to FC-WP) in germination", "INDEX": "79", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "68", "NAME": "critical photoslow daylength", "INDEX": "81", "UNIT": "hour", "MIN": "14", "MAX": "18", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "69", "NAME": "slope of relative photoslow development rate", "INDEX": "82", "UNIT": "dimless", "MIN": "0.005", "MAX": "0.005", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "70", "NAME": "critical vernalization temperature 1", "INDEX": "84", "UNIT": "Celsius", "MIN": "-5", "MAX": "5", "DEPENDENCE": "0", "GROUP": "9", "TYPE": "1"},
{"X": "71", "NAME": "critical vernalization temperature 2", "INDEX": "85", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "1", "GROUP": "9", "TYPE": "1"},
{"X": "72", "NAME": "critical vernalization temperature 3", "INDEX": "86", "UNIT": "Celsius", "MIN": "5", "MAX": "15", "DEPENDENCE": "2", "GROUP": "9", "TYPE": "1"},
{"X": "73", "NAME": "critical vernalization temperature 4", "INDEX": "87", "UNIT": "Celsius", "MIN": "10", "MAX": "20", "DEPENDENCE": "3", "GROUP": "9", "TYPE": "1"},
{"X": "74", "NAME": "slope of relative vernalization development rate", "INDEX": "88", "UNIT": "dimless", "MIN": "0.04", "MAX": "0.04", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "75", "NAME": "required vernalization days (in vernalization development rate)", "INDEX": "89", "UNIT": "dimless", "MIN": "30", "MAX": "70", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "76", "NAME": "critical flowering heat stress temperature 1", "INDEX": "91", "UNIT": "Celsius", "MIN": "30", "MAX": "40", "DEPENDENCE": "0", "GROUP": "10", "TYPE": "1"},
{"X": "77", "NAME": "critical flowering heat stress temperature 2", "INDEX": "92", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "1", "GROUP": "10", "TYPE": "1"},
{"X": "78", "NAME": "theoretical maximum of flowering thermal stress mortality", "INDEX": "93", "UNIT": "prop", "MIN": "0", "MAX": "0.4", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "79", "NAME": "VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)", "INDEX": "96", "UNIT": "prop", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "80", "NAME": "VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)", "INDEX": "97", "UNIT": "prop", "MIN": "0.5", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "81", "NAME": "minimum of soil moisture limit2 multiplicator (full anoxic stress value)", "INDEX": "98", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "82", "NAME": "vapor pressure deficit: start of conductance reduction", "INDEX": "99", "UNIT": "Pa", "MIN": "500", "MAX": "1500", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "83", "NAME": "vapor pressure deficit: complete conductance reduction", "INDEX": "100", "UNIT": "Pa", "MIN": "1500", "MAX": "3500", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "84", "NAME": "maximum senescence mortality coefficient of aboveground plant material", "INDEX": "101", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "85", "NAME": "maximum senescence mortality coefficient of belowground plant material", "INDEX": "102", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "86", "NAME": "maximum senescence mortality coefficient of non-structured plant material", "INDEX": "103", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "87", "NAME": "lower limit extreme high temperature effect on senescence mortality", "INDEX": "104", "UNIT": "Celsius", "MIN": "30", "MAX": "40", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "88", "NAME": "upper limit extreme high temperature effect on senescence mortality", "INDEX": "105", "UNIT": "Celsius", "MIN": "30", "MAX": "50", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "89", "NAME": "turnover rate of wilted standing biomass to litter", "INDEX": "106", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "90", "NAME": "turnover rate of cut-down non-woody biomass to litter", "INDEX": "107", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "91", "NAME": "turnover rate of cut-down woody biomass to litter", "INDEX": "108", "UNIT": "prop", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "92", "NAME": "drought tolerance parameter (critical value of day since water stress)", "INDEX": "109", "UNIT": "n_day", "MIN": "0", "MAX": "100", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "93", "NAME": "crit. amount of snow limiting photosyn.", "INDEX": "112", "UNIT": "kg/m2", "MIN": "0", "MAX": "20", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "94", "NAME": "limit1 (under:full constrained) of HEATSUM index", "INDEX": "113", "UNIT": "Celsius", "MIN": "0", "MAX": "50", "DEPENDENCE": "0", "GROUP": "11", "TYPE": "1"},
{"X": "95", "NAME": "limit2 (above:unconstrained) of HEATSUM index", "INDEX": "114", "UNIT": "Celsius", "MIN": "0", "MAX": "100", "DEPENDENCE": "1", "GROUP": "11", "TYPE": "1"},
{"X": "96", "NAME": "limit1 (under:full constrained) of TMIN index", "INDEX": "115", "UNIT": "Celsius", "MIN": "-5", "MAX": "5", "DEPENDENCE": "0", "GROUP": "12", "TYPE": "1"},
{"X": "97", "NAME": "limit2 (above:unconstrained) of TMIN index", "INDEX": "116", "UNIT": "Celsius", "MIN": "0", "MAX": "10", "DEPENDENCE": "1", "GROUP": "12", "TYPE": "1"},
{"X": "98", "NAME": "limit1 (above:full constrained) of VPD index", "INDEX": "117", "UNIT": "Pa", "MIN": "2000", "MAX": "600", "DEPENDENCE": "0", "GROUP": "13", "TYPE": "1"},
{"X": "99", "NAME": "limit2 (under:unconstrained) of VPD index", "INDEX": "118", "UNIT": "Pa", "MIN": "500", "MAX": "1500", "DEPENDENCE": "1", "GROUP": "13", "TYPE": "1"},
{"X": "100", "NAME": "limit1 (under:full constrained) of DAYLENGTH index", "INDEX": "119", "UNIT": "s", "MIN": "0", "MAX": "0", "DEPENDENCE": "0", "GROUP": "14", "TYPE": "1"},
{"X": "101", "NAME": "limit2 (above:unconstrained) of DAYLENGTH index", "INDEX": "120", "UNIT": "s", "MIN": "0", "MAX": "0", "DEPENDENCE": "1", "GROUP": "14", "TYPE": "1"},
{"X": "102", "NAME": "moving average (to avoid the effects of extreme events)", "INDEX": "121", "UNIT": "n_day", "MIN": "2", "MAX": "20", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "103", "NAME": "GSI limit1 (greater that limit -> start of vegper)", "INDEX": "122", "UNIT": "dimless", "MIN": "0", "MAX": "0.2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "104", "NAME": "GSI limit2 (less that limit -> end of vegper)", "INDEX": "123", "UNIT": "dimless", "MIN": "0", "MAX": "0.1", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "105", "NAME": "length of phenophase (GDD)-0", "INDEX": "127.6", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "106", "NAME": "leaf ALLOCATION -0", "INDEX": "128.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "107", "NAME": "fine root ALLOCATION-0", "INDEX": "129.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "108", "NAME": "fruit ALLOCATION -0", "INDEX": "130.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "109", "NAME": "soft stem ALLOCATION-0", "INDEX": "131.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "110", "NAME": "live woody stem ALLOCATION -0", "INDEX": "132.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "111", "NAME": "dead woody stem ALLOCATION -0", "INDEX": "133.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "112", "NAME": "live coarse root ALLOCATION-0", "INDEX": "134.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "113", "NAME": "dead coarse root ALLOCATION -0", "INDEX": "135.6", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "15", "TYPE": "-3"},
{"X": "114", "NAME": "canopy average specific leaf area-0", "INDEX": "136.6", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "115", "NAME": "current growth proportion-0", "INDEX": "137.6", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "116", "NAME": "maximal lifetime of plant tissue-0", "INDEX": "138.6", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "105", "NAME": "length of phenophase (GDD)-1", "INDEX": "127.61", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "106", "NAME": "leaf ALLOCATION -1", "INDEX": "128.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "107", "NAME": "fine root ALLOCATION-1", "INDEX": "129.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "108", "NAME": "fruit ALLOCATION -1", "INDEX": "130.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "109", "NAME": "soft stem ALLOCATION-1", "INDEX": "131.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "110", "NAME": "live woody stem ALLOCATION -1", "INDEX": "132.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "111", "NAME": "dead woody stem ALLOCATION -1", "INDEX": "133.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "112", "NAME": "live coarse root ALLOCATION-1", "INDEX": "134.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "113", "NAME": "dead coarse root ALLOCATION -1", "INDEX": "135.61", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "16", "TYPE": "-3"},
{"X": "114", "NAME": "canopy average specific leaf area-1", "INDEX": "136.61", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "115", "NAME": "current growth proportion-1", "INDEX": "137.61", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "116", "NAME": "maximal lifetime of plant tissue-1", "INDEX": "138.61", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "105", "NAME": "length of phenophase (GDD)-2", "INDEX": "127.62", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "106", "NAME": "leaf ALLOCATION -2", "INDEX": "128.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "107", "NAME": "fine root ALLOCATION-2", "INDEX": "129.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "108", "NAME": "fruit ALLOCATION -2", "INDEX": "130.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "109", "NAME": "soft stem ALLOCATION-2", "INDEX": "131.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "110", "NAME": "live woody stem ALLOCATION -2", "INDEX": "132.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "111", "NAME": "dead woody stem ALLOCATION -2", "INDEX": "133.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "112", "NAME": "live coarse root ALLOCATION-2", "INDEX": "134.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "113", "NAME": "dead coarse root ALLOCATION -2", "INDEX": "135.62", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "17", "TYPE": "-3"},
{"X": "114", "NAME": "canopy average specific leaf area-2", "INDEX": "136.62", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "115", "NAME": "current growth proportion-2", "INDEX": "137.62", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "116", "NAME": "maximal lifetime of plant tissue-2", "INDEX": "138.62", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "105", "NAME": "length of phenophase (GDD)-3", "INDEX": "127.63", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "106", "NAME": "leaf ALLOCATION -3", "INDEX": "128.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "107", "NAME": "fine root ALLOCATION-3", "INDEX": "129.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "108", "NAME": "fruit ALLOCATION -3", "INDEX": "130.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "109", "NAME": "soft stem ALLOCATION-3", "INDEX": "131.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "110", "NAME": "live woody stem ALLOCATION -3", "INDEX": "132.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "111", "NAME": "dead woody stem ALLOCATION -3", "INDEX": "133.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "112", "NAME": "live coarse root ALLOCATION-3", "INDEX": "134.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "113", "NAME": "dead coarse root ALLOCATION -3", "INDEX": "135.63", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "18", "TYPE": "-3"},
{"X": "114", "NAME": "canopy average specific leaf area-3", "INDEX": "136.63", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "115", "NAME": "current growth proportion-3", "INDEX": "137.63", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "116", "NAME": "maximal lifetime of plant tissue-3", "INDEX": "138.63", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "105", "NAME": "length of phenophase (GDD)-4", "INDEX": "127.64", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "106", "NAME": "leaf ALLOCATION -4", "INDEX": "128.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "107", "NAME": "fine root ALLOCATION-4", "INDEX": "129.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "108", "NAME": "fruit ALLOCATION -4", "INDEX": "130.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "109", "NAME": "soft stem ALLOCATION-4", "INDEX": "131.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "110", "NAME": "live woody stem ALLOCATION -4", "INDEX": "132.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "111", "NAME": "dead woody stem ALLOCATION -4", "INDEX": "133.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "112", "NAME": "live coarse root ALLOCATION-4", "INDEX": "134.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "113", "NAME": "dead coarse root ALLOCATION -4", "INDEX": "135.64", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "19", "TYPE": "-3"},
{"X": "114", "NAME": "canopy average specific leaf area-4", "INDEX": "136.64", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "115", "NAME": "current growth proportion-4", "INDEX": "137.64", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "116", "NAME": "maximal lifetime of plant tissue-4", "INDEX": "138.64", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "105", "NAME": "length of phenophase (GDD)-5", "INDEX": "127.65", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "106", "NAME": "leaf ALLOCATION -5", "INDEX": "128.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "107", "NAME": "fine root ALLOCATION-5", "INDEX": "129.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "108", "NAME": "fruit ALLOCATION -5", "INDEX": "130.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "109", "NAME": "soft stem ALLOCATION-5", "INDEX": "131.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "110", "NAME": "live woody stem ALLOCATION -5", "INDEX": "132.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "111", "NAME": "dead woody stem ALLOCATION -5", "INDEX": "133.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "112", "NAME": "live coarse root ALLOCATION-5", "INDEX": "134.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "113", "NAME": "dead coarse root ALLOCATION -5", "INDEX": "135.65", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "20", "TYPE": "-3"},
{"X": "114", "NAME": "canopy average specific leaf area-5", "INDEX": "136.65", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "115", "NAME": "current growth proportion-5", "INDEX": "137.65", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "116", "NAME": "maximal lifetime of plant tissue-5", "INDEX": "138.65", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "105", "NAME": "length of phenophase (GDD)-6", "INDEX": "127.6", "UNIT": "Celsius", "MIN": "0", "MAX": "10000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "106", "NAME": "leaf ALLOCATION -6", "INDEX": "128.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "107", "NAME": "fine root ALLOCATION-6", "INDEX": "129.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "108", "NAME": "fruit ALLOCATION -6", "INDEX": "130.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "109", "NAME": "soft stem ALLOCATION-6", "INDEX": "131.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "110", "NAME": "live woody stem ALLOCATION -6", "INDEX": "132.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "111", "NAME": "dead woody stem ALLOCATION -6", "INDEX": "133.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "112", "NAME": "live coarse root ALLOCATION-6", "INDEX": "134.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "113", "NAME": "dead coarse root ALLOCATION -6", "INDEX": "135.66", "UNIT": "prop", "MIN": "0", "MAX": "1", "DEPENDENCE": "1", "GROUP": "21", "TYPE": "-3"},
{"X": "114", "NAME": "canopy average specific leaf area-6", "INDEX": "136.66", "UNIT": "m2/kg", "MIN": "0", "MAX": "2", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "115", "NAME": "current growth proportion-6", "INDEX": "137.66", "UNIT": "prop", "MIN": "0", "MAX": "0", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"},
{"X": "116", "NAME": "maximal lifetime of plant tissue-6", "INDEX": "138.66", "UNIT": "Celsius", "MIN": "1", "MAX": "20000", "DEPENDENCE": "NA", "GROUP": "0", "TYPE": "0"}
]

View File

@ -0,0 +1,18 @@
"child","parent","mod","name"
"wth","ini",1,"weather"
"endpoint","ini",1,"endpointIn"
"endpoint","ini",2,"endpointOut"
"txt","ini",1,"co2"
"txt","ini",2,"nitrogen"
"soi","ini",1,"soil"
"epc","ini",1,"startEpc"
"mgm","ini",1,"management"
"plt","mgm",1,"planting"
"thn","mgm",1,"thining"
"mow","mgm",1,"mowing"
"grz","mgm",1,"grazing"
"hrv","mgm",1,"harvest"
"cul","mgm",1,"cultivation"
"frz","mgm",1,"fertilization"
"irr","mgm",1,"irrigation"
"epc","plt",0,"plantEpc"
1 child parent mod name
2 wth ini 1 weather
3 endpoint ini 1 endpointIn
4 endpoint ini 2 endpointOut
5 txt ini 1 co2
6 txt ini 2 nitrogen
7 soi ini 1 soil
8 epc ini 1 startEpc
9 mgm ini 1 management
10 plt mgm 1 planting
11 thn mgm 1 thining
12 mow mgm 1 mowing
13 grz mgm 1 grazing
14 hrv mgm 1 harvest
15 cul mgm 1 cultivation
16 frz mgm 1 fertilization
17 irr mgm 1 irrigation
18 epc plt 0 plantEpc

File diff suppressed because one or more lines are too long

File diff suppressed because it is too large Load Diff

File diff suppressed because one or more lines are too long

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,7 @@
## ---- fig.show='hold'---------------------------------------------------------
plot(1:10)
plot(10:1)
## ---- echo=FALSE, results='asis'----------------------------------------------
knitr::kable(head(mtcars, 10))

View File

@ -0,0 +1,58 @@
---
title: "Vignette Title"
author: "Vignette Author"
date: "`r Sys.Date()`"
output: rmarkdown::html_vignette
vignette: >
%\VignetteIndexEntry{Vignette Title}
%\VignetteEngine{knitr::rmarkdown}
%\VignetteEncoding{UTF-8}
---
Vignettes are long form documentation commonly included in packages. Because they are part of the distribution of the package, they need to be as compact as possible. The `html_vignette` output type provides a custom style sheet (and tweaks some options) to ensure that the resulting html is as small as possible. The `html_vignette` format:
- Never uses retina figures
- Has a smaller default figure size
- Uses a custom CSS stylesheet instead of the default Twitter Bootstrap style
## Vignette Info
Note the various macros within the `vignette` section of the metadata block above. These are required in order to instruct R how to build the vignette. Note that you should change the `title` field and the `\VignetteIndexEntry` to match the title of your vignette.
## Styles
The `html_vignette` template includes a basic CSS theme. To override this theme you can specify your own CSS in the document metadata as follows:
output:
rmarkdown::html_vignette:
css: mystyles.css
## Figures
The figure sizes have been customised so that you can easily put two images side-by-side.
```{r, fig.show='hold'}
plot(1:10)
plot(10:1)
```
You can enable figure captions by `fig_caption: yes` in YAML:
output:
rmarkdown::html_vignette:
fig_caption: yes
Then you can use the chunk option `fig.cap = "Your figure caption."` in **knitr**.
## More Examples
You can write math expressions, e.g. $Y = X\beta + \epsilon$, footnotes^[A footnote here.], and tables, e.g. using `knitr::kable()`.
```{r, echo=FALSE, results='asis'}
knitr::kable(head(mtcars, 10))
```
Also a quote using `>`:
> "He who gives up [code] safety for [code] speed deserves neither."
([via](https://twitter.com/hadleywickham/status/504368538874703872))

File diff suppressed because one or more lines are too long

View File

@ -0,0 +1,119 @@
1900 296.10
1901 296.10
1902 296.50
1903 296.80
1904 297.20
1905 297.60
1906 298.10
1907 298.50
1908 298.90
1909 299.30
1910 299.70
1911 300.10
1912 300.40
1913 300.80
1914 301.10
1915 301.40
1916 301.70
1917 302.10
1918 302.40
1919 302.70
1920 303.00
1921 303.40
1922 303.80
1923 304.10
1924 304.50
1925 305.00
1926 305.40
1927 305.80
1928 306.30
1929 306.80
1930 307.20
1931 307.70
1932 308.20
1933 308.60
1934 309.00
1935 309.40
1936 309.80
1937 310.00
1938 310.20
1939 310.30
1940 310.40
1941 310.40
1942 310.30
1943 310.20
1944 310.10
1945 310.10
1946 310.10
1947 310.20
1948 310.30
1949 310.50
1950 310.70
1951 311.10
1952 311.50
1953 311.90
1954 312.40
1955 313.00
1956 313.60
1957 314.20
1958 314.90
1959 315.79
1960 316.61
1961 317.33
1962 318.08
1963 318.70
1964 319.36
1965 320.02
1966 321.09
1967 321.99
1968 322.93
1969 324.21
1970 325.24
1971 326.06
1972 327.18
1973 328.84
1974 329.73
1975 330.73
1976 331.83
1977 333.25
1978 334.60
1979 336.85
1980 338.69
1981 339.93
1982 341.13
1983 342.78
1984 344.42
1985 345.90
1986 347.15
1987 348.93
1988 351.48
1989 352.91
1990 354.19
1991 355.59
1992 356.37
1993 357.04
1994 358.88
1995 360.88
1996 362.64
1997 363.76
1998 366.63
1999 368.31
2000 369.48
2001 372.59
2002 374.37
2003 378.04
2004 380.88
2005 383.88
2006 385.64
2007 385.76
2008 386.13
2009 387.37
2010 389.85
2011 391.62
2012 393.82
2013 396.48
2014 398.61
2015 400.00
2016 401.00
2017 402.00
2018 404.00

View File

@ -0,0 +1,367 @@
yyyy mm dd NEE GPP TER LE flag
2012 1 1 0.440 0.284 0.724 0.030 0
2012 1 2 0.540 0.486 1.026 0.222 0
2012 1 3 0.716 0.313 1.030 0.002 0
2012 1 4 0.627 0.468 1.095 0.055 0
2012 1 5 0.868 0.080 0.948 0.061 0
2012 1 6 0.077 0.751 0.828 0.372 0
2012 1 7 0.396 0.394 0.791 0.219 0
2012 1 8 0.110 0.767 0.877 0.125 0
2012 1 9 0.239 0.771 1.010 0.182 0
2012 1 10 0.207 0.732 0.938 0.271 0
2012 1 11 0.115 1.043 1.158 0.173 0
2012 1 12 0.509 0.443 0.952 0.351 0
2012 1 13 0.245 0.694 0.940 0.294 0
2012 1 14 0.509 0.521 1.030 0.192 0
2012 1 15 0.516 0.521 1.037 0.120 0
2012 1 16 0.142 0.630 0.772 0.195 0
2012 1 17 0.423 0.333 0.756 0.172 0
2012 1 18 0.277 0.586 0.863 0.256 0
2012 1 19 0.609 0.264 0.873 0.179 0
2012 1 20 0.853 0.191 1.043 0.028 0
2012 1 21 1.004 0.345 1.349 0.240 0
2012 1 22 0.658 0.828 1.486 0.313 0
2012 1 23 0.339 0.739 1.078 0.153 0
2012 1 24 0.281 0.752 1.032 0.045 0
2012 1 25 0.275 0.612 0.886 0.234 0
2012 1 26 0.098 0.614 0.712 0.189 0
2012 1 27 0.065 0.526 0.591 0.198 0
2012 1 28 0.270 0.307 0.577 0.101 0
2012 1 29 0.180 0.327 0.507 0.062 0
2012 1 30 0.916 0.371 1.287 0.086 0
2012 1 31 0.462 0.159 0.621 0.119 0
2012 2 1 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 2 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 3 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 4 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 5 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 6 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 7 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 8 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 9 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 10 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 11 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 12 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 13 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 14 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 15 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 16 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 17 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 18 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 19 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 2 20 0.263 0.396 0.660 0.255 0
2012 2 21 0.517 0.294 0.811 0.450 0
2012 2 22 0.497 0.381 0.878 0.340 0
2012 2 23 0.593 0.362 0.955 0.254 0
2012 2 24 0.361 0.510 0.872 0.491 0
2012 2 25 1.043 0.667 1.710 0.435 0
2012 2 26 0.471 0.545 1.016 0.287 0
2012 2 27 0.208 0.616 0.825 0.416 0
2012 2 28 0.421 0.399 0.820 0.092 0
2012 2 29 1.095 0.905 2.000 0.336 0
2012 3 1 0.458 1.085 1.542 0.146 0
2012 3 2 1.019 1.193 2.212 0.515 0
2012 3 3 0.848 1.016 1.865 0.681 0
2012 3 4 0.043 1.019 1.063 0.478 0
2012 3 5 0.326 0.870 1.196 0.502 0
2012 3 6 0.478 0.837 1.315 0.495 0
2012 3 7 0.206 0.470 0.675 0.332 0
2012 3 8 0.117 0.888 1.005 0.400 0
2012 3 9 -0.025 1.098 1.074 0.476 0
2012 3 10 0.449 1.011 1.460 0.587 0
2012 3 11 1.073 0.594 1.667 0.219 0
2012 3 12 1.044 0.590 1.634 0.047 0
2012 3 13 0.517 1.387 1.904 0.408 0
2012 3 14 0.166 1.769 1.935 0.505 0
2012 3 15 0.412 1.703 2.115 0.599 0
2012 3 16 0.244 1.535 1.779 0.483 0
2012 3 17 0.908 1.756 2.664 0.687 0
2012 3 18 0.885 1.659 2.544 0.539 0
2012 3 19 -0.386 2.395 2.009 0.502 0
2012 3 20 -0.606 2.823 2.217 0.859 0
2012 3 21 0.268 2.692 2.960 0.995 0
2012 3 22 -0.066 2.926 2.861 0.886 0
2012 3 23 0.009 3.536 3.545 0.854 0
2012 3 24 0.148 3.509 3.658 0.906 0
2012 3 25 -0.373 4.010 3.638 1.150 0
2012 3 26 -0.715 3.039 2.325 0.854 0
2012 3 27 -1.472 4.040 2.568 1.404 0
2012 3 28 -1.693 4.342 2.649 1.060 0
2012 3 29 0.028 3.126 3.155 0.736 0
2012 3 30 0.353 2.246 2.598 0.348 0
2012 3 31 -1.879 5.469 3.589 1.439 0
2012 4 1 -2.075 3.925 1.849 0.868 0
2012 4 2 -1.823 3.726 1.903 0.912 0
2012 4 3 -1.644 4.712 3.068 1.198 0
2012 4 4 -1.513 5.074 3.562 1.154 0
2012 4 5 -1.560 5.514 3.954 1.246 0
2012 4 6 1.817 1.514 3.331 0.048 0
2012 4 7 2.102 1.280 3.382 1.149 0
2012 4 8 -1.261 4.121 2.861 1.043 0
2012 4 9 -0.849 3.436 2.586 1.254 0
2012 4 10 -1.403 4.031 2.628 1.119 0
2012 4 11 -2.714 5.045 2.331 0.973 0
2012 4 12 -0.814 3.435 2.621 0.371 0
2012 4 13 -1.430 5.563 4.133 1.196 0
2012 4 14 0.886 3.198 4.085 0.124 0
2012 4 15 -1.468 5.235 3.767 0.354 0
2012 4 16 -0.391 3.663 3.272 0.408 0
2012 4 17 -2.404 5.576 3.172 0.967 0
2012 4 18 -2.231 5.599 3.368 0.857 0
2012 4 19 -4.172 7.629 3.457 1.407 0
2012 4 20 -3.302 7.423 4.121 1.344 0
2012 4 21 -2.392 6.356 3.965 0.839 0
2012 4 22 -1.016 4.731 3.715 0.532 0
2012 4 23 -3.809 7.395 3.586 0.974 0
2012 4 24 -2.960 6.773 3.813 0.612 0
2012 4 25 -4.338 8.789 4.451 2.042 0
2012 4 26 -5.087 10.121 5.034 2.478 0
2012 4 27 -4.817 8.607 3.790 2.461 0
2012 4 28 -4.396 8.659 4.263 2.372 0
2012 4 29 -6.780 10.393 3.613 2.607 0
2012 4 30 -6.309 9.668 3.358 2.703 0
2012 5 1 -3.619 8.815 5.196 2.805 0
2012 5 2 -4.568 10.142 5.574 2.899 0
2012 5 3 -3.377 7.731 4.355 1.086 0
2012 5 4 -0.910 5.555 4.645 0.711 0
2012 5 5 -5.536 11.269 5.733 2.516 0
2012 5 6 -6.022 11.611 5.589 2.154 0
2012 5 7 -1.552 6.454 4.903 0.780 0
2012 5 8 -4.539 11.023 6.485 2.654 0
2012 5 9 -6.838 12.291 5.453 2.248 0
2012 5 10 -6.109 13.095 6.986 2.653 0
2012 5 11 -6.404 13.728 7.324 2.453 0
2012 5 12 -3.041 11.038 7.998 1.494 0
2012 5 13 -2.685 8.466 5.781 1.701 0
2012 5 14 -1.911 7.159 5.247 0.614 0
2012 5 15 -4.420 10.143 5.723 1.881 0
2012 5 16 -2.677 7.455 4.778 0.899 0
2012 5 17 -4.086 8.456 4.370 1.535 0
2012 5 18 -2.892 8.133 5.241 1.827 0
2012 5 19 -3.103 9.789 6.686 2.036 0
2012 5 20 -3.446 10.774 7.328 1.722 0
2012 5 21 -1.290 8.958 7.668 0.755 0
2012 5 22 2.787 3.587 6.373 1.697 0
2012 5 23 -0.447 9.872 9.425 1.763 0
2012 5 24 0.187 10.434 10.622 2.221 0
2012 5 25 -1.949 10.115 8.166 2.603 0
2012 5 26 0.660 5.055 5.715 1.618 0
2012 5 27 2.652 3.893 6.545 1.588 0
2012 5 28 1.376 4.117 5.492 0.978 0
2012 5 29 1.416 4.619 6.035 1.400 0
2012 5 30 2.294 4.686 6.981 1.480 0
2012 5 31 4.244 2.414 6.659 1.549 0
2012 6 1 5.654 1.717 7.371 1.859 0
2012 6 2 -0.535 6.426 5.891 0.618 0
2012 6 3 -2.344 10.030 7.686 2.302 0
2012 6 4 1.526 5.390 6.916 1.171 0
2012 6 5 3.911 2.762 6.673 1.908 0
2012 6 6 -2.767 7.480 4.713 1.747 0
2012 6 7 -0.002 5.994 5.993 2.189 0
2012 6 8 -1.293 8.200 6.907 2.516 0
2012 6 9 2.902 3.437 6.339 0.607 0
2012 6 10 1.859 5.307 7.167 1.120 0
2012 6 11 2.909 4.120 7.030 0.814 0
2012 6 12 1.635 7.776 9.411 0.162 0
2012 6 13 3.300 9.112 12.413 1.079 0
2012 6 14 -0.500 13.424 12.924 2.230 0
2012 6 15 -0.555 13.719 13.164 2.650 0
2012 6 16 -2.240 15.315 13.075 2.788 0
2012 6 17 -3.710 15.421 11.711 3.815 0
2012 6 18 -1.316 13.615 12.299 3.467 0
2012 6 19 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 6 20 0.835 9.146 9.981 2.682 0
2012 6 21 -3.757 11.764 8.007 2.801 0
2012 6 22 -3.178 9.991 6.813 1.756 0
2012 6 23 -2.973 11.667 8.695 2.479 0
2012 6 24 -1.681 8.276 6.595 2.378 0
2012 6 25 1.698 4.862 6.559 0.469 0
2012 6 26 -0.333 8.257 7.924 2.947 0
2012 6 27 -1.240 9.078 7.839 2.568 0
2012 6 28 -2.438 8.591 6.153 2.323 0
2012 6 29 -0.041 6.786 6.745 2.320 0
2012 6 30 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 1 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 2 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 3 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 4 -1.694 7.565 5.871 2.055 0
2012 7 5 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 6 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 7 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 8 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 7 9 0.081 8.633 8.714 1.883 0
2012 7 10 5.480 4.571 10.050 2.978 0
2012 7 11 3.540 6.345 9.885 2.251 0
2012 7 12 3.573 6.518 10.092 2.055 0
2012 7 13 0.738 6.337 7.074 0.663 0
2012 7 14 2.392 5.352 7.744 1.730 0
2012 7 15 2.621 3.246 5.867 0.517 0
2012 7 16 0.002 5.766 5.768 2.395 0
2012 7 17 2.181 4.233 6.414 2.290 0
2012 7 18 0.333 5.522 5.855 2.121 0
2012 7 19 2.896 4.745 7.641 1.881 0
2012 7 20 -4.409 12.188 7.779 2.913 0
2012 7 21 2.161 4.473 6.635 0.085 0
2012 7 22 -1.966 9.473 7.507 1.158 0
2012 7 23 -3.943 12.987 9.044 2.395 0
2012 7 24 -1.126 11.111 9.984 1.840 0
2012 7 25 0.630 9.271 9.901 1.197 0
2012 7 26 0.641 10.025 10.666 2.289 0
2012 7 27 -3.677 14.036 10.359 3.401 0
2012 7 28 4.881 6.944 11.825 2.951 0
2012 7 29 -0.567 10.221 9.654 2.393 0
2012 7 30 -5.159 13.376 8.217 2.932 0
2012 7 31 -1.854 11.970 10.116 2.514 0
2012 8 1 -2.916 12.214 9.298 3.764 0
2012 8 2 0.390 8.301 8.691 2.852 0
2012 8 3 -3.120 12.612 9.492 2.479 0
2012 8 4 -0.243 9.906 9.662 3.369 0
2012 8 5 0.921 7.809 8.730 2.621 0
2012 8 6 1.958 7.150 9.108 2.832 0
2012 8 7 -3.802 12.456 8.654 2.834 0
2012 8 8 -3.271 10.859 7.588 1.917 0
2012 8 9 -2.539 10.918 8.379 1.708 0
2012 8 10 -4.573 13.220 8.647 2.166 0
2012 8 11 -1.417 7.881 6.464 0.969 0
2012 8 12 -5.064 11.249 6.185 2.064 0
2012 8 13 -3.401 10.948 7.547 1.999 0
2012 8 14 -4.735 11.421 6.685 2.658 0
2012 8 15 -1.630 9.253 7.623 2.609 0
2012 8 16 -0.523 9.221 8.698 2.449 0
2012 8 17 1.732 5.620 7.352 1.526 0
2012 8 18 1.792 5.627 7.419 1.600 0
2012 8 19 1.106 5.309 6.415 1.804 0
2012 8 20 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 8 21 -1.427 6.966 5.539 1.564 0
2012 8 22 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 8 23 1.842 3.369 5.211 1.107 0
2012 8 24 -9999.000 -9999.000 -9999.000 -9999.000 1
2012 8 25 0.752 4.044 4.796 1.564 0
2012 8 26 3.442 2.638 6.080 0.522 0
2012 8 27 4.227 2.070 6.297 1.209 0
2012 8 28 2.774 2.543 5.317 0.935 0
2012 8 29 0.889 6.332 7.221 1.144 0
2012 8 30 1.106 5.600 6.705 0.831 0
2012 8 31 1.499 4.726 6.225 0.397 0
2012 9 1 5.480 0.607 6.087 0.086 0
2012 9 2 4.770 3.085 7.854 1.212 0
2012 9 3 1.925 4.683 6.608 1.032 0
2012 9 4 1.147 4.621 5.768 0.847 0
2012 9 5 0.741 4.361 5.102 1.092 0
2012 9 6 0.236 3.269 3.505 0.792 0
2012 9 7 0.763 2.721 3.484 0.940 0
2012 9 8 1.173 3.364 4.537 1.023 0
2012 9 9 0.653 4.112 4.765 1.027 0
2012 9 10 0.912 4.461 5.373 0.874 0
2012 9 11 1.132 4.765 5.898 0.767 0
2012 9 12 1.016 5.574 6.589 0.666 0
2012 9 13 4.085 0.392 4.477 0.011 0
2012 9 14 3.004 2.271 5.276 0.517 0
2012 9 15 2.511 3.204 5.715 0.893 0
2012 9 16 1.539 4.356 5.896 0.949 0
2012 9 17 1.364 4.156 5.520 1.255 0
2012 9 18 2.299 4.659 6.957 0.954 0
2012 9 19 0.491 5.345 5.836 0.542 0
2012 9 20 1.374 4.325 5.699 1.097 0
2012 9 21 0.522 3.115 3.637 0.972 0
2012 9 22 0.051 3.473 3.524 1.001 0
2012 9 23 -0.100 2.702 2.602 0.878 0
2012 9 24 0.966 2.419 3.385 0.719 0
2012 9 25 1.793 2.237 4.030 1.720 0
2012 9 26 1.756 2.586 4.342 1.772 0
2012 9 27 0.954 3.168 4.122 0.882 0
2012 9 28 0.857 3.393 4.250 1.065 0
2012 9 29 1.165 3.372 4.537 0.451 0
2012 9 30 -0.759 5.569 4.811 0.830 0
2012 10 1 0.207 4.616 4.823 0.919 0
2012 10 2 2.516 1.735 4.251 0.041 0
2012 10 3 -1.047 4.089 3.042 0.614 0
2012 10 4 -1.631 4.975 3.343 0.784 0
2012 10 5 -1.277 4.647 3.369 0.901 0
2012 10 6 -1.711 5.633 3.922 0.899 0
2012 10 7 -1.559 5.570 4.011 0.717 0
2012 10 8 -2.029 5.085 3.056 0.904 0
2012 10 9 -1.604 5.274 3.671 0.692 0
2012 10 10 0.803 1.903 2.705 0.122 0
2012 10 11 -2.131 4.498 2.367 0.456 0
2012 10 12 0.644 2.323 2.966 0.063 0
2012 10 13 0.037 2.745 2.783 0.162 0
2012 10 14 -1.170 4.054 2.884 0.115 0
2012 10 15 -2.453 5.964 3.511 0.608 0
2012 10 16 0.666 1.569 2.235 0.361 0
2012 10 17 -2.423 5.213 2.790 0.140 0
2012 10 18 -2.999 7.236 4.237 0.575 0
2012 10 19 -2.974 6.842 3.869 0.509 0
2012 10 20 -0.961 6.009 5.047 0.313 0
2012 10 21 -1.929 6.137 4.208 0.308 0
2012 10 22 -1.843 7.383 5.540 0.478 0
2012 10 23 0.129 4.387 4.516 0.030 0
2012 10 24 1.710 3.265 4.975 0.073 0
2012 10 25 1.606 3.260 4.866 0.060 0
2012 10 26 0.887 2.925 3.811 0.051 0
2012 10 27 -1.423 4.769 3.346 0.060 0
2012 10 28 0.073 2.014 2.088 0.099 0
2012 10 29 0.697 0.838 1.535 0.002 0
2012 10 30 -0.362 1.947 1.585 0.214 0
2012 10 31 -0.675 2.402 1.727 0.288 0
2012 11 1 0.985 0.571 1.556 0.159 0
2012 11 2 0.282 1.449 1.731 0.123 0
2012 11 3 -1.547 3.771 2.224 0.479 0
2012 11 4 -1.364 4.402 3.038 0.569 0
2012 11 5 1.604 0.670 2.273 0.159 0
2012 11 6 0.679 2.410 3.089 0.170 0
2012 11 7 -0.727 2.904 2.176 0.374 0
2012 11 8 -0.928 3.313 2.385 0.377 0
2012 11 9 -0.790 2.533 1.743 0.293 0
2012 11 10 -0.660 2.691 2.031 0.184 0
2012 11 11 -0.739 2.588 1.850 0.136 0
2012 11 12 2.039 0.224 2.263 0.002 0
2012 11 13 1.237 2.104 3.341 0.052 0
2012 11 14 0.073 2.379 2.452 0.243 0
2012 11 15 -1.381 3.138 1.757 0.207 0
2012 11 16 0.103 1.772 1.875 0.067 0
2012 11 17 -0.843 2.621 1.778 0.094 0
2012 11 18 0.383 1.353 1.736 0.017 0
2012 11 19 1.891 0.365 2.256 0.007 0
2012 11 20 0.456 1.504 1.960 0.027 0
2012 11 21 0.973 1.028 2.002 0.011 0
2012 11 22 1.407 0.499 1.905 0.014 0
2012 11 23 0.676 1.122 1.798 0.011 0
2012 11 24 -0.320 2.203 1.883 0.023 0
2012 11 25 0.519 1.067 1.586 0.024 0
2012 11 26 0.191 1.449 1.640 0.067 0
2012 11 27 -0.142 2.655 2.512 0.536 0
2012 11 28 -0.100 2.787 2.686 0.361 0
2012 11 29 -0.291 2.827 2.536 0.099 0
2012 11 30 1.480 0.791 2.271 0.216 0
2012 12 1 -0.573 1.355 0.782 0.104 0
2012 12 2 1.006 0.284 1.290 0.009 0
2012 12 3 0.518 1.285 1.803 0.211 0
2012 12 4 0.150 1.210 1.360 0.035 0
2012 12 5 0.435 1.623 2.058 0.033 0
2012 12 6 0.319 0.842 1.161 0.022 0
2012 12 7 0.430 0.904 1.334 0.080 0
2012 12 8 1.286 0.000 1.286 0.012 0
2012 12 9 0.610 0.205 0.815 0.104 0
2012 12 10 0.676 0.293 0.969 0.087 0
2012 12 11 0.656 0.223 0.878 0.034 0
2012 12 12 0.418 0.242 0.660 0.101 0
2012 12 13 0.494 0.000 0.494 0.042 0
2012 12 14 0.662 0.316 0.978 0.005 0
2012 12 15 0.458 0.707 1.164 0.006 0
2012 12 16 0.185 0.889 1.073 0.005 0
2012 12 17 0.743 0.345 1.088 0.044 0
2012 12 18 0.764 0.111 0.875 0.009 0
2012 12 19 0.554 0.677 1.231 0.044 0
2012 12 20 0.308 0.775 1.083 0.028 0
2012 12 21 0.439 0.496 0.934 0.044 0
2012 12 22 0.141 0.800 0.941 0.005 0
2012 12 23 0.146 0.846 0.992 0.044 0
2012 12 24 -0.763 1.761 0.999 0.066 0
2012 12 25 0.390 1.345 1.735 0.131 0
2012 12 26 1.101 0.369 1.470 0.015 0
2012 12 27 -0.462 1.742 1.280 0.048 0
2012 12 28 0.525 0.520 1.045 0.044 0
2012 12 29 -0.086 0.827 0.740 0.060 0
2012 12 30 -0.044 0.648 0.604 0.056 0
2012 12 31 -0.040 0.731 0.692 0.092 0

View File

@ -0,0 +1,119 @@
1900 0.0003911
1901 0.0003922
1902 0.0003952
1903 0.0003982
1904 0.0004012
1905 0.0004043
1906 0.0004073
1907 0.0004103
1908 0.0004133
1909 0.0004164
1910 0.0004224
1911 0.0004267
1912 0.0004310
1913 0.0004353
1914 0.0004396
1915 0.0004439
1916 0.0004482
1917 0.0004525
1918 0.0004568
1919 0.0004611
1920 0.0004697
1921 0.0004741
1922 0.0004786
1923 0.0004830
1924 0.0004875
1925 0.0004919
1926 0.0004964
1927 0.0005008
1928 0.0005053
1929 0.0005097
1930 0.0005186
1931 0.0005214
1932 0.0005243
1933 0.0005271
1934 0.0005299
1935 0.0005327
1936 0.0005356
1937 0.0005384
1938 0.0005412
1939 0.0005440
1940 0.0005497
1941 0.0005600
1942 0.0005703
1943 0.0005806
1944 0.0005909
1945 0.0006013
1946 0.0006116
1947 0.0006219
1948 0.0006322
1949 0.0006425
1950 0.0006632
1951 0.0006775
1952 0.0006919
1953 0.0007063
1954 0.0007207
1955 0.0007350
1956 0.0007494
1957 0.0007638
1958 0.0007782
1959 0.0007925
1960 0.0008213
1961 0.0008407
1962 0.0008601
1963 0.0008795
1964 0.0008989
1965 0.0009183
1966 0.0009378
1967 0.0009572
1968 0.0009766
1969 0.0009960
1970 0.0010348
1971 0.0010591
1972 0.0010465
1973 0.0010524
1974 0.0010582
1975 0.0010641
1976 0.0010699
1977 0.0010758
1978 0.0010816
1979 0.0010875
1980 0.0010933
1981 0.0010992
1982 0.0011050
1983 0.0011109
1984 0.0011167
1985 0.0011226
1986 0.0011284
1987 0.0011343
1988 0.0011401
1989 0.0011460
1990 0.0011519
1991 0.0011577
1992 0.0011636
1993 0.0011694
1994 0.0011753
1995 0.0011811
1996 0.0011870
1997 0.0011928
1998 0.0011987
1999 0.0012045
2000 0.0012104
2001 0.0012239
2002 0.0012347
2003 0.0012654
2004 0.0012762
2005 0.0012870
2006 0.0012977
2007 0.0013085
2008 0.0013192
2009 0.0013200
2010 0.0013407
2011 0.0013515
2012 0.0013722
2013 0.0013830
2014 0.0013938
2015 0.0014010
2016 0.0014020
2017 0.0014040
2018 0.0014050

View File

@ -1,139 +1,139 @@
ECOPHYS FILE - C3 grass muso6
----------------------------------------------------------------------------------------
FLAGS
0 (flag) biome type flag (1 = WOODY 0 = NON-WOODY)
0 (flag) woody type flag (1 = EVERGREEN 0 = DECIDUOUS)
1 (flag) photosyn. type flag (1 = C3 PSN 0 = C4 PSN)
----------------------------------------------------------------------------------------
PLANT FUNCTIONING PARAMETERS
0 (yday) yearday to start new growth (when phenology flag = 0)
364 (yday) yearday to end litterfall (when phenology flag = 0)
0.5 (prop.) transfer growth period as fraction of growing season (when transferGDD_flag = 0)
0.5 (prop.) litterfall as fraction of growing season (when transferGDD_flag = 0)
0 (Celsius) base temperature
-9999 (Celsius) minimum temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) optimal1 temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) optimal2 temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) maxmimum temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) minimum temperature for carbon assimilation displayed on current day (-9999: no limitation)
-9999 (Celsius) optimal1 temperature for carbon assimilation displayed on current day (-9999: no limitation)
-9999 (Celsius) optimal2 temperature for carbon assimilation displayed on current day (-9999: no limitation)
-9999 (Celsius) maxmimum temperature for carbon assimilation displayed on current day (-9999: no limitation)
1.0 (1/yr) annual leaf and fine root turnover fraction
0.00 (1/yr) annual live wood turnover fraction
0.03 (1/yr) annual fire mortality fraction
0.01 (1/vegper) whole-plant mortality fraction in vegetation period
36.6 (kgC/kgN) C:N of leaves
45.0 (kgC/kgN) C:N of leaf litter, after retranslocation
50.0 (kgC/kgN) C:N of fine roots
36.6 *(kgC/kgN) C:N of fruit
36.6 (kgC/kgN) C:N of soft stem
0.0 *(kgC/kgN) C:N of live wood
0.0 *(kgC/kgN) C:N of dead wood
0.4 (kgC/kgDM) dry matter carbon content of leaves
0.4 (kgC/kgDM) dry matter carbon content of leaf litter
0.4 (kgC/kgDM) dry matter carbon content of fine roots
0.4 *(kgC/kgDM) dry matter carbon content of fruit
0.4 (kgC/kgDM) dry matter carbon content of soft stem
0.4 *(kgC/kgDM) dry matter carbon content of live wood
0.4 *(kgC/kgDM) dry matter carbon content of dead wood
0.68 (DIM) leaf litter labile proportion
0.23 (DIM) leaf litter cellulose proportion
0.34 (DIM) fine root labile proportion
0.44 (DIM) fine root cellulose proportion
0.68 *(DIM) fruit litter labile proportion
0.23 *(DIM) fruit litter cellulose proportion
0.68 (DIM) soft stem litter labile proportion
0.23 (DIM) soft stem litter cellulose proportion
0.00 *(DIM) dead wood cellulose proportion
0.01 (1/LAI/d) canopy water interception coefficient
0.63 (DIM) canopy light extinction coefficient
2.0 (g/MJ) potential radiation use efficiency
0.781 (DIM) radiation parameter1 (Jiang et al.2015)
-13.596 (DIM) radiation parameter2 (Jiang et al.2015)
2.0 (DIM) all-sided to projected leaf area ratio
2.0 (DIM) ratio of shaded SLA:sunlit SLA
0.14 (DIM) fraction of leaf N in Rubisco
0.03 (DIM) fraction of leaf N in PEP Carboxylase
0.004 (m/s) maximum stomatal conductance (projected area basis)
0.00006 (m/s) cuticular conductance (projected area basis)
0.04 (m/s) boundary layer conductance (projected area basis)
1.5 (m) maximum height of plant
0.8 (kgC) stem weight corresponding to maximum height
0.5 (dimless) plant height function shape parameter (slope)
4.0 (m) maximum depth of rooting zone
3.67 (DIM) root distribution parameter
0.4 (kgC) root weight corresponding to max root depth
0.5 (dimless) root depth function shape parameter (slope)
1000 (m/kg) root weight to root length conversion factor
0.3 (prop.) growth resp per unit of C grown
0.218 (kgC/kgN/d) maintenance respiration in kgC/day per kg of tissue N
0.1 (DIM) theoretical maximum prop. of non-structural and structural carbohydrates
0.24 (DIM) prop. of non-structural carbohydrates available for maintanance respiration
0.02 (kgN/m2/yr) symbiotic+asymbiotic fixation of N
0 (day) time delay for temperature in photosynthesis acclimation
----------------------------------------------------------------------------------------
CROP SPECIFIC PARAMETERS
0 (DIM) number of phenophase of germination (from 1 to 7; 0: NO specific)
0 (DIM) number of phenophase of emergence (from 1 to 7; 0: NO specific)
0.5 (prop.) critical VWCratio (prop. to FC-WP) in germination
0 (DIM) number of phenophase of photoperiodic slowing effect (from 1 to 7; 0: NO effect)
20 (hour) critical photoslow daylength
0.005 (DIM) slope of relative photoslow development rate
0 (DIM) number of phenophase of vernalization (from 1 to 7; 0: NO effect)
0 (Celsius) critical vernalization temperature 1
5 (Celsius) critical vernalization temperature 2
8 (Celsius) critical vernalization temperature 3
15 (Celsius) critical vernalization temperature 4
0.04 (DIM) slope of relative vernalization development rate
50 (n) required vernalization days (in vernalization development rate)
0 (DIM) number of flowering phenophase (from 1 to 7;0: NO effect)
35 (Celsius) critical flowering heat stress temperature 1
40 (Celsius) critical flowering heat stress temperature 2
0.2 (prop.) theoretical maximum of flowering thermal stress mortality parameter
----------------------------------------------------------------------------------------
STRESS AND SENESCENCE PARAMETERS
0.98 (prop) VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)
0.7 (prop) VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)
0.4 (prop) minimum of soil moisture limit2 multiplicator (full anoxic stress value)
1000 (Pa) vapor pressure deficit: start of conductance reduction
4000 (Pa) vapor pressure deficit: complete conductance reduction
0.003 (prop.) maximum senescence mortality coefficient of aboveground plant material
0.001 (prop.) maximum senescence mortality coefficient of belowground plant material
0.0 (prop.) maximum senescence mortality coefficient of non-structured plant material
35 (Celsius) lower limit extreme high temperature effect on senescence mortality
40 (Celsius) upper limit extreme high temperature effect on senescence mortality
0.01 (prop.) turnover rate of wilted standing biomass to litter
0.047 (prop.) turnover rate of non-woody cut-down biomass to litter
0.01 (prop.) turnover rate of woody cut-down biomass to litter
17 (nday) drought tolerance parameter (critical value of DSWS)
0.3 (prop) soil water deficit effect on photosynthesis downregulation
----------------------------------------------------------------------------------------
GROWING SEASON PARAMETERS
5 (kg/m2) crit. amount of snow limiting photosyn.
20 (Celsius) limit1 (under:full constrained) of HEATSUM index
60 (Celsius) limit2 (above:unconstrained) of HEATSUM index
0 (Celsius) limit1 (under:full constrained) of TMIN index
5 (Celsius) limit2 (above:unconstrained) of TMIN index
4000 (Pa) limit1 (above:full constrained) of VPD index
1000 (Pa) limit2 (under:unconstrained) of VPD index
0 (s) limit1 (under:full constrained) of DAYLENGTH index
0 (s) limit2 (above:unconstrained) of DAYLENGTH index
10 (day) moving average (to avoid the effects of extreme events)
0.10 (dimless) GSI limit1 (greater that limit -> start of vegper)
0.01 (dimless) GSI limit2 (less that limit -> end of vegper)
----------------------------------------------------------------------------------------
PHENOLOGICAL (ALLOCATION) PARAMETERS (7 phenological phases)
phase1 phase2 phase3 phase4 phase5 phase6 phase7 (text) name of the phenophase
5000 200 500 200 400 200 100 (Celsius) length of phenophase (GDD)
0.3 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) leaf ALLOCATION
0.5 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) fine root ALLOCATION
0.0 0.0 0.0 0.0 0.0 0.0 0.0 (ratio) fruit ALLOCATION
0.2 0.2 0.2 0.2 0.2 0.2 0.2 (ratio) soft stem ALLOCATION
0 0 0 0 0 0 0 (ratio) live woody stem ALLOCATION
0 0 0 0 0 0 0 (ratio) dead woody stem ALLOCATION
0 0 0 0 0 0 0 (ratio) live coarse root ALLOCATION
0 0 0 0 0 0 0 (ratio) dead coarse root ALLOCATION
49 49 49 49 49 49 49 (m2/kgC) canopy average specific leaf area (projected area basis)
0.37 0.37 0.37 0.37 0.37 0.37 0.37 (prop.) current growth proportion
10000 10000 10000 10000 10000 10000 10000 (Celsius) maximal lifetime of plant tissue
ECOPHYS FILE - C3 grass muso6
----------------------------------------------------------------------------------------
FLAGS
0 (flag) biome type flag (1 = WOODY 0 = NON-WOODY)
0 (flag) woody type flag (1 = EVERGREEN 0 = DECIDUOUS)
1 (flag) photosyn. type flag (1 = C3 PSN 0 = C4 PSN)
----------------------------------------------------------------------------------------
PLANT FUNCTIONING PARAMETERS
0 (yday) yearday to start new growth (when phenology flag = 0)
364 (yday) yearday to end litterfall (when phenology flag = 0)
0.5 (prop.) transfer growth period as fraction of growing season (when transferGDD_flag = 0)
0.5 (prop.) litterfall as fraction of growing season (when transferGDD_flag = 0)
0 (Celsius) base temperature
-9999 (Celsius) minimum temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) optimal1 temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) optimal2 temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) maxmimum temperature for growth displayed on current day (-9999: no T-dependence of allocation)
-9999 (Celsius) minimum temperature for carbon assimilation displayed on current day (-9999: no limitation)
-9999 (Celsius) optimal1 temperature for carbon assimilation displayed on current day (-9999: no limitation)
-9999 (Celsius) optimal2 temperature for carbon assimilation displayed on current day (-9999: no limitation)
-9999 (Celsius) maxmimum temperature for carbon assimilation displayed on current day (-9999: no limitation)
1.0 (1/yr) annual leaf and fine root turnover fraction
0.00 (1/yr) annual live wood turnover fraction
0.03 (1/yr) annual fire mortality fraction
0.01 (1/vegper) whole-plant mortality fraction in vegetation period
36.6 (kgC/kgN) C:N of leaves
45.0 (kgC/kgN) C:N of leaf litter, after retranslocation
50.0 (kgC/kgN) C:N of fine roots
36.6 *(kgC/kgN) C:N of fruit
36.6 (kgC/kgN) C:N of soft stem
0.0 *(kgC/kgN) C:N of live wood
0.0 *(kgC/kgN) C:N of dead wood
0.4 (kgC/kgDM) dry matter carbon content of leaves
0.4 (kgC/kgDM) dry matter carbon content of leaf litter
0.4 (kgC/kgDM) dry matter carbon content of fine roots
0.4 *(kgC/kgDM) dry matter carbon content of fruit
0.4 (kgC/kgDM) dry matter carbon content of soft stem
0.4 *(kgC/kgDM) dry matter carbon content of live wood
0.4 *(kgC/kgDM) dry matter carbon content of dead wood
0.68 (DIM) leaf litter labile proportion
0.23 (DIM) leaf litter cellulose proportion
0.34 (DIM) fine root labile proportion
0.44 (DIM) fine root cellulose proportion
0.68 *(DIM) fruit litter labile proportion
0.23 *(DIM) fruit litter cellulose proportion
0.68 (DIM) soft stem litter labile proportion
0.23 (DIM) soft stem litter cellulose proportion
0.00 *(DIM) dead wood cellulose proportion
0.01 (1/LAI/d) canopy water interception coefficient
0.63 (DIM) canopy light extinction coefficient
2.0 (g/MJ) potential radiation use efficiency
0.781 (DIM) radiation parameter1 (Jiang et al.2015)
-13.596 (DIM) radiation parameter2 (Jiang et al.2015)
2.0 (DIM) all-sided to projected leaf area ratio
2.0 (DIM) ratio of shaded SLA:sunlit SLA
0.14 (DIM) fraction of leaf N in Rubisco
0.03 (DIM) fraction of leaf N in PEP Carboxylase
0.004 (m/s) maximum stomatal conductance (projected area basis)
0.00006 (m/s) cuticular conductance (projected area basis)
0.04 (m/s) boundary layer conductance (projected area basis)
1.5 (m) maximum height of plant
0.8 (kgC) stem weight corresponding to maximum height
0.5 (dimless) plant height function shape parameter (slope)
4.0 (m) maximum depth of rooting zone
3.67 (DIM) root distribution parameter
0.4 (kgC) root weight corresponding to max root depth
0.5 (dimless) root depth function shape parameter (slope)
1000 (m/kg) root weight to root length conversion factor
0.3 (prop.) growth resp per unit of C grown
0.218 (kgC/kgN/d) maintenance respiration in kgC/day per kg of tissue N
0.1 (DIM) theoretical maximum prop. of non-structural and structural carbohydrates
0.24 (DIM) prop. of non-structural carbohydrates available for maintanance respiration
0.02 (kgN/m2/yr) symbiotic+asymbiotic fixation of N
0 (day) time delay for temperature in photosynthesis acclimation
----------------------------------------------------------------------------------------
CROP SPECIFIC PARAMETERS
0 (DIM) number of phenophase of germination (from 1 to 7; 0: NO specific)
0 (DIM) number of phenophase of emergence (from 1 to 7; 0: NO specific)
0.5 (prop.) critical VWCratio (prop. to FC-WP) in germination
0 (DIM) number of phenophase of photoperiodic slowing effect (from 1 to 7; 0: NO effect)
20 (hour) critical photoslow daylength
0.005 (DIM) slope of relative photoslow development rate
0 (DIM) number of phenophase of vernalization (from 1 to 7; 0: NO effect)
0 (Celsius) critical vernalization temperature 1
5 (Celsius) critical vernalization temperature 2
8 (Celsius) critical vernalization temperature 3
15 (Celsius) critical vernalization temperature 4
0.04 (DIM) slope of relative vernalization development rate
50 (n) required vernalization days (in vernalization development rate)
0 (DIM) number of flowering phenophase (from 1 to 7;0: NO effect)
35 (Celsius) critical flowering heat stress temperature 1
40 (Celsius) critical flowering heat stress temperature 2
0.2 (prop.) theoretical maximum of flowering thermal stress mortality parameter
----------------------------------------------------------------------------------------
STRESS AND SENESCENCE PARAMETERS
0.98 (prop) VWC ratio to calc. soil moisture limit 1 (prop. to FC-WP)
0.7 (prop) VWC ratio to calc. soil moisture limit 2 (prop. to SAT-FC)
0.4 (prop) minimum of soil moisture limit2 multiplicator (full anoxic stress value)
1000 (Pa) vapor pressure deficit: start of conductance reduction
4000 (Pa) vapor pressure deficit: complete conductance reduction
0.003 (prop.) maximum senescence mortality coefficient of aboveground plant material
0.001 (prop.) maximum senescence mortality coefficient of belowground plant material
0.0 (prop.) maximum senescence mortality coefficient of non-structured plant material
35 (Celsius) lower limit extreme high temperature effect on senescence mortality
40 (Celsius) upper limit extreme high temperature effect on senescence mortality
0.01 (prop.) turnover rate of wilted standing biomass to litter
0.047 (prop.) turnover rate of non-woody cut-down biomass to litter
0.01 (prop.) turnover rate of woody cut-down biomass to litter
17 (nday) drought tolerance parameter (critical value of DSWS)
0.3 (prop) soil water deficit effect on photosynthesis downregulation
----------------------------------------------------------------------------------------
GROWING SEASON PARAMETERS
5 (kg/m2) crit. amount of snow limiting photosyn.
20 (Celsius) limit1 (under:full constrained) of HEATSUM index
60 (Celsius) limit2 (above:unconstrained) of HEATSUM index
0 (Celsius) limit1 (under:full constrained) of TMIN index
5 (Celsius) limit2 (above:unconstrained) of TMIN index
4000 (Pa) limit1 (above:full constrained) of VPD index
1000 (Pa) limit2 (under:unconstrained) of VPD index
0 (s) limit1 (under:full constrained) of DAYLENGTH index
0 (s) limit2 (above:unconstrained) of DAYLENGTH index
10 (day) moving average (to avoid the effects of extreme events)
0.10 (dimless) GSI limit1 (greater that limit -> start of vegper)
0.01 (dimless) GSI limit2 (less that limit -> end of vegper)
----------------------------------------------------------------------------------------
PHENOLOGICAL (ALLOCATION) PARAMETERS (7 phenological phases)
phase1 phase2 phase3 phase4 phase5 phase6 phase7 (text) name of the phenophase
5000 200 500 200 400 200 100 (Celsius) length of phenophase (GDD)
0.3 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) leaf ALLOCATION
0.5 0.4 0.4 0.4 0.4 0.4 0.4 (ratio) fine root ALLOCATION
0.0 0.0 0.0 0.0 0.0 0.0 0.0 (ratio) fruit ALLOCATION
0.2 0.2 0.2 0.2 0.2 0.2 0.2 (ratio) soft stem ALLOCATION
0 0 0 0 0 0 0 (ratio) live woody stem ALLOCATION
0 0 0 0 0 0 0 (ratio) dead woody stem ALLOCATION
0 0 0 0 0 0 0 (ratio) live coarse root ALLOCATION
0 0 0 0 0 0 0 (ratio) dead coarse root ALLOCATION
49 49 49 49 49 49 49 (m2/kgC) canopy average specific leaf area (projected area basis)
0.37 0.37 0.37 0.37 0.37 0.37 0.37 (prop.) current growth proportion
10000 10000 10000 10000 10000 10000 10000 (Celsius) maximal lifetime of plant tissue

View File

@ -1,33 +1,33 @@
MANAGEMENT_INFORMATION MuSo6
-------------------------------------------------------------------------------------------------------------------
PLANTING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
THINNING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
MOWING
1 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
hhs.mow
-------------------------------------------------------------------------------------------------------------------
GRAZING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
HARVESTING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
PLOUGHING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
FERTILIZING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
IRRIGATING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
MANAGEMENT_INFORMATION MuSo6
-------------------------------------------------------------------------------------------------------------------
PLANTING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
THINNING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
MOWING
1 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
hhs.mow
-------------------------------------------------------------------------------------------------------------------
GRAZING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
HARVESTING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
PLOUGHING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
FERTILIZING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none
-------------------------------------------------------------------------------------------------------------------
IRRIGATING
0 (flag) flag of management action: 0 - no MGM, 1 - MGM information from file below
none

View File

@ -0,0 +1,23 @@
DATE afterLAI(m2/m2) transPART(%)
2006.08.09 1 90
2007.06.18 1 90
2008.05.30 1 90
2008.08.18 1 90
2009.06.08 1 90
2009.08.07 1 90
2010.06.12 1 90
2010.09.26 1 90
2011.06.01 1 90
2011.08.21 1 90
2012.05.24 1 90
2012.08.17 1 90
2013.06.16 1 90
2013.09.29 1 90
2014.06.09 1 90
2015.06.13 1 90
2015.09.30 1 90
2016.06.22 1 90
2016.08.14 1 90
2017.06.18 1 90
2018.06.03 1 90
2018.07.30 1 90

File diff suppressed because it is too large Load Diff

View File

@ -1,64 +1,64 @@
SOILPROP FILE - hhs muso6
----------------------------------------------------------------------------------------
NITROGEN AND DECOMPOSITION PARAMETERS
0.1 (prop.) denitrification rate per g of CO2 respiration of SOM
0.2 (prop.) nitrification coefficient 1
0.1 (prop.) nitrification coefficient 2
0.02 (prop.) coefficient of N2O emission of nitrification
0.1 (prop.) NH4 mobilen proportion
1.0 denitrification related N2/N2O ratio multiplier (soil texture effect)
10 (m) e-folding depth of decomposition rate's depth scalar
0.002 (prop.) fraction of dissolved part of SOIL1 organic matter
0.002 (prop.) fraction of dissolved part of SOIL2 organic matter
0.002 (prop.) fraction of dissolved part of SOIL3 organic matter
0.002 (prop.) fraction of dissolved part of SOIL4 organic matter
0.1 (prop.) minimum WFPS for scalar of nitrification calculation
0.45 (prop.) lower optimum WFPS for scalar of nitrification calculation
0.55 (prop.) higher optimum WFPS for scalar of nitrification calculation
0.2 (prop.) minimum value for saturated WFPS scalar of nitrification calculation
10 (ppm) C:N ratio of recaltirant SOM (slowest)
----------------------------------------------------------------------------------------
RATE SCALARS
0.39 (DIM) respiration fractions for fluxes between compartments (l1s1)
0.55 (DIM) respiration fractions for fluxes between compartments (l2s2)
0.29 (DIM) respiration fractions for fluxes between compartments (l4s3)
0.28 (DIM) respiration fractions for fluxes between compartments (s1s2)
0.46 (DIM) respiration fractions for fluxes between compartments (s2s3)
0.55 (DIM) respiration fractions for fluxes between compartments (s3s4)
0.7 (DIM) rate constant scalar of labile litter pool
0.07 (DIM) rate constant scalar of cellulose litter pool
0.014 (DIM) rate constant scalar of lignin litter pool
0.07 (DIM) rate constant scalar of fast microbial recycling pool
0.014 (DIM) rate constant scalar of medium microbial recycling pool
0.0014 (DIM) rate constant scalar of slow microbial recycling pool
0.0001 (DIM) rate constant scalar of recalcitrant SOM (humus) pool
0.001 (DIM) rate constant scalar of physical fragmentation of coarse woody debris
----------------------------------------------------------------------------------------
CH4 PARAMETERS
212.5 (DIM) soil CH4 emission bulk density dependence parameter1
1.81 (DIM) soil CH4 emission bulk density dependence parameter2
-1.353 (DIM) soil CH4 emission soil water content dependence parameter1
0.2 (DIM) soil CH4 emission soil water content dependence parameter2
1.781 (DIM) soil CH4 emission soil water content dependence parameter3
6.786 (DIM) soil CH4 emission soil water content dependence parameter4
0.010 (DIM) soil CH4 emission soil temperature dependence parameter1
----------------------------------------------------------------------------------------
SOIL PARAMETERS
2 (m) depth of soil
6 (mm) limit of first stage evaporation
5.00 (mm) maximum height of pond water
1 (dimless) curvature of soil stress function
-9999 (dimless) runoff curve number (-9999: no , model estimation)
107 (s/m) aerodynamic resistance (Wallace and Holwill, 1997)
----------------------------------------------------------------------------------------
SOIL COMPOSITION AND CHARACTERISTIC VALUES (-9999: no measured data)
30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 (%) sand percentage by volume in rock-free soil
50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 (%) silt percentage by volume in rock-free soil
7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 (dimless) soil pH (dimless) measured runoff curve number
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (g/cm3) bulk density
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at saturation
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at field capacity
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at wilting point
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at hygroscopic water content
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (dimless) drainage coefficient
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (cm/day) hydraulic condictivity at saturation
SOILPROP FILE - hhs muso6
----------------------------------------------------------------------------------------
NITROGEN AND DECOMPOSITION PARAMETERS
0.1 (prop.) denitrification rate per g of CO2 respiration of SOM
0.2 (prop.) nitrification coefficient 1
0.1 (prop.) nitrification coefficient 2
0.02 (prop.) coefficient of N2O emission of nitrification
0.1 (prop.) NH4 mobilen proportion
1.0 denitrification related N2/N2O ratio multiplier (soil texture effect)
10 (m) e-folding depth of decomposition rate's depth scalar
0.002 (prop.) fraction of dissolved part of SOIL1 organic matter
0.002 (prop.) fraction of dissolved part of SOIL2 organic matter
0.002 (prop.) fraction of dissolved part of SOIL3 organic matter
0.002 (prop.) fraction of dissolved part of SOIL4 organic matter
0.1 (prop.) minimum WFPS for scalar of nitrification calculation
0.45 (prop.) lower optimum WFPS for scalar of nitrification calculation
0.55 (prop.) higher optimum WFPS for scalar of nitrification calculation
0.2 (prop.) minimum value for saturated WFPS scalar of nitrification calculation
10 (ppm) C:N ratio of recaltirant SOM (slowest)
----------------------------------------------------------------------------------------
RATE SCALARS
0.39 (DIM) respiration fractions for fluxes between compartments (l1s1)
0.55 (DIM) respiration fractions for fluxes between compartments (l2s2)
0.29 (DIM) respiration fractions for fluxes between compartments (l4s3)
0.28 (DIM) respiration fractions for fluxes between compartments (s1s2)
0.46 (DIM) respiration fractions for fluxes between compartments (s2s3)
0.55 (DIM) respiration fractions for fluxes between compartments (s3s4)
0.7 (DIM) rate constant scalar of labile litter pool
0.07 (DIM) rate constant scalar of cellulose litter pool
0.014 (DIM) rate constant scalar of lignin litter pool
0.07 (DIM) rate constant scalar of fast microbial recycling pool
0.014 (DIM) rate constant scalar of medium microbial recycling pool
0.0014 (DIM) rate constant scalar of slow microbial recycling pool
0.0001 (DIM) rate constant scalar of recalcitrant SOM (humus) pool
0.001 (DIM) rate constant scalar of physical fragmentation of coarse woody debris
----------------------------------------------------------------------------------------
CH4 PARAMETERS
212.5 (DIM) soil CH4 emission bulk density dependence parameter1
1.81 (DIM) soil CH4 emission bulk density dependence parameter2
-1.353 (DIM) soil CH4 emission soil water content dependence parameter1
0.2 (DIM) soil CH4 emission soil water content dependence parameter2
1.781 (DIM) soil CH4 emission soil water content dependence parameter3
6.786 (DIM) soil CH4 emission soil water content dependence parameter4
0.010 (DIM) soil CH4 emission soil temperature dependence parameter1
----------------------------------------------------------------------------------------
SOIL PARAMETERS
2 (m) depth of soil
6 (mm) limit of first stage evaporation
5.00 (mm) maximum height of pond water
1 (dimless) curvature of soil stress function
-9999 (dimless) runoff curve number (-9999: no , model estimation)
107 (s/m) aerodynamic resistance (Wallace and Holwill, 1997)
----------------------------------------------------------------------------------------
SOIL COMPOSITION AND CHARACTERISTIC VALUES (-9999: no measured data)
30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 30.0 (%) sand percentage by volume in rock-free soil
50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 50.0 (%) silt percentage by volume in rock-free soil
7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 7.0 (dimless) soil pH (dimless) measured runoff curve number
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (g/cm3) bulk density
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at saturation
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at field capacity
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at wilting point
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (m3/m3) SWC at hygroscopic water content
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (dimless) drainage coefficient
-9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 -9999 (cm/day) hydraulic condictivity at saturation

View File

@ -0,0 +1,147 @@
BBGCMuSo simulation
MET_INPUT
hhs.mtc43 (filename) met file name
4 (int) number of header lines in met file
365 (int) number of simdays in last simyear (truncated year: <= 365)
RESTART
1 (flag) 1 = read restart; 0 = dont read restart
0 (flag) 1 = write restart; 0 = dont write restart
hhs_MuSo6.endpoint (filename) name of the input restart file
hhs_MuSo6.endpoint (filename) name of the output restart file
TIME_DEFINE
9 (int) number of simulation years
2007 (int) first simulation year
0 (flag) 1 = spinup run; 0 = normal run
6000 (int) maximum number of spinup years
CO2_CONTROL
1 (flag) 0=constant; 1=vary with file
395.0 (ppm) constant atmospheric CO2 concentration
CO2.txt (filename) name of the CO2 file
NDEP_CONTROL
1 (flag) 0=constant; 1=vary with file
0.001400 (kgN/m2/yr) wet+dry atmospheric deposition of N
Ndep.txt (filename) name of the N-dep file
SITE
248.0 (m) site elevation
46.95 (degrees) site latitude (- for S.Hem.)
0.20 (DIM) site shortwave albedo
9.00 (Celsius) mean annual air temperature
10.15 (Celsius) mean annual air temperature range
0.50 (prop.) proprortion of NH4 flux of N-deposition
SOIL_FILE
hhs.soi (filename) SOIL filename
EPC_FILE
c3grass_muso6.epc (filename) EPC filename
MANAGEMENT_FILE
hhs.mgm (filename) MGM filename (or "none")
SIMULATION_CONTROL
1 (flag) phenology flag (1 = MODEL PHENOLOGY 0 = USER-SPECIFIED PHENOLOGY)
1 (flag) vegper calculation method if MODEL PHENOLOGY is used (0: original, 1: GSI)
0 (flag) transferGDD flag (1= transfer calc. from GDD 0 = transfer calc. from EPC)
1 (flag) q10 flag (1 = temperature dependent q10 value; 0= constans q10 value)
1 (flag) acclimation flag of photosynthesis (1 = acclimation 0 = no acclimation)
1 (flag) acclimation flag of respiration (1 = acclimation 0 = no acclimation)
1 (flag) CO2 conductance reduction flag (0: no effect, 1: multiplier)
0 (flag) soil temperature calculation method (0: Zheng, 1: DSSAT)
1 (flag) soil hydrological calculation method (0: Richards, 1: tipping DSSAT)
0 (int) discretization level of soil hydr.calc.[Richards-method] (0: low, 1: medium, 2: high)
0 (flag) photosynthesis calculation method (0: Farquhar, 1: DSSAT)
0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor)
0 (flag) radiation calculation method (0: SWabs, 1: Rn)
0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand)
W_STATE
0.0 (kg/m2) water stored in snowpack
1.0 (DIM) initial soil water as a proportion of field capacity
CN_STATE
0.001 (kgC/m2) first-year maximum leaf carbon
0.001 (kgC/m2) first-year maximum fine root carbon
0.001 (kgC/m2) first-year maximum fruit carbon
0.001 (kgC/m2) first-year maximum softstem carbon
0.001 (kgC/m2) first-year maximum live woody stem carbon
0.001 (kgC/m2) first-year maximum live coarse root carbon
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) coarse woody debris carbon
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, labile pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, unshielded cellulose pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, shielded cellulose pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, lignin pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, fast microbial recycling pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, medium microbial recycling pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, slow microbial recycling pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, recalcitrant SOM (slowest)
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) litter nitrogen, labile pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NH4 pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NO3 pool
CLIM_CHANGE
0.0 (degC) - offset for Tmax
0.0 (degC) - offset for Tmin
1.0 (degC) - multiplier for PRCP
1.0 (degC) - multiplier for VPD
1.0 (degC) - multiplier for RAD
CONDITIONAL_MANAGEMENT_STRATEGIES
0 (flag) conditional mowing ? 0 - no, 1 - yes
0.0 (m2/m2) fixed value of the LAI before MOWING
0.0 (m2/m2) fixed value of the LAI after MOWING
0.0 (%) transported part of plant material after MOWING
0 (flag) conditional irrigation? 0 - no, 1 - yes
0.0 (prop) SMSI before cond. IRRIGATION (-9999: SWCratio is used)
0.0 (prop) SWCratio of rootzone before cond. IRRIGATION (-9999: SMSI is used)
0.0 (prop) SWCratio of rootzone after cond. IRRIGATION
0.0 (kgH2O/m2) maximum amount of irrigated water
OUTPUT_CONTROL
hhs_MuSo6 (filename) output prefix
1 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
0 (flag) writing annual output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
1 (flag) for on-screen progress indicator
DAILY_OUTPUT
12 number of daily output variables
2520 proj_lai
3009 daily_GPP
3014 daily_Reco
171 evapotransp
2502 n_actphen
2603 vwc00-03cm
2604 vwc03-10cm
2605 vwc10-30cm
75 GDD
2636 rooting_depth
2716 m_soilstress
671 m_vegc_to_SNSC
ANNUAL_OUTPUT
16 number of annual output variables
3000 annprcp
3001 anntavg
3002 annrunoff
3003 annoutflow
2734 annmax_lai
3031 cum_Closs_MGM
3032 cum_Cplus_MGM
3045 cum_Closs_SNSC
3046 cum_Cplus_STDB
3058 vegc
3064 totalc
3066 SOM_C_top30
3070 SOM_C_30to60
3071 SOM_C_60to90
3068 NH4_top30
3069 NO3_top30
END_INIT

View File

@ -0,0 +1,15 @@
ABREVIATION,INDEX,min,max MuSo6
TRANSFERGROWTHP,11,0.1,1
T_BASE,13,0,8
WPM,25,0,0.1
CN_leaf,26,14.3,58.8
CWIC,49,0.01,0.07
CLEC,50,0.3,0.8
FLNR,56,0.1,0.2
MSTOMACOND,58,0.001,0.007
ROOTDEPTH,64,0.5,3
ROOTDISTRIB,65,0.2,5
RELSWCCRIT1,96,0.97,1
RELSWCCRIT2,97,0.4,1
SENESCENCABG,101,0,0.1
SLA,137.60,10,60
1 ABREVIATION INDEX min max MuSo6
2 TRANSFERGROWTHP 11 0.1 1
3 T_BASE 13 0 8
4 WPM 25 0 0.1
5 CN_leaf 26 14.3 58.8
6 CWIC 49 0.01 0.07
7 CLEC 50 0.3 0.8
8 FLNR 56 0.1 0.2
9 MSTOMACOND 58 0.001 0.007
10 ROOTDEPTH 64 0.5 3
11 ROOTDISTRIB 65 0.2 5
12 RELSWCCRIT1 96 0.97 1
13 RELSWCCRIT2 97 0.4 1
14 SENESCENCABG 101 0 0.1
15 SLA 137.60 10 60

View File

@ -0,0 +1,147 @@
BBGCMuSo simulation
MET_INPUT
hhs.mtc43 (filename) met file name
4 (int) number of header lines in met file
365 (int) number of simdays in last simyear (truncated year: <= 365)
RESTART
0 (flag) 1 = read restart; 0 = dont read restart
1 (flag) 1 = write restart; 0 = dont write restart
hhs_MuSo6.endpoint (filename) name of the input restart file
hhs_MuSo6.endpoint (filename) name of the output restart file
TIME_DEFINE
54 (int) number of simulation years
1961 (int) first simulation year
1 (flag) 1 = spinup run; 0 = normal run
6000 (int) maximum number of spinup years
CO2_CONTROL
1 (flag) 0=constant; 1=vary with file
290.0 (ppm) constant atmospheric CO2 concentration
CO2.txt (filename) name of the CO2 file
NDEP_CONTROL
1 (flag) 0=constant; 1=vary with file
0.000200 (kgN/m2/yr) wet+dry atmospheric deposition of N
Ndep.txt (filename) name of the N-dep file
SITE
248.0 (m) site elevation
46.95 (degrees) site latitude (- for S.Hem.)
0.20 (DIM) site shortwave albedo
9.00 (Celsius) mean annual air temperature
10.15 (Celsius) mean annual air temperature range
0.50 (prop.) proprortion of NH4 flux of N-deposition
SOIL_FILE
hhs.soi (filename) SOIL filename
EPC_FILE
c3grass_muso6.epc (filename) EPC filename
MANAGEMENT_FILE
none (filename) MGM filename (or "none")
SIMULATION_CONTROL
1 (flag) phenology flag (1 = MODEL PHENOLOGY 0 = USER-SPECIFIED PHENOLOGY)
1 (flag) vegper calculation method if MODEL PHENOLOGY is used (0: original, 1: GSI)
0 (flag) transferGDD flag (1= transfer calc. from GDD 0 = transfer calc. from EPC)
1 (flag) q10 flag (1 = temperature dependent q10 value; 0= constans q10 value)
1 (flag) acclimation flag of photosynthesis (1 = acclimation 0 = no acclimation)
1 (flag) acclimation flag of respiration (1 = acclimation 0 = no acclimation)
1 (flag) CO2 conductance reduction flag (0: no effect, 1: multiplier)
0 (flag) soil temperature calculation method (0: Zheng, 1: DSSAT)
1 (flag) soil hydrological calculation method (0: Richards, 1: tipping DSSAT)
0 (int) discretization level of soil hydr.calc.[Richards-method] (0: low, 1: medium, 2: high)
0 (flag) photosynthesis calculation method (0: Farquhar, 1: DSSAT)
0 (flag) evapotranspiration calculation method (0: Penman-Montieth, 1: Priestly-Taylor)
0 (flag) radiation calculation method (0: SWabs, 1: Rn)
0 (flag) soilstress calculation method (0: based on VWC, 1: based on transp. demand)
W_STATE
0.0 (kg/m2) water stored in snowpack
1.0 (DIM) initial soil water as a proportion of field capacity
CN_STATE
0.001 (kgC/m2) first-year maximum leaf carbon
0.001 (kgC/m2) first-year maximum fine root carbon
0.001 (kgC/m2) first-year maximum fruit carbon
0.001 (kgC/m2) first-year maximum softstem carbon
0.001 (kgC/m2) first-year maximum live woody stem carbon
0.001 (kgC/m2) first-year maximum live coarse root carbon
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) coarse woody debris carbon
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, labile pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, unshielded cellulose pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, shielded cellulose pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) litter carbon, lignin pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, fast microbial recycling pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, medium microbial recycling pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, slow microbial recycling pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgC/m2) soil carbon, recalcitrant SOM (slowest)
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) litter nitrogen, labile pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NH4 pool
0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 (kgN/m2) soil mineralized nitrogen, NO3 pool
CLIM_CHANGE
0.0 (degC) - offset for Tmax
0.0 (degC) - offset for Tmin
1.0 (degC) - multiplier for PRCP
1.0 (degC) - multiplier for VPD
1.0 (degC) - multiplier for RAD
CONDITIONAL_MANAGEMENT_STRATEGIES
0 (flag) conditional mowing ? 0 - no, 1 - yes
0.0 (m2/m2) fixed value of the LAI before MOWING
0.0 (m2/m2) fixed value of the LAI after MOWING
0.0 (%) transported part of plant material after MOWING
0 (flag) conditional irrigation? 0 - no, 1 - yes
0.0 (prop) SMSI before cond. IRRIGATION (-9999: SWCratio is used)
0.0 (prop) SWCratio of rootzone before cond. IRRIGATION (-9999: SMSI is used)
0.0 (prop) SWCratio of rootzone after cond. IRRIGATION
0.0 (kgH2O/m2) maximum amount of irrigated water
OUTPUT_CONTROL
hhs_MuSo6_Spinup (filename) output prefix
0 (flag) writing daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
0 (flag) writing monthly average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
0 (flag) writing annual average of daily output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
2 (flag) writing annual output (0 = no; 1 = binary; 2 = ascii; 3 = on-screen)
1 (flag) for on-screen progress indicator
DAILY_OUTPUT
12 number of daily output variables
2502 n_actphen
2603 vwc00-03cm
2604 vwc03-10cm
2605 vwc10-30cm
75 GDD
2636 rooting_depth
2716 m_soilstress
671 m_vegc_to_SNSC
171 evapotransp
3009 daily_gpp
3014 daily_tr
2520 proj_lai
ANNUAL_OUTPUT
16 number of annual output variables
3000 annprcp
3001 anntavg
3002 annrunoff
3003 annoutflow
2734 annmax_lai
3031 cum_Closs_MGM
3032 cum_Cplus_MGM
3045 cum_Closs_SNSC
3046 cum_Cplus_STDB
3058 vegc
3064 totalc
3066 SOM_C_top30
3070 SOM_C_30to60
3071 SOM_C_60to90
3068 NH4_top30
3069 NO3_top30
END_INIT

View File

@ -0,0 +1,115 @@
---
title: "ParameterSweep"
auth or: ""
date: "`r format(Sys.time(), '%d %B, %Y')`"
output: html_document
---
```{r setup, include=FALSE}
knitr::opts_chunk$set(echo = TRUE)
```
```{r,echo=FALSE}
library("RBBGCMuso")
quickAndDirty <- function(settings, parameters, inputDir= "./", outLoc, iterations=2, outVar=8,){
outLocPlain <- basename(outLoc)
currDir <- getwd()
inputDir <- normalizePath(inputDir)
tmp <- file.path(outLoc,"tmp/")
if(!dir.exists(outLoc)){
dir.create(outLoc)
warning(paste(outLoc," is not exists, so it was created"))
}
if(dir.exists(tmp)){
stop("There is a tmp directory inside the output location, please replace it. tmp is an important temporary directory for the function")
}
dir.create(tmp)
outLoc <- normalizePath(outLoc)
tmp <- normalizePath(tmp)
inputFiles <- file.path(inputDir,grep(basename(outLoc),list.files(inputDir),invert = TRUE,value = TRUE))
for(i in inputFiles){
file.copy(i,tmp)
}
setwd(tmp)
if(is.null(settings)){
settings <- setupMuso()
}
file.copy(settings$epcInput[2],"epc-save",overwrite = TRUE)
calibrationPar <- matrix[,"INDEX"]
npar <- nrow(matrix)
paramMatrices <- list()
parameters <- matrix(nrow = npar,ncol = iterations)
paramtest <- parameters
rownames(paramtest) <- matrix[,1]
for(i in 1:npar){
parameters[i,] <- seq(from=matrix[i,5],to=matrix[i,6],length=iterations)
#print(parameters[i,])
settings$calibrationPar <- calibrationPar[i]
for(j in 1:iterations){
p <- try(calibMuso(settings,parameters =parameters[i,j],silent=TRUE))
if(length(p)>1){
paramtest[i,j] <- max(p[,outVar])
# print(paramtest)
} else {
paramtest[i,j] <- NA
# print(paramtest)
}
}
file.copy("epc-save",settings$epcInput[2],overwrite = TRUE)
}
print("###################################################")
paramMatrices <- (function(){
for(i in 1:nrow(paramtest)){
matrx <- matrix(ncol = 2,nrow=iterations)
matrx[,1] <- parameters[i,]
matrx[,2] <- paramtest[i,]
paramMatrices[[i]] <- matrx
names(paramMatrices)[i] <- rownames(paramtest)[i]
}
return(paramMatrices)
})()
return(list(paramtest,paramMatrices))
}
```
```{r, echo=FALSE,cache=TRUE}
parconstrains <- read.csv("parconstrains_extended.csv")
settings <- setupMuso()
parSeq<-quickAndDirty(settings = settings,matrix = parconstrains,outVar = 8,iterations = 5)
```
```{r}
parSeq
```
```{r,echo=FALSE}
parlist<-parSeq[[2]]
lparlist<-length(parlist)
for(i in 1:lparlist){
title<-names(parlist)[i]
plot(x = parlist[[i]][,1], y= parlist[[i]][,2], ylim=c(0,15), main=title,ylab="LAI")
}
```

View File

@ -0,0 +1,14 @@
NAME,INDEX,MIN,MAX
BASETEMP,25,3,9
WPM,36,0,0.1
CN_lv,38,10,50
CN_li,39,32,70
CN_root,40,20,70
CN_fruit,41,10.50,70
CN_stem,42,0,70
CLEC,55,0.4,0.8
FLNR,61,0.05,0.8
STOMA,63,0.003,0.015
ROOTDEPTH,74,0.3,2.
SWCGERMIN,87,0.2,0.9
NH4MOBILEPROP,120,0.05,0.7
1 NAME INDEX MIN MAX
2 BASETEMP 25 3 9
3 WPM 36 0 0.1
4 CN_lv 38 10 50
5 CN_li 39 32 70
6 CN_root 40 20 70
7 CN_fruit 41 10.50 70
8 CN_stem 42 0 70
9 CLEC 55 0.4 0.8
10 FLNR 61 0.05 0.8
11 STOMA 63 0.003 0.015
12 ROOTDEPTH 74 0.3 2.
13 SWCGERMIN 87 0.2 0.9
14 NH4MOBILEPROP 120 0.05 0.7

Binary file not shown.

View File

@ -0,0 +1,21 @@
context("Post processing")
library(testthat)
library(RBBGCMuso)
setwd(system.file("examples/hhs","",package = "RBBGCMuso"))
test_that("Post processing string",{
testMatrix1 <- data.frame(first = rep(1,5), second = rep(2,5), third = rep(3,5))
testMatrix1c <- testMatrix1
testMatrix1c[,"newCol"] <- testMatrix1c[,2] + 3 * testMatrix1c[,3]
expect_equal(postProcMuso(testMatrix1,"newCol <- @2 + 3*@3"),testMatrix1c)
})
test_that("calibMuso with postprocessing",{
model <- calibMuso(skipSpinup = FALSE, silent = TRUE)
modelc<- model
newCol <- modelc[,1]
modelc<- cbind.data.frame(modelc,newCol)
modelc[,"newCol"]<- model[,5]+3*model[,7]
expect_equal(calibMuso(skipSpinup = FALSE,silent = TRUE, postProcString = "newCol <- @5 + 3* @7"), modelc)
})

View File

@ -0,0 +1,21 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/musoTime.R
\name{alignData}
\alias{alignData}
\title{alignData}
\usage{
alignData(
mdata,
dataCol,
modellSettings = NULL,
startDate = NULL,
endDate = NULL,
formatString = "\%Y-\%m-\%d",
leapYear = TRUE,
continious = FALSE
)
}
\description{
This function align the data to the model and the model to the data
}
\keyword{internal}

View File

@ -0,0 +1,49 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/calibMuso.R
\name{calibMuso}
\alias{calibMuso}
\title{calibMuso}
\usage{
calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL,
keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
}
\arguments{
\item{settings}{You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment}
\item{parameters}{In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4)}
\item{timee}{The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly. I recommend to use daily data, the yearly and monthly data is not well-tested yet.}
\item{debugging}{If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles}
\item{logfilename}{If you want to set a specific name for your logfiles you can set this via logfile parameter}
\item{keepEpc}{If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.}
\item{export}{if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.}
\item{silent}{If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed.}
\item{aggressive}{It deletes every possible modell-outputs from the previous modell runs.}
\item{keepBinary}{In default RBBGCMuso to keep working area as clean as possible, deletes all the regular output files. The results are directly printed to the standard output, but you can redirect it, and save it to a variable, or you can export your results to the desired destination in a desired format. Whith this variable you can enable to keep the binary output files. If you want to set the location of the binary output, please take a look at the binaryPlace argument.}
\item{binaryPlace}{The place of the binary output files.}
\item{fileToChange}{You can change any line of the epc or the ini file, you just have to specify with this variable which file you van a change. Two options possible: "epc", "ini"}
\item{skipSpinup}{If TRUE, calibMuso wont do spinup simulation}
\item{prettyOut}{date ad Date type, separate year, month, day vectors}
\item{leapYear}{Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.}
}
\value{
No return, outputs are written to file
}
\description{
This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a well-structured way.
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,43 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/calibrateMuso.R
\name{calibrateMuso}
\alias{calibrateMuso}
\title{calibrateMuso}
\usage{
calibrateMuso(
measuredData,
parameters = read.csv("parameters.csv", stringsAsFactor = FALSE),
startDate = NULL,
endDate = NULL,
formatString = "\%Y-\%m-\%d",
dataVar,
outLoc = "./calib",
preTag = "cal-",
settings = setupMuso(),
outVars = NULL,
iterations = 100,
skipSpinup = TRUE,
plotName = "calib.jpg",
modifyOriginal = TRUE,
likelihood,
uncertainity = NULL,
naVal = NULL,
postProcString = NULL,
thread_prefix = "thread",
numCores = (parallel::detectCores() - 1),
pb = txtProgressBar(min = 0, max = iterations, style = 3),
maxLikelihoodEpc = TRUE,
pbUpdate = setTxtProgressBar,
outputLoc = "./",
method = "GLUE",
lg = FALSE,
w = NULL,
...
)
}
\description{
This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution for all selected parameters.
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,14 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/changeMuso.R
\name{changemulline}
\alias{changemulline}
\title{changemulline}
\usage{
changemulline(filePaths, calibrationPar, contents, src, outFiles = filePaths)
}
\description{
The function uses the previous changspecline function to operate.
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,16 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/flat.R
\name{checkFileSystem}
\alias{checkFileSystem}
\title{checkFileSystem}
\usage{
checkFileSystem(iniName, root = ".", depTree = options("RMuso_depTree")[[1]])
}
\arguments{
\item{iniName}{The name of the ini file}
\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]}
}
\description{
This function checks the MuSo file system, if it is correct
}

View File

@ -0,0 +1,33 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/checkMeteoBGC.R
\name{checkMeteoBGC}
\alias{checkMeteoBGC}
\title{checkMeteoBGC}
\usage{
checkMeteoBGC(
settings = NULL,
skip = 4,
numericReport = FALSE,
type = "normal"
)
}
\arguments{
\item{settings}{The output of setupMuso}
\item{skip}{Number of header lines in meteorology file.}
\item{numericReport}{If numericReport is set to FALSE, the function returns with a text report. If numericReport is set to TRUE, the function returns with a numeric report.}
\item{type}{meteorology for spinup or normal run}
\item{metFileName}{The name of the meteorology file (mtc43).}
}
\value{
It depends on the numericReport parameter. The function returns with a text report, or with a numeric report.
}
\description{
This function calculates the daily and yearly statistics for a given meteorology file (mtc43).
}
\author{
Erzsebet Kristof
}

View File

@ -0,0 +1,21 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/cleanup.R
\name{cleanupMuso}
\alias{cleanupMuso}
\title{cleanupMuso}
\usage{
cleanupMuso(location=NULL, simplicity=TRUE,deep=FALSE)
}
\arguments{
\item{location}{This is the place (directory) where your output files are located.}
\item{simplicity}{TRUE or FALSE. If TRUE cleanupMuso will erase only the log files from the location}
\item{deep}{If it is TRUE, it will delete every files from the subdirectories also}
}
\description{
cleanupMuso can erase all of the unnecessary log and output files.
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,21 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/multiSite.R
\name{compareCalibratedWithOriginal}
\alias{compareCalibratedWithOriginal}
\title{compareCalibratedWithOriginal}
\usage{
compareCalibratedWithOriginal(
key,
modOld,
modNew,
mes,
likelihoods,
alignIndexes,
musoCodeToIndex,
nameGroupTable,
groupFun
)
}
\description{
This functions compareses the likelihood and the RMSE values of the simulations and the measurements
}

View File

@ -0,0 +1,33 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/plotMuso.R
\name{compareMuso}
\alias{compareMuso}
\title{compareMuso}
\usage{
compareMuso(
settings = NULL,
parameters,
variable = 1,
calibrationPar = NULL,
fileToChange = "epc",
skipSpinup = TRUE,
timeFrame = "day"
)
}
\arguments{
\item{settings}{RBBGCMuso uses variables that define the entire simulation environment. Those environment variables include the name of the INI files, the name of the meteorology files, the path to the model executable and its file name, the entire output list, the entire output variable matrix, the dependency rules for the EPC parameters etc. Using the runMuso function RBBGCMuso can automatically create those environment variables by inspecting the files in the working directory (this happens through the setupMuso function). It means that by default model setup is performed automatically in the background and the user has nothing to do. With this settings parameter we can force runMuso to skip automatic environment setup as we provide the environment settings to runMuso. In a typical situation the user can skip this option.}
\item{parameters}{Using this function it is possible to change some of the EPC parameters prior to model execution. This can be achieved with this option. In the parameters variable you have set the row indices of the variables that you wish to change. In this parameters you can give an exact value for them in a vector form like c(1,2,3,4).}
\item{variable}{The name of the output variable to plot}
\item{calibrationPar}{You might want to change some parameters in your EPC file before running the model. This function offers possibility for this without editing the EPC file. In this situation you have to select the appropirate model parameters first. You can refer to these parameters with the number of the line in the EPC file. Indexing of lines start from one. You should use a vector for this referencing like c(1,5,8)}
\item{fileToChange}{You can change any line of the EPC or the INI file. Please choose "EPC", "INI" or "BOTH". This file will be used for the analysis, and the original parameter values will be changed according to the choice of the user.}
}
\description{
This function runs the model, then changes one of its input data, runs it again, and plots both results in one graph.
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,16 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/musoExample.R
\name{copyMusoExampleTo}
\alias{copyMusoExampleTo}
\title{copyMusoExampleTo}
\usage{
copyMusoExampleTo(example = NULL, destination = NULL)
}
\arguments{
\item{example}{This is the name of the example file. If it is not set then a simple graphical user interface (tcl/tk menu) will open to select the target dataset (which is typically an experimental site). In the list hhs means the Hegyhatsal eddy covariance site in Hungary.}
\item{destination}{The destination where the example files will be copied.}
}
\description{
This function enables the user to download a complete, working file set to quickly start using Biome-BGCMuSo through RBBGCMuso (or in standalone mode). The user has to specify the target directory for the files. The file set contains the model executable (muso.exe in Windows), the INI files that drive the model, and other files like meteorology input, ecophysiological constants file (EPC), and other ancillary files (CO2 concentration, parameter range definition file called parameters.csv). Note that we strongly recommend to read the User's Guide of Biome-BGCMuSo to clarify the meaning of the input files. The input files (s.ini, n.ini, maize.epc, meteorology files) are simple text files, so the user can read (and modify) them with his/her favourite text editor (like Editpad Lite, vim, emacs). Note that some files use UNIX/Linux style text which means that the text will not be readable using the Windows Notepad.
}

View File

@ -0,0 +1,22 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/otherUsefullFunctions.R
\name{corrigMuso}
\alias{corrigMuso}
\title{corrigMuso}
\usage{
corrigMuso(settings, data)
}
\arguments{
\item{settings}{This is the output of the setupMuso() function. It contains all of the RBBGCMuso settings}
\item{data}{the models outputdata}
}
\value{
It returns the modells leapyear-corrigated output data.
}
\description{
This function leapyear-corrigate the output of the modell
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,11 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/soilQuery.R
\name{createSoilFile}
\alias{createSoilFile}
\title{createSoilFile}
\description{
This function collects soil data from a given restapi, de default is soilGrid
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,22 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/assistantFunctions.R
\name{dynRound}
\alias{dynRound}
\title{dynRound}
\usage{
dynRound(x, y, seqLen)
}
\arguments{
\item{x}{The lower end of the sequence}
\item{y}{The higher end of the sequence}
\item{seqLen}{The length of the sequence}
}
\value{
rounded sequence
}
\description{
This function rounds a sequence (definded by its endpoints and the length) optimally
}
\keyword{internal}

View File

@ -0,0 +1,20 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/otherUsefullFunctions.R
\name{fextension}
\alias{fextension}
\title{fextension}
\usage{
fextension(filename)
}
\arguments{
\item{filename}{The string of the filenam}
}
\value{
the extension of the given file
}
\description{
A function for extracting the extension name from the filename string
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,25 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/flat.R
\name{flatMuso}
\alias{flatMuso}
\title{flatMuso}
\usage{
flatMuso(
iniName,
execPath = "./",
depTree = options("RMuso_depTree")[[1]],
directory = "flatdir",
d = TRUE,
outE = TRUE
)
}
\arguments{
\item{iniName}{The name of the ini file}
\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]}
\item{directory}{The destination directory for flattening. At default it will be flatdir}
}
\description{
This function reads the ini file and creates a directory (named after the directory argument) with all the files the modell uses with this file. the directory will be flat.
}

View File

@ -0,0 +1,14 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/getOutPutList.R
\name{getAnnualOutputList}
\alias{getAnnualOutputList}
\title{getAnnualOutputList}
\usage{
getAnnualOutputList(settings = NULL)
}
\arguments{
\item{settings}{bla}
}
\description{
bla bla
}

View File

@ -0,0 +1,19 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/otherUsefullFunctions.R
\name{getConstMatrix}
\alias{getConstMatrix}
\title{getConstMatrix}
\usage{
getConstMatrix(
filetype = "epc",
version = as.character(getOption("RMuso_version"))
)
}
\arguments{
\item{filetype}{It can be "epc" or "soil".}
\item{version}{The version of the MuSo environment}
}
\description{
getConstMatrix is a function whith wich you can get the default constrain matrix for your choosen type and version.
}

View File

@ -0,0 +1,14 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/getOutPutList.R
\name{getDailyOutputList}
\alias{getDailyOutputList}
\title{getDailyOutputList}
\usage{
getDailyOutputList(settings = NULL)
}
\arguments{
\item{settings}{bla}
}
\description{
bla bla
}

View File

@ -0,0 +1,23 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/flat.R
\name{getFilePath}
\alias{getFilePath}
\title{getFilePath}
\usage{
getFilePath(
iniName,
fileType,
execPath = "./",
depTree = options("RMuso_depTree")[[1]]
)
}
\arguments{
\item{iniName}{The name of the ini file}
\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]}
\item{filetype}{The type of the choosen file. For options see options("RMuso_depTree")[[1]]$name}
}
\description{
This function reads the ini file and for a chosen fileType it gives you the filePath
}

View File

@ -0,0 +1,20 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/flat.R
\name{getFilesFromIni}
\alias{getFilesFromIni}
\title{getFilesFromIni}
\usage{
getFilesFromIni(
iniName,
execPath = "./",
depTree = options("RMuso_depTree")[[1]]
)
}
\arguments{
\item{iniName}{The name of the ini file}
\item{depTree}{The file dependency defining dataframe. At default it is: options("RMuso_depTree")[[1]]}
}
\description{
This function reads the ini file and gives yout back the path of all file involved in model run
}

View File

@ -0,0 +1,20 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/assistantFunctions.R
\name{getLogs}
\alias{getLogs}
\title{getLogs}
\usage{
getLogs(outputLoc, outputNames, type = "spinup")
}
\arguments{
\item{outputLoc}{This is the location of the output files.}
\item{outputNames}{These are the prefixes of the logfiles}
}
\value{
Logfiles with paths
}
\description{
This function gives us the muso logfiles with their path
}
\keyword{internal}

View File

@ -0,0 +1,20 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/assistantFunctions.R
\name{getOutFiles}
\alias{getOutFiles}
\title{getOutFiles}
\usage{
getOutFiles(outputLoc, outputNames)
}
\arguments{
\item{outputLoc}{This is the location of the output files.}
\item{outputNames}{These are the prefixes of the logfiles.}
}
\value{
Output files with their paths.
}
\description{
This function gives us the muso output files with their paths
}
\keyword{internal}

View File

@ -0,0 +1,11 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/soilQuery.R
\name{getSoilDataFull}
\alias{getSoilDataFull}
\title{getSoilDataFull}
\description{
This function collects soil data from a given restapi, de default is soilGrid
}
\author{
Roland HOLLÓS
}

View File

@ -0,0 +1,20 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/otherUsefullFunctions.R
\name{getyearlycum}
\alias{getyearlycum}
\title{getyearlycum}
\usage{
getyearlycum(daily_observations)
}
\arguments{
\item{daily_observations}{vector of the daily observations.}
}
\value{
A vector of yearly data
}
\description{
Funtion for getting cumulative yearly data from observations
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,20 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/otherUsefullFunctions.R
\name{getyearlymax}
\alias{getyearlymax}
\title{getyearlymax}
\usage{
getyearlymax(daily_observations)
}
\arguments{
\item{daily_observations}{vector of the daily observations}
}
\value{
A vector of yearly data
}
\description{
Function for getting the maximum values of the years, from daily data
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,64 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/multiSite.R
\name{multiSiteCalib}
\alias{multiSiteCalib}
\title{multiSiteCalib}
\usage{
multiSiteCalib(
measurements,
calTable,
parameters,
dataVar,
iterations = 100,
burnin = ifelse(iterations < 3000, 3000, NULL),
likelihood,
execPath,
thread_prefix = "thread",
numCores = (parallel::detectCores() - 1),
pb = txtProgressBar(min = 0, max = iterations, style = 3),
pbUpdate = setTxtProgressBar,
copyThread = TRUE,
constraints = NULL,
th = 10,
treeControl = rpart.control()
)
}
\arguments{
\item{calTable}{A dataframe which contantains the ini file locations and the domains they belongs to}
\item{parameters}{A dataframe with the name, the minimum, and the maximum value for the parameters used in MonteCarlo experiment}
\item{dataVar}{A named vector where the elements are the MuSo variable codes and the names are the same as provided in measurements and likelihood}
\item{iterations}{The number of MonteCarlo experiments to be executed}
\item{burnin}{Currently not used, altought it is the length of burnin period of the MCMC sampling used to generate random parameters}
\item{likelihood}{A list of likelihood functions which names are linked to dataVar}
\item{execPath}{If you are running the calibration from different location than the MuSo executable, you have to provide the path}
\item{thread_prefix}{The prefix of thread directory names in the tmp directory created during the calibrational process}
\item{numCores}{The number of processes used during the calibration. At default it uses one less than the number of threads available}
\item{pb}{The progress bar function. If you use (web-)GUI you can provide a different function}
\item{pbUpdate}{The update function for pb (progress bar)}
\item{copyThread}{A boolean, recreate tmp directory for calibration or not (case of repeating the calibration)}
\item{th}{A trashold value for multisite calibration. What percentage of the site should satisfy the constraints.}
\item{treeControl}{A list which controls (maximal complexity, maximal depth) the details of the decession tree making.}
\item{measuremets}{The table which contains the measurements}
\item{contsraints}{A dataframe containing the constraints logic the minimum and a maximum value for the calibration.}
}
\description{
This funtion uses the Monte Carlo technique to uniformly sample the parameter space from user defined parameters of the Biome-BGCMuSo model. The sampling algorithm ensures that the parameters are constrained by the model logic which means that parameter dependencies are fully taken into account (parameter dependency means that e.g leaf C:N ratio must be smaller than C:N ratio of litter; more complicated rules apply to the allocation parameters where the allocation fractions to different plant compartments must sum up 1). This function implements a mathematically correct solution to provide uniform distriution of the random parameters on convex polytopes.
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,36 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/multiSite.R
\name{multiSiteThread}
\alias{multiSiteThread}
\title{multiSiteThread}
\usage{
multiSiteThread(
measuredData,
parameters = NULL,
startDate = NULL,
endDate = NULL,
formatString = "\%Y-\%m-\%d",
calTable,
dataVar,
outLoc = "./calib",
outVars = NULL,
iterations = 300,
skipSpinup = TRUE,
plotName = "calib.jpg",
modifyOriginal = TRUE,
likelihood,
uncertainity = NULL,
burnin = NULL,
naVal = NULL,
postProcString = NULL,
threadNumber,
constraints = NULL,
th = 10
)
}
\description{
This is an
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,21 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/musoTime.R
\name{musoDate}
\alias{musoDate}
\title{musoDate}
\usage{
musoDate(
startYear,
endYears = NULL,
numYears,
combined = TRUE,
leapYearHandling = FALSE,
prettyOut = FALSE
)
}
\description{
This function generates MuSo compatibla dates for the data
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,24 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/calibration.R
\name{musoGlue}
\alias{musoGlue}
\title{musoGlue}
\usage{
musoGlue(
presCalFile,
w,
delta = 0.17,
settings = setupMuso(),
parameters = read.csv("parameters.csv", stringsAsFactors = FALSE),
lg = FALSE
)
}
\arguments{
\item{plotName}{u}
}
\description{
This function calculates the -users specified- likelihood for random model input.
}
\author{
Roland HOLLOS
}

View File

@ -0,0 +1,22 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/outputMapping.R
\name{musoMapping}
\alias{musoMapping}
\title{musoMapping}
\usage{
musoMapping(code, mapData=NULL)
}
\arguments{
\item{code}{the MuSo outputcode}
\item{mapData}{updateMusomapping generated matrix}
}
\value{
The name of the Biome-BGCMuSo output code (e.g. if code is 3009 this function should return GPP to the user)
}
\description{
musoMapping can provide the user the name of a Biome-BGCMuSo output code. Within Biome-BGCMuSo the state variables and fluxes are marked by integer numbers. In order to provide meaningful variable names (e.g. 3009 means Gross Primary Production) a conversion table is needed which is utilized by this function. This function converts variable codes into names musoMappingFind does the opposite.
}
\author{
Roland HOLLOS
}

Some files were not shown because too many files have changed in this diff Show More