[chronojump] testing capture and pass stuff to R



commit cd92ba35c4851c0e698c9b68a85a3abdae57cbbc
Author: Xavier de Blas <xaviblas gmail com>
Date:   Thu Jan 15 18:38:17 2015 +0100

    testing capture and pass stuff to R

 encoder/Makefile.am  |    1 +
 encoder/capture.R    |  100 +++++++++++
 encoder/graph.R      |  479 -------------------------------------------------
 encoder/util.R       |  484 ++++++++++++++++++++++++++++++++++++++++++++++++++
 no-rdotnet/passToR.R |    1 +
 src/gui/encoder.cs   |  138 +++++++++++++--
 src/utilEncoder.cs   |   85 +---------
 7 files changed, 708 insertions(+), 580 deletions(-)
---
diff --git a/encoder/Makefile.am b/encoder/Makefile.am
index 639404d..a485df8 100644
--- a/encoder/Makefile.am
+++ b/encoder/Makefile.am
@@ -2,6 +2,7 @@ encoderdatadir = @datadir@/@PACKAGE@/encoder
 
 dist_encoderdata_DATA = pyserial_pyper.py \
             call_graph.R \
+            capture.R \
             graph.R \
             inertia-momentum.R \
             neuromuscularProfile.R \
diff --git a/encoder/capture.R b/encoder/capture.R
new file mode 100644
index 0000000..1396fc6
--- /dev/null
+++ b/encoder/capture.R
@@ -0,0 +1,100 @@
+#http://stackoverflow.com/questions/26053302/is-there-a-way-to-use-standard-input-output-stream-to-communicate-c-sharp-and-r/26058010#26058010
+
+cat("Arrived at capture.R\n")
+
+f <- file("stdin")
+open(f)
+
+
+args <- commandArgs(TRUE)
+optionsFile <- args[1]
+#print(optionsFile)
+
+
+getOptionsFromFile <- function(optionsFile, lines) {
+       optionsCon <- file(optionsFile, 'r')
+       options=readLines(optionsCon, n=lines)
+       close(optionsCon)
+       return (options)
+}
+
+options <- getOptionsFromFile(optionsFile, 1)
+
+#print(options)
+
+scriptUtilR = options[1]
+#print(scriptUtilR)
+
+source(scriptUtilR)
+
+#print("Loaded libraries")
+       
+input <- readLines(f, n = 1L)
+while(input[1] != "Q") {
+       #Sys.sleep(4) #just to test how Chronojump reacts if process takes too long
+       cat(paste("input is:", input, "\n"))
+
+       displacement = as.numeric(unlist(strsplit(input, " ")))
+       #if data file ends with comma. Last character will be an NA. remove it
+       #this removes all NAs
+       displacement  = displacement[!is.na(displacement)]
+       
+       position = cumsum(displacement)
+       #print("position")
+       #print(position)
+                               
+       reduceTemp = reduceCurveBySpeed("c", 1, 
+                                     1, 0, #startT, startH
+                                     displacement, #displacement
+                                     .7 #SmoothingOneC
+                                     )
+       start = reduceTemp[1]
+       end = reduceTemp[2]
+       if(end > length(displacement))
+               end = length(displacement)
+       
+       #print("printing reduceTemp")
+       #print(c(start, end, length(displacement)))
+
+       displacement = displacement[start:end]
+
+       #print("reduced")
+                               
+       myMassBody = 50
+       myMassExtra = 100
+       myExPercentBodyWeight = 0
+       myEncoderConfigurationName = "LINEAR"
+       myDiameter = 0
+       myDiameterExt = 0
+       myAnglePush = 90
+       myAngleWeight = 90
+       myInertiaMomentum = 0
+       myGearedDown = 0
+       SmoothingsEC = 0.7
+       SmoothingOneC = 0.7
+       g = 9.81
+       myEcconKn = "c" #in ec can be "e" or "c"
+       isPropulsive = TRUE
+       
+       #print("pre kinematicsResult")
+
+       kinematicsResult <- kinematicsF(displacement, 
+                   myMassBody, myMassExtra, myExPercentBodyWeight,
+                   
myEncoderConfigurationName,myDiameter,myDiameterExt,myAnglePush,myAngleWeight,myInertiaMomentum,myGearedDown,
+                   SmoothingsEC,SmoothingOneC, 
+                   g, myEcconKn, isPropulsive)
+       #print("kinematicsResult")
+       #print(kinematicsResult)
+
+       paf = pafGenerate("c", kinematicsResult, myMassBody, myMassExtra)
+       print("paf")
+       print(paf)
+
+       #do not use print because it shows the [1] first. Use cat:
+       cat(paste(paf$meanSpeed, paf$maxSpeed, paf$maxSpeedT, paf$meanPower, paf$peakPower, paf$peakPowerT, 
paf$pp_ppt, sep=", "))
+
+
+       input <- readLines(f, n = 1L)
+}
+#cat("Ending capture.R\n")
+quit()
diff --git a/encoder/graph.R b/encoder/graph.R
index e7003e1..8e29257 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -396,341 +396,8 @@ findSmoothingsEC <- function(singleFile, displacement, curves, eccon, smoothingO
        return(smoothings)
 }
 
