big changes + version upgrade
This commit is contained in:
parent
9ebaec00e7
commit
b6b700a27a
@ -1,6 +1,6 @@
|
||||
Package: RBBGCMuso
|
||||
Title: An R package for BiomeBGC-MuSo ecosystem modelling
|
||||
Version: 0.4.0.0-2
|
||||
Version: 0.5.0.0-0
|
||||
Authors@R: person("Roland", "Hollo's", , "hollorol@gmail.com", role = c("aut", "cre"))
|
||||
Description: What the package does (one paragraph).
|
||||
Depends: R (>= 2.10)
|
||||
|
||||
@ -22,6 +22,7 @@ musoMonte <- function(settings=NULL,
|
||||
outputType = "moreCsv",
|
||||
fun=mean,
|
||||
varIndex = 1,
|
||||
silent = TRUE,
|
||||
...){
|
||||
|
||||
outLocPlain <- basename(outLoc)
|
||||
@ -75,8 +76,12 @@ musoMonte <- function(settings=NULL,
|
||||
## run.
|
||||
preservedEpc <- matrix(nrow = (iterations +1 ), ncol = npar)
|
||||
preservedEpc[1,] <- origEpc
|
||||
colnames(preservedEpc) <- Otable[[1]][,1]
|
||||
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
|
||||
@ -86,9 +91,10 @@ musoMonte <- function(settings=NULL,
|
||||
|
||||
## Creating function for generating separate
|
||||
## csv files for each run
|
||||
progBar <- txtProgressBar(1,iterations,style=3)
|
||||
moreCsv <- function(){
|
||||
a <- numeric(iterations+1)
|
||||
tempData <- calibMuso(settings, debugging = "stamplog", parameters = origEpc,keepEpc = TRUE)
|
||||
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=",")
|
||||
@ -99,12 +105,15 @@ musoMonte <- function(settings=NULL,
|
||||
exportName <- paste0(preTag,(i+1),".csv")
|
||||
tempData <- calibMuso(settings,debugging = "stamplog",
|
||||
parameters = parVar,
|
||||
keepEpc = TRUE)
|
||||
keepEpc = TRUE,
|
||||
silent=silent)
|
||||
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)
|
||||
}
|
||||
|
||||
|
||||
@ -25,46 +25,19 @@ musoSensi <- function(monteCarloFile = NULL,
|
||||
inputDir = "./",
|
||||
outLoc = "./calib",
|
||||
iterations = 30,
|
||||
preTag = "mount-",
|
||||
preTag = "mont-",
|
||||
outputType = "moreCsv",
|
||||
fun = mean,
|
||||
varIndex = 1,
|
||||
outputFile = "sensitivity.csv",
|
||||
plotName = "sensitivity.jpg"){
|
||||
|
||||
if(is.null(monteCarloFile)){
|
||||
M <- musoMonte(parameters = parameters,
|
||||
settings = settings,
|
||||
inputDir = inputDir,
|
||||
outLoc = outLoc,
|
||||
iterations = iterations,
|
||||
preTag = preTag,
|
||||
outputType = outputType,
|
||||
fun = fun,
|
||||
varIndex = varIndex
|
||||
)
|
||||
doSensi <- function(M){
|
||||
npar <- ncol(M)-1
|
||||
M <- M[which(!is.na(M$y)),]
|
||||
y <- M[,(npar+1)]
|
||||
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^2*w^2)
|
||||
S=numeric(npar)
|
||||
for(i in 1:npar){
|
||||
S[i] <- ((w[i]^2*Sv[i]^2)/overalVar)*100
|
||||
}
|
||||
write.csv(file = outputFile, x = S)
|
||||
names(S)<-varNames
|
||||
barplot(S,las=2)
|
||||
return(S)
|
||||
} else {
|
||||
M <- read.csv(monteCarloFile)
|
||||
|
||||
npar <- ncol(M)-1
|
||||
M <- M[which(!is.na(M$y)),]
|
||||
M <- M[which(!is.na(M[,"y"])),]
|
||||
y <- M[,(npar+1)]
|
||||
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]
|
||||
@ -79,4 +52,24 @@ musoSensi <- function(monteCarloFile = NULL,
|
||||
barplot(S,las=2)
|
||||
return(S)
|
||||
}
|
||||
|
||||
|
||||
|
||||
if(is.null(monteCarloFile)){
|
||||
M <- musoMonte(parameters = parameters,
|
||||
settings = settings,
|
||||
inputDir = inputDir,
|
||||
outLoc = outLoc,
|
||||
iterations = iterations,
|
||||
preTag = preTag,
|
||||
outputType = outputType,
|
||||
fun = fun,
|
||||
varIndex = varIndex
|
||||
)
|
||||
return(doSensi(M))
|
||||
|
||||
} else {
|
||||
M <- read.csv(monteCarloFile)
|
||||
return(doSensi(M))
|
||||
}
|
||||
}
|
||||
|
||||
@ -6,7 +6,7 @@
|
||||
\usage{
|
||||
musoMonte(settings = NULL, parameters, inputDir = "./",
|
||||
outLoc = "./calib", iterations = 10, preTag = "mont-",
|
||||
outputType = "moreCsv", fun = mean, varIndex = 1, ...)
|
||||
outputType = "moreCsv", fun = mean, varIndex = 1, silent = TRUE, ...)
|
||||
}
|
||||
\arguments{
|
||||
\item{settings}{A list of montecarlos environmental variables. It is generated by the setupMuso() function. In default the settings parameter is generated automatically.}
|
||||
|
||||
@ -6,7 +6,7 @@
|
||||
\usage{
|
||||
musoSensi(monteCarloFile = NULL, parameters, settings = NULL,
|
||||
inputDir = "./", outLoc = "./calib", iterations = 30,
|
||||
preTag = "mount-", outputType = "moreCsv", fun = mean, varIndex = 1,
|
||||
preTag = "mont-", outputType = "moreCsv", fun = mean, varIndex = 1,
|
||||
outputFile = "sensitivity.csv", plotName = "sensitivity.jpg")
|
||||
}
|
||||
\arguments{
|
||||
|
||||
Loading…
Reference in New Issue
Block a user