fix musoSensi, musoMonte, musoRand
This commit is contained in:
parent
78781c3103
commit
fdc50f7060
@ -132,18 +132,25 @@ musoMonte <- function(settings=NULL,
|
|||||||
modellOut[1,]<- tmp2
|
modellOut[1,]<- tmp2
|
||||||
|
|
||||||
for(i in 2:(iterations+1)){
|
for(i in 2:(iterations+1)){
|
||||||
tmp <- calibMuso(settings = settings,
|
tmp <- tryCatch(calibMuso(settings = settings,
|
||||||
parameters = randValues[(i-1),],
|
parameters = randValues[(i-1),],
|
||||||
silent= TRUE,
|
silent= TRUE,
|
||||||
skipSpinup = skipSpinup,
|
skipSpinup = skipSpinup,
|
||||||
keepEpc = keepEpc,
|
keepEpc = keepEpc,
|
||||||
debugging = debugging,
|
debugging = debugging,
|
||||||
outVars = outVars)
|
outVars = outVars), error = function (e) NA)
|
||||||
|
|
||||||
|
|
||||||
|
if(!is.na(tmp)){
|
||||||
for(j in 1:numVars){
|
for(j in 1:numVars){
|
||||||
tmp2[j]<-funct[[j]](tmp[,j])
|
tmp2[j]<-funct[[j]](tmp[,j])
|
||||||
}
|
}
|
||||||
|
} else {
|
||||||
|
for(j in 1:numVars){
|
||||||
|
tmp2[j]<-rep(NA,length(settings$outputVars[[1]]))
|
||||||
|
}
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
modellOut[i,]<- tmp2
|
modellOut[i,]<- tmp2
|
||||||
write.csv(x=tmp, file=paste0(pretag,(i+1),".csv"))
|
write.csv(x=tmp, file=paste0(pretag,(i+1),".csv"))
|
||||||
|
|||||||
@ -68,7 +68,7 @@ musoRand <- function(parameters, constrains = NULL, iterations=3000){
|
|||||||
G <- cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0))
|
G <- cbind(matrix(ncol=(Range[1]-1),nrow=numRowsInG,data=0),G,matrix(ncol=(N-Range[2]),nrow=numRowsInG,data=0))
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
return(list(G=G,h=rep(0,nrow(G))))
|
return(list(G=-1*G,h=-1*rep(0,nrow(G))))
|
||||||
}
|
}
|
||||||
|
|
||||||
genMat2 <- function(dep, N){
|
genMat2 <- function(dep, N){
|
||||||
@ -90,7 +90,7 @@ musoRand <- function(parameters, constrains = NULL, iterations=3000){
|
|||||||
|
|
||||||
G <- t(matrix(sign(dep[2,4])*G))
|
G <- t(matrix(sign(dep[2,4])*G))
|
||||||
h <- abs(dep[1,4])
|
h <- abs(dep[1,4])
|
||||||
if(dep[1,"TYPE"]==2){
|
if(dep[1,"TYPE"]==2){ # This is not needed, I'll have to remove the if part, and keep the content
|
||||||
G <- G*(-1)
|
G <- G*(-1)
|
||||||
h <- h*(-1)
|
h <- h*(-1)
|
||||||
}
|
}
|
||||||
|
|||||||
@ -57,7 +57,7 @@ musoSensi <- function(monteCarloFile = NULL,
|
|||||||
varNames<- colnames(M)[1:npar]
|
varNames<- colnames(M)[1:npar]
|
||||||
w <- lm(y~M)$coefficients[-1]
|
w <- lm(y~M)$coefficients[-1]
|
||||||
Sv <- apply(M,2,var)
|
Sv <- apply(M,2,var)
|
||||||
overalVar <- sum(Sv*w^2)
|
overalVar <- sum(Sv*w^2,na.rm = TRUE)
|
||||||
S=numeric(npar)
|
S=numeric(npar)
|
||||||
|
|
||||||
for(i in 1:npar){
|
for(i in 1:npar){
|
||||||
@ -95,6 +95,7 @@ musoSensi <- function(monteCarloFile = NULL,
|
|||||||
varIndex = varIndex,
|
varIndex = varIndex,
|
||||||
skipSpinup = skipSpinup
|
skipSpinup = skipSpinup
|
||||||
)
|
)
|
||||||
|
M <- cbind(seq_along(M[,1]),M)
|
||||||
yInd <- grep("mod.", colnames(M))[varIndex]
|
yInd <- grep("mod.", colnames(M))[varIndex]
|
||||||
parNames <- grep("mod.",colnames(M), invert=TRUE, value = TRUE)
|
parNames <- grep("mod.",colnames(M), invert=TRUE, value = TRUE)
|
||||||
M <- M[,c(grep("mod.", colnames(M),invert=TRUE),yInd)]
|
M <- M[,c(grep("mod.", colnames(M),invert=TRUE),yInd)]
|
||||||
|
|||||||
Binary file not shown.
Loading…
Reference in New Issue
Block a user