-#used in alls eccons
-reduceCurveBySpeed <- function(eccon, row, startT, startH, displacement, smoothingOneC) 
-{
-       print("at reduceCurveBySpeed")
-
-       #In 1.4.0 and before, we use smoothingOneEC on "ec", "ce"
-       #but the problem is findSmoothingsEC has problems knowing the smoothingEC when users stays stand up 
lot of time before jump.
-        #is better to reduceCurveBySpeed first in order to remove the not-moving phase
-       #and then do findSmoothingsEC
-       #for this reason, following code is commented, and it's only used smoothingOneC 
 
-       #smoothing = smoothingOneEC
-       #if(eccon == "c" || eccon == "ecS" || eccon == "ceS")
-       #       smoothing = smoothingOneC
-               
-       smoothing = smoothingOneC
-
-       speed <- getSpeed(displacement, smoothing)
-       
-       speed.ext=extrema(speed$y)
-
-       #in order to reduce curve by speed, we search the cross of speed (in 0m/s)
-        #before and after the peak value, but in "ec" and "ce" there are two peak values:
-       #
-       #ec         2
-       #\         / \
-       # \       /   \
-       #-----------------
-       #   \   /       \
-       #    \ /         \
-       #     1     
-       #
-       #ce   1
-       #    / \         /
-       #   /   \       /
-       #-----------------
-       # /       \   /
-       #/         \ /
-       #           2
-       #
-       #then we need two times: time1, time2 to search cross speed 0 before and after them
-
-       time1 = 0
-       time2 = 0
-       if(eccon=="ec") {
-               time1 = min(which(speed$y == min(speed$y)))
-               time2 = max(which(speed$y == max(speed$y)))
-       } else if(eccon=="ce") {
-               time1 = min(which(speed$y == max(speed$y)))
-               time2 = max(which(speed$y == min(speed$y)))
-       } else {
-               speed$y=abs(speed$y)
-               time1 = min(which(speed$y == max(speed$y)))
-               time2 = max(which(speed$y == max(speed$y)))
-       }
-
-       #now that times are defined we can work in ABS for all the curves
-       speed$y=abs(speed$y)
-
-       #left adjust
-       #find the speed.ext$cross at left of max speed
-       x.ini = 0 #good to declare here
-       ext.cross.len = length(speed.ext$cross[,2])
-       if(ext.cross.len == 0)
-               x.ini = 0
-       else if(ext.cross.len == 1) {
-               if(speed.ext$cross[,2] < time1) 
-                       x.ini = speed.ext$cross[,2]
-       } else { 
-               for(i in speed.ext$cross[,2]) 
-                       if(i < time1) 
-                               x.ini = i
-       }
-
-       #right adjust
-       #find the speed.ext$cross at right of max speed
-       x.end = length(displacement) #good to declare here
-       #ext.cross.len = length(speed.ext$cross[,2])
-       if(ext.cross.len == 0)
-               x.end = length(displacement)
-       else if(ext.cross.len == 1) {
-               if(speed.ext$cross[,2] > time2) 
-                       x.end = speed.ext$cross[,2]
-       } else { 
-               for(i in rev(speed.ext$cross[,2])) 
-                       if(i > time2) 
-                               x.end = i
-       }
 
-       #debug
-       print(speed.ext$cross[,2])
-       #print(ext.cross.len)
-       print(c("time1,time2",time1,time2))
-       print(c("x.ini x.end",x.ini,x.end))
-
-       #to know the new startH
-       #calculate displacement from original start to the new: x.ini
-       startH.old = startH
-       startH = startH + sum(displacement[1:x.ini])
-       print(c("old startH:", startH.old, "; new startH:", startH))
-
-       return(c(startT + x.ini, startT + x.end, startH))
-}
-
-findECPhases <- function(displacement,speed) {
-       speed.ext=extrema(speed)
-       #print(speed.ext)
-       #print(speed)
-       
-       #In all the extrema minindex values, search which range (row) has the min values,
-       #and in this range search last value
-       print("searchMinSpeedEnd")
-       searchMinSpeedEnd = max(which(speed == min(speed)))
-       print(searchMinSpeedEnd)
-       
-       #In all the extrema maxindex values, search which range (row) has the max values,
-       #and in this range search first value
-       print("searchMaxSpeedIni")
-       searchMaxSpeedIni = min(which(speed == max(speed)))
-       print(searchMaxSpeedIni)
-       
-       #find the cross between both
-       print("speed.ext-Cross")
-       print(speed.ext$cross[,1])
-       print("search min cross: crossMinRow")
-       crossMinRow=which(speed.ext$cross[,1] > searchMinSpeedEnd & speed.ext$cross[,1] < searchMaxSpeedIni)
-       print(crossMinRow)
-                       
-       #if (length(crossMinRow) > 0) {
-       #       print(crossMinRow)
-       #} else {
-       #       propulsiveEnd = length(displacement)
-       #       errorSearching = TRUE
-       #}
-       
-       eccentric = 0
-       isometric = 0
-       concentric = 0
-
-       #temporary fix problem of found MinSpeedEnd at right
-       if(searchMinSpeedEnd > searchMaxSpeedIni)
-               return(list(
-                           eccentric=0,
-                           isometric=0,
-                           concentric=0))
-
-
-       isometricUse = TRUE
-
-       print("at findECPhases")
-
-       if(isometricUse) {
-               eccentric=1:min(speed.ext$cross[crossMinRow,1])
-               isometric=min(speed.ext$cross[crossMinRow,1]+1):max(speed.ext$cross[crossMinRow,2])
-               concentric=max(speed.ext$cross[crossMinRow,2]+1):length(displacement)
-       } else {
-               eccentric=1:mean(speed.ext$cross[crossMinRow,1])
-               #isometric=mean(speed.ext$cross[crossMinRow,1]+1):mean(speed.ext$cross[crossMinRow,2])
-               concentric=mean(speed.ext$cross[crossMinRow,2]+1):length(displacement)
-       }
-       return(list(
-               eccentric=eccentric,
-               isometric=isometric,
-               concentric=concentric))
-}
-
-findPropulsiveEnd <- function(accel, concentric, maxSpeedTInConcentric,
-                            encoderConfigurationName, anglePush, angleWeight, 
-                            massBody, massExtra, exercisePercentBodyWeight) {
-
-       propulsiveEndsAt <- -g
-
-       if(encoderConfigurationName == "LINEARONPLANE") {
-               #propulsive phase ends at: -g*sin(alfa)
-               propulsiveEndsAt <- -g * sin(anglePush * pi / 180)
-       } else if(encoderConfigurationName == "LINEARONPLANEWEIGHTDIFFANGLE") {
-               massBodyUsed <- getMassBodyByExercise(massBody, exercisePercentBodyWeight)
-               
-               #propulsive phase ends at: [massBodyUsed*sin(anglePush) + massExtra*sin(angleWeight)] / 
(massBodyUsed + massExtra)
-               propulsiveEndsAt <- -g * (massBodyUsed * sin(anglePush * pi / 180) + massExtra * 
sin(angleWeight * pi / 180)) / (massBodyUsed + massExtra)
-       }
-
-       if(length(which(accel[concentric] <= propulsiveEndsAt)) > 0) {
-               #this:
-               #       propulsiveEnd = min(which(accel[concentric] <= -g))
-               #can be a problem because some people does an strange countermovement at start of concentric 
movement
-               #this people moves arms down and legs go up
-               #at this moment acceleration can be lower than -g
-               #if this happens, propulsiveEnd will be very early and detected jump will be very high
-               #is exactly the same problem than findTakeOff, see that method for further help
-               #another option can be using extrema
-
-               accelCon = accel[concentric]
-               df=data.frame(accelCon <= propulsiveEndsAt, accelCon, 
abs(1:length(accelCon)-maxSpeedTInConcentric))
-               colnames(df)=c("belowG","accel","dist")
-               df2 = subset(df,subset=df$belowG)
-       
-               df2row = min(which(df2$dist == min(df2$dist)))
-               propulsiveEnd = as.integer(rownames(df2)[df2row])
-       }
-       else
-               propulsiveEnd = length(concentric)
-       
-return (propulsiveEnd)
-}
-
-#go here with every single curve
-#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,
-                       
encoderConfigurationName,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown,
-                       smoothingOneEC, smoothingOneC, g, eccon, isPropulsive) {
-
-       smoothing = 0
-       if(eccon == "c" || eccon == "e")
-               smoothing = smoothingOneC
-       else
-               smoothing = smoothingOneEC
-
-print(c(" smoothing:",smoothing))
-
-       #x vector should contain at least 4 different values
-       if(length(displacement) >= 4)
-               speed <- getSpeed(displacement, smoothing)
-       else
-               speed=list(y=rep(0,length(displacement)))
-       
-       if(length(displacement) >= 4)
-               accel <- getAcceleration(speed)
-       else
-               accel=list(y=rep(0,length(displacement)))
-
-       #print(c(" ms",round(mean(speed$y),5)," ma",round(mean(accel$y),5)))
-       #print(c(" Ms",round(max(speed$y),5)," Ma",round(max(accel$y),5)))
-       #print(c(" |ms|",round(mean(abs(speed$y)),5)," |ma|:",round(mean(abs(accel$y)),5)))
-       #print(c(" |Ms|",round(max(abs(speed$y)),5)," |Ma|",round(max(abs(accel$y)),5)))
-
-       #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
-       accel$y <- accel$y * 1000 
-       errorSearching = FALSE
-
-       concentric = 0
-       propulsiveEnd = 0
-
-       print(c("at kinematicsF eccon: ", eccon, " length(displacement): ",length(displacement)))
-
-       #search propulsiveEnd
-       if(isPropulsive) {
-               if(eccon=="c") {
-                       concentric=1:length(displacement)
-                       
-                       maxSpeedT <- min(which(speed$y == max(speed$y)))
-                       maxSpeedTInConcentric = maxSpeedT
-                       
-                       propulsiveEnd = findPropulsiveEnd(accel$y,concentric,maxSpeedTInConcentric,
-                                                         encoderConfigurationName, anglePush, angleWeight, 
-                                                         massBody, massExtra, exercisePercentBodyWeight)
-               } else if(eccon=="ec") {
-                       phases=findECPhases(displacement,speed$y)
-                       eccentric = phases$eccentric
-                       isometric = phases$isometric
-                       concentric = phases$concentric
-       
-                       #temporary fix problem of found MinSpeedEnd at right
-                       if(eccentric == 0 && isometric == 0 && concentric == 0)
-                               propulsiveEnd = length(displacement)
-                       else {
-                               maxSpeedT <- min(which(speed$y == max(speed$y)))
-                               maxSpeedTInConcentric = maxSpeedT - (length(eccentric) + length(isometric))
-
-                               propulsiveEnd = length(eccentric) + length(isometric) + 
-                                               findPropulsiveEnd(accel$y,concentric,maxSpeedTInConcentric, 
-                                                                 encoderConfigurationName, anglePush, 
angleWeight, 
-                                                                 massBody, massExtra, 
exercisePercentBodyWeight)
-                               #print(c("lengths: ", length(eccentric), length(isometric), 
findPropulsiveEnd(accel$y,concentric), propulsiveEnd))
-                       }
-               } else if(eccon=="e") {
-                       #not eccon="e" because not propulsive calculations on eccentric
-               } else { #ecS
-                       print("WARNING ECS\n\n\n\n\n")
-               }
-       }
-
-       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
-
-
-       if( isPropulsive && ( eccon== "c" || eccon == "ec" ) )
-               return(list(speedy=speed$y[1:propulsiveEnd], accely=accel$y[1:propulsiveEnd], 
-                           force=force[1:propulsiveEnd], power=power[1:propulsiveEnd], mass=mass))
-       else
-               return(list(speedy=speed$y, accely=accel$y, force=force, power=power, mass=mass))
-}
-
-pafGenerate <- function(eccon, kinematics, massBody, massExtra) {
-       #print("speed$y")
-       #print(kinematics$speedy)
-
-       meanSpeed <- mean(kinematics$speedy)
-       #max speed and max speed time can be at eccentric or concentric
-       maxSpeed <- max(abs(kinematics$speedy))
-       maxSpeedT <- min(which(abs(kinematics$speedy) == maxSpeed))
-
-       if(eccon == "c")
-               meanPower <- mean(kinematics$power)
-       else
-               meanPower <- mean(abs(kinematics$power))
-
-       #print(c("eccon meanPowerSigned meanPowerABS",eccon, mean(kinematics$power), 
mean(abs(kinematics$power))))
-       #print("kinematics$power")
-       #print(abs(kinematics$power))
-
-       peakPower <- max(abs(kinematics$power))
-       peakPowerT <- min(which(abs(kinematics$power) == peakPower))
-       
-       #print(which(abs(kinematics$power) == peakPower))
-
-       pp_ppt <- peakPower / (peakPowerT/1000) # ms->s
-       meanForce <- mean(kinematics$force)
-       maxForce <- max(abs(kinematics$force))
-
-       #here paf is generated
-       #mass is not used by pafGenerate, but used by Kg/W (loadVSPower)
-       #meanForce and maxForce are not used by pafGenerate, but used by F/S (forceVSSpeed)
-       return(data.frame(
-                         meanSpeed, maxSpeed, maxSpeedT,
-                         meanPower, peakPower, peakPowerT, pp_ppt,
-                         meanForce, maxForce,
-                         kinematics$mass, massBody, massExtra)) #kinematics$mass is Load
-}
 
 kinematicRanges <- function(singleFile, displacement, curves,
                            massBody, massExtra, exercisePercentBodyWeight,
@@ -1964,15 +1631,6 @@ find.yrange <- function(singleFile, displacement, curves) {
 
 #-------------------- EncoderConfiguration conversions --------------------------
 
-isInertial <- function(encoderConfigurationName) {
-       if(encoderConfigurationName == "LINEARINERTIAL" ||
-          encoderConfigurationName == "ROTARYFRICTIONSIDEINERTIAL" ||
-          encoderConfigurationName == "ROTARYFRICTIONAXISINERTIAL" ||
-          encoderConfigurationName == "ROTARYAXISINERTIAL") 
-               return(TRUE)
-       else
-               return(FALSE)
-}
 
 #in signals and curves, need to do conversions (invert, inertiaMomentum, diameter)
 #we use 'data' variable because can be position or displacement
@@ -2031,144 +1689,7 @@ fixDisplacementInertial <- function(displacement, encoderConfigurationName, diam
        return (displacement)
 }
 
-getSpeed <- function(displacement, smoothing) {
-       #no change affected by encoderConfiguration
-
-       return (smooth.spline( 1:length(displacement), displacement, spar=smoothing))
-}
-
-getAcceleration <- function(speed) {
-       #no change affected by encoderConfiguration
-       return (predict( speed, deriv=1 ))
-}
-
-#gearedDown is positive, normally 2
-getMass <- function(mass, gearedDown, angle) {
-       if(mass == 0)
-               return (0)
-
-       #default value of angle is 90 degrees. If is not selected, it's -1
-       if(angle == -1)
-               angle = 90
-
-       return ( ( mass / gearedDown ) * sin( angle * pi / 180 ) )
-}
-
-getMassBodyByExercise <- function(massBody, exercisePercentBodyWeight) {
-       if(massBody == 0 || exercisePercentBodyWeight == 0)
-               return (0)
-       
-       return (massBody * exercisePercentBodyWeight / 100.0)
-}
-
-getMassByEncoderConfiguration <- function(encoderConfigurationName, massBody, massExtra, 
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight)
-{
-       massBody = getMassBodyByExercise(massBody,exercisePercentBodyWeight)
-
-       if(
-          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON1" ||
-          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON1INV" ||
-          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON2" ||
-          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON2INV" ||
-          encoderConfigurationName == "WEIGHTEDMOVPULLEYROTARYFRICTION" ||
-          encoderConfigurationName == "WEIGHTEDMOVPULLEYROTARYAXIS" ) 
-       {
-               massExtra = getMass(massExtra, gearedDown, anglePush)
-       } else if(encoderConfigurationName == "LINEARONPLANE") {
-               massBody = getMass(massBody, gearedDown, anglePush)
-               massExtra = getMass(massExtra, gearedDown, anglePush)
-       } else if(encoderConfigurationName == "LINEARONPLANEWEIGHTDIFFANGLE") {
-               massBody = getMass(massBody, gearedDown, anglePush)
-               massExtra = getMass(massExtra, gearedDown, angleWeight)
-       }
-               
-       mass = massBody + massExtra
-       return (mass)
-}
-
-getDynamics <- function(encoderConfigurationName,
-                       speed, accel, massBody, massExtra, exercisePercentBodyWeight, gearedDown, anglePush, 
angleWeight,
-                       displacement, diameter, diameterExt, inertiaMomentum, smoothing)
-{
-       mass = getMassByEncoderConfiguration (encoderConfigurationName, massBody, massExtra, 
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight)
-
-       if(isInertial(encoderConfigurationName))
-               return (getDynamicsInertial(encoderConfigurationName, displacement, diameter, diameterExt, 
mass, inertiaMomentum, smoothing))
-       else 
-               return (getDynamicsNotInertial (encoderConfigurationName, speed, accel, mass, 
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, exercisePercentBodyWeight, 
gearedDown, anglePush, angleWeight) 
-{
-       force <- mass*(accel+g) #g:9.81 (used when movement is against gravity)
-
-       power <- force*speed
-
-       return(list(mass=mass, force=force, power=power))
-}
-
-#d: diameter axis
-#D: diameter external (disc)
-#angle: angle (rotation of disc) in radians
-#angleSpeed: speed of angle
-#angleAccel: acceleration of angle
-#encoderConfiguration:
-#  LINEARINERTIAL Linear encoder on inertial machine (rolled on axis)
-#  ROTARYFRICTIONSIDEINERTIAL Rotary friction encoder connected to inertial machine on the side of the disc
-#  ROTARYFRICTIONAXISINERTIAL Rotary friction encoder connected to inertial machine on the axis
-#  ROTARYAXISINERTIAL Rotary axis encoder  connected to inertial machine on the axis
-
-getDynamicsInertial <- function(encoderConfigurationName, displacement, d, D, mass, inertiaMomentum, 
smoothing)
-{
-       speed = getSpeed(displacement, smoothing) #mm/ms == m/s 
-
-       # accel will be:
-       accel = getAcceleration(speed) 
 
-       accel$y = accel$y * 1000 # mm/ms² -> m/s²
-       
-       #use the values
-       speed = speed$y
-       accel = accel$y
-       
-       #----------------------
-       #let's work with SI now
-       #----------------------
-
-       position.m = abs(cumsum(displacement)) / 1000 #m
-       d.m = d / 100 #cm -> m
-       D.m = D / 100 #cm -> m
-
-       angle = position.m * 2 / d.m
-       angleSpeed = speed * 2 / d.m
-       angleAccel = accel * 2 / d.m
-
-       force = abs(inertiaMomentum * angleAccel) * (2 / d.m) + mass * (accel + g)
-       power = abs((inertiaMomentum * angleAccel) * angleSpeed) + mass * (accel + g) * speed
-       powerBody = mass * (accel + g) * speed
-       powerWheel = abs((inertiaMomentum * angleAccel) * angleSpeed)
-
-       #print(c("displacement",displacement))
-       #print(c("displacement cumsum",cumsum(displacement)))
-       print(c("inertia momentum",inertiaMomentum))
-        #print(c("d",d))
-        #print(c("mass",mass))
-        #print(c("g",g))
-        print(c("max angle",max(abs(angle))))
-       print(c("max angleSpeed",max(abs(angleSpeed))))
-       print(c("max angleAccel",max(abs(angleAccel))))
-       #print(c("speed",speed))
-       #print(c("accel",accel))
-       print(c("max force",max(abs(force))))
-       print(c("max power at inertial",max(abs(power))))
-       #print(c("powerBody",powerBody[1000]))
-       #print(c("powerWheel",powerWheel[1000]))
-       print(c("d.m, D.m", d.m, D.m))
-       print(c("max angle, max pos", max(angle), max(position.m)))
-
-       return(list(displacement=displacement, mass=mass, force=force, power=power))
-}
 
 #-------------- end of EncoderConfiguration conversions -------------------------
 
diff --git a/encoder/util.R b/encoder/util.R
index 10c6664..30864f8 100644
--- a/encoder/util.R
+++ b/encoder/util.R
@@ -125,3 +125,487 @@ findTakeOff <- function(forceConcentric, maxSpeedTInConcentric)
        return(takeoff)
 }
 
+getSpeed <- function(displacement, smoothing) {
+       #no change affected by encoderConfiguration
+
+       return (smooth.spline( 1:length(displacement), displacement, spar=smoothing))
+}
+
+getAcceleration <- function(speed) {
+       #no change affected by encoderConfiguration
+       return (predict( speed, deriv=1 ))
+}
+
+#gearedDown is positive, normally 2
+getMass <- function(mass, gearedDown, angle) {
+       if(mass == 0)
+               return (0)
+
+       #default value of angle is 90 degrees. If is not selected, it's -1
+       if(angle == -1)
+               angle = 90
+
+       return ( ( mass / gearedDown ) * sin( angle * pi / 180 ) )
+}
+
+getMassBodyByExercise <- function(massBody, exercisePercentBodyWeight) {
+       if(massBody == 0 || exercisePercentBodyWeight == 0)
+               return (0)
+       
+       return (massBody * exercisePercentBodyWeight / 100.0)
+}
+
+getMassByEncoderConfiguration <- function(encoderConfigurationName, massBody, massExtra, 
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight)
+{
+       massBody = getMassBodyByExercise(massBody,exercisePercentBodyWeight)
+
+       if(
+          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON1" ||
+          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON1INV" ||
+          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON2" ||
+          encoderConfigurationName == "WEIGHTEDMOVPULLEYLINEARONPERSON2INV" ||
+          encoderConfigurationName == "WEIGHTEDMOVPULLEYROTARYFRICTION" ||
+          encoderConfigurationName == "WEIGHTEDMOVPULLEYROTARYAXIS" ) 
+       {
+               massExtra = getMass(massExtra, gearedDown, anglePush)
+       } else if(encoderConfigurationName == "LINEARONPLANE") {
+               massBody = getMass(massBody, gearedDown, anglePush)
+               massExtra = getMass(massExtra, gearedDown, anglePush)
+       } else if(encoderConfigurationName == "LINEARONPLANEWEIGHTDIFFANGLE") {
+               massBody = getMass(massBody, gearedDown, anglePush)
+               massExtra = getMass(massExtra, gearedDown, angleWeight)
+       }
+               
+       mass = massBody + massExtra
+       return (mass)
+}
+
+#used in alls eccons
+reduceCurveBySpeed <- function(eccon, row, startT, startH, displacement, smoothingOneC) 
+{
+       #print("at reduceCurveBySpeed")
+
+       #In 1.4.0 and before, we use smoothingOneEC on "ec", "ce"
+       #but the problem is findSmoothingsEC has problems knowing the smoothingEC when users stays stand up 
lot of time before jump.
+        #is better to reduceCurveBySpeed first in order to remove the not-moving phase
+       #and then do findSmoothingsEC
+       #for this reason, following code is commented, and it's only used smoothingOneC 
+
+       #smoothing = smoothingOneEC
+       #if(eccon == "c" || eccon == "ecS" || eccon == "ceS")
+       #       smoothing = smoothingOneC
+               
+       smoothing = smoothingOneC
+
+       speed <- getSpeed(displacement, smoothing)
+       
+       speed.ext=extrema(speed$y)
+
+       #in order to reduce curve by speed, we search the cross of speed (in 0m/s)
+        #before and after the peak value, but in "ec" and "ce" there are two peak values:
+       #
+       #ec         2
+       #\         / \
+       # \       /   \
+       #-----------------
+       #   \   /       \
+       #    \ /         \
+       #     1     
+       #
+       #ce   1
+       #    / \         /
+       #   /   \       /
+       #-----------------
+       # /       \   /
+       #/         \ /
+       #           2
+       #
+       #then we need two times: time1, time2 to search cross speed 0 before and after them
+
+       time1 = 0
+       time2 = 0
+       if(eccon=="ec") {
+               time1 = min(which(speed$y == min(speed$y)))
+               time2 = max(which(speed$y == max(speed$y)))
+       } else if(eccon=="ce") {
+               time1 = min(which(speed$y == max(speed$y)))
+               time2 = max(which(speed$y == min(speed$y)))
+       } else {
+               speed$y=abs(speed$y)
+               time1 = min(which(speed$y == max(speed$y)))
+               time2 = max(which(speed$y == max(speed$y)))
+       }
+
+       #now that times are defined we can work in ABS for all the curves
+       speed$y=abs(speed$y)
+
+       #left adjust
+       #find the speed.ext$cross at left of max speed
+       x.ini = 0 #good to declare here
+       ext.cross.len = length(speed.ext$cross[,2])
+       if(ext.cross.len == 0)
+               x.ini = 0
+       else if(ext.cross.len == 1) {
+               if(speed.ext$cross[,2] < time1) 
+                       x.ini = speed.ext$cross[,2]
+       } else { 
+               for(i in speed.ext$cross[,2]) 
+                       if(i < time1) 
+                               x.ini = i
+       }
+
+       #right adjust
+       #find the speed.ext$cross at right of max speed
+       x.end = length(displacement) #good to declare here
+       #ext.cross.len = length(speed.ext$cross[,2])
+       if(ext.cross.len == 0)
+               x.end = length(displacement)
+       else if(ext.cross.len == 1) {
+               if(speed.ext$cross[,2] > time2) 
+                       x.end = speed.ext$cross[,2]
+       } else { 
+               for(i in rev(speed.ext$cross[,2])) 
+                       if(i > time2) 
+                               x.end = i
+       }
+
+       #debug
+       #print(speed.ext$cross[,2])
+       #print(ext.cross.len)
+       #print(c("time1,time2",time1,time2))
+       #print(c("x.ini x.end",x.ini,x.end))
+
+       #to know the new startH
+       #calculate displacement from original start to the new: x.ini
+       startH.old = startH
+       startH = startH + sum(displacement[1:x.ini])
+       #print(c("old startH:", startH.old, "; new startH:", startH))
+
+       return(c(startT + x.ini, startT + x.end, startH))
+}
+
+#go here with every single curve
+#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,
+                       
encoderConfigurationName,diameter,diameterExt,anglePush,angleWeight,inertiaMomentum,gearedDown,
+                       smoothingOneEC, smoothingOneC, g, eccon, isPropulsive) {
+
+       smoothing = 0
+       if(eccon == "c" || eccon == "e")
+               smoothing = smoothingOneC
+       else
+               smoothing = smoothingOneEC
+
+#print(c(" smoothing:",smoothing))
+
+       #x vector should contain at least 4 different values
+       if(length(displacement) >= 4)
+               speed <- getSpeed(displacement, smoothing)
+       else
+               speed=list(y=rep(0,length(displacement)))
+       
+       if(length(displacement) >= 4)
+               accel <- getAcceleration(speed)
+       else
+               accel=list(y=rep(0,length(displacement)))
+
+       #print(c(" ms",round(mean(speed$y),5)," ma",round(mean(accel$y),5)))
+       #print(c(" Ms",round(max(speed$y),5)," Ma",round(max(accel$y),5)))
+       #print(c(" |ms|",round(mean(abs(speed$y)),5)," |ma|:",round(mean(abs(accel$y)),5)))
+       #print(c(" |Ms|",round(max(abs(speed$y)),5)," |Ma|",round(max(abs(accel$y)),5)))
+
+       #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
+       accel$y <- accel$y * 1000 
+       errorSearching = FALSE
+
+       concentric = 0
+       propulsiveEnd = 0
+
+       #print(c("at kinematicsF eccon: ", eccon, " length(displacement): ",length(displacement)))
+
+       #search propulsiveEnd
+       if(isPropulsive) {
+               if(eccon=="c") {
+                       concentric=1:length(displacement)
+                       
+                       maxSpeedT <- min(which(speed$y == max(speed$y)))
+                       maxSpeedTInConcentric = maxSpeedT
+                       
+                       propulsiveEnd = findPropulsiveEnd(accel$y,concentric,maxSpeedTInConcentric,
+                                                         encoderConfigurationName, anglePush, angleWeight, 
+                                                         massBody, massExtra, exercisePercentBodyWeight)
+               } else if(eccon=="ec") {
+                       phases=findECPhases(displacement,speed$y)
+                       eccentric = phases$eccentric
+                       isometric = phases$isometric
+                       concentric = phases$concentric
+       
+                       #temporary fix problem of found MinSpeedEnd at right
+                       if(eccentric == 0 && isometric == 0 && concentric == 0)
+                               propulsiveEnd = length(displacement)
+                       else {
+                               maxSpeedT <- min(which(speed$y == max(speed$y)))
+                               maxSpeedTInConcentric = maxSpeedT - (length(eccentric) + length(isometric))
+
+                               propulsiveEnd = length(eccentric) + length(isometric) + 
+                                               findPropulsiveEnd(accel$y,concentric,maxSpeedTInConcentric, 
+                                                                 encoderConfigurationName, anglePush, 
angleWeight, 
+                                                                 massBody, massExtra, 
exercisePercentBodyWeight)
+                               #print(c("lengths: ", length(eccentric), length(isometric), 
findPropulsiveEnd(accel$y,concentric), propulsiveEnd))
+                       }
+               } else if(eccon=="e") {
+                       #not eccon="e" because not propulsive calculations on eccentric
+               } else { #ecS
+                       #print("WARNING ECS\n\n\n\n\n")
+               }
+       }
+
+       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
+
+
+       if( isPropulsive && ( eccon== "c" || eccon == "ec" ) )
+               return(list(speedy=speed$y[1:propulsiveEnd], accely=accel$y[1:propulsiveEnd], 
+                           force=force[1:propulsiveEnd], power=power[1:propulsiveEnd], mass=mass))
+       else
+               return(list(speedy=speed$y, accely=accel$y, force=force, power=power, mass=mass))
+}
+
+findECPhases <- function(displacement,speed) {
+       speed.ext=extrema(speed)
+       #print(speed.ext)
+       #print(speed)
+       
+       #In all the extrema minindex values, search which range (row) has the min values,
+       #and in this range search last value
+       #print("searchMinSpeedEnd")
+       searchMinSpeedEnd = max(which(speed == min(speed)))
+       #print(searchMinSpeedEnd)
+       
+       #In all the extrema maxindex values, search which range (row) has the max values,
+       #and in this range search first value
+       #print("searchMaxSpeedIni")
+       searchMaxSpeedIni = min(which(speed == max(speed)))
+       #print(searchMaxSpeedIni)
+       
+       #find the cross between both
+       #print("speed.ext-Cross")
+       #print(speed.ext$cross[,1])
+       #print("search min cross: crossMinRow")
+       crossMinRow=which(speed.ext$cross[,1] > searchMinSpeedEnd & speed.ext$cross[,1] < searchMaxSpeedIni)
+       #print(crossMinRow)
+                       
+       #if (length(crossMinRow) > 0) {
+       #       print(crossMinRow)
+       #} else {
+       #       propulsiveEnd = length(displacement)
+       #       errorSearching = TRUE
+       #}
+       
+       eccentric = 0
+       isometric = 0
+       concentric = 0
+
+       #temporary fix problem of found MinSpeedEnd at right
+       if(searchMinSpeedEnd > searchMaxSpeedIni)
+               return(list(
+                           eccentric=0,
+                           isometric=0,
+                           concentric=0))
+
+
+       isometricUse = TRUE
+
+       #print("at findECPhases")
+
+       if(isometricUse) {
+               eccentric=1:min(speed.ext$cross[crossMinRow,1])
+               isometric=min(speed.ext$cross[crossMinRow,1]+1):max(speed.ext$cross[crossMinRow,2])
+               concentric=max(speed.ext$cross[crossMinRow,2]+1):length(displacement)
+       } else {
+               eccentric=1:mean(speed.ext$cross[crossMinRow,1])
+               #isometric=mean(speed.ext$cross[crossMinRow,1]+1):mean(speed.ext$cross[crossMinRow,2])
+               concentric=mean(speed.ext$cross[crossMinRow,2]+1):length(displacement)
+       }
+       return(list(
+               eccentric=eccentric,
+               isometric=isometric,
+               concentric=concentric))
+}
+
+findPropulsiveEnd <- function(accel, concentric, maxSpeedTInConcentric,
+                            encoderConfigurationName, anglePush, angleWeight, 
+                            massBody, massExtra, exercisePercentBodyWeight) {
+
+       propulsiveEndsAt <- -g
+
+       if(encoderConfigurationName == "LINEARONPLANE") {
+               #propulsive phase ends at: -g*sin(alfa)
+               propulsiveEndsAt <- -g * sin(anglePush * pi / 180)
+       } else if(encoderConfigurationName == "LINEARONPLANEWEIGHTDIFFANGLE") {
+               massBodyUsed <- getMassBodyByExercise(massBody, exercisePercentBodyWeight)
+               
+               #propulsive phase ends at: [massBodyUsed*sin(anglePush) + massExtra*sin(angleWeight)] / 
(massBodyUsed + massExtra)
+               propulsiveEndsAt <- -g * (massBodyUsed * sin(anglePush * pi / 180) + massExtra * 
sin(angleWeight * pi / 180)) / (massBodyUsed + massExtra)
+       }
+
+       if(length(which(accel[concentric] <= propulsiveEndsAt)) > 0) {
+               #this:
+               #       propulsiveEnd = min(which(accel[concentric] <= -g))
+               #can be a problem because some people does an strange countermovement at start of concentric 
movement
+               #this people moves arms down and legs go up
+               #at this moment acceleration can be lower than -g
+               #if this happens, propulsiveEnd will be very early and detected jump will be very high
+               #is exactly the same problem than findTakeOff, see that method for further help
+               #another option can be using extrema
+
+               accelCon = accel[concentric]
+               df=data.frame(accelCon <= propulsiveEndsAt, accelCon, 
abs(1:length(accelCon)-maxSpeedTInConcentric))
+               colnames(df)=c("belowG","accel","dist")
+               df2 = subset(df,subset=df$belowG)
+       
+               df2row = min(which(df2$dist == min(df2$dist)))
+               propulsiveEnd = as.integer(rownames(df2)[df2row])
+       }
+       else
+               propulsiveEnd = length(concentric)
+       
+return (propulsiveEnd)
+}
+
+pafGenerate <- function(eccon, kinematics, massBody, massExtra) {
+       #print("speed$y")
+       #print(kinematics$speedy)
+
+       meanSpeed <- mean(kinematics$speedy)
+       #max speed and max speed time can be at eccentric or concentric
+       maxSpeed <- max(abs(kinematics$speedy))
+       maxSpeedT <- min(which(abs(kinematics$speedy) == maxSpeed))
+
+       if(eccon == "c")
+               meanPower <- mean(kinematics$power)
+       else
+               meanPower <- mean(abs(kinematics$power))
+
+       #print(c("eccon meanPowerSigned meanPowerABS",eccon, mean(kinematics$power), 
mean(abs(kinematics$power))))
+       #print("kinematics$power")
+       #print(abs(kinematics$power))
+
+       peakPower <- max(abs(kinematics$power))
+       peakPowerT <- min(which(abs(kinematics$power) == peakPower))
+       
+       #print(which(abs(kinematics$power) == peakPower))
+
+       pp_ppt <- peakPower / (peakPowerT/1000) # ms->s
+       meanForce <- mean(kinematics$force)
+       maxForce <- max(abs(kinematics$force))
+
+       #here paf is generated
+       #mass is not used by pafGenerate, but used by Kg/W (loadVSPower)
+       #meanForce and maxForce are not used by pafGenerate, but used by F/S (forceVSSpeed)
+       return(data.frame(
+                         meanSpeed, maxSpeed, maxSpeedT,
+                         meanPower, peakPower, peakPowerT, pp_ppt,
+                         meanForce, maxForce,
+                         kinematics$mass, massBody, massExtra)) #kinematics$mass is Load
+}
+
+isInertial <- function(encoderConfigurationName) {
+       if(encoderConfigurationName == "LINEARINERTIAL" ||
+          encoderConfigurationName == "ROTARYFRICTIONSIDEINERTIAL" ||
+          encoderConfigurationName == "ROTARYFRICTIONAXISINERTIAL" ||
+          encoderConfigurationName == "ROTARYAXISINERTIAL") 
+               return(TRUE)
+       else
+               return(FALSE)
+}
+
+getDynamics <- function(encoderConfigurationName,
+                       speed, accel, massBody, massExtra, exercisePercentBodyWeight, gearedDown, anglePush, 
angleWeight,
+                       displacement, diameter, diameterExt, inertiaMomentum, smoothing)
+{
+       mass = getMassByEncoderConfiguration (encoderConfigurationName, massBody, massExtra, 
exercisePercentBodyWeight, gearedDown, anglePush, angleWeight)
+
+       if(isInertial(encoderConfigurationName))
+               return (getDynamicsInertial(encoderConfigurationName, displacement, diameter, diameterExt, 
mass, inertiaMomentum, smoothing))
+       else 
+               return (getDynamicsNotInertial (encoderConfigurationName, speed, accel, mass, 
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, exercisePercentBodyWeight, 
gearedDown, anglePush, angleWeight) 
+{
+       force <- mass*(accel+g) #g:9.81 (used when movement is against gravity)
+
+       power <- force*speed
+
+       return(list(mass=mass, force=force, power=power))
+}
+
+#d: diameter axis
+#D: diameter external (disc)
+#angle: angle (rotation of disc) in radians
+#angleSpeed: speed of angle
+#angleAccel: acceleration of angle
+#encoderConfiguration:
+#  LINEARINERTIAL Linear encoder on inertial machine (rolled on axis)
+#  ROTARYFRICTIONSIDEINERTIAL Rotary friction encoder connected to inertial machine on the side of the disc
+#  ROTARYFRICTIONAXISINERTIAL Rotary friction encoder connected to inertial machine on the axis
+#  ROTARYAXISINERTIAL Rotary axis encoder  connected to inertial machine on the axis
+
+getDynamicsInertial <- function(encoderConfigurationName, displacement, d, D, mass, inertiaMomentum, 
smoothing)
+{
+       speed = getSpeed(displacement, smoothing) #mm/ms == m/s 
+
+       # accel will be:
+       accel = getAcceleration(speed) 
+
+       accel$y = accel$y * 1000 # mm/ms² -> m/s²
+       
+       #use the values
+       speed = speed$y
+       accel = accel$y
+       
+       #----------------------
+       #let's work with SI now
+       #----------------------
+
+       position.m = abs(cumsum(displacement)) / 1000 #m
+       d.m = d / 100 #cm -> m
+       D.m = D / 100 #cm -> m
+
+       angle = position.m * 2 / d.m
+       angleSpeed = speed * 2 / d.m
+       angleAccel = accel * 2 / d.m
+
+       force = abs(inertiaMomentum * angleAccel) * (2 / d.m) + mass * (accel + g)
+       power = abs((inertiaMomentum * angleAccel) * angleSpeed) + mass * (accel + g) * speed
+       powerBody = mass * (accel + g) * speed
+       powerWheel = abs((inertiaMomentum * angleAccel) * angleSpeed)
+
+       #print(c("displacement",displacement))
+       #print(c("displacement cumsum",cumsum(displacement)))
+       #print(c("inertia momentum",inertiaMomentum))
+        #print(c("d",d))
+        #print(c("mass",mass))
+        #print(c("g",g))
+        #print(c("max angle",max(abs(angle))))
+       #print(c("max angleSpeed",max(abs(angleSpeed))))
+       #print(c("max angleAccel",max(abs(angleAccel))))
+       #print(c("speed",speed))
+       #print(c("accel",accel))
+       #print(c("max force",max(abs(force))))
+       #print(c("max power at inertial",max(abs(power))))
+       #print(c("powerBody",powerBody[1000]))
+       #print(c("powerWheel",powerWheel[1000]))
+       #print(c("d.m, D.m", d.m, D.m))
+       #print(c("max angle, max pos", max(angle), max(position.m)))
+
+       return(list(displacement=displacement, mass=mass, force=force, power=power))
+}
diff --git a/no-rdotnet/passToR.R b/no-rdotnet/passToR.R
index aa7b8f5..e6ac191 100644
--- a/no-rdotnet/passToR.R
+++ b/no-rdotnet/passToR.R
@@ -4,6 +4,7 @@ open(f)
 
 input <- readLines(f, n = 1L)
 while(input[1] != "Q") {
+       #Sys.sleep(4) #just to test how Chronojump reacts if process takes too long
        cat(paste("input is:", input, "\n"))
        input <- readLines(f, n = 1L)
 }
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index a42bf45..9a676a2 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -4424,7 +4424,7 @@ public partial class ChronoJumpWindow
                                                 }
                                                 */
                                        } else
