[chronojump] neuromuscularProfile 75% done (tests reamain)
- From: Xavier de Blas <xaviblas src gnome org>
- To: commits-list gnome org
- Cc:
- Subject: [chronojump] neuromuscularProfile 75% done (tests reamain)
- Date: Thu, 20 Mar 2014 15:54:30 +0000 (UTC)
commit 115b6f9705cf97a31da6556732abc270fc330f6d
Author: Xavier de Blas <xaviblas gmail com>
Date: Thu Mar 20 16:53:48 2014 +0100
neuromuscularProfile 75% done (tests reamain)
encoder/graph.R | 195 ++++++++++++++++++++++++++++++++++++++++++++-----------
1 files changed, 156 insertions(+), 39 deletions(-)
---
diff --git a/encoder/graph.R b/encoder/graph.R
index 6ec2729..5e02dd2 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -221,7 +221,7 @@ neuromuscularProfileJump <- function(e1, c, e2, mass, smoothingC)
#e1f.rdf.avg
#average force on e1f / e1f.t
- e1f.rfd.avg <- mean(e1f.force) / e1f.t
+ e1f.rfd.avg <- mean(e1f.force) / e1f.t #bars LOAD
#e1f.i (Impulse)
#average force on e1f * e1f.t / weight
@@ -231,7 +231,7 @@ neuromuscularProfileJump <- function(e1, c, e2, mass, smoothingC)
range = e1.range,
t = e1f.t,
fmax = e1f.fmax,
- rdf.avg = e1f.rfd.avg,
+ rfd.avg = e1f.rfd.avg,
i = e1f.i
)
@@ -239,59 +239,122 @@ neuromuscularProfileJump <- function(e1, c, e2, mass, smoothingC)
#2.- c variables
#----------------
- c.list = list(fmax=21) #TODO: delete this
+ #find takeoff
+ c.speed <- getSpeed(c, smoothingC)
+ c.accel = getAcceleration(c.speed)
+ #speed comes in mm/ms when derivate to accel its mm/ms^2 to convert it to m/s^2 need to *1000 because
it's quadratic
+ c.accel$y <- c.accel$y * 1000
+ c.force <- mass * (c.accel$y + g)
+
+ c.position = cumsum(c)
+ c.takeoff = min(which(c.force <= weight))
+ #c.jumpHeight = (c.position[length(c.position)] - c.position[c.takeoff]) /10
- #c1l "land" from bottom to takeoff (force < weight)
- #c1a "air" from takeoff to max height
- #c1 = c1l + c1a
+ #cl "land" from bottom to takeoff (force < weight)
+ #ca "air" from takeoff to max height
+ #c = cl + ca
+ cl = c[1:c.takeoff]
+ ca = c[c.takeoff:length(c)]
- #c1aRange
+ #ca.range
#flight phase on concentric
+ ca.pos = cumsum(ca)
+ ca.range = ca.pos[length(ca)]
- #c1lt = contact time on c1l
+ #cl.t = contact time (duration) on cl
+ cl.t <- length(cl)
- #c1lRFDavg = average force on c1l / c1lt / weight
- #c1lImpulse = average force on c1l * c1lt / weight
-
- #c1lFavg = average force on c1l / weight
-
- #c1lvF (vF -> valley Force)
- #minimum force on c1l before de concentric Speed max
-
- #c1lFmax = max force at right of valley
-
-
- #c1lSavg = avg Speed on c1l
- #c1lPavg = avg Power on c1l
- #c1lSmax = max Speed on c1l
- #c1lPmax = max Power on c1l
+ #cl.rfd.avg = average force on cl / cl.t / weight #bars EXPLODE
+ cl.speed <- getSpeed(cl, smoothingC)
+ cl.accel = getAcceleration(cl.speed)
+ #speed comes in mm/ms when derivate to accel its mm/ms^2 to convert it to m/s^2 need to *1000 because
it's quadratic
+ cl.accel$y <- cl.accel$y * 1000
+ cl.force <- mass * (cl.accel$y + g)
+ cl.rfd.avg <- mean(cl.force) / cl.t / weight
+
+ #cl.i = average force on cl * cl.t / weight #impulse #bars DRIVE
+ cl.i <- mean(cl.force) * cl.t / weight
+
+ #cl.f.avg = average force on cl / weight
+ cl.f.avg <- mean(cl.force) / weight
+
+ #cl.vf (vF -> valley Force)
+ #minimum force on cl before concentric Speed max
+ cl.speed.max.pos <- min(which(cl.speed$y == max(cl.speed$y)))
+ cl.vf.pos <- min(which(cl.speed$y == min(cl.speed$y[1:cl.speed.max.pos])))
+ cl.vf <- cl.force[cl.vf.pos]
+
+ #cl.f.max = max force at right of valley
+ cl.f.max <- max(cl.force[cl.vf.pos:length(cl)])
+
+ #cl.s.avg = avg Speed on cl
+ cl.s.avg <- mean(cl.speed$y)
+ #cl.s.max = max Speed on cl
+ cl.s.max <- max(cl.speed$y)
+
+ #power
+ cl.p <- cl.force * cl.speed$y
+ #cl.p.avg = avg Power on cl
+ cl.p.avg <- mean(cl.p)
+ #cl.p.max = max Power on cl
+ cl.p.max <- max(cl.p)
+
+ c.list = list(
+ ca.range = ca.range,
+ cl.t = cl.t,
+ cl.rfd.avg = cl.rfd.avg,
+ cl.i = cl.i,
+ cl.f.avg = cl.f.avg,
+ cl.vf = cl.vf,
+ cl.f.max = cl.f.max,
+ cl.s.avg = cl.s.avg, cl.s.max = cl.s.max,
+ cl.p.avg = cl.p.avg, cl.p.max = cl.p.max
+ )
#----------------
#3.- e2 variables
#----------------
- e2.list = list(fmax=22) #TODO: delete this
+ #get landing
+ e2.speed <- getSpeed(e2, smoothingC)
+ e2.accel = getAcceleration(e2.speed)
+ #speed comes in mm/ms when derivate to accel its mm/ms^2 to convert it to m/s^2 need to *1000 because
it's quadratic
+ e2.accel$y <- e2.accel$y * 1000
+ e2.force <- mass * (e2.accel$y + g)
+ e2.land.pos = max(which(e2.force <= weight))
#e2f (when force is done)
#is the same as contact phase (land on eccentric)
+ e2f <- e2[e2.land.pos:length(e2)]
- #e2ft duration of e2f
+ #e2f.t duration of e2f
+ e2f.t <- length(e2f)
- #e2fFmax = max force on e2f
+ #for this variables, we use e2 instead of e2f because there's lot more force on e2f
+ #so there's no need to use e2f
+ #e2f.f.max = max force on e2f
+ e2f.f.max <- max(e2.force)
#e2fFmaxt = duration from land to max force
+ e2f.f.max.t <- min(which(e2.force == e2f.f.max)) - e2.land.pos
- #e2fRFDmax = e2fFmax / e2fFmaxT
-
+ #e2f.rfd.max = e2f.f.max / e2f.f.max.t
+ e2f.rfd.max <- e2f.f.max / e2f.f.max.t
+ e2.list = list(
+ e2f.t = e2f.t,
+ e2f.f.max = e2f.f.max,
+ e2f.f.max.t = e2f.f.max.t,
+ e2f.rfd.max = e2f.rfd.max
+ )
#return an object, yes, object oriented, please
- return (list(e1.list = e1.list, c.list = c.list, e2.list = e2.list))
+ return (list(e1 = e1.list, c = c.list, e2 = e2.list))
}
#Manuel Lapuente analysis of 6 separate ABKs (e1, c, e2)
-neuromuscularProfileDoAnalysis <- function(displacement, curves, mass, smoothingC)
+neuromuscularProfileGetData <- function(displacement, curves, mass, smoothingC)
{
weight=mass*g
@@ -341,21 +404,50 @@ neuromuscularProfileDoAnalysis <- function(displacement, curves, mass, smoothing
}
- #show avg of each three values
+ #create a list of avg of each three values
+ #npmeans = list(
+ # e1.fmax = mean(npj[[1]]$e1$fmax, npj[[2]]$e1$fmax, npj[[3]]$e1$fmax),
+ # c.fmax = mean(npj[[1]]$c$fmax, npj[[2]]$c$fmax, npj[[3]]$c$fmax),
+ # e2.fmax = mean(npj[[1]]$e2$fmax, npj[[2]]$e2$fmax, npj[[3]]$e2$fmax)
+ # )
+ #return the list
+ #return (npmeans)
+
+ return (npj)
+}
+
+neuromuscularProfilePlotBars <- function(load, explode, drive)
+{
+ barplot(c(load,explode,drive),col=topo.colors(3),names.arg=c("Load","Explode","Drive"))
+ print(c("load, explode, drive", load, explode, drive))
+
+ #show small text related to graph result and how to train
+}
- print(c("e1 fmax 1,2,3", npj[[1]]$e1.list$fmax, npj[[2]]$e1.list$fmax, npj[[3]]$e1.list$fmax,
- "c fmax 1,2,3", npj[[1]]$c.list$fmax, npj[[2]]$c.list$fmax, npj[[3]]$c.list$fmax,
- "e2 fmax 1,2,3", npj[[1]]$e2.list$fmax, npj[[2]]$e2.list$fmax, npj[[3]]$e2.list$fmax
- ))
+neuromuscularProfilePlotOther <- function()
+{
+ #plot
+ #curve e1,c,e2 distance,speed,force /time of best jump
+ #curve e1,c,e2 force/time (of the three best jumps)
+ #to plot e1,c,e2 curves, just sent to paint() the xmin:xmax from start e1 to end of e2
+}
- #plot a graph with these averages
+neuromuscularProfileWriteData <- function(npj, outputData1)
+{
+ #values of first, 2nd and 3d jumps
+ jump1 <- as.numeric(c(npj[[1]]$e1, npj[[1]]$c, npj[[1]]$e2))
+ jump2 <- as.numeric(c(npj[[2]]$e1, npj[[2]]$c, npj[[2]]$e2))
+ jump3 <- as.numeric(c(npj[[3]]$e1, npj[[3]]$c, npj[[3]]$e2))
+ df <- data.frame(rbind(jump1,jump2,jump3))
+ colnames(df) <- c(paste("e1.",names(npj[[1]]$e1),sep=""), names(npj[[1]]$c), names(npj[[1]]$e2))
+ print(df)
+ write.csv(df, outputData1, quote=FALSE)
}
-
# This function converts top curve into bottom curve
#
# /\
@@ -2746,7 +2838,8 @@ doProcess <- function(options) {
if(
Analysis == "powerBars" || Analysis == "cross" ||
Analysis == "1RMBadillo2010" || Analysis == "1RMAnyExercise" ||
- Analysis == "curves" || writeCurves)
+ Analysis == "curves" || Analysis == "neuromuscularProfile" ||
+ writeCurves)
{
paf = data.frame()
discardedCurves = NULL
@@ -2907,7 +3000,31 @@ doProcess <- function(options) {
write("", OutputData1)
quit()
}
- neuromuscularProfileDoAnalysis(displacement, curves, (MassBody + MassExtra),
SmoothingOneC)
+ npj <- neuromuscularProfileGetData(displacement, curves, (MassBody + MassExtra),
SmoothingOneC)
+
+ np.bar.load <- mean(
+ npj[[1]]$e1$rfd.avg,
+ npj[[2]]$e1$rfd.avg,
+ npj[[3]]$e1$rfd.avg
+ )
+ np.bar.explode <- mean(
+ npj[[1]]$c$cl.rfd.avg,
+ npj[[2]]$c$cl.rfd.avg,
+ npj[[3]]$c$cl.rfd.avg
+ )
+ np.bar.drive <- mean(
+ npj[[1]]$c$cl.i,
+ npj[[2]]$c$cl.i,
+ npj[[3]]$c$cl.i
+ )
+
+ par(mar=c(5,4,4,5))
+ neuromuscularProfilePlotBars(np.bar.load, np.bar.explode, np.bar.drive)
+
+ #don't write the curves, write npj
+ writeCurves = FALSE
+
+ neuromuscularProfileWriteData(npj, OutputData1)
}
if(Analysis == "curves" || writeCurves) {
[
Date Prev][
Date Next] [
Thread Prev][
Thread Next]
[
Thread Index]
[
Date Index]
[
Author Index]