fixing optiMuso
This commit is contained in:
parent
76cc52cd3b
commit
96f98dba48
@ -18,6 +18,7 @@ export(musoRand)
|
||||
export(musoRandomizer)
|
||||
export(musoSensi)
|
||||
export(normalMuso)
|
||||
export(optiMuso)
|
||||
export(paramSweep)
|
||||
export(plotMuso)
|
||||
export(plotMusoWithData)
|
||||
@ -33,6 +34,7 @@ export(updateMusoMapping)
|
||||
import(ggplot2)
|
||||
import(utils)
|
||||
importFrom(Rcpp,evalCpp)
|
||||
importFrom(data.table,':=')
|
||||
importFrom(data.table,data.table)
|
||||
importFrom(data.table,fread)
|
||||
importFrom(digest,digest)
|
||||
@ -60,7 +62,9 @@ importFrom(ggplot2,theme)
|
||||
importFrom(ggplot2,theme_classic)
|
||||
importFrom(ggplot2,xlab)
|
||||
importFrom(ggplot2,ylab)
|
||||
importFrom(gridExtra,grid.arrange)
|
||||
importFrom(limSolve,xsample)
|
||||
importFrom(lubridate,leap_year)
|
||||
importFrom(magrittr,'%<>%')
|
||||
importFrom(magrittr,'%>%')
|
||||
importFrom(rmarkdown,pandoc_version)
|
||||
|
||||
@ -29,9 +29,10 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
debugging=FALSE, logfilename=NULL,
|
||||
keepEpc=FALSE, export=FALSE,
|
||||
silent=FALSE, aggressive=FALSE,
|
||||
leapYear=FALSE,keepBinary=FALSE,
|
||||
keepBinary=FALSE,
|
||||
binaryPlace="./", fileToChange="epc",
|
||||
skipSpinup = TRUE, modifyOriginal =FALSE, prettyOut = FALSE){
|
||||
skipSpinup = TRUE, modifyOriginal =FALSE, prettyOut = FALSE,
|
||||
postProcString = NULL){ #
|
||||
########################################################################
|
||||
###########################Set local variables and places###############
|
||||
########################################################################
|
||||
@ -103,11 +104,11 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
|
||||
if(!modifyOriginal & (!is.null(parameters) | !is.null(outVars)))
|
||||
{
|
||||
# browser()
|
||||
|
||||
toModif <- sapply(toModif, function (x){
|
||||
paste0(tools::file_path_sans_ext(basename(x)),"-tmp.",tools::file_ext(x))
|
||||
})
|
||||
toModif[[1]] <- file.path(dirname(epc[2]),toModif[[1]])
|
||||
|
||||
}
|
||||
|
||||
##change the epc file if and only if there are given parameters
|
||||
@ -119,18 +120,15 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
|
||||
##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(!modifyOriginal & (!is.null(parameters) | !is.null(outVars))){
|
||||
# browser()
|
||||
epc[2]<-file.path(dirname(epc[2]),toModif[1]) # Writing back the lost path
|
||||
toModif[2]<-file.path(dirname(iniInput[2]),toModif[2]) #for the Initmp, also
|
||||
if((!is.null(outVars) | !file.exists(toModif[2])) & !modifyOriginal){
|
||||
# browser()
|
||||
file.copy(iniInput[2],toModif[2],overwrite = TRUE)
|
||||
}
|
||||
|
||||
iniInput[2] <- toModif[2]}
|
||||
|
||||
if(!is.null(parameters) & ((fileToChange == "epc") | (fileToChange == "both")) & !modifyOriginal){
|
||||
# browser()
|
||||
tmp<-readLines(iniInput[2])
|
||||
tmpInd<-grep("EPC_FILE",tmp)+1
|
||||
tmp[tmpInd]<-file.path(dirname(tmp[tmpInd]),basename(epc[2]))
|
||||
@ -324,19 +322,18 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
stop("Modell Failure")
|
||||
}
|
||||
|
||||
|
||||
|
||||
|
||||
if(timee=="d"){
|
||||
if(!prettyOut){
|
||||
colnames(Reva) <- unlist(settings$outputVars[[1]])
|
||||
} else{
|
||||
dates <- as.Date(musoDate(startYear = settings$startYear,
|
||||
numYears = settings$numYears,
|
||||
timestep="d",combined = TRUE,corrigated = FALSE),
|
||||
"%d.%m.%Y")
|
||||
Reva <- cbind.data.frame(dates,
|
||||
musoDate(startYear = settings$startYear,
|
||||
numYears = settings$numYears,
|
||||
timestep = "d", combined = FALSE, corrigated = FALSE),
|
||||
Reva)
|
||||
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]])) )
|
||||
|
||||
}
|
||||
@ -345,21 +342,26 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
colnames(Reva) <- unlist(settings$outputVars[[2]])
|
||||
}
|
||||
|
||||
|
||||
|
||||
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, corrigated=FALSE)
|
||||
}
|
||||
|
||||
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){
|
||||
@ -376,5 +378,6 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
|
||||
} else{
|
||||
setwd(whereAmI)
|
||||
return(Reva)}
|
||||
return(Reva)
|
||||
}
|
||||
}
|
||||
|
||||
172
RBBGCMuso/R/calibration.R
Normal file
172
RBBGCMuso/R/calibration.R
Normal file
@ -0,0 +1,172 @@
|
||||
#' 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",
|
||||
leapYearHandling = TRUE,
|
||||
dataVar, outLoc = "./calib",
|
||||
preTag = "cal-",
|
||||
settings = NULL,
|
||||
outVars = NULL,
|
||||
iterations = 30,
|
||||
skipSpinup = TRUE,
|
||||
constrains = NULL,
|
||||
plotName = "calib.jpg",
|
||||
likelihood = function(x, y){
|
||||
exp(-sqrt(mean((x-y)^2)))
|
||||
},
|
||||
continious,
|
||||
modelVar = 3009,
|
||||
postProcString = NULL)
|
||||
{
|
||||
mdata <- measuredData
|
||||
dataCol <- grep(dataVar, colnames(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)
|
||||
|
||||
if(is.null(settings)){
|
||||
settings <- setupMuso()
|
||||
}
|
||||
|
||||
parameterNames <- parameters[,1]
|
||||
pretag <- file.path(outLoc,preTag)
|
||||
npar <- length(settings$calibrationPar)
|
||||
|
||||
##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 = constrains, iterations = 3000)
|
||||
randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),]
|
||||
} else {
|
||||
randVals <- musoRand(parameters = parameters,constrains = constrains, iterations = iterations)
|
||||
}
|
||||
|
||||
origEpc <- readValuesFromFile(settings$epc[2],parameters[,2])
|
||||
|
||||
## Prepare the preservedCalib 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)
|
||||
colNumb <- which(settings$dailyVarCodes == modelVar)
|
||||
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]]
|
||||
list2env(alignData(measuredData,dataCol = dataCol,modellSettings = settings,startDate = startDate,endDate = endDate,leapYear = leapYearHandling, continious = continious),envir=environment())
|
||||
## modIndex and measuredData are created.
|
||||
|
||||
modellOut <- numeric(iterations + 1) # single variable solution
|
||||
rmse <- numeric(iterations + 1)
|
||||
origModellOut <- calibMuso(settings=settings,silent=TRUE, skipSpinup = skipSpinup)
|
||||
|
||||
|
||||
write.csv(x=origModellOut, file=paste0(pretag,1,".csv"))
|
||||
modellOut[1] <- likelihood(measuredData,origModellOut[modIndex,colNumb])
|
||||
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= FALSE,
|
||||
skipSpinup = skipSpinup, postProcString = postProcString)[modIndex,colNumb], error = function (e) NA)
|
||||
browser()
|
||||
|
||||
modellOut[i]<- likelihood(measuredData,tmp)
|
||||
rmse[i] <- sqrt(mean((measuredData-tmp)^2))
|
||||
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)
|
||||
|
||||
|
||||
|
||||
epcStrip <- rbind(origEpc[order(parameters[,2])],
|
||||
randValues[,randVals[[1]] %in% parameters[,2]][,randInd])
|
||||
|
||||
|
||||
preservedCalib <- cbind(epcStrip,rmse,
|
||||
modellOut)
|
||||
columNames <- c(parameterNames[paramLines],"rmse", "likelihood")
|
||||
colnames(preservedCalib) <- columNames
|
||||
write.csv(preservedCalib,"preservedCalib.csv")
|
||||
p<-list()
|
||||
preservedCalib <- preservedCalib[-1,]
|
||||
dontInclude <-c((ncol(preservedCalib)-1),ncol(preservedCalib))
|
||||
for(i in seq_along(colnames(preservedCalib)[-dontInclude])){
|
||||
p[[i]] <- ggplot(as.data.frame(preservedCalib),aes_string(colnames(preservedCalib)[i],"likelihood")) +
|
||||
geom_point(shape='.',size=1,alpha=0.8)
|
||||
}
|
||||
|
||||
ggsave(plotName,grid.arrange(grobs = p, ncol = floor(sqrt(ncol(preservedCalib)-1))),dpi = 300)
|
||||
maxLikelihoodPlace <- which(preservedCalib[,"likelihood"]==max(preservedCalib[,"likelihood"],na.rm = TRUE))
|
||||
resPlot <- plotMusoWithData(mdata = mdata, startDate = startDate, endDate = endDate,
|
||||
dataVar = dataVar, modelVar = modelVar, settings = settings, continious = continious) +
|
||||
plotMuso(settings = settings, parameters = randValues[maxLikelihoodPlace,],
|
||||
postProcString = postProcString, skipSpinup = FALSE, variable = colNumb, layerPlot = TRUE, colour = "green")
|
||||
|
||||
print(resPlot)
|
||||
tempEpc <- paste0(tools::file_path_sans_ext(basename(settings$epcInput[2])),"-tmp.",tools::file_ext(settings$epcInput[2]))
|
||||
file.rename(tempEpc, "optimizedEpc.epc")
|
||||
return(preservedCalib[maxLikelihoodPlace,])
|
||||
}
|
||||
|
||||
|
||||
@ -26,20 +26,22 @@ changemulline <- function(filePaths, calibrationPar, contents, fileOut, fileToCh
|
||||
}
|
||||
|
||||
if(fileToChange == "epc" | fileToChange == "ini"){
|
||||
parMat<-cbind(calibrationPar, contents)
|
||||
parMat <- parMat[order(parMat[,1]),]
|
||||
parMat<-matrix(c(calibrationPar, contents),nrow=length(calibrationPar))
|
||||
if(nrow(parMat)!=1){
|
||||
parMat <- parMat[order(parMat[,1]),]
|
||||
}
|
||||
changeMusoC(inFile = filePaths[selectFileToWrite(filePaths, fileToChange)],
|
||||
outFile = fileOut[selectFileToWrite(filePaths, fileToChange)],
|
||||
parMat)
|
||||
}
|
||||
|
||||
if(fileToChange == "both"){
|
||||
parMat<-list()
|
||||
parMat[[1]]<-cbind(calibrationPar[[1]], contents[[1]])
|
||||
parMat[[1]]<- parMat[[1]][order(parMat[[1]][,1]),]
|
||||
parMat[[2]]<-cbind(calibrationPar[[2]], contents[[2]])
|
||||
parmat[[2]]<- parMat[[2]][order(parMat[[2]][,1]),]
|
||||
|
||||
browser()
|
||||
changeMusoC(filePaths[1],fileOut[1],parMat[[1]] )
|
||||
changeMusoC(filePaths[2],fileOut[2],parMat[[2]] )
|
||||
}
|
||||
|
||||
@ -1,160 +1,116 @@
|
||||
#' isLeapyear
|
||||
#' musoDate
|
||||
#'
|
||||
#'This function tells us if its argument a leapyear or not.
|
||||
#'
|
||||
#'@param year a year
|
||||
#'@usage isLeapyear(year)
|
||||
#'@return TRUE, if leapyear, FALSE if dont.
|
||||
#' @keywords internal
|
||||
isLeapyear <- function(year){
|
||||
##This Boolean function tells us whether the given year is leapyear or not
|
||||
|
||||
if(((year%%4==0)&(year%%100!=0))|(year%%400==0)){
|
||||
return(TRUE)
|
||||
} else {
|
||||
return(FALSE)
|
||||
}
|
||||
}
|
||||
|
||||
#' dayOfMonths
|
||||
#'
|
||||
#'This function gives as a vector which contains the number of the days per each month
|
||||
#'
|
||||
#'@param year a year
|
||||
#'@param corrigated Do you want to handle the leapyears, if yes choose TRUE
|
||||
#'@usage dayOfMonths(year, corrigated=TRUE)
|
||||
#'@return vector with 12 element. First is January, the last is December. All of the vector element represents the number of the days in that specific month
|
||||
#'@keywords internal
|
||||
|
||||
|
||||
|
||||
dayOfMonths <- function(year,corrigated=TRUE){
|
||||
##This function tells us how many days are in the months in the choosen year.
|
||||
|
||||
dayMonths <- c(31,28,31,30,31,30,31,31,30,31,30,31)
|
||||
|
||||
if(corrigated){
|
||||
|
||||
if(isLeapyear(year)==TRUE){
|
||||
dayMonths[2] <-29
|
||||
}
|
||||
}
|
||||
|
||||
return(dayMonths)
|
||||
}
|
||||
|
||||
|
||||
|
||||
#' This function tells us how many days are in the given year.
|
||||
#'
|
||||
#' This function tells us how many days are in the given year.
|
||||
#' @author Roland Hollos
|
||||
#' @keywords internal
|
||||
|
||||
dayOfYears <- function(year, corrigated=TRUE){
|
||||
##This function tells us how many days are in the given year.
|
||||
|
||||
if(corrigated){
|
||||
if(isLeapyear(year)==TRUE){
|
||||
return(366)
|
||||
} else {
|
||||
return(365)
|
||||
}
|
||||
} else {
|
||||
return(365)
|
||||
}
|
||||
|
||||
}
|
||||
|
||||
#' How many days are from the given date and given period length(periodlen)?
|
||||
#'
|
||||
#'How many days are from the given date and given period length(periodlen)?
|
||||
#' @author Roland Hollos
|
||||
#' @keywords internal
|
||||
|
||||
sumDaysOfPeriod <- function(year, periodlen, corrigated=TRUE){
|
||||
##How many days are from the given date and given period length(periodlen)?
|
||||
|
||||
years <- year:(year+periodlen)
|
||||
|
||||
if(corrigated){
|
||||
years100 <-length(which(years%%100==0))
|
||||
years400 <-length(which(years%%400==0))
|
||||
years4 <- length(which(years%%4==0))
|
||||
numberOfLeapdays <- years4-years100+years400
|
||||
days <- periodlen*365+numberOfLeapdays
|
||||
return(days)
|
||||
} else {
|
||||
days <- periodlen*365
|
||||
return(days)
|
||||
}
|
||||
}
|
||||
|
||||
#' Musoleapyear
|
||||
#'
|
||||
#' How many days are from the given date and given period length(periodlen)?
|
||||
#' @author Roland Hollos
|
||||
#' @keywords internal
|
||||
|
||||
musoLeapYears <- function(settings){
|
||||
days <- 365*settings$numyears
|
||||
years <- settings$startyear:(settings$startyear+settings$numyears-1)
|
||||
Leapyears <-unlist(lapply(years,isLeapyear))
|
||||
return(Leapyears)
|
||||
}
|
||||
|
||||
#' It generates BiomeBGC-MuSo dates
|
||||
#'
|
||||
#' It generates all of the day-dates which are between the start and endyear of BiomeBGC-MuSo run.
|
||||
#' How many days are from the given date and given period length(periodlen)?
|
||||
#' @author Roland Hollos
|
||||
#' @param timestep timestep, which can be daily ("d"), monthly ("m"), yearly("y")
|
||||
#' @param settings You have to run the setupMuso function before musoDate. It is its output which contains all of the necessary system variables. It sets the whole environment.
|
||||
#' @param combined If FALSE the output is a vector of 3 string: day, month year, if true, these strings will be concatenated.
|
||||
#' @param corrigated If True it counts with leapyears, else dont.
|
||||
#' @param format This is the format of the date. It can be "en" (dd.mm.yyyy), or "hu" (yyyy.mm.dd)
|
||||
#' @return The exact date-vectors for the BioBGC-MuSo output. You can use this for labelling purpose for example.
|
||||
#' 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, numYears, timestep="d", combined=TRUE, corrigated=TRUE, format="en"){
|
||||
##purpose: generate date label for muso
|
||||
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
|
||||
}
|
||||
|
||||
|
||||
days <- sumDaysOfPeriod(startYear, numYears, corrigated=corrigated)
|
||||
dates <- matrix(rep(NA,days*3),ncol=3)
|
||||
|
||||
dates[1,] <- c(1,1,startYear)
|
||||
for(i in 2:days){
|
||||
dates[i,]<-dates[(i-1),]
|
||||
if((dates[i-1,2]==12)&(dates[i-1,1]==31)){
|
||||
dates[i,] <-c(1,1,(dates[(i-1),3]+1))
|
||||
} else {
|
||||
|
||||
if(dates[i-1,1]==(dayOfMonths(dates[(i-1),3],corrigated=corrigated)[dates[(i-1),2]] )){
|
||||
dates[i,]<-c(1,(dates[(i-1),2]+1),dates[(i-1),3])
|
||||
} else {
|
||||
dates[i,1]<-dates[(i-1),1]+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"))
|
||||
}
|
||||
if(format=="en"){
|
||||
|
||||
} else {
|
||||
if(format=="hu"){
|
||||
dates<-dates[,c(3,2,1)]
|
||||
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 {
|
||||
cat("format is coerced to english, because I don't know what do you mean by:",format)
|
||||
return(format(dates,"%d.%m.%Y"))
|
||||
}
|
||||
}
|
||||
|
||||
if(combined==TRUE){
|
||||
dates <- apply(dates,1,function(x) paste(x,collapse="."))
|
||||
return(dates)
|
||||
}
|
||||
#' 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)
|
||||
}
|
||||
|
||||
return(dates)
|
||||
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)
|
||||
}
|
||||
|
||||
@ -25,6 +25,7 @@
|
||||
#' @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 = 1,
|
||||
@ -38,13 +39,13 @@ plotMuso <- function(settings = NULL, variable = 1,
|
||||
layerPlot = FALSE, colour = "blue",
|
||||
skipSpinup = TRUE, fromData = FALSE,
|
||||
timeFrame = "day", selectYear = NULL,
|
||||
groupFun = mean, separateFile = FALSE, dpi=300){
|
||||
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"
|
||||
}
|
||||
# browser()
|
||||
|
||||
if(is.null(settings)){
|
||||
settings <- setupMuso()
|
||||
}
|
||||
@ -60,13 +61,12 @@ plotMuso <- function(settings = NULL, variable = 1,
|
||||
## logfilename=logfilename,
|
||||
## export=export)
|
||||
|
||||
groupByTimeFrame <- function(data, timeFrame, groupFun){
|
||||
datas <- data %>%
|
||||
group_by(eval(parse(text=timeFrame))) %>%
|
||||
summarize(variable=groupFun(eval(parse(text=variable))))
|
||||
datas[,1]<-as.numeric(unlist(datas[,1]))
|
||||
colnames(datas) <- c("date",variable)
|
||||
datas
|
||||
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){
|
||||
@ -84,20 +84,16 @@ plotMuso <- function(settings = NULL, variable = 1,
|
||||
mutate(date=as.Date(as.character(date),"%d.%m.%Y"))
|
||||
} else {
|
||||
if(!is.element("cum_yieldC_HRV",unlist(settings$outputVars[[1]]))){
|
||||
musoData <- calibMuso(settings,silent = TRUE,skipSpinup=skipSpinup) %>%
|
||||
as.data.frame() %>%
|
||||
rownames_to_column("date") %>%
|
||||
mutate(date2=date,date=as.Date(date,"%d.%m.%Y")) %>%
|
||||
separate(date2,c("day","month","year"),sep="\\.")
|
||||
musoData <- calibMuso(postProcString = postProcString,settings,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 gropFun is not found")})
|
||||
musoData <- tryCatch(groupByTimeFrame(Data=musoData, timeFrame = timeFrame, groupFun = groupFun),
|
||||
error=function(e){stop("The timeFrame or the groupFun is not found")})
|
||||
}} else {
|
||||
musoData <- calibMuso(settings,silent = TRUE,skipSpinup=skipSpinup,parameters = parameters, calibrationPar = calibrationPar,fileToChange = fileToChange) %>%
|
||||
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"),
|
||||
@ -120,7 +116,6 @@ plotMuso <- function(settings = NULL, variable = 1,
|
||||
numVari <- ncol(musoData)-5
|
||||
|
||||
pointOrLineOrPlot <- function(musoData, variableName, plotType="cts", expandPlot=FALSE, plotName=NULL){
|
||||
# browser()
|
||||
if(!expandPlot){
|
||||
if(plotType=="cts"){
|
||||
if(length(variableName)==1){
|
||||
@ -205,7 +200,12 @@ plotMuso <- function(settings = NULL, variable = 1,
|
||||
if(identical(character(0),setdiff(variable,as.character(settings$outputVars[[1]])))){
|
||||
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(!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.")
|
||||
}
|
||||
|
||||
}
|
||||
}
|
||||
|
||||
@ -248,40 +248,54 @@ plotMuso <- function(settings = NULL, variable = 1,
|
||||
#' debugging=FALSE, keepEpc=FALSE,
|
||||
#' logfilename=NULL, aggressive=FALSE,
|
||||
#' leapYear=FALSE, export=FALSE)
|
||||
#' @import ggplot2
|
||||
#' @importFrom ggplot2 ggplot geom_line geom_point aes aes_string labs theme element_blank
|
||||
#' @export
|
||||
plotMusoWithData <- function(csvFile, variable, NACHAR=NA, settings=NULL, sep=",", savePlot=NULL,colour=c("black","blue"), calibrationPar=NULL, parameters=NULL){
|
||||
if(!is.na(NACHAR)){
|
||||
warning("NACHAR is not implemented yet")
|
||||
}
|
||||
if(is.null(settings)){
|
||||
settings <- setupMuso()
|
||||
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. ")
|
||||
}
|
||||
|
||||
numberOfYears <- settings$numYears
|
||||
startYear <- settings$startYear
|
||||
yearVec <- seq(from = startYear, length=numberOfYears,by=1)
|
||||
dataCol<- grep(paste0("^",dataVar,"$"), colnames(mdata))
|
||||
selVar <- grep(modelVar,(settings$dailyVarCodes))+4
|
||||
|
||||
|
||||
data <- read.table(csvFile,header = TRUE, sep = ",") %>%
|
||||
select(variable)
|
||||
|
||||
baseData <- calibMuso(settings,silent=TRUE) %>%
|
||||
as.data.frame() %>%
|
||||
rownames_to_column("date") %>%
|
||||
mutate(date2=date,date=as.Date(date,"%d.%m.%Y"),yearDay=rep(1:365,numberOfYears)) %>%
|
||||
separate(date2,c("day","month","year"),sep="\\.")
|
||||
baseData <- cbind(baseData,data)
|
||||
colnames(baseData)[ncol(baseData)] <- "measuredData"
|
||||
|
||||
p <- baseData %>%
|
||||
ggplot(aes_string("date",variable)) +
|
||||
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(colour=colour[2], aes(date,measuredData)) +
|
||||
labs(y = paste0(variable,"_measured"))+
|
||||
geom_point(data = mesData, colour=colour[2], aes(date,measured)) +
|
||||
labs(y = paste0(selVarName,"_measured"))+
|
||||
theme(axis.title.x = element_blank())
|
||||
if(!is.null(savePlot)){
|
||||
ggsave(savePlot,p)
|
||||
if(!is.null(plotName)){
|
||||
ggsave(plotName,p)
|
||||
return(p)
|
||||
} else {
|
||||
return(p)
|
||||
@ -301,7 +315,7 @@ plotMusoWithData <- function(csvFile, variable, NACHAR=NA, settings=NULL, sep=",
|
||||
#' @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"){
|
||||
compareMuso <- function(settings=NULL,parameters, variable=1, calibrationPar=NULL, fileToChange="epc", skipSpinup=TRUE, timeFrame="day"){
|
||||
|
||||
if(is.null(settings)){
|
||||
settings <- setupMuso()
|
||||
|
||||
@ -198,6 +198,33 @@ setupMuso <- function(executable=NULL,
|
||||
}
|
||||
|
||||
}
|
||||
# browser()
|
||||
# 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<-readLines(mgmConn,n=1)
|
||||
# }
|
||||
# }
|
||||
# management <- list()
|
||||
# Map(function(mt,dm){
|
||||
# if(dm == 1){
|
||||
# management[[mt]] <-
|
||||
# }
|
||||
# },manTypes,doManagement)
|
||||
# manFile <- iniFiles[[2]]
|
||||
# close(mgmConn)
|
||||
# }
|
||||
|
||||
outputName <- character(2)
|
||||
outputName[1] <- basename(unlist(strsplit(iniFiles[[1]][grep("OUTPUT_CONTROL",iniFiles[[1]])+1],"[\ \t]"))[1])
|
||||
outputName[2] <- basename(unlist(strsplit(iniFiles[[2]][grep("OUTPUT_CONTROL",iniFiles[[2]])+1],"[\ \t]"))[1])
|
||||
@ -232,7 +259,7 @@ setupMuso <- function(executable=NULL,
|
||||
## 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]])+2],"[\ \t]"))[1])
|
||||
numData[1] <- numValues * sumDaysOfPeriod(startYear,numYears,corrigated=leapYear)
|
||||
numData[1] <- numValues * numYears * 365 # Have to corrigate leapyears
|
||||
|
||||
numData[2] <- numYears * numValues*12
|
||||
numData[3] <- numYears * numValues
|
||||
|
||||
21
RBBGCMuso/man/alignData.Rd
Normal file
21
RBBGCMuso/man/alignData.Rd
Normal 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}
|
||||
@ -26,8 +26,6 @@ keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
|
||||
|
||||
\item{aggressive}{It deletes every possible modell-outputs from the previous modell runs.}
|
||||
|
||||
\item{leapYear}{Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.}
|
||||
|
||||
\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.}
|
||||
@ -37,6 +35,8 @@ keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
|
||||
\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
|
||||
|
||||
@ -1,20 +0,0 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/musoTime.R
|
||||
\name{dayOfMonths}
|
||||
\alias{dayOfMonths}
|
||||
\title{dayOfMonths}
|
||||
\usage{
|
||||
dayOfMonths(year, corrigated=TRUE)
|
||||
}
|
||||
\arguments{
|
||||
\item{year}{a year}
|
||||
|
||||
\item{corrigated}{Do you want to handle the leapyears, if yes choose TRUE}
|
||||
}
|
||||
\value{
|
||||
vector with 12 element. First is January, the last is December. All of the vector element represents the number of the days in that specific month
|
||||
}
|
||||
\description{
|
||||
This function gives as a vector which contains the number of the days per each month
|
||||
}
|
||||
\keyword{internal}
|
||||
@ -1,15 +0,0 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/musoTime.R
|
||||
\name{dayOfYears}
|
||||
\alias{dayOfYears}
|
||||
\title{This function tells us how many days are in the given year.}
|
||||
\usage{
|
||||
dayOfYears(year, corrigated = TRUE)
|
||||
}
|
||||
\description{
|
||||
This function tells us how many days are in the given year.
|
||||
}
|
||||
\author{
|
||||
Roland Hollos
|
||||
}
|
||||
\keyword{internal}
|
||||
@ -1,18 +0,0 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/musoTime.R
|
||||
\name{isLeapyear}
|
||||
\alias{isLeapyear}
|
||||
\title{isLeapyear}
|
||||
\usage{
|
||||
isLeapyear(year)
|
||||
}
|
||||
\arguments{
|
||||
\item{year}{a year}
|
||||
}
|
||||
\value{
|
||||
TRUE, if leapyear, FALSE if dont.
|
||||
}
|
||||
\description{
|
||||
This function tells us if its argument a leapyear or not.
|
||||
}
|
||||
\keyword{internal}
|
||||
@ -2,35 +2,20 @@
|
||||
% Please edit documentation in R/musoTime.R
|
||||
\name{musoDate}
|
||||
\alias{musoDate}
|
||||
\title{It generates BiomeBGC-MuSo dates}
|
||||
\title{musoDate}
|
||||
\usage{
|
||||
musoDate(
|
||||
startYear,
|
||||
endYears = NULL,
|
||||
numYears,
|
||||
timestep = "d",
|
||||
combined = TRUE,
|
||||
corrigated = TRUE,
|
||||
format = "en"
|
||||
leapYearHandling = FALSE,
|
||||
prettyOut = FALSE
|
||||
)
|
||||
}
|
||||
\arguments{
|
||||
\item{timestep}{timestep, which can be daily ("d"), monthly ("m"), yearly("y")}
|
||||
|
||||
\item{combined}{If FALSE the output is a vector of 3 string: day, month year, if true, these strings will be concatenated.}
|
||||
|
||||
\item{corrigated}{If True it counts with leapyears, else dont.}
|
||||
|
||||
\item{format}{This is the format of the date. It can be "en" (dd.mm.yyyy), or "hu" (yyyy.mm.dd)}
|
||||
|
||||
\item{settings}{You have to run the setupMuso function before musoDate. It is its output which contains all of the necessary system variables. It sets the whole environment.}
|
||||
}
|
||||
\value{
|
||||
The exact date-vectors for the BioBGC-MuSo output. You can use this for labelling purpose for example.
|
||||
}
|
||||
\description{
|
||||
It generates all of the day-dates which are between the start and endyear of BiomeBGC-MuSo run.
|
||||
How many days are from the given date and given period length(periodlen)?
|
||||
This function generates MuSo compatibla dates for the data
|
||||
}
|
||||
\author{
|
||||
Roland Hollos
|
||||
Roland HOLLOS
|
||||
}
|
||||
|
||||
@ -1,15 +0,0 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/musoTime.R
|
||||
\name{musoLeapYears}
|
||||
\alias{musoLeapYears}
|
||||
\title{Musoleapyear}
|
||||
\usage{
|
||||
musoLeapYears(settings)
|
||||
}
|
||||
\description{
|
||||
How many days are from the given date and given period length(periodlen)?
|
||||
}
|
||||
\author{
|
||||
Roland Hollos
|
||||
}
|
||||
\keyword{internal}
|
||||
73
RBBGCMuso/man/optiMuso.Rd
Normal file
73
RBBGCMuso/man/optiMuso.Rd
Normal file
@ -0,0 +1,73 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/calibration.R
|
||||
\name{optiMuso}
|
||||
\alias{optiMuso}
|
||||
\title{optiMuso}
|
||||
\usage{
|
||||
optiMuso(
|
||||
measuredData,
|
||||
parameters = NULL,
|
||||
startDate = NULL,
|
||||
endDate = NULL,
|
||||
formatString = "\%Y-\%m-\%d",
|
||||
leapYearHandling = TRUE,
|
||||
dataVar,
|
||||
outLoc = "./calib",
|
||||
preTag = "cal-",
|
||||
settings = NULL,
|
||||
outVars = NULL,
|
||||
iterations = 30,
|
||||
skipSpinup = TRUE,
|
||||
constrains = NULL,
|
||||
plotName = "calib.jpg",
|
||||
likelihood = function(x, y) { exp(-sqrt(mean((x - y)^2))) },
|
||||
continious,
|
||||
modelVar = 3009,
|
||||
postProcString = NULL
|
||||
)
|
||||
}
|
||||
\arguments{
|
||||
\item{parameters}{b}
|
||||
|
||||
\item{startDate}{d}
|
||||
|
||||
\item{endDate}{e}
|
||||
|
||||
\item{formatString}{a}
|
||||
|
||||
\item{outLoc}{c}
|
||||
|
||||
\item{settings}{e}
|
||||
|
||||
\item{iterations}{c}
|
||||
|
||||
\item{skipSpinup}{a}
|
||||
|
||||
\item{constrains}{d}
|
||||
|
||||
\item{plotName}{u}
|
||||
|
||||
\item{likelihood}{d}
|
||||
|
||||
\item{measuredDataFile}{a}
|
||||
|
||||
\item{sep}{c}
|
||||
|
||||
\item{filterCol}{a}
|
||||
|
||||
\item{filterVal}{b}
|
||||
|
||||
\item{selVar}{c}
|
||||
|
||||
\item{pretag}{a}
|
||||
|
||||
\item{calPar}{a}
|
||||
|
||||
\item{leapYear}{b}
|
||||
}
|
||||
\description{
|
||||
This function calculates the -users specified- likelihood for random model input.
|
||||
}
|
||||
\author{
|
||||
Roland HOLLOS
|
||||
}
|
||||
@ -11,18 +11,18 @@ logfilename=NULL, aggressive=FALSE,
|
||||
leapYear=FALSE, export=FALSE)
|
||||
}
|
||||
\arguments{
|
||||
\item{csvFile}{This specifies the filename of the measurements. It must contain a header. Typically this is a CSV file.}
|
||||
|
||||
\item{variable}{The name of the output variable to plot}
|
||||
|
||||
\item{NACHAR}{This is not implemented yet}
|
||||
|
||||
\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{sep}{This is the separator symbol used in the measurement file (that is supposed to be a delimited text file)}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{variable}{The name of the output variable to plot}
|
||||
|
||||
\item{NACHAR}{This is not implemented yet}
|
||||
|
||||
\item{csvFile}{This specifies the filename of the measurements. It must contain a header. Typically this is a CSV file.}
|
||||
|
||||
\item{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)}
|
||||
|
||||
\item{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).}
|
||||
|
||||
23
RBBGCMuso/man/readObservedData.Rd
Normal file
23
RBBGCMuso/man/readObservedData.Rd
Normal file
@ -0,0 +1,23 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/assistantFunctions.R
|
||||
\name{readObservedData}
|
||||
\alias{readObservedData}
|
||||
\title{readMeasuredMuso}
|
||||
\usage{
|
||||
readObservedData(
|
||||
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
|
||||
)
|
||||
}
|
||||
\description{
|
||||
MuSo data reader
|
||||
}
|
||||
@ -1,15 +0,0 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/musoTime.R
|
||||
\name{sumDaysOfPeriod}
|
||||
\alias{sumDaysOfPeriod}
|
||||
\title{How many days are from the given date and given period length(periodlen)?}
|
||||
\usage{
|
||||
sumDaysOfPeriod(year, periodlen, corrigated = TRUE)
|
||||
}
|
||||
\description{
|
||||
How many days are from the given date and given period length(periodlen)?
|
||||
}
|
||||
\author{
|
||||
Roland Hollos
|
||||
}
|
||||
\keyword{internal}
|
||||
Loading…
Reference in New Issue
Block a user