Many changes and work...

This commit is contained in:
hollorol 2018-06-22 00:17:14 +02:00
parent ed79e6a50b
commit 1de976fdf3
16 changed files with 397 additions and 453 deletions

View File

@ -4,7 +4,6 @@ export(OtableMaker)
export(calibMuso) export(calibMuso)
export(cleanupMuso) export(cleanupMuso)
export(corrigMuso) export(corrigMuso)
export(file.path2)
export(getyearlycum) export(getyearlycum)
export(getyearlymax) export(getyearlymax)
export(musoDate) export(musoDate)
@ -13,6 +12,7 @@ export(musoMappingFind)
export(musoMonte) export(musoMonte)
export(musoRandomizer) export(musoRandomizer)
export(musoSensi) export(musoSensi)
export(normalMuso)
export(plotMuso) export(plotMuso)
export(rungetMuso) export(rungetMuso)
export(setupMuso) export(setupMuso)

View File

@ -1,256 +0,0 @@
#' setupMuso
#'
#' This funcion is fundamental for the BiomBGC-MuSo modell related functions like spinupMuso, normalMuso, rungetMuso, because it sets the modells environment.
#'
#' @author Roland Hollos
#' @param parallel Do you want to run multiple modell paralelly, if yes, set this variable to TRUE
#' @param executable This parameter stores the place of the modell-executable file. In normal usage, you don't have to be set this, because a RBBgcmuso package contains allways the latest modell executable. In spite of this, if you would like to use this package for modell development or just want to use different models (for example for comparison), you will find it useful
#' @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 outputLoc Where should the modell puts its outputs. You should give a location for it via this variable, for example: outputLoc="/place/of/the/outputs/"
#' @param inputLoc Usually it is the root directory, where you put the iniFiles for the modell
#' @param metInput Via metInput parameter, you can tell the modell where are the meteorological files. As default it reads this from the iniFiles.
#' @param CO2Input Via CO2 parameter, you can tell the modell where are the CO2 data files. As default it reads this from the iniFiles.
#' @param plantInput Via planting parameter, you can tell the modell where are the data files, which contains the planting informations. As default it reads this from the iniFiles.
#' @param thinInput Via thining parameter, you can tell the modell where are the data files, which contains the thining informations. As default it reads this from the iniFiles.
#' @param mowInput Via mowing parameter, you can tell the modell where are the data files, which contains the mowing informations. As default it reads this from the iniFiles.
#' @param grazInput Via grazing parameter, you can tell the modell where are the data files, which contains the grazing informations. As default it reads this from the iniFiles.
#' @param harvInput Via harvesting parameter, you can tell the modell where are the data files, which contains the harvesting informations. As default it reads this from the iniFiles.
#' @param plougInput Via ploughing parameter, you can tell the modell where are the data files, which contains the ploughing informations. As default it reads this from the iniFiles.
#' @param fertInput Via fertilizing parameter, you can tell the modell where are the fertilizing data files, which contains the fertilizing informations. As default it reads this from the iniFiles.
#' @param irrInput Via irrigation parameter, you can tell the modell where are the data files, which contains the irrigation informations. As default it reads this from the iniFiles.
#' @param nitInput Via this parameter, you can tell the modell where are the NO2 data files. As default it reads this from the iniFiles.
#' @param iniInput Via this parameter, you can tell the modell where are the ini files. As default it reads this from the iniFiles.
#' @param epcInput Via this parameter, you can tell the modell where are the epc data files. As default it reads this from the iniFiles.
#' @usage setupMuso(executable=NULL, parallel = F, calibrationPar =c(1),
#' outputLoc=NULL, inputLoc=NULL,
#' metInput=NULL, CO2Input=NULL,
#' plantInput=NULL, thinInput=NULL,
#' mowInput=NULL, grazInput=NULL,
#' harvInput=NULL, plougInput=NULL,
#' fertInput=NULL, irrInput=NULL,
#' nitInput=NULL, iniInput=NULL, epcInput=NULL)
#' @return The output is a the modell setting list wich contains the following elements:
#' executable, calibrationPar, outputLoc, outputName, inputLoc, iniInput, metInput, epcInput,thinInput,CO2Input, mowInput, grazInput, harvInput, plougInput, fertInput, irrInput, nitInput, inputFiles, numData, startyear, numYears, outputVars
#' @export
setupMuso <- function(executable=NULL,
parallel = F,
calibrationPar =c(1),
outputLoc=NULL,
inputLoc=NULL,
metInput=NULL,
CO2Input=NULL,
plantInput=NULL,
thinInput=NULL,
mowInput=NULL,
grazInput=NULL,
harvInput=NULL,
plougInput=NULL,
fertInput=NULL,
irrInput=NULL,
nitInput=NULL,
iniInput=NULL,
epcInput=NULL,
mapData=NULL,
leapYear=FALSE,
version=5
){
Linuxp <-(Sys.info()[1]=="Linux")
writep <- 0
if(is.null(mapData)&version==4){
mData <- mMapping4
}
inputParser <- function(string,fileName,counter,value=TRUE){
unlist(strsplit(grep(string,fileName,value=TRUE),"[\ \t]"))[counter]
}
outMaker <- function(inputVar,grepString,filep){
tempVar <- eval(parse(text=inputVar))
if(is.null(tempVar)){
writep <<- writep+1
if(filep)
{
tempVar["spinup"] <- paste0(inputLoc,inputParser(string=grepString,fileName=iniFiles$spinup,counter=1,value=TRUE))
tempVar["normal"] <- paste0(inputLoc,inputParser(string=grepString,fileName=iniFiles$normal,counter=1,value=TRUE))
} else {
tempVar["spinup"] <- inputParser(string=grepString,fileName=iniFiles$spinup,counter=1,value=TRUE)
tempVar["normal"] <- inputParser(string=grepString,fileName=iniFiles$normal,counter=1,value=TRUE)
}
} else {
iniFiles$spinup[grep(grepString,iniFiles$spinup)] <<- paste0(tempVar[1],"\t ",grepString)
if(length(tempVar)==2){
iniFiles$normal[grep(" grepString",iniFiles$normal)] <<- paste0(tempVar[2],"\t ",grepString)
}
}
return(tempVar)
}
if(is.null(inputLoc)){
inputLoc<- "./"}
#iniChangedp <- FALSE
if(is.null(iniInput)){
spinups<-grep("s.ini$",list.files(inputLoc),value=TRUE)
normals<-grep("n.ini$",list.files(inputLoc),value=TRUE)
if(length(spinups)==1){
iniInput[1]<-file.path(inputLoc,spinups)
} else {stop("There are multiple or no spinup ini files, please choose")}
if(length(normals)==1){
iniInput[2]<-file.path(inputLoc,normals)
} else {stop("There are multiple or no normal ini files, please choose")}
}
##read the ini files for the further changes
iniFiles<-lapply(iniInput, function (x) readLines(x,-1))
iniFiles[[1]] <- gsub("\\","/", iniFiles[[1]],fixed=TRUE) #replacing \ to /
iniFiles[[2]] <- gsub("\\","/", iniFiles[[2]],fixed=TRUE) #replacing \ to /
names(iniFiles) <- c("spinup","normal")
inputs <- lapply(1:nrow(grepHelper), function (x) {
outMaker(grepHelper[x,1],grepHelper[x,2],grepHelper[x,3])
})
names(inputs) <- grepHelper$inputVar
## grepHelper is in sysdata.rda it is a table like this:
##
## inputVar string isFile
## 1 epcInput EPC file name TRUE
## 2 metInput met file name TRUE
## 3 CO2Input CO2 file TRUE
## 4 nitInput N-dep file TRUE
## 5 thinInput do THINNING FALSE
## 6 plantInput do PLANTING FALSE
## 7 mowInput do MOWING FALSE
## 8 grazInput do GRAZING FALSE
## 9 harvInput do HARVESTING FALSE
## 10 plougInput do PLOUGHING FALSE
## 11 fertInput do FERTILIZING FALSE
## 12 irrInput do IRRIGATION FALSE
# return(inputs) debug element
if(is.null(mapData)){
c<-grep("DAILY_OUTPUT",iniFiles[[2]])+1
numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1])
dailyVarCodes<-iniFiles[[2]][(c+1):(c+numVar)]
dailyVarnames<-lapply(dailyVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1]))
c<-grep("ANNUAL_OUTPUT",iniFiles[[2]])+1
numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1])
annualVarCodes<-iniFiles[[2]][(c+1):(c+numVar)]
annualVarnames<-lapply(annualVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1]))
outputVars<-list(dailyVarnames,annualVarnames)} else {
c<-grep("DAILY_OUTPUT",iniFiles[[2]])+1
numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1])
dailyVarCodes<-iniFiles[[2]][(c+1):(c+numVar)]
dailyVarnames<-lapply(dailyVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1],mapData))
c<-grep("ANNUAL_OUTPUT",iniFiles[[2]])+1
numVar<-as.numeric(unlist(strsplit(iniFiles[[2]][c],"[\ \t]"))[1])
annualVarCodes<-iniFiles[[2]][(c+1):(c+numVar)]
annualVarnames<-lapply(annualVarCodes, function(x) musoMapping(unlist(strsplit(x,"[\ \t]"))[1],mapData))
outputVars<-list(dailyVarnames,annualVarnames)
}
if(is.null(executable)){
if(Linuxp){
executable<-file.path(inputLoc,"muso")
} else {
executable<-file.path(inputLoc,"muso.exe")
}
} else {
file.copy(executable,inputLoc)
}
outputName <- unlist(strsplit(iniFiles[[2]][grep("OUTPUT_CONTROL",iniFiles[[2]])+1],"[\ \t]"))[1]
## outputName <- unlist(strsplit(grep("output",grep("prefix",iniFiles[[2]],value=TRUE),value=TRUE),"[\ \t]"))[1]
##THIS IS AN UGLY SOLUTION, WHICH NEEDS AN UPGRADE!!! FiXED (2017.09.11)
## outputName <- unlist(strsplit(grep("prefix for output files",iniFiles[[2]],value=TRUE),"[\ \t]"))[1]
if(is.null(outputName)){
stop("I cannot find outputName in your default ini file \n Please make sure that the line wich contains the name also contains the prefix and the outmut keywords!")
}
## outputName<-unlist(read.table(iniInput[2],skip=93,nrows = 1))[1]
if(is.null(outputLoc)){
## outputLoc<-paste((rev(rev(unlist(strsplit(outputName,"/")))[-1])),collapse="/")
outputLoc <- dirname(outputName)
}
inputFiles<-c(iniInput,epcInput,metInput)
numData<-rep(NA,3)
numYears <- as.numeric(unlist(strsplit(grep("simulation years",iniFiles[[2]],value=TRUE),"[\ \t]"))[1])
## numYears<-unlist(read.table(iniInput[2],skip = 14,nrows = 1)[1])
numValues <- as.numeric(unlist(strsplit(grep("number of daily output variables",iniFiles[[2]],value=TRUE),"[\ \t]"))[1])
## numValues will be replaced to numVar
## numValues<-unlist(read.table(iniInput[2],skip=102,nrows = 1)[1])
startyear <- as.numeric(unlist(strsplit(grep("first simulation year",iniFiles[[2]],value=TRUE),"[\ \t]"))[1])
numData[1] <- numValues * sumDaysOfPeriod(startyear,numYears,corrigated=leapYear)
numData[2] <- numYears * numValues*12
numData[3] <- numYears * numValues
##Writing out changed ini-file
writeLines(iniFiles[[1]],iniInput[1])
writeLines(iniFiles[[2]],iniInput[2])
settings = list(executable = executable,
calibrationPar = calibrationPar,
outputLoc=outputLoc,
outputNames=outputName,
inputLoc=inputLoc,
iniInput=iniInput,
metInput=inputs$metInput,
epcInput=inputs$epcInput,
thinInput=inputs$thinInput,
CO2Input=inputs$CO2Input,
mowInput=inputs$mowInput,
grazInput=inputs$grazInput,
harvInput=inputs$harvInput,
plougInput=inputs$plougInput,
fertInput=inputs$fertInput,
irrInput=inputs$irrInput,
nitInput=inputs$nitInput,
inputFiles=inputFiles,
numData=numData,
startyear=startyear,
numYears=numYears,
outputVars=outputVars
)
if(writep!=nrow(grepHelper)){
writeLines(iniFiles[[1]],iniInput[[1]])
if(epcInput[1]!=epcInput[2]){ #Change need here
writeLines(iniFiles[[2]],iniInput[[2]])
}
}
return(settings)
}

