[chronojump] Encoder: propulsive phase on single (done)



commit 27f080d0061f26a09813508e14614024c670bb14
Author: Xavier de Blas <xaviblas gmail com>
Date:   Sun Nov 18 22:00:06 2012 +0100

    Encoder: propulsive phase on single (done)

 encoder/call_graph.py |    4 ++-
 encoder/graph.R       |   55 +++++++++++++++++++++++++++++++-----------------
 src/encoder.cs        |   10 ++++++--
 src/gui/encoder.cs    |   13 +++++++++++
 4 files changed, 58 insertions(+), 24 deletions(-)
---
diff --git a/encoder/call_graph.py b/encoder/call_graph.py
index c6266c2..81da06a 100644
--- a/encoder/call_graph.py
+++ b/encoder/call_graph.py
@@ -17,7 +17,9 @@ subprocess.Popen([
 	sys.argv[9],			#ep.analysis
 	sys.argv[10],			#ep.smooth
 	sys.argv[11],			#ep.curve
-	sys.argv[12],sys.argv[13]	#ep.width, ep.height
+	sys.argv[12],			#ep.analysisOptions
+	sys.argv[13],			#ep.width
+	sys.argv[14]			#ep.height
 	]).wait()
 
 
diff --git a/encoder/graph.R b/encoder/graph.R
index 0caa4b8..58eb674 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -230,7 +230,7 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
 			plot(startX:length(a),a[startX:length(a)],type="l",xlim=c(1,length(a)),ylim=ylim,xlab="",ylab="",col=colNormal,lty=2,lwd=3,axes=F)
 		abline(h=0,lty=3,col="black")
 
-		abline(v=seq(from=0,to=length(a),by=500),lty=3,col="gray")
+		#abline(v=seq(from=0,to=length(a),by=500),lty=3,col="gray")
 	}
 
 	#speed
@@ -313,13 +313,21 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
 			propulsiveEnds=length(concentric)
 		}
 
+		#mean speed propulsive in concentric
+		myMeanSpeed = mean(speed$y[concentric[1]:length(concentric)])
+		myMeanSpeedRight = length(concentric)
+		
 		if(eccon != "c") {
-			propulsiveEnds = propulsiveEnds + length(eccentric)
+			propulsiveEnds = propulsiveEnds + concentric[1]
+			myMeanSpeedRight = length(eccentric) + length(concentric)
 		}
-		#mean speed propulsive in concentric
-		meanSpeedPropulsive = mean(speed$y[concentric[1]:propulsiveEnds])
-		arrows(x0=min(concentric),y0=meanSpeedPropulsive,x1=propulsiveEnds,y1=meanSpeedPropulsive,col=cols[1],code=3)
-		text(x=mean(concentric[1]:propulsiveEnds), y=meanSpeedPropulsive, labels=paste("mean speed P:",round(meanSpeedPropulsive,3)), adj=c(0.5,0),cex=.8,col=cols[1])
+
+		if(analysisOptions == "p") {
+			myMeanSpeed = mean(speed$y[concentric[1]:propulsiveEnds])
+			myMeanSpeedRight = propulsiveEnds
+		}
+		arrows(x0=min(concentric),y0=myMeanSpeed,x1=myMeanSpeedRight,y1=myMeanSpeed,col=cols[1],code=3)
+		mtext(paste("mean speed:",round(myMeanSpeed,3)),side=2,at=myMeanSpeed,line=-1.8,col=cols[1],cex=.8,padj=0)
 
 		ylim=c(-max(abs(range(accel$y))),max(abs(range(accel$y))))	 #put 0 in the middle
 		#if(knRanges[1] != "undefined")
@@ -399,7 +407,7 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
 			ylim = knRanges$power
 		par(new=T);
 		if(highlight==FALSE)
-			plot(startX:length(power),power[startX:length(power)],type="l",xlim=c(1,length(a)),ylim=ylim,xlab="",ylab="",col=cols[3],lty=lty[3],lwd=1,axes=F)
+			plot(startX:length(power),power[startX:length(power)],type="l",xlim=c(1,length(a)),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(a)),ylim=ylim,xlab="",ylab="",col="darkred",lty=2,lwd=3,axes=F)
 		if(axesAndTitle) 
@@ -410,8 +418,8 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
 	peakPowerT=which(power == max(power))
 	if(draw & !superpose) {
 		abline(v=peakPowerT, col=cols[3])
-		#points(peakPowerT, max(power),col=cols[3])
-		text(x=peakPowerT,y=max(power),labels=round(max(power),3), adj=c(0.5,0),cex=.8,col=cols[3])
+		points(peakPowerT, max(power),col=cols[3])
+		mtext(text=paste("peak power:",round(max(power),3)),side=3,at=peakPowerT,cex=.8,col=cols[3])
 		mtext(text=peakPowerT,side=1,at=peakPowerT,cex=.8,col=cols[3])
 	}
 	#average power
