[chronojump] Encoder: curves graphs working: side, powerbars
- From: Xavier de Blas <xaviblas src gnome org>
- To: commits-list gnome org
- Cc: 
- Subject: [chronojump] Encoder: curves graphs working: side, powerbars
- Date: Thu, 31 May 2012 11:01:09 +0000 (UTC)
commit bfcbd841839d8ad88f56b2e6b2a154da30bb8b1c
Author: Xavier de Blas <xaviblas gmail com>
Date:   Thu May 31 13:00:11 2012 +0200
    Encoder: curves graphs working: side, powerbars
 encoder/graph.R        |  194 ++++++++++++++++++++++++++++++++++--------------
 glade/chronojump.glade |    3 +-
 src/constants.cs       |    4 +
 src/encoder.cs         |   12 ++-
 src/gui/chronojump.cs  |    1 +
 src/gui/encoder.cs     |   88 ++++++++++++++++++----
 src/sqlite/encoder.cs  |   10 ++-
 src/util.cs            |    4 +
 8 files changed, 237 insertions(+), 79 deletions(-)
---
diff --git a/encoder/graph.R b/encoder/graph.R
index 0b27368..7d9abb4 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -126,11 +126,10 @@ reduceCurveBySpeed <- function(eccon, row, startT, rawdata, smoothing) {
 }
 
 #go here with every single jump
