[chronojump] Fixed bug: 695654. Other minor changes



commit a6409e547fa32468ca7e7cf6c398c8b2fc06b3ca
Author: Xavier de Blas <xaviblas gmail com>
Date:   Tue Mar 12 21:15:57 2013 +0100

    Fixed bug: 695654. Other minor changes

 encoder/graph.R                   |  120 ++--
 encoder/pyserial_pyper.py         |   42 +-
 encoder/pyserial_pyper_windows.py |   42 +-
 glade/chronojump.glade            | 1319 +++++++++++++++++++++----------------
 rdotnet/Makefile                  |   20 +-
 src/encoder.cs                    |   24 +-
 src/gui/chronojump.cs             |   10 +
 src/gui/encoder.cs                |   41 +-
 src/gui/preferences.cs            |   68 ++-
 src/sqlite/encoder.cs             |    6 +-
 src/sqlite/main.cs                |   16 +-
 src/sqlite/preferences.cs         |    4 +
 12 files changed, 982 insertions(+), 730 deletions(-)
---
diff --git a/encoder/graph.R b/encoder/graph.R
index 753a90e..b3320a6 100644
--- a/encoder/graph.R
+++ b/encoder/graph.R
@@ -36,7 +36,7 @@ cols=c(colSpeed,colForce,colPower); lty=rep(1,3)
 #way A. passing options to a file
 getOptionsFromFile <- function(optionsFile) {
        optionsCon <- file(optionsFile, 'r')
-       options=readLines(optionsCon,n=17)
+       options=readLines(optionsCon,n=18)
        close(optionsCon)
        return (options)
 }
@@ -56,7 +56,7 @@ options=getOptionsFromFile(optionsFile);
 print(options)
 
 OutputData2=options[4] #currently used to display status
-OperatingSystem=options[17]
+OperatingSystem=options[18]
 
 write("(1/5) Starting R", OutputData2)
 
