[chronojump] ForceSensor export all files managed from maximumIsometricForce.R
- From: Xavier de Blas <xaviblas src gnome org>
- To: commits-list gnome org
- Cc:
- Subject: [chronojump] ForceSensor export all files managed from maximumIsometricForce.R
- Date: Mon, 8 Feb 2021 11:46:58 +0000 (UTC)
commit cb52db1e63b9bde89deba975124b31f51ca64684
Author: Xavier de Blas <xaviblas gmail com>
Date: Mon Feb 8 12:46:28 2021 +0100
ForceSensor export all files managed from maximumIsometricForce.R
r-scripts/maximumIsometricForce.R | 204 ++++++++++++++++++++-------------
src/forceSensor.cs | 233 +++++++++++++++++++++++++++++++-------
src/gui/app1/forceSensor.cs | 15 ++-
src/utilEncoder.cs | 3 +
4 files changed, 327 insertions(+), 128 deletions(-)
---
diff --git a/r-scripts/maximumIsometricForce.R b/r-scripts/maximumIsometricForce.R
index 8dcc718e..0e2b7f07 100644
--- a/r-scripts/maximumIsometricForce.R
+++ b/r-scripts/maximumIsometricForce.R
@@ -55,7 +55,8 @@ assignOptions <- function(options)
triggersOffList = as.numeric(unlist(strsplit(options[24], "\\;"))),
startSample = as.numeric(options[25]),
endSample = as.numeric(options[26]),
- startEndOptimized = options[27] #bool
+ startEndOptimized = options[27], #bool
+ singleOrMultiple = options[28] #bool (true is single)
))
}
@@ -65,7 +66,6 @@ args <- commandArgs(TRUE)
tempPath <- args[1]
optionsFile <- paste(tempPath, "/Roptions.txt", sep="")
-dataFile <- paste(tempPath, "/cj_mif_Data.csv", sep="")
pngFile <- paste(tempPath, "/cj_mif_Graph.png", sep="")
#-------------- scan options file -------------
@@ -76,12 +76,7 @@ op <- assignOptions(options)
print(op)
source(paste(op$scriptsPath, "/scripts-util.R", sep=""))
-
-op$title = fixTitleAndOtherStrings(op$title)
-op$exercise = fixTitleAndOtherStrings(op$exercise)
-titleFull = paste(op$title, op$exercise, sep=" - ")
-op$datetime = fixDatetime(op$datetime)
-
+dfExport = NULL #global variable that will be changed by methods
#Fits the data to the model f = fmax*(1 - exp(-K*t))
#Important! It fits the data with the axes moved to startTime.
@@ -116,7 +111,7 @@ getForceModel <- function(time, force, startTime, # startTime is the instant whe
return(list(fmax = fmax, K = K, T0 = T0, error = 100*residuals(model)/mean(data$force)))
}
-getDynamicsFromLoadCellFile <- function(captureOptions, inputFile, averageLength = 0.1, percentChange = 5,
testLength = -1)
+getDynamicsFromLoadCellFile <- function(captureOptions, inputFile, averageLength = 0.1, percentChange = 5,
testLength = -1, startSample, endSample)
{
print("Entered getDynamicsFromLoadCellFile")
@@ -129,15 +124,15 @@ getDynamicsFromLoadCellFile <- function(captureOptions, inputFile, averageLength
else if(captureOptions == "INVERTED")
originalTest$force = -1 * originalTest$force
- print(paste("op$startSample: ", op$startSample))
- print(paste("op$endtSample: ", op$endSample))
+ print(paste("startSample: ", startSample))
+ print(paste("endtSample: ", endSample))
#If Roptions.txt does have endSample values greater than 1 it means that the user has selected a range
- if( op$startSample != op$endSample & (op$endSample > 1) & op$startSample <= length(originalTest$time) &
op$endSample <= length(originalTest$time))
+ if( startSample != endSample & (endSample > 1) & startSample <= length(originalTest$time) & endSample
<= length(originalTest$time))
{
print("Range selected by user. Analyzed the specified range")
- originalTest = originalTest[(op$startSample:op$endSample),]
+ originalTest = originalTest[(startSample:endSample),]
originalTest$time = originalTest$time - originalTest$time[1]
# print("originalTest$time:")
# print(originalTest$time)
@@ -214,7 +209,7 @@ getDynamicsFromLoadCellFile <- function(captureOptions, inputFile, averageLength
))
}
-drawDynamicsFromLoadCell <- function(
+drawDynamicsFromLoadCell <- function(titleFull, datetime,
dynamics, captureOptions, vlineT0=T, vline50fmax.raw=F, vline50fmax.fitted=F,
hline50fmax.raw=F, hline50fmax.fitted=F,
rfdDrawingOptions, triggersOn = "", triggersOff = "", xlimits = NA, forceLines = TRUE, timeLines = TRUE)
@@ -233,7 +228,6 @@ drawDynamicsFromLoadCell <- function(
}
par(mar = c(6, 4, 6, 4))
- exportNames = NULL
exportValues = NULL
#Detecting if the duration of the sustained force is enough
@@ -260,7 +254,7 @@ drawDynamicsFromLoadCell <- function(
#main = dynamics$nameOfFile,
main = paste(parse(text = paste0("'", titleFull, "'"))), #process unicode, needed paste because
its an expression. See graph.R
yaxs= "i", xaxs = "i")
- mtext(op$datetime, line = 0)
+ mtext(datetime, line = 0)
xmin = xlimits[1]
xmax = xlimits[2]
#points(dynamics$time[dynamics$startSample:dynamics$endSample] ,
dynamics$f.raw[dynamics$startSample:dynamics$endSample])
@@ -275,7 +269,7 @@ drawDynamicsFromLoadCell <- function(
#main = dynamics$nameOfFile,
main = paste(parse(text = paste0("'", titleFull, "'"))), #process unicode, needed paste because
its an expression. See graph.R
yaxs= "i", xaxs = "i")
- mtext(op$datetime, line = 0)
+ mtext(datetime, line = 0)
}
@@ -447,7 +441,6 @@ drawDynamicsFromLoadCell <- function(
)
legendColor = c("blue", "blue", "blue")
- exportNames = paste("Fmax")
exportValues = dynamics$fmax.fitted
#The coordinates where the lines and dots are plotted are calculated with the sampled data in raw and
fitted data.
@@ -645,15 +638,11 @@ drawDynamicsFromLoadCell <- function(
abline(a = intercept, b = RFD, lty = 2, col = color)
if(! is.null(RFD))
- {
- exportNames = c(exportNames, paste("RFD", RFDoptions$rfdFunction, RFDoptions$type,
RFDoptions$start, RFDoptions$end, sep ="_"))
exportValues = c(exportValues, RFD)
- }
}
}
- exportNames = c(exportNames, paste("Impulse", impulseOptions$impulseFunction, impulseOptions$type,
impulseOptions$start, impulseOptions$end, sep ="_"))
exportValues = c(exportValues, impulse)
if(impulseLegend != ""){
@@ -671,56 +660,48 @@ drawDynamicsFromLoadCell <- function(
legend(x = xmax, y = dynamics$fmax.fitted/2, legend = legendText, xjust = 1, yjust = 0.1, text.col =
legendColor)
- if(is.null(exportValues))
- {
- write(0, file = paste(tempPath, "/cj_mif_export.csv", sep = "")) # write something blank to be able
to know in C# that operation ended
- }
- else
- {
- exportValues = rbind(exportValues)
- colnames(exportValues) = exportNames
- write.csv2(exportValues, file = paste(tempPath, "/cj_mif_export.csv", sep = ""), row.names = FALSE,
col.names = TRUE, quote = FALSE)
- }
-
+ #modifying global variable:
+ if(op$singleOrMultiple == "FALSE")
+ dfExport <<- rbind(dfExport, exportValues)
}
-getDynamicsFromLoadCellFolder <- function(folderName, resultFileName, export2Pdf)
-{
- originalFiles = list.files(path=folderName, pattern="*")
- nFiles = length(originalFiles)
- results = matrix(rep(NA, 16*nFiles), ncol = 16)
- colnames(results)=c("fileName", "fmax.fitted", "k.fitted", "fmax.raw", "startTime", "previousForce",
"fmax.smoothed",
- "rfd0.fitted", "rfd100.raw", "rfd0_100.raw", "rfd0_100.fitted",
- "rfd200.raw", "rfd0_200.raw", "rfd0_200.fitted",
- "rfd50pfmax.raw", "rfd50pfmax.fitted")
-
- results[,"fileName"] = originalFiles
-
- for(i in 1:nFiles)
- {
- dynamics = getDynamicsFromLoadCellFile(op$captureOptions, paste(folderName,originalFiles[i], sep =
""))
-
- results[i, "fileName"] = dynamics$nameOfFile
- results[i, "fmax.fitted"] = dynamics$fmax.fitted
- results[i, "k.fitted"] = dynamics$k.fitted
- results[i, "fmax.raw"] = dynamics$fmax.raw
- results[i, "startTime"] = dynamics$startTime
- results[i, "previousForce"] = dynamics$previousForce
- results[i, "fmax.smoothed"] = dynamics$fmax.smoothed
- results[i, "rfd0.fitted"] = dynamics$rfd0.fitted
- results[i, "rfd100.raw"] = dynamics$rfd100.raw
- results[i, "rfd0_100.raw"] = dynamics$rfd0_100.raw
- results[i, "rfd0_100.fitted"] = dynamics$rfd0_100.fitted
- results[i, "rfd200.raw"] = dynamics$rfd200.raw
- results[i, "rfd0_200.raw"] = dynamics$rfd0_200.raw
- results[i, "rfd0_200.fitted"] = dynamics$rfd0_200.fitted
- results[i, "rfd50pfmax.raw"] = dynamics$rfd50pfmax.rawfilter(test$force, rep(1/19, 19), sides = 2)
- results[i, "rfd50pfmax.fitted"] = dynamics$rfd50pfmax.fitted
- }
- write.table(results, file = resultFileName, sep = ";", dec = ",", col.names = NA)
- return(results)
-
-}
+#getDynamicsFromLoadCellFolder <- function(folderName, resultFileName, captureOptions)
+#{
+# originalFiles = list.files(path=folderName, pattern="*")
+# nFiles = length(originalFiles)
+# results = matrix(rep(NA, 16*nFiles), ncol = 16)
+# colnames(results)=c("fileName", "fmax.fitted", "k.fitted", "fmax.raw", "startTime", "previousForce",
"fmax.smoothed",
+# "rfd0.fitted", "rfd100.raw", "rfd0_100.raw", "rfd0_100.fitted",
+# "rfd200.raw", "rfd0_200.raw", "rfd0_200.fitted",
+# "rfd50pfmax.raw", "rfd50pfmax.fitted")
+#
+# results[,"fileName"] = originalFiles
+#
+# for(i in 1:nFiles)
+# {
+# dynamics = getDynamicsFromLoadCellFile(captureOptions, paste(folderName,originalFiles[i], sep = ""))
+#
+# results[i, "fileName"] = dynamics$nameOfFile
+# results[i, "fmax.fitted"] = dynamics$fmax.fitted
+# results[i, "k.fitted"] = dynamics$k.fitted
+# results[i, "fmax.raw"] = dynamics$fmax.raw
+# results[i, "startTime"] = dynamics$startTime
+# results[i, "previousForce"] = dynamics$previousForce
+# results[i, "fmax.smoothed"] = dynamics$fmax.smoothed
+# results[i, "rfd0.fitted"] = dynamics$rfd0.fitted
+# results[i, "rfd100.raw"] = dynamics$rfd100.raw
+# results[i, "rfd0_100.raw"] = dynamics$rfd0_100.raw
+# results[i, "rfd0_100.fitted"] = dynamics$rfd0_100.fitted
+# results[i, "rfd200.raw"] = dynamics$rfd200.raw
+# results[i, "rfd0_200.raw"] = dynamics$rfd0_200.raw
+# results[i, "rfd0_200.fitted"] = dynamics$rfd0_200.fitted
+# results[i, "rfd50pfmax.raw"] = dynamics$rfd50pfmax.rawfilter(test$force, rep(1/19, 19), sides = 2)
+# results[i, "rfd50pfmax.fitted"] = dynamics$rfd50pfmax.fitted
+# }
+# write.table(results, file = resultFileName, sep = ";", dec = ",", col.names = NA)
+# return(results)
+#
+#}
#Finds the sample in which the force start incresing with two optional methods
# - SD method: When the force increase 3 times the standard deviation
@@ -1092,17 +1073,80 @@ readImpulseOptions <- function(optionsStr)
}
}
-print("Going to enter prepareGraph")
-prepareGraph(op$os, pngFile, op$graphWidth, op$graphHeight)
-print("Going to enter getDynamicsFromLoadCellFille")
-dynamics = getDynamicsFromLoadCellFile(op$captureOptions, dataFile, op$averageLength, op$percentChange,
testLength = op$testLength)
-drawDynamicsFromLoadCell(dynamics, op$captureOptions, op$vlineT0, op$vline50fmax.raw, op$vline50fmax.fitted,
op$hline50fmax.raw, op$hline50fmax.fitted,
- op$drawRfdOptions, triggersOn = op$triggersOnList, triggersOff = op$triggersOffList)
-# op$drawRfdOptions, xlimits = c(0.5, 1.5))
-endGraph()
+doProcess <- function(dataFile, title, exercise, datetime, captureOptions, startSample, endSample)
+{
+ title = fixTitleAndOtherStrings(title)
+ exercise = fixTitleAndOtherStrings(exercise)
+ titleFull = paste(title, exercise, sep=" - ")
+ datetime = fixDatetime(datetime)
+
+ print("Going to enter prepareGraph")
+ prepareGraph(op$os, pngFile, op$graphWidth, op$graphHeight)
+
+ print("Going to enter getDynamicsFromLoadCellFille")
+ dynamics = getDynamicsFromLoadCellFile(captureOptions, dataFile, op$averageLength, op$percentChange,
testLength = op$testLength, startSample, endSample)
+
+ print("Going to draw")
+ drawDynamicsFromLoadCell(titleFull, datetime, dynamics, captureOptions, op$vlineT0,
op$vline50fmax.raw, op$vline50fmax.fitted, op$hline50fmax.raw, op$hline50fmax.fitted,
+ op$drawRfdOptions, triggersOn = op$triggersOnList, triggersOff = op$triggersOffList)
+# op$drawRfdOptions, xlimits = c(0.5, 1.5))
+ endGraph()
+}
+
+if(op$singleOrMultiple == "TRUE")
+{
+ dataFile <- paste(tempPath, "/cj_mif_Data.csv", sep="")
+ doProcess(dataFile, op$title, op$exercise, op$datetime, op$captureOptions, op$startSample,
op$endSample)
+} else
+{
+ #1) read the csv
+ dataFiles = read.csv(file = paste(tempPath, "/maximumIsometricForceInputMulti.csv", sep=""),
sep=";", stringsAsFactors=F)
+
+ #2) call doProcess
+ for(i in 1:length(dataFiles[,1])) {
+ print("fullURL")
+ print(as.vector(dataFiles$fullURL[i]))
+
+ executing <- tryCatch({
+ doProcess(as.vector(dataFiles$fullURL[i]), dataFiles$title[i],
dataFiles$exercise[i], dataFiles$datetime[i],
+ dataFiles$captureOptions[i], dataFiles$startSample[i],
dataFiles$endSample[i])
+ }, error = function(e) {
+ print("error on doProcess:")
+ print(message(e))
+ })
+
+ print("done")
+ }
+
+ #3) write the file
+ if(is.null(dfExport))
+ write(0, file = paste(tempPath, "/cj_mif_export.csv", sep = "")) # write something blank to
be able to know in C# that operation ended
+ else {
+ print("dfExport")
+ print(dfExport)
+
+ #preparing header row
+ exportNames = "Fmax"
+ for(i in 1:length(op$drawRfdOptions))
+ {
+ RFDoptions = readRFDOptions(op$drawRfdOptions[i])
+ if(RFDoptions$rfdFunction != "-1")
+ exportNames = c(exportNames, paste("RFD", RFDoptions$rfdFunction,
RFDoptions$type, RFDoptions$start, RFDoptions$end, sep ="_"))
+ }
+
+ impulseOptions = readImpulseOptions(op$drawImpulseOptions)
+ if(impulseOptions$impulseFunction != "-1")
+ exportNames = c(exportNames, paste("Impulse", impulseOptions$impulseFunction,
impulseOptions$type, impulseOptions$start, impulseOptions$end, sep ="_"))
+
+ colnames(dfExport) <- exportNames
+
+ #print csv
+ write.csv2(dfExport, file = paste(tempPath, "/cj_mif_export.csv", sep = ""), row.names =
FALSE, col.names = TRUE, quote = FALSE)
+ }
+}
#dynamics = getDynamicsFromLoadCellFile("~/ownCloud/Xavier/Recerca/Yoyo-Tests/Galga/RowData/APl1",
averageLength = 0.1, percentChange = 5, sep = ";", dec = ",")
-#drawDynamicsFromLoadCell(dynamics, vlineT0=F, vline50fmax.raw=F, vline50fmax.fitted=T, hline50fmax.raw=F,
hline50fmax.fitted=T,
+#drawDynamicsFromLoadCell(titlefull, dynamics, vlineT0=F, vline50fmax.raw=F, vline50fmax.fitted=T,
hline50fmax.raw=F, hline50fmax.fitted=T,
# rfd0.fitted=T, rfd100.raw=F, rfd0_100.raw=F, rfd0_100.fitted = F, rfd200.raw=F,
rfd0_200.raw=F, rfd0_200.fitted = F,
# rfd50pfmax.raw=F, rfd50pfmax.fitted=T)
-#getDynamicsFromLoadCellFolder("~/Documentos/RowData/", resultFileName = "~/Documentos/results.csv")
+#getDynamicsFromLoadCellFolder("~/Documentos/RowData/", resultFileName = "~/Documentos/results.csv",
op$captureOptions)
diff --git a/src/forceSensor.cs b/src/forceSensor.cs
index dd57059b..39e0083e 100644
--- a/src/forceSensor.cs
+++ b/src/forceSensor.cs
@@ -1382,6 +1382,54 @@ public class ForceSensorImpulse : ForceSensorRFD
}
}
+//A-B data sent to R
+//can be just one on analyze or multiple (as a list) on export
+public class ForceSensorGraphAB
+{
+ public string fullURL;
+ public ForceSensor.CaptureOptions fsco;
+ public int startSample;
+ public int endSample;
+ public string title;
+ public string exercise;
+ public string datetime;
+ public TriggerList triggerList;
+
+ public ForceSensorGraphAB (string fullURL,
+ ForceSensor.CaptureOptions fsco, int startSample, int endSample,
+ string title, string exercise, string datetime, TriggerList triggerList)
+ {
+ this.fullURL = fullURL;
+ this.fsco = fsco;
+ this.startSample = startSample;
+ this.endSample = endSample;
+ this.title = title;
+ this.exercise = exercise;
+ this.datetime = datetime;
+ this.triggerList = triggerList;
+ }
+
+ public string ToCSVRow()
+ {
+ return fullURL + ";" +
+ fsco.ToString() + ";" +
+ title + ";" +
+ exercise + ";" +
+ datetime + ";" +
+ "\"\";\"\";" + // triggers unused on export
+ startSample.ToString() + ";" +
+ endSample.ToString();
+ }
+
+ public static string PrintCSVHeader()
+ {
+ return "fullURL;captureOptions;title;exercise;datetime;" +
+ "triggersON;triggersOFF;" + //unused on export
+ "startSample;endSample";
+ }
+
+}
+
public class ForceSensorGraph
{
ForceSensor.CaptureOptions fsco;
@@ -1404,22 +1452,17 @@ public class ForceSensorGraph
private bool startEndOptimized;
private bool decimalIsPoint;
- public ForceSensorGraph(ForceSensor.CaptureOptions fsco, List<ForceSensorRFD> rfdList,
+ //private method to help on assigning params
+ private void assignGenericParams(
+ List<ForceSensorRFD> rfdList,
ForceSensorImpulse impulse, int testLength, int percentChange,
- string title, string exercise, string datetime, TriggerList triggerList,
- int startSample, int endSample, bool startEndOptimized, bool decimalIsPoint)
+ bool startEndOptimized, bool decimalIsPoint)
{
- this.fsco = fsco;
+ //generic of any data
this.rfdList = rfdList;
this.impulse = impulse;
this.testLength = testLength;
this.percentChange = percentChange;
- this.title = title;
- this.exercise = exercise;
- this.datetime = datetime;
- this.triggerList = triggerList;
- this.startSample = startSample;
- this.endSample = endSample;
this.startEndOptimized = startEndOptimized;
this.decimalIsPoint = decimalIsPoint;
@@ -1431,16 +1474,52 @@ public class ForceSensorGraph
hline50fmax_fitted = false;
}
- public bool CallR(int graphWidth, int graphHeight)
+ //constructor for analyze one graph of a set from startSample to endSample. singleOrMultiple = true
+ public ForceSensorGraph(
+ List<ForceSensorRFD> rfdList,
+ ForceSensorImpulse impulse, int testLength, int percentChange,
+ bool startEndOptimized, bool decimalIsPoint,
+ ForceSensorGraphAB fsgAB
+ )
+ {
+ assignGenericParams(rfdList, impulse, testLength, percentChange,
+ startEndOptimized, decimalIsPoint);
+
+ //this A-B data
+ this.fsco = fsgAB.fsco;
+ this.startSample = fsgAB.startSample;
+ this.endSample = fsgAB.endSample;
+ this.title = fsgAB.title;
+ this.exercise = fsgAB.exercise;
+ this.datetime = fsgAB.datetime;
+ this.triggerList = fsgAB.triggerList;
+ }
+
+ //constructor for export. singleOrMultiple = false
+ public ForceSensorGraph(
+ List<ForceSensorRFD> rfdList,
+ ForceSensorImpulse impulse, int testLength, int percentChange,
+ bool startEndOptimized, bool decimalIsPoint,
+ List<ForceSensorGraphAB> fsgAB_l
+ )
+ {
+ assignGenericParams(rfdList, impulse, testLength, percentChange,
+ startEndOptimized, decimalIsPoint);
+
+ writeMultipleFilesCSV(fsgAB_l);
+ }
+
+ //multiple is export
+ public bool CallR(int graphWidth, int graphHeight, bool singleOrMultiple)
{
LogB.Information("\nforceSensor CallR ----->");
- writeOptionsFile(graphWidth, graphHeight);
+ writeOptionsFile(graphWidth, graphHeight, singleOrMultiple);
return ExecuteProcess.CallR(UtilEncoder.GetmifScript());
}
- private void writeOptionsFile(int graphWidth, int graphHeight)
+ private void writeOptionsFile(int graphWidth, int graphHeight, bool singleOrMultiple)
{
-LogB.Information("writeOptionsFile 0");
+ LogB.Information("writeOptionsFile 0");
string scriptsPath = UtilEncoder.GetSprintPath();
if(UtilAll.IsWindows())
scriptsPath = scriptsPath.Replace("\\","/");
@@ -1448,7 +1527,7 @@ LogB.Information("writeOptionsFile 0");
System.Globalization.NumberFormatInfo localeInfo = new
System.Globalization.NumberFormatInfo();
localeInfo = System.Globalization.NumberFormatInfo.CurrentInfo;
-LogB.Information("writeOptionsFile 1");
+ LogB.Information("writeOptionsFile 1");
//since 2.0.3 decimalChar is . (before it was locale specific)
string decimalChar = ".";
if(! decimalIsPoint)
@@ -1468,32 +1547,49 @@ LogB.Information("writeOptionsFile 1");
"#hline50fmax.fitted\n" + Util.BoolToRBool(hline50fmax_fitted) + "\n" +
"#RFDs";
-LogB.Information("writeOptionsFile 2");
+ LogB.Information("writeOptionsFile 2");
foreach(ForceSensorRFD rfd in rfdList)
if(rfd.active)
scriptOptions += "\n" + rfd.ToR();
else
scriptOptions += "\n-1";
-LogB.Information("writeOptionsFile 3");
+ LogB.Information("writeOptionsFile 3");
if(impulse.active)
scriptOptions += "\n" + impulse.ToR();
else
scriptOptions += "\n-1";
-LogB.Information("writeOptionsFile 4");
+ LogB.Information("writeOptionsFile 4");
+
+ string captureOptionsStr = "-1";
+ string triggersOnStr = TriggerList.TriggersNotFoundString;
+ string triggersOffStr = TriggerList.TriggersNotFoundString;
+ if(singleOrMultiple)
+ {
+ captureOptionsStr = fsco.ToString();
+ triggersOnStr = printTriggers(TriggerList.Type3.ON);
+ triggersOffStr = printTriggers(TriggerList.Type3.OFF);
+ } else {
+ captureOptionsStr = "-1";
+ title = "-1";
+ exercise = "-1";
+ datetime = "-1";
+ }
+
scriptOptions +=
"\n#testLength\n" + testLength.ToString() + "\n" +
- "#captureOptions\n" + fsco.ToString() + "\n" +
- "#title\n" + title + "\n" +
- "#exercise\n" + exercise + "\n" +
- "#datetime\n" + datetime + "\n" +
+ "#captureOptions\n" + captureOptionsStr + "\n" + //unused on multiple
+ "#title\n" + title + "\n" + //unused on multiple
+ "#exercise\n" + exercise + "\n" + //unused on multiple
+ "#datetime\n" + datetime + "\n" + //unused on multiple
"#scriptsPath\n" + UtilEncoder.GetScriptsPath() + "\n" +
- printTriggers(TriggerList.Type3.ON) + "\n" +
- printTriggers(TriggerList.Type3.OFF) + "\n" +
- "#startSample\n" + startSample.ToString() + "\n" +
- "#endSample\n" + endSample.ToString() + "\n" +
- "#startEndOptimized\n" + Util.BoolToRBool(startEndOptimized) + "\n";
+ triggersOnStr + "\n" + //unused on multiple
+ triggersOffStr + "\n" + //unused on
multiple
+ "#startSample\n" + startSample.ToString() + "\n" + //unused on multiple
+ "#endSample\n" + endSample.ToString() + "\n" + //unused on multiple
+ "#startEndOptimized\n" + Util.BoolToRBool(startEndOptimized) + "\n" +
+ "#singleOrMultiple\n" + Util.BoolToRBool(singleOrMultiple) + "\n";
/*
#startEndOptimized on gui can be:
@@ -1502,13 +1598,31 @@ LogB.Information("writeOptionsFile 4");
- startEndOptimized TRUE (default): optimized range (program will find best fitting samples
on user selected range)
*/
-LogB.Information("writeOptionsFile 5");
+ LogB.Information("writeOptionsFile 5");
TextWriter writer = File.CreateText(Path.GetTempPath() + "Roptions.txt");
writer.Write(scriptOptions);
writer.Flush();
writer.Close();
((IDisposable)writer).Dispose();
-LogB.Information("writeOptionsFile 6");
+ LogB.Information("writeOptionsFile 6");
+ }
+
+ private void writeMultipleFilesCSV(List<ForceSensorGraphAB> fsgAB_l)
+ {
+ LogB.Information("writeMultipleFilesCSV start");
+ TextWriter writer = File.CreateText(UtilEncoder.GetmifCSVInputMulti());
+
+ //write header
+ writer.WriteLine(ForceSensorGraphAB.PrintCSVHeader());
+
+ //write fsgAB_l for
+ foreach(ForceSensorGraphAB fsgAB in fsgAB_l)
+ writer.WriteLine(fsgAB.ToCSVRow());
+
+ writer.Flush();
+ writer.Close();
+ ((IDisposable)writer).Dispose();
+ LogB.Information("writeMultipleFilesCSV end");
}
private string printTriggers(TriggerList.Type3 type3)
@@ -2244,8 +2358,9 @@ public class ForceSensorExport
private void forceSensorExportDo()
{
getData();
- if(processForceSensorSets()) //false if cancelled
- writeFile();
+// if(processForceSensorSets()) //false if cancelled
+// writeFile();
+ processForceSensorSets();
}
private void getData ()
@@ -2261,6 +2376,8 @@ public class ForceSensorExport
Person p = new Person();
PersonSession ps = new PersonSession();
+ List<ForceSensorGraphAB> fsgAB_l = new List<ForceSensorGraphAB>();
+
int count = 0;
foreach(ForceSensor fs in fs_l)
{
@@ -2337,25 +2454,27 @@ public class ForceSensorExport
if (title == null || title == "")
title = "unnamed";
+
+ string destination = UtilEncoder.GetmifCSVInputMulti();
+ Util.FileDelete(destination);
+
+
+
+/*
//copy file to tmp to be written readed by R
File.Copy(fs.FullURL, UtilEncoder.GetmifCSVFileName(), true); //can be overwritten
//delete result file
Util.FileDelete(UtilEncoder.GetmifExportFileName());
+ */
foreach(ForceSensorRepetition rep in fsAI.ForceSensorRepetition_l)
{
- if(cancel)
- return false;
-
- ForceSensorGraph fsg = new ForceSensorGraph(fs.CaptureOption, rfdList,
impulse,
- duration, durationPercent,
- title, exercise, fs.DateTimePublic, new TriggerList(),
- rep.sampleStart, rep.sampleEnd, forceSensorStartEndOptimized,
- Util.CSVDecimalColumnIsPoint(UtilEncoder.GetmifCSVFileName(),
1) // (*)
- );
-
- bool success = fsg.CallR(imageWidth -5, imageHeight -5);
+ fsgAB_l.Add(new ForceSensorGraphAB (
+ fs.FullURL,
+ fs.CaptureOption, rep.sampleStart, rep.sampleEnd,
+ title, exercise, fs.DateTimePublic, new TriggerList()
+ ));
}
//TODO: or check cancel when there is a thread, also R should write something blank
if there is any problem
@@ -2365,7 +2484,7 @@ public class ForceSensorExport
while ( ! ( Util.FileReadable(UtilEncoder.GetmifExportFileName())))
;
*/
-
+/*
// 6) write exportedRFDs (includes impulse)
if(File.Exists(UtilEncoder.GetmifExportFileName()))
{
@@ -2386,11 +2505,38 @@ public class ForceSensorExport
}
}
pulseFraction = UtilAll.DivideSafeFraction (count ++, fs_l.Count);
+*/
+ }
+
+ if(fsgAB_l.Count > 0)
+ {
+ ForceSensorGraph fsg = new ForceSensorGraph(
+ rfdList, impulse,
+ duration, durationPercent,
+ forceSensorStartEndOptimized,
+ Util.CSVDecimalColumnIsPoint(UtilEncoder.GetmifCSVFileName(), 1),
+ fsgAB_l
+ );
+
+ bool success = fsg.CallR(imageWidth -5, imageHeight -5, false);
}
+ /*
+ ForceSensorGraph fsg = new ForceSensorGraph(
+ //fs.CaptureOption,
+ rfdList, impulse,
+ duration, durationPercent,
+ //title, exercise, fs.DateTimePublic, new TriggerList(),
+ //rep.sampleStart, rep.sampleEnd,
+ forceSensorStartEndOptimized,
+ );
+ */
+
pulseFraction = 1;
return true;
}
+ /*
+ //this exports the csv... it should be done by R
private bool writeFile()
{
string destination = UtilEncoder.GetmifExportFileName();
@@ -2441,6 +2587,7 @@ public class ForceSensorExport
return false;
}
}
+ */
}
//we need this class because we started using forcesensor without database (only text files)
diff --git a/src/gui/app1/forceSensor.cs b/src/gui/app1/forceSensor.cs
index f2e47f6e..80efc705 100644
--- a/src/gui/app1/forceSensor.cs
+++ b/src/gui/app1/forceSensor.cs
@@ -2167,11 +2167,16 @@ LogB.Information(" fs R ");
* read this file to see which is the decimal point
*/
- ForceSensorGraph fsg = new ForceSensorGraph(getForceSensorCaptureOptions(), rfdList, impulse,
+ ForceSensorGraph fsg = new ForceSensorGraph(
+ rfdList, impulse,
duration, Convert.ToInt32(spin_force_rfd_duration_percent.Value),
- title, exercise, currentForceSensor.DateTimePublic, triggerListForceSensor,
- sampleA, sampleB, preferences.forceSensorStartEndOptimized,
- Util.CSVDecimalColumnIsPoint(UtilEncoder.GetmifCSVFileName(), 1)
// (*)
+ preferences.forceSensorStartEndOptimized,
+ Util.CSVDecimalColumnIsPoint(UtilEncoder.GetmifCSVFileName(), 1),
+ new ForceSensorGraphAB(
+ "", //unused on single graph (no export)
+ getForceSensorCaptureOptions(),
+ sampleA, sampleB,
+ title, exercise, currentForceSensor.DateTimePublic,
triggerListForceSensor)
);
int imageWidth = UtilGtk.WidgetWidth(viewport_force_sensor_graph);
@@ -2181,7 +2186,7 @@ LogB.Information(" fs R ");
if(imageHeight < 300)
imageHeight = 300; //Not crash R with a png height of -1 or "figure margins too large"
- bool success = fsg.CallR(imageWidth -5, imageHeight -5);
+ bool success = fsg.CallR(imageWidth -5, imageHeight -5, true);
if(! success)
{
diff --git a/src/utilEncoder.cs b/src/utilEncoder.cs
index df190554..cde19960 100644
--- a/src/utilEncoder.cs
+++ b/src/utilEncoder.cs
@@ -257,6 +257,9 @@ public class UtilEncoder
public static string GetmifScript() {
return System.IO.Path.Combine(GetSprintPath(), "maximumIsometricForce.R");
}
+ public static string GetmifCSVInputMulti() {
+ return Path.Combine(Path.GetTempPath(), "maximumIsometricForceInputMulti.csv");
+ }
public static string GetmifCSVFileName() {
return Path.Combine(Path.GetTempPath(), "cj_mif_Data.csv");
}
[
Date Prev][
Date Next] [
Thread Prev][
Thread Next]
[
Thread Index]
[
Date Index]
[
Author Index]