[chronojump] encoder analyze side compare can share X axis if desired



commit 4affb6afa52ea683ad195d674d142ac8b55f9a98
Author: Xavier de Blas <xaviblas gmail com>
Date:   Fri Mar 30 08:30:27 2018 +0200

    encoder analyze side compare can share X axis if desired

 encoder/graph.R    |   65 +++++++++++++++++++++++++++++++++++----------------
 glade/app1.glade   |   20 ++++++++++++++++
 src/gui/encoder.cs |   25 +++++++++++++++++--
 3 files changed, 86 insertions(+), 24 deletions(-)
---
diff --git a/encoder/graph.R b/encoder/graph.R
index 687e0a1..d0b7007 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -495,7 +495,7 @@ canJump <- function(encoderConfigurationName)
 }
 
 
-paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose, highlight,
+paint <- function(displacement, eccon, xmin, xmax, xrange, yrange, knRanges, superpose, highlight,
                   startX, startH, smoothingOneEC, smoothingOneC, massBody, massExtra, 
                   
encoderConfigurationName,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown, 
#encoderConfiguration stuff
                   title, subtitle, draw, width, showLabels, marShrink, showAxes, legend,
@@ -545,7 +545,7 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
         if(draw) {
                 #three vertical axis inspired on http://www.r-bloggers.com/multiple-y-axis-in-a-r-plot/
                 par(mar=c(3, 3.5, 5, marginRight))
-                if(marShrink) #used on "side" compare
+                if(marShrink) #used on "side" && "sideShareX" compare
                         par(mar=c(1, 1, 4, 1))
                 
                 #plot distance
@@ -555,9 +555,14 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
                 #      xlab="time (ms)"
                 #      ylab="Left: distance (mm); Right: speed (m/s), force (N), power (W)"
                 #}
+
+               xlim=xrange
+                if(xlim[1]=="undefined") { xlim=c(1,length(position)) }
+
                 ylim=yrange
                 if(ylim[1]=="undefined") { ylim=NULL }
-                plot(position-min(position),type="n",xlim=c(1,length(position)),ylim=ylim,xlab=xlab, 
ylab=ylab, col="gray", axes=F)
+
+               plot(position-min(position),type="n",xlim=xlim,ylim=ylim,xlab=xlab, ylab=ylab, col="gray", 
axes=F)
                 
                 title(main=title,line=-2,outer=T)
                 mtext(subtitle,side=1,adj=0,cex=.8)
@@ -574,14 +579,14 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
                         colNormal="gray30"
                 yValues = position[startX:length(position)]-min(position[startX:length(position)])
                 if(highlight==FALSE) {
-                        plot(startX:length(position),yValues,type="l",xlim=c(1,length(position)),ylim=ylim,
+                        plot(startX:length(position),yValues,type="l",xlim=xlim,ylim=ylim,
                              xlab="",ylab="",col="black",lty=lty[1],lwd=2,axes=F)
                         par(new=T)
-                        plot(startX:length(position),yValues,type="h",xlim=c(1,length(position)),ylim=ylim,
+                        plot(startX:length(position),yValues,type="h",xlim=xlim,ylim=ylim,
                              xlab="",ylab="",col="grey90",lty=lty[1],lwd=1,axes=F)
                 }
                 else
-                        
plot(startX:length(position),yValues,type="l",xlim=c(1,length(position)),ylim=ylim,xlab="",ylab="",col=colNormal,lty=2,lwd=3,axes=F)
+                        
plot(startX:length(position),yValues,type="l",xlim=xlim,ylim=ylim,xlab="",ylab="",col=colNormal,lty=2,lwd=3,axes=F)
                 abline(h=0,lty=3,col="black")
 
                if(triggersOnList != "" && triggersOnList != -1)
@@ -607,6 +612,8 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
         #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
         
+       xlim=xrange
+        if(xlim[1]=="undefined") { xlim=c(1,length(displacement)) }
         
         #if(draw & !superpose) 
         #      
segments(x0=speed.ext$maxindex,y0=0,x1=speed.ext$maxindex,y1=speed$y[speed.ext$maxindex],col=cols[1])
@@ -742,10 +749,10 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
                 
                 if(highlight==FALSE)
                         plot(startX:length(speedPlot),speedPlot[startX:length(speedPlot)],type="l",
-                             
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col=cols[1],lty=lty[1],lwd=1,axes=F)
+                             xlim=xlim,ylim=ylim,xlab="",ylab="",col=cols[1],lty=lty[1],lwd=1,axes=F)
                 else
                         plot(startX:length(speedPlot),speedPlot[startX:length(speedPlot)],type="l",
-                             
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col="darkgreen",lty=2,lwd=3,axes=F)
+                             xlim=xlim,ylim=ylim,xlab="",ylab="",col="darkgreen",lty=2,lwd=3,axes=F)
                 
         }
         
@@ -856,10 +863,10 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
                         par(new=T)
                         if(highlight==FALSE)
                                 plot(startX:length(accel$y),accel$y[startX:length(accel$y)],type="l",
-                                     
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col="magenta",lty=lty[2],lwd=1,axes=F)
+                                     
xlim=xlim,ylim=ylim,xlab="",ylab="",col="magenta",lty=lty[2],lwd=1,axes=F)
                         else
                                 plot(startX:length(accel$y),accel$y[startX:length(accel$y)],type="l",
-                                     
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col="darkblue",lty=2,lwd=3,axes=F)
+                                     xlim=xlim,ylim=ylim,xlab="",ylab="",col="darkblue",lty=2,lwd=3,axes=F)
                 }
                 
                 #show propulsive stuff if line if differentiation is relevant (propulsivePhase ends before 
