[chronojump] Set analyze instant can select all set



commit 8f8340de2f679ee56939e88a3be07c230e1521e7
Author: Xavier de Blas <xaviblas gmail com>
Date:   Fri Mar 18 17:26:41 2016 +0100

    Set analyze instant can select all set

 encoder/graph.R            |  123 +++++++++++++++++++++++++++++++++++++++-----
 encoder/graphSmoothingEC.R |   86 +++++++++++++++++++++---------
 encoder/util.R             |    6 +-
 src/gui/encoder.cs         |   38 +++++++++-----
 4 files changed, 196 insertions(+), 57 deletions(-)
---
diff --git a/encoder/graph.R b/encoder/graph.R
index 41dcc13..3248171 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -2043,6 +2043,7 @@ createPchVector <- function(ecconVector) {
        return (as.numeric(pchVector))
 }
 
+
 #-------------------- EncoderConfiguration conversions --------------------------
 
 
@@ -2096,7 +2097,6 @@ doProcess <- function(options)
        if(op$Analysis == "neuromuscularProfile")
                source(paste(op$EncoderRScriptsPath, "/neuromuscularProfile.R", sep=""))
 
-
        print(op$File)
        print(op$OutputGraph)
        print(op$OutputData1)
@@ -2474,7 +2474,11 @@ doProcess <- function(options)
        file.create(paste(op$FeedbackFileBase,"4.txt",sep=""))
        #print(curves)
 
