[chronojump] Encoder: lots of fixes on graphs



commit a06136df8dc63295e99bd146bbac2b79302a0b2f
Author: Xavier de Blas <xaviblas gmail com>
Date:   Sat Jun 2 19:42:35 2012 +0200

    Encoder: lots of fixes on graphs

 encoder/graph.R        |  127 +++++++++++++++++++++++++++++++++++-------------
 glade/chronojump.glade |    2 +-
 src/constants.cs       |    2 +-
 src/gui/encoder.cs     |   66 ++++++++++++++-----------
 4 files changed, 132 insertions(+), 65 deletions(-)
---
diff --git a/encoder/graph.R b/encoder/graph.R
index 25dde84..0e047ce 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -375,13 +375,23 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
 	}
 }
 
-paintPowerPeakPowerBars <- function(paf) {
+paintPowerPeakPowerBars <- function(paf, myEccons) {
 	pafColors=c("tomato1","tomato4",topo.colors(10)[3])
 	myNums = 1:length(paf[,1])
 	if(eccon=="ecS") {
-		myEc=c("c","e")
-		myNums = paste(trunc((myNums+1)/2),myEc[(myNums%%2)+1],sep="")
+		if(! singleFile) {
+			j=0
+			for(i in 1:length(myEccons)) {
+				myNums[i] = paste(i-j,myEccons[i],sep="")
+				if(myEccons[i] == "e")
+					j=j+1
+			}
+		} else {
+			myEc=c("c","e")
+			myNums = paste(trunc((myNums+1)/2),myEc[(myNums%%2)+1],sep="")
+		}
 	}
+
 	bp <- barplot(rbind(paf[,3],paf[,4]),beside=T,col=pafColors[1:2],width=c(1.4,.6),
 			names.arg=myNums,xlim=c(1,n*3+.5),xlab="",ylab="Power (W)")
 	par(new=T, xpd=T)
@@ -405,13 +415,16 @@ find.yrange <- function(singleFile, rawdata, curves) {
 	} else {
 		n=length(curves[,1])
 		y.max = 0
+		y.min = 10000
 		for(i in 1:n) { 
 			y.current = cumsum(rawdata[curves[i,1]:curves[i,2]])
-			if(max(y.current) > y.max){
+			if(max(y.current) > y.max)
 				y.max = max(y.current)
-			}
+			if(min(y.current) < y.min)
+				y.min = min(y.current)
+			
 		}
-		return (c(0,y.max))
+		return (c(y.min,y.max))
 	}
 }
 
@@ -474,10 +487,10 @@ if(length(args) < 3) {
 
 	singleFile = TRUE
 	if(nchar(file) >= 40) {
-		#file="/tmp...../chronojump-encoder-graph-input-multi.txt"
+		#file="/tmp...../chronojump-encoder-graph-input-multi.csv"
 		#substr(file, nchar(file)-39, nchar(file))
-		#[1] "chronojump-encoder-graph-input-multi.txt"
-		if(substr(file, nchar(file)-39, nchar(file)) == "chronojump-encoder-graph-input-multi.txt") {
+		#[1] "chronojump-encoder-graph-input-multi.csv"
+		if(substr(file, nchar(file)-39, nchar(file)) == "chronojump-encoder-graph-input-multi.csv") {
 			singleFile = FALSE
 		}
 	}
@@ -487,29 +500,60 @@ if(length(args) < 3) {
 		#this are separated movements
 		#maybe all are concentric (there's no returning to 0 phase)
 
-		#this version of curves will have added specific data cols: exerciseName, mass, smoothingOne, dateTime
-		inputMultiData=read.csv(file=file,sep=",")
+		#this version of curves has added specific data cols:
+		#exerciseName, mass, smoothingOne, dateTime, myEccon
+
+		inputMultiData=read.csv(file=file,sep=",",stringsAsFactors=F)
+
 		rawdata = NULL
 		count = 1
 		start = NULL; end = NULL; startH = NULL
-		exerciseName = NULL; mass = NULL; smooth = NULL; dateTime = NULL
+		exerciseName = NULL; mass = NULL; smooth = NULL; dateTime = NULL; myEccon = NULL
+		newLines=0; 
 		for(i in 1:length(inputMultiData[,1])) { 
-			print (i)
-			dataTemp=scan(file=as.vector(inputMultiData$fullURL[i]),sep=",")
-			print(length(dataTemp))
-			rawdata = c(rawdata, dataTemp)
-			start[i] = count
-			end[i] = length(dataTemp) + count -1
-			startH[i] = 0
-			exerciseName[i] = as.vector(inputMultiData$exerciseName[i])
-			mass[i] = inputMultiData$mass[i]
-			smooth[i] = inputMultiData$smoothingOne[i]
-			dateTime[i] = inputMultiData$dateTime[i]
-			count = count + length(dataTemp)
+			dataTempFile=scan(file=as.vector(inputMultiData$fullURL[i]),sep=",")
+			dataTempPhase=dataTempFile
+			processTimes = 1
+			changePos = 0
+			#if this curve is ecc-con and we want separated, divide the curve in two
+			if(as.vector(inputMultiData$eccon[i]) != "c" & eccon =="ecS") {
+				changePos = mean(which(cumsum(dataTempFile) == min(cumsum(dataTempFile))))
+				processTimes = 2
+			}
+			for(j in 1:processTimes) {
+				if(processTimes == 2) {
+					if(j == 1) {
+						dataTempPhase=dataTempFile[1:changePos]
+					} else {
+						dataTempPhase=dataTempFile[(changePos+1):length(dataTempFile)]
+						newLines=newLines+1
+					}
+				}
+				rawdata = c(rawdata, dataTempPhase)
+				start[i+newLines] = count
+				end[i+newLines] = length(dataTempPhase) + count -1
+				startH[i+newLines] = 0
+				exerciseName[i+newLines] = as.vector(inputMultiData$exerciseName[i])
+				mass[i+newLines] = inputMultiData$mass[i]
+				smooth[i+newLines] = inputMultiData$smoothingOne[i]
+				dateTime[i+newLines] = as.vector(inputMultiData$dateTime[i])
+
+				#myEccon[i+newLines] = as.vector(inputMultiData$eccon[i])
+				if(processTimes == 2 & j == 1) 
+					myEccon[i+newLines] = "e"
+				else {
+					if(inputMultiData$eccon[i] == "c")
+						myEccon[i+newLines] = "c"
+					else
+						myEccon[i+newLines] = "ec"
+				}
+
+				count = count + length(dataTempPhase)
+			}
 		}		
-		curves = data.frame(start,end,startH,exerciseName,mass,smooth,dateTime,stringsAsFactors=F)
+		curves = data.frame(start,end,startH,exerciseName,mass,smooth,dateTime,myEccon,stringsAsFactors=F)
 		rownames(curves)=1:length(rownames(curves))
-		#print(curves)
+		print(curves)
 		n=length(curves[,1])
 		quitIfNoData(n, curves, outputData1)
 	} else {
@@ -555,30 +599,43 @@ if(length(args) < 3) {
 		#print(curves)
 	}
 
-	if(analysis=="single") 
-		if(jump>0) 
-			paint(rawdata, eccon, curves[jump,1],curves[jump,2],"undefined","undefined",FALSE,FALSE,
-					1,curves[jump,3],smoothingOne,mass,
-					paste(analysis, " ", eccon, " ", titleType, " ", jump," (smoothing: ",smoothingOne,")",sep=""),
+	if(analysis=="single") {
+		if(jump>0) {
+			myMass = mass
+			mySmoothingOne = smoothingOne
+			myEccon = eccon
+			if(! singleFile) {
+				myMass = curves[jump,5]
+				mySmoothingOne = curves[jump,6]
+				myEccon = curves[jump,8]
+			}
+			paint(rawdata, myEccon, curves[jump,1],curves[jump,2],"undefined","undefined",FALSE,FALSE,
+					1,curves[jump,3],mySmoothingOne,myMass,
+					paste(analysis, " ", myEccon, " ", titleType, " ", jump," (smoothing: ",mySmoothingOne,")",sep=""),
 					TRUE,FALSE,TRUE,TRUE)
+		}
+	}
+
 	if(analysis=="side") {
 		#comparar 6 salts, falta que xlim i ylim sigui el mateix
 		par(mfrow=find.mfrow(n))
 
 		#a=cumsum(rawdata)
 		#yrange=c(min(a),max(a))
-		yrange=find.yrange(singleFile, rawdata,curves)
+		yrange=find.yrange(singleFile, rawdata, curves)
 
 		knRanges=kinematicRanges(singleFile,rawdata,curves,mass,smoothingOne,g)
 
 		for(i in 1:n) {
 			myMass = mass
 			mySmoothingOne = smoothingOne
+			myEccon = eccon
 			if(! singleFile) {
 				myMass = curves[i,5]
 				mySmoothingOne = curves[i,6]
+				myEccon = curves[i,8]
 			}
-			paint(rawdata, eccon, curves[i,1],curves[i,2],yrange,knRanges,FALSE,FALSE,
+			paint(rawdata, myEccon, curves[i,1],curves[i,2],yrange,knRanges,FALSE,FALSE,
 				1,curves[i,3],mySmoothingOne,myMass,paste(titleType,i),TRUE,FALSE,TRUE,FALSE)
 		}
 		par(mfrow=c(1,1))
@@ -614,14 +671,16 @@ if(length(args) < 3) {
 		for(i in 1:n) { 
 			myMass = mass
 			mySmoothingOne = smoothingOne
+			myEccon = eccon
 			if(! singleFile) {
 				myMass = curves[i,5]
 				mySmoothingOne = curves[i,6]
+				myEccon = curves[i,8]
 			}
 			paf=rbind(paf,(powerBars(kinematicsF(rawdata[curves[i,1]:curves[i,2]], myMass, mySmoothingOne, g))))
 		}
 		if(analysis=="powerBars") {
-			paintPowerPeakPowerBars(paf)
+			paintPowerPeakPowerBars(paf, curves[,8])	#myEccon
 		} 
 		if(analysis=="curves") {
 			paf=cbind(curves[,1],curves[,2]-curves[,1],rawdata.cumsum[curves[,2]]-curves[,3],paf)
diff --git a/glade/chronojump.glade b/glade/chronojump.glade
index a0537ae..782ddae 100644
--- a/glade/chronojump.glade
+++ b/glade/chronojump.glade
@@ -24890,7 +24890,7 @@ Evaluator can use real name or nickname.</property>
                                                         <child>
                                                           <widget class="GtkHBox" id="hbox_encoder_analyze_eccon">
                                                             <property name="visible">True</property>
-                                                            <property name="sensitive">False</property>
+                                                            <property name="sensitive">True</property>
                                                             <property name="spacing">8</property>
                                                             <child>
                                                             <widget class="GtkRadioButton" id="radiobutton_encoder_eccon_together">
diff --git a/src/constants.cs b/src/constants.cs
index d949b1a..1adba9c 100644
--- a/src/constants.cs
+++ b/src/constants.cs
@@ -581,6 +581,6 @@ public class Constants
 
 	//note next has 40 chars, and its used also in encoder/graph.R to detect how a file will be treated
 	//if this name changes, change it in encoder/graph.R
-	public static string EncoderGraphInputMulti = "chronojump-encoder-graph-input-multi.txt"; 
+	public static string EncoderGraphInputMulti = "chronojump-encoder-graph-input-multi.csv"; 
 
 }
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index 494a899..2ec3ccc 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -75,8 +75,6 @@ public partial class ChronoJumpWindow
 	[Widget] Gtk.Image image_encoder_analyze;
 	[Widget] Gtk.ProgressBar encoder_pulsebar_analyze;
 
-	TreeStore encoderStore;
-
 	ArrayList encoderCurves;
         Gtk.ListStore encoderListStore;
 
@@ -93,13 +91,9 @@ public partial class ChronoJumpWindow
 	
 	//TODO: auto close capturing window
 
-	//TODO: fixing powerbars problem, [false: sqlite.encoder curves don't store if it's "c" or "ec", then graph.R when doing the curves, don't do a row for the e and another for the c, because don't know in which curves have to differentiate], also don't plot names ok. This affects at multi and do it good in order to compare c and ec contractions of same person. change encoder table, adding "contraction", "exerciseID" (uniqueID of table encoderExercise), "laterality" (Right, Left, Both)
-	//
-	//
 	//TODO: Put person name in graph (at title,with small separation, or inside graph at topright) (if we click on another person on treeview person, we need to know wich person was last generated graph)
-	//TODO: if mode is ecc-con, curves used have to be eccon
 	//TODO: when change person: unsensitive: recalculate, capture graph, treeview capture, buttons caputre on bottom, analyze button
-	//TODO: when selected user curves, Single curve spinbutton have to grow. Also do it if person changes
+	//TODO: when selected user curves, Single curve spinbutton have to grow (done). Also do it if person changes (pending)
 	//TODO: laterality have to be shown on treeviews: stream and curve. also check that is correct in database
 
 	//TODO: put chronopic detection in a generic place. Done But:
@@ -126,17 +120,7 @@ public partial class ChronoJumpWindow
 		sensitiveEncoderRowButtons(false);
 		createEncoderCombos();
 		sensitiveEncoderGlobalButtons(false);
-	}
-
-	private void on_radiobutton_encoder_eccon_toggled (object obj, EventArgs args) {
-		if(Util.FindOnArray(':',1,0,UtilGtk.ComboGetActive(combo_encoder_eccon),
-					encoderEcconTranslation) == "Concentric") {
-			label_encoder_analyze_eccon.Sensitive=false;
-			hbox_encoder_analyze_eccon.Sensitive=false;
-		} else if(radiobutton_encoder_analyze_powerbars.Active) {
-			label_encoder_analyze_eccon.Sensitive=true;
-			hbox_encoder_analyze_eccon.Sensitive=true;
-		}
+		spin_encoder_analyze_curve_num.SetRange(1,1);
 	}
 
 	//TODO: garantir path windows	
@@ -511,6 +495,13 @@ public partial class ChronoJumpWindow
 		string dataFileName = "";
 
 		if(radiobutton_encoder_analyze_data_user_curves.Active) {
+			string myEccon = "ec";
+			if(! radiobutton_encoder_eccon_together.Active)
+				myEccon = "ecS";
+			int myCurveNum = -1;
+			if(encoderAnalysis == "single")
+				myCurveNum = (int) spin_encoder_analyze_curve_num.Value;
+
 			//-1 because data will be different on any curve
 			ep = new EncoderParams(
 					-1, 
@@ -518,10 +509,10 @@ public partial class ChronoJumpWindow
 						Util.FindOnArray(':', 2, 3, UtilGtk.ComboGetActive(combo_encoder_exercise), 
 						encoderExercisesTranslationAndBodyPWeight) ),
 					"-1",			//mass
-					findEccon(false),	//do not force ecS (ecc-conc separated)
+					myEccon,	//this decides if analysis will be together or separated
 					encoderAnalysis,
 					"-1",
-					-1,
+					myCurveNum,
 					image_encoder_width, 
 					image_encoder_height); 
 			
@@ -533,7 +524,7 @@ public partial class ChronoJumpWindow
 					currentPerson.UniqueID, currentSession.UniqueID, "curve");
 
 			TextWriter writer = File.CreateText(dataFileName);
-			writer.WriteLine("exerciseName,mass,smoothingOne,dateTime,fullURL");
+			writer.WriteLine("exerciseName,mass,smoothingOne,dateTime,fullURL,eccon");
 			foreach(EncoderSQL eSQL in data) {
 				double mass = Convert.ToDouble(eSQL.extraWeight); //TODO: future problem if this has '%'
 				EncoderExercise ex = (EncoderExercise) SqliteEncoder.SelectEncoderExercises(eSQL.exerciseID)[0];
@@ -541,7 +532,9 @@ public partial class ChronoJumpWindow
 
 				writer.WriteLine(ex.name + "," + mass.ToString() + "," + 
 						Util.ConvertToPoint(eSQL.smooth) + "," + eSQL.GetDate(true) + "," + 
-						eSQL.url + Path.DirectorySeparatorChar + eSQL.filename);
+						eSQL.url + Path.DirectorySeparatorChar + eSQL.filename + "," +
+						eSQL.eccon	//this is the eccon of every curve
+						);
 			}
 			writer.Flush();
 			((IDisposable)writer).Dispose();
@@ -573,10 +566,15 @@ public partial class ChronoJumpWindow
 	private void on_radiobutton_encoder_analyze_data_current_stream_toggled (object obj, EventArgs args) {
 		button_encoder_analyze.Sensitive = encoderTimeStamp != null;
 		button_encoder_analyze_data_show_user_curves.Sensitive = false;
+
+		spin_encoder_analyze_curve_num.SetRange(1, UtilGtk.CountRows(encoderListStore));
 	}
 	private void on_radiobutton_encoder_analyze_data_user_curves_toggled (object obj, EventArgs args) {
 		button_encoder_analyze.Sensitive = currentPerson != null;
 		button_encoder_analyze_data_show_user_curves.Sensitive = currentPerson != null;
+		
+		ArrayList data = SqliteEncoder.Select(false, -1, currentPerson.UniqueID, currentSession.UniqueID, "curve");
+		spin_encoder_analyze_curve_num.SetRange(1, data.Count);
 	}
 
 	//show curve_num only on simple and superpose
@@ -609,11 +607,11 @@ public partial class ChronoJumpWindow
 		spin_encoder_analyze_curve_num.Sensitive=false;
 		encoderAnalysis="powerBars";
 		//can select together or separated
-		if(Util.FindOnArray(':',1,0,UtilGtk.ComboGetActive(combo_encoder_eccon),
-					encoderEcconTranslation) != "Concentric") {
+		//if(Util.FindOnArray(':',1,0,UtilGtk.ComboGetActive(combo_encoder_eccon),
+		//			encoderEcconTranslation) != "Concentric") {
 			label_encoder_analyze_eccon.Sensitive=true;
 			hbox_encoder_analyze_eccon.Sensitive=true;
-		}
+		//}
 	}
 
 	private string findMass(bool includePerson) {
@@ -628,13 +626,14 @@ public partial class ChronoJumpWindow
 
 		return Util.ConvertToPoint(mass); //R decimal: '.'
 	}
-	
-	private string findEccon(bool ecconSeparated) {	
+
+	//TODO: check all this	
+	private string findEccon(bool forceEcconSeparated) {	
 		if(Util.FindOnArray(':',1,0,UtilGtk.ComboGetActive(combo_encoder_eccon),
 					encoderEcconTranslation) == "Concentric") 
 			return "c";
 		else {
-			if(ecconSeparated || ! radiobutton_encoder_eccon_together.Active)
+			if(forceEcconSeparated || ! radiobutton_encoder_eccon_together.Active)
 				return "ecS";
 			else 
 				return "ec";
@@ -715,7 +714,16 @@ public partial class ChronoJumpWindow
 
 	void on_combo_encoder_eccon_changed (object o, EventArgs args) 
 	{
-		//TODO
+		/*
+		if(Util.FindOnArray(':',1,0,UtilGtk.ComboGetActive(combo_encoder_eccon),
+					encoderEcconTranslation) == "Concentric") {
+			label_encoder_analyze_eccon.Sensitive=false;
+			hbox_encoder_analyze_eccon.Sensitive=false;
+		} else if(radiobutton_encoder_analyze_powerbars.Active) {
+			label_encoder_analyze_eccon.Sensitive=true;
+			hbox_encoder_analyze_eccon.Sensitive=true;
+		}
+		*/
 	}
 
 	void on_combo_encoder_laterality_changed (object o, EventArgs args) 



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