the end of the movement)
@@ -911,10 +918,10 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
                 par(new=T)
                 if(highlight==FALSE)
                         plot(startX:length(force),force[startX:length(force)],type="l",
-                             
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col=cols[2],lty=lty[2],lwd=1,axes=F)
+                             xlim=xlim,ylim=ylim,xlab="",ylab="",col=cols[2],lty=lty[2],lwd=1,axes=F)
                 else
                         plot(startX:length(force),force[startX:length(force)],type="l",
-                             
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col="darkblue",lty=2,lwd=3,axes=F)
+                             xlim=xlim,ylim=ylim,xlab="",ylab="",col="darkblue",lty=2,lwd=3,axes=F)
                 if(showAxes) {
                         axis(4, col=cols[2], lty=lty[2], line=axisLineRight, lwd=1, padj=-.5)
                         axisLineRight = axisLineRight +2
@@ -924,10 +931,10 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
                         #print("dynamics$forceDisc")
                         #print(dynamics$forceDisc)
                         par(new=T)
-                        plot(dynamics$forceDisc, col="blue", xlab="", ylab="", 
xlim=c(1,length(displacement)),ylim=ylim, type="p", pch=1, axes=F);
+                        plot(dynamics$forceDisc, col="blue", xlab="", ylab="", xlim=xlim,ylim=ylim, 
type="p", pch=1, axes=F);
                         
                         par(new=T)
-                        plot(dynamics$forceBody, col="blue", xlab="", ylab="", 
xlim=c(1,length(displacement)),ylim=ylim, type="p", pch=3, axes=F);
+                        plot(dynamics$forceBody, col="blue", xlab="", ylab="", xlim=xlim,ylim=ylim, 
type="p", pch=3, axes=F);
                 }
         }
         