View File

@ -26,8 +26,24 @@ getLogs <- function(outputLoc, outputNames, type = "spinup"){
#'@keywords internal #'@keywords internal
readErrors <- function(outputLoc, logfiles){ readErrors <- function(outputLoc, logfiles, type = "both"){
return(as.numeric(as.vector(lapply(paste(outputLoc,logfiles,sep = "/"),function(x) tail(readLines(x,-1),1)))) ) switch( type,
"both" = return(
as.numeric(
as.vector(
lapply(paste(outputLoc,logfiles,sep = "/"),
function(x) {
tail(readLines(x,-1),1)
}
)
)
)
),
"spinup" = print("spinup"),
"normal" = return(
abs(as.numeric(tail(readLines(file.path(outputLoc,logfiles),-1),1))-1)
)
)
} }
#' getOutFiles #' getOutFiles

View File

@ -1,10 +1,10 @@
#' calibMuso #' calibMuso
#' #'
#' This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a very structured way. #' This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a well-structured way.
#' #'
#' @author Roland Hollos #' @author Roland Hollos
#' @param settings You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment #' @param settings You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment
#' @param timee The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly #' @param timee The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly. I recommend to use daily data, the yearly and monthly data is not well-tested yet.
#' @param debugging If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles #' @param debugging If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles
#' @param keepEpc If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory. #' @param keepEpc If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.
#' @param export if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv. #' @param export if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.
@ -13,18 +13,24 @@
#' @param parameters In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4) #' @param parameters In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4)
#' @param logfilename If you want to set a specific name for your logfiles you can set this via logfile parameter #' @param logfilename If you want to set a specific name for your logfiles you can set this via logfile parameter
#' @param leapYear Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled. #' @param leapYear Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.
#' @param 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.
#' @param binaryPlace The place of the binary output files.
#' @param fileToChange You can change any line of the epc or the ini file, you just have to specify with this variable which file you van a change. Two options possible: "epc", "ini"
#' @return No return, outputs are written to file #' @return No return, outputs are written to file
#' @usage calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, #' @usage calibMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL,
#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE) #' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
#' @import utils #' @import utils
#' @export #' @export
calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE,keepBinary=FALSE, binaryPlace="./", fileToChange="epc"){ calibMuso <- function(settings=NULL,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL, keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE,keepBinary=FALSE, binaryPlace="./", fileToChange="epc"){
########################################################################## ##########################################################################
###########################Set local variables and places######################## ###########################Set local variables and places########################
######################################################################## ########################################################################
if(is.null(settings)){
settings <- setupMuso()
}
Linuxp <-(Sys.info()[1]=="Linux") Linuxp <-(Sys.info()[1]=="Linux")
##Copy the variables from settings ##Copy the variables from settings
@ -90,9 +96,13 @@ calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logf
switch(fileToChange, switch(fileToChange,
"epc"=tryCatch(changemulline(filename=epc[2],calibrationPar,parameters), "epc"=tryCatch(changemulline(filename=epc[2],calibrationPar,parameters),
error= function (e) {stop("Cannot change the epc file")}), error= function (e){
setwd(whereAmI)
stop("Cannot change the epc file")}),
"ini"=tryCatch(changemulline(filename=iniInput[2],calibrationPar,parameters), "ini"=tryCatch(changemulline(filename=iniInput[2],calibrationPar,parameters),
error= function (e) {stop("Cannot change the ini file")}), error= function (e){
setwd((whereAmI))
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"))
) )
} }
@ -107,11 +117,15 @@ calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logf
if(Linuxp){ if(Linuxp){
#In this case, in linux machines #In this case, in linux machines
tryCatch(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!")}) error= function (e){
setwd((whereAmI))
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
tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE), tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE),
error= function (e){stop("Cannot run the modell-check the executable!")}) error= function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")})
} }
} else { } else {
@ -128,8 +142,11 @@ calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logf
stampnum<-stamp(EPCS) stampnum<-stamp(EPCS)
lapply(epc,function (x) file.copy(from = x ,to=paste(EPCS,"/",(stampnum+1),"-", basename(x),sep=""))) lapply(epc,function (x) file.copy(from = x ,to=paste(EPCS,"/",(stampnum+1),"-", basename(x),sep="")))
lapply(epc, function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",basename(x),sep=""), to=WRONGEPC)) lapply(epc, function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",basename(x),sep=""), to=WRONGEPC))
setwd(whereAmI)
stop("Modell Failure")
} }
return("Modell Failure") #in that case the modell did not create even a logfile setwd(whereAmI)
stop("Modell Failure") #in that case the modell did not create even a logfile
} }
if(length(logspinup)>1){ if(length(logspinup)>1){
@ -156,15 +173,21 @@ calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logf
if(silent){ if(silent){
if(Linuxp){ if(Linuxp){
tryCatch(system(paste(executable,iniInput[2],"> /dev/null",sep=" ")), tryCatch(system(paste(executable,iniInput[2],"> /dev/null",sep=" ")),
error =function (e) {stop("Cannot run the modell-check the executable!")}) error =function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")})
} else { } else {
tryCatch(system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE), tryCatch(system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE),
error =function (e) {stop("Cannot run the modell-check the executable!")} ) error =function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")} )
} }
} else { } else {
tryCatch(system(paste(executable,iniInput[2],sep=" ")), tryCatch(system(paste(executable,iniInput[2],sep=" ")),
error =function (e) {stop("Cannot run the modell-check the executable!")}) error =function (e){
setwd((whereAmI))
stop("Cannot run the modell-check the executable!")})
} }
@ -172,21 +195,33 @@ calibMuso <- function(settings,parameters=NULL, timee="d", debugging=FALSE, logf
switch(timee, switch(timee,
"d"=(Reva <- tryCatch(getdailyout(settings), "d"=(Reva <- tryCatch(getdailyout(settings),
error = function (e) {stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})), error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"m"=(Reva <- tryCatch(getmonthlyout(settings), "m"=(Reva <- tryCatch(getmonthlyout(settings),
error = function (e) {stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})), error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"y"=(Reva <- tryCatch(getyearlyout(settings), "y"=(Reva <- tryCatch(getyearlyout(settings),
error = function (e) {stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})) error = function (e){
setwd((whereAmI))
stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")}))
) )
if(keepBinary){ if(keepBinary){
possibleNames <- getOutFiles(outputLoc = outputLoc,outputNames = outputNames) possibleNames <- tryCatch(getOutFiles(outputLoc = outputLoc,outputNames = outputNames),
error=function (e){
setwd((whereAmI))
stop("Cannot find output files")})
stampAndDir(outputLoc = outputLoc,names = possibleNames,stampDir=binaryPlace,type="output") stampAndDir(outputLoc = outputLoc,names = possibleNames,stampDir=binaryPlace,type="output")
} }
} }
logfiles <- getLogs(outputLoc,outputNames,type="both") logfiles <- tryCatch(getLogs(outputLoc,outputNames,type="both"),
error = function (e){
setwd(whereAmI)
"Cannot find log files, something went wrong"})
## list.files(outputLoc)[grep("log$",list.files(outputLoc))]#creating a vector for logfilenames ## list.files(outputLoc)[grep("log$",list.files(outputLoc))]#creating a vector for logfilenames
############################################### ###############################################

View File

@ -16,10 +16,10 @@ cleanupMuso <- function(location=NULL, simplicity=TRUE,deep=FALSE){
location<-"./" location<-"./"
} }
logDir<-file.path2(location,"LOG") logDir<-file.path(location,"LOG")
errDir<-file.path2(location,"ERROR") errDir<-file.path(location,"ERROR")
epcDir<-file.path2(location,"EPCS") epcDir<-file.path(location,"EPCS")
wroDir<-file.path2(location,"WRONGEPC") wroDir<-file.path(location,"WRONGEPC")
if(deep){ if(deep){

View File

@ -1,21 +1,52 @@
normalMuso<- function(settings,parameters=NULL,timee="d",debugging=FALSE,logfilename=NULL,keepEpc=FALSE, export=FALSE,silent=FALSE,aggressive=FALSE,leapYear=FALSE, binaryPlace="./",fileToChange="epc"){ #' normalMuso
#'
#' This function changes the epc file and after that runs the BBGC-MuSo model in normal phase and reads in its outputfile in a well-structured way.
#'
#' @author Roland Hollos
#' @param settings You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment
#' @param timee The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly. I recommend to use daily data, the yearly and monthly data is not well-tested yet.
#' @param debugging If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles
#' @param keepEpc If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.
#' @param export if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.
#' @param silent If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed.
#' @param aggressive It deletes every possible modell-outputs from the previous modell runs.
#' @param parameters In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4)
#' @param logfilename If you want to set a specific name for your logfiles you can set this via logfile parameter
#' @param leapYear Should the function do a leapyear correction on the outputdata? If TRUE, then the 31.12 day will be doubled.
#' @param 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.
#' @param binaryPlace The place of the binary output files.
#' @param fileToChange You can change any line of the epc or the ini file, you just have to specify with this variable which file you van a change. Two options possible: "epc", "ini"
#' @return The simunation output matrix, where the columns are the choosen variables and each row is a day/month/year data.
#' @usage normalMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL,
#' keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
#' @import utils
#' @export
normalMuso<- function(settings=NULL,parameters=NULL,timee="d",debugging=FALSE,logfilename=NULL,keepEpc=FALSE, export=FALSE,silent=FALSE,aggressive=FALSE,leapYear=FALSE, binaryPlace=NULL,fileToChange="epc", keepBinary=FALSE){
########################################################################## ##########################################################################
###########################Set local variables######################## ###########################Set local variables########################
######################################################################## ########################################################################
if(is.null(settings)){
settings <- setupMuso()
}
Linuxp <-(Sys.info()[1]=="Linux") Linuxp <-(Sys.info()[1]=="Linux")
##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
calibrationPar <- settings$calibrationPar calibrationPar <- settings$calibrationPar
whereAmI<-getwd() whereAmI<-getwd()
if(is.null(binaryPlace)){
binaryPlace <- outputLoc
}
@ -24,7 +55,7 @@ normalMuso<- function(settings,parameters=NULL,timee="d",debugging=FALSE,logfile
if(!is.null(parameters)){ if(!is.null(parameters)){
switch(fileToChange, switch(fileToChange,
"epc"=(changemulline(filename=epc[2],calibrationPar,parameters)), "epc"=(changemulline(filename=epc[2],calibrationPar,parameters)), #(:TODO: trycatch /p4/)
"ini"=(changemulline(filename=iniInput[2],calibrationPar,parameters)), "ini"=(changemulline(filename=iniInput[2],calibrationPar,parameters)),
"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"))
) )
@ -35,32 +66,65 @@ normalMuso<- function(settings,parameters=NULL,timee="d",debugging=FALSE,logfile
setwd(inputLoc) setwd(inputLoc)
#normal run #normal run
## if(silent){
## if(Linuxp){
## system(paste(executable,iniInput[2],"> /dev/null",sep=" "))
## } else {
## system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE)
## }
## } else {
## system(paste(executable,iniInput[2],sep=" "))
## }
## system(paste(executable,iniInput[2],sep=" "))
## switch(timee,
## "d"=(Reva<-getdailyout(settings)),
## "m"=(Reva<-getmonthlyout(settings)),
## "y"=(Reva<-getyearlyout(settings))
## )
if(silent){ if(silent){
if(Linuxp){ if(Linuxp){
system(paste(executable,iniInput[2],"> /dev/null",sep=" ")) tryCatch(system(paste(executable,iniInput[2],"> /dev/null",sep=" ")),
error =function (e) {stop("Cannot run the modell-check the executable!")})
} else { } else {
system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE) tryCatch(system(paste(executable,iniInput[2],sep=" "),show.output.on.console = FALSE),
error =function (e) {stop("Cannot run the modell-check the executable!")} )
} }
} else { } else {
system(paste(executable,iniInput[2],sep=" ")) tryCatch(system(paste(executable,iniInput[2],sep=" ")),
error =function (e) {stop("Cannot run the modell-check the executable!")})
} }
##read the output
system(paste(executable,iniInput[2],sep=" "))
switch(timee, switch(timee,
"d"=(Reva<-getdailyout(settings)), "d"=(Reva <- tryCatch(getdailyout(settings),
"m"=(Reva<-getmonthlyout(settings)), error = function (e) {stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"y"=(Reva<-getyearlyout(settings)) "m"=(Reva <- tryCatch(getmonthlyout(settings),
error = function (e) {stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")})),
"y"=(Reva <- tryCatch(getyearlyout(settings),
error = function (e) {stop("Cannot read binary output, please check if the output type is set 2 in the ini files!")}))
) )
if(keepBinary){
possibleNames <- getOutFiles(outputLoc = outputLoc,outputNames = outputNames)
stampAndDir(outputLoc = outputLoc,names = possibleNames,stampDir=binaryPlace,type="output")
}
logfiles<-list.files(inputloc)[grep("log$",list.files(inputloc))]
logfiles <- getLogs(outputLoc,outputNames,type = "normal")
#############LOG SECTION####################### #############LOG SECTION#######################
perror<-as.numeric(as.vector(lapply(paste(inputloc,logfiles,sep=""),function(x) tail(readLines(x,-1),1)))) errorsign <- readErrors(outputLoc = outputLoc,logfiles = logfiles,type="normal")
dirName<-paste(inputloc,"/LOG",sep="") dirName<-paste(inputloc,"/LOG",sep="")
dirERROR<-paste(inputloc,"/ERROR",sep="") dirERROR<-paste(inputloc,"/ERROR",sep="")
ERROR_EPC<-paste(inputloc,"/ERROR_EPC",sep="") ERROR_EPC<-paste(inputloc,"/ERROR_EPC",sep="")
@ -73,11 +137,6 @@ normalMuso<- function(settings,parameters=NULL,timee="d",debugging=FALSE,logfile
dir.create(dirERROR) dir.create(dirERROR)
} }
if(length(perror)>sum(perror)){
errorsign <- 1
} else {
errorsign <- 0
}

View File

@ -114,28 +114,28 @@ corrigMuso <- function(settings, data){
return(data) return(data)
} }
#' file.path2 ## #' file.path2
#' ## #'
#' It is an extended file.path function, it can concatenate path where the first ends and the second begins with "/", so ## #' It is an extended file.path function, it can concatenate path where the first ends and the second begins with "/", so
#' there wont be two slash nearby eachother ## #' there wont be two slash nearby eachother
#' @author Roland Hollos ## #' @author Roland Hollos
#' @param str1 This is the first path string ## #' @param str1 This is the first path string
#' @param str2 This is the second path string ## #' @param str2 This is the second path string
#' @return A concatenated path ## #' @return A concatenated path
#' @export ## #' @export
#' @usage file.path2(str1, str2) ## #' @usage file.path2(str1, str2)
file.path2<-function(str1, str2){ ## file.path2<-function(str1, str2){
if(str1==""|str1=="./"){ ## if(str1==""|str1=="./"){
return(str2) ## return(str2)
} ## }
str1<-file.path(dirname(str1),basename(str1)) ## str1<-file.path(dirname(str1),basename(str1))
if(substring(str2,1,1)=="/"){ ## if(substring(str2,1,1)=="/"){
return(paste(str1,str2,sep="")) ## return(paste(str1,str2,sep=""))
} else{ ## } else{
return(file.path(str1,str2)) ## return(file.path(str1,str2))
} ## }
} ## }
numFactors <- function(x,type="pos"){ numFactors <- function(x,type="pos"){
x <- as.integer(abs(x)) x <- as.integer(abs(x))

View File

@ -22,8 +22,8 @@
#' @import graphics #' @import graphics
#' @export #' @export
plotMuso <- function(settings, plotMuso <- function(settings=NULL,
variable, variable=1,
##compare, ##compare,
##plotname, ##plotname,
timee="d", timee="d",
@ -36,6 +36,10 @@ plotMuso <- function(settings,
export=FALSE){ export=FALSE){
if(is.null(settings)){
settings <- setupMuso()
}
musoData <- rungetMuso(settings=settings, musoData <- rungetMuso(settings=settings,
silent=silent, silent=silent,
timee=timee, timee=timee,

View File

@ -15,12 +15,16 @@
#' logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE) #' logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE)
#' @export #' @export
spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE, fileToChange="epc"){ spinupMuso <- function(settings=NULL, parameters=NULL, debugging=FALSE, logfilename=NULL, keepEpc=FALSE, silent=FALSE, aggressive=FALSE, fileToChange="epc"){
########################################################################## ##########################################################################
###########################Set local variables######################## ###########################Set local variables########################
######################################################################## ########################################################################
if(is.null(settings)){
settings <- setupMuso()
}
Linuxp <-(Sys.info()[1]=="Linux") Linuxp <-(Sys.info()[1]=="Linux")
##Copy the variables from settings ##Copy the variables from settings
inputLoc <- settings$inputLoc inputLoc <- settings$inputLoc
@ -37,20 +41,9 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
############################spinup run############################ ############################spinup run############################
########################################################## ##########################################################
##Sometimes a bug occure due to logfiles and controlfiles in the input loc directory
if(silent!=TRUE){
if(length(grep("(dayout$)|(log$)",list.files(inputLoc)))>0){
warning(" \n \n WARMING: there is a log or dayout file nearby the ini files, that may cause problemes. \n \n If you want to avoid that possible problemes, please copy the log or dayout files into a save place, and after do a cleanupMuso(), or delete these manually, or run the rungetMuso(), with the agressive=TRUE parameter \n \n")}}
##With the aggressive option every unneeded file will deleted
if(aggressive==TRUE){ if(aggressive==TRUE){
cleanupMuso(location=outputLoc,deep=TRUE)} cleanupMuso(location=outputLoc,deep=TRUE)}
##change the epc file if and only if there are given parameters
## if(!is.null(parameters)){
## changemulline(filename=epc[1], calibrationPar, parameters)}
if(!is.null(parameters)){ if(!is.null(parameters)){
switch(fileToChange, switch(fileToChange,
"epc"=tryCatch(changemulline(filename=epc[2],calibrationPar,parameters), "epc"=tryCatch(changemulline(filename=epc[2],calibrationPar,parameters),
@ -77,17 +70,24 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
#In windows machines there is a show.output.on.console option #In windows machines there is a show.output.on.console option
tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE), tryCatch(system(paste(executable,iniInput[1],sep=" "),show.output.on.console = FALSE),
error= function (e){stop("Cannot run the modell-check the executable!")}) error= function (e){stop("Cannot run the modell-check the executable!")})
}} }} else {
system(paste(executable,iniInput[1],sep=" "))
}
############################################### ###############################################
#############LOG SECTION####################### #############LOG SECTION#######################
############################################### ###############################################
logspinup<-list.files(outputLoc)[grep("log$",list.files(outputLoc))] logspinup <- getLogs(outputLoc,outputNames,type="spinup")
## spincrash<-tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)==0
logspinup<-list.files(outputLoc)[grep("log$",list.files(outputLoc))]#load the logfiles
if(length(logspinup)==0){ if(length(logspinup)==0){
spincrash <- TRUE if(keepEpc){
stampnum<-stamp(EPCS)
lapply(epc,function (x) file.copy(from = x ,to=paste(EPCS,"/",(stampnum+1),"-", basename(x),sep="")))
lapply(epc, function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",basename(x),sep=""), to=WRONGEPC))
setwd(whereAmI)
stop("Modell Failure")
}
setwd(whereAmI)
stop("Modell Failure") #in that case the modell did not create even a logfile
} }
if(length(logspinup)>1){ if(length(logspinup)>1){
@ -100,9 +100,7 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
} }
} }
logfiles <- list.files(outputLoc)[grep("log$",list.files(outputLoc))] dirName<-normalizePath(paste(inputLoc,"/LOG",sep=""))
dirName<-paste(inputLoc,"/LOG",sep="")
dirERROR<-paste(inputLoc,"/ERROR",sep="") dirERROR<-paste(inputLoc,"/ERROR",sep="")
if(!dir.exists(dirName)){ if(!dir.exists(dirName)){
@ -118,83 +116,14 @@ spinupMuso <- function(settings, parameters=NULL, debugging=FALSE, logfilename=N
if(keepEpc){#if keepepc option tured on if(debugging==TRUE){
stampAndDir(outputLoc=outputLoc,stampDir=dirName, names=logspinup, type="output")
if(length(unique(dirname(epc)))>1){
print("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?")
} else {
epcdir <- dirname(epc[1])
WRONGEPC<-paste(inputLoc,"WRONGEPC",sep="")
EPCS<-paste(inputLoc,"EPCS",sep="")
if(!dir.exists(WRONGEPC)){
dir.create(WRONGEPC)
} }
if(!dir.exists(EPCS)){
dir.create(EPCS)
}
epcfiles <- list.files(epcdir)[grep("epc$",list.files(epcdir))]
stampnum<-stamp(EPCS)
lapply(epcfiles,function (x) file.copy(from = paste(epcdir,"/",x,sep=""),to=paste(EPCS,"/",(stampnum+1),"-",x,sep="")))
if(errorsign==1){
lapply(epcfiles,function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",x,sep=""), to=WRONGEPC))
}
}
}
if(debugging=="stamplog"){
stampnum<-stamp(dirName)
if(inputLoc==outputLoc){
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
} else {
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
}
if(errorsign==1){
lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",(stampnum+1),"-",x,sep=""), to=dirERROR ))}
} else { if(debugging){
if(is.null(logfilename)){
if(inputLoc==outputLoc){
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName,"/", x, sep="")))
} else {
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName,"/", x, sep="")))
}
if(errorsign==1){
lapply( logfiles, function (x) file.rename(from=paste(dirName,"/", x, sep=""), to=dirERROR))
}
} else {
if(inputLoc==outputLoc){#These are very ugly solutions for a string problem: inputLoc: "./", if outputLoc equalent of inputLoc, it ends with "/", the string manipulation can not handle this. The better solution is easy, but I dont have enough time(Roland Hollo's)
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",logfilename,"-",x,sep="")))
} else {
lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",logfilename,"-",x,sep="")))
}
if(errorsign==1){
lapply( logfiles, function (x) file.rename(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR))
}
}
}}
#cleanupMuso(location=outputLoc)
if(errorsign==1){ if(errorsign==1){
return("Modell Failure") stop("Modell Failure")
} }

View File

@ -32,7 +32,7 @@ keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
No return, outputs are written to file No return, outputs are written to file
} }
\description{ \description{
This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a very structured way. This function changes the epc file and after that runs the BBGC-MuSo model and reads in its outputfile in a well-structured way.
} }
\author{ \author{
Roland Hollos Roland Hollos

View File

@ -1,23 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/otherUsefullFunctions.R
\name{file.path2}
\alias{file.path2}
\title{file.path2}
\usage{
file.path2(str1, str2)
}
\arguments{
\item{str1}{This is the first path string}
\item{str2}{This is the second path string}
}
\value{
A concatenated path
}
\description{
It is an extended file.path function, it can concatenate path where the first ends and the second begins with "/", so
there wont be two slash nearby eachother
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,20 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/outputMapping.R
\name{musoMappingFind}
\alias{musoMappingFind}
\title{musoMappingFind}
\usage{
musoMapping(code, mapData=NULL)
}
\arguments{
\item{variable}{If null return the whole mapping, else search a variable code}
}
\value{
The code of th specific name
}
\description{
musoMapping can give us the name of a muso outputcode
}
\author{
Roland Hollos
}

View File

@ -0,0 +1,45 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/normalMuso.R
\name{normalMuso}
\alias{normalMuso}
\title{normalMuso}
\usage{
normalMuso(settings,parameters=NULL, timee="d", debugging=FALSE, logfilename=NULL,
keepEpc=FALSE, export=FALSE, silent=FALSE, aggressive=FALSE, leapYear=FALSE)
}
\arguments{
\item{settings}{You have to run the setupMuso function before calibMuso. It is its output which contains all of the necessary system variables. It sets the whole running environment}
\item{parameters}{In the settings variable you have set the row indexes of the variables, you wish to change. In this parameter you can give an exact value for them in a vector like: c(1,2,3,4)}
\item{timee}{The required timesteps in the modell output. It can be "d", if it is daily, "m", if it's monthly, "y", it it is yearly. I recommend to use daily data, the yearly and monthly data is not well-tested yet.}
\item{debugging}{If it is TRUE, it copies the log file to a Log directory to store it, if it is stamplog it contatenate a number before the logfile, which is one more than the maximum of the represented ones in the LOG directory. If it is true or stamplog it collects the "wrong" logfiles}
\item{logfilename}{If you want to set a specific name for your logfiles you can set this via logfile parameter}
\item{keepEpc}{If TRUE, it keeps the epc file and stamp it, after these copies it to the EPCS directory. If debugging True or false, it copies the wrong epc files to the wrong epc directory.}
\item{export}{if it is yes or you give a filename here, it converts the ouxtput to the specific extension. For example, if you set export to "example.csv", it converts the output to "csv", if you set it to "example.xls" it converts to example.xls with the xlsx package. If it is not installed it gives back a warning message and converts it to csv.}
\item{silent}{If you set it TRUE all off the modells output to the screen will be suppressed. It can be usefull, because it increases the model-speed.}
\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{binaryPlace}{The place of the binary output files.}
\item{fileToChange}{You can change any line of the epc or the ini file, you just have to specify with this variable which file you van a change. Two options possible: "epc", "ini"}
\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.}
}
\value{
The simunation output matrix, where the columns are the choosen variables and each row is a day/month/year data.
}
\description{
This function changes the epc file and after that runs the BBGC-MuSo model in normal phase and reads in its outputfile in a well-structured way.
}
\author{
Roland Hollos
}

View File

@ -4,7 +4,7 @@
\alias{readErrors} \alias{readErrors}
\title{readErrors} \title{readErrors}
\usage{ \usage{
readErrors(outputLoc, logfiles) readErrors(outputLoc, logfiles, type = "both")
} }
\arguments{ \arguments{
\item{outputLoc}{This is the location of the output files.} \item{outputLoc}{This is the location of the output files.}

View File

@ -0,0 +1,21 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/assistantFunctions.R
\name{stampAndDir}
\alias{stampAndDir}
\title{stampAndCopy}
\usage{
stampAndDir(outputLoc, names, stampDir, wrongDir, type = "output", errorsign,
logfiles)
}
\arguments{
\item{outputLoc}{This is the location of the output files.}
\item{outputNames}{These are the prefixis of the logfiles}
}
\value{
Output files with their paths
}
\description{
This function gives us the muso output files with their paths
}
\keyword{internal}

View File

@ -350,3 +350,97 @@ getyearlyout<-function(settings){
} }
}} }}
##Sometimes a bug occure due to logfiles and controlfiles in the input loc directory- NOT ANYMORE! :)
## if(silent!=TRUE){
## if(length(grep("(dayout$)|(log$)",list.files(inputLoc)))>0){
## warning(" \n \n WARMING: there is a log or dayout file nearby the ini files, that may cause problemes. \n \n If you want to avoid that possible problemes, please copy the log or dayout files into a save place, and after do a cleanupMuso(), or delete these manually, or run the rungetMuso(), with the agressive=TRUE parameter \n \n")}}
##With the aggressive option every unneeded file will deleted
##change the epc file if and only if there are given parameters
## if(!is.null(parameters)){
## changemulline(filename=epc[1], calibrationPar, parameters)}
## logspinup<-list.files(outputLoc)[grep("log$",list.files(outputLoc))]
## spincrash<-tail(readLines(paste(outputLoc,logspinup,sep="/"),-1),1)==0
# logspinup<-list.files(outputLoc)[grep("log$",list.files(outputLoc))]#load the logfiles
## logfiles <- list.files(outputLoc)[grep("log$",list.files(outputLoc))]
## if(keepEpc){#if keepepc option tured on
## if(length(unique(dirname(epc)))>1){
## print("Why are you playing with my nervs? Seriously? You hold your epc-s in different folders?")
## } else {
## epcdir <- dirname(epc[1])
## WRONGEPC<-paste(inputLoc,"WRONGEPC",sep="")
## EPCS<-paste(inputLoc,"EPCS",sep="")
## if(!dir.exists(WRONGEPC)){
## dir.create(WRONGEPC)
## }
## if(!dir.exists(EPCS)){
## dir.create(EPCS)
## }
## epcfiles <- list.files(epcdir)[grep("epc$",list.files(epcdir))]
## stampnum<-stamp(EPCS)
## lapply(epcfiles,function (x) file.copy(from = paste(epcdir,"/",x,sep=""),to=paste(EPCS,"/",(stampnum+1),"-",x,sep="")))
## if(errorsign==1){
## lapply(epcfiles,function (x) file.copy(from = paste(EPCS,"/",(stampnum+1),"-",x,sep=""), to=WRONGEPC))
## }
## }
## }
## if(debugging=="stamplog"){
## stampnum<-stamp(dirName)
## if(inputLoc==outputLoc){
## lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
## } else {
## lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",(stampnum+1),"-",x,sep="")))
## }
## if(errorsign==1){
## lapply( logfiles, function (x) file.copy(from=paste(dirName, "/",(stampnum+1),"-",x,sep=""), to=dirERROR ))}
## } else { if(debugging){
## if(is.null(logfilename)){
## if(inputLoc==outputLoc){
## lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName,"/", x, sep="")))
## } else {
## lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName,"/", x, sep="")))
## }
## if(errorsign==1){
## lapply( logfiles, function (x) file.rename(from=paste(dirName,"/", x, sep=""), to=dirERROR))
## }
## } else {
## if(inputLoc==outputLoc){#These are very ugly solutions for a string problem: inputLoc: "./", if outputLoc equalent of inputLoc, it ends with "/", the string manipulation can not handle this. The better solution is easy, but I dont have enough time(Roland Hollo's)
## lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep=""), to=paste(dirName, "/",logfilename,"-",x,sep="")))
## } else {
## lapply( logfiles, function (x) file.rename(from=paste(outputLoc,x, sep="/"), to=paste(dirName, "/",logfilename,"-",x,sep="")))
## }
## if(errorsign==1){
## lapply( logfiles, function (x) file.rename(from=paste(dirName, "/",logfilename,"-",x,sep=""), to=dirERROR))
## }
## }
## }}
#cleanupMuso(location=outputLoc)