Many changes and bugfix
This commit is contained in:
parent
52b0f0553b
commit
75f96239e0
@ -12,12 +12,13 @@ export(getyearlymax)
|
||||
export(musoDate)
|
||||
export(musoMapping)
|
||||
export(musoMappingFind)
|
||||
export(musoMont)
|
||||
export(musoMonte)
|
||||
export(musoQuickEffect)
|
||||
export(musoRand)
|
||||
export(musoRandomizer)
|
||||
export(musoSensi)
|
||||
export(normalMuso)
|
||||
export(paramSweep)
|
||||
export(plotMuso)
|
||||
export(plotMusoWithData)
|
||||
export(rungetMuso)
|
||||
@ -34,4 +35,6 @@ import(stats)
|
||||
import(tidyr)
|
||||
import(utils)
|
||||
importFrom(Rcpp,evalCpp)
|
||||
importFrom(digest,digest)
|
||||
importFrom(rmarkdown,render)
|
||||
useDynLib(RBBGCMuso)
|
||||
|
||||
@ -27,6 +27,16 @@ getLogs <- function(outputLoc, outputNames, type = "spinup"){
|
||||
|
||||
|
||||
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(
|
||||
|
||||
@ -46,7 +46,10 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
executable <- settings$executable
|
||||
iniInput <- settings$iniInput
|
||||
epc <- settings$epcInput
|
||||
calibrationPar <- settings$calibrationPar
|
||||
|
||||
if(is.null(calibrationPar)){
|
||||
calibrationPar <- settings$calibrationPar
|
||||
}
|
||||
binaryPlace <- normalizePath(binaryPlace)
|
||||
whereAmI<-getwd()
|
||||
|
||||
@ -314,7 +317,7 @@ calibMuso <- function(settings=NULL, calibrationPar=NULL,
|
||||
|
||||
#cleanupMuso(location=outputLoc,deep = FALSE)
|
||||
if(errorsign==1){
|
||||
return("Modell Failure")
|
||||
stop("Modell Failure")
|
||||
}
|
||||
|
||||
if(timee=="d"){
|
||||
|
||||
0
RBBGCMuso/R/musoExample.R
Executable file → Normal file
0
RBBGCMuso/R/musoExample.R
Executable file → Normal file
@ -15,7 +15,7 @@
|
||||
#' @param keepEpc if you set keepEpc also true, it will save every selected epc file, and put the wrong ones in the WRONGEPC directory.
|
||||
#' @export
|
||||
|
||||
musoMont <- function(settings=NULL,
|
||||
musoMonte <- function(settings=NULL,
|
||||
parameters=NULL,
|
||||
inputDir = "./",
|
||||
outLoc = "./calib",
|
||||
@ -24,44 +24,36 @@ musoMont <- function(settings=NULL,
|
||||
outputType = "moreCsv",
|
||||
fun=mean,
|
||||
varIndex = 1,
|
||||
outVars = NULL,
|
||||
silent = TRUE,
|
||||
skipSpinup = TRUE,
|
||||
skipSpinup = FALSE,
|
||||
debugging = FALSE,
|
||||
keepEpc = FALSE,
|
||||
constrains = NULL,
|
||||
...){
|
||||
|
||||
|
||||
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)
|
||||
getEpcValue <- function(epc, linum){
|
||||
numcord <- numeric(3)
|
||||
numcord[1] <- as.integer(linNum)
|
||||
linNum <- as.integer(round(linNum * 100))
|
||||
numcord[3] <-linNum %% 10 +1
|
||||
numcord[2] <- (linNum %/% 10) %% 10 + 1
|
||||
numcord
|
||||
}
|
||||
|
||||
|
||||
if(is.null(parameters)){
|
||||
parameters <- tryCatch(read.csv("parameters.csv", stringsAsFactor=FALSE), error = function (e) {
|
||||
parameters <- tryCatch(read.csv("parameters.csv"), 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){
|
||||
parameters <- tryCatch(read.csv(parameters), error = function (e){
|
||||
stop("Cannot find neither parameters file neither the parameters matrix")
|
||||
})
|
||||
}}
|
||||
|
||||
outLocPlain <- basename(outLoc)
|
||||
currDir <- getwd()
|
||||
outLocPlain <- basename(outLoc) #Where to put the csv outputs
|
||||
currDir <- getwd() # just to go back, It is unlikely to be used
|
||||
inputDir <- normalizePath(inputDir) # Where are the model files.
|
||||
|
||||
if(!dir.exists(outLoc)){
|
||||
dir.create(outLoc)
|
||||
@ -70,39 +62,44 @@ musoMont <- function(settings=NULL,
|
||||
|
||||
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)
|
||||
}
|
||||
|
||||
parameterNames <- parameters[,1]
|
||||
# settings$calibrationPar <- A[,1] #:LATER:
|
||||
parReal <- parameters[,-1]
|
||||
Otable <- OtableMaker(parReal)
|
||||
A <- as.matrix(Otable[[1]][,c(2,4,5,6)])
|
||||
B <- as.matrix(Otable[[2]])
|
||||
settings$calibrationPar <- A[,1]
|
||||
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,constrains = constrains, iterations = 3000)
|
||||
randVals[[2]]<- randVals[[2]][sample(1:3000,iterations),]
|
||||
} else {
|
||||
randVals <- musoRand(parameters = parameters,constrains = constrains, iterations = iterations)
|
||||
}
|
||||
|
||||
origEpc <- readValuesFromEpc(settings$epc[2],parameters[,2])
|
||||
origEpcFile <- readLines(settings$epcInput[2])
|
||||
|
||||
origEpc <- unlist(lapply(settings$calibrationPar, function (x) {
|
||||
as.numeric(unlist(strsplit(origEpcFile[x],split="[\t ]"))[1])
|
||||
}))
|
||||
|
||||
## Prepare the preservedEpc matrix for the faster
|
||||
## run.
|
||||
|
||||
preservedEpc <- matrix(nrow = (iterations +1 ), ncol = npar)
|
||||
preservedEpc[1,] <- origEpc
|
||||
Otable[[1]][,1] <- (as.character(Otable[[1]][,1]))
|
||||
for(i in parameters[,2]){
|
||||
Otable[[1]][Otable[[1]][,2]==i,1] <- as.character(parameters[parameters[,2]==i,1])
|
||||
}
|
||||
|
||||
colnames(preservedEpc) <- Otable[[1]][,1]
|
||||
preservedEpc <- cbind(preservedEpc,rep(NA,(iterations+1)))
|
||||
colnames(preservedEpc)[(npar+1)] <- "y"
|
||||
## Save the backupEpc, while change the settings
|
||||
## variable and set the output.
|
||||
file.copy(settings$epc[2],"savedEpc",overwrite = TRUE) # do I need this?
|
||||
pretag <- file.path(outLoc,preTag)
|
||||
|
||||
## Creating function for generating separate
|
||||
@ -110,59 +107,49 @@ musoMont <- function(settings=NULL,
|
||||
|
||||
progBar <- txtProgressBar(1,iterations,style=3)
|
||||
|
||||
modelRun <- function(settings, debugging, parameters, keepEpc, silent, skipSpinup){
|
||||
if(!skipSpinup){
|
||||
calibMuso(settings, debugging = debugging, parameters = parameters, keepEpc = keepEpc, silent = silent)
|
||||
} else {
|
||||
normalMuso(settings, debugging = debugging, parameters = parameters, keepEpc = keepEpc, silent = silent)
|
||||
}
|
||||
|
||||
}
|
||||
|
||||
moreCsv <- function(){
|
||||
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(silent=TRUE)
|
||||
write.csv(x=origModellOut, file=paste0(pretag,1,".csv"))
|
||||
|
||||
if(!is.list(fun)){
|
||||
funct <- rep(list(fun), numVars)
|
||||
if(skipSpinup){#skipSpinup is boolean
|
||||
spinupMuso(settings = settings , silent = silent)
|
||||
}
|
||||
|
||||
tmp2 <- numeric(numVars)
|
||||
|
||||
for(j in 1:numVars){
|
||||
tmp2[j]<-funct[[j]](origModellOut[,j])
|
||||
}
|
||||
modellOut[1,]<- tmp2
|
||||
|
||||
for(i in 2:(iterations+1)){
|
||||
tmp <- calibMuso(settings = settings,
|
||||
parameters = randValues[(i-1),],
|
||||
silent= TRUE,
|
||||
skipSpinup = skipSpinup,
|
||||
keepEpc = keepEpc,
|
||||
a <- numeric(iterations+1)
|
||||
tempData <- modelRun(settings=settings,
|
||||
debugging = debugging,
|
||||
outVars = outVars)
|
||||
parameters = origEpc,
|
||||
keepEpc = keepEpc,
|
||||
silent = silent,
|
||||
skipSpinup = skipSpinup)
|
||||
## tempData <- calibMuso(settings, debugging = "stamplog", parameters = origEpc,keepEpc = TRUE,silent = silent)
|
||||
a[1] <- tryCatch(fun(tempData[,varIndex]),error=function(e){return(NA)})
|
||||
preservedEpc[1,(npar+1)] <- a[1]
|
||||
write.table(t(preservedEpc[1,]),row.names = FALSE,"preservedEpc.csv",sep=",")
|
||||
write.csv(x=tempData, file=paste0(preTag,1,".csv"))
|
||||
for(i in 1:iterations){
|
||||
parVar <- musoRandomizer(A,B)[,2]
|
||||
preservedEpc[(i+1),] <- c(parVar,NA)
|
||||
exportName <- paste0(preTag,(i+1),".csv")
|
||||
tempData <- modelRun(settings = settings,
|
||||
debugging = debugging,
|
||||
parameters = parVar,
|
||||
keepEpc = keepEpc,
|
||||
silent=silent,
|
||||
skipSpinup =skipSpinup)
|
||||
write.csv(x=tempData,file=exportName)
|
||||
|
||||
|
||||
for(j in 1:numVars){
|
||||
tmp2[j]<-funct[[j]](tmp[,j])
|
||||
}
|
||||
|
||||
modellOut[i,]<- tmp2
|
||||
write.csv(x=tmp, file=paste0(pretag,(i+1),".csv"))
|
||||
preservedEpc[(i+1),(npar+1)] <- a[i+1]<- tryCatch(fun(tempData[,varIndex]),error=function(e){return(NA)})
|
||||
write.table(t(preservedEpc[(i+1),]),file="preservedEpc.csv",row.names=FALSE,col.names=FALSE, append=TRUE,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)))
|
||||
cat("\n")
|
||||
return(preservedEpc)
|
||||
}
|
||||
|
||||
@ -170,27 +157,26 @@ musoMont <- function(settings=NULL,
|
||||
## csv files for each run
|
||||
|
||||
oneCsv <- function () {
|
||||
stop("This function is not implemented yet")
|
||||
## numDays <- settings$numdata[1]
|
||||
## if(!onDisk){
|
||||
## for(i in 1:iterations){
|
||||
numDays <- settings$numdata[1]
|
||||
if(!onDisk){
|
||||
for(i in 1:iterations){
|
||||
|
||||
## parVar <- apply(parameters,1,function (x) {
|
||||
## runif(1, as.numeric(x[3]), as.numeric(x[4]))})
|
||||
parVar <- apply(parameters,1,function (x) {
|
||||
runif(1, as.numeric(x[3]), as.numeric(x[4]))})
|
||||
|
||||
## preservedEpc[(i+1),] <- parVar
|
||||
## exportName <- paste0(preTag,".csv")
|
||||
## write.csv(parvar,"preservedEpc.csv",append=TRUE)
|
||||
## calibMuso(settings,debugging = "stamplog",
|
||||
## parameters = parVar,keepEpc = TRUE) %>%
|
||||
## {mutate(.,iD = i)} %>%
|
||||
## {write.csv(.,file=exportName,append=TRUE)}
|
||||
## }
|
||||
preservedEpc[(i+1),] <- parVar
|
||||
exportName <- paste0(preTag,".csv")
|
||||
write.csv(parvar,"preservedEpc.csv",append=TRUE)
|
||||
calibMuso(settings,debugging = "stamplog",
|
||||
parameters = parVar,keepEpc = TRUE) %>%
|
||||
{mutate(.,iD = i)} %>%
|
||||
{write.csv(.,file=exportName,append=TRUE)}
|
||||
}
|
||||
|
||||
## return(preservedEpc)
|
||||
## } else {
|
||||
return(preservedEpc)
|
||||
} else {
|
||||
|
||||
## }
|
||||
}
|
||||
}
|
||||
|
||||
netCDF <- function () {
|
||||
@ -202,9 +188,18 @@ musoMont <- function(settings=NULL,
|
||||
"oneCsv" = (a <- oneCsv()),
|
||||
"moreCsv" = (a <- moreCsv()),
|
||||
"netCDF" = (a <- netCDF()))
|
||||
write.csv(a,"preservedEpc.csv")
|
||||
|
||||
|
||||
## Change back the epc file to the original
|
||||
for(i in file.path("./",grep(outLocPlain, list.files(inputDir), invert = TRUE, value = TRUE))){
|
||||
file.remove(i,recursive=TRUE)
|
||||
}
|
||||
for(i in list.files()){
|
||||
file.copy(i,outLoc,recursive=TRUE,overwrite = TRUE)
|
||||
}
|
||||
|
||||
unlink(tmp,recursive = TRUE)
|
||||
setwd(currDir)
|
||||
file.copy("savedEpc",settings$epc[2],overwrite = TRUE)
|
||||
return(a)
|
||||
}
|
||||
|
||||
|
||||
@ -1,205 +0,0 @@
|
||||
#' musoMont
|
||||
#'
|
||||
#' This function does monteCarlo on BiomeBGC-MuSo. It samples specified modell variables in given rangge from conditional multivariate uniform distribution, and runs the modell for each run.
|
||||
#' @author Roland Hollos
|
||||
#' @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 debugging If you set this parameter, you can save every logfile, and RBBGCMuso will select those which contains errors.
|
||||
#' @param keepEpc if you set keepEpc also true, it will save every selected epc file, and put the wrong ones in the WRONGEPC directory.
|
||||
#' @export
|
||||
|
||||
musoMonte <- function(settings=NULL,
|
||||
parameters=NULL,
|
||||
inputDir = "./",
|
||||
outLoc = "./calib",
|
||||
iterations = 10,
|
||||
preTag = "mont-",
|
||||
outputType = "moreCsv",
|
||||
fun=mean,
|
||||
varIndex = 1,
|
||||
silent = TRUE,
|
||||
skipSpinup = FALSE,
|
||||
debugging = FALSE,
|
||||
keepEpc = FALSE,
|
||||
...){
|
||||
|
||||
getEpcValue <- function(epc, linum){
|
||||
numcord <- numeric(3)
|
||||
numcord[1] <- as.integer(linNum)
|
||||
linNum <- as.integer(round(linNum * 100))
|
||||
numcord[3] <-linNum %% 10 +1
|
||||
numcord[2] <- (linNum %/% 10) %% 10 + 1
|
||||
numcord
|
||||
}
|
||||
|
||||
|
||||
if(is.null(parameters)){
|
||||
parameters <- tryCatch(read.csv("parameters.csv"), 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), error = function (e){
|
||||
stop("Cannot find neither parameters file neither the parameters matrix")
|
||||
})
|
||||
}}
|
||||
|
||||
outLocPlain <- basename(outLoc) #Where to put the csv outputs
|
||||
currDir <- getwd() # just to go back, It is unlikely to be used
|
||||
inputDir <- normalizePath(inputDir) # Where are the model files.
|
||||
|
||||
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]
|
||||
parReal <- parameters[,-1]
|
||||
Otable <- OtableMaker(parReal)
|
||||
A <- as.matrix(Otable[[1]][,c(2,4,5,6)])
|
||||
B <- as.matrix(Otable[[2]])
|
||||
settings$calibrationPar <- A[,1]
|
||||
pretag <- file.path(outLoc,preTag)
|
||||
npar <- length(settings$calibrationPar)
|
||||
|
||||
##reading the original epc file at the specified
|
||||
## row numbers
|
||||
|
||||
origEpcFile <- readLines(settings$epcInput[2])
|
||||
|
||||
origEpc <- unlist(lapply(settings$calibrationPar, function (x) {
|
||||
as.numeric(unlist(strsplit(origEpcFile[x],split="[\t ]"))[1])
|
||||
}))
|
||||
|
||||
## Prepare the preservedEpc matrix for the faster
|
||||
## run.
|
||||
preservedEpc <- matrix(nrow = (iterations +1 ), ncol = npar)
|
||||
preservedEpc[1,] <- origEpc
|
||||
Otable[[1]][,1] <- (as.character(Otable[[1]][,1]))
|
||||
for(i in parameters[,2]){
|
||||
Otable[[1]][Otable[[1]][,2]==i,1] <- as.character(parameters[parameters[,2]==i,1])
|
||||
}
|
||||
|
||||
colnames(preservedEpc) <- Otable[[1]][,1]
|
||||
preservedEpc <- cbind(preservedEpc,rep(NA,(iterations+1)))
|
||||
colnames(preservedEpc)[(npar+1)] <- "y"
|
||||
## Save the backupEpc, while change the settings
|
||||
## variable and set the output.
|
||||
file.copy(settings$epc[2],"savedEpc",overwrite = TRUE) # do I need this?
|
||||
pretag <- file.path(outLoc,preTag)
|
||||
|
||||
## Creating function for generating separate
|
||||
## csv files for each run
|
||||
|
||||
progBar <- txtProgressBar(1,iterations,style=3)
|
||||
|
||||
modelRun <- function(settings, debugging, parameters, keepEpc, silent, skipSpinup){
|
||||
if(!skipSpinup){
|
||||
calibMuso(settings, debugging = debugging, parameters = parameters, keepEpc = keepEpc, silent = silent)
|
||||
} else {
|
||||
normalMuso(settings, debugging = debugging, parameters = parameters, keepEpc = keepEpc, silent = silent)
|
||||
}
|
||||
|
||||
}
|
||||
|
||||
moreCsv <- function(){
|
||||
|
||||
if(skipSpinup){#skipSpinup is boolean
|
||||
spinupMuso(settings = settings , silent = silent)
|
||||
}
|
||||
a <- numeric(iterations+1)
|
||||
tempData <- modelRun(settings=settings,
|
||||
debugging = debugging,
|
||||
parameters = origEpc,
|
||||
keepEpc = keepEpc,
|
||||
silent = silent,
|
||||
skipSpinup = skipSpinup)
|
||||
## tempData <- calibMuso(settings, debugging = "stamplog", parameters = origEpc,keepEpc = TRUE,silent = silent)
|
||||
a[1] <- tryCatch(fun(tempData[,varIndex]),error=function(e){return(NA)})
|
||||
preservedEpc[1,(npar+1)] <- a[1]
|
||||
write.table(t(preservedEpc[1,]),row.names = FALSE,"preservedEpc.csv",sep=",")
|
||||
write.csv(x=tempData, file=paste0(preTag,1,".csv"))
|
||||
for(i in 1:iterations){
|
||||
parVar <- musoRandomizer(A,B)[,2]
|
||||
preservedEpc[(i+1),] <- c(parVar,NA)
|
||||
exportName <- paste0(preTag,(i+1),".csv")
|
||||
tempData <- modelRun(settings = settings,
|
||||
debugging = debugging,
|
||||
parameters = parVar,
|
||||
keepEpc = keepEpc,
|
||||
silent=silent,
|
||||
skipSpinup =skipSpinup)
|
||||
write.csv(x=tempData,file=exportName)
|
||||
|
||||
preservedEpc[(i+1),(npar+1)] <- a[i+1]<- tryCatch(fun(tempData[,varIndex]),error=function(e){return(NA)})
|
||||
write.table(t(preservedEpc[(i+1),]),file="preservedEpc.csv",row.names=FALSE,col.names=FALSE, append=TRUE,sep=",")
|
||||
setTxtProgressBar(progBar,i)
|
||||
}
|
||||
cat("\n")
|
||||
return(preservedEpc)
|
||||
}
|
||||
|
||||
## Creating function for generating one
|
||||
## csv files for each run
|
||||
|
||||
oneCsv <- function () {
|
||||
numDays <- settings$numdata[1]
|
||||
if(!onDisk){
|
||||
for(i in 1:iterations){
|
||||
|
||||
parVar <- apply(parameters,1,function (x) {
|
||||
runif(1, as.numeric(x[3]), as.numeric(x[4]))})
|
||||
|
||||
preservedEpc[(i+1),] <- parVar
|
||||
exportName <- paste0(preTag,".csv")
|
||||
write.csv(parvar,"preservedEpc.csv",append=TRUE)
|
||||
calibMuso(settings,debugging = "stamplog",
|
||||
parameters = parVar,keepEpc = TRUE) %>%
|
||||
{mutate(.,iD = i)} %>%
|
||||
{write.csv(.,file=exportName,append=TRUE)}
|
||||
}
|
||||
|
||||
return(preservedEpc)
|
||||
} else {
|
||||
|
||||
}
|
||||
}
|
||||
|
||||
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()))
|
||||
|
||||
## Change back the epc file to the original
|
||||
for(i in file.path("./",grep(outLocPlain, list.files(inputDir), invert = TRUE, value = TRUE))){
|
||||
file.remove(i,recursive=TRUE)
|
||||
}
|
||||
for(i in list.files()){
|
||||
file.copy(i,outLoc,recursive=TRUE,overwrite = TRUE)
|
||||
}
|
||||
|
||||
unlink(tmp,recursive = TRUE)
|
||||
setwd(currDir)
|
||||
file.copy("savedEpc",settings$epc[2],overwrite = TRUE)
|
||||
return(a)
|
||||
}
|
||||
|
||||
@ -1,13 +1,72 @@
|
||||
## #' paramsweep
|
||||
## #'
|
||||
## #' This function update the the muso outputcode-variable matrix
|
||||
## #' @author Roland Hollos
|
||||
## #' @return The outputcode-variable matrix, and also change the global variable
|
||||
## #' @import rmarkdown
|
||||
## #' @export
|
||||
#' 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
|
||||
#' @importFrom digest digest
|
||||
#' @export
|
||||
|
||||
## paramSweep <- function(inputDir="./",parameters=NULL,outputDir=NULL){
|
||||
paramSweep <- function(inputDir="./",
|
||||
parameters=NULL,
|
||||
outputDir=NULL,
|
||||
iterations=10,
|
||||
outVar="daily_gpp",
|
||||
htmlOutName = "paramsweep.html"){
|
||||
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"){
|
||||
system(paste0("start ",htmlOutName))
|
||||
} else {
|
||||
system(paste0("open ",htmlOutName))
|
||||
}
|
||||
}
|
||||
setwd(currDir)
|
||||
|
||||
}
|
||||
|
||||
|
||||
## read.csv(system.file("markdowns","parameters.csv",package="RBBGCMuso"))
|
||||
## }
|
||||
|
||||
@ -8,7 +8,7 @@
|
||||
#' @keywords internal
|
||||
putOutVars <- function(iniFile,outputVars,modifyOriginal = FALSE){
|
||||
ini <- readLines(iniFile)
|
||||
numVarsOriginal <- as.numeric(ini[grep("DAILY_OUTPUT",ini)+1])
|
||||
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 {
|
||||
|
||||
57
RBBGCMuso/R/quickeffect.R
Normal file
57
RBBGCMuso/R/quickeffect.R
Normal file
@ -0,0 +1,57 @@
|
||||
#' musoQuickEffect
|
||||
#'
|
||||
#' This function changes a choosen parameter, and visualize the effect of the change on a chosen variable.
|
||||
#' @author Roland Hollos
|
||||
#' @param settings The settings from setupMuso output
|
||||
#' @param startVal The oroginal parameterValue
|
||||
#' @param endVal The goal value while the function pass
|
||||
#' @param nSteps How many steps 'till you reach the endVal
|
||||
#' @param fileTochange Please choose "epc" "ini" or "both". This is the place of the orininal variable.
|
||||
#' @return An effect plot
|
||||
#' @export
|
||||
|
||||
musoQuickEffect <- function(settings = NULL,calibrationPar = NULL, startVal, endVal, nSteps = 1, fileTochange="epc", outVar, parName = "parVal"){
|
||||
|
||||
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(settings)){
|
||||
settings <- setupMuso()
|
||||
}
|
||||
if(is.null(calibrationPar)){
|
||||
calibrationPar <- settings$calibrationPar
|
||||
}
|
||||
|
||||
parVals <- seq(startVal, endVal, length = (nSteps + 1))
|
||||
a <- do.call(rbind,lapply(parVals, function(parVal){
|
||||
calResult <- tryCatch(calibMuso(settings = settings,calibrationPar = calibrationPar, parameters = parVal, outVars = outVarIndex, silent = TRUE), error = function(e){NA})
|
||||
if(all(is.na(calResult))){
|
||||
b <- cbind(rep(NA,365),parVal)
|
||||
rownames(b) <- tail(musoDate(startYear = settings$startYear, numYears = settings$numYears),365)
|
||||
colnames(b)[1] <- varNames
|
||||
return(b)
|
||||
} else {
|
||||
return(cbind(tail(calResult,365), parVal))
|
||||
}
|
||||
|
||||
}))
|
||||
|
||||
a %<>%
|
||||
tbl_df %>%
|
||||
mutate(date=as.Date(rownames(a),"%d.%m.%Y")) %>%
|
||||
select(date,varNames,parVal)
|
||||
print(ggplot(data = a, aes_string(x= "date", y= varNames))+geom_line(aes(alpha = factor(round(parVal,2)))) + labs(y=varNames, alpha = parName) + scale_alpha_discrete(range=c(0.4,1)))
|
||||
}
|
||||
57
RBBGCMuso/R/quickeffect.R~
Normal file
57
RBBGCMuso/R/quickeffect.R~
Normal file
@ -0,0 +1,57 @@
|
||||
#' musoQuickEffect
|
||||
#'
|
||||
#' This function changes a choosen parameter, and visualize the effect of the change on a chosen variable.
|
||||
#' @author Roland Hollos
|
||||
#' @param settings The settings from setupMuso output
|
||||
#' @param startVal The oroginal parameterValue
|
||||
#' @param endVal The goal value while the function pass
|
||||
#' @param nSteps How many steps 'till you reach the endVal
|
||||
#' @param fileTochange Please choose "epc" "ini" or "both". This is the place of the orininal variable.
|
||||
#' @return An effect plot
|
||||
#' @export
|
||||
|
||||
musoQuickEffect <- function(settings = NULL,calibrationPar = NULL, startVal, endVal, nSteps = 1, fileTochange="epc", outVar, parName = "parVal"){
|
||||
|
||||
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(settings)){
|
||||
settings <- setupMuso()
|
||||
}
|
||||
if(is.null(calibrationPar)){
|
||||
calibrationPar <- settings$calibrationPar
|
||||
}
|
||||
|
||||
parVals <- seq(startVal, endVal, length = (nSteps + 1))
|
||||
a <- do.call(rbind,lapply(parVals, function(parVal){
|
||||
calResult <- tryCatch(calibMuso(settings = settings,calibrationPar = calibrationPar, parameters = parVal, outVars = outVarIndex, silent = TRUE), error = function(e){NA})
|
||||
if(all(is.na(calResult))){
|
||||
b <- cbind(rep(NA,365),parVal)
|
||||
rownames(b) <- tail(musoDate(startYear = settings$startYear, numYears = settings$numYears),365)
|
||||
colnames(b)[1] <- varNames
|
||||
return(b)
|
||||
} else {
|
||||
return(cbind(tail(calResult,365), parVal))
|
||||
}
|
||||
|
||||
}))
|
||||
|
||||
a %<>%
|
||||
tbl_df %>%
|
||||
mutate(date=as.Date(rownames(a),"%d.%m.%Y")) %>%
|
||||
select(date,varNames,parVal)
|
||||
print(ggplot(data = a, aes_string(x= "date", y= varNames))+geom_line(aes(alpha = factor(round(parVal,2)))) + labs(y=varNames, alpha = parName) + scale_alpha_discrete(range=c(0.4,1)))
|
||||
}
|
||||
0
RBBGCMuso/inst/examples/hhs/muso
Executable file → Normal file
0
RBBGCMuso/inst/examples/hhs/muso
Executable file → Normal file
@ -1,41 +0,0 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/musoMont.R
|
||||
\name{musoMont}
|
||||
\alias{musoMont}
|
||||
\title{musoMont}
|
||||
\usage{
|
||||
musoMont(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, ...)
|
||||
}
|
||||
\arguments{
|
||||
\item{settings}{A list of montecarlos environmental variables. It is generated by the setupMuso() function. In default the settings parameter is generated automatically.}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{inputDir}{The location of the input directory, this directory must content a viable pack of all inputfiles and the executable file.}
|
||||
|
||||
\item{iterations}{number of the monteCarlo run.}
|
||||
|
||||
\item{preTag}{It will be the name of the output files. For example preTag-1.csv, pretag-2csv...}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{debugging}{If you set this parameter, you can save every logfile, and RBBGCMuso will select those which contains errors.}
|
||||
|
||||
\item{keepEpc}{if you set keepEpc also true, it will save every selected epc file, and put the wrong ones in the WRONGEPC directory.}
|
||||
|
||||
\item{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)}
|
||||
}
|
||||
\description{
|
||||
This function does monteCarlo on BiomeBGC-MuSo. It samples specified modell variables in given rangge from conditional multivariate uniform distribution, and runs the modell for each run.
|
||||
}
|
||||
\author{
|
||||
Roland Hollos
|
||||
}
|
||||
@ -1,9 +1,14 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/musoMonte.R
|
||||
% Please edit documentation in R/musoMont.R, R/musoMonte.R
|
||||
\name{musoMonte}
|
||||
\alias{musoMonte}
|
||||
\title{musoMonte}
|
||||
\title{musoMont}
|
||||
\usage{
|
||||
musoMonte(settings = NULL, parameters = NULL, inputDir = "./",
|
||||
outLoc = "./calib", iterations = 10, preTag = "mont-",
|
||||
outputType = "moreCsv", fun = mean, varIndex = 1, silent = TRUE,
|
||||
skipSpinup = FALSE, debugging = FALSE, keepEpc = FALSE, ...)
|
||||
|
||||
musoMonte(settings = NULL, parameters = NULL, inputDir = "./",
|
||||
outLoc = "./calib", iterations = 10, preTag = "mont-",
|
||||
outputType = "moreCsv", fun = mean, varIndex = 1, silent = TRUE,
|
||||
@ -31,10 +36,36 @@ musoMonte(settings = NULL, parameters = NULL, inputDir = "./",
|
||||
\item{keepEpc}{if you set keepEpc also true, it will save every selected epc file, and put the wrong ones in the WRONGEPC directory.}
|
||||
|
||||
\item{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)}
|
||||
|
||||
\item{settings}{A list of montecarlos environmental variables. It is generated by the setupMuso() function. In default the settings parameter is generated automatically.}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{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)}
|
||||
|
||||
\item{inputDir}{The location of the input directory, this directory must content a viable pack of all inputfiles and the executable file.}
|
||||
|
||||
\item{iterations}{number of the monteCarlo run.}
|
||||
|
||||
\item{preTag}{It will be the name of the output files. For example preTag-1.csv, pretag-2csv...}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{debugging}{If you set this parameter, you can save every logfile, and RBBGCMuso will select those which contains errors.}
|
||||
|
||||
\item{keepEpc}{if you set keepEpc also true, it will save every selected epc file, and put the wrong ones in the WRONGEPC directory.}
|
||||
}
|
||||
\description{
|
||||
This function does monteCarlo on BiomeBGC-MuSo. It samples specified modell variables in given rangge from conditional multivariate uniform distribution, and runs the modell for each run.
|
||||
|
||||
This function does monteCarlo on BiomeBGC-MuSo. It samples specified modell variables in given rangge from conditional multivariate uniform distribution, and runs the modell for each run.
|
||||
}
|
||||
\author{
|
||||
Roland Hollos
|
||||
|
||||
Roland Hollos
|
||||
}
|
||||
|
||||
30
RBBGCMuso/man/musoQuickEffect.Rd
Normal file
30
RBBGCMuso/man/musoQuickEffect.Rd
Normal file
@ -0,0 +1,30 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/quickeffect.R
|
||||
\name{musoQuickEffect}
|
||||
\alias{musoQuickEffect}
|
||||
\title{musoQuickEffect}
|
||||
\usage{
|
||||
musoQuickEffect(settings = NULL, calibrationPar = NULL, startVal,
|
||||
endVal, nSteps = 1, fileTochange = "epc", outVar,
|
||||
parName = "parVal")
|
||||
}
|
||||
\arguments{
|
||||
\item{settings}{The settings from setupMuso output}
|
||||
|
||||
\item{startVal}{The oroginal parameterValue}
|
||||
|
||||
\item{endVal}{The goal value while the function pass}
|
||||
|
||||
\item{nSteps}{How many steps 'till you reach the endVal}
|
||||
|
||||
\item{fileTochange}{Please choose "epc" "ini" or "both". This is the place of the orininal variable.}
|
||||
}
|
||||
\value{
|
||||
An effect plot
|
||||
}
|
||||
\description{
|
||||
This function changes a choosen parameter, and visualize the effect of the change on a chosen variable.
|
||||
}
|
||||
\author{
|
||||
Roland Hollos
|
||||
}
|
||||
29
RBBGCMuso/man/paramSweep.Rd
Normal file
29
RBBGCMuso/man/paramSweep.Rd
Normal file
@ -0,0 +1,29 @@
|
||||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/parametersweep.R
|
||||
\name{paramSweep}
|
||||
\alias{paramSweep}
|
||||
\title{paramSweep}
|
||||
\usage{
|
||||
paramSweep(inputDir = "./", parameters = NULL, outputDir = NULL,
|
||||
iterations = 10, outVar = "daily_gpp",
|
||||
htmlOutName = "paramsweep.html")
|
||||
}
|
||||
\arguments{
|
||||
\item{inputDir}{The directory which contains the MuSo model's ini files}
|
||||
|
||||
\item{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.}
|
||||
|
||||
\item{outputDir}{The path of the directory where the html file will be generated.}
|
||||
|
||||
\item{iterations}{The number of changes in the parameter}
|
||||
|
||||
\item{outVar}{The name of the output variable to plot, of the MuSo code of it.}
|
||||
|
||||
\item{htmlOutName}{The name of the rendered html file}
|
||||
}
|
||||
\description{
|
||||
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
|
||||
}
|
||||
0
RBBGCMuso_0.5.0.0-0.zip
Executable file → Normal file
0
RBBGCMuso_0.5.0.0-0.zip
Executable file → Normal file
0
RBBGCMuso_0.6.0.0-1.tar.gz
Executable file → Normal file
0
RBBGCMuso_0.6.0.0-1.tar.gz
Executable file → Normal file
0
RBBGCMuso_0.6.0.0-1.zip
Executable file → Normal file
0
RBBGCMuso_0.6.0.0-1.zip
Executable file → Normal file
0
docs/reveal.js/lib/font/league-gothic/league-gothic.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/league-gothic/league-gothic.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/league-gothic/league-gothic.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/league-gothic/league-gothic.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/league-gothic/league-gothic.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/league-gothic/league-gothic.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-italic.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-italic.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-italic.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-italic.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-italic.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-italic.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-regular.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-regular.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-regular.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-regular.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-regular.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-regular.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibold.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibold.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibold.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibold.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibold.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibold.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibolditalic.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibolditalic.eot
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibolditalic.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibolditalic.ttf
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibolditalic.woff
Executable file → Normal file
0
docs/reveal.js/lib/font/source-sans-pro/source-sans-pro-semibolditalic.woff
Executable file → Normal file
0
docs/reveal.js/plugin/markdown/markdown.js
Executable file → Normal file
0
docs/reveal.js/plugin/markdown/markdown.js
Executable file → Normal file
0
docs/reveal.js/plugin/math/math.js
Executable file → Normal file
0
docs/reveal.js/plugin/math/math.js
Executable file → Normal file
2
installWin.R
Executable file → Normal file
2
installWin.R
Executable file → Normal file
@ -2,5 +2,3 @@ basePackages <- c("dplyr","digest","ggplot2","shiny","latex2expr",
|
||||
"magrittr","tibble","tidyr")
|
||||
install.packages(basePackages)
|
||||
install.packages("https://github.com/hollorol/RBBGCMuso/raw/master/RBBGCMuso_0.5.0.0-0.zip", repos = NULL, type = "win.binary")
|
||||
|
||||
copyMu
|
||||
Loading…
Reference in New Issue
Block a user