@@ -1005,18 +1012,18 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
                 par(new=T);
                 if(highlight==FALSE)
                         plot(startX:length(power),power[startX:length(power)],type="l",
-                             
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col=cols[3],lty=lty[3],lwd=2,axes=F)
+                             xlim=xlim,ylim=ylim,xlab="",ylab="",col=cols[3],lty=lty[3],lwd=2,axes=F)
                 else
                         plot(startX:length(power),power[startX:length(power)],type="l",
-                             
xlim=c(1,length(displacement)),ylim=ylim,xlab="",ylab="",col="darkred",lty=2,lwd=3,axes=F)
+                             xlim=xlim,ylim=ylim,xlab="",ylab="",col="darkred",lty=2,lwd=3,axes=F)
                 
                 
                 if(isInertial(encoderConfigurationName) && debugOld) {
                         par(new=T)
-                        plot(dynamics$powerDisc, col="orangered3", xlab="", ylab="", 
xlim=c(1,length(displacement)),ylim=ylim, type="p", pch=1, axes=F);
+                        plot(dynamics$powerDisc, col="orangered3", xlab="", ylab="", xlim=xlim, ylim=ylim, 
type="p", pch=1, axes=F);
                         
                         par(new=T)
-                        plot(dynamics$powerBody, col="orangered3", xlab="", ylab="", 
xlim=c(1,length(displacement)),ylim=ylim, type="p", pch=3, axes=F);
+                        plot(dynamics$powerBody, col="orangered3", xlab="", ylab="", xlim=xlim, ylim=ylim, 
type="p", pch=3, axes=F);
                 }
                 
                 
@@ -2346,6 +2353,17 @@ find.mfrow <- function(n) {
         else return(c(3, ceiling(n/3)))
 }
 