-                                               processCaptureNoRDotNet = 
UtilEncoder.RunEncoderCaptureNoRDotNetInitialize();
+                                               processCaptureNoRDotNet = 
runEncoderCaptureNoRDotNetInitialize();
                                }
                                
 
@@ -4453,7 +4453,6 @@ public partial class ChronoJumpWindow
                                        captureCurvesBarsData = new ArrayList();
                                        updatingEncoderCaptureGraphRCalc = false;
        
-                                       curvesSentToR = 0;
                                        encoderThread = new Thread(new ThreadStart(encoderDoCaptureCsharp));
                                        GLib.Idle.Add (new GLib.IdleHandler 
(pulseGTKEncoderCaptureAndCurves));
                                }
@@ -4582,6 +4581,82 @@ public partial class ChronoJumpWindow
                pen_selected_encoder_capture.SetLineAttributes (2, Gdk.LineStyle.Solid, Gdk.CapStyle.NotLast, 
Gdk.JoinStyle.Miter);
        }
 
+
+
+       Process pCaptureNoRDotNet;
+       private Process runEncoderCaptureNoRDotNetInitialize() 
+       {
+LogB.Debug("A");
+               ProcessStartInfo pinfo;
+               //If output file is not given, R will try to write in the running folder
+               //in which we may haven't got permissions
+       
+               string pBin="";
+               pinfo = new ProcessStartInfo();
+
+               pBin="Rscript";
+               if (UtilAll.IsWindows()) {
+                       //on Windows we need the \"str\" to call without problems in path with spaces
+                       pBin = "\"" + System.IO.Path.Combine(Util.GetPrefixDir(), "bin" + 
Path.DirectorySeparatorChar + "Rscript.exe") + "\"";
+                       LogB.Information("pBin:", pBin);
+               }
+LogB.Debug("B");
+
+               string scriptOptions = UtilEncoder.GetEncoderScriptUtilR();
+               if (UtilAll.IsWindows())
+                       scriptOptions = scriptOptions.Replace("\\","/");
+
+
+               string optionsFile = Path.GetTempPath() + "Roptions.txt";
+               TextWriter writer = File.CreateText(optionsFile);
+               writer.Write(scriptOptions);
+               writer.Flush();
+               writer.Close();
+               ((IDisposable)writer).Dispose();
+
+
+       
+               //on Windows we need the \"str\" to call without problems in path with spaces
+               //pinfo.Arguments = "\"" + "passToR.R" + "\" " + optionsFile;
+               pinfo.Arguments = "\"" + UtilEncoder.GetEncoderScriptCaptureNoRdotNet() + "\" " + optionsFile;
+       
+               LogB.Information("Arguments:", pinfo.Arguments);
+               LogB.Information("--- 1 --- " + optionsFile.ToString() + " ---");
+               LogB.Information("--- 2 --- " + pinfo.Arguments.ToString() + " ---");
+
+               pinfo.FileName=pBin;
+
+               pinfo.CreateNoWindow = true;
+               pinfo.UseShellExecute = false;
+               pinfo.RedirectStandardInput = true;
+               pinfo.RedirectStandardError = true;
+               pinfo.RedirectStandardOutput = true; 
+
+               
+
+LogB.Debug("C");
+               Process pCaptureNoRDotNet = new Process();
+               pCaptureNoRDotNet.StartInfo = pinfo;
+               
+               // output will go here
+               pCaptureNoRDotNet.OutputDataReceived += new DataReceivedEventHandler(readingCurveFromR);
+               //pCaptureNoRDotNet.ErrorDataReceived += new DataReceivedEventHandler(readingCurveFromRerror);
+
+               pCaptureNoRDotNet.Start();
+
+               // Start asynchronous read of the output.
+               pCaptureNoRDotNet.BeginOutputReadLine();
+
+LogB.Debug("D");
+//             LogB.Information(p.StandardOutput.ReadToEnd());
+//             LogB.Warning(p.StandardError.ReadToEnd());
+
+//             p.WaitForExit();
+
+//             while ( ! ( File.Exists(outputFileCheck) || CancelRScript ) );
+
+               return pCaptureNoRDotNet;
+       }
        
        /*
         * unused, done while capturing
@@ -4630,20 +4705,47 @@ public partial class ChronoJumpWindow
        }
        */
        