-       if(op$Analysis=="single") {
+
+       if(op$Analysis=="single") 
+       {
+               df = NULL
+
                if(op$Jump>0) {
                        myStart = curves[op$Jump,1]
                        myEnd = curves[op$Jump,2]
@@ -2521,10 +2525,6 @@ doProcess <- function(options)
                              )
                
        
-                       write(op$Width, op$SpecialData)
-                       write(par("usr"), op$SpecialData, append=TRUE)
-                       write(par("plt"),  op$SpecialData, append=TRUE)
-
                        #record array of data   
                        write("going to create array of data", stderr())
                        kn <- kinematicsF(displacement[curves[op$Jump,1]:curves[op$Jump,2]],
@@ -2542,19 +2542,114 @@ doProcess <- function(options)
                        else
                                smoothingTemp = SmoothingsEC[smoothingPos]
 
+                       #prepare dataframe (will be written later)
                        df=data.frame(cbind(getPositionSmoothed(kn$displ,smoothingTemp), kn$speedy, 
kn$accely, kn$force, kn$power))
-                       colnames(df)=c("displacement","speed","acceleration","force","power")
+               } else {
+                       #1) find maxPowerAtAnyRep
+                       maxPowerAtAnyRep <- 0
+                       for(i in 1:n) {
+                               i.displ <- displacement[curves[i,1]:curves[i,2]]        
+                               speed <- getSpeedSafe(i.displ, op$SmoothingOneC)
+                               accel <- getAccelerationSafe(speed)
+                               #speed comes in mm/ms when derivate to accel its mm/ms^2 to convert it to 
m/s^2 need to *1000 because it's quadratic
+                               accel$y <- accel$y * 1000 
+
+                               dynamics <- getDynamics ("LINEAR",
+                                                        speed$y, accel$y, 
+                                                        op$MassBody, op$MassExtra, 
op$ExercisePercentBodyWeight,
+                                                        1, -1, -1,     #gearedDown, anglePush, angleWeight,
+                                                        i.displ, op$diameter, 
+                                                        -1, op$SmoothingOneC           #inertiaMomentum, 
smoothing
+                                                        )
+                               if(max(dynamics$power) > maxPowerAtAnyRep)
+                                       maxPowerAtAnyRep <- max(dynamics$power)
+                       }
+
+                       #2.a) find max power (y) for some smoothings(x)
+                       x <- seq(from = op$SmoothingOneC, to = 0, length.out = 30)
+                       y <- smoothAllSerieYPoints(x, displacement, op$MassBody, op$MassExtra, 
op$ExercisePercentBodyWeight, op$diameter)
+
+                       #2.b) create a model with x,y to find optimal x
+                       smodel <- smooth.spline(y,x)
+                       smoothingAll <- predict(smodel, maxPowerAtAnyRep)$y
+
+                       debugParameters(listN(x, y, maxPowerAtAnyRep, smoothingAll), "paint all smoothing 1")
+
+                       #2.c) find x values close to previous model
+                       temp.list <- findXValuesClose(x, y, maxPowerAtAnyRep)
+                       xUpperValue <- temp.list[[1]]
+                       xLowerValue <- temp.list[[2]]
+
+                       debugParameters(listN(xUpperValue, xLowerValue), "paint all smoothing 2")
+
+                       #3.a) find max power (y) for some smoothings(x) (closer)
+                       x <- seq(from = xUpperValue, to = xLowerValue, length.out = 5)
+                       y <- smoothAllSerieYPoints(x, displacement, op$MassBody, op$MassExtra, 
op$ExercisePercentBodyWeight, op$diameter)
+
+                       #3.b) create a model with x,y to find optimal x (in closer values)
+                       smodel <- smooth.spline(y,x)
+                       smoothingAll <- predict(smodel, maxPowerAtAnyRep)$y
+
+                       debugParameters(listN(x, y, maxPowerAtAnyRep, smoothingAll), "paint all smoothing 3")
 
-                       write("going to write it to file", stderr())
-                       #write(paste("length", curves[op$Jump,2] - curves[op$Jump,1] ), stderr())
-                       #write(paste("df", length(df[,1])), stderr())
-                       #write(paste("eccon", repOp$eccon), stderr())
-                       write.csv(df, paste(op$EncoderTempPath,"/chronojump-analysis-instant.csv",sep=""), 
append=TRUE, quote=FALSE)
+                       #4) create dynamics data for this smoothing
+                       speed <- getSpeedSafe(displacement, smoothingAll)
+                       accel <- getAccelerationSafe(speed)
+                       #speed comes in mm/ms when derivate to accel its mm/ms^2 to convert it to m/s^2 need 
to *1000 because it's quadratic
+                       accel$y <- accel$y * 1000 
+
+                       dynamics <- getDynamics ("LINEAR",
+                                                speed$y, accel$y, 
+                                                op$MassBody, op$MassExtra, op$ExercisePercentBodyWeight,
+                                                1, -1, -1,     #gearedDown, anglePush, angleWeight,
+                                                i.displ, op$diameter, 
+                                                -1, smoothingAll               #inertiaMomentum, smoothing
+                                                )
+
+
+                       #5) prepare dataframe (will be written later)
+                       df=data.frame(cbind(getPositionSmoothed(displacement,smoothingAll), speed$y, accel$y, 
dynamics$force, dynamics$power))
+
+                       #6) paint
+                       plot((1:length(position))/1000                  #ms -> s
+                            ,position/10,                              #mm -> cm
+                            type="l", xlab="",ylab="",axes=T, lty=1,col="black",
+                            main="Seing all serie (only works with LINEAR configurations right now)") 
+
+                       if (op$AnalysisVariables[1] == "Speed") { #show speed
+                               par(new=T)      
+                               plot(speed$y, col=cols[1], type="l", xlab="",ylab="",axes=F)
+                       }
+
+                       if (op$AnalysisVariables[2] == "Accel") { #show accel
+                               par(new=T)      
+                               plot(accel$y, col="magenta", type="l", xlab="",ylab="",axes=F)
+                       }
+
+                       if (op$AnalysisVariables[3] == "Force") { #show force
+                               par(new=T)      
+                               plot(dynamics$force, col=cols[2], type="l", xlab="",ylab="",axes=F)
+                       }
+
+                       if (op$AnalysisVariables[4] == "Power") {  #show power
+                               par(new=T)      
+                               plot(dynamics$power, col=cols[3], type="l", lwd=2, xlab="",ylab="",axes=F)
+                       }
 
-                       write("done!", stderr())
                }
+       
+               #needed to align the AB vertical lines on C#
+               write(op$Width, op$SpecialData)
+               write(par("usr"), op$SpecialData, append=TRUE)
+               write(par("plt"),  op$SpecialData, append=TRUE)
+               
+               #write dataframe to file        
+               colnames(df)=c("displacement","speed","acceleration","force","power")
+               write("going to write it to file", stderr())
+               write.csv(df, paste(op$EncoderTempPath,"/chronojump-analysis-instant.csv",sep=""), 
append=TRUE, quote=FALSE)
+               write("done!", stderr())
        }
-
+       
        if(op$Analysis=="side") {
                #comparar 6 salts, falta que xlim i ylim sigui el mateix
                par(mfrow=find.mfrow(n))
diff --git a/encoder/graphSmoothingEC.R b/encoder/graphSmoothingEC.R
index 6d2f884..95e7b2d 100644
--- a/encoder/graphSmoothingEC.R
+++ b/encoder/graphSmoothingEC.R
@@ -77,6 +77,8 @@ findSmoothingsECYPoints <- function(eccentric.concentric, conStart, conEnd, x, m
 
        return(y)
 }
+                               
+
 
 #called on "ec" and "ce" to have a smoothingOneEC for every curve
 #this smoothingOneEC has produce same speeds than smoothing "c"
@@ -190,32 +192,9 @@ findSmoothingsEC <- function(singleFile, displacement, curves, eccon, smoothingO
 
                                #4 create new x values closer
 
-                               #eg 
-                               #x:   .7,     .6125,     .525,     .4375,     .35
-                               #y: 1156, 1190     , 1340    , 1736     , 2354
-                               #lowerValue ald it's lowerPos are reffered to the x vector. 1 means the first 
(0.7)
-                               #A) if we find the x for an y = 1900, x should be between .4375 (lowerValue) 
and .35 (upperValue)
-                               #B) if we find the x for an y = 2500, x should be between .35 (lowerValue) 
and (right of .35) (upperValue)
-                               #C) if we find the x for an y = 1000, x should be between (left of .7) 
(lowerValue) and .7 (upperValue)
-
-                               xUpperValue = NULL
-                               xLowerValue = NULL
-
-                               upperPos <- min(which(y > maxPowerConAtCon)) #A: 5, C:1
-                               if(is.infinite(upperPos)) {     
-                                       xUpperValue <- x[length(x)] - (x[length(x) -1] - x[length(x)])  #B: 
.35 - (.4375-.35) = .2625
-                                       xLowerValue <- x[length(x)]                                     #B: 
.35
-                               }
-                               else {
-                                       xUpperValue <- x[upperPos]      #A: .35
-                                       lowerPos <- upperPos -1
-                                       
-                                       if(lowerPos >= 1)
-                                               xLowerValue <- x[lowerPos]      #A: .4375
-                                       else
-                                               xLowerValue <- x[1] + (x[1] - x[2]) #C: .7 + (.7-.6125) = 
.7875
-                               }
-
+                               temp.list <- findXValuesClose(x, y, maxPowerConAtCon)
+                               xUpperValue <- temp.list[[1]]
+                               xLowerValue <- temp.list[[2]]
 
                                #5 get max power concentric (y) at eccentric-concentric phase with current 
smoothing of an interval of possible smoothings (x)
                                
@@ -259,3 +238,58 @@ findSmoothingsEC <- function(singleFile, displacement, curves, eccon, smoothingO
                
        return(smoothings)
 }
+
+smoothAllSerieYPoints <- function(smooth.seq, displacement, massBody, massExtra, exPercentBodyWeight, 
diameter)
+{
+       y <- NULL 
+       count <- 1
+       for (i in smooth.seq) {
+               #print(c("i",i))
+               speed <- getSpeedSafe(displacement, i)
+               accel <- getAccelerationSafe(speed)
+               #speed comes in mm/ms when derivate to accel its mm/ms^2 to convert it to m/s^2 need to *1000 
because it's quadratic
+               accel$y <- accel$y * 1000 
+
+               dynamics <- getDynamics ("LINEAR",
+                                        speed$y, accel$y, 
+                                        massBody, massExtra, exPercentBodyWeight, 
+                                        1, -1, -1,     #gearedDown, anglePush, angleWeight,
+                                        displacement, diameter, 
+                                        -1, i          #inertiaMomentum, smoothing
+                                        )
+               y[count] = max(dynamics$power)
+               count <- count +1
+       }
+       return(y)
+}
+
+#Attention: x should be from high to low!
+#eg 
+#x:   .7,     .6125,     .525,     .4375,     .35
+#y: 1156, 1190     , 1340    , 1736     , 2354
+#lowerValue ald it's lowerPos are reffered to the x vector. 1 means the first (0.7)
+#A) if we find the x for an y = 1900, x should be between .4375 (lowerValue) and .35 (upperValue)
+#B) if we find the x for an y = 2500, x should be between .35 (lowerValue) and (right of .35) (upperValue)
+#C) if we find the x for an y = 1000, x should be between (left of .7) (lowerValue) and .7 (upperValue)
+
+findXValuesClose <- function(x, y, y.searched)
+{
+       xUpperValue = NULL
+       xLowerValue = NULL
+
+       upperPos <- min(which(y > y.searched)) #A: 5, C:1
+       if(is.infinite(upperPos)) {     
+               xUpperValue <- x[length(x)] - (x[length(x) -1] - x[length(x)])  #B: .35 - (.4375-.35) = .2625
+               xLowerValue <- x[length(x)]                                     #B: .35
+       }
+       else {
+               xUpperValue <- x[upperPos]      #A: .35
+               lowerPos <- upperPos -1
+
+               if(lowerPos >= 1)
+                       xLowerValue <- x[lowerPos]      #A: .4375
+               else
+                       xLowerValue <- x[1] + (x[1] - x[2]) #C: .7 + (.7-.6125) = .7875
+       }
+       return(list(xUpperValue, xLowerValue))
+}
diff --git a/encoder/util.R b/encoder/util.R
index b18587d..5ef9b9a 100644
--- a/encoder/util.R
+++ b/encoder/util.R
@@ -739,9 +739,9 @@ getDynamics <- function(encoderConfigurationName,
                        speed, accel, massBody, massExtra, exercisePercentBodyWeight, gearedDown, anglePush, 
angleWeight,
                        displacement, diameter, inertiaMomentum, smoothing)
 {
-       debugParameters(listN(encoderConfigurationName,
-                            speed, accel, massBody, massExtra, exercisePercentBodyWeight, gearedDown, 
anglePush, angleWeight,
-                            displacement, diameter, inertiaMomentum, smoothing), "getDynamics")
+       #debugParameters(listN(encoderConfigurationName,
+       #                    speed, accel, massBody, massExtra, exercisePercentBodyWeight, gearedDown, 
anglePush, angleWeight,
+       #                    displacement, diameter, inertiaMomentum, smoothing), "getDynamics")
        
 
        massBody = getMassBodyByExercise(massBody,exercisePercentBodyWeight)
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index c6abf31..e1aebf5 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -828,12 +828,13 @@ public partial class ChronoJumpWindow
                                                encoderEcconTranslation) != Constants.Concentric) 
                                        curvesNum = curvesNum / 2;
                        
-                               string [] activeCurvesList = new String[curvesNum];
-                               for(int i=0; i < curvesNum; i++)
-                                       activeCurvesList[i] = (i+1).ToString();
+                               string [] activeCurvesList = new String[curvesNum +1];
+                               activeCurvesList[0] = Catalog.GetString("All");
+                               for(int i=1; i <= curvesNum; i++)
+                                       activeCurvesList[i] = i.ToString();
                                UtilGtk.ComboUpdate(combo_encoder_analyze_curve_num_combo, activeCurvesList, 
"");
                                combo_encoder_analyze_curve_num_combo.Active = 
-                                       UtilGtk.ComboMakeActive(combo_encoder_analyze_curve_num_combo, 
activeCurvesList[0]);
+                                       UtilGtk.ComboMakeActive(combo_encoder_analyze_curve_num_combo, 
activeCurvesList[1]);
                                
                                encoderButtonsSensitive(encoderSensEnum.DONEYESSIGNAL);
                        }
@@ -1079,9 +1080,10 @@ public partial class ChronoJumpWindow
                label_encoder_user_curves_active_num.Text = activeCurvesNum.ToString();
 
                string [] activeCurvesList = getActiveCheckboxesList(checkboxes, activeCurvesNum);
+               activeCurvesList = Util.AddArrayString(activeCurvesList, Catalog.GetString("All"), true); 
//Add "All" first
                UtilGtk.ComboUpdate(combo_encoder_analyze_curve_num_combo, activeCurvesList, "");
                combo_encoder_analyze_curve_num_combo.Active = 
-                       UtilGtk.ComboMakeActive(combo_encoder_analyze_curve_num_combo, activeCurvesList[0]);
+                       UtilGtk.ComboMakeActive(combo_encoder_analyze_curve_num_combo, activeCurvesList[1]);
 
                genericWin.HideAndNull();
                
@@ -1949,7 +1951,7 @@ public partial class ChronoJumpWindow
                if(check_encoder_analyze_signal_or_curves.Active)
                        updateComboEncoderAnalyzeCurveNumFromCurrentSet ();
                else
-                       updateComboEncoderAnalyzeCurveNum(data, activeCurvesNum);       
+                       updateComboEncoderAnalyzeCurveNumSavedReps(data, activeCurvesNum);      
        
                button_encoder_analyze_sensitiveness();
        }