@@ -420,21 +428,25 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
 	if(eccon != "c") 
 		meanPowerE = mean(abs(power[eccentric]))
 	meanPowerC = mean(abs(power[concentric]))
-	if(draw & !superpose) {
+	if(draw & !superpose & analysisOptions != "p") {
 		if(eccon != "c") {
 			arrows(x0=1,y0=meanPowerE,x1=max(eccentric),y1=meanPowerE,col=cols[3],code=3)
-			text(x=mean(eccentric), y=meanPowerE, labels=paste("mean power C:",round(meanPowerE,3)), adj=c(0.5,0),cex=.8,col=cols[3])
+			#text(x=min(eccentric), y=meanPowerE, labels=expression(bar(x)), adj=c(1,0),cex=.8,col=cols[3])
+			text(x=mean(eccentric), y=meanPowerE, labels=paste("mean power:",round(meanPowerE,3)), adj=c(0.5,0),cex=.8,col=cols[3])
+			#mtext(paste("mean power:",round(meanPowerE,3)),side=4,at=meanPowerE,line=-2,col=cols[3],cex=.8)
 		}
 		arrows(x0=min(concentric),y0=meanPowerC,x1=max(concentric),y1=meanPowerC,col=cols[3],code=3)
-		text(x=mean(concentric), y=meanPowerC, labels=paste("mean power C:",round(meanPowerC,3)), adj=c(0.5,0),cex=.8,col=cols[3])
+		#text(x=min(concentric), y=meanPowerC, labels=expression(bar(x)), adj=c(1,0),cex=.8,col=cols[3])
+		text(x=mean(concentric), y=meanPowerC, labels=paste("mean power:",round(meanPowerC,3)), adj=c(0.5,0),cex=.8,col=cols[3])
+		#mtext(paste("mean power:",round(meanPowerC,3)),side=4,at=meanPowerC,line=-2,col=cols[3],cex=.8)
 	}
 		
 	#propulsive phase ends when accel is -9.8
-	if(draw) {
+	if(draw & analysisOptions == "p") {
 		#mean power propulsive in concentric
 		meanPowerPropulsive = mean(power[concentric[1]:propulsiveEnds])
 		arrows(x0=min(concentric),y0=meanPowerPropulsive,x1=propulsiveEnds,y1=meanPowerPropulsive,col=cols[3],code=3)
-		text(x=mean(concentric[1]:propulsiveEnds), y=meanPowerPropulsive, labels=paste("mean power P:",round(meanPowerPropulsive,3)), adj=c(0.5,0),cex=.8,col=cols[3])
+		mtext(paste("mean power:",round(meanPowerPropulsive,3)),side=4,at=meanPowerPropulsive,line=-2,col=cols[3],cex=.8)
 	}
 
 	#legend, axes and title
@@ -443,7 +455,7 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
 			legendPos = "bottom"
 			par(xpd=T)
 			legend(legendPos, xjust=1, legend=c("Distance","","Speed","Accel.","Force","Power"), lty=c(1,0,1,1,1,1), 
-					lwd=1, col=c("black","black",cols[1],"magenta",cols[2],cols[3]), cex=1, bg="white", ncol=6, inset=-.2)
+					lwd=c(1,1,1,1,1,2), col=c("black","black",cols[1],"magenta",cols[2],cols[3]), cex=1, bg="white", ncol=6, inset=-.2)
 			par(xpd=F)
 			#mtext(text="[ESC: Quit; mouse left: Zoom in; mouse right: Zoom out]",side=3)
 		}
