[chronojump] Big in EncoderSQL, graph.R pass encoderConf params
- From: Xavier de Blas <xaviblas src gnome org>
- To: commits-list gnome org
- Cc:
- Subject: [chronojump] Big in EncoderSQL, graph.R pass encoderConf params
- Date: Tue, 25 Feb 2014 15:18:07 +0000 (UTC)
commit d6d275d3c63c83cbbc5ccdc476f664514bea5f75
Author: Xavier de Blas <xaviblas gmail com>
Date: Tue Feb 25 16:17:00 2014 +0100
Big in EncoderSQL, graph.R pass encoderConf params
diagrams/classes/encoder_classes.dia | Bin 2059 -> 2556 bytes
encoder/graph.R | 244 ++++++++++++++++++++++++----------
src/encoder.cs | 68 +++++-----
src/gui/encoder.cs | 22 +--
src/gui/encoderConfiguration.cs | 26 +++-
src/sqlite/encoder.cs | 74 ++++-------
src/sqlite/main.cs | 47 +++++++-
src/sqlite/oldConvert.cs | 166 +++++++++++++++++++++++
8 files changed, 475 insertions(+), 172 deletions(-)
---
diff --git a/diagrams/classes/encoder_classes.dia b/diagrams/classes/encoder_classes.dia
index a66aaa4..e6636b7 100644
Binary files a/diagrams/classes/encoder_classes.dia and b/diagrams/classes/encoder_classes.dia differ
diff --git a/encoder/graph.R b/encoder/graph.R
index ababc06..f941b74 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -104,7 +104,7 @@ print(options)
OutputData2 = options[4] #currently used to display processing feedback
SpecialData = options[5]
OperatingSystem=options[27]
-EncoderConfiguration = ""
+EncoderConfigurationName = ""
write("(1/5) Starting R", OutputData2)
@@ -571,7 +571,8 @@ return (propulsiveEnd)
#eccon="c" one time each curve
#eccon="ec" one time each curve
#eccon="ecS" means ecSeparated. two times each curve: one for "e", one for "c"
-kinematicsF <- function(displacement, massBody, massExtra, exercisePercentBodyWeight,
+kinematicsF <- function(displacement, massBody, massExtra, exercisePercentBodyWeight,
+
encoderConfigurationName,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown,
smoothingOneEC, smoothingOneC, g, eccon, isPropulsive) {
smoothing = 0
@@ -617,27 +618,18 @@ kinematicsF <- function(displacement, massBody, massExtra, exercisePercentBodyWe
} else if(eccon=="e") {
#not eccon="e" because not propulsive calculations on eccentric
} else { #ecS
-print("WARNING ECS\n\n\n\n\n")
+ print("WARNING ECS\n\n\n\n\n")
}
}
- mass = getMassByEncoderConfiguration(massBody, massExtra, exercisePercentBodyWeight, gearedDown,
anglePush, angleWeight)
- print(c("MASS: ", mass, massBody, massExtra, exercisePercentBodyWeight))
+ dynamics = getDynamics(encoderConfigurationName,
+ speed$y, accel$y, massBody, massExtra, exercisePercentBodyWeight, gearedDown,
anglePush, angleWeight,
+ displacement, diameter, diameterExt, inertiaMomentum, smoothing)
+ mass = dynamics$mass
+ force = dynamics$force
+ power = dynamics$power
-# force <- mass*accel$y
-# if(isJump)
- force <- mass*(accel$y+g) #g:9.81 (used when movement is against gravity)
-
- power <- force*speed$y
-
- #print("propulsiveEnd")
- #print(propulsiveEnd)
-
print("at kinematicsF")
- #print(c("mass",mass))
- #print(c("speed$y",speed$y))
- #print(c("accel$y",accel$y))
- #print(c("power",power))
if( isPropulsive && ( eccon== "c" || eccon == "ec" ) )
return(list(speedy=speed$y[1:propulsiveEnd], accely=accel$y[1:propulsiveEnd],
@@ -686,6 +678,7 @@ pafGenerate <- function(eccon, kinematics, massBody, massExtra) {
kinematicRanges <- function(singleFile, displacement, curves,
massBody, massExtra, exercisePercentBodyWeight,
+
encoderConfiguration,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown,
smoothingsEC, smoothingOneC, g, eccon, isPropulsive) {
n=length(curves[,1])
maxSpeedy=0; maxAccely=0; maxForce=0; maxPower=0
@@ -693,16 +686,34 @@ kinematicRanges <- function(singleFile, displacement, curves,
for(i in 1:n) {
myMassBody = massBody
myMassExtra = massExtra
- #mySmoothingOne = smoothingOne
myExPercentBodyWeight = exercisePercentBodyWeight
+
+ #encoderConfiguration
+ myEncoderConfigurationName = EncoderConfigurationName
+ myDiameter = diameter
+ myDiameterExt = diameterExt
+ myAnglePush = anglePush
+ myAngleWeight = angleWeight
+ myInertiaMomentum = inertiaMomentum
+ myGearedDown = gearedDown
if(! singleFile) {
myMassBody = curves[i,5]
myMassExtra = curves[i,6]
myEccon = curves[i,8]
myExPercentBodyWeight = curves[i,10]
+
+ #encoderConfiguration
+ myEncoderConfigurationName = curves[i,11]
+ myDiameter = curves[i,12]
+ myDiameterExt = curves[i,13]
+ myAnglePush = curves[i,14]
+ myAngleWeight = curves[i,15]
+ myInertiaMomentum = curves[i,16]
+ myGearedDown = curves[i,17]
}
kn=kinematicsF(displacement[curves[i,1]:curves[i,2]],
myMassBody, myMassExtra, myExPercentBodyWeight,
+
myEncoderConfigurationName,myDiameter,myDiameterExt,myAnglePush,myAngleWeight,myInertiaMomentum,myGearedDown,
smoothingsEC[i], smoothingOneC, g, myEccon, isPropulsive)
if(max(abs(kn$speedy)) > maxSpeedy)
@@ -724,6 +735,7 @@ kinematicRanges <- function(singleFile, displacement, curves,
paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose, highlight,
startX, startH, smoothingOneEC, smoothingOneC, massBody, massExtra,
+ encoderConfigurationName,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown,
#encoderConfiguration stuff
title, subtitle, draw, showLabels, marShrink, showAxes, legend,
Analysis, isPropulsive, inertialType, exercisePercentBodyWeight,
showSpeed, showAccel, showForce, showPower
@@ -998,12 +1010,17 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
#mtext(text=paste("max accel:",round(max(accel$y),3)),side=3,at=which(accel$y ==
max(accel$y)),cex=.8,col=cols[1],line=2)
}
- mass = getMassByEncoderConfiguration(massBody, massExtra, exercisePercentBodyWeight, gearedDown,
anglePush, angleWeight)
+ dynamics = getDynamics(encoderConfigurationName,
+ speed$y, accel$y, massBody, massExtra, exercisePercentBodyWeight, gearedDown,
anglePush, angleWeight,
+ displacement, diameter, diameterExt, inertiaMomentum, smoothing)
+ mass = dynamics$mass
+ force = dynamics$force
+ power = dynamics$power
#print(c(knRanges$accely, max(accel$y), min(accel$y)))
# force <- mass*accel$y
# if(isJump)
- force <- mass*(accel$y+g) #g:9.81 (used when movement is against gravity)
+# force <- mass*(accel$y+g) #g:9.81 (used when movement is against gravity)
#print("MAXFORCE!!!!!")
#print(max(force))
@@ -1060,21 +1077,21 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
- power = NULL
+ #power = NULL
- if(inertialType == "li" || inertialType == "ri") {
+ #if(inertialType == "li" || inertialType == "ri") {
#Explanation rotatory encoder on inertial machine
#speed$y comes in mm/ms, is the same than m/s
#speedw in meters:
- speedw <- speed$y / diameter #m radius
+ # speedw <- speed$y / diameter #m radius
#accel$y comes in meters
#accelw in meters:
- accelw <- accel$y / diameter
+ # accelw <- accel$y / diameter
#power = power to the inertial machine (rotatory disc) + power to the displaced body mass
(lineal)
#power = ( inertia momentum * angular acceleration * angular velocity ) + mass(includes extra
weight if any) * accel$y * speed$y
#abs(speedw) because disc is rolling in the same direction and we don't have to make power to
change it
- power <- inertiaMomentum * accelw * speedw + mass * (accel$y +g) * speed$y
+ # power <- inertiaMomentum * accelw * speedw + mass * (accel$y +g) * speed$y
#print("at Paint")
#print(c("mass",mass))
@@ -1083,9 +1100,9 @@ paint <- function(displacement, eccon, xmin, xmax, yrange, knRanges, superpose,
#print(c("accel$y",accel$y))
#print(c("accelw",accelw))
#print(c("power",power))
- }
- else #(inertialType == "")
- power <- force*speed$y
+ #}
+ #else #(inertialType == "")
+ # power <- force*speed$y
@@ -1679,7 +1696,7 @@ find.yrange <- function(singleFile, displacement, curves) {
#in signals and curves, need to do conversions (invert, inertiaMomentum, diameter)
#we use 'data' variable because can be position or displacement
-getDisplacement <- function(data, diameter, diameterExt) {
+getDisplacement <- function(encoderConfigurationName, data, diameter, diameterExt) {
#no change
#WEIGHTEDMOVPULLEYLINEARONPERSON1, WEIGHTEDMOVPULLEYLINEARONPERSON1INV,
#WEIGHTEDMOVPULLEYLINEARONPERSON2, WEIGHTEDMOVPULLEYLINEARONPERSON2INV,
@@ -1687,15 +1704,15 @@ getDisplacement <- function(data, diameter, diameterExt) {
#ROTARYFRICTIONSIDE
#WEIGHTEDMOVPULLEYROTARYFRICTION
- if(EncoderConfiguration == "LINEARINVERTED") {
+ if(encoderConfigurationName == "LINEARINVERTED") {
data = -data
- } else if(EncoderConfiguration == "WEIGHTEDMOVPULLEYONLINEARENCODER") {
+ } else if(encoderConfigurationName == "WEIGHTEDMOVPULLEYONLINEARENCODER") {
#default is: gearedDowniplication = 2. Future maybe this will be a parameter
data = data *2
- } else if(EncoderConfiguration == "ROTARYFRICTIONAXIS") {
+ } else if(encoderConfigurationName == "ROTARYFRICTIONAXIS") {
data = data * diameter / diameterExt
- } else if(EncoderConfiguration == "ROTARYAXIS" ||
- EncoderConfiguration == "WEIGHTEDMOVPULLEYROTARYAXIS") {
+ } else if(encoderConfigurationName == "ROTARYAXIS" ||
+ encoderConfigurationName == "WEIGHTEDMOVPULLEYROTARYAXIS") {
ticksRotaryEncoder = 200 #our rotary axis encoder send 200 ticks by turn
#diameter m -> mm
data = ( data / ticksRotaryEncoder ) * 2 * pi * ( diameter * 1000 / 2 )
@@ -1704,12 +1721,12 @@ getDisplacement <- function(data, diameter, diameterExt) {
}
getSpeed <- function(displacement, smoothing) {
- #no change depending on EncoderConfiguration
+ #no change affected by encoderConfiguration
return (smooth.spline( 1:length(displacement), displacement, spar=smoothing))
}
getAcceleration <- function(speed) {
- #no change depending on EncoderConfiguration
+ #no change affected by encoderConfiguration
return (predict( speed, deriv=1 ))
}
@@ -1728,23 +1745,23 @@ getMassBodyByExercise <- function(mass.body, exercisePercentBodyWeight) {
return (mass.body * exercisePercentBodyWeight / 100.0)
}
-getMassByEncoderConfiguration <- function(mass.body, mass.extra, exercisePercentBodyWeight, gearedDown,
anglePush, angleWeight)
+getMassByEncoderConfiguration <- function(encoderConfigurationName, mass.body, mass.extra,
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight)
{
mass.body = getMassBodyByExercise(mass.body,exercisePercentBodyWeight)
if(
- EncoderConfiguration == "WEIGHTEDMOVPULLEYLINEARONPERSON1" ||
- EncoderConfiguration == "WEIGHTEDMOVPULLEYLINEARONPERSON1INV" ||
- EncoderConfiguration == "WEIGHTEDMOVPULLEYLINEARONPERSON2" ||
- EncoderConfiguration == "WEIGHTEDMOVPULLEYLINEARONPERSON2INV" ||
- EncoderConfiguration == "WEIGHTEDMOVPULLEYROTARYFRICTION" ||
- EncoderConfiguration == "WEIGHTEDMOVPULLEYROTARYAXIS" )
+ encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON1" ||
+ encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON1INV" ||
+ encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON2" ||
+ encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON2INV" ||
+ encoderConfigurationName == "WEIGHTEDMOVPULLEYROTARYFRICTION" ||
+ encoderConfigurationName == "WEIGHTEDMOVPULLEYROTARYAXIS" )
{
mass.extra = getMass(mass.extra, gearedDown, anglePush)
- } else if(EncoderConfiguration == "LINEARONPLANE") {
+ } else if(encoderConfigurationName == "LINEARONPLANE") {
mass.body = getMass(mass.body, gearedDown, anglePush)
mass.extra = getMass(mass.extra, gearedDown, anglePush)
- } else if(EncoderConfiguration == "LINEARONPLANEWEIGHTDIFFANGLE") {
+ } else if(encoderConfigurationName == "LINEARONPLANEWEIGHTDIFFANGLE") {
mass.body = getMass(mass.body, gearedDown, anglePush)
mass.extra = getMass(mass.extra, gearedDown, angleWeight)
}
@@ -1753,10 +1770,25 @@ getMassByEncoderConfiguration <- function(mass.body, mass.extra, exercisePercent
return (mass)
}
-#mass extra can be connected to body or connected to a pulley depending on EncoderConfiguration
-getDynamics <- function(speed, accel, mass.body, mass.extra, exercisePercentBodyWeight, gearedDown,
anglePush, angleWeight)
+getDynamics <- function(encoderConfigurationName,
+ speed, accel, massBody, massExtra, exercisePercentBodyWeight, gearedDown, anglePush,
angleWeight,
+ displacement, diameter, diameterExt, inertiaMomentum, smoothing)
{
- mass = getMassByEncoderConfiguration (mass.body, mass.extra, exercisePercentBodyWeight, gearedDown,
anglePush, angleWeight)
+ if(encoderConfigurationName == "LINEARINERTIAL" ||
+ encoderConfigurationName == "ROTARYFRICTIONSIDEINERTIAL" ||
+ encoderConfigurationName == "ROTARYFRICTIONAXISINERTIAL" ||
+ encoderConfigurationName == "ROTARYAXISINERTIAL")
+ {
+ return (getDynamicsInertial(encoderConfigurationName, displacement, diameter, diameterExt,
inertiaMomentum, smoothing))
+ } else {
+ return (getDynamicsNotInertial (encoderConfigurationName, speed, accel, massBody, massExtra,
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight))
+ }
+}
+
+#mass extra can be connected to body or connected to a pulley depending on encoderConfiguration
+getDynamicsNotInertial <- function(encoderConfigurationName, speed, accel, mass.body, mass.extra,
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight)
+{
+ mass = getMassByEncoderConfiguration (encoderConfigurationName, mass.body, mass.extra,
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight)
force <- mass*(accel+g) #g:9.81 (used when movement is against gravity)
@@ -1783,9 +1815,9 @@ getDynamics <- function(speed, accel, mass.body, mass.extra, exercisePercentBody
# ROTARYFRICTIONAXISINERTIAL Rotary friction encoder connected to inertial machine on the axis
# ROTARYAXISINERTIAL Rotary axis encoder connected to inertial machine on the axis
-getDynamicsInertial <- function(displacement, d, D, mass, inertiaMomentum, smoothing)
+getDynamicsInertial <- function(encoderConfigurationName, displacement, d, D, mass, inertiaMomentum,
smoothing)
{
- if(EncoderConfiguration == "ROTARYFRICTIONSIDEINERTIAL")
+ if(encoderConfigurationName == "ROTARYFRICTIONSIDEINERTIAL")
{
angle = displacement * 2 / D #displacement of the disc
displacement = displacement * d / D #displacement of the axis
@@ -1793,9 +1825,9 @@ getDynamicsInertial <- function(displacement, d, D, mass, inertiaMomentum, smoot
position = abs(cumsum(displacement)) / 1000 #mm -> m
- if(EncoderConfiguration == "LINEARINERTIAL" ||
- EncoderConfiguration == "ROTARYFRICTIONSIDEINERTIAL" ||
- EncoderConfiguration == "ROTARYFRICTIONAXISINERTIAL") {
+ if(encoderConfigurationName == "LINEARINERTIAL" ||
+ encoderConfigurationName == "ROTARYFRICTIONSIDEINERTIAL" ||
+ encoderConfigurationName == "ROTARYFRICTIONAXISINERTIAL") {
speed = getSpeed(displacement, smoothing)
accel = getAcceleration(speed)
@@ -1807,7 +1839,7 @@ getDynamicsInertial <- function(displacement, d, D, mass, inertiaMomentum, smoot
angleSpeed = speed * 2 / d
angleAccel = accel * 2 / d
} else {
- #(EncoderConfiguration == "ROTARYAXISINERTIAL")
+ #(encoderConfigurationName == "ROTARYAXISINERTIAL")
ticksRotaryEncoder = 200 #our rotary axis encoder send 200 ticks by turn
angle = abs(cumsum(displacement)) * 2 * pi / ticksRotaryEncoder
@@ -1825,7 +1857,7 @@ getDynamicsInertial <- function(displacement, d, D, mass, inertiaMomentum, smoot
force = abs(inertiaMomentum * angleAccel) * (2 / d) + mass(accel + g)
power = abs((inertiaMomentum * angleAccel) * angleSpeed) + mass(accel + g) * speed
- return(list(displacement=displacement, position=position, mass=mass, force=force, power=power))
+ return(list(displacement=displacement, mass=mass, force=force, power=power))
}
#-------------- end of EncoderConfiguration conversions -------------------------
@@ -1879,12 +1911,13 @@ doProcess <- function(options) {
AnalysisOptions=options[13]
- EncoderConfiguration= options[14] #just the name of the EncoderConfiguration
+ #TODO: all this have to be applicable also on ! singleFILE
+ EncoderConfigurationName= options[14] #just the name of the EncoderConfiguration
diameter= as.numeric(options[15]) #in meters, eg: 0.0175
diameterExt= as.numeric(options[16]) #in meters, eg: 0.0175
anglePush = options[17]
angleWeight = options[18]
- inertiaMomentum=as.numeric(options[19])/10000 #comes in Kg*cm^2 eg: 100; convert it to Kg*m^2 eg:
0.010
+ inertiaMomentum=as.numeric(options[19])/10000.0 #comes in Kg*cm^2 eg: 100; convert it to Kg*m^2 eg:
0.010
gearedDown = options[20]
SmoothingOneC=options[21]
@@ -1977,9 +2010,13 @@ doProcess <- function(options) {
count = 1
start = NULL; end = NULL; startH = NULL
status = NULL; id = NULL; exerciseName = NULL; massBody = NULL; massExtra = NULL
- smooth = NULL ; dateTime = NULL; myEccon = NULL; curvesHeight = NULL
+ dateTime = NULL; myEccon = NULL; curvesHeight = NULL
seriesName = NULL; percentBodyWeight = NULL;
+ #encoderConfiguration
+ econfName = NULL; econfd = NULL; econfD = NULL; econfAnglePush = NULL; econfAngleWeight =
NULL;
+ econfInertia = NULL; econfGearedDown = NULL;
+
newLines=0;
countLines=1; #useful to know the correct ids of active curves
for(i in 1:length(inputMultiData[,1])) {
@@ -1997,7 +2034,7 @@ doProcess <- function(options) {
#this removes all NAs on a curve
dataTempFile = dataTempFile[!is.na(dataTempFile)]
- dataTempFile = getDisplacement(dataTempFile, diameter, diameterExt)
+ dataTempFile = getDisplacement(inputMultiData$econfName[i], dataTempFile, diameter,
diameterExt)
dataTempPhase=dataTempFile
processTimes = 1
@@ -2033,6 +2070,15 @@ doProcess <- function(options) {
dateTime[(i+newLines)] = as.vector(inputMultiData$dateTime[i])
percentBodyWeight[(i+newLines)] =
as.vector(inputMultiData$percentBodyWeight[i])
+
+ #also encoder configuration stuff
+ econfName[(i+newLines)] = inputMultiData$econfName[i]
+ econfd[(i+newLines)] = inputMultiData$econfd[i]
+ econfD[(i+newLines)] = inputMultiData$econfD[i]
+ econfAnglePush[(i+newLines)] = inputMultiData$econfAnglePush[i]
+ econfAngleWeight[(i+newLines)] = inputMultiData$econfAngleWeight[i]
+ econfInertia[(i+newLines)] = inputMultiData$econfInertia[i]
+ econfGearedDown[(i+newLines)] = inputMultiData$econfGearedDown[i]
curvesHeight[(i+newLines)] = sum(dataTempPhase)
@@ -2061,7 +2107,7 @@ doProcess <- function(options) {
#position=cumsum(displacement)
- #curves =
data.frame(id,start,end,startH,exerciseName,mass,smooth,dateTime,myEccon,stringsAsFactors=F,row.names=1)
+ #curves =
data.frame(id,start,end,startH,exerciseName,mass,dateTime,myEccon,stringsAsFactors=F,row.names=1)
#this is a problem when there's only one row as seen by the R code of data.frame. ?data.frame:
#"If row names are supplied of length one and the data frame has a
#single row, the ‘row.names’ is taken to specify the row names and
@@ -2071,10 +2117,12 @@ doProcess <- function(options) {
if(length(id)==1) {
curves = data.frame(start,end,startH,exerciseName,massBody,massExtra,
dateTime,myEccon,seriesName,percentBodyWeight,
+
econfName,econfd,econfD,econfAnglePush,econfAngleWeight,econfInertia,econfGearedDown,
stringsAsFactors=F,row.names=id)
} else {
curves = data.frame(id,start,end,startH,exerciseName,massBody,massExtra,
dateTime,myEccon,seriesName,percentBodyWeight,
+
econfName,econfd,econfD,econfAnglePush,econfAngleWeight,econfInertia,econfGearedDown,
stringsAsFactors=F,row.names=1)
}
@@ -2093,7 +2141,7 @@ doProcess <- function(options) {
#this removes all NAs
displacement = displacement[!is.na(displacement)]
- displacement = getDisplacement(displacement, diameter, diameterExt)
+ displacement = getDisplacement(EncoderConfigurationName, displacement, diameter, diameterExt)
if(length(displacement)==0) {
plot(0,0,type="n",axes=F,xlab="",ylab="")
@@ -2103,8 +2151,8 @@ doProcess <- function(options) {
quit()
}
- if(inertialType == "ri")
- displacement = fixRawdataInertial(displacement)
+ #if(inertialType == "ri")
+ # displacement = fixRawdataInertial(displacement)
curves=findCurves(displacement, Eccon, MinHeight, curvesPlot, Title)
@@ -2178,17 +2226,33 @@ doProcess <- function(options) {
if(Jump>0) {
myMassBody = MassBody
myMassExtra = MassExtra
- #mySmoothingOne = SmoothingOne
myEccon = Eccon
myStart = curves[Jump,1]
myEnd = curves[Jump,2]
myExPercentBodyWeight = ExercisePercentBodyWeight
+
+ #encoderConfiguration
+ myEncoderConfigurationName = EncoderConfigurationName
+ myDiameter = diameter
+ myDiameterExt = diameterExt
+ myAnglePush = anglePush
+ myAngleWeight = angleWeight
+ myInertiaMomentum = inertiaMomentum
+ myGearedDown = gearedDown
if(! singleFile) {
myMassBody = curves[Jump,5]
myMassExtra = curves[Jump,6]
- #mySmoothingOne = curves[Jump,7]
myEccon = curves[Jump,8]
myExPercentBodyWeight = curves[Jump,10]
+
+ #encoderConfiguration
+ myEncoderConfigurationName = curves[Jump,11]
+ myDiameter = curves[Jump,12]
+ myDiameterExt = curves[Jump,13]
+ myAnglePush = curves[Jump,14]
+ myAngleWeight = curves[Jump,15]
+ myInertiaMomentum = curves[Jump,16]
+ myGearedDown = curves[Jump,17]
}
myCurveStr = paste("curve=", Jump, ", ", myMassExtra, "Kg", sep="")
@@ -2201,6 +2265,7 @@ doProcess <- function(options) {
paint(displacement, myEccon, myStart, myEnd,"undefined","undefined",FALSE,FALSE,
1,curves[Jump,3],SmoothingsEC[as.numeric(Jump)],SmoothingOneC,myMassBody,myMassExtra,
+
myEncoderConfigurationName,myDiameter,myDiameterExt,myAnglePush,myAngleWeight,myInertiaMomentum,myGearedDown,
paste(Title, " ", Analysis, " ", myEccon, " ", myCurveStr, sep=""),
"", #subtitle
TRUE, #draw
@@ -2226,21 +2291,38 @@ doProcess <- function(options) {
#if !singleFile kinematicRanges takes the 'curves' values
knRanges=kinematicRanges(singleFile, displacement, curves,
MassBody, MassExtra, ExercisePercentBodyWeight,
+
EncoderConfigurationName,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown,
SmoothingsEC, SmoothingOneC,
g, Eccon, isPropulsive)
for(i in 1:n) {
myMassBody = MassBody
myMassExtra = MassExtra
- #mySmoothingOne = SmoothingOne
myEccon = Eccon
myExPercentBodyWeight = ExercisePercentBodyWeight
+
+ #encoderConfiguration
+ myEncoderConfigurationName = EncoderConfigurationName
+ myDiameter = diameter
+ myDiameterExt = diameterExt
+ myAnglePush = anglePush
+ myAngleWeight = angleWeight
+ myInertiaMomentum = inertiaMomentum
+ myGearedDown = gearedDown
if(! singleFile) {
myMassBody = curves[i,5]
myMassExtra = curves[i,6]
- #mySmoothingOne = curves[i,7]
myEccon = curves[i,8]
myExPercentBodyWeight = curves[i,10]
+
+ #encoderConfiguration
+ myEncoderConfigurationName = curves[i,11]
+ myDiameter = curves[i,12]
+ myDiameterExt = curves[i,13]
+ myAnglePush = curves[i,14]
+ myAngleWeight = curves[i,15]
+ myInertiaMomentum = curves[i,16]
+ myGearedDown = curves[i,17]
}
myTitle = ""
@@ -2250,7 +2332,9 @@ doProcess <- function(options) {
mySubtitle = paste("curve=", rownames(curves)[i], ", ", myMassExtra, "Kg", sep="")
paint(displacement, myEccon, curves[i,1],curves[i,2],yrange,knRanges,FALSE,FALSE,
-
1,curves[i,3],SmoothingsEC[i],SmoothingOneC,myMassBody,myMassExtra,myTitle,mySubtitle,
+ 1,curves[i,3],SmoothingsEC[i],SmoothingOneC,myMassBody,myMassExtra,
+
myEncoderConfigurationName,myDiameter,myDiameterExt,myAnglePush,myAngleWeight,myInertiaMomentum,myGearedDown,
+ myTitle,mySubtitle,
TRUE, #draw
FALSE, #showLabels
TRUE, #marShrink
@@ -2319,16 +2403,32 @@ doProcess <- function(options) {
for(i in 1:n) {
myMassBody = MassBody
myMassExtra = MassExtra
- #mySmoothingOne = SmoothingOne
myEccon = Eccon
myExPercentBodyWeight = ExercisePercentBodyWeight
+
+ #encoderConfiguration
+ myEncoderConfigurationName = EncoderConfigurationName
+ myDiameter = diameter
+ myDiameterExt = diameterExt
+ myAnglePush = anglePush
+ myAngleWeight = angleWeight
+ myInertiaMomentum = inertiaMomentum
+ myGearedDown = gearedDown
if(! singleFile) {
myMassBody = curves[i,5]
myMassExtra = curves[i,6]
- #mySmoothingOne = curves[i,7]
myEccon = curves[i,8]
myExPercentBodyWeight = curves[i,10]
+ #encoderConfiguration
+ myEncoderConfigurationName = curves[i,11]
+ myDiameter = curves[i,12]
+ myDiameterExt = curves[i,13]
+ myAnglePush = curves[i,14]
+ myAngleWeight = curves[i,15]
+ myInertiaMomentum = curves[i,16]
+ myGearedDown = curves[i,17]
+
#only use concentric data
if( (Analysis == "1RMBadillo2010" || Analysis == "1RMAnyExercise") & myEccon
== "e") {
discardedCurves = c(i,discardedCurves)
@@ -2368,6 +2468,7 @@ doProcess <- function(options) {
myEccon,
kinematicsF(displacement[curves[i,1]:curves[i,2]],
myMassBody, myMassExtra,
myExPercentBodyWeight,
+
myEncoderConfigurationName,myDiameter,myDiameterExt,myAnglePush,myAngleWeight,myInertiaMomentum,myGearedDown,
SmoothingsEC[i],SmoothingOneC,
g, myEcconKn, isPropulsive),
myMassBody, myMassExtra
@@ -2500,6 +2601,7 @@ doProcess <- function(options) {
for(i in 1:curvesNum) {
kn = kinematicsF (displacement[curves[i,1]:curves[i,2]],
MassBody, MassExtra, ExercisePercentBodyWeight,
+
EncoderConfigurationName,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown,
SmoothingsEC[i], SmoothingOneC, g, Eccon, isPropulsive)
#fill with NAs in order to have the same length
diff --git a/src/encoder.cs b/src/encoder.cs
index bb319ec..0f4b61b 100644
--- a/src/encoder.cs
+++ b/src/encoder.cs
@@ -284,16 +284,15 @@ public class EncoderSQL
public string url;
public int time;
public int minHeight;
- public double smooth; //unused on curves, since 1.3.7 it's in database
public string description;
public string status; //active or inactive curves
public string videoURL; //URL of video of signals
//encoderConfiguration conversions
//in signals and curves, need to do conversions (invert, inertiaMomentum, diameter)
- public string encoderConfigurationName;
- public int inertiaMomentum; //kg*cm^2
- public double diameter;
+ public EncoderConfiguration encoderConfiguration;
+// public int inertiaMomentum; //kg*cm^2
+// public double diameter;
public string future1;
public string future2;
@@ -309,9 +308,9 @@ public class EncoderSQL
public EncoderSQL (string uniqueID, int personID, int sessionID, int exerciseID,
string eccon, string laterality, string extraWeight, string signalOrCurve,
- string filename, string url, int time, int minHeight, double smooth,
+ string filename, string url, int time, int minHeight,
string description, string status, string videoURL,
- string encoderConfigurationName, int inertiaMomentum, double diameter,
+ EncoderConfiguration encoderConfiguration,
string future1, string future2, string future3,
string exerciseName
)
@@ -328,13 +327,10 @@ public class EncoderSQL
this.url = url;
this.time = time;
this.minHeight = minHeight;
- this.smooth = smooth;
this.description = description;
this.status = status;
this.videoURL = videoURL;
- this.encoderConfigurationName = encoderConfigurationName;
- this.inertiaMomentum = inertiaMomentum;
- this.diameter = diameter;
+ this.encoderConfiguration = encoderConfiguration;
this.future1 = future1;
this.future2 = future2;
this.future3 = future3;
@@ -379,6 +375,7 @@ public class EncoderSQL
if(video)
all++;
+
string [] str = new String [all];
int i=0;
str[i++] = uniqueID;
@@ -390,9 +387,7 @@ public class EncoderSQL
str[i++] = exerciseName;
str[i++] = extraWeight;
- EncoderConfiguration econf = new EncoderConfiguration( (Constants.EncoderConfigurationNames)
- Enum.Parse(typeof(Constants.EncoderConfigurationNames),
encoderConfigurationName) );
- str[i++] = econf.code.ToString();
+ str[i++] = encoderConfiguration.code.ToString();
str[i++] = ecconLong;
str[i++] = GetDate(true);
@@ -645,24 +640,6 @@ public class EncoderConfiguration {
gearedDown = 1;
}
- //decimalPointForR: ensure decimal is point in order to work in R
- public string ToString(string sep, bool decimalPointForR) {
- string str_d = "";
- string str_D = "";
- if(decimalPointForR) {
- str_d = Util.ConvertToPoint(d);
- str_D = Util.ConvertToPoint(D);
- } else {
- str_d = d.ToString();
- str_D = D.ToString();
- }
-
- return
- name + sep + str_d + sep + str_D + sep +
- anglePush.ToString() + sep + angleWeight.ToString() + sep +
- inertia.ToString() + sep + gearedDown.ToString();
- }
-
/* note: if this changes, change also in:
* UtilEncoder.EncoderConfigurationList(enum encoderType)
*/
@@ -847,4 +824,33 @@ public class EncoderConfiguration {
gearedDown = 2;
}
}
+
+ public void FromSQL (string [] strFull) {
+ //adds other params
+ this.d = Convert.ToDouble(Util.ChangeDecimalSeparator(strFull[1]));
+ this.D = Convert.ToDouble(Util.ChangeDecimalSeparator(strFull[2]));
+ this.anglePush = Convert.ToInt32(strFull[3]);
+ this.angleWeight = Convert.ToInt32(strFull[4]);
+ this.inertia = Convert.ToInt32(strFull[5]);
+ this.gearedDown = Convert.ToInt32(strFull[6]);
+ }
+
+ //decimalPointForR: ensure decimal is point in order to work in R
+ public string ToString(string sep, bool decimalPointForR) {
+ string str_d = "";
+ string str_D = "";
+ if(decimalPointForR) {
+ str_d = Util.ConvertToPoint(d);
+ str_D = Util.ConvertToPoint(D);
+ } else {
+ str_d = d.ToString();
+ str_D = D.ToString();
+ }
+
+ return
+ name + sep + str_d + sep + str_D + sep +
+ anglePush.ToString() + sep + angleWeight.ToString() + sep +
+ inertia.ToString() + sep + gearedDown.ToString();
+ }
+
}
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index c75b4f7..f3fda7f 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -667,12 +667,9 @@ public partial class ChronoJumpWindow
"", //path, //url
(int) encoderCaptureOptionsWin.spin_encoder_capture_time.Value,
(int) encoderCaptureOptionsWin.spin_encoder_capture_min_height.Value,
- -1, //Since 1.3.7 smooth is not stored in curves
"", //desc,
"","", //status, videoURL
- encoderConfigurationCurrent.name.ToString(),
- encoderConfigurationCurrent.inertia,
- encoderConfigurationCurrent.d,
+ encoderConfigurationCurrent,
"","","", //future1, 2, 3
Util.FindOnArray(':', 2, 1, UtilGtk.ComboGetActive(combo_encoder_exercise),
encoderExercisesTranslationAndBodyPWeight) //exerciseName
(english)
@@ -1173,10 +1170,7 @@ public partial class ChronoJumpWindow
encoderSignalUniqueID = eSQL.uniqueID;
button_video_play_this_test_encoder.Sensitive = (eSQL.videoURL != "");
- encoderConfigurationCurrent = new EncoderConfiguration(
(Constants.EncoderConfigurationNames)
- Enum.Parse(typeof(Constants.EncoderConfigurationNames),
eSQL.encoderConfigurationName) );
- encoderConfigurationCurrent.d = eSQL.diameter;
- encoderConfigurationCurrent.inertia = eSQL.inertiaMomentum;
+ encoderConfigurationCurrent = eSQL.encoderConfiguration;
label_encoder_selected.Text = encoderConfigurationCurrent.code;
}
@@ -1604,9 +1598,7 @@ public partial class ChronoJumpWindow
eSQL.url = path;
eSQL.description = desc;
- eSQL.encoderConfigurationName = encoderConfigurationCurrent.name.ToString();
- eSQL.inertiaMomentum = encoderConfigurationCurrent.inertia;
- eSQL.diameter = encoderConfigurationCurrent.d;
+ eSQL.encoderConfiguration = encoderConfigurationCurrent;
//if is a signal that we just loaded, then don't insert, do an update
@@ -2175,7 +2167,8 @@ public partial class ChronoJumpWindow
//create dataFileName
TextWriter writer = File.CreateText(dataFileName);
-
writer.WriteLine("status,seriesName,exerciseName,massBody,massExtra,smoothingOne,dateTime,fullURL,eccon,percentBodyWeight");
+
writer.WriteLine("status,seriesName,exerciseName,massBody,massExtra,dateTime,fullURL,eccon,percentBodyWeight,"
+
+ "econfName, econfd, econfD, econfAnglePush, econfAngleWeight,
econfInertia, econfGearedDown");
ArrayList eeArray = SqliteEncoder.SelectEncoderExercises(false, -1, false);
EncoderExercise ex = new EncoderExercise();
@@ -2241,10 +2234,11 @@ Log.WriteLine(str);
writer.WriteLine(eSQL.status + "," + seriesName + "," + ex.name + "," +
Util.ConvertToPoint(iteratingMassBody).ToString() + "," +
Util.ConvertToPoint(Convert.ToDouble(eSQL.extraWeight)) + ","
+
- Util.ConvertToPoint(eSQL.smooth) + "," + eSQL.GetDate(true) +
"," +
+ eSQL.GetDate(true) + "," +
fullURL + "," +
eSQL.eccon + "," + //this is the eccon of every curve
- ex.percentBodyWeight.ToString()
+ ex.percentBodyWeight.ToString() + "," +
+ eSQL.encoderConfiguration.ToString(",",true)
);
countSeries ++;
}
diff --git a/src/gui/encoderConfiguration.cs b/src/gui/encoderConfiguration.cs
index 36da3ae..b809aa4 100644
--- a/src/gui/encoderConfiguration.cs
+++ b/src/gui/encoderConfiguration.cs
@@ -197,11 +197,27 @@ public class EncoderConfigurationWindow {
public EncoderConfiguration GetAcceptedValues()
{
EncoderConfiguration ec = (EncoderConfiguration) list[listCurrent];
- ec.d = (double) spin_d.Value;
- ec.D = (double) spin_D.Value;
- ec.anglePush = (int) spin_angle_push.Value;
- ec.angleWeight = (int) spin_angle_weight.Value;
- ec.inertia = (int) spin_inertia.Value;
+
+ ec.d = -1;
+ ec.D = -1;
+ ec.anglePush = -1;
+ ec.angleWeight = -1;
+ ec.inertia = -1;
+
+ if(ec.has_d)
+ ec.d = (double) spin_d.Value;
+
+ if(ec.has_D)
+ ec.D = (double) spin_D.Value;
+
+ if(ec.has_angle_push)
+ ec.anglePush = (int) spin_angle_push.Value;
+
+ if(ec.has_angle_weight)
+ ec.angleWeight = (int) spin_angle_weight.Value;
+
+ if(ec.has_inertia)
+ ec.inertia = (int) spin_inertia.Value;
return ec;
}
diff --git a/src/sqlite/encoder.cs b/src/sqlite/encoder.cs
index 3a83d0e..45b3562 100644
--- a/src/sqlite/encoder.cs
+++ b/src/sqlite/encoder.cs
@@ -38,7 +38,6 @@ class SqliteEncoder : Sqlite
protected internal static void createTableEncoder()
{
- /* old
dbcmd.CommandText =
"CREATE TABLE " + Constants.EncoderTable + " ( " +
"uniqueID INTEGER PRIMARY KEY, " +
@@ -53,34 +52,10 @@ class SqliteEncoder : Sqlite
"url TEXT, " +
"time INT, " +
"minHeight INT, " +
- "smooth FLOAT, " + //unused. since 1.3.7 is on preferences
- "description TEXT, " +
- "future1 TEXT, " + //works as status: "active", "inactive"
- "future2 TEXT, " + //URL of video of signals
- "future3 TEXT )"; //Constants.EncoderSignalMode (only on signals) (add "-0.01"
for inertia momentum)
- dbcmd.ExecuteNonQuery();
- */
- dbcmd.CommandText =
- "CREATE TABLE " + Constants.EncoderTable + " ( " +
- "uniqueID INTEGER PRIMARY KEY, " +
- "personID INT, " +
- "sessionID INT, " +
- "exerciseID INT, " +
- "eccon TEXT, " + //"c" or "ec"
- "laterality TEXT, " + //"left" "right" "both"
- "extraWeight TEXT, " + //string because can contain "33%" or "50Kg"
- "signalOrCurve TEXT, " + //"signal" or "curve"
- "filename TEXT, " +
- "url TEXT, " +
- "time INT, " +
- "minHeight INT, " +
- "smooth FLOAT, " + //unused. since 1.3.7 is on preferences
"description TEXT, " +
"status TEXT, " + //"active", "inactive"
"videoURL TEXT, " + //URL of video of signals
- "mode TEXT, " + //Constants.EncoderSignalMode (signals, and curves)
- "inertiaMomentum INT, " + //signals and curves
- "diameter FLOAT, " + //signals and curves
+ "encoderConfiguration TEXT, " + //text separated by ':'
"future1 TEXT, " +
"future2 TEXT, " +
"future3 TEXT )";
@@ -101,19 +76,17 @@ class SqliteEncoder : Sqlite
dbcmd.CommandText = "INSERT INTO " + Constants.EncoderTable +
" (uniqueID, personID, sessionID, exerciseID, eccon, laterality, extraWeight, " +
- "signalOrCurve, filename, url, time, minHeight, smooth, description, status, " +
- "videoURL, mode, inertiaMomentum, diameter, future1, future2, future3)" +
+ "signalOrCurve, filename, url, time, minHeight, description, status, " +
+ "videoURL, encoderConfiguration, future1, future2, future3)" +
" VALUES (" + es.uniqueID + ", " +
es.personID + ", " + es.sessionID + ", " +
es.exerciseID + ", '" + es.eccon + "', '" +
es.laterality + "', '" + es.extraWeight + "', '" +
es.signalOrCurve + "', '" + es.filename + "', '" +
- es.url + "', " + es.time + ", " + es.minHeight + ", " +
- Util.ConvertToPoint(es.smooth) + ", '" + es.description +
- "', 'active', '" + es.videoURL + "', '" + es.encoderConfigurationName + "', " +
- es.inertiaMomentum + ", " + Util.ConvertToPoint(es.diameter) + ", '" +
- es.future1 + "', '" + es.future2 + "', '" +
- es.future3 + "')";
+ es.url + "', " + es.time + ", " + es.minHeight + ", '" + es.description +
+ "', '" + es.status + "', '" + es.videoURL + "', '" +
+ es.encoderConfiguration.ToString(":",true) + "', '" +
+ es.future1 + "', '" + es.future2 + "', '" + es.future3 + "')";
Log.WriteLine(dbcmd.CommandText.ToString());
dbcmd.ExecuteNonQuery();
@@ -149,14 +122,11 @@ class SqliteEncoder : Sqlite
"', url = '" + es.url +
"', time = " + es.time +
", minHeight = " + es.minHeight +
- ", smooth = " + Util.ConvertToPoint(es.smooth) + //unused. in 1.3.7 is
on preferences
", description = '" + es.description +
"', status = '" + es.status +
"', videoURL = '" + es.videoURL +
- "', mode = '" + es.encoderConfigurationName +
- "', inertiaMomentum = " + es.inertiaMomentum +
- ", diameter = " + Util.ConvertToPoint(es.diameter) +
- ", future1 = '" + es.future1 +
+ "', encoderConfiguration = '" + es.encoderConfiguration.ToString(":",true) +
+ "', future1 = '" + es.future1 +
"', future2 = '" + es.future2 +
"', future3 = '" + es.future3 +
"' WHERE uniqueID == " + es.uniqueID ;
@@ -225,6 +195,13 @@ class SqliteEncoder : Sqlite
EncoderSQL es = new EncoderSQL();
while(reader.Read()) {
+ string [] strFull = reader[15].ToString().Split(new char[] {':'});
+ EncoderConfiguration econf = new EncoderConfiguration(
+ (Constants.EncoderConfigurationNames)
+ Enum.Parse(typeof(Constants.EncoderConfigurationNames), strFull[0]) );
+ econf.FromSQL(strFull);
+
+ Log.WriteLine(econf.ToString(":", true));
es = new EncoderSQL (
reader[0].ToString(), //uniqueID
Convert.ToInt32(reader[1].ToString()), //personID
@@ -238,17 +215,14 @@ class SqliteEncoder : Sqlite
reader[9].ToString(), //url
Convert.ToInt32(reader[10].ToString()), //time
Convert.ToInt32(reader[11].ToString()), //minHeight
- Convert.ToDouble(Util.ChangeDecimalSeparator(reader[12].ToString())),
//smooth UNUSED
- reader[13].ToString(), //description
- reader[14].ToString(), //status
- reader[15].ToString(), //videoURL
- reader[16].ToString(), //encoderConfigurationName
- Convert.ToInt32(reader[17].ToString()), //inertiaMomentum
- Convert.ToDouble(Util.ChangeDecimalSeparator(reader[18].ToString())),
//diameter
- reader[19].ToString(), //future1
- reader[20].ToString(), //future2
- reader[21].ToString(), //future3
- reader[22].ToString() //EncoderExercise.name
+ reader[12].ToString(), //description
+ reader[13].ToString(), //status
+ reader[14].ToString(), //videoURL
+ econf, //encoderConfiguration
+ reader[16].ToString(), //future1
+ reader[17].ToString(), //future2
+ reader[18].ToString(), //future3
+ reader[19].ToString() //EncoderExercise.name
);
array.Add (es);
}
diff --git a/src/sqlite/main.cs b/src/sqlite/main.cs
index 6fa818d..aaacbcc 100644
--- a/src/sqlite/main.cs
+++ b/src/sqlite/main.cs
@@ -74,7 +74,7 @@ class Sqlite
* Important, change this if there's any update to database
* Important2: if database version get numbers higher than 1, check if the comparisons with
currentVersion works ok
*/
- static string lastChronojumpDatabaseVersion = "1.03";
+ static string lastChronojumpDatabaseVersion = "1.04";
public Sqlite() {
}
@@ -1427,6 +1427,50 @@ class Sqlite
currentVersion = "1.03";
}
+ if(currentVersion == "1.03") {
+ dbcon.Open();
+
+ ArrayList array =
SqliteOldConvert.EncoderSelect103(true,-1,-1,-1,"all",false);
+
+ conversionRateTotal = array.Count;
+
+ dropTable(Constants.EncoderTable);
+ SqliteEncoder.createTableEncoder();
+
+ //in this conversion put this as default for all SQL rows
+ EncoderConfiguration econf = new EncoderConfiguration();
+
+ int count = 1;
+ foreach(EncoderSQL103 es in array) {
+ conversionRate = count;
+
+ //do not use SqliteEncoder.Insert because that method maybe changes
in the future,
+ //and here we need to do a conversion that works from 1.03 to 1.04
+ dbcmd.CommandText = "INSERT INTO " + Constants.EncoderTable +
+ " (uniqueID, personID, sessionID, exerciseID, eccon,
laterality, extraWeight, " +
+ "signalOrCurve, filename, url, time, minHeight, description,
status, " +
+ "videoURL, encoderConfiguration, future1, future2, future3)" +
+ " VALUES (" + es.uniqueID + ", " +
+ es.personID + ", " + es.sessionID + ", " +
+ es.exerciseID + ", '" + es.eccon + "', '" +
+ es.laterality + "', '" + es.extraWeight + "', '" +
+ es.signalOrCurve + "', '" + es.filename + "', '" +
+ es.url + "', " + es.time + ", " + es.minHeight + ", '" +
es.description + "', '" +
+ es.status + "', '" + es.videoURL + "', '" +
+ econf.ToString(":", true) + "', '" + //in this conversion put
this as default for all SQL rows
+ es.future1 + "', '" + es.future2 + "', '" + es.future3 + "')";
+ Log.WriteLine(dbcmd.CommandText.ToString());
+ dbcmd.ExecuteNonQuery();
+ count ++;
+ }
+
+ conversionRate = count;
+ Log.WriteLine("Encoder table improved");
+ SqlitePreferences.Update ("databaseVersion", "1.04", true);
+ dbcon.Close();
+
+ currentVersion = "1.04";
+ }
}
@@ -1568,6 +1612,7 @@ class Sqlite
SqliteCountry.initialize();
//changes [from - to - desc]
+ //1.03 - 1-04 Converted DB to 1.04 Encoder table improved
//1.02 - 1-03 Converted DB to 1.03 Updated encoder exercise, angle is now on encoder
configuration
//1.01 - 1-02 Converted DB to 1.02 Added Agility Tests: Agility-T-Test, Agility-3L3R
//1.00 - 1.01 Converted DB to 1.01 Added export to CSV configuration on preferences
diff --git a/src/sqlite/oldConvert.cs b/src/sqlite/oldConvert.cs
index 06552d1..64a693b 100644
--- a/src/sqlite/oldConvert.cs
+++ b/src/sqlite/oldConvert.cs
@@ -28,6 +28,99 @@ using Mono.Data.Sqlite;
class SqliteOldConvert : Sqlite
{
+
+ //pass uniqueID value and then will return one record. do like this:
+ //EncoderSQL eSQL = (EncoderSQL) SqliteEncoder.Select(false, myUniqueID, 0, 0, "")[0];
+ //or
+ //pass uniqueID==-1 and personID, sessionID, signalOrCurve values, and will return some records
+ //personID can be -1 to get all on that session
+ //sessionID can be -1 to get all sessions
+ //signalOrCurve can be "all"
+ public static ArrayList EncoderSelect103 (bool dbconOpened,
+ int uniqueID, int personID, int sessionID, string signalOrCurve, bool onlyActive)
+ {
+ if(! dbconOpened)
+ dbcon.Open();
+
+ string personIDStr = "";
+ if(personID != -1)
+ personIDStr = " personID = " + personID + " AND ";
+
+ string sessionIDStr = "";
+ if(sessionID != -1)
+ sessionIDStr = " sessionID = " + sessionID + " AND ";
+
+ string selectStr = "";
+ if(uniqueID != -1)
+ selectStr = Constants.EncoderTable + ".uniqueID = " + uniqueID;
+ else {
+ if(signalOrCurve == "all")
+ selectStr = personIDStr + sessionIDStr;
+ else
+ selectStr = personIDStr + sessionIDStr + " signalOrCurve = '" + signalOrCurve
+ "'";
+ }
+
+ string andString = "";
+ if(selectStr != "")
+ andString = " AND ";
+
+ string onlyActiveString = "";
+ if(onlyActive)
+ onlyActiveString = " AND " + Constants.EncoderTable + ".status = 'active' ";
+
+ dbcmd.CommandText = "SELECT " +
+ Constants.EncoderTable + ".*, " + Constants.EncoderExerciseTable + ".name FROM " +
+ Constants.EncoderTable + ", " + Constants.EncoderExerciseTable +
+ " WHERE " + selectStr +
+ andString + Constants.EncoderTable + ".exerciseID = " +
+ Constants.EncoderExerciseTable + ".uniqueID " +
+ onlyActiveString +
+ " ORDER BY substr(filename,-23,19)"; //this contains the date of capture signal
+
+ Log.WriteLine(dbcmd.CommandText.ToString());
+
+ SqliteDataReader reader;
+ reader = dbcmd.ExecuteReader();
+
+ ArrayList array = new ArrayList(1);
+
+ EncoderSQL103 es = new EncoderSQL103();
+ while(reader.Read()) {
+ es = new EncoderSQL103 (
+ reader[0].ToString(), //uniqueID
+ Convert.ToInt32(reader[1].ToString()), //personID
+ Convert.ToInt32(reader[2].ToString()), //sessionID
+ Convert.ToInt32(reader[3].ToString()), //exerciseID
+ reader[4].ToString(), //eccon
+ reader[5].ToString(), //laterality
+ reader[6].ToString(), //extraWeight
+ reader[7].ToString(), //signalOrCurve
+ reader[8].ToString(), //filename
+ reader[9].ToString(), //url
+ Convert.ToInt32(reader[10].ToString()), //time
+ Convert.ToInt32(reader[11].ToString()), //minHeight
+ Convert.ToDouble(Util.ChangeDecimalSeparator(reader[12].ToString())),
//smooth UNUSED
+ reader[13].ToString(), //description
+ reader[14].ToString(), //status
+ reader[15].ToString(), //videoURL
+ reader[16].ToString(), //encoderConfigurationName
+ Convert.ToInt32(reader[17].ToString()), //inertiaMomentum
+ Convert.ToDouble(Util.ChangeDecimalSeparator(reader[18].ToString())),
//diameter
+ reader[19].ToString(), //future1
+ reader[20].ToString(), //future2
+ reader[21].ToString(), //future3
+ reader[22].ToString() //EncoderExercise.name
+ );
+ array.Add (es);
+ }
+ reader.Close();
+ if(! dbconOpened)
+ dbcon.Close();
+
+ return array;
+ }
+
+
//pass uniqueID value and then will return one record. do like this:
//EncoderSQL eSQL = (EncoderSQL) SqliteEncoder.Select(false, myUniqueID, 0, 0, "")[0];
//or
@@ -115,6 +208,79 @@ class SqliteOldConvert : Sqlite
}
}
+//used in DB version 1.03 and before
+public class EncoderSQL103
+{
+ public string uniqueID;
+ public int personID;
+ public int sessionID;
+ public int exerciseID;
+ public string eccon;
+ public string laterality;
+ public string extraWeight;
+ public string signalOrCurve;
+ public string filename;
+ public string url;
+ public int time;
+ public int minHeight;
+ public double smooth; //unused on curves, since 1.3.7 it's in database
+ public string description;
+ public string status; //active or inactive curves
+ public string videoURL; //URL of video of signals
+
+ //encoderConfiguration conversions
+ //in signals and curves, need to do conversions (invert, inertiaMomentum, diameter)
+ public string encoderConfigurationName;
+ public int inertiaMomentum; //kg*cm^2
+ public double diameter;
+
+ public string future1;
+ public string future2;
+ public string future3;
+
+ public string exerciseName;
+
+ public EncoderSQL103 ()
+ {
+ }
+
+ public EncoderSQL103 (string uniqueID, int personID, int sessionID, int exerciseID,
+ string eccon, string laterality, string extraWeight, string signalOrCurve,
+ string filename, string url, int time, int minHeight, double smooth,
+ string description, string status, string videoURL,
+ string encoderConfigurationName, int inertiaMomentum, double diameter,
+ string future1, string future2, string future3,
+ string exerciseName
+ )
+ {
+ this.uniqueID = uniqueID;
+ this.personID = personID;
+ this.sessionID = sessionID;
+ this.exerciseID = exerciseID;
+ this.eccon = eccon;
+ this.laterality = laterality;
+ this.extraWeight = extraWeight;
+ this.signalOrCurve = signalOrCurve;
+ this.filename = filename;
+ this.url = url;
+ this.time = time;
+ this.minHeight = minHeight;
+ this.smooth = smooth;
+ this.description = description;
+ this.status = status;
+ this.videoURL = videoURL;
+ this.encoderConfigurationName = encoderConfigurationName;
+ this.inertiaMomentum = inertiaMomentum;
+ this.diameter = diameter;
+ this.future1 = future1;
+ this.future2 = future2;
+ this.future3 = future3;
+ this.exerciseName = exerciseName;
+ }
+
+}
+
+
//used in DB version 0.98 and before
public class EncoderSQL098
{
[
Date Prev][
Date Next] [
Thread Prev][
Thread Next]
[
Thread Index]
[
Date Index]
[
Author Index]