@@ -1976,21 +1978,24 @@ public partial class ChronoJumpWindow
                if(ecconLast != "c")
                        rows = rows / 2;
 
+               int defaultValue = 0;
                string [] activeCurvesList;
                if(rows == 0)
                        activeCurvesList = Util.StringToStringArray("");
                else {
-                       activeCurvesList = new String[rows];
-                       for(int i=0; i < rows; i++)
-                               activeCurvesList[i] = (i+1).ToString();
+                       activeCurvesList = new String[rows +1];
+                       activeCurvesList[0] = Catalog.GetString("All");
+                       for(int i=1; i <= rows; i++)
+                               activeCurvesList[i] = i.ToString();
+                       defaultValue = 1;
                }
 
                UtilGtk.ComboUpdate(combo_encoder_analyze_curve_num_combo, activeCurvesList, "");
                combo_encoder_analyze_curve_num_combo.Active = 
-                       UtilGtk.ComboMakeActive(combo_encoder_analyze_curve_num_combo, activeCurvesList[0]);
+                       UtilGtk.ComboMakeActive(combo_encoder_analyze_curve_num_combo, 
activeCurvesList[defaultValue]);
        }
        //saved repetitions
-       private void updateComboEncoderAnalyzeCurveNum (ArrayList data, int activeCurvesNum) 
+       private void updateComboEncoderAnalyzeCurveNumSavedReps (ArrayList data, int activeCurvesNum) 
        {
                string [] checkboxes = new string[data.Count]; //to store active or inactive status of curves
                int count = 0;
@@ -3034,6 +3039,11 @@ public partial class ChronoJumpWindow
                                        sendAnalysis = "1RMIndirect";
                                }
                        }