@@ -585,11 +597,14 @@ if(length(args) < 3) {
 	mass=as.numeric(args[7])
 	eccon=args[8]
 	analysis=args[9]	#in cross comes as "cross.Force.Speed.mean"
-	smoothingOne=args[10]
-	jump=args[11]
-	width=as.numeric(args[12])
-	height=as.numeric(args[13])
-
+	analysisOptions=args[10]	#p: propulsive
+	smoothingOne=args[11]
+	jump=args[12]
+	width=as.numeric(args[13])
+	height=as.numeric(args[14])
+
+print("++++++++++++++++++++++++++++++");
+print(paste("width",width));
 	png(outputGraph, width=width, height=height)
 	
 
diff --git a/src/encoder.cs b/src/encoder.cs
index ece053d..dd9d9e9 100644
--- a/src/encoder.cs
+++ b/src/encoder.cs
@@ -33,6 +33,7 @@ public class EncoderParams
 	private int exercisePercentBodyWeight; //was private bool isJump; (if it's 0 is like "jump")
 	private string eccon;
 	private string analysis;
+	private string analysisOptions;		//p: propulsive
 	private string smooth; //to pass always as "." to R
 	private int curve;
 	private int width;
@@ -52,6 +53,7 @@ public class EncoderParams
 	{
 	}
 
+	//to encoder capture (pyserial_pyper.py)
 	public EncoderParams(int time, int minHeight, int exercisePercentBodyWeight, string mass, string smooth, string eccon,
 			double heightHigherCondition, double heightLowerCondition, 
 			double meanSpeedHigherCondition, double meanSpeedLowerCondition, 
@@ -90,14 +92,16 @@ public class EncoderParams
 			" " + peakPowerHigherCondition.ToString() + 	" " + peakPowerLowerCondition.ToString();
 	}
 	
+	//to graph.R	
 	public EncoderParams(int minHeight, int exercisePercentBodyWeight, string mass, string eccon, 
-			string analysis, string smooth, int curve, int width, int height)
+			string analysis, string analysisOptions, string smooth, int curve, int width, int height)
 	{
 		this.minHeight = minHeight;
 		this.exercisePercentBodyWeight = exercisePercentBodyWeight;
 		this.mass = mass;
 		this.eccon = eccon;
 		this.analysis = analysis;
+		this.analysisOptions = analysisOptions;
 		this.smooth = smooth;
 		this.curve = curve;
 		this.width = width;
@@ -106,8 +110,8 @@ public class EncoderParams
 	
 	public string ToString2 () 
 	{
-		return minHeight + " " + exercisePercentBodyWeight + " " + mass + " " + eccon + " " + analysis + " " + 
-			smooth + " " + curve + " " + width + " " + height;
+		return minHeight + " " + exercisePercentBodyWeight + " " + mass + " " + eccon + " " + 
+			analysis + " " + analysisOptions + " " + smooth + " " + curve + " " + width + " " + height;
 	}
 	
 	public string Analysis {
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index 20605d3..d393989 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -32,6 +32,8 @@ public partial class ChronoJumpWindow
 {
 	[Widget] Gtk.SpinButton spin_encoder_extra_weight;
 	[Widget] Gtk.SpinButton spin_encoder_smooth;
+	
+	[Widget] Gtk.CheckButton checkbutton_encoder_propulsive;
 
 	[Widget] Gtk.Button button_encoder_capture;
 	[Widget] Gtk.Button button_encoder_bells;
@@ -285,6 +287,10 @@ public partial class ChronoJumpWindow
 	//I suppose reading gtk is ok, changing will be the problem
 	private void encoderCreateCurvesGraphR() 
 	{
+		string analysisOptions = "-";
+		if(checkbutton_encoder_propulsive.Active)
+			analysisOptions = "p";
+
 		EncoderParams ep = new EncoderParams(
 				(int) spin_encoder_capture_min_height.Value, 
 				Convert.ToInt32(
@@ -293,6 +299,7 @@ public partial class ChronoJumpWindow
 				findMass(true),
 				findEccon(true),					//force ecS (ecc-conc separated)
 				"curves",
+				analysisOptions,
 				Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: '.'
 			       	0, 			//curve is not used here
 				image_encoder_width, image_encoder_height); 
@@ -694,6 +701,10 @@ public partial class ChronoJumpWindow
 		EncoderParams ep = new EncoderParams();
 		string dataFileName = "";
 		
+		string analysisOptions = "-";
+		if(checkbutton_encoder_propulsive.Active)
+			analysisOptions = "p";
+
 		//use this send because we change it to send it to R
 		//but we don't want to change encoderAnalysis because we want to know again if == "cross" 
 		string sendAnalysis = encoderAnalysis;
@@ -727,6 +738,7 @@ public partial class ChronoJumpWindow
 					"-1",			//mass
 					myEccon,	//this decides if analysis will be together or separated
 					sendAnalysis,
+					analysisOptions,
 					"-1",
 					myCurveNum,
 					image_encoder_width, 
@@ -765,6 +777,7 @@ public partial class ChronoJumpWindow
 					findMass(true),
 					findEccon(false),		//do not force ecS (ecc-conc separated)
 					sendAnalysis,
+					analysisOptions,
 					Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: '.'
 					Convert.ToInt32(UtilGtk.ComboGetActive(combo_encoder_analyze_curve_num_combo)),
 					image_encoder_width,



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