[chronojump] Improving realtime inertial capture
- From: Xavier de Blas <xaviblas src gnome org>
- To: commits-list gnome org
- Cc:
- Subject: [chronojump] Improving realtime inertial capture
- Date: Thu, 12 Feb 2015 20:09:24 +0000 (UTC)
commit 26ace41b2295273c60b34f0e12fb7f009615d345
Author: Xavier de Blas <xaviblas gmail com>
Date: Thu Feb 12 21:08:28 2015 +0100
Improving realtime inertial capture
encoder/capture.R | 105 +++++++++++++++++++++++++++++++---------------------
encoder/util.R | 7 ++-
src/gui/encoder.cs | 22 +++++++++-
3 files changed, 86 insertions(+), 48 deletions(-)
---
diff --git a/encoder/capture.R b/encoder/capture.R
index 7bfcb9a..86380a5 100644
--- a/encoder/capture.R
+++ b/encoder/capture.R
@@ -26,6 +26,50 @@ options <- getOptionsFromFile(optionsFile, 32)
scriptUtilR = options[28]
source(scriptUtilR)
+g = 9.81
+
+
+calcule <- function(displacement, op)
+{
+ #read AnalysisOptions
+ #if is propulsive and rotatory inertial is: "p;ri"
+ #if nothing: "-;-"
+ analysisOptionsTemp = unlist(strsplit(op$AnalysisOptions, "\\;"))
+ isPropulsive = (analysisOptionsTemp[1] == "p")
+
+
+ #simplify on capture and have the SmoothingEC == SmoothingC
+ SmoothingsEC = op$SmoothingOneC
+
+
+ #if ecS go kinematics first time with "e" and second with "c"
+ #ceS do the opposite
+ myEcconKn = op$Eccon
+ if(myEcconKn == "ecS" || myEcconKn == "ceS") {
+ if(mean(displacement) < 0)
+ myEcconKn = "e"
+ else
+ myEcconKn = "c"
+ }
+
+
+ kinematicsResult <- kinematicsF(displacement,
+ op$MassBody, op$MassExtra, op$ExercisePercentBodyWeight,
+ op$EncoderConfigurationName, op$diameter, op$diameterExt, op$anglePush, op$angleWeight,
op$inertiaMomentum, op$gearedDown,
+ SmoothingsEC, op$SmoothingOneC,
+ g, myEcconKn, isPropulsive)
+
+ paf = data.frame()
+ paf = pafGenerate(op$Eccon, kinematicsResult, op$MassBody, op$MassExtra)
+
+ position = cumsum(displacement)
+
+ #do not use print because it shows the [1] first. Use cat:
+ cat(paste(#start, #start is not used because we have no data of the initial zeros
+ (end-start), (position[end]-position[start]),
+ paf$meanSpeed, paf$maxSpeed, paf$maxSpeedT, paf$meanPower, paf$peakPower, paf$peakPowerT,
paf$pp_ppt, sep=", "))
+ cat("\n") #mandatory to read this from C#, but beware, there we will need a trim to remove the
windows \r\n
+}
input <- readLines(f, n = 1L)
while(input[1] != "Q") {
@@ -51,10 +95,7 @@ while(input[1] != "Q") {
displacement = getDisplacement(op$EncoderConfigurationName, displacement, op$diameter,
op$diameterExt)
}
- position = cumsum(displacement)
-
start = 1
-#TODO................. #in inertial here it can be two phases: first, second or both
end = length(displacement)
if( ! isInertial(op$EncoderConfigurationName)) {
reduceTemp = reduceCurveBySpeed(op$Eccon, 1,
@@ -73,49 +114,29 @@ while(input[1] != "Q") {
displacement = displacement[start:end]
}
- position = cumsum(displacement)
-
- g = 9.81
-
- #read AnalysisOptions
- #if is propulsive and rotatory inertial is: "p;ri"
- #if nothing: "-;-"
- analysisOptionsTemp = unlist(strsplit(op$AnalysisOptions, "\\;"))
- isPropulsive = (analysisOptionsTemp[1] == "p")
-
-
- #simplify on capture and have the SmoothingEC == SmoothingC
- SmoothingsEC = op$SmoothingOneC
-
- #if ecS go kinematics first time with "e" and second with "c"
- #ceS do the opposite
- myEcconKn = op$Eccon
- if(myEcconKn == "ecS" || myEcconKn == "ceS") {
- if(mean(displacement) < 0)
- myEcconKn = "e"
- else
- myEcconKn = "c"
+ #if isInertial: getDisplacementInertialBody separate phases using initial height of full extended
person
+ #so now there will be two different curves to process
+ if(isInertial(op$EncoderConfigurationName))
+ {
+ position = cumsum(displacement)
+ positionBottom <- floor(mean(which(position == min(position))))
+ displacement1 = displacement[1:positionBottom]
+ calcule(displacement1, op)
+
+ if( (positionBottom +1) < length(displacement)){
+ displacement2 = displacement[(positionBottom+1):length(displacement)]
+ calcule(displacement2, op)
+ }
+ write(c("positionBottom", positionBottom), stderr())
+ write(c("length(displacement)", length(displacement)), stderr())
+ } else {
+ calcule(displacement, op)
}
-
- kinematicsResult <- kinematicsF(displacement,
- op$MassBody, op$MassExtra, op$ExercisePercentBodyWeight,
- op$EncoderConfigurationName, op$diameter, op$diameterExt, op$anglePush, op$angleWeight,
op$inertiaMomentum, op$gearedDown,
- SmoothingsEC, op$SmoothingOneC,
- g, myEcconKn, isPropulsive)
-
- paf = data.frame()
- paf = pafGenerate(op$Eccon, kinematicsResult, op$MassBody, op$MassExtra)
-
- #do not use print because it shows the [1] first. Use cat:
- cat(paste(#start, #start is not used because we have no data of the initial zeros
- (end-start), (position[end]-position[start]),
- paf$meanSpeed, paf$maxSpeed, paf$maxSpeedT, paf$meanPower, paf$peakPower, paf$peakPowerT,
paf$pp_ppt, sep=", "))
- cat("\n") #mandatory to read this from C#, but beware, there we will need a trim to remove the
windows \r\n
-
-
input <- readLines(f, n = 1L)
}
+
+
write("Ending capture.R", stderr())
quit()
diff --git a/encoder/util.R b/encoder/util.R
index 63f7c8a..a373938 100644
--- a/encoder/util.R
+++ b/encoder/util.R
@@ -686,7 +686,7 @@ getDisplacementInertialBody <- function(displacement, draw, title)
#TODO: check if started backwards on realtime capture (extrema is null)
firstDownPhaseTime = 1
downHeight = 0
- if(position.ext$nextreme > 0) {
+ if( position.ext$nextreme > 0 && ! is.null(position.ext$minindex) && ! is.null(position.ext$maxindex)
) {
#Fix if disc goes wrong direction at start
if(position.ext$maxindex[1] < position.ext$minindex[1]) {
displacement = displacement * -1
@@ -768,8 +768,9 @@ fixDisplacementInertial <- function(displacement, encoderConfigurationName, diam
ticksRotaryEncoder = 200 #our rotary axis encoder send 200 ticks by turn
#angle in radians
- angle = abs(cumsum(displacementMeters * 1000)) * 2 * pi / ticksRotaryEncoder
- position = angle * diameterMeters / 2
+ angle = cumsum(displacementMeters * 1000) * 2 * pi / ticksRotaryEncoder
+ #abs makes it change direction when signal is lower than initial position (0)
+ position = abs(angle * diameterMeters / 2)
position = position * 1000 #m -> mm
#this is to make "inverted cumsum"
displacement = c(0,diff(position)) #this displacement is going to be used now
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index 5541349..8d7dc29 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -2074,6 +2074,11 @@ public partial class ChronoJumpWindow
int previousFrameChange = 0;
int previousEnd = 0;
int lastNonZero = 0;
+
+ //used to send the heightAtCurveStart to R
+ //this is need on inertial to convert on direction curve (recorded by encoder) to a con-ecc
curve (done by the person)
+ double heightAtCurveStart = 0;
+ double heightAccumulated = 0;
//this will be used to stop encoder automatically
int consecutiveZeros = -1;
@@ -2219,7 +2224,10 @@ public partial class ChronoJumpWindow
string eccon = findEccon(true);
LogB.Debug("curve stuff" + ecc.startFrame + ":" +
ecc.endFrame + ":" + encoderReaded.Length);
- if(ecc.endFrame - ecc.startFrame > 0 ) {
+ if(ecc.endFrame - ecc.startFrame > 0 )
+ {
+ heightAtCurveStart = heightAccumulated;
+
double heightCurve = 0;
double [] curve = new double[ecc.endFrame -
ecc.startFrame];
for(int k=0, j=ecc.startFrame; j <
ecc.endFrame ; j ++) {
@@ -2229,6 +2237,8 @@ public partial class ChronoJumpWindow
}
previousEnd = ecc.endFrame;
+
+ heightAccumulated += heightCurve;
heightCurve = Math.Abs(heightCurve / 10);
//mm -> cm
LogB.Information(" height: " +
heightCurve.ToString());
@@ -2243,7 +2253,13 @@ public partial class ChronoJumpWindow
( ( eccon == "c" &&
previousWasUp ) || eccon != "c" ) && //2
! ( (eccon == "ec" || eccon
== "ecS") && ecc.up && ecca.curvesAccepted == 0 ) //3
) {
-
UtilEncoder.RunEncoderCaptureNoRDotNetSendCurve(pCaptureNoRDotNet, curve);
+ //this is need on inertial to convert
on direction curve (recorded by encoder)
+ //to a con-ecc curve (done by the
person)
+
if(encoderConfigurationCurrent.has_inertia)
+ curve[0] =
heightAtCurveStart;
+
+
UtilEncoder.RunEncoderCaptureNoRDotNetSendCurve(
+ pCaptureNoRDotNet,
curve);
ecca.curvesDone ++;
ecca.curvesAccepted ++;
ecca.ecc.Add(ecc);
@@ -4954,7 +4970,7 @@ LogB.Debug("D");
Convert.ToInt32( (graphWidth/2) - textWidth/2), 0,
//x, y
layout_encoder_capture_curves_bars);
- updateEncoderCaptureGraph(true, false, false); //graphSignal, not
calcCurves, not plotCurvesBars
+ updateEncoderCaptureGraph(true, true, true); //graphSignal,
calcCurves, plotCurvesBars
} else
updateEncoderCaptureGraph(true, true, true); //graphSignal,
calcCurves, plotCurvesBars
} else {
[
Date Prev][
Date Next] [
Thread Prev][
Thread Next]
[
Thread Index]
[
Date Index]
[
Author Index]