+find.xrange <- function(singleFile, displacement, curves) {
+        n=length(curves[,1])
+        x.max = 0
+        for(i in 1:n) {
+                x.current = length(displacement[curves[i,1]:curves[i,2]])
+                if(max(x.current) > x.max)
+                        x.max = max(x.current)
+        }
+        return (c(0,x.max))
+}
+
 find.yrange <- function(singleFile, displacement, curves) {
         n=length(curves[,1])
         y.max = 0
@@ -2974,7 +2992,7 @@ doProcess <- function(options)
                        if(! cutByTriggers(op))
                                triggersOnList = op$TriggersOnList;
 
-                        paint(displacement, repOp$eccon, myStart, myEnd,"undefined","undefined",FALSE,FALSE,
+                        paint(displacement, repOp$eccon, myStart, myEnd, 
"undefined","undefined","undefined",FALSE,FALSE,
                               
1,curves[op$Jump,3],SmoothingsEC[smoothingPos],op$SmoothingOneC,repOp$massBody,repOp$massExtra,
                               
repOp$econfName,repOp$diameter,repOp$diameterExt,repOp$anglePush,repOp$angleWeight,repOp$inertiaM,repOp$gearedDown,
                               paste(op$Title, " ", op$Analysis, " ", repOp$eccon, ". ", myCurveStr, sep=""),
@@ -3191,10 +3209,15 @@ doProcess <- function(options)
                 write("done!", stderr())
         }
         
-        if(op$Analysis=="side") {
+        if(op$Analysis=="side" || op$Analysis=="sideShareX") {
                 #comparar 6 salts, falta que xlim i ylim sigui el mateix
                 par(mfrow=find.mfrow(n))
                 
+               xrange="undefined"
+               if(op$Analysis=="sideShareX") {
+                       xrange=find.xrange(singleFile, displacement, curves)
+               }
+
                 yrange=find.yrange(singleFile, displacement, curves)
                 
                 #if !singleFile kinematicRanges takes the 'curves' values
@@ -3223,7 +3246,7 @@ doProcess <- function(options)
                        if(! cutByTriggers(op))
                                triggersOnList = op$TriggersOnList;
 
-                        paint(displacement, repOp$eccon, curves[i,1],curves[i,2],yrange,knRanges,FALSE,FALSE,
+                        paint(displacement, repOp$eccon, 
curves[i,1],curves[i,2],xrange,yrange,knRanges,FALSE,FALSE,
                               1,curves[i,3],SmoothingsEC[i],op$SmoothingOneC,repOp$massBody,repOp$massExtra,
                               
repOp$econfName,repOp$diameter,repOp$diameterExt,repOp$anglePush,repOp$angleWeight,repOp$inertiaM,repOp$gearedDown,
                               myTitle,mySubtitle,
diff --git a/glade/app1.glade b/glade/app1.glade
index 015922f..616b12b 100644
--- a/glade/app1.glade
+++ b/glade/app1.glade
@@ -1652,6 +1652,9 @@
                                                             <placeholder/>
                                                             </child>
                                                             <child>
+                                                            <placeholder/>
+                                                            </child>
+                                                            <child>
                                                             <widget class="GtkLabel" 
id="label_start_selector_jumps">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
@@ -22952,6 +22955,20 @@ then click this button.</property>
                                                             <property name="position">1</property>
                                                             </packing>
                                                             </child>
+                                                            <child>
+                                                            <widget class="GtkCheckButton" 
id="checkbutton_encoder_analyze_side_share_x">
+                                                            <property name="label" translatable="yes">Share 
X axis</property>
+                                                            <property name="can_focus">True</property>
+                                                            <property 
name="receives_default">False</property>
+                                                            <property name="draw_indicator">True</property>
+                                                            <signal name="toggled" 
handler="on_checkbutton_encoder_analyze_side_share_x_toggled" swapped="no"/>
+                                                            </widget>
+                                                            <packing>
+                                                            <property name="expand">True</property>
+                                                            <property name="fill">True</property>
+                                                            <property name="position">2</property>
+                                                            </packing>
+                                                            </child>
                                                             </widget>
                                                             <packing>
                                                             <property name="expand">False</property>
@@ -24945,6 +24962,9 @@ then click this button.</property>
                                                             <child>
                                                             <placeholder/>
                                                             </child>
+                                                            <child>
+                                                            <placeholder/>
+                                                            </child>
                                                             </widget>
                                                             <packing>
                                                             <property name="expand">False</property>
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index 8027d6d..8725528 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -164,6 +164,7 @@ public partial class ChronoJumpWindow
        [Widget] Gtk.CheckButton check_encoder_analyze_show_accel;
        [Widget] Gtk.CheckButton check_encoder_analyze_show_force;
        [Widget] Gtk.CheckButton check_encoder_analyze_show_power;
+       [Widget] Gtk.CheckButton checkbutton_encoder_analyze_side_share_x;
        
        [Widget] Gtk.CheckButton checkbutton_crossvalidate;
        [Widget] Gtk.Button button_encoder_analyze;
@@ -2683,7 +2684,7 @@ public partial class ChronoJumpWindow
                        }
                }
                
-               if(sendAnalysis == "powerBars" || sendAnalysis == "single" || sendAnalysis == "side")
+               if(sendAnalysis == "powerBars" || sendAnalysis == "single" || sendAnalysis == "side" || 
sendAnalysis == "sideShareX")
                        analysisVariables = getAnalysisVariables(sendAnalysis);
 
                if( ! radio_encoder_analyze_individual_current_set.Active) //not current set
@@ -3174,7 +3175,7 @@ public partial class ChronoJumpWindow
                        else
                                analysisVariables += ";NoRange";
                }
-               else {  //analysis == "single" || analysis == "side")
+               else {  //analysis == "single" || analysis == "side" || analysis == "sideShareX"
                        if(check_encoder_analyze_show_speed.Active)
                                analysisVariables = "Speed";
                        else
@@ -3210,6 +3211,7 @@ public partial class ChronoJumpWindow
                check_encoder_analyze_mean_or_max.Visible=false;
                hbox_encoder_analyze_show_powerbars.Visible=false;
                hbox_encoder_analyze_show_SAFE.Visible=true;
+               checkbutton_encoder_analyze_side_share_x.Visible = false;
                encoderSelectedAnalysis = "single";
                
                //together, mandatory
@@ -3235,6 +3237,7 @@ public partial class ChronoJumpWindow
                check_encoder_analyze_mean_or_max.Visible=false;
                hbox_encoder_analyze_show_powerbars.Visible=false;
                hbox_encoder_analyze_show_SAFE.Visible=true;
+               checkbutton_encoder_analyze_side_share_x.Visible = false;
                encoderSelectedAnalysis = "superpose";
                
                //together, mandatory
@@ -3257,7 +3260,12 @@ public partial class ChronoJumpWindow
                check_encoder_analyze_mean_or_max.Visible=false;
                hbox_encoder_analyze_show_powerbars.Visible=false;
                hbox_encoder_analyze_show_SAFE.Visible=true;
-               encoderSelectedAnalysis = "side";
+               checkbutton_encoder_analyze_side_share_x.Visible = true;
+
+               if(checkbutton_encoder_analyze_side_share_x.Active)
+                       encoderSelectedAnalysis = "sideShareX";
+               else
+                       encoderSelectedAnalysis = "side";
                
                //together, mandatory
                check_encoder_analyze_eccon_together.Sensitive=false;
@@ -3271,6 +3279,13 @@ public partial class ChronoJumpWindow
                encoderButtonsSensitive(encoderSensEnumStored);
                button_encoder_analyze_sensitiveness();
        }
+       private void on_checkbutton_encoder_analyze_side_share_x_toggled (object o, EventArgs args)
+       {
+               if(checkbutton_encoder_analyze_side_share_x.Active)
+                       encoderSelectedAnalysis = "sideShareX";
+               else
+                       encoderSelectedAnalysis = "side";
+       }
        private void on_radiobutton_encoder_analyze_powerbars_toggled (object obj, EventArgs args) {
                hbox_encoder_analyze_curve_num.Visible=false;
                hbox_combo_encoder_analyze_curve_num_combo.Visible = false;
@@ -3279,6 +3294,7 @@ public partial class ChronoJumpWindow
                check_encoder_analyze_mean_or_max.Visible=false;
                hbox_encoder_analyze_show_powerbars.Visible=true;
                hbox_encoder_analyze_show_SAFE.Visible=false;
+               checkbutton_encoder_analyze_side_share_x.Visible = false;
                encoderSelectedAnalysis = "powerBars";
                
                check_encoder_analyze_eccon_together.Sensitive=true;
@@ -3302,6 +3318,7 @@ public partial class ChronoJumpWindow
                check_encoder_analyze_mean_or_max.Visible=true;
                hbox_encoder_analyze_show_powerbars.Visible=false;
                hbox_encoder_analyze_show_SAFE.Visible=false;
+               checkbutton_encoder_analyze_side_share_x.Visible = false;
                encoderSelectedAnalysis = "cross";
                
                check_encoder_analyze_eccon_together.Sensitive=true;
@@ -3325,6 +3342,7 @@ public partial class ChronoJumpWindow
                check_encoder_analyze_mean_or_max.Visible=true;
                hbox_encoder_analyze_show_powerbars.Visible=false;
                hbox_encoder_analyze_show_SAFE.Visible=false;
+               checkbutton_encoder_analyze_side_share_x.Visible = false;
                encoderSelectedAnalysis = "1RM";
                
                check_encoder_analyze_eccon_together.Sensitive=true;
@@ -3348,6 +3366,7 @@ public partial class ChronoJumpWindow
                check_encoder_analyze_mean_or_max.Visible=false;
                hbox_encoder_analyze_show_powerbars.Visible=false;
                hbox_encoder_analyze_show_SAFE.Visible=false;
+               checkbutton_encoder_analyze_side_share_x.Visible = false;
                encoderSelectedAnalysis = "neuromuscularProfile";
                
                //separated, mandatory


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