-       int curvesSentToR;
-       private void readingCurveFromR() 
+       private void readingCurveFromR (object sendingProcess, DataReceivedEventArgs curveFromR)
        {
-               if(! eccaCreated)
-                       return;
-
-               if(ecca.curvesAccepted > curvesSentToR) {
-                       LogB.Information("ReadingCurveFromR");
-
-                       string str = processCaptureNoRDotNet.StandardOutput.ReadLine();
-                       if(str != null && str != "" && str != "\n")
-                               Console.WriteLine(str);
-
-                       curvesSentToR ++;
+               if (!String.IsNullOrEmpty(curveFromR.Data))
+               {
+                       LogB.Warning(curveFromR.Data);
+               
+               /*      
+                       encoderCaptureStringR += 
string.Format("\n{0},2,a,3,4,{1},{2},{3},{4},{5},{6},{7},{8},{9},{10},7",
+                       */
+                                       /*
+                                       ecca.curvesAccepted +1,
+                                       ecc.startFrame, ecc.endFrame-ecc.startFrame,
+                                       Util.ConvertToPoint(height*10), //cm    
+                                       Util.ConvertToPoint(meanSpeed), Util.ConvertToPoint(maxSpeed), 
speedT1,
+                                       Util.ConvertToPoint(meanPower), Util.ConvertToPoint(peakPower), 
+                                       Util.ConvertToPoint(peakPowerT*1000), Util.ConvertToPoint(peakPower / 
peakPowerT) 
+                                       */
+                       /*
+                                       0,
+                                       0, 0,
+                                       0,
+                                       */
+                                       /*
+                                       meanSpeed, maxSpeed, maxSpeedT,
+                                       meanPower, peakPower, peakPowerT,
+                                       peakPowerDividedByPeakPowerT
+                                       */
+                       /*
+                                       curveFromR.Data
+                                       );
+                                       */
+                       //TODO: this has to be done by the GTK thread on pulse method
+                       //treeviewEncoderCaptureRemoveColumns();
+                       //ecca.curvesAccepted = createTreeViewEncoderCapture(encoderCaptureStringR);
+               }
+       }
+       private void readingCurveFromRerror (object sendingProcess, DataReceivedEventArgs curveFromR)
+       {
+               if (!String.IsNullOrEmpty(curveFromR.Data))
+               {
+                       LogB.Error(curveFromR.Data);
                }
        }
                                
@@ -4653,8 +4755,10 @@ public partial class ChronoJumpWindow
                        LogB.ThreadEnding(); 
                        finishPulsebar(encoderActions.CURVES);
 
-                       if(! useRDotNet)
+                       if(! useRDotNet) {
                                UtilEncoder.RunEncoderCaptureNoRDotNetSendEnd(processCaptureNoRDotNet);
+                               processCaptureNoRDotNet.WaitForExit();
+                       }
                        
                        LogB.ThreadEnded(); 
                        return false;
@@ -4681,7 +4785,7 @@ public partial class ChronoJumpWindow
                                        updateEncoderCaptureGraph(true, true, true); //graphSignal, 
calcCurves, plotCurvesBars
                        } else {
                                //capturingSendCurveToR(); //unused, done while capturing
-                               readingCurveFromR();
+                               //readingCurveFromR();
                                
                                updateEncoderCaptureGraph(true, false, false); //graphSignal, no calcCurves, 
no plotCurvesBars
                        }
