changeing the input method is no longer necessary
This commit is contained in:
parent
f677995038
commit
0e50f0c1f0
@ -113,10 +113,14 @@ calibMuso <- function(settings=setupMuso(), calibrationPar=NULL,
|
|||||||
##change the epc file if and only if there are given parameters
|
##change the epc file if and only if there are given parameters
|
||||||
|
|
||||||
if(!is.null(parameters)){
|
if(!is.null(parameters)){
|
||||||
changemulline(filePaths = epcInput,
|
changemulline(filePaths = epc[2],
|
||||||
calibrationPar = calibrationPar,
|
calibrationPar = calibrationPar,
|
||||||
contents = parameters,
|
contents = parameters,
|
||||||
fileOut = toModif,
|
src = if(file.exists(bck)){
|
||||||
|
bck
|
||||||
|
} else {
|
||||||
|
NULL
|
||||||
|
})
|
||||||
# fileToChange = fileToChange,)
|
# fileToChange = fileToChange,)
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -7,45 +7,30 @@
|
|||||||
#' @keywords internal
|
#' @keywords internal
|
||||||
#'
|
#'
|
||||||
|
|
||||||
changemulline <- function(filePaths, calibrationPar, contents, fileOut, fileToChange, modifyOriginal=FALSE){
|
|
||||||
selectFileToWrite <- function(filePaths, fileTochange){
|
changemulline <- function(filePaths, calibrationPar, contents, src){
|
||||||
if(fileToChange == "epc"){
|
# browser()
|
||||||
return(1)
|
if(is.null(src)){
|
||||||
} else{
|
src <- filePaths
|
||||||
return(2)
|
|
||||||
}
|
}
|
||||||
|
|
||||||
}
|
fileStringVector <- readLines(src)
|
||||||
|
Map(function(index, content){
|
||||||
|
fileStringVector <<- changeByIndex(index, content, fileStringVector)
|
||||||
|
|
||||||
if(xor(is.list(calibrationPar), is.list(contents)) ){
|
}, calibrationPar, contents)
|
||||||
stop("If you change epc and ini files also, you have to use list for calibrationPar, and paramateters.")
|
writeLines(fileStringVector, filePaths)
|
||||||
}
|
|
||||||
|
|
||||||
if(!is.element(fileToChange,c("ini","epc","both"))){
|
|
||||||
stop("RBBGCMuso can only change ini or epc file, so fileToChange can be 'epc/ini/both'")
|
|
||||||
}
|
|
||||||
|
|
||||||
if(fileToChange == "epc" | fileToChange == "ini"){
|
|
||||||
parMat<-matrix(c(calibrationPar, contents),nrow=length(calibrationPar))
|
|
||||||
if(nrow(parMat)!=1){
|
|
||||||
parMat <- parMat[order(parMat[,1]),]
|
|
||||||
}
|
|
||||||
changeMusoC(inFile = filePaths[selectFileToWrite(filePaths, fileToChange)],
|
|
||||||
outFile = fileOut[selectFileToWrite(filePaths, fileToChange)],
|
|
||||||
parMat)
|
|
||||||
}
|
|
||||||
|
|
||||||
if(fileToChange == "both"){
|
|
||||||
parMat[[1]]<-cbind(calibrationPar[[1]], contents[[1]])
|
|
||||||
parMat[[1]]<- parMat[[1]][order(parMat[[1]][,1]),]
|
|
||||||
parMat[[2]]<-cbind(calibrationPar[[2]], contents[[2]])
|
|
||||||
parmat[[2]]<- parMat[[2]][order(parMat[[2]][,1]),]
|
|
||||||
|
|
||||||
browser()
|
|
||||||
changeMusoC(filePaths[1],fileOut[1],parMat[[1]] )
|
|
||||||
changeMusoC(filePaths[2],fileOut[2],parMat[[2]] )
|
|
||||||
}
|
|
||||||
|
|
||||||
}
|
}
|
||||||
|
|
||||||
|
changeNth <- function (string,place,replacement) {
|
||||||
|
trimws(gsub(sprintf("^((.*?\\s+){%s})(.*?\\s+)", place), sprintf("\\1%s ", replacement), paste0(string," "), perl=TRUE),
|
||||||
|
which="right")
|
||||||
|
}
|
||||||
|
|
||||||
|
changeByIndex <- function (rowIndex, parameter, fileStringVector){
|
||||||
|
h <- round((rowIndex*100) %% 10)
|
||||||
|
i <- as.integer(rowIndex)
|
||||||
|
fileStringVector[i] <- changeNth(fileStringVector[i], h, parameter)
|
||||||
|
fileStringVector
|
||||||
|
}
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user