+                       
+                       //if combo_encoder_analyze_curve_num_combo "All" is selected, then use a 0, else get 
the number
+                       int curveNum = 0; //all
+                       if(Util.IsNumber(UtilGtk.ComboGetActive(combo_encoder_analyze_curve_num_combo), 
false))
+                               curveNum = 
Convert.ToInt32(UtilGtk.ComboGetActive(combo_encoder_analyze_curve_num_combo));
 
                        ep = new EncoderParams(
                                        
encoderCaptureOptionsWin.GetMinHeight(encoderConfigurationCurrent.has_inertia),
@@ -3046,7 +3056,7 @@ public partial class ChronoJumpWindow
                                        analysisOptions,
                                        encoderConfigurationCurrent,
                                        Util.ConvertToPoint(preferences.encoderSmoothCon),      //R decimal: 
'.'
-                                       
Convert.ToInt32(UtilGtk.ComboGetActive(combo_encoder_analyze_curve_num_combo)),
+                                       curveNum,
                                        image_encoder_width,
                                        image_encoder_height,
                                        preferences.CSVExportDecimalSeparator 
@@ -3126,7 +3136,7 @@ public partial class ChronoJumpWindow
                                                "curve", EncoderSQL.Eccons.ALL,
                                                false, true);
                                int activeCurvesNum = getActiveCurvesNum(data);
-                               updateComboEncoderAnalyzeCurveNum(data, activeCurvesNum);       
+                               updateComboEncoderAnalyzeCurveNumSavedReps(data, activeCurvesNum);      
                        }
 
                        hbox_encoder_user_curves.Visible = currentPerson != null;
@@ -4147,7 +4157,7 @@ public partial class ChronoJumpWindow
                        //then combo_encoder_analyze_curve_num_combo has to be empty
                        UtilGtk.ComboUpdate(combo_encoder_analyze_curve_num_combo, new string [] {}, "");
                } else {        //saved repetitions
-                       updateComboEncoderAnalyzeCurveNum(data, activeCurvesNum);       
+                       updateComboEncoderAnalyzeCurveNumSavedReps(data, activeCurvesNum);      
                }
        
                encoderButtonsSensitive(encoderSensEnum.YESPERSON);


[Date Prev][Date Next]   [Thread Prev][Thread Next]   [Thread Index] [Date Index] [Author Index]