diff --git a/src/utilEncoder.cs b/src/utilEncoder.cs
index b4bc615..8c5c23c 100644
--- a/src/utilEncoder.cs
+++ b/src/utilEncoder.cs
@@ -176,7 +176,7 @@ public class UtilEncoder
                                        Util.GetDataDir(), "encoder", 
Constants.EncoderScriptCapturePythonLinux);
        }
        */
-       private static string getEncoderScriptCaptureNoRdotNet() {
+       public static string GetEncoderScriptCaptureNoRdotNet() {
                return System.IO.Path.Combine(
                                Util.GetDataDir(), "encoder", Constants.EncoderScriptCaptureNoRDotNet);
        }
@@ -472,88 +472,6 @@ public class UtilEncoder
        }
        */
 
-       //Process pCaptureNoRDotNet;
-       public static Process RunEncoderCaptureNoRDotNetInitialize() 
-       {
-LogB.Debug("A");
-               ProcessStartInfo pinfo;
-               //If output file is not given, R will try to write in the running folder
-               //in which we may haven't got permissions
-       
-               string pBin="";
-               pinfo = new ProcessStartInfo();
-
-               pBin="Rscript";
-               if (UtilAll.IsWindows()) {
-                       //on Windows we need the \"str\" to call without problems in path with spaces
-                       pBin = "\"" + System.IO.Path.Combine(Util.GetPrefixDir(), "bin" + 
Path.DirectorySeparatorChar + "Rscript.exe") + "\"";
-                       LogB.Information("pBin:", pBin);
-               }
-LogB.Debug("B");
-       
-       /*      
-               string optionsFile = Path.GetTempPath() + "Roptions.txt";
-               TextWriter writer = File.CreateText(optionsFile);
-               //writer.Write("some options for the capture, like end at n seconds or maybe not needed 
because we can send the Q from the software");
-               writer.Write(GetEncoderScriptUtilR() + "\n" +
-                               UtilEncoder.GetEncoderCaptureNoRDotNetStart() + "\n" + //curve sent to R
-                               UtilEncoder.GetEncoderCaptureNoRDotNetProcessed() + "\n" +      //curve 
processed from R (maybe discardedwith some text file)
-                               UtilEncoder.GetEncoderCaptureNoRDotNetEnded()                   //signal that 
processing ended (maybe not needed)
-               writer.Flush();
-               writer.Close();
-               ((IDisposable)writer).Dispose();
-               */
-       
-       /*      
-               if (UtilAll.IsWindows()) {
-                       //On win32 R understands backlash as an escape character and 
-                       //a file path uses Unix-like path separator '/'         
-                       optionsFile = optionsFile.Replace("\\","/");
-               }
-               */
-               //on Windows we need the \"str\" to call without problems in path with spaces
-               //pinfo.Arguments = "\"" + "passToR.R" + "\" " + optionsFile;
-               pinfo.Arguments = "\"" + 
"/home/xavier/informatica/progs_meus/chronojump/chronojump/no-rdotnet/passToR.R" + "\"";
-       
-               LogB.Information("Arguments:", pinfo.Arguments);
-               //LogB.Information("--- 1 --- " + optionsFile.ToString() + " ---");
-               //LogB.Information("--- 2 --- " + scriptOptions + " ---");
-               LogB.Information("--- 3 --- " + pinfo.Arguments.ToString() + " ---");
-
-//             string outputFileCheck = UtilEncoder.UtilEncoder.GetEncoderCaptureNoRDotNetEnded();
-               
-               pinfo.FileName=pBin;
-
-               pinfo.CreateNoWindow = true;
-               pinfo.UseShellExecute = false;
-               pinfo.RedirectStandardInput = true;
-               pinfo.RedirectStandardError = true;
-               pinfo.RedirectStandardOutput = true; 
-
-/*
-               //delete output file check(s)
-               LogB.Information("Deleting... " + outputFileCheck);
-               if (File.Exists(outputFileCheck))
-                       File.Delete(outputFileCheck);
-                       */
-               
-
-LogB.Debug("C");
-               Process pCaptureNoRDotNet = new Process();
-               pCaptureNoRDotNet.StartInfo = pinfo;
-               pCaptureNoRDotNet.Start();
-
-LogB.Debug("D");
-//             LogB.Information(p.StandardOutput.ReadToEnd());
-//             LogB.Warning(p.StandardError.ReadToEnd());
-
-//             p.WaitForExit();
-
-//             while ( ! ( File.Exists(outputFileCheck) || CancelRScript ) );
-
-               return pCaptureNoRDotNet;
-       }
-       
        public static void RunEncoderCaptureNoRDotNetSendCurve(Process p, double [] d)
        {
                LogB.Debug("writing line 1");
@@ -568,7 +486,6 @@ LogB.Debug("D");
        {
                LogB.Debug("sending end line");
                p.StandardInput.WriteLine("Q");
-               p.WaitForExit();
        }
 
        /*



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