Many changey in structiure, and documenting musoMappingFind function

This commit is contained in:
hollorol 2018-06-03 12:39:53 +02:00
parent 471dbcc22a
commit ed79e6a50b
7 changed files with 49 additions and 14 deletions

View File

@ -9,6 +9,7 @@ export(getyearlycum)
export(getyearlymax) export(getyearlymax)
export(musoDate) export(musoDate)
export(musoMapping) export(musoMapping)
export(musoMappingFind)
export(musoMonte) export(musoMonte)
export(musoRandomizer) export(musoRandomizer)
export(musoSensi) export(musoSensi)

View File

@ -12,7 +12,7 @@ getLogs <- function(outputLoc, outputNames, type = "spinup"){
switch(type, switch(type,
"spinup" = return(grep(paste0(outputNames[1], ".log"), list.files(outputLoc), value = TRUE)), "spinup" = return(grep(paste0(outputNames[1], ".log"), list.files(outputLoc), value = TRUE)),
"normal" = return(grep(paste0(outputNames[2], ".log"), list.files(outputLoc), value = TRUE)), "normal" = return(grep(paste0(outputNames[2], ".log"), list.files(outputLoc), value = TRUE)),
"both" = return(grep(paste0(outputNames[2], ".log"), list.files(outputLoc), value = TRUE))) "both" = return(sapply(1:2, function (x){grep(paste0(outputNames[x], ".log"), list.files(outputLoc), value = TRUE)})))
} }

View File

@ -30,6 +30,7 @@ calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logf
##Copy the variables from settings ##Copy the variables from settings
inputLoc <- settings$inputLoc inputLoc <- settings$inputLoc
outputLoc <- settings$outputLoc outputLoc <- settings$outputLoc
outputNames <- settings$outputNames
executable <- settings$executable executable <- settings$executable
iniInput <- settings$iniInput iniInput <- settings$iniInput
epc <- settings$epcInput epc <- settings$epcInput
@ -219,7 +220,7 @@ calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logf
stop("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?") stop("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?")
} else { } else {
stampAndDir(stampDir=EPCS,wrongDir=WRONGEPC,names=epc,type="general",errorsign=errorsign,logfiles=logfiles) stampAndDir(stampDir=EPCS, wrongDir=WRONGEPC, names=epc, type="general", errorsign=errorsign, logfiles=logfiles)
} }
} }

View File

@ -37,6 +37,17 @@ musoMapping <- function(code, mapData=NULL){
} }
} }
#' musoMappingFind
#'
#' musoMapping can give us the name of a muso outputcode
#' @author Roland Hollos
#' @param variable If null return the whole mapping, else search a variable code
#' @return The code of th specific name
#' @export
#' @usage musoMapping(code, mapData=NULL)
musoMappingFind <- function(variable=NULL){ musoMappingFind <- function(variable=NULL){
if(is.null(variable)){ if(is.null(variable)){
return(mMapping) return(mMapping)

21
RBBGCMuso/R/runModell.R Normal file
View File

@ -0,0 +1,21 @@
## runModell <- function(executable,)
## {
## if(silent){#silenc mode
## if(Linuxp){
## #In this case, in linux machines
## tryCatch(system(paste(executable,iniInput[1],"> /dev/null",sep=" ")),
## error= function (e){stop("Cannot run the modell-check the executable!")})
## } else {
## #In windows machines there is a show.output.on.console option
## tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE),
## error= function (e){stop("Cannot run the modell-check the executable!")})
## }
## } else {
## system(paste(executable,iniInput[1],sep=" "))
## }
## }

View File

@ -230,9 +230,9 @@ setupMuso <- function(executable=NULL,
writeLines(iniFiles[[1]],iniInput[1]) writeLines(iniFiles[[1]],iniInput[1])
writeLines(iniFiles[[2]],iniInput[2]) writeLines(iniFiles[[2]],iniInput[2])
suppressWarnings(file.remove(paste0(file.path(outputLoc,outputNames[1]),".log"))) suppressWarnings(file.remove(paste0(file.path(outputLoc,outputName[1]),".log")))
## I use file.path additionally because We do not know if outputLoc ends or not to "/" ## I use file.path additionally because We do not know if outputLoc ends or not to "/"
suppressWarnings(file.remove(paste0(file.path(outputLoc,outputNames[2]),".log"))) suppressWarnings(file.remove(paste0(file.path(outputLoc,outputName[2]),".log")))
settings = list(executable = executable, settings = list(executable = executable,
calibrationPar = calibrationPar, calibrationPar = calibrationPar,

View File

@ -25,6 +25,7 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
##Copy the variables from settings ##Copy the variables from settings
inputLoc <- settings$inputLoc inputLoc <- settings$inputLoc
outputLoc <- settings$outputLoc outputLoc <- settings$outputLoc
outputNames <- settings$outputNames
executable <- settings$executable executable <- settings$executable
iniInput <- settings$iniInput iniInput <- settings$iniInput
epc <- settings$epcInput epc <- settings$epcInput
@ -52,8 +53,10 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
## changemulline(filename=epc[1], calibrationPar, parameters)} ## changemulline(filename=epc[1], calibrationPar, parameters)}
if(!is.null(parameters)){ if(!is.null(parameters)){
switch(fileToChange, switch(fileToChange,
"epc"=(changemulline(filename=epc[2],calibrationPar,parameters)), "epc"=tryCatch(changemulline(filename=epc[2],calibrationPar,parameters),
"ini"=(changemulline(filename=iniInput[2],calibrationPar,parameters)), error = function (e) {stop("Cannot change the epc file")}),
"ini"=tryCatch(changemulline(filename=iniInput[2],calibrationPar,parameters),
error = function (e) {stop("Cannot change the ini file")}),
"both"=(stop("This option is not implemented yet, please choose epc or ini")) "both"=(stop("This option is not implemented yet, please choose epc or ini"))
) )
} }
@ -64,18 +67,17 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
setwd(inputLoc) setwd(inputLoc)
##Run the spinup ##Run the spinup
if(silent){#silenc mode if(silent){#silenc mode
if(Linuxp){ if(Linuxp){
#In this case, in linux machines #In this case, in linux machines
system(paste(executable,iniInput[1],"> /dev/null",sep=" ")) tryCatch(system(paste(executable,iniInput[1],"> /dev/null",sep=" ")),
error= function (e){stop("Cannot run the modell-check the executable!")})
} else { } else {
#In windows machines there is a show.output.on.console option #In windows machines there is a show.output.on.console option
system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE)} tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE),
} else { error= function (e){stop("Cannot run the modell-check the executable!")})
system(paste(executable,iniInput[1],sep=" "))} }}
############################################### ###############################################
#############LOG SECTION####################### #############LOG SECTION#######################
############################################### ###############################################
@ -197,4 +199,3 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
} }