-kinematicsF <- function(a, mass, g) {
+kinematicsF <- function(a, mass, smoothingOne, g) {
 	speed <- smooth.spline( 1:length(a), a, spar=smoothingOne)
 	accel <- predict( speed, deriv=1 )
 	accel$y <- accel$y * 1000 #input data is in mm, conversion to m
-
 #	force <- mass*accel$y
 #	if(isJump)
 		force <- mass*(accel$y+g)	#g:9.81 (used when movement is against gravity)
@@ -149,11 +148,17 @@ powerBars <- function(kinematics) {
 	return(data.frame(meanSpeed, maxSpeed, meanPower,peakPower,peakPowerT,pp_ppt))
 }
 
-kinematicRanges <- function(rawdata,curves,mass,g) {
+kinematicRanges <- function(singleFile,rawdata,curves,mass,smoothingOne,g) {
 	n=length(curves[,1])
 	maxSpeedy=0;maxForce=0;maxPower=0
 	for(i in 1:n) { 
-		kn=kinematicsF(rawdata[curves[i,1]:curves[i,2]],mass,g)
+		myMass = mass
+		mySmoothingOne = smoothingOne
+		if(! singleFile) {
+			myMass = curves[i,5]
+			mySmoothingOne = curves[i,6]
+		}
+		kn=kinematicsF(rawdata[curves[i,1]:curves[i,2]],myMass,mySmoothingOne,g)
 		if(max(abs(kn$speedy)) > maxSpeedy)
 			maxSpeedy = max(abs(kn$speedy))
 		if(max(abs(kn$force)) > maxForce)
@@ -391,6 +396,24 @@ find.mfrow <- function(n) {
 	else if(n<=8) return(c(2,ceiling(n/2)))
 	else return(c(3, ceiling(n/3)))
 }
+
+find.yrange <- function(singleFile, rawdata, curves) {
+	if(singleFile) {
+		a=cumsum(rawdata)
+		return (c(min(a),max(a)))
+	} else {
+		n=length(curves[,1])
+		y.max = 0
+		for(i in 1:n) { 
+			y.current = cumsum(rawdata[curves[i,1]:curves[i,2]])
+			if(max(y.current) > y.max){
+				y.max = max(y.current)
+			}
+		}
+		return (c(0,y.max))
+	}
+}
+
 #concentric, eccentric-concentric, repetitions of eccentric-concentric
 #currently only used "c" and "ec". no need of ec-rep because c and ec are repetitive
 #"ecS" is like ec but eccentric and concentric phases are separated, used in findCurves, this is good for treeview to know power... on the 2 phases
@@ -425,18 +448,7 @@ if(length(args) < 3) {
 	height=as.numeric(args[13])
 
 	png(outputGraph, width=width, height=height)
-
-	rawdata=scan(file=file,sep=",")
-
-	if(length(rawdata)==0) {
-		plot(0,0,type="n",axes=F,xlab="",ylab="")
-		text(x=0,y=0,"Encoder is not connected.",cex=1.5)
-		dev.off()
-		write("", outputData1)
-		quit()
-	}
-
-	rawdata.cumsum=cumsum(rawdata)
+	
 
 	titleType = "execution"
 	if(isJump)
@@ -447,44 +459,97 @@ if(length(args) < 3) {
 		curvesPlot = TRUE
 		par(mar=c(2,2.5,1,1))
 	}
-	curves=findCurves(rawdata, eccon, minHeight, curvesPlot)
-	print(curves)
 
-	n=length(curves[,1])
-
-	#if not found curves with this data, plot a "sorry" message and exit
-	if(n == 1 & curves[1,1] == 0 & curves[1,2] == 0) {
-		plot(0,0,type="n",axes=F,xlab="",ylab="")
-		text(x=0,y=0,"Sorry, no curves matched your criteria.",cex=1.5)
-		dev.off()
-		write("", outputData1)
-		quit()
+	singleFile = TRUE
+	if(nchar(file) >= 40) {
+		#file="/tmp...../chronojump-encoder-graph-input-multi.txt"
+		#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") {
+			singleFile = FALSE
+		}
 	}
+	
+	if(! singleFile) {
+		#this produces a rawdata, but note that a cumsum(rawdata) cannot be done because:
+		#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: type, mass, smoothingOne, dateTime
+		inputMultiData=read.csv(file=file,sep=",")
+		rawdata = NULL
+		count = 1
+		start = NULL; end = NULL; startH = NULL
+		type = NULL; mass = NULL; smooth = NULL; dateTime = NULL
+		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
+			type[i] = as.vector(inputMultiData$type[i])
+			mass[i] = inputMultiData$mass[i]
+			smooth[i] = inputMultiData$smoothingOne[i]
+			dateTime[i] = inputMultiData$dateTime[i]
+			count = count + length(dataTemp)
+		}		
+		curves = data.frame(start,end,startH,type,mass,smooth,dateTime,stringsAsFactors=F)
+		rownames(curves)=1:length(rownames(curves))
+		#print(curves)
+		n=length(curves[,1])
+	} else {
+		rawdata=scan(file=file,sep=",")
+
+		if(length(rawdata)==0) {
+			plot(0,0,type="n",axes=F,xlab="",ylab="")
+			text(x=0,y=0,"Encoder is not connected.",cex=1.5)
+			dev.off()
+			write("", outputData1)
+			quit()
+		}
 
-	for(i in 1:n) { 
-		curves[i,1]=reduceCurveBySpeed(eccon, i, curves[i,1],rawdata[curves[i,1]:curves[i,2]], smoothingOne)
-	}
-	if(curvesPlot) {
-		#/10 mm -> cm
-		for(i in 1:length(curves[,1])) { 
-			myLabel = i
-			myY = min(rawdata.cumsum)/10
-			adjVert = 0
-			if(eccon=="ecS") {
-				myEc=c("c","e")
-				myLabel = paste(trunc((i+1)/2),myEc[(i%%2)+1],sep="")
-				myY = rawdata.cumsum[curves[i,1]]/10
-				if(i%%2 == 1) {
-					adjVert = 1
+		rawdata.cumsum=cumsum(rawdata)
+	
+		curves=findCurves(rawdata, eccon, minHeight, curvesPlot)
+		#print(curves)
+		n=length(curves[,1])
+
+		#if not found curves with this data, plot a "sorry" message and exit
+		if(n == 1 & curves[1,1] == 0 & curves[1,2] == 0) {
+			plot(0,0,type="n",axes=F,xlab="",ylab="")
+			text(x=0,y=0,"Sorry, no curves matched your criteria.",cex=1.5)
+			dev.off()
+			write("", outputData1)
+			quit()
+		}
+
+		for(i in 1:n) { 
+			curves[i,1]=reduceCurveBySpeed(eccon, i, curves[i,1],rawdata[curves[i,1]:curves[i,2]], smoothingOne)
+		}
+		if(curvesPlot) {
+			#/10 mm -> cm
+			for(i in 1:length(curves[,1])) { 
+				myLabel = i
+				myY = min(rawdata.cumsum)/10
+				adjVert = 0
+				if(eccon=="ecS") {
+					myEc=c("c","e")
+					myLabel = paste(trunc((i+1)/2),myEc[(i%%2)+1],sep="")
+					myY = rawdata.cumsum[curves[i,1]]/10
+					if(i%%2 == 1) {
+						adjVert = 1
+					}
 				}
+				text(x=(curves[i,1]+curves[i,2])/2,y=myY,labels=myLabel, adj=c(0.5,adjVert),cex=1,col="blue")
+				arrows(x0=curves[i,1],y0=myY,x1=curves[i,2],y1=myY,
+						col="blue",code=3,length=0.1)
 			}
-			text(x=(curves[i,1]+curves[i,2])/2,y=myY,labels=myLabel, adj=c(0.5,adjVert),cex=1,col="blue")
-			arrows(x0=curves[i,1],y0=myY,x1=curves[i,2],y1=myY,
-					col="blue",code=3,length=0.1)
 		}
-	}
 
-	print(curves)
+		#print(curves)
+	}
 
 	if(analysis=="single") 
 		if(jump>0) 
@@ -495,12 +560,22 @@ if(length(args) < 3) {
 	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))
-		knRanges=kinematicRanges(rawdata,curves,mass,g)
+
+		#a=cumsum(rawdata)
+		#yrange=c(min(a),max(a))
+		yrange=find.yrange(singleFile, rawdata,curves)
+
+		knRanges=kinematicRanges(singleFile,rawdata,curves,mass,smoothingOne,g)
+
 		for(i in 1:n) {
+			myMass = mass
+			mySmoothingOne = smoothingOne
+			if(! singleFile) {
+				myMass = curves[i,5]
+				mySmoothingOne = curves[i,6]
+			}
 			paint(rawdata, eccon, curves[i,1],curves[i,2],yrange,knRanges,FALSE,FALSE,
-				1,curves[i,3],smoothingOne,mass,paste(titleType,i),TRUE,FALSE,TRUE,FALSE)
+				1,curves[i,3],mySmoothingOne,myMass,paste(titleType,i),TRUE,FALSE,TRUE,FALSE)
 		}
 		par(mfrow=c(1,1))
 	}
@@ -510,9 +585,12 @@ if(length(args) < 3) {
 		#arreglar que els eixos de l'esq han de seguir un ylim,pero els de la dreta un altre, basat en el que es vol observar
 		#fer que es pugui enviar colors que es vol per cada curva, o linetypes
 		wide=max(curves$end-curves$start)
-		a=cumsum(rawdata)
-		yrange=c(min(a),max(a))
-		knRanges=kinematicRanges(rawdata,curves,mass,g)
+		
+		#a=cumsum(rawdata)
+		#yrange=c(min(a),max(a))
+		yrange=find.yrange(singleFile, rawdata,curves)
+
+		knRanges=kinematicRanges(singleFile,rawdata,curves,mass,smoothingOne,g)
 		for(i in 1:n) {
 			#in superpose all jumps end at max height
 			#start can change, some are longer than other
@@ -530,7 +608,13 @@ if(length(args) < 3) {
 	if(analysis=="powerBars" || analysis=="curves") {
 		paf = data.frame()
 		for(i in 1:n) { 
-			paf=rbind(paf,(powerBars(kinematicsF(rawdata[curves[i,1]:curves[i,2]], mass, g))))
+			myMass = mass
+			mySmoothingOne = smoothingOne
+			if(! singleFile) {
+				myMass = curves[i,5]
+				mySmoothingOne = curves[i,6]
+			}
+			paf=rbind(paf,(powerBars(kinematicsF(rawdata[curves[i,1]:curves[i,2]], myMass, mySmoothingOne, g))))
 		}
 		if(analysis=="powerBars") {
 			paintPowerPeakPowerBars(paf)
diff --git a/glade/chronojump.glade b/glade/chronojump.glade
index c9a038c..017f848 100644
--- a/glade/chronojump.glade
+++ b/glade/chronojump.glade
@@ -24705,6 +24705,7 @@ Evaluator can use real name or nickname.</property>
                                                         <property name="receives_default">False</property>
                                                         <property name="active">True</property>
                                                         <property name="draw_indicator">True</property>
+                                                        <signal name="toggled" handler="on_radiobutton_encoder_analyze_data_current_stream_toggled"/>
                                                       </widget>
                                                       <packing>
                                                         <property name="expand">False</property>
@@ -24725,6 +24726,7 @@ Evaluator can use real name or nickname.</property>
                                                             <property name="active">True</property>
                                                             <property name="draw_indicator">True</property>
                                                             <property name="group">radiobutton_encoder_analyze_data_current_stream</property>
+                                                            <signal name="toggled" handler="on_radiobutton_encoder_analyze_data_user_curves_toggled"/>
                                                           </widget>
                                                           <packing>
                                                             <property name="position">0</property>
@@ -24733,7 +24735,6 @@ Evaluator can use real name or nickname.</property>
                                                         <child>
                                                           <widget class="GtkButton" id="button_encoder_analyze_data_select_user_curves">
                                                             <property name="label" translatable="yes">Select</property>
-                                                            <property name="visible">True</property>
                                                             <property name="can_focus">True</property>
                                                             <property name="receives_default">True</property>
                                                           </widget>
diff --git a/src/constants.cs b/src/constants.cs
index 434e9ae..c3631c0 100644
--- a/src/constants.cs
+++ b/src/constants.cs
@@ -578,4 +578,8 @@ public class Constants
 	public static string EncoderCurvesTemp = "chronojump-last-encoder-curves.txt";
 	public static string EncoderGraphTemp = "chronojump-last-encoder-graph.png";
 
+	//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"; 
+
 }
diff --git a/src/encoder.cs b/src/encoder.cs
index 45c3ce5..134c033 100644
--- a/src/encoder.cs
+++ b/src/encoder.cs
@@ -46,7 +46,11 @@ public class EncoderParams
 	private int powerLowerCondition;
 	private int peakPowerHigherCondition;
 	private int peakPowerLowerCondition;
-	
+
+	public EncoderParams()
+	{
+	}
+
 	public EncoderParams(int time, int minHeight, bool isJump, string mass, string smooth, string eccon,
 			double heightHigherCondition, double heightLowerCondition, 
 			double meanSpeedHigherCondition, double meanSpeedLowerCondition, 
@@ -105,11 +109,10 @@ public class EncoderParams
 			smooth + " " + curve + " " + width + " " + height;
 	}
 	
-	public string Analysis
-	{
+	public string Analysis {
 		get { return analysis; }
 	}
-
+	
 
 	~EncoderParams() {}
 }
@@ -241,4 +244,5 @@ public class EncoderSQL
 		str[5] = description;
 		return str;
 	}
+
 }
diff --git a/src/gui/chronojump.cs b/src/gui/chronojump.cs
index f82e1fe..e95ead6 100644
--- a/src/gui/chronojump.cs
+++ b/src/gui/chronojump.cs
@@ -5171,6 +5171,7 @@ Console.WriteLine("X");
 		hbox_execute_test.Sensitive = true;
 
 		label_encoder_person_weight.Text = currentPersonSession.Weight.ToString();
+		button_encoder_analyze.Sensitive = radiobutton_encoder_analyze_data_user_curves.Active;
 	}
 	
 	private void sensitiveGuiYesEvent () {
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index 4b136d1..e160c34 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -53,6 +53,8 @@ public partial class ChronoJumpWindow
 	[Widget] Gtk.Button button_encoder_save_stream;
 	
 	[Widget] Gtk.Button button_encoder_analyze;
+	[Widget] Gtk.RadioButton radiobutton_encoder_analyze_data_current_stream;
+	[Widget] Gtk.RadioButton radiobutton_encoder_analyze_data_user_curves;
 	[Widget] Gtk.RadioButton radiobutton_encoder_analyze_powerbars;
 	[Widget] Gtk.RadioButton radiobutton_encoder_analyze_single;
 	[Widget] Gtk.RadioButton radiobutton_encoder_analyze_side;
@@ -83,12 +85,12 @@ public partial class ChronoJumpWindow
 	private string encoderStreamUniqueID;
 	enum encoderModes { CAPTURE, ANALYZE }
 	
-	//TODO: store encoder data: auto save, and show on a treeview.
 	//TODO: auto close capturing window
-	//TODO: fix date of creation-saving stream and curve
 
 	//TODO: put chronopic detection in a generic place. Done But:
 	//TODO: solve the problem of connecting two different chronopics
+	//
+	//TODO: analyze-user curves: create file with n lines: titlecurve,otherparams,...,filecurve and pass this file to graph.R. graph.R will know that this file is not a rawdata file because will be called chronojump-encoder-graph-input-multi.txt
 
 	
 	private void encoderInitializeVariables() {
@@ -219,6 +221,7 @@ public partial class ChronoJumpWindow
 
 
 	//this is called by non gtk thread. Don't do gtk stuff here
+	//I suppose reading gtk is ok, changing will be the problem
 	private void encoderCreateCurvesGraphR() 
 	{
 		EncoderParams ep = new EncoderParams(
@@ -246,7 +249,7 @@ public partial class ChronoJumpWindow
 		
 	void on_button_encoder_load_stream_clicked (object o, EventArgs args) 
 	{
-		ArrayList data = SqliteEncoder.SelectStreams(false, -1, currentPerson.UniqueID, currentSession.UniqueID);
+		ArrayList data = SqliteEncoder.Select(false, -1, currentPerson.UniqueID, currentSession.UniqueID, "stream");
 
 		ArrayList dataPrint = new ArrayList();
 		foreach(EncoderSQL es in data) {
@@ -276,8 +279,8 @@ public partial class ChronoJumpWindow
 		genericWin.Button_accept.Clicked -= new EventHandler(on_encoder_load_stream_accepted);
 		int uniqueID = genericWin.TreeviewSelectedRowID();
 
-		ArrayList data = SqliteEncoder.SelectStreams(false, uniqueID, 
-				currentPerson.UniqueID, currentSession.UniqueID);
+		ArrayList data = SqliteEncoder.Select(false, uniqueID, 
+				currentPerson.UniqueID, currentSession.UniqueID, "stream");
 
 		foreach(EncoderSQL es in data) {	//it will run only one time
 			Util.CopyEncoderDataToTemp(es.url, es.name);
@@ -433,24 +436,74 @@ public partial class ChronoJumpWindow
 	}
 	
 	//this is called by non gtk thread. Don't do gtk stuff here
+	//I suppose reading gtk is ok, changing will be the problem
 	private void analyze () 
 	{
-		EncoderParams ep = new EncoderParams(
-				(int) spin_encoder_capture_min_height.Value, 
-				!radiobutton_encoder_capture_bar.Active,
-				findMass(true),
-				findEccon(false),		//do not force ecS (ecc-conc separated)
-				encoderAnalysis,
-				Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: '.'
-				(int) spin_encoder_analyze_curve_num.Value, 
-				image_encoder_width, image_encoder_height); 
+		EncoderParams ep = new EncoderParams();
+		string dataFileName = "";
+
+		if(radiobutton_encoder_analyze_data_user_curves.Active) {
+			//-1 because data will be different on any curve
+			ep = new EncoderParams(
+					-1, 
+					!radiobutton_encoder_capture_bar.Active,
+					"-1",			//mass
+					findEccon(false),	//do not force ecS (ecc-conc separated)
+					encoderAnalysis,
+					"-1",
+					-1,
+					image_encoder_width, 
+					image_encoder_height); 
+			
+			dataFileName = Util.GetEncoderGraphInputMulti();
 
-		EncoderStruct es = new EncoderStruct(
-				Util.GetEncoderDataTempFileName(), 
+			//create dataFileName
+			double bodyMass = Convert.ToDouble(label_encoder_person_weight.Text);
+			ArrayList data = SqliteEncoder.Select(false, -1, 
+					currentPerson.UniqueID, currentSession.UniqueID, "curve");
+		
+				
+			TextWriter writer = File.CreateText(dataFileName);
+			writer.WriteLine("type,mass,smoothingOne,dateTime,fullURL");
+			foreach(EncoderSQL eSQL in data) {
+				double mass = Convert.ToDouble(eSQL.extraWeight);	//TODO: check this
+				if(eSQL.type == "curveJUMP")
+					mass += bodyMass;
+
+				writer.WriteLine(eSQL.type + "," + mass.ToString() + "," + 
+						Util.ConvertToPoint(eSQL.smooth) + "," + eSQL.GetDate(true) + "," + 
+						eSQL.url + Path.DirectorySeparatorChar + eSQL.name);
+			}
+			writer.Flush();
+			((IDisposable)writer).Dispose();
+		} else {
+			ep = new EncoderParams(
+					(int) spin_encoder_capture_min_height.Value, 
+					!radiobutton_encoder_capture_bar.Active,
+					findMass(true),
+					findEccon(false),		//do not force ecS (ecc-conc separated)
+					encoderAnalysis,
+					Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: '.'
+					(int) spin_encoder_analyze_curve_num.Value, 
+					image_encoder_width,
+					image_encoder_height); 
+			
+			dataFileName = Util.GetEncoderDataTempFileName();
+		}
+
+		EncoderStruct encoderStruct = new EncoderStruct(
+				dataFileName, 
 				Util.GetEncoderGraphTempFileName(),
 				"NULL", "NULL", ep);		//no data ouptut
 
-		Util.RunPythonEncoder(Constants.EncoderScriptGraphCall, es, false);
+		Util.RunPythonEncoder(Constants.EncoderScriptGraphCall, encoderStruct, false);
+	}
+	
+	private void on_radiobutton_encoder_analyze_data_current_stream_toggled (object obj, EventArgs args) {
+		button_encoder_analyze.Sensitive = encoderTimeStamp != null;
+	}
+	private void on_radiobutton_encoder_analyze_data_user_curves_toggled (object obj, EventArgs args) {
+		button_encoder_analyze.Sensitive = currentPerson != null;
 	}
 
 	//show curve_num only on simple and superpose
@@ -900,6 +953,7 @@ public partial class ChronoJumpWindow
 			image_encoder_height = UtilGtk.WidgetHeight(viewport_image_encoder_analyze)-3;
 
 			encoder_pulsebar_analyze.Text = Catalog.GetString("Please, wait.");
+
 			encoderThread = new Thread(new ThreadStart(analyze));
 			GLib.Idle.Add (new GLib.IdleHandler (pulseGTKEncoderAnalyze));
 		}
diff --git a/src/sqlite/encoder.cs b/src/sqlite/encoder.cs
index 022ab39..1b8494c 100644
--- a/src/sqlite/encoder.cs
+++ b/src/sqlite/encoder.cs
@@ -119,7 +119,8 @@ class SqliteEncoder : Sqlite
 	}
 	
 	
-	public static ArrayList SelectStreams (bool dbconOpened, int uniqueID, int personID, int sessionID)
+	public static ArrayList Select (bool dbconOpened, 
+			int uniqueID, int personID, int sessionID, string typeStartsWith)
 	{
 		if(! dbconOpened)
 			dbcon.Open();
@@ -128,10 +129,15 @@ class SqliteEncoder : Sqlite
 		if(uniqueID != -1)
 			uniqueIDStr = " AND uniqueID = " + uniqueID;
 
+		string typeStr = "";
+		if(typeStartsWith == "stream")
+			typeStr = " AND SUBSTR(type,1,6)='stream'";
+		else if(typeStartsWith == "curve")
+			typeStr = " AND SUBSTR(type,1,5)='curve'";
 
 		dbcmd.CommandText = "SELECT * FROM " + Constants.EncoderTable + 
 			" WHERE personID = " + personID + " AND sessionID = " + sessionID +
-			" AND SUBSTR(type,1,6)='stream'" + uniqueIDStr;
+			typeStr + uniqueIDStr;
 		
 		SqliteDataReader reader;
 		reader = dbcmd.ExecuteReader();
diff --git a/src/util.cs b/src/util.cs
index c444f58..f3c8a71 100644
--- a/src/util.cs
+++ b/src/util.cs
@@ -853,6 +853,10 @@ public class Util
 	public static string GetEncoderGraphTempFileName() {
 		return Path.Combine(Path.GetTempPath(), Constants.EncoderGraphTemp);
 	}
+	public static string GetEncoderGraphInputMulti() {
+		return Path.Combine(Path.GetTempPath(), Constants.EncoderGraphInputMulti);
+	}
+
 
 //	public static void MoveTempToEncoderData(int sessionID, int uniqueID) {
 	public static string CopyTempToEncoderData(int sessionID, int uniqueID, string personName, string timeStamp) 
[
Date Prev][
Date Next]   [
Thread Prev][
Thread Next]   
[
Thread Index]
[
Date Index]
[
Author Index]