@@ -158,8 +158,13 @@ findCurves <- function(rawdata, eccon, min_height, draw, title) {
 #based on findPics2BySpeed
 #only used in eccon "c"
 #if this changes, change also in python capture file
-reduceCurveBySpeed <- function(eccon, row, startT, rawdata, smoothing) {
+reduceCurveBySpeed <- function(eccon, row, startT, rawdata, smoothingOneEC, smoothingOneC) {
        a=rawdata
+
+       smoothing = 0
+       if(eccon == "c")
+               smoothing = smoothingOneC
+
        speed <- smooth.spline( 1:length(a), a, spar=smoothing) 
        b=extrema(speed$y)
 
@@ -241,11 +246,17 @@ 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(a, mass, smoothingOne, g, eccon, analysisOptions) {
+kinematicsF <- function(a, mass, smoothingOneEC, smoothingOneC, g, eccon, analysisOptions) {
        print("length unique x in spline")
        print(length(unique(1:length(a))))
 
-       speed <- smooth.spline( 1:length(a), a, spar=smoothingOne)
+       smoothing = 0
+       if(eccon == "c")
+               smoothing = smoothingOneC
+       else
+               smoothing = smoothingOneEC
+
+       speed <- smooth.spline( 1:length(a), a, spar=smoothing)
        accel <- predict( speed, deriv=1 )
        #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 
@@ -312,19 +323,18 @@ powerBars <- function(eccon, kinematics) {
                          kinematics$mass,meanForce,maxForce))
 }
 
-kinematicRanges <- function(singleFile,rawdata,curves,mass,smoothingOne,g,eccon,analysisOptions) {
+kinematicRanges <- 
function(singleFile,rawdata,curves,mass,smoothingOneEC,smoothingOneC,g,eccon,analysisOptions) {
        n=length(curves[,1])
        maxSpeedy=0;maxForce=0;maxPower=0
        myEccon = eccon
        for(i in 1:n) { 
                myMass = mass
-               mySmoothingOne = smoothingOne
+               #mySmoothingOne = smoothingOne
                if(! singleFile) {
                        myMass = curves[i,5]
-                       mySmoothingOne = curves[i,6]
-                       myEccon = curves[i,8]
+                       myEccon = curves[i,7]
                }
-               
kn=kinematicsF(rawdata[curves[i,1]:curves[i,2]],myMass,mySmoothingOne,g,myEccon,analysisOptions)
+               
kn=kinematicsF(rawdata[curves[i,1]:curves[i,2]],myMass,smoothingOneEC,smoothingOneC,g,myEccon,analysisOptions)
                if(max(abs(kn$speedy)) > maxSpeedy)
                        maxSpeedy = max(abs(kn$speedy))
                if(max(abs(kn$force)) > maxForce)
@@ -340,7 +350,7 @@ kinematicRanges <- function(singleFile,rawdata,curves,mass,smoothingOne,g,eccon,
 
 
 paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highlight,
-       startX, startH, smoothing, mass, title, subtitle, draw, showLabels, marShrink, showAxes, legend,
+       startX, startH, smoothingOneEC, smoothingOneC, mass, title, subtitle, draw, showLabels, marShrink, 
showAxes, legend,
        Analysis, AnalysisOptions, ExercisePercentBodyWeight 
        ) {
 
@@ -348,6 +358,12 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
        meanSpeedC = 0
        meanPowerE = 0
        meanPowerC = 0
+       
+       smoothing = 0
+       if(eccon == "c")
+               smoothing = smoothingOneC
+       else
+               smoothing = smoothingOneEC
 
        #eccons ec and ecS is the same here (only show one curve)
        #receive data as cumulative sum
@@ -560,10 +576,12 @@ paint <- function(rawdata, eccon, xmin, xmax, yrange, knRanges, superpose, highl
                        plot(startX:length(accel$y),accel$y[startX:length(accel$y)],type="l",
                             xlim=c(1,length(a)),ylim=ylim,xlab="",ylab="",col="darkblue",lty=2,lwd=3,axes=F)
                        
-               #propulsive stuff
-               abline(h=-g,lty=3,col="magenta")
-               abline(v=propulsiveEnd,lty=3,col="magenta") 
-               points(propulsiveEnd, -g, col="magenta")
+               if(AnalysisOptions == "p") {
+                       #propulsive stuff
+                       abline(h=-g,lty=3,col="magenta")
+                       abline(v=propulsiveEnd,lty=3,col="magenta") 
+                       points(propulsiveEnd, -g, col="magenta")
+               }
                
                if(showAxes)
                        axis(4, col="magenta", lty=lty[1], line=2, lwd=1, padj=-.5)
@@ -1031,13 +1049,15 @@ doProcess <- function(options) {
        Eccon=options[8]
        Analysis=options[9]     #in cross comes as "cross.Force.Speed.mean"
        AnalysisOptions=options[10]     #p: propulsive
-       SmoothingOne=options[11]
-       Jump=options[12]
-       Width=as.numeric(options[13])
-       Height=as.numeric(options[14])
-       DecimalSeparator=options[15]
-       Title=options[16]
-       OperatingSystem=options[17]
+       SmoothingOneEC=options[11]
+       SmoothingOneC=options[12]
+       Jump=options[13]
+       Width=as.numeric(options[14])
+       Height=as.numeric(options[15])
+       DecimalSeparator=options[16]
+       Title=options[17]
+       OperatingSystem=options[18]     #if this changes, change it also at start of this R file
+       #important, if this grows, change the readLines value on getOptionsFromFile
 
        print(File)
        print(OutputGraph)
@@ -1137,7 +1157,7 @@ doProcess <- function(options) {
                                startH[(i+newLines)] = 0
                                exerciseName[(i+newLines)] = as.vector(inputMultiData$exerciseName[i])
                                mass[(i+newLines)] = inputMultiData$mass[i]
-                               smooth[(i+newLines)] = inputMultiData$smoothingOne[i]
+                               #smooth[(i+newLines)] = inputMultiData$smoothingOne[i] #unused since 1.3.7
                                dateTime[(i+newLines)] = as.vector(inputMultiData$dateTime[i])
 
                                curvesHeight[(i+newLines)] = sum(dataTempPhase)
@@ -1175,10 +1195,10 @@ doProcess <- function(options) {
                #then a column id is created when there's only on row, but it is not created there's more 
than one.
                #solution:
                if(length(id)==1) {
-                       curves = data.frame(start,end,startH,exerciseName,mass,smooth,
+                       curves = data.frame(start,end,startH,exerciseName,mass,
                                            dateTime,myEccon,seriesName,stringsAsFactors=F,row.names=id)
                } else {
-                       curves = data.frame(id,start,end,startH,exerciseName,mass,smooth,
+                       curves = data.frame(id,start,end,startH,exerciseName,mass,
                                            dateTime,myEccon,seriesName,stringsAsFactors=F,row.names=1)
                }
 
@@ -1207,8 +1227,8 @@ doProcess <- function(options) {
                quitIfNoData(n, curves, OutputData1)
 
                for(i in 1:n) { 
-                       curves[i,1]=reduceCurveBySpeed(Eccon, i, curves[i,1],
-                                                      rawdata[curves[i,1]:curves[i,2]], SmoothingOne)
+                       curves[i,1]=reduceCurveBySpeed(Eccon, i, curves[i,1], 
rawdata[curves[i,1]:curves[i,2]], 
+                                                      SmoothingOneEC, SmoothingOneC)
                }
                if(curvesPlot) {
                        #/10 mm -> cm
@@ -1237,20 +1257,19 @@ doProcess <- function(options) {
        if(Analysis=="single") {
                if(Jump>0) {
                        myMass = Mass
-                       mySmoothingOne = SmoothingOne
+                       #mySmoothingOne = SmoothingOne
                        myEccon = Eccon
                        myStart = curves[Jump,1]
                        myEnd = curves[Jump,2]
                        if(! singleFile) {
                                myMass = curves[Jump,5]
-                               mySmoothingOne = curves[Jump,6]
-                               myEccon = curves[Jump,8]
+                               #mySmoothingOne = curves[Jump,6]
+                               myEccon = curves[Jump,7]
                        }
                        myCurveStr = paste("curve=", Jump, ", ", myMass, "Kg", sep="")
                        paint(rawdata, myEccon, myStart, myEnd,"undefined","undefined",FALSE,FALSE,
-                             1,curves[Jump,3],mySmoothingOne,myMass,
-                             paste(Title, " ", Analysis, " ", myEccon, " ", myCurveStr,
-                                   " (smoothing: ",mySmoothingOne,")",sep=""),
+                             1,curves[Jump,3],SmoothingOneEC,SmoothingOneC,myMass,
+                             paste(Title, " ", Analysis, " ", myEccon, " ", myCurveStr, sep=""),
                              "", #subtitle
                              TRUE,     #draw
                              TRUE,     #showLabels
@@ -1270,16 +1289,17 @@ doProcess <- function(options) {
                #yrange=c(min(a),max(a))
                yrange=find.yrange(singleFile, rawdata, curves)
 
-               knRanges=kinematicRanges(singleFile,rawdata,curves,Mass,SmoothingOne,g,Eccon,AnalysisOptions)
+               knRanges=kinematicRanges(singleFile,rawdata,curves,Mass,SmoothingOneEC,SmoothingOneC,
+                                        g,Eccon,AnalysisOptions)
 
                for(i in 1:n) {
                        myMass = Mass
-                       mySmoothingOne = SmoothingOne
+                       #mySmoothingOne = SmoothingOne
                        myEccon = Eccon
                        if(! singleFile) {
                                myMass = curves[i,5]
-                               mySmoothingOne = curves[i,6]
-                               myEccon = curves[i,8]
+                               #mySmoothingOne = curves[i,6]
+                               myEccon = curves[i,7]
                        }
 
                        myTitle = ""
@@ -1289,7 +1309,7 @@ doProcess <- function(options) {
                        mySubtitle = paste("curve=", rownames(curves)[i], ", ", myMass, "Kg", sep="")
 
                        paint(rawdata, myEccon, curves[i,1],curves[i,2],yrange,knRanges,FALSE,FALSE,
-                             1,curves[i,3],mySmoothingOne,myMass,myTitle,mySubtitle,
+                             1,curves[i,3],SmoothingOneEC,SmoothingOneC,myMass,myTitle,mySubtitle,
                              TRUE,     #draw
                              FALSE,    #showLabels
                              TRUE,     #marShrink
@@ -1312,7 +1332,7 @@ doProcess <- function(options) {
                #yrange=c(min(a),max(a))
                yrange=find.yrange(singleFile, rawdata,curves)
 
-               knRanges=kinematicRanges(singleFile,rawdata,curves,Mass,SmoothingOne,g,Eccon,AnalysisOptions)
+               
knRanges=kinematicRanges(singleFile,rawdata,curves,Mass,SmoothingOneEC,SmoothingOneC,g,Eccon,AnalysisOptions)
                for(i in 1:n) {
                        #in superpose all jumps end at max height
                        #start can change, some are longer than other
@@ -1325,7 +1345,7 @@ doProcess <- function(options) {
                                myTitle = paste(titleType,Jump);
 
                        paint(rawdata, Eccon, curves[i,2]-wide,curves[i,2],yrange,knRanges,TRUE,(i==Jump),
-                             startX,curves[i,3],SmoothingOne,Mass,myTitle,"",
+                             startX,curves[i,3],SmoothingOneEC,SmoothingOneC,Mass,myTitle,"",
                              TRUE,     #draw
                              TRUE,     #showLabels
                              FALSE,    #marShrink
@@ -1358,12 +1378,12 @@ doProcess <- function(options) {
                discardingCurves = FALSE
                for(i in 1:n) { 
                        myMass = Mass
-                       mySmoothingOne = SmoothingOne
+                       #mySmoothingOne = SmoothingOne
                        myEccon = Eccon
                        if(! singleFile) {
                                myMass = curves[i,5]
-                               mySmoothingOne = curves[i,6]
-                               myEccon = curves[i,8]
+                               #mySmoothingOne = curves[i,6]
+                               myEccon = curves[i,7]
 
                                #only use concentric data       
                                if(Analysis == "1RMBadillo2010" & myEccon == "e") {
@@ -1392,7 +1412,8 @@ doProcess <- function(options) {
                        }
                        paf=rbind(paf,(powerBars(myEccon,
                                                 kinematicsF(rawdata[curves[i,1]:curves[i,2]], 
-                                                            myMass, mySmoothingOne, g, myEcconKn, 
AnalysisOptions))))
+                                                            myMass, SmoothingOneEC,SmoothingOneC, 
+                                                            g, myEcconKn, AnalysisOptions))))
                }
 
                #on 1RMBadillo discard curves "e", because paf has this curves discarded
@@ -1409,17 +1430,17 @@ doProcess <- function(options) {
                if(Analysis == "powerBars") {
                        if(! singleFile) 
                                paintPowerPeakPowerBars(singleFile, Title, paf, 
-                                                       curves[,8], Eccon,              #myEccon, Eccon
+                                                       curves[,7], Eccon,              #myEccon, Eccon
                                                        curvesHeight, n)                        #height
                        else 
                                paintPowerPeakPowerBars(singleFile, Title, paf, 
-                                                       curves[,8], Eccon,              #myEccon, Eccon
+                                                       curves[,7], Eccon,              #myEccon, Eccon
                                                        rawdata.cumsum[curves[,2]]-curves[,3], n) #height
                }
                else if(analysisCross[1] == "cross") {
                        mySeries = "1"
                        if(! singleFile)
-                               mySeries = curves[,9]
+                               mySeries = curves[,8]
 
                        if(analysisCross[2] == "Speed,Power") {
                                par(mar=c(5,4,4,5))
@@ -1453,7 +1474,7 @@ doProcess <- function(options) {
                                        curvesHeight = curvesHeight[-discardedCurves]
 
                                paf=cbind(
-                                         curves[,9],           #seriesName
+                                         curves[,8],           #seriesName
                                          curves[,4],           #exerciseName
                                          curves[,5],           #mass
                                          curves[,1],           
@@ -1490,7 +1511,8 @@ doProcess <- function(options) {
                namesNums=paste(namesNums, units)
 
                for(i in 1:curvesNum) { 
-                       kn = kinematicsF (rawdata[curves[i,1]:curves[i,2]], Mass, SmoothingOne, g, Eccon, 
AnalysisOptions)
+                       kn = kinematicsF (rawdata[curves[i,1]:curves[i,2]], Mass, 
+                                         SmoothingOneEC, SmoothingOneC, g, Eccon, AnalysisOptions)
 
                        #fill with NAs in order to have the same length
                        col1 = rawdata[curves[i,1]:curves[i,2]]
diff --git a/encoder/pyserial_pyper.py b/encoder/pyserial_pyper.py
index efe6357..8d27dd4 100644
--- a/encoder/pyserial_pyper.py
+++ b/encoder/pyserial_pyper.py
@@ -49,20 +49,21 @@ record_time = int(sys.argv[3])*1000         #from s to ms
 minRange = int(sys.argv[4])                    #all is stored, but only display when vertical range is >= 
minRange
 isJump = sys.argv[5]
 mass = float(sys.argv[6])
-smoothingOne = float(sys.argv[7])
-eccon = sys.argv[8]                            #contraction "ec" or "c"
-heightHigherCondition = int(sys.argv[9])
-heightLowerCondition = int(sys.argv[10])
-meanSpeedHigherCondition = float(sys.argv[11])
-meanSpeedLowerCondition = float(sys.argv[12])
-maxSpeedHigherCondition = float(sys.argv[13])
-maxSpeedLowerCondition = float(sys.argv[14])
-powerHigherCondition = int(sys.argv[15])
-powerLowerCondition = int(sys.argv[16])
-peakPowerHigherCondition = int(sys.argv[17])
-peakPowerLowerCondition = int(sys.argv[18])
-mainVariable = sys.argv[19]
-w_serial_port = sys.argv[20]
+smoothingOneEC = float(sys.argv[7])
+smoothingOneC = float(sys.argv[8])
+eccon = sys.argv[9]                            #contraction "ec" or "c"
+heightHigherCondition = int(sys.argv[10])
+heightLowerCondition = int(sys.argv[11])
+meanSpeedHigherCondition = float(sys.argv[12])
+meanSpeedLowerCondition = float(sys.argv[13])
+maxSpeedHigherCondition = float(sys.argv[14])
+maxSpeedLowerCondition = float(sys.argv[15])
+powerHigherCondition = int(sys.argv[16])
+powerLowerCondition = int(sys.argv[17])
+peakPowerHigherCondition = int(sys.argv[18])
+peakPowerLowerCondition = int(sys.argv[19])
+mainVariable = sys.argv[20]
+w_serial_port = sys.argv[21]
 
 delete_initial_time = 20                       #delete first records because there's encoder bug
 #w_baudrate = 9600                           # Setting the baudrate of Chronopic(9600)
@@ -147,7 +148,8 @@ meanSpeedList = list()
 maxSpeedList = list()
 meanPowerList = list()
 peakPowerList = list()
-def calculate_all_in_r(temp, top_values, bottom_values, direction_now, smoothingOne, eccon, minRange, 
isJump):
+def calculate_all_in_r(temp, top_values, bottom_values, direction_now,
+               smoothingOneEC, smoothingOneC, eccon, minRange, isJump):
        if (len(top_values)>0 and len(bottom_values)>0):
                if direction_now == 1:
                        start=top_values[len(top_values)-1]
@@ -156,7 +158,11 @@ def calculate_all_in_r(temp, top_values, bottom_values, direction_now, smoothing
                        start=bottom_values[len(bottom_values)-1]
                        end=top_values[len(top_values)-1]
                
-               myR.assign('smoothingOne',smoothingOne)
+               if(eccon == "c")
+                       myR.assign('smoothingOne',smoothingOneC)
+               else
+                       myR.assign('smoothingOne',smoothingOneEC)
+
                myR.assign('a',temp[start:end])
                
                if direction_now == -1:
@@ -195,7 +201,7 @@ def calculate_all_in_r(temp, top_values, bottom_values, direction_now, smoothing
                #without the 'min', if there's more than one value it returns a list and this make crash 
later in
                #this code:  pp_ppt = peakPower / peakPowerT
                myR.run('peakPowerT=min(which(power == peakPower))') 
-               
+
                meanSpeed = myR.get('mean(abs(speed$y))')
                if direction_now == 1:
                        maxSpeed = myR.get('min(speed$y)')
@@ -545,7 +551,7 @@ if __name__ == '__main__':
 
                                if len(frames_pull_top1)>0 and len(frames_push_bottom1)>0:
                                        calculate_all_in_r(temp, frames_pull_top1, frames_push_bottom1, 
-                                                       direction_now, smoothingOne, eccon, minRange, isJump)
+                                                       direction_now, smoothingOneEC, smoothingOneC, eccon, 
minRange, isJump)
                                        
                                file.write(''+','.join([str(i) for i in temp[
                                        previous_frame_change:new_frame_change
diff --git a/encoder/pyserial_pyper_windows.py b/encoder/pyserial_pyper_windows.py
index 876d52c..11ca93c 100644
--- a/encoder/pyserial_pyper_windows.py
+++ b/encoder/pyserial_pyper_windows.py
@@ -51,21 +51,22 @@ record_time = int(sys.argv[3])*1000         #from s to ms
 minRange = int(sys.argv[4])                    #all is stored, but only display when vertical range is >= 
minRange
 isJump = sys.argv[5]
 mass = float(sys.argv[6])
-smoothingOne = float(sys.argv[7])
-eccon = sys.argv[8]                            #contraction "ec" or "c"
-heightHigherCondition = int(sys.argv[9])
-heightLowerCondition = int(sys.argv[10])
-meanSpeedHigherCondition = float(sys.argv[11])
-meanSpeedLowerCondition = float(sys.argv[12])
-maxSpeedHigherCondition = float(sys.argv[13])
-maxSpeedLowerCondition = float(sys.argv[14])
-powerHigherCondition = int(sys.argv[15])
-powerLowerCondition = int(sys.argv[16])
-peakPowerHigherCondition = int(sys.argv[17])
-peakPowerLowerCondition = int(sys.argv[18])
-mainVariable = sys.argv[19]
-w_serial_port = sys.argv[20]
-r_path = sys.argv[21]
+smoothingOneEC = float(sys.argv[7])
+smoothingOneC = float(sys.argv[8])
+eccon = sys.argv[9]                            #contraction "ec" or "c"
+heightHigherCondition = int(sys.argv[10])
+heightLowerCondition = int(sys.argv[11])
+meanSpeedHigherCondition = float(sys.argv[12])
+meanSpeedLowerCondition = float(sys.argv[13])
+maxSpeedHigherCondition = float(sys.argv[14])
+maxSpeedLowerCondition = float(sys.argv[15])
+powerHigherCondition = int(sys.argv[16])
+powerLowerCondition = int(sys.argv[17])
+peakPowerHigherCondition = int(sys.argv[18])
+peakPowerLowerCondition = int(sys.argv[19])
+mainVariable = sys.argv[20]
+w_serial_port = sys.argv[21]
+r_path = sys.argv[22]
 
 delete_initial_time = 20                       #delete first records because there's encoder bug
 #w_baudrate = 9600                           # Setting the baudrate of Chronopic(9600)
@@ -150,7 +151,8 @@ meanSpeedList = list()
 maxSpeedList = list()
 meanPowerList = list()
 peakPowerList = list()
-def calculate_all_in_r(temp, top_values, bottom_values, direction_now, smoothingOne, eccon, minRange, 
isJump):
+def calculate_all_in_r(temp, top_values, bottom_values, direction_now,
+               smoothingOneEC, smoothingOneC, eccon, minRange, isJump):
        if (len(top_values)>0 and len(bottom_values)>0):
                if direction_now == 1:
                        start=top_values[len(top_values)-1]
@@ -159,7 +161,11 @@ def calculate_all_in_r(temp, top_values, bottom_values, direction_now, smoothing
                        start=bottom_values[len(bottom_values)-1]
                        end=top_values[len(top_values)-1]
                
-               myR.assign('smoothingOne',smoothingOne)
+               if(eccon == "c")
+                       myR.assign('smoothingOne',smoothingOneC)
+               else
+                       myR.assign('smoothingOne',smoothingOneEC)
+
                myR.assign('a',temp[start:end])
                
                if direction_now == -1:
@@ -558,7 +564,7 @@ if __name__ == '__main__':
 
                                if len(frames_pull_top1)>0 and len(frames_push_bottom1)>0:
                                        calculate_all_in_r(temp, frames_pull_top1, frames_push_bottom1, 
-                                                       direction_now, smoothingOne, eccon, minRange, isJump)
+                                                       direction_now, smoothingOneEC, smoothingOneC, eccon, 
minRange, isJump)
                                        
                                file.write(''+','.join([str(i) for i in temp[
                                        previous_frame_change:new_frame_change
diff --git a/glade/chronojump.glade b/glade/chronojump.glade
index 2ae7bd7..3f24907 100644
--- a/glade/chronojump.glade
+++ b/glade/chronojump.glade
@@ -12008,14 +12008,14 @@ on current Chronojump version.</property>
                                                       <widget class="GtkHBox" id="hbox58">
                                                         <property name="visible">True</property>
                                                         <property name="can_focus">False</property>
-                                                        <property name="spacing">12</property>
+                                                        <property name="spacing">20</property>
                                                         <child>
                                                           <widget class="GtkTable" id="table10">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
                                                             <property name="n_rows">2</property>
                                                             <property name="n_columns">2</property>
-                                                            <property name="column_spacing">7</property>
+                                                            <property name="column_spacing">6</property>
                                                             <property name="row_spacing">6</property>
                                                             <child>
                                                             <widget class="GtkHBox" 
id="hbox_combo_encoder_exercise">
@@ -12030,48 +12030,12 @@ on current Chronojump version.</property>
                                                             </packing>
                                                             </child>
                                                             <child>
-                                                            <widget class="GtkHBox" id="hbox95">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <child>
-                                                            <widget class="GtkLabel" id="label90">
-                                                            <property name="can_focus">False</property>
-                                                            <property name="label" 
translatable="yes">Options: </property>
-                                                            </widget>
-                                                            <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">False</property>
-                                                            <property name="position">0</property>
-                                                            </packing>
-                                                            </child>
-                                                            <child>
-                                                            <widget class="GtkLabel" id="label82">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <property name="xalign">0</property>
-                                                            <property name="label" 
translatable="yes">Recording time</property>
-                                                            </widget>
-                                                            <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">False</property>
-                                                            <property name="pack_type">end</property>
-                                                            <property name="position">1</property>
-                                                            </packing>
-                                                            </child>
-                                                            </widget>
-                                                            <packing>
-                                                            <property name="top_attach">1</property>
-                                                            <property name="bottom_attach">2</property>
-                                                            <property name="x_options">GTK_FILL</property>
-                                                            </packing>
-                                                            </child>
-                                                            <child>
                                                             <widget class="GtkHBox" id="hbox96">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="spacing">4</property>
+                                                            <property name="spacing">6</property>
                                                             <child>
-                                                            <widget class="GtkSpinButton" 
id="spin_encoder_capture_time">
+                                                            <widget class="GtkSpinButton" 
id="spin_encoder_extra_weight">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">True</property>
                                                             <property name="invisible_char">●</property>
@@ -12080,28 +12044,27 @@ on current Chronojump version.</property>
                                                             <property 
name="secondary_icon_activatable">False</property>
                                                             <property 
name="primary_icon_sensitive">True</property>
                                                             <property 
name="secondary_icon_sensitive">True</property>
-                                                            <property name="adjustment">20 5 180 1 10 
0</property>
+                                                            <property name="adjustment">10 0 300 1 10 
0</property>
                                                             <property name="climb_rate">1</property>
                                                             <property name="snap_to_ticks">True</property>
                                                             <property name="numeric">True</property>
                                                             </widget>
                                                             <packing>
                                                             <property name="expand">False</property>
-                                                            <property name="fill">False</property>
+                                                            <property name="fill">True</property>
                                                             <property name="position">0</property>
                                                             </packing>
                                                             </child>
                                                             <child>
-                                                            <widget class="GtkLabel" id="label71">
+                                                            <widget class="GtkLabel" id="label89">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="xalign">0</property>
-                                                            <property name="label" 
translatable="yes">s</property>
+                                                            <property name="label" 
translatable="yes">Kg</property>
                                                             <property name="use_markup">True</property>
                                                             </widget>
                                                             <packing>
                                                             <property name="expand">False</property>
-                                                            <property name="fill">False</property>
+                                                            <property name="fill">True</property>
                                                             <property name="position">1</property>
                                                             </packing>
                                                             </child>
@@ -12171,33 +12134,75 @@ on current Chronojump version.</property>
                                                             <property name="x_options">GTK_FILL</property>
                                                             </packing>
                                                             </child>
+                                                            <child>
+                                                            <widget class="GtkLabel" id="label88">
+                                                            <property name="visible">True</property>
+                                                            <property name="can_focus">False</property>
+                                                            <property name="xalign">1</property>
+                                                            <property name="label" translatable="yes">Extra 
weight</property>
+                                                            <property name="use_markup">True</property>
+                                                            </widget>
+                                                            <packing>
+                                                            <property name="top_attach">1</property>
+                                                            <property name="bottom_attach">2</property>
+                                                            <property name="x_options">GTK_FILL</property>
+                                                            </packing>
+                                                            </child>
                                                           </widget>
                                                           <packing>
-                                                            <property name="expand">True</property>
+                                                            <property name="expand">False</property>
                                                             <property name="fill">True</property>
                                                             <property name="position">0</property>
                                                           </packing>
                                                         </child>
                                                         <child>
-                                                          <widget class="GtkTable" id="table11">
+                                                          <widget class="GtkVBox" id="vbox2">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="n_rows">2</property>
-                                                            <property name="n_columns">3</property>
-                                                            <property name="column_spacing">4</property>
-                                                            <property name="row_spacing">6</property>
+                                                            <property name="spacing">6</property>
                                                             <child>
-                                                            <widget class="GtkLabel" id="label88">
+                                                            <widget class="GtkHBox" 
id="hbox_combo_encoder_eccon">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="xalign">0</property>
-                                                            <property name="label" translatable="yes">Extra 
weight</property>
-                                                            <property name="use_markup">True</property>
+                                                            <child>
+                                                            <placeholder/>
+                                                            </child>
                                                             </widget>
                                                             <packing>
-                                                            <property name="x_options">GTK_FILL</property>
+                                                            <property name="expand">False</property>
+                                                            <property name="fill">True</property>
+                                                            <property name="position">0</property>
+                                                            </packing>
+                                                            </child>
+                                                            <child>
+                                                            <widget class="GtkHBox" 
id="hbox_combo_encoder_laterality">
+                                                            <property name="visible">True</property>
+                                                            <property name="can_focus">False</property>
+                                                            <child>
+                                                            <placeholder/>
+                                                            </child>
+                                                            </widget>
+                                                            <packing>
+                                                            <property name="expand">False</property>
+                                                            <property name="fill">True</property>
+                                                            <property name="position">1</property>
                                                             </packing>
                                                             </child>
+                                                          </widget>
+                                                          <packing>
+                                                            <property name="expand">False</property>
+                                                            <property name="fill">True</property>
+                                                            <property name="position">1</property>
+                                                          </packing>
+                                                        </child>
+                                                        <child>
+                                                          <widget class="GtkTable" id="table11">
+                                                            <property name="visible">True</property>
+                                                            <property name="can_focus">False</property>
+                                                            <property name="n_rows">2</property>
+                                                            <property name="n_columns">3</property>
+                                                            <property name="column_spacing">6</property>
+                                                            <property name="row_spacing">6</property>
                                                             <child>
                                                             <widget class="GtkLabel" id="label78">
                                                             <property name="visible">True</property>
@@ -12252,7 +12257,18 @@ on current Chronojump version.</property>
                                                             </packing>
                                                             </child>
                                                             <child>
-                                                            <widget class="GtkSpinButton" 
id="spin_encoder_extra_weight">
+                                                            <widget class="GtkLabel" id="label82">
+                                                            <property name="visible">True</property>
+                                                            <property name="can_focus">False</property>
+                                                            <property name="xalign">0</property>
+                                                            <property name="label" 
translatable="yes">Recording time</property>
+                                                            </widget>
+                                                            <packing>
+                                                            <property name="x_options">GTK_FILL</property>
+                                                            </packing>
+                                                            </child>
+                                                            <child>
+                                                            <widget class="GtkSpinButton" 
id="spin_encoder_capture_time">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">True</property>
                                                             <property name="invisible_char">●</property>
@@ -12261,7 +12277,7 @@ on current Chronojump version.</property>
                                                             <property 
name="secondary_icon_activatable">False</property>
                                                             <property 
name="primary_icon_sensitive">True</property>
                                                             <property 
name="secondary_icon_sensitive">True</property>
-                                                            <property name="adjustment">10 0 300 1 10 
0</property>
+                                                            <property name="adjustment">10 5 180 1 10 
0</property>
                                                             <property name="climb_rate">1</property>
                                                             <property name="snap_to_ticks">True</property>
                                                             <property name="numeric">True</property>
@@ -12269,82 +12285,75 @@ on current Chronojump version.</property>
                                                             <packing>
                                                             <property name="left_attach">1</property>
                                                             <property name="right_attach">2</property>
-                                                            <property name="x_options"/>
+                                                            <property name="x_options">GTK_FILL</property>
                                                             </packing>
                                                             </child>
                                                             <child>
-                                                            <widget class="GtkLabel" id="label89">
+                                                            <widget class="GtkLabel" id="label71">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="label" 
translatable="yes">Kg</property>
+                                                            <property name="xalign">0</property>
+                                                            <property name="label" 
translatable="yes">s</property>
                                                             <property name="use_markup">True</property>
                                                             </widget>
                                                             <packing>
                                                             <property name="left_attach">2</property>
                                                             <property name="right_attach">3</property>
-                                                            <property name="x_options"/>
+                                                            <property name="x_options">GTK_FILL</property>
                                                             </packing>
                                                             </child>
                                                           </widget>
                                                           <packing>
-                                                            <property name="expand">True</property>
+                                                            <property name="expand">False</property>
                                                             <property name="fill">True</property>
-                                                            <property name="position">1</property>
+                                                            <property name="position">2</property>
                                                           </packing>
                                                         </child>
                                                         <child>
-                                                          <widget class="GtkVBox" id="vbox2">
+                                                          <widget class="GtkVBox" id="vbox5">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
                                                             <property name="spacing">6</property>
                                                             <child>
-                                                            <widget class="GtkHBox" 
id="hbox_combo_encoder_eccon">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <child>
                                                             <placeholder/>
                                                             </child>
-                                                            </widget>
-                                                            <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">True</property>
-                                                            <property name="position">0</property>
-                                                            </packing>
-                                                            </child>
                                                             <child>
-                                                            <widget class="GtkHBox" id="hbox86">
+                                                            <widget class="GtkButton" 
id="button_encoder_bells">
+                                                            <property name="visible">True</property>
+                                                            <property name="can_focus">True</property>
+                                                            <property name="receives_default">True</property>
+                                                            <property name="has_tooltip">True</property>
+                                                            <property name="tooltip" 
translatable="yes">Bells</property>
+                                                            <property 
name="use_action_appearance">False</property>
+                                                            <signal name="clicked" 
handler="on_button_encoder_bells_clicked" swapped="no"/>
+                                                            <child>
+                                                            <widget class="GtkAlignment" id="alignment21">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="spacing">6</property>
+                                                            <property name="xscale">0</property>
+                                                            <property name="yscale">0</property>
                                                             <child>
-                                                            <widget class="GtkLabel" id="label85">
+                                                            <widget class="GtkHBox" id="hbox90">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="xalign">0</property>
-                                                            <property name="label" 
translatable="yes">Smoothing</property>
-                                                            <property name="use_markup">True</property>
+                                                            <property name="spacing">2</property>
+                                                            <child>
+                                                            <widget class="GtkImage" id="image_encoder_bell">
+                                                            <property name="visible">True</property>
+                                                            <property name="can_focus">False</property>
+                                                            <property name="icon-size">2</property>
                                                             </widget>
                                                             <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">False</property>
+                                                            <property name="expand">True</property>
+                                                            <property name="fill">True</property>
                                                             <property name="position">0</property>
                                                             </packing>
                                                             </child>
                                                             <child>
-                                                            <widget class="GtkSpinButton" 
id="spin_encoder_smooth">
+                                                            <widget class="GtkLabel" id="label86">
                                                             <property name="visible">True</property>
-                                                            <property name="can_focus">True</property>
-                                                            <property name="invisible_char">●</property>
-                                                            <property 
name="invisible_char_set">True</property>
-                                                            <property 
name="primary_icon_activatable">False</property>
-                                                            <property 
name="secondary_icon_activatable">False</property>
-                                                            <property 
name="primary_icon_sensitive">True</property>
-                                                            <property 
name="secondary_icon_sensitive">True</property>
-                                                            <property name="adjustment">0.69999999999999996 
0 1 0.01 0.10000000000000001 0</property>
-                                                            <property name="climb_rate">1</property>
-                                                            <property name="digits">2</property>
-                                                            <property name="snap_to_ticks">True</property>
-                                                            <property name="numeric">True</property>
+                                                            <property name="can_focus">False</property>
+                                                            <property name="use_underline">True</property>
                                                             </widget>
                                                             <packing>
                                                             <property name="expand">False</property>
@@ -12353,49 +12362,9 @@ on current Chronojump version.</property>
                                                             </packing>
                                                             </child>
                                                             </widget>
-                                                            <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">False</property>
-                                                            <property name="position">1</property>
-                                                            </packing>
-                                                            </child>
-                                                          </widget>
-                                                          <packing>
-                                                            <property name="expand">True</property>
-                                                            <property name="fill">True</property>
-                                                            <property name="position">2</property>
-                                                          </packing>
-                                                        </child>
-                                                        <child>
-                                                          <widget class="GtkVBox" id="vbox5">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <property name="spacing">6</property>
-                                                            <child>
-                                                            <widget class="GtkHBox" 
id="hbox_combo_encoder_laterality">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <child>
-                                                            <placeholder/>
                                                             </child>
                                                             </widget>
-                                                            <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">True</property>
-                                                            <property name="position">0</property>
-                                                            </packing>
                                                             </child>
-                                                            <child>
-                                                            <widget class="GtkCheckButton" 
id="checkbutton_encoder_capture_propulsive">
-                                                            <property name="label" 
translatable="yes">Propulsive</property>
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">True</property>
-                                                            <property 
name="receives_default">False</property>
-                                                            <property name="has_tooltip">True</property>
-                                                            <property name="tooltip" translatable="yes">On 
concentric evaluate only propulsive phase</property>
-                                                            <property 
name="use_action_appearance">False</property>
-                                                            <property name="active">True</property>
-                                                            <property name="draw_indicator">True</property>
                                                             </widget>
                                                             <packing>
                                                             <property name="expand">False</property>
@@ -12405,7 +12374,7 @@ on current Chronojump version.</property>
                                                             </child>
                                                           </widget>
                                                           <packing>
-                                                            <property name="expand">True</property>
+                                                            <property name="expand">False</property>
                                                             <property name="fill">True</property>
                                                             <property name="position">3</property>
                                                           </packing>
@@ -12460,30 +12429,10 @@ on current Chronojump version.</property>
                                                             <property name="can_focus">False</property>
                                                             <property name="spacing">4</property>
                                                             <child>
-                                                            <widget class="GtkButton" 
id="button_encoder_bells">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">True</property>
-                                                            <property name="receives_default">True</property>
-                                                            <property name="has_tooltip">True</property>
-                                                            <property name="tooltip" 
translatable="yes">Bells</property>
-                                                            <property 
name="use_action_appearance">False</property>
-                                                            <signal name="clicked" 
handler="on_button_encoder_bells_clicked" swapped="no"/>
-                                                            <child>
-                                                            <widget class="GtkAlignment" id="alignment21">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <property name="xscale">0</property>
-                                                            <property name="yscale">0</property>
-                                                            <child>
-                                                            <widget class="GtkHBox" id="hbox90">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <property name="spacing">2</property>
-                                                            <child>
-                                                            <widget class="GtkImage" id="image_encoder_bell">
+                                                            <widget class="GtkLabel" id="label113">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">False</property>
-                                                            <property name="icon-size">2</property>
+                                                            <property name="label">Capture:</property>
                                                             </widget>
                                                             <packing>
                                                             <property name="expand">True</property>
@@ -12492,41 +12441,6 @@ on current Chronojump version.</property>
                                                             </packing>
                                                             </child>
                                                             <child>
-                                                            <widget class="GtkLabel" id="label86">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <property name="use_underline">True</property>
-                                                            </widget>
-                                                            <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">False</property>
-                                                            <property name="position">1</property>
-                                                            </packing>
-                                                            </child>
-                                                            </widget>
-                                                            </child>
-                                                            </widget>
-                                                            </child>
-                                                            </widget>
-                                                            <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">False</property>
-                                                            <property name="position">0</property>
-                                                            </packing>
-                                                            </child>
-                                                            <child>
-                                                            <widget class="GtkLabel" id="label113">
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">False</property>
-                                                            <property name="label">Capture:</property>
-                                                            </widget>
-                                                            <packing>
-                                                            <property name="expand">True</property>
-                                                            <property name="fill">True</property>
-                                                            <property name="position">1</property>
-                                                            </packing>
-                                                            </child>
-                                                            <child>
                                                             <widget class="GtkButton" 
id="button_encoder_capture">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">True</property>
@@ -12547,7 +12461,7 @@ on current Chronojump version.</property>
                                                             <packing>
                                                             <property name="expand">True</property>
                                                             <property name="fill">False</property>
-                                                            <property name="position">2</property>
+                                                            <property name="position">1</property>
                                                             </packing>
                                                             </child>
                                                             <child>
@@ -12571,7 +12485,7 @@ on current Chronojump version.</property>
                                                             <packing>
                                                             <property name="expand">True</property>
                                                             <property name="fill">False</property>
-                                                            <property name="position">3</property>
+                                                            <property name="position">2</property>
                                                             </packing>
                                                             </child>
                                                             <child>
@@ -12593,7 +12507,7 @@ on current Chronojump version.</property>
                                                             <packing>
                                                             <property name="expand">True</property>
                                                             <property name="fill">True</property>
-                                                            <property name="position">4</property>
+                                                            <property name="position">3</property>
                                                             </packing>
                                                             </child>
                                                             </widget>
@@ -12876,7 +12790,7 @@ on current Chronojump version.</property>
                                                         <property name="visible">True</property>
                                                         <property name="can_focus">False</property>
                                                         <child>
-                                                          <widget class="GtkSpinButton" 
id="spin_encoder_capture_height">
+                                                          <widget class="GtkSpinButton" 
id="spin_encoder_capture_curves_height_range">
                                                             <property name="visible">True</property>
                                                             <property name="can_focus">True</property>
                                                             <property name="has_tooltip">True</property>
@@ -13583,24 +13497,6 @@ on current Chronojump version.</property>
                                                           </packing>
                                                         </child>
                                                         <child>
-                                                          <widget class="GtkCheckButton" 
id="checkbutton_encoder_analyze_propulsive">
-                                                            <property name="label" 
translatable="yes">P.</property>
-                                                            <property name="visible">True</property>
-                                                            <property name="can_focus">True</property>
-                                                            <property 
name="receives_default">False</property>
-                                                            <property name="has_tooltip">True</property>
-                                                            <property name="tooltip" translatable="yes">On 
concentric evaluate only propulsive phase</property>
-                                                            <property 
name="use_action_appearance">False</property>
-                                                            <property name="active">True</property>
-                                                            <property name="draw_indicator">True</property>
-                                                          </widget>
-                                                          <packing>
-                                                            <property name="expand">False</property>
-                                                            <property name="fill">False</property>
-                                                            <property name="position">1</property>
-                                                          </packing>
-                                                        </child>
-                                                        <child>
                                                           <widget class="GtkHBox" 
id="hbox_encoder_analyze_curve_num">
                                                             <property name="can_focus">False</property>
                                                             <property name="spacing">6</property>
@@ -13634,7 +13530,7 @@ on current Chronojump version.</property>
                                                           <packing>
                                                             <property name="expand">False</property>
                                                             <property name="fill">False</property>
-                                                            <property name="position">2</property>
+                                                            <property name="position">1</property>
                                                           </packing>
                                                         </child>
                                                         <child>
@@ -13647,7 +13543,7 @@ on current Chronojump version.</property>
                                                           <packing>
                                                             <property name="expand">False</property>
                                                             <property name="fill">False</property>
-                                                            <property name="position">3</property>
+                                                            <property name="position">2</property>
                                                           </packing>
                                                         </child>
                                                         <child>
@@ -13694,7 +13590,7 @@ on current Chronojump version.</property>
                                                           <packing>
                                                             <property name="expand">False</property>
                                                             <property name="fill">False</property>
-                                                            <property name="position">4</property>
+                                                            <property name="position">3</property>
                                                           </packing>
                                                         </child>
                                                         <child>
@@ -13707,7 +13603,7 @@ on current Chronojump version.</property>
                                                           <packing>
                                                             <property name="expand">False</property>
                                                             <property name="fill">False</property>
-                                                            <property name="position">5</property>
+                                                            <property name="position">4</property>
                                                           </packing>
                                                         </child>
                                                       </widget>
@@ -24392,6 +24288,7 @@ options</property>
     </child>
   </widget>
   <widget class="GtkWindow" id="preferences">
+    <property name="height_request">450</property>
     <property name="visible">True</property>
     <property name="can_focus">False</property>
     <property name="border_width">10</property>
@@ -24410,6 +24307,8 @@ options</property>
             <property name="visible">True</property>
             <property name="can_focus">True</property>
             <property name="border_width">6</property>
+            <property name="tab_hborder">10</property>
+            <property name="tab_vborder">4</property>
             <child>
               <widget class="GtkVBox" id="vbox142">
                 <property name="visible">True</property>
@@ -24461,7 +24360,6 @@ options</property>
                             <property name="visible">True</property>
                             <property name="can_focus">True</property>
                             <property name="receives_default">False</property>
-                            <property name="tooltip" translatable="yes">Make a copy of the 
database</property>
                             <property name="use_action_appearance">False</property>
                             <property name="use_underline">True</property>
                             <signal name="clicked" handler="on_button_db_folder_open_clicked" swapped="no"/>
@@ -24500,7 +24398,7 @@ options</property>
                     </child>
                   </widget>
                   <packing>
-                    <property name="expand">True</property>
+                    <property name="expand">False</property>
                     <property name="fill">True</property>
                     <property name="position">0</property>
                   </packing>
@@ -24548,7 +24446,7 @@ options</property>
                     </child>
                   </widget>
                   <packing>
-                    <property name="expand">True</property>
+                    <property name="expand">False</property>
                     <property name="fill">True</property>
                     <property name="position">1</property>
                   </packing>
@@ -24567,335 +24465,450 @@ options</property>
               </packing>
             </child>
             <child>
-              <widget class="GtkVBox" id="vbox122">
+              <widget class="GtkVBox" id="vbox1">
                 <property name="visible">True</property>
                 <property name="can_focus">False</property>
-                <property name="border_width">7</property>
-                <property name="spacing">6</property>
-                <child>
-                  <widget class="GtkCheckButton" id="checkbutton_height">
-                    <property name="label" translatable="yes">Show height</property>
-                    <property name="visible">True</property>
-                    <property name="can_focus">True</property>
-                    <property name="receives_default">False</property>
-                    <property name="use_action_appearance">False</property>
-                    <property name="use_underline">True</property>
-                    <property name="draw_indicator">True</property>
-                  </widget>
-                  <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">False</property>
-                    <property name="position">0</property>
-                  </packing>
-                </child>
-                <child>
-                  <widget class="GtkCheckButton" id="checkbutton_power">
-                    <property name="label" translatable="yes">Show power</property>
-                    <property name="visible">True</property>
-                    <property name="can_focus">True</property>
-                    <property name="receives_default">False</property>
-                    <property name="use_action_appearance">False</property>
-                    <property name="use_underline">True</property>
-                    <property name="draw_indicator">True</property>
-                    <signal name="clicked" handler="on_checkbutton_power_clicked" swapped="no"/>
-                  </widget>
-                  <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">False</property>
-                    <property name="position">1</property>
-                  </packing>
-                </child>
-                <child>
-                  <widget class="GtkAlignment" id="alignment1">
-                    <property name="visible">True</property>
-                    <property name="can_focus">False</property>
-                    <property name="left_padding">12</property>
-                    <child>
-                      <widget class="GtkTextView" id="textview_power">
-                        <property name="width_request">300</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="editable">False</property>
-                        <property name="wrap_mode">word</property>
-                        <property name="left_margin">4</property>
-                        <property name="cursor_visible">False</property>
-                        <property name="text" translatable="yes">On jumps results tab, power is calculated 
depending on jump type:
-
-Jumps with TC &amp; TF: Bosco Relative Power (W/Kg)
-P = 24.6 * (Total time + Flight time) / Contact time
-
-Jumps without TC: Lewis Peak Power 1974 (W)
-P = SQRT(4.9) * 9.8 * (body weight+extra weight) * SQRT(jump height in meters)
-
-If you want to use other formulas, go to Statistics.</property>
-                      </widget>
-                    </child>
-                  </widget>
-                  <packing>
-                    <property name="expand">True</property>
-                    <property name="fill">True</property>
-                    <property name="padding">2</property>
-                    <property name="position">2</property>
-                  </packing>
-                </child>
-                <child>
-                  <widget class="GtkCheckButton" id="checkbutton_initial_speed">
-                    <property name="label" translatable="yes">Show initial speed</property>
-                    <property name="visible">True</property>
-                    <property name="can_focus">True</property>
-                    <property name="receives_default">False</property>
-                    <property name="use_action_appearance">False</property>
-                    <property name="use_underline">True</property>
-                    <property name="draw_indicator">True</property>
-                  </widget>
-                  <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">False</property>
-                    <property name="position">3</property>
-                  </packing>
-                </child>
-                <child>
-                  <widget class="GtkCheckButton" id="checkbutton_angle">
-                    <property name="label" translatable="yes">Show knee angle</property>
-                    <property name="visible">True</property>
-                    <property name="can_focus">True</property>
-                    <property name="receives_default">False</property>
-                    <property name="use_action_appearance">False</property>
-                    <property name="use_underline">True</property>
-                    <property name="draw_indicator">True</property>
-                  </widget>
-                  <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">False</property>
-                    <property name="position">4</property>
-                  </packing>
-                </child>
+                <property name="spacing">20</property>
                 <child>
-                  <widget class="GtkCheckButton" id="checkbutton_show_tv_tc_index">
-                    <property name="label" translatable="yes">Show indexes between TF and TC</property>
+                  <widget class="GtkScrolledWindow" id="scrolledwindow1">
                     <property name="visible">True</property>
                     <property name="can_focus">True</property>
-                    <property name="receives_default">False</property>
-                    <property name="use_action_appearance">False</property>
-                    <property name="use_underline">True</property>
-                    <property name="draw_indicator">True</property>
-                    <signal name="clicked" handler="on_checkbutton_show_tv_tc_index_clicked" swapped="no"/>
-                  </widget>
-                  <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">False</property>
-                    <property name="position">5</property>
-                  </packing>
-                </child>
-                <child>
-                  <widget class="GtkHBox" id="hbox_indexes">
-                    <property name="visible">True</property>
-                    <property name="can_focus">False</property>
-                    <property name="spacing">6</property>
-                    <child>
-                      <widget class="GtkRadioButton" id="radiobutton_show_q_index">
-                        <property name="label" translatable="yes">QIndex</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="use_underline">True</property>
-                        <property name="active">True</property>
-                        <property name="draw_indicator">True</property>
-                      </widget>
-                      <packing>
-                        <property name="expand">False</property>
-                        <property name="fill">False</property>
-                        <property name="padding">12</property>
-                        <property name="position">0</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkRadioButton" id="radiobutton_show_dj_index">
-                        <property name="label" translatable="yes">DjIndex</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="use_underline">True</property>
-                        <property name="draw_indicator">True</property>
-                        <property name="group">radiobutton_show_q_index</property>
-                      </widget>
-                      <packing>
-                        <property name="expand">False</property>
-                        <property name="fill">False</property>
-                        <property name="position">1</property>
-                      </packing>
-                    </child>
-                  </widget>
-                  <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">True</property>
-                    <property name="position">6</property>
-                  </packing>
-                </child>
-                <child>
-                  <widget class="GtkTable" id="table1">
-                    <property name="visible">True</property>
-                    <property name="can_focus">False</property>
-                    <property name="n_rows">3</property>
-                    <property name="n_columns">3</property>
-                    <property name="column_spacing">6</property>
-                    <property name="row_spacing">6</property>
-                    <child>
-                      <widget class="GtkLabel" id="label2">
-                        <property name="visible">True</property>
-                        <property name="can_focus">False</property>
-                        <property name="xalign">0</property>
-                        <property name="label" translatable="yes">On statistics
-show elevation as:</property>
-                      </widget>
-                      <packing>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkLabel" id="label3">
-                        <property name="visible">True</property>
-                        <property name="can_focus">False</property>
-                        <property name="xalign">0</property>
-                        <property name="label" translatable="yes">Speed units:</property>
-                      </widget>
-                      <packing>
-                        <property name="top_attach">1</property>
-                        <property name="bottom_attach">2</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
+                    <property name="border_width">4</property>
+                    <property name="hscrollbar_policy">never</property>
+                    <property name="vscrollbar_policy">automatic</property>
                     <child>
-                      <widget class="GtkLabel" id="label5">
+                      <widget class="GtkViewport" id="viewport1">
                         <property name="visible">True</property>
                         <property name="can_focus">False</property>
-                        <property name="xalign">0</property>
-                        <property name="label" translatable="yes">Weight units:</property>
-                      </widget>
-                      <packing>
-                        <property name="top_attach">2</property>
-                        <property name="bottom_attach">3</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkRadioButton" id="radio_elevation_height">
-                        <property name="label" translatable="yes">Height (cm)</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="xalign">0</property>
-                        <property name="active">True</property>
-                        <property name="draw_indicator">True</property>
-                      </widget>
-                      <packing>
-                        <property name="left_attach">1</property>
-                        <property name="right_attach">2</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkRadioButton" id="radio_elevation_tf">
-                        <property name="label">TF (s)</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="xalign">0</property>
-                        <property name="draw_indicator">True</property>
-                        <property name="group">radio_elevation_height</property>
-                      </widget>
-                      <packing>
-                        <property name="left_attach">2</property>
-                        <property name="right_attach">3</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkRadioButton" id="radio_speed_ms">
-                        <property name="label">m/s</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="xalign">0</property>
-                        <property name="active">True</property>
-                        <property name="draw_indicator">True</property>
-                      </widget>
-                      <packing>
-                        <property name="left_attach">1</property>
-                        <property name="right_attach">2</property>
-                        <property name="top_attach">1</property>
-                        <property name="bottom_attach">2</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkRadioButton" id="radio_speed_km">
-                        <property name="label">Km/h</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="xalign">0</property>
-                        <property name="draw_indicator">True</property>
-                        <property name="group">radio_speed_ms</property>
-                      </widget>
-                      <packing>
-                        <property name="left_attach">2</property>
-                        <property name="right_attach">3</property>
-                        <property name="top_attach">1</property>
-                        <property name="bottom_attach">2</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkRadioButton" id="radio_weight_percent">
-                        <property name="label">%</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="xalign">0</property>
-                        <property name="active">True</property>
-                        <property name="draw_indicator">True</property>
-                      </widget>
-                      <packing>
-                        <property name="left_attach">1</property>
-                        <property name="right_attach">2</property>
-                        <property name="top_attach">2</property>
-                        <property name="bottom_attach">3</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
-                    </child>
-                    <child>
-                      <widget class="GtkRadioButton" id="radio_weight_kg">
-                        <property name="label">Kg</property>
-                        <property name="visible">True</property>
-                        <property name="can_focus">True</property>
-                        <property name="receives_default">False</property>
-                        <property name="use_action_appearance">False</property>
-                        <property name="xalign">0</property>
-                        <property name="draw_indicator">True</property>
-                        <property name="group">radio_weight_percent</property>
+                        <child>
+                          <widget class="GtkVBox" id="vbox3">
+                            <property name="visible">True</property>
+                            <property name="can_focus">False</property>
+                            <property name="border_width">8</property>
+                            <property name="spacing">12</property>
+                            <child>
+                              <widget class="GtkVBox" id="vbox2">
+                                <property name="visible">True</property>
+                                <property name="can_focus">False</property>
+                                <property name="spacing">8</property>
+                                <child>
+                                  <widget class="GtkHBox" id="hbox87">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="spacing">6</property>
+                                    <child>
+                                      <widget class="GtkLabel" id="label38">
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="label" translatable="yes">Decimal number</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">False</property>
+                                        <property name="position">0</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkComboBox" id="combo_decimals">
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">False</property>
+                                        <property name="items">1
+2
+3</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">False</property>
+                                        <property name="position">1</property>
+                                      </packing>
+                                    </child>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="position">0</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkCheckButton" id="checkbutton_ask_deletion">
+                                    <property name="label" translatable="yes">Ask for confirm test 
deletion</property>
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">True</property>
+                                    <property name="receives_default">False</property>
+                                    <property name="has_tooltip">True</property>
+                                    <property name="tooltip" translatable="yes">Ask user if really wants to 
delete a test</property>
+                                    <property name="use_action_appearance">False</property>
+                                    <property name="use_underline">True</property>
+                                    <property name="active">True</property>
+                                    <property name="draw_indicator">True</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="position">1</property>
+                                  </packing>
+                                </child>
+                              </widget>
+                              <packing>
+                                <property name="expand">False</property>
+                                <property name="fill">False</property>
+                                <property name="position">0</property>
+                              </packing>
+                            </child>
+                            <child>
+                              <widget class="GtkHSeparator" id="hseparator1">
+                                <property name="visible">True</property>
+                                <property name="can_focus">False</property>
+                              </widget>
+                              <packing>
+                                <property name="expand">False</property>
+                                <property name="fill">True</property>
+                                <property name="position">1</property>
+                              </packing>
+                            </child>
+                            <child>
+                              <widget class="GtkVBox" id="vbox122">
+                                <property name="visible">True</property>
+                                <property name="can_focus">False</property>
+                                <property name="spacing">8</property>
+                                <child>
+                                  <widget class="GtkCheckButton" id="checkbutton_height">
+                                    <property name="label" translatable="yes">Show height</property>
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">True</property>
+                                    <property name="receives_default">False</property>
+                                    <property name="use_action_appearance">False</property>
+                                    <property name="use_underline">True</property>
+                                    <property name="draw_indicator">True</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="position">0</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkHBox" id="hbox1">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="spacing">8</property>
+                                    <child>
+                                      <widget class="GtkCheckButton" id="checkbutton_power">
+                                        <property name="label" translatable="yes">Show power</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="use_underline">True</property>
+                                        <property name="draw_indicator">True</property>
+                                        <signal name="clicked" handler="on_checkbutton_power_clicked" 
swapped="no"/>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">False</property>
+                                        <property name="position">0</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkButton" id="button_help_power">
+                                        <property name="label">gtk-help</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">True</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="use_stock">True</property>
+                                        <signal name="clicked" handler="on_button_help_power_clicked" 
swapped="no"/>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">True</property>
+                                        <property name="position">1</property>
+                                      </packing>
+                                    </child>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="position">1</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkCheckButton" id="checkbutton_initial_speed">
+                                    <property name="label" translatable="yes">Show initial speed</property>
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">True</property>
+                                    <property name="receives_default">False</property>
+                                    <property name="use_action_appearance">False</property>
+                                    <property name="use_underline">True</property>
+                                    <property name="draw_indicator">True</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="position">2</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkCheckButton" id="checkbutton_angle">
+                                    <property name="label" translatable="yes">Show knee angle</property>
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">True</property>
+                                    <property name="receives_default">False</property>
+                                    <property name="use_action_appearance">False</property>
+                                    <property name="use_underline">True</property>
+                                    <property name="draw_indicator">True</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="position">3</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkCheckButton" id="checkbutton_show_tv_tc_index">
+                                    <property name="label" translatable="yes">Show indexes between TF and 
TC</property>
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">True</property>
+                                    <property name="receives_default">False</property>
+                                    <property name="use_action_appearance">False</property>
+                                    <property name="use_underline">True</property>
+                                    <property name="draw_indicator">True</property>
+                                    <signal name="clicked" handler="on_checkbutton_show_tv_tc_index_clicked" 
swapped="no"/>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="position">4</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkHBox" id="hbox_indexes">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="spacing">6</property>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radiobutton_show_q_index">
+                                        <property name="label" translatable="yes">QIndex</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="use_underline">True</property>
+                                        <property name="active">True</property>
+                                        <property name="draw_indicator">True</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">False</property>
+                                        <property name="padding">12</property>
+                                        <property name="position">0</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radiobutton_show_dj_index">
+                                        <property name="label" translatable="yes">DjIndex</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="use_underline">True</property>
+                                        <property name="draw_indicator">True</property>
+                                        <property name="group">radiobutton_show_q_index</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">False</property>
+                                        <property name="position">1</property>
+                                      </packing>
+                                    </child>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">True</property>
+                                    <property name="position">5</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkTable" id="table1">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="n_rows">3</property>
+                                    <property name="n_columns">3</property>
+                                    <property name="column_spacing">6</property>
+                                    <property name="row_spacing">6</property>
+                                    <child>
+                                      <widget class="GtkLabel" id="label2">
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="label" translatable="yes">On statistics
+show elevation as:</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkLabel" id="label3">
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="label" translatable="yes">Speed units:</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="top_attach">1</property>
+                                        <property name="bottom_attach">2</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkLabel" id="label5">
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="label" translatable="yes">Weight units:</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="top_attach">2</property>
+                                        <property name="bottom_attach">3</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radio_elevation_height">
+                                        <property name="label" translatable="yes">Height (cm)</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="active">True</property>
+                                        <property name="draw_indicator">True</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="left_attach">1</property>
+                                        <property name="right_attach">2</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radio_elevation_tf">
+                                        <property name="label">TF (s)</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="draw_indicator">True</property>
+                                        <property name="group">radio_elevation_height</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="left_attach">2</property>
+                                        <property name="right_attach">3</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radio_speed_ms">
+                                        <property name="label">m/s</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="active">True</property>
+                                        <property name="draw_indicator">True</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="left_attach">1</property>
+                                        <property name="right_attach">2</property>
+                                        <property name="top_attach">1</property>
+                                        <property name="bottom_attach">2</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radio_speed_km">
+                                        <property name="label">Km/h</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="draw_indicator">True</property>
+                                        <property name="group">radio_speed_ms</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="left_attach">2</property>
+                                        <property name="right_attach">3</property>
+                                        <property name="top_attach">1</property>
+                                        <property name="bottom_attach">2</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radio_weight_percent">
+                                        <property name="label">%</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="active">True</property>
+                                        <property name="draw_indicator">True</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="left_attach">1</property>
+                                        <property name="right_attach">2</property>
+                                        <property name="top_attach">2</property>
+                                        <property name="bottom_attach">3</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkRadioButton" id="radio_weight_kg">
+                                        <property name="label">Kg</property>
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">True</property>
+                                        <property name="receives_default">False</property>
+                                        <property name="use_action_appearance">False</property>
+                                        <property name="xalign">0</property>
+                                        <property name="draw_indicator">True</property>
+                                        <property name="group">radio_weight_percent</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="left_attach">2</property>
+                                        <property name="right_attach">3</property>
+                                        <property name="top_attach">2</property>
+                                        <property name="bottom_attach">3</property>
+                                        <property name="x_options">GTK_FILL</property>
+                                      </packing>
+                                    </child>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">False</property>
+                                    <property name="padding">2</property>
+                                    <property name="position">6</property>
+                                  </packing>
+                                </child>
+                              </widget>
+                              <packing>
+                                <property name="expand">False</property>
+                                <property name="fill">False</property>
+                                <property name="position">2</property>
+                              </packing>
+                            </child>
+                          </widget>
+                        </child>
                       </widget>
-                      <packing>
-                        <property name="left_attach">2</property>
-                        <property name="right_attach">3</property>
-                        <property name="top_attach">2</property>
-                        <property name="bottom_attach">3</property>
-                        <property name="x_options">GTK_FILL</property>
-                      </packing>
                     </child>
                   </widget>
                   <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">False</property>
-                    <property name="padding">2</property>
-                    <property name="position">7</property>
+                    <property name="expand">True</property>
+                    <property name="fill">True</property>
+                    <property name="position">0</property>
                   </packing>
                 </child>
               </widget>
@@ -24907,7 +24920,7 @@ show elevation as:</property>
               <widget class="GtkLabel" id="label4">
                 <property name="visible">True</property>
                 <property name="can_focus">False</property>
-                <property name="label" translatable="yes">Show</property>
+                <property name="label" translatable="yes">Contacts</property>
               </widget>
               <packing>
                 <property name="position">1</property>
@@ -24920,61 +24933,207 @@ show elevation as:</property>
                 <property name="visible">True</property>
                 <property name="can_focus">False</property>
                 <property name="border_width">8</property>
-                <property name="spacing">6</property>
+                <property name="spacing">12</property>
+                <child>
+                  <widget class="GtkCheckButton" id="checkbutton_encoder_propulsive">
+                    <property name="label" translatable="yes">Propulsive</property>
+                    <property name="visible">True</property>
+                    <property name="can_focus">True</property>
+                    <property name="receives_default">False</property>
+                    <property name="has_tooltip">True</property>
+                    <property name="tooltip" translatable="yes">On concentric evaluate only propulsive 
phase</property>
+                    <property name="use_action_appearance">False</property>
+                    <property name="active">True</property>
+                    <property name="draw_indicator">True</property>
+                  </widget>
+                  <packing>
+                    <property name="expand">False</property>
+                    <property name="fill">False</property>
+                    <property name="position">0</property>
+                  </packing>
+                </child>
                 <child>
-                  <widget class="GtkHBox" id="hbox87">
+                  <widget class="GtkFrame" id="frame1">
                     <property name="visible">True</property>
                     <property name="can_focus">False</property>
-                    <property name="spacing">6</property>
+                    <property name="label_xalign">0</property>
+                    <property name="label_yalign">0.69999998807907104</property>
+                    <property name="shadow_type">out</property>
                     <child>
-                      <widget class="GtkLabel" id="label38">
+                      <widget class="GtkAlignment" id="alignment1">
                         <property name="visible">True</property>
                         <property name="can_focus">False</property>
-                        <property name="xalign">0</property>
-                        <property name="label" translatable="yes">Decimal number</property>
+                        <property name="left_padding">12</property>
+                        <child>
+                          <widget class="GtkVBox" id="vbox4">
+                            <property name="visible">True</property>
+                            <property name="can_focus">False</property>
+                            <property name="border_width">8</property>
+                            <property name="spacing">12</property>
+                            <child>
+                              <widget class="GtkTable" id="table2">
+                                <property name="visible">True</property>
+                                <property name="can_focus">False</property>
+                                <property name="n_rows">2</property>
+                                <property name="n_columns">2</property>
+                                <property name="column_spacing">10</property>
+                                <property name="row_spacing">8</property>
+                                <child>
+                                  <widget class="GtkSpinButton" id="spin_encoder_smooth_ecc_con">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">True</property>
+                                    <property name="invisible_char">●</property>
+                                    <property name="invisible_char_set">True</property>
+                                    <property name="primary_icon_activatable">False</property>
+                                    <property name="secondary_icon_activatable">False</property>
+                                    <property name="primary_icon_sensitive">True</property>
+                                    <property name="secondary_icon_sensitive">True</property>
+                                    <property name="adjustment">0.59999999999999998 0 1 0.01 
0.10000000000000001 0</property>
+                                    <property name="climb_rate">1</property>
+                                    <property name="digits">2</property>
+                                    <property name="snap_to_ticks">True</property>
+                                    <property name="numeric">True</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="left_attach">1</property>
+                                    <property name="right_attach">2</property>
+                                    <property name="x_options">GTK_FILL</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkSpinButton" id="spin_encoder_smooth_con">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">True</property>
+                                    <property name="invisible_char">●</property>
+                                    <property name="invisible_char_set">True</property>
+                                    <property name="primary_icon_activatable">False</property>
+                                    <property name="secondary_icon_activatable">False</property>
+                                    <property name="primary_icon_sensitive">True</property>
+                                    <property name="secondary_icon_sensitive">True</property>
+                                    <property name="adjustment">0.69999999999999996 0 1 0.01 
0.10000000000000001 0</property>
+                                    <property name="climb_rate">1</property>
+                                    <property name="digits">2</property>
+                                    <property name="snap_to_ticks">True</property>
+                                    <property name="numeric">True</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="left_attach">1</property>
+                                    <property name="right_attach">2</property>
+                                    <property name="top_attach">1</property>
+                                    <property name="bottom_attach">2</property>
+                                    <property name="x_options">GTK_FILL</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkLabel" id="label7">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="xalign">0</property>
+                                    <property name="label" translatable="yes">Eccentric-concentric</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="x_options">GTK_FILL</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkLabel" id="label8">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="xalign">0</property>
+                                    <property name="label" translatable="yes">Concentric</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="top_attach">1</property>
+                                    <property name="bottom_attach">2</property>
+                                    <property name="x_options">GTK_FILL</property>
+                                  </packing>
+                                </child>
+                              </widget>
+                              <packing>
+                                <property name="expand">False</property>
+                                <property name="fill">True</property>
+                                <property name="position">0</property>
+                              </packing>
+                            </child>
+                            <child>
+                              <widget class="GtkHBox" id="hbox4">
+                                <property name="visible">True</property>
+                                <property name="can_focus">False</property>
+                                <property name="spacing">12</property>
+                                <child>
+                                  <widget class="GtkLabel" id="label13">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="label" translatable="yes">Recommended values:</property>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">True</property>
+                                    <property name="position">0</property>
+                                  </packing>
+                                </child>
+                                <child>
+                                  <widget class="GtkHBox" id="hbox5">
+                                    <property name="visible">True</property>
+                                    <property name="can_focus">False</property>
+                                    <property name="spacing">8</property>
+                                    <child>
+                                      <widget class="GtkLabel" id="label10">
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">False</property>
+                                        <property name="label" translatable="yes">0.6</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">True</property>
+                                        <property name="position">0</property>
+                                      </packing>
+                                    </child>
+                                    <child>
+                                      <widget class="GtkLabel" id="label12">
+                                        <property name="visible">True</property>
+                                        <property name="can_focus">False</property>
+                                        <property name="label" translatable="yes">0.7</property>
+                                      </widget>
+                                      <packing>
+                                        <property name="expand">False</property>
+                                        <property name="fill">True</property>
+                                        <property name="position">1</property>
+                                      </packing>
+                                    </child>
+                                  </widget>
+                                  <packing>
+                                    <property name="expand">False</property>
+                                    <property name="fill">True</property>
+                                    <property name="position">1</property>
+                                  </packing>
+                                </child>
+                              </widget>
+                              <packing>
+                                <property name="expand">True</property>
+                                <property name="fill">True</property>
+                                <property name="position">1</property>
+                              </packing>
+                            </child>
+                          </widget>
+                        </child>
                       </widget>
-                      <packing>
-                        <property name="expand">False</property>
-                        <property name="fill">False</property>
-                        <property name="position">0</property>
-                      </packing>
                     </child>
                     <child>
-                      <widget class="GtkComboBox" id="combo_decimals">
+                      <widget class="GtkLabel" id="label1">
                         <property name="visible">True</property>
                         <property name="can_focus">False</property>
-                        <property name="items">1
-2
-3</property>
+                        <property name="label" translatable="yes">Smoothing</property>
+                        <property name="use_markup">True</property>
                       </widget>
                       <packing>
-                        <property name="expand">False</property>
-                        <property name="fill">False</property>
-                        <property name="position">1</property>
+                        <property name="type">label_item</property>
                       </packing>
                     </child>
                   </widget>
                   <packing>
                     <property name="expand">False</property>
                     <property name="fill">True</property>
-                    <property name="position">0</property>
-                  </packing>
-                </child>
-                <child>
-                  <widget class="GtkCheckButton" id="checkbutton_ask_deletion">
-                    <property name="label" translatable="yes">Ask for confirm test deletion</property>
-                    <property name="visible">True</property>
-                    <property name="can_focus">True</property>
-                    <property name="receives_default">False</property>
-                    <property name="tooltip" translatable="yes">Ask user if really wants to delete a 
test</property>
-                    <property name="use_action_appearance">False</property>
-                    <property name="use_underline">True</property>
-                    <property name="active">True</property>
-                    <property name="draw_indicator">True</property>
-                  </widget>
-                  <packing>
-                    <property name="expand">False</property>
-                    <property name="fill">False</property>
                     <property name="position">1</property>
                   </packing>
                 </child>
@@ -24987,7 +25146,7 @@ show elevation as:</property>
               <widget class="GtkLabel" id="label6">
                 <property name="visible">True</property>
                 <property name="can_focus">False</property>
-                <property name="label" translatable="yes">Other</property>
+                <property name="label" translatable="yes">Encoder</property>
               </widget>
               <packing>
                 <property name="position">2</property>
diff --git a/rdotnet/Makefile b/rdotnet/Makefile
index 5fba62a..3ad6652 100644
--- a/rdotnet/Makefile
+++ b/rdotnet/Makefile
@@ -49,8 +49,8 @@ POST_INSTALL = :
 NORMAL_UNINSTALL = :
 PRE_UNINSTALL = :
 POST_UNINSTALL = :
-build_triplet = x86_64-unknown-linux-gnu
-host_triplet = x86_64-unknown-linux-gnu
+build_triplet = i686-pc-linux-gnu
+host_triplet = i686-pc-linux-gnu
 subdir = rdotnet
 DIST_COMMON = $(srcdir)/Makefile.am $(srcdir)/Makefile.in
 ACLOCAL_M4 = $(top_srcdir)/aclocal.m4
@@ -110,7 +110,7 @@ AUTOMAKE = ${SHELL} /home/xavier/informatica/progs_meus/chronojump/chronojump/mi
 AWK = gawk
 CC = gcc
 CCDEPMODE = depmode=gcc3
-CESARPLAYER_CFLAGS = -pthread -I/usr/include/gtk-2.0 -I/usr/lib/x86_64-linux-gnu/gtk-2.0/include 
-I/usr/include/atk-1.0 -I/usr/include/cairo -I/usr/include/gdk-pixbuf-2.0 -I/usr/include/pango-1.0 
-I/usr/include/gio-unix-2.0/ -I/usr/include/glib-2.0 -I/usr/lib/x86_64-linux-gnu/glib-2.0/include 
-I/usr/include/pixman-1 -I/usr/include/freetype2 -I/usr/include/libpng12 -I/usr/include/gstreamer-0.10 
-I/usr/include/libxml2  
+CESARPLAYER_CFLAGS = -pthread -I/usr/include/gtk-2.0 -I/usr/lib/i386-linux-gnu/gtk-2.0/include 
-I/usr/include/atk-1.0 -I/usr/include/cairo -I/usr/include/gdk-pixbuf-2.0 -I/usr/include/pango-1.0 
-I/usr/include/gio-unix-2.0/ -I/usr/include/glib-2.0 -I/usr/lib/i386-linux-gnu/glib-2.0/include 
-I/usr/include/pixman-1 -I/usr/include/freetype2 -I/usr/include/libpng12 -I/usr/include/gstreamer-0.10 
-I/usr/include/libxml2  
 CESARPLAYER_LIBS = -pthread -lgtk-x11-2.0 -latk-1.0 -lpangoft2-1.0 -lfreetype -lfontconfig -lgdk-x11-2.0 
-lpangocairo-1.0 -lgdk_pixbuf-2.0 -lpango-1.0 -lcairo -lgio-2.0 -lgstaudio-0.10 -lgstvideo-0.10 
-lgstpbutils-0.10 -lgstinterfaces-0.10 -lgstapp-0.10 -lgstbase-0.10 -lgsttag-0.10 -lgstreamer-0.10 
-lgobject-2.0 -lgmodule-2.0 -lgthread-2.0 -lrt -lxml2 -lglib-2.0  
 CFLAGS = -g -O2
 CPP = gcc -E
@@ -139,7 +139,7 @@ INSTALL_DATA = ${INSTALL} -m 644
 INSTALL_PROGRAM = ${INSTALL}
 INSTALL_SCRIPT = ${INSTALL}
 INSTALL_STRIP_PROGRAM = $(install_sh) -c -s
-LD = /usr/bin/ld -m elf_x86_64
+LD = /usr/bin/ld
 LDFLAGS = 
 LIBOBJS = 
 LIBS = 
@@ -197,11 +197,11 @@ am__quote =
 am__tar = $${TAR-tar} chof - "$$tardir"
 am__untar = $${TAR-tar} xf -
 bindir = ${exec_prefix}/bin
-build = x86_64-unknown-linux-gnu
+build = i686-pc-linux-gnu
 build_alias = 
-build_cpu = x86_64
+build_cpu = i686
 build_os = linux-gnu
-build_vendor = unknown
+build_vendor = pc
 builddir = .
 datadir = ${datarootdir}
 datarootdir = ${prefix}/share
@@ -211,11 +211,11 @@ exec_prefix = /usr/local
 expanded_bindir = /usr/local/bin
 expanded_datadir = /usr/local/share
 expanded_libdir = /usr/local/lib
-host = x86_64-unknown-linux-gnu
+host = i686-pc-linux-gnu
 host_alias = 
-host_cpu = x86_64
+host_cpu = i686
 host_os = linux-gnu
-host_vendor = unknown
+host_vendor = pc
 htmldir = ${docdir}
 includedir = ${prefix}/include
 infodir = ${datarootdir}/info
diff --git a/src/encoder.cs b/src/encoder.cs
index 8ab232c..6a31ffe 100644
--- a/src/encoder.cs
+++ b/src/encoder.cs
@@ -34,7 +34,8 @@ public class EncoderParams
        private string eccon;
        private string analysis;
        private string analysisOptions;         //p: propulsive
-       private string smooth; //to pass always as "." to R
+       private string smoothEccCon; //to pass always as "." to R
+       private string smoothCon; //to pass always as "." to R
        private int curve;
        private int width;
        private int height;
@@ -56,7 +57,8 @@ public class EncoderParams
        }
 
        //to encoder capture (pyserial_pyper.py)
-       public EncoderParams(int time, int minHeight, int exercisePercentBodyWeight, string mass, string 
smooth, string eccon,
+       public EncoderParams(int time, int minHeight, int exercisePercentBodyWeight, string mass, 
+                       string smoothEccCon, string smoothCon, string eccon,
                        double heightHigherCondition, double heightLowerCondition, 
                        double meanSpeedHigherCondition, double meanSpeedLowerCondition, 
                        double maxSpeedHigherCondition, double maxSpeedLowerCondition, 
@@ -68,7 +70,8 @@ public class EncoderParams
                this.minHeight = minHeight;
                this.exercisePercentBodyWeight = exercisePercentBodyWeight;
                this.mass = mass;
-               this.smooth = smooth;
+               this.smoothEccCon = smoothEccCon;
+               this.smoothCon = smoothCon;
                this.eccon = eccon;
                this.heightHigherCondition = heightHigherCondition;
                this.heightLowerCondition = heightLowerCondition;
@@ -86,7 +89,7 @@ public class EncoderParams
        public string ToString1 () 
        {
                return time.ToString() + " " + minHeight.ToString() + " " + 
exercisePercentBodyWeight.ToString() + 
-                       " " + mass.ToString() + " " + smooth + " " + eccon +
+                       " " + mass.ToString() + " " + smoothEccCon + " " + smoothCon + " " + eccon +
                        " " + heightHigherCondition.ToString() +        " " + heightLowerCondition.ToString() 
+
                        " " + Util.ConvertToPoint(meanSpeedHigherCondition.ToString()) +        
                        " " + Util.ConvertToPoint(meanSpeedLowerCondition.ToString()) +
@@ -99,8 +102,8 @@ public class EncoderParams
        
        //to graph.R    
        public EncoderParams(int minHeight, int exercisePercentBodyWeight, string mass, string eccon, 
-                       string analysis, string analysisOptions, string smooth, int curve, int width, int 
height,
-                       string decimalSeparator)
+                       string analysis, string analysisOptions, string smoothEccCon, string smoothCon,
+                       int curve, int width, int height, string decimalSeparator)
        {
                this.minHeight = minHeight;
                this.exercisePercentBodyWeight = exercisePercentBodyWeight;
@@ -108,7 +111,8 @@ public class EncoderParams
                this.eccon = eccon;
                this.analysis = analysis;
                this.analysisOptions = analysisOptions;
-               this.smooth = smooth;
+               this.smoothEccCon = smoothEccCon;
+               this.smoothCon = smoothCon;
                this.curve = curve;
                this.width = width;
                this.height = height;
@@ -118,8 +122,8 @@ public class EncoderParams
        public string ToString2 (string sep) 
        {
                return minHeight + sep + exercisePercentBodyWeight + sep + mass + sep + eccon + 
-                       sep + analysis + sep + analysisOptions + sep + smooth + sep + curve + 
-                       sep + width + sep + height + sep + decimalSeparator;
+                       sep + analysis + sep + analysisOptions + sep + smoothEccCon + sep + smoothCon + 
+                       sep + curve + sep + width + sep + height + sep + decimalSeparator;
        }
        
        public string Analysis {
@@ -236,7 +240,7 @@ public class EncoderSQL
        public string url;
        public int time;
        public int minHeight;
-       public double smooth;
+       public double smooth;   //unused on curves, since 1.3.7 it's in database
        public string description;
        public string future1;
        public string future2;
diff --git a/src/gui/chronojump.cs b/src/gui/chronojump.cs
index 7c481a1..7b0fd98 100644
--- a/src/gui/chronojump.cs
+++ b/src/gui/chronojump.cs
@@ -872,6 +872,11 @@ public partial class ChronoJumpWindow
                
                update_sqlite_at_runs_speed_radios = true;
 
+               encoderPropulsive = SqlitePreferences.Select("encoderPropulsive") == "True"; 
+               encoderSmoothEccCon = Convert.ToDouble ( Util.ChangeDecimalSeparator ( 
+                                       SqlitePreferences.Select("encoderSmoothEccCon") ) );
+               encoderSmoothCon = Convert.ToDouble ( Util.ChangeDecimalSeparator (
+                               SqlitePreferences.Select("encoderSmoothCon") ) );
 
 
                //change language works on windows. On Linux let's change the locale
@@ -2662,6 +2667,11 @@ public partial class ChronoJumpWindow
                 else 
                        metersSecondsPreferred = false;
                
+               encoderPropulsive = SqlitePreferences.Select("encoderPropulsive") == "True"; 
+               encoderSmoothEccCon = Convert.ToDouble ( Util.ChangeDecimalSeparator ( 
+                                       SqlitePreferences.Select("encoderSmoothEccCon") ) );
+               encoderSmoothCon = Convert.ToDouble ( Util.ChangeDecimalSeparator (
+                               SqlitePreferences.Select("encoderSmoothCon") ) );
 
                //change language works on windows. On Linux let's change the locale
                //if(Util.IsWindows()) 
diff --git a/src/gui/encoder.cs b/src/gui/encoder.cs
index 1681694..2f731e1 100644
--- a/src/gui/encoder.cs
+++ b/src/gui/encoder.cs
@@ -32,11 +32,7 @@ using Mono.Unix;
 public partial class ChronoJumpWindow 
 {
        [Widget] Gtk.SpinButton spin_encoder_extra_weight;
-       [Widget] Gtk.SpinButton spin_encoder_smooth;
        
-       [Widget] Gtk.CheckButton checkbutton_encoder_capture_propulsive;
-       [Widget] Gtk.CheckButton checkbutton_encoder_analyze_propulsive;
-
        [Widget] Gtk.Button button_encoder_capture;
        [Widget] Gtk.Button button_encoder_capture_csharp;
        [Widget] Gtk.Button button_encoder_bells;
@@ -47,8 +43,8 @@ public partial class ChronoJumpWindow
        [Widget] Gtk.Viewport viewport_image_encoder_capture;
        [Widget] Gtk.Image image_encoder_bell;
        [Widget] Gtk.SpinButton spin_encoder_capture_time;
-       [Widget] Gtk.SpinButton spin_encoder_capture_height;
        [Widget] Gtk.SpinButton spin_encoder_capture_min_height;
+       [Widget] Gtk.SpinButton spin_encoder_capture_curves_height_range;
        [Widget] Gtk.Image image_encoder_capture;
        [Widget] Gtk.ProgressBar encoder_pulsebar_capture;
        [Widget] Gtk.Entry entry_encoder_signal_comment;
@@ -132,6 +128,11 @@ public partial class ChronoJumpWindow
        private static bool encoderProcessCancel;
        private static bool encoderProcessFinish;
 
+       //smooth preferences on Sqlite since 1.3.7
+       bool encoderPropulsive;
+       double encoderSmoothEccCon; 
+       double encoderSmoothCon;
+
        //CAPTURE is the capture from csharp (not from external python) 
        //difference between CALCULECURVES and RECALCULATE_OR_LOAD is: CALCULECURVES does a autosave at end
        enum encoderModes { CAPTURE, CALCULECURVES, RECALCULATE_OR_LOAD, ANALYZE } 
@@ -221,7 +222,8 @@ public partial class ChronoJumpWindow
                                        Util.FindOnArray(':', 2, 3, exerciseNameShown, 
                                        encoderExercisesTranslationAndBodyPWeight) ),   
//ex.percentBodyWeight 
                                findMass(true),
-                               Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: '.'
+                               Util.ConvertToPoint(encoderSmoothEccCon),               //R decimal: '.'
+                               Util.ConvertToPoint(encoderSmoothCon),                  //R decimal: '.'
                                findEccon(true),                                        //force ecS (ecc-conc 
separated)
                                heightHigherCondition, heightLowerCondition,
                                meanSpeedHigherCondition, meanSpeedLowerCondition,
@@ -363,7 +365,7 @@ public partial class ChronoJumpWindow
        private void encoderCreateCurvesGraphR() 
        {
                string analysisOptions = "-";
-               if(checkbutton_encoder_capture_propulsive.Active)
+               if(encoderPropulsive)
                        analysisOptions = "p";
 
                EncoderParams ep = new EncoderParams(
@@ -375,7 +377,8 @@ public partial class ChronoJumpWindow
                                findEccon(true),                                        //force ecS (ecc-conc 
separated)
                                "curves",
                                analysisOptions,
-                               Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: '.'
+                               Util.ConvertToPoint(encoderSmoothEccCon),               //R decimal: '.'
+                               Util.ConvertToPoint(encoderSmoothCon),                  //R decimal: '.'
                                0,                      //curve is not used here
                                image_encoder_width, image_encoder_height,
                                Util.GetDecimalSeparator()
@@ -747,7 +750,6 @@ public partial class ChronoJumpWindow
                                spin_encoder_extra_weight.Value = Convert.ToInt32(es.extraWeight);
 
                                spin_encoder_capture_min_height.Value = es.minHeight;
-                               spin_encoder_smooth.Value = es.smooth;
                                entry_encoder_signal_comment.Text = es.description;
                                encoderTimeStamp = es.GetDate(false); 
                                encoderSignalUniqueID = es.uniqueID;
@@ -773,7 +775,7 @@ public partial class ChronoJumpWindow
        void on_button_encoder_export_all_curves_file_selected (string selectedFileName) 
        {
                string analysisOptions = "-";
-               if(checkbutton_encoder_capture_propulsive.Active)
+               if(encoderPropulsive)
                        analysisOptions = "p";
 
                EncoderParams ep = new EncoderParams(
@@ -785,7 +787,8 @@ public partial class ChronoJumpWindow
                                findEccon(false),               //do not force ecS (ecc-conc separated)
                                "exportCSV",
                                analysisOptions,
-                               Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: '.'
+                               Util.ConvertToPoint(encoderSmoothEccCon),               //R decimal: '.'
+                               Util.ConvertToPoint(encoderSmoothCon),                  //R decimal: '.'
                                
Convert.ToInt32(UtilGtk.ComboGetActive(combo_encoder_analyze_curve_num_combo)),
                                image_encoder_width,
                                image_encoder_height,
@@ -1077,7 +1080,7 @@ public partial class ChronoJumpWindow
                                path,                   //url
                                (int) spin_encoder_capture_time.Value, 
                                (int) spin_encoder_capture_min_height.Value, 
-                               (double) spin_encoder_smooth.Value,
+                               -1,                     //Since 1.3.7 smooth is not stored in curves
                                desc,
                                "","","",
                                Util.FindOnArray(':', 2, 1, UtilGtk.ComboGetActive(combo_encoder_exercise), 
@@ -1193,7 +1196,7 @@ public partial class ChronoJumpWindow
        {
                int width=encoder_capture_drawingarea.Allocation.Width;
                int height=encoder_capture_drawingarea.Allocation.Height;
-               double realHeight = 1000 * 2 * spin_encoder_capture_height.Value;
+               double realHeight = 1000 * 2 * spin_encoder_capture_curves_height_range.Value;
                
                Log.WriteLine("00a 2");
                SerialPort sp = new SerialPort(port);
@@ -1278,7 +1281,7 @@ public partial class ChronoJumpWindow
                string dataFileName = "";
                
                string analysisOptions = "-";
-               if(checkbutton_encoder_analyze_propulsive.Active)
+               if(encoderPropulsive)
                        analysisOptions = "p";
 
                //use this send because we change it to send it to R
@@ -1323,7 +1326,8 @@ public partial class ChronoJumpWindow
                                        myEccon,        //this decides if analysis will be together or 
separated
                                        sendAnalysis,
                                        analysisOptions,
-                                       "-1",
+                                       Util.ConvertToPoint(encoderSmoothEccCon),               //R decimal: 
'.'
+                                       Util.ConvertToPoint(encoderSmoothCon),                  //R decimal: 
'.'
                                        myCurveNum,
                                        image_encoder_width, 
                                        image_encoder_height,
@@ -1438,7 +1442,8 @@ Log.WriteLine(str);
                                        findEccon(false),               //do not force ecS (ecc-conc 
separated)
                                        sendAnalysis,
                                        analysisOptions,
-                                       Util.ConvertToPoint((double) spin_encoder_smooth.Value), //R decimal: 
'.'
+                                       Util.ConvertToPoint(encoderSmoothEccCon),               //R decimal: 
'.'
+                                       Util.ConvertToPoint(encoderSmoothCon),                  //R decimal: 
'.'
                                        
Convert.ToInt32(UtilGtk.ComboGetActive(combo_encoder_analyze_curve_num_combo)),
                                        image_encoder_width,
                                        image_encoder_height,
@@ -2563,7 +2568,6 @@ Log.Write("l");
        private void encoderButtonsSensitive(encoderSensEnum option) {
                //columns
                //c0 button_encoder_capture, button_encoder_capture_csharp, 
-               //      button_encoder_bells, spin_encoder_capture_time, spin_encoder_capture_height
                //c1 button_encoder_recalculate
                //c2 button_encoder_load_signal
                //c3 button_encoder_save_all_curves, button_encoder_export_all_curves,
@@ -2625,9 +2629,6 @@ Log.Write("l");
 
                button_encoder_capture.Sensitive = Util.IntToBool(table[0]);
                button_encoder_capture_csharp.Sensitive = Util.IntToBool(table[0]);
-               button_encoder_bells.Sensitive = Util.IntToBool(table[0]);
-               spin_encoder_capture_time.Sensitive = Util.IntToBool(table[0]);
-               spin_encoder_capture_height.Sensitive = Util.IntToBool(table[0]);
 
                button_encoder_recalculate.Sensitive = Util.IntToBool(table[1]);
                button_encoder_load_signal.Sensitive = Util.IntToBool(table[2]);
diff --git a/src/gui/preferences.cs b/src/gui/preferences.cs
index e5f7a7c..09a72b4 100644
--- a/src/gui/preferences.cs
+++ b/src/gui/preferences.cs
@@ -43,6 +43,8 @@ public class PreferencesWindow {
        [Widget] Gtk.CheckButton checkbutton_initial_speed;
        [Widget] Gtk.CheckButton checkbutton_angle;
        
+       [Widget] Gtk.Button button_help_power;
+       
        [Widget] Gtk.CheckButton checkbutton_show_tv_tc_index;
        [Widget] Gtk.Box hbox_indexes;
        [Widget] Gtk.RadioButton radiobutton_show_q_index;
@@ -56,7 +58,10 @@ public class PreferencesWindow {
        [Widget] Gtk.RadioButton radio_speed_km;
        [Widget] Gtk.RadioButton radio_weight_percent;
        [Widget] Gtk.RadioButton radio_weight_kg;
-       [Widget] Gtk.TextView textview_power;
+       
+       [Widget] Gtk.CheckButton checkbutton_encoder_propulsive;
+       [Widget] Gtk.SpinButton spin_encoder_smooth_ecc_con;
+       [Widget] Gtk.SpinButton spin_encoder_smooth_con;
 
 //     [Widget] Gtk.Box hbox_language_row;
 //     [Widget] Gtk.Box hbox_combo_language;
@@ -113,10 +118,10 @@ public class PreferencesWindow {
                
                if(showPower) {
                        PreferencesWindowBox.checkbutton_power.Active = true; 
-                       PreferencesWindowBox.textview_power.Show();
+                       PreferencesWindowBox.button_help_power.Sensitive = true;
                } else {
                        PreferencesWindowBox.checkbutton_power.Active = false; 
-                       PreferencesWindowBox.textview_power.Hide();
+                       PreferencesWindowBox.button_help_power.Sensitive = false;
                }
                
                if(showInitialSpeed)  
@@ -214,10 +219,21 @@ public class PreferencesWindow {
        }
                
        private void on_checkbutton_power_clicked (object o, EventArgs args) {
-               if(checkbutton_power.Active)
-                       textview_power.Show();
-               else
-                       textview_power.Hide();
+               button_help_power.Sensitive = checkbutton_power.Active;
+       }
+       private void on_button_help_power_clicked (object o, EventArgs args) {
+               new DialogMessage(Constants.MessageTypes.INFO, 
+                               Catalog.GetString("On jumps results tab, power is calculated depending on 
jump type:") + 
+                               "\n\n" +
+                               Catalog.GetString("Jumps with TC & TF: Bosco Relative Power (W/Kg)") + 
+                               "\n" +
+                               Catalog.GetString("P = 24.6 * (Total time + Flight time) / Contact time") + 
+                               "\n\n" +
+                               Catalog.GetString("Jumps without TC: Lewis Peak Power 1974 (W)") + 
+                               "\n" +
+                               Catalog.GetString("P = SQRT(4.9) * 9.8 * (body weight+extra weight) * 
SQRT(jump height in meters)") + 
+                               "\n\n" +
+                               Catalog.GetString("If you want to use other formulas, go to Statistics."));
        }
        
        void on_button_cancel_clicked (object o, EventArgs args)
@@ -324,26 +340,36 @@ public class PreferencesWindow {
 
        void on_button_accept_clicked (object o, EventArgs args)
        {
-               /* the falses are for the dbcon that is not opened */
-               SqlitePreferences.Update("digitsNumber", UtilGtk.ComboGetActive(combo_decimals), false);
-               SqlitePreferences.Update("showHeight", 
PreferencesWindowBox.checkbutton_height.Active.ToString(), false);
-               SqlitePreferences.Update("showPower", 
PreferencesWindowBox.checkbutton_power.Active.ToString(), false);
-               SqlitePreferences.Update("showInitialSpeed", 
PreferencesWindowBox.checkbutton_initial_speed.Active.ToString(), false);
-               SqlitePreferences.Update("showAngle", 
PreferencesWindowBox.checkbutton_angle.Active.ToString(), false);
+               Sqlite.Open();
+
+               SqlitePreferences.Update("digitsNumber", UtilGtk.ComboGetActive(combo_decimals), true);
+               SqlitePreferences.Update("showHeight", 
PreferencesWindowBox.checkbutton_height.Active.ToString(), true);
+               SqlitePreferences.Update("showPower", 
PreferencesWindowBox.checkbutton_power.Active.ToString(), true);
+               SqlitePreferences.Update("showInitialSpeed", 
PreferencesWindowBox.checkbutton_initial_speed.Active.ToString(), true);
+               SqlitePreferences.Update("showAngle", 
PreferencesWindowBox.checkbutton_angle.Active.ToString(), true);
                
                if(PreferencesWindowBox.checkbutton_show_tv_tc_index.Active) {
-                       SqlitePreferences.Update("showQIndex", 
PreferencesWindowBox.radiobutton_show_q_index.Active.ToString(), false);
-                       SqlitePreferences.Update("showDjIndex", 
PreferencesWindowBox.radiobutton_show_dj_index.Active.ToString(), false);
+                       SqlitePreferences.Update("showQIndex", 
PreferencesWindowBox.radiobutton_show_q_index.Active.ToString(), true);
+                       SqlitePreferences.Update("showDjIndex", 
PreferencesWindowBox.radiobutton_show_dj_index.Active.ToString(), true);
                } else {
-                       SqlitePreferences.Update("showQIndex", "False", false);
-                       SqlitePreferences.Update("showDjIndex", "False", false);
+                       SqlitePreferences.Update("showQIndex", "False", true);
+                       SqlitePreferences.Update("showDjIndex", "False", true);
                }
                
                
-               SqlitePreferences.Update("askDeletion", 
PreferencesWindowBox.checkbutton_ask_deletion.Active.ToString(), false);
-               SqlitePreferences.Update("weightStatsPercent", 
PreferencesWindowBox.radio_weight_percent.Active.ToString(), false);
-               SqlitePreferences.Update("heightPreferred", 
PreferencesWindowBox.radio_elevation_height.Active.ToString(), false);
-               SqlitePreferences.Update("metersSecondsPreferred", 
PreferencesWindowBox.radio_speed_ms.Active.ToString(), false);
+               SqlitePreferences.Update("askDeletion", 
PreferencesWindowBox.checkbutton_ask_deletion.Active.ToString(), true);
+               SqlitePreferences.Update("weightStatsPercent", 
PreferencesWindowBox.radio_weight_percent.Active.ToString(), true);
+               SqlitePreferences.Update("heightPreferred", 
PreferencesWindowBox.radio_elevation_height.Active.ToString(), true);
+               SqlitePreferences.Update("metersSecondsPreferred", 
PreferencesWindowBox.radio_speed_ms.Active.ToString(), true);
+               
+               SqlitePreferences.Update("encoderPropulsive", 
+                               PreferencesWindowBox.checkbutton_encoder_propulsive.Active.ToString(), true);
+               SqlitePreferences.Update("encoderSmoothEccCon", Util.ConvertToPoint( 
+                               (double) PreferencesWindowBox.spin_encoder_smooth_ecc_con.Value), true);
+               SqlitePreferences.Update("encoderSmoothCon", Util.ConvertToPoint( 
+                               (double) PreferencesWindowBox.spin_encoder_smooth_con.Value), true);
+       
+               Sqlite.Close();
                
                /*
                if(Util.IsWindows()) {
diff --git a/src/sqlite/encoder.cs b/src/sqlite/encoder.cs
index ace2f30..b2cb96b 100644
--- a/src/sqlite/encoder.cs
+++ b/src/sqlite/encoder.cs
@@ -52,7 +52,7 @@ class SqliteEncoder : Sqlite
                        "url TEXT, " +
                        "time INT, " +
                        "minHeight INT, " +
-                       "smooth FLOAT, " +  
+                       "smooth FLOAT, " +      //unused. since 1.3.7 is on preferences
                        "description TEXT, " +
                        "future1 TEXT, " +      //works as status: "active", "inactive"
                        "future2 TEXT, " +
@@ -116,7 +116,7 @@ class SqliteEncoder : Sqlite
                                "', url = '" + es.url +
                                "', time = " + es.time +
                                ", minHeight = " + es.minHeight +
-                               ", smooth = " + Util.ConvertToPoint(es.smooth) +
+                               ", smooth = " + Util.ConvertToPoint(es.smooth) +        //unused. in 1.3.7 is 
on preferences
                                ", description = '" + es.description + 
                                "', future1 = '" + es.future1 + 
                                "', future2 = '" + es.future2 + 
@@ -192,7 +192,7 @@ 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
+                                       Convert.ToDouble(Util.ChangeDecimalSeparator(reader[12].ToString())), 
//smooth UNUSED
                                        reader[13].ToString(),                  //description
                                        reader[14].ToString(),                  //future1
                                        reader[15].ToString(),                  //future2
diff --git a/src/sqlite/main.cs b/src/sqlite/main.cs
index 1c51b36..024233a 100644
--- a/src/sqlite/main.cs
+++ b/src/sqlite/main.cs
@@ -72,7 +72,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 = "0.89";
+       static string lastChronojumpDatabaseVersion = "0.90";
 
        public Sqlite() {
        }
@@ -1216,6 +1216,19 @@ class Sqlite
 
                                currentVersion = "0.89";
                        }
+                       if(currentVersion == "0.89") {
+                               dbcon.Open();
+       
+                               SqlitePreferences.Insert("encoderPropulsive", "True");
+                               SqlitePreferences.Insert("encoderSmoothEccCon", "0.6");
+                               SqlitePreferences.Insert("encoderSmoothCon", "0.7");
+                               Log.WriteLine("Preferences added propulsive and encoder smooth");
+                               
+                               SqlitePreferences.Update ("databaseVersion", "0.90", true); 
+                               dbcon.Close();
+
+                               currentVersion = "0.90";
+                       }
                }
 
                //if changes are made here, remember to change also in CreateTables()
@@ -1354,6 +1367,7 @@ class Sqlite
                SqliteCountry.initialize();
                
                //changes [from - to - desc]
+               //0.89 - 0.90 Converted DB to 0.90 Preferences added propulsive and encoder smooth
                //0.88 - 0.89 Converted DB to 0.89 Added encoder exercise: Free
                //0.87 - 0.88 Converted DB to 0.88 Deleted fake RSA test and added known RSA tests
                //0.86 - 0.87 Converted DB to 0.87 Added run speed start preferences on sqlite
diff --git a/src/sqlite/preferences.cs b/src/sqlite/preferences.cs
index 715e7f0..53e1ea8 100644
--- a/src/sqlite/preferences.cs
+++ b/src/sqlite/preferences.cs
@@ -70,6 +70,10 @@ class SqlitePreferences : Sqlite
                Insert ("machineID", machineID);
                
                Insert ("multimediaStorage", Constants.MultimediaStorage.BYSESSION.ToString());
+               
+               Insert ("encoderPropulsive", "True");
+               Insert ("encoderSmoothEccCon", "0.6");
+               Insert ("encoderSmoothCon", "0.7");
        }
 
        public static void Insert(string myName, string myValue)


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