iccsa-21-wind

git clone https://git.igankevich.com/iccsa-21-wind.git
Log | Files | Refs

commit 74fe1ed063bbf5f5ab782dc054cc0c7104765ab9
parent 14c2f9cb5ca9dc8f411d332a8d79bfa3364715d1
Author: Ivan Gankevich <i.gankevich@spbu.ru>
Date:   Tue, 30 Mar 2021 23:14:07 +0300

Add scripts and data from anemometer repository.

Diffstat:
.gitignore | 1+
R/anal.R | 494+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
R/calibrate.R | 36++++++++++++++++++++++++++++++++++++
anemometer-wind/2/x | 46++++++++++++++++++++++++++++++++++++++++++++++
anemometer-wind/2/x-origin | 39+++++++++++++++++++++++++++++++++++++++
anemometer-wind/2/x-reverse | 25+++++++++++++++++++++++++
anemometer-wind/2/x-reverse-origin | 41+++++++++++++++++++++++++++++++++++++++++
anemometer-wind/2/y | 27+++++++++++++++++++++++++++
anemometer-wind/2/y-origin | 48++++++++++++++++++++++++++++++++++++++++++++++++
anemometer-wind/2/y-reverse | 40++++++++++++++++++++++++++++++++++++++++
anemometer-wind/2/y-reverse-origin | 42++++++++++++++++++++++++++++++++++++++++++
anemometer-wind/2/z | 22++++++++++++++++++++++
anemometer-wind/2/z-origin | 32++++++++++++++++++++++++++++++++
anemometer-wind/2/z-reverse | 25+++++++++++++++++++++++++
anemometer-wind/2/z-reverse-origin | 28++++++++++++++++++++++++++++
anemometer-wind/3/x | 25+++++++++++++++++++++++++
anemometer-wind/3/x-origin | 28++++++++++++++++++++++++++++
anemometer-wind/3/x-reverse | 25+++++++++++++++++++++++++
anemometer-wind/3/x-reverse-origin | 28++++++++++++++++++++++++++++
anemometer-wind/3/y | 23+++++++++++++++++++++++
anemometer-wind/3/y-origin | 30++++++++++++++++++++++++++++++
anemometer-wind/3/y-reverse | 23+++++++++++++++++++++++
anemometer-wind/3/y-reverse-origin | 30++++++++++++++++++++++++++++++
anemometer-wind/3/z | 24++++++++++++++++++++++++
anemometer-wind/3/z-origin | 29+++++++++++++++++++++++++++++
anemometer-wind/3/z-reverse | 49+++++++++++++++++++++++++++++++++++++++++++++++++
anemometer-wind/3/z-reverse-origin | 36++++++++++++++++++++++++++++++++++++
anemometer-wind/4/x | 25+++++++++++++++++++++++++
anemometer-wind/4/x-origin | 28++++++++++++++++++++++++++++
anemometer-wind/4/x-reverse | 25+++++++++++++++++++++++++
anemometer-wind/4/x-reverse-origin | 28++++++++++++++++++++++++++++
anemometer-wind/4/y | 24++++++++++++++++++++++++
anemometer-wind/4/y-origin | 29+++++++++++++++++++++++++++++
anemometer-wind/4/y-reverse | 24++++++++++++++++++++++++
anemometer-wind/4/y-reverse-origin | 29+++++++++++++++++++++++++++++
anemometer-wind/4/z | 25+++++++++++++++++++++++++
anemometer-wind/4/z-origin | 28++++++++++++++++++++++++++++
anemometer-wind/4/z-reverse | 21+++++++++++++++++++++
anemometer-wind/4/z-reverse-origin | 32++++++++++++++++++++++++++++++++
anemometer-wind/5/x | 24++++++++++++++++++++++++
anemometer-wind/5/x-origin | 29+++++++++++++++++++++++++++++
anemometer-wind/5/x-reverse | 25+++++++++++++++++++++++++
anemometer-wind/5/x-reverse-origin | 28++++++++++++++++++++++++++++
anemometer-wind/5/y | 25+++++++++++++++++++++++++
anemometer-wind/5/y-origin | 28++++++++++++++++++++++++++++
anemometer-wind/6/z-fan | 32++++++++++++++++++++++++++++++++
anemometer-wind/6/z-fan-and-wind | 25+++++++++++++++++++++++++
anemometer-wind/6/z-fan-and-wind-origin | 27+++++++++++++++++++++++++++
anemometer-wind/6/z-fan-origin | 18++++++++++++++++++
anemometer-wind/merge.sh | 25+++++++++++++++++++++++++
gnuplot/daily-stats.gnuplot | 13+++++++++++++
guix/manifest.scm | 10++++++++++
manifest.scm | 7-------
mchs.txt | 7+++++++
sh/properties | 32++++++++++++++++++++++++++++++++
55 files changed, 1962 insertions(+), 7 deletions(-)

diff --git a/.gitignore b/.gitignore @@ -1,4 +1,5 @@ /build +Rplots.pdf # Created by https://www.toptal.com/developers/gitignore/api/vim,linux # Edit at https://www.toptal.com/developers/gitignore?templates=vim,linux diff --git a/R/anal.R b/R/anal.R @@ -0,0 +1,494 @@ +library(DBI) +library(fitdistrplus) +library(plotrix) +library(sn) + +datetime_format <- "%FT%H:%M" + +# https://stackoverflow.com/questions/13023274/how-to-do-printf-in-r +printf <- function(...) cat(sprintf(...)) + +# https://stackoverflow.com/questions/32370485/convert-radians-to-degree-degree-to-radians +rad2deg <- function(rad) {(rad * 180) / (pi)} +deg2rad <- function(deg) {(deg * pi) / (180)} + +# https://stackoverflow.com/questions/27455948/in-r-whats-the-simplest-way-to-scale-a-vector-to-a-unit-vector +unit <- function(x) { + length = sqrt(sum(x**2)) + ifelse(length == 0, x, x/length) +} + +time_string_to_timestamp <- function(str) { + as.integer(as.POSIXct(strptime(str, datetime_format))) +} + +speed <- function(x,y,z) { sqrt(x**2 + y**2 + z**2) } +direction <- function(x,y) { atan2(y,x) } +# retain the original sign +power <- function(x,y) { + ifelse(abs(x) < 1, sign(x)*abs(x)**y, x**y) + #sign(x)*abs(x)**y + #abs(x)**y +} + +dweibull2 <- function (x, a1=1, b1=1, c1=1, a2=1, b2=1, c2=1, g=0) { + #ifelse(x<g, + # a1* abs(c1*b1)*(abs(b1*(x-g))**(c1-1))* exp(-(abs(b1*(x-g))**c1)), + # a1* abs(c2*b2)*(abs(b2*(x-g))**(c2-1))* exp(-(abs(b2*(x-g))**c2))) + ifelse(x<g, + a1*abs(b1*c1)*exp(-(abs(b1*(abs(x-g)-abs((c1-1)/c1)**(1/c1)))**c1)), + a2*abs(b2*c2)*exp(-(abs(b2*(abs(x-g)-abs((c2-1)/c2)**(1/c2)))**c2))) +} + +dweibull4 <- function (x, a1=1, b1=1, c1=1, a2=1, b2=1, c2=1, g1=0, + a3=1, b3=1, c3=1, a4=1, b4=1, c4=1, g2=0) { + ifelse(x<0, + dweibull2(x,a1,b1,c1,a2,b2,c2,g1), + dweibull2(x,a3,b3,c3,a4,b4,c4,g2)) +} + +dvonmises <- function (x, x_mean=0, a=1, b=1, c=1) { + a * exp(b*cos(c*(x-x_mean))) / (2*pi*besselI(b,0)) +} + +dgumbel <- function (x, location=0, scale=1) { + z <- (x-location)/scale + (1/scale) * exp(-(z + exp(-z))) +} + +drayleigh <- function (x, location=0, scale=1) { +} + +# https://www.tutorialspoint.com/r/r_mean_median_mode.htm +# https://stackoverflow.com/questions/2547402/how-to-find-the-statistical-mode +getmode <- function(v) { + #uniqv <- unique(v) + #uniqv[which.max(tabulate(match(v, uniqv)))] + as.numeric(names(sort(-table(v)))[1]) +} + +# https://stackoverflow.com/questions/27418461/calculate-the-modes-in-a-multimodal-distribution-in-r +find_peaks_indices <- function (x) { + modes <- c() + for (i in 2:(length(x)-1)){ + if ((x[i] > x[i-1]) & (x[i] > x[i+1])) { + modes <- c(modes,i) + } + } + modes +} + +find_real_peaks_indices <- function (x, max_modes=2) { + n <- 1024 + #x_density <- density(x,n=n,adjust=0.125) + #y <- x_density$y + y <- x + modes <- find_peaks_indices(y) + # find the first N highest peaks + modes_xy <- data.frame(x=modes,y=y[modes]) + modes_xy <- modes_xy[order(modes_xy$y, decreasing=TRUE),] + modes_xy <- modes_xy[c(1:max_modes), ] + # scale indices to [0,1] + (modes_xy$x-1)/(n-1) +} + +find_max_x <- function (x, y) { + n <- length(y)-1 + indices <- c(0:n) + index <- indices[y == max(y)]/n + x[floor(index*(length(x)-1)+1)] +} + +normalize_hist <- function(pdf_x) { + #data.frame(density=pdf_x$density/max(abs(pdf_x$density)),x=pdf_x$mids) + data.frame(density=pdf_x$density,x=pdf_x$mids) +} + +fit_velocity_pdf <- function (xx, x, density, sign=-1, plot=TRUE, axis="x", dist="weibull2") { + a0 <- 0 + b0 <- 0 + c0 <- 1 + c1 <- 3 + indices <- find_real_peaks_indices(x, max_modes=1) + if (FALSE) { + pdf <- normalize_hist(hist(x, plot=FALSE, breaks=1000)) + print(indices) + indices = floor(indices * length(pdf$x)) + x_modes <- pdf$x[indices] + print(x_modes) + model <- nls(pdf$density ~ dweibull4(pdf$x,a1,b1,c1,a2,b2,c2,x_modes[[1]],a3,b3,c3,a4,b4,c4,x_modes[[2]]), + data=pdf, + start=list(a1=1,b1=1,c1=1,a2=1,b2=1,c2=1, + a3=1,b3=1,c3=1,a4=1,b4=1,c4=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(a0,b0,c0,a0,b0,c0,a0,b0,c0,a0,b0,c0), + upper=c(1000,1000,3,1000,2000,3,1000,1000,3,1000,2000,3)) + c = summary(model)$coefficients + if (plot) { + pdf_x_est <- dweibull4(pdf$x,c[[1]],c[[2]],c[[3]],c[[4]],c[[5]],c[[6]],x_modes[[1]], + c[[7]],c[[8]],c[[9]],c[[10]],c[[11]],c[[12]],x_modes[[2]]) + plot(pdf$x, pdf$density, xlab=paste('Velocity', axis), ylab='PDF') + lines(pdf$x, pdf_x_est, col='red') + } + c + } else { + #x_mode <- getmode(x) + #pdf_x <- normalize_hist(hist(x, plot=FALSE, breaks=100)) + pdf_x <- data.frame(x=xx,density=x) + c <- c() + pdf_x_set <- c() + if (dist == "weibull2") { + x_mode <- find_max_x(pdf_x$x,pdf_x$density) + #indices = floor(indices * length(pdf_x$x)) + 1 + #x_mode <- pdf_x$x[indices][[1]] + c <- tryCatch( + { + model <- nls(pdf_x$density ~ dweibull2(pdf_x$x,a,b,c,d,e,f,g=x_mode), + data=pdf_x, + start=list(a=1,b=1,c=1,d=1,e=1,f=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(a0,b0,c0,a0,b0,c0), upper=c(1000,1000,c1,1000,2000,c1)) + summary(model)$coefficients + }, + error=function(cond) { + message(cond) + c(1,1,1,1,1,1) + }) + pdf_x_est <- dweibull2(pdf_x$x,c[[1]],c[[2]],c[[3]],c[[4]],c[[5]],c[[6]],x_mode) + } else if (dist == "vonmises") { + c <- tryCatch({ + model <- nls(density ~ dvonmises(2*pi*pdf_x$x/(max(pdf_x$x)),0,a,b,c), + data=pdf_x, + start=list(a=1,b=1,c=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(0,1,0), upper=c(1000,1000,pi)) + c <- summary(model)$coefficients + print(c) + },error=function(cond) { + message(cond) + c(1,1,1) + }) + pdf_x_est <- dvonmises(2*pi*pdf_x$x/max(pdf_x$x),0,c[[1]],c[[2]],c[[3]]) + } else if (dist == "gumbel") { + c <- tryCatch( + { + model <- nls(pdf_x$density ~ c*dgumbel(pdf_x$x,location=a,scale=b), + data=pdf_x, + start=list(a=1,b=1,c=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(-1000,0.1,c=1), upper=c(1000,1000,1000)) + c = summary(model)$coefficients + }, + error=function(cond) { + message(cond) + c <- c(1,1,1,1) + }) + pdf_x_est <- c[[3]]*dgumbel(pdf_x$x,location=c[[1]],scale=c[[2]]) + } else if (dist == "norm") { + fit <- fitdist(pdf_x$x, "norm") + c <- coef(fit) + pdf_x_est <- dnorm(pdf_x$x,mean=c[[1]],sd=c[[2]]) + } else if (dist == "rayleigh") { + c <- tryCatch( + { + model <- nls(pdf_x$density ~ b*dweibull(sign*pdf_x$x,scale=a,shape=2), + data=pdf_x, + start=list(a=1,b=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(0.1,0), upper=c(1000,1000)) + c = summary(model)$coefficients + }, + error=function(cond) { + message(cond) + c <- c(1,1,1,1) + }) + pdf_x_est <- c[[2]]*dweibull(sign*pdf_x$x,scale=c[[1]],shape=2) + } else { + c <- tryCatch( + { + model <- nls(pdf_x$density ~ c*dweibull(sign*pdf_x$x,scale=a,shape=b), + data=pdf_x, + start=list(a=1,b=1,c=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(0.1,0.1,0), upper=c(1000,1000,1000)) + c = summary(model)$coefficients + }, + error=function(cond) { + message(cond) + c <- c(1,1,1,1) + }) + pdf_x_est <- c[[3]]*dweibull(sign*pdf_x$x,scale=c[[1]],shape=c[[2]]) + } + #if (plot) { + # plot(sign*pdf_x$x, pdf_x$density, xlab=paste('Velocity', axis), ylab='PDF') + # lines(density(sign*x), col='blue') + # lines(sign*pdf_x$x, pdf_x_est, col='red') + #} + #if (sign < 0) { + # print(pdf_x$x) + # pdf_x$x = -rev(pdf_x$x) + # pdf_x$density = rev(pdf_x$density) + # pdf_x_est = rev(pdf_x_est) + #} + list(coefficients=c, + actual_density=pdf_x$density, + estimated_density=pdf_x_est, + x=pdf_x$x) + } +} + +fit_velocity_pdf_bilateral <- function (velocity, axis="x") { + velocity_hist <- normalize_hist(hist(velocity, plot=FALSE, breaks=100)) + x = velocity_hist$x; + v = velocity_hist$density; + d = density(velocity,adjust=0.5) + dist_left <- fit_velocity_pdf(x[x<=0], v[x<=0], density=d$y[d$x<=0], + sign=-1, plot=FALSE, axis=axis, dist="weibull") + dist_right <- fit_velocity_pdf(x[x>=0], v[x>=0], density=d$y[d$x>=0], + sign=1, plot=FALSE, axis=axis, dist="weibull") + #x <- c(dist_left$x, dist_right$x) + actual_density <- c(dist_left$actual_density, dist_right$actual_density) + estimated_density <- c(dist_left$estimated_density, dist_right$estimated_density) + plot(x, actual_density, xlab=paste('Velocity', axis), ylab='PDF') + #hist(velocity, xlab=paste('Velocity', axis), ylab='PDF', freq=FALSE, breaks=100) + lines(d, col='green', lwd=2) + #lines(x, estimated_density, col='red', lwd=2) + lines(dist_left$x, dist_left$estimated_density, col='red', lwd=2) + lines(dist_right$x, dist_right$estimated_density, col='blue', lwd=2) + dist_left$coefficients +} + +fit_velocity_pdf_v2 <- function (x, sign=-1, plot=TRUE, axis="x") { + #fit <- fitdist(x, "weibull") + x_mode <- getmode(x) + fit <- fitdist(x-x_mode, "weibull2", start=list(a1=1, b1=1, c1=1, a2=1, b2=1, c2=1)) + if (plot) { + plot(fit) + } + coef(fit) +} + +fit_velocity_acf <- function (x, plot=TRUE, axis="x") { + acf_x <- acf(x, type="correlation", plot=FALSE) + acf_x <- data.frame(acf=acf_x$acf, lag=acf_x$lag/(nrow(acf_x$lag)-1)) + model <- nls(acf ~ a*exp(-(b*lag)**c), + data=acf_x, + start=list(a=1,b=1,c=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(0.1,0,0.1), upper=c(20,1000,2)) + c <- summary(model)$coefficients + if (plot) { + acf_est <- sapply(acf_x$lag, function (lag) { c[[1]]*exp(-(c[[2]]*lag)**c[[3]]) }) + plot(acf_x$lag, acf_x$acf, xlab='Lag', ylab=paste('ACF', axis)) + lines(acf_x$lag, acf_est, col='red') + } + c +} + +fit_direction <- function (x, x_mode, plot=TRUE) { + pdf_x <- hist(x-x_mode, plot=FALSE, breaks=1000) + pdf_x <- data.frame(density=pdf_x$density/max(abs(pdf_x$density)), + x=pdf_x$mids/max(abs(pdf_x$mids))) + c <- tryCatch({ + model <- nls(density ~ dvonmises(x,0,a,b,c), + data=pdf_x, + start=list(a=1,b=1,c=1), + control=list(warnOnly=TRUE), + algorithm="port", + lower=c(0,1,0), upper=c(1000,1000,1000)) + c <- summary(model)$coefficients + },error=function(cond) { + message(cond) + c(1,1,1) + }) + if (plot) { + pdf_x_est <- sapply(pdf_x$x, function (x) { dvonmises(x,0,c[[1]],c[[2]],c[[3]]) }) + plot(pdf_x$x+x_mode, pdf_x$density, xlab='Direction', ylab='PDF') + lines(pdf_x$x+x_mode, pdf_x_est, col='red') + } + c +} + +mydb <- dbConnect(RSQLite::SQLite(), "samples/load-cell.sqlite3") + +time_start = time_string_to_timestamp("2021-03-06T00:00") +time_end = time_string_to_timestamp("2021-03-06T23:00") +time_delta = 60*60*2 + +print(time_start) +print(time_end) + + +cumulative_data <- data.frame(speed=numeric(0),direction=numeric(0), + x_mode=numeric(0),abs_x_mode=numeric(0),x_sd=numeric(0), + y_mean=numeric(0), + acf_x_a=numeric(0),acf_x_b=numeric(0),acf_x_c=numeric(0), + x_a=numeric(0),x_b=numeric(0),x_c=numeric(0), + x_d=numeric(0),x_e=numeric(0),x_f=numeric(0), + # Y + y_mode=numeric(0), + y_a=numeric(0),y_b=numeric(0),y_c=numeric(0), + y_d=numeric(0),y_e=numeric(0),y_f=numeric(0), + acf_y_a=numeric(0),acf_y_b=numeric(0),acf_y_c=numeric(0)) +timestamps <- seq(time_start, time_end, time_delta) +pb <- txtProgressBar(min = 0, max = length(timestamps), style = 3) + +i <- 0 +for (timestamp in timestamps) { + velocity = dbGetQuery(mydb, + "SELECT x,y,z FROM samples WHERE timestamp BETWEEN :t0 AND (:t0 + :dt) ORDER BY timestamp", + params = list(t0 = timestamp, dt=time_delta)) + velocity = dbGetQuery(mydb, + "SELECT x,y,z FROM samples + WHERE timestamp BETWEEN :t0 AND (:t0 + :dt) + AND ABS(x-:xmean)<10000 AND ABS(y-:ymean)<10000 AND ABS(z-:zmean)<10000 + ORDER BY timestamp", + params = list(t0 = timestamp, dt=time_delta, + xmean=mean(velocity$x), ymean=mean(velocity$y), zmean=mean(velocity$z))) + old_mean_x <- max(abs(velocity$x)) - mean(velocity$x) + velocity$x = (velocity$x - mean(velocity$x)) + velocity$y = (velocity$y - mean(velocity$y)) + velocity$z = (velocity$z - mean(velocity$z)) + # convert energy to velocity (U^2 -> U) + velocity$x = sign(velocity$x)*sqrt(abs(velocity$x)) + velocity$y = sign(velocity$y)*sqrt(abs(velocity$y)) + velocity$z = sign(velocity$z)*sqrt(abs(velocity$z)) + x_mode <- getmode(velocity$x) + y_mode <- getmode(velocity$y) + #direction_mode <- getmode(velocity$direction) + direction_mode <- direction(x_mode, y_mode) + velocity$speed = speed(velocity$x,velocity$y,velocity$z) + velocity$direction = direction(velocity$x,velocity$y) + new_row = nrow(cumulative_data)+1 + cumulative_data[new_row, "x_mode"] = x_mode + cumulative_data[new_row, "y_mode"] = y_mode + cumulative_data[new_row, "speed"] = mean(velocity$speed) + cumulative_data[new_row, "direction"] = direction_mode + #fit <- fitdist(velocity$x, "sn", start=list(omega=1,alpha=-1)) + #fit <- fitdist(velocity$x, "weibull") + #fit <- fitdist(velocity$x, "expnorm", start=list(a=1,b=1,c=1)) + #fit <- fitdist(velocity$x, "norm") + #fit <- fitdist(velocity$x, "gumbel", start=list(a=1, b=1)) + #plot(fit) + # Velocity X + x_coefs <- fit_velocity_pdf_bilateral(velocity$x, axis="x") + cumulative_data[new_row, "x_a"] = x_coefs[[1]] + cumulative_data[new_row, "x_b"] = x_coefs[[2]] + #cumulative_data[new_row, "x_c"] = x_coefs[[3]] + #cumulative_data[new_row, "x_d"] = x_coefs[[4]] + #cumulative_data[new_row, "x_e"] = x_coefs[[5]] + #cumulative_data[new_row, "x_f"] = x_coefs[[6]] + # Velocity Y + y_coefs <- fit_velocity_pdf_bilateral(velocity$y, axis="y") + cumulative_data[new_row, "y_a"] = y_coefs[[1]] + cumulative_data[new_row, "y_b"] = y_coefs[[2]] + #cumulative_data[new_row, "y_c"] = y_coefs[[3]] + #cumulative_data[new_row, "y_d"] = y_coefs[[4]] + #cumulative_data[new_row, "y_e"] = y_coefs[[5]] + #cumulative_data[new_row, "y_f"] = y_coefs[[6]] + # Velocity Z + z_coefs <- fit_velocity_pdf_bilateral(velocity$z, axis="z") + # ACF X + x_coefs <- fit_velocity_acf(velocity$x, plot=TRUE, axis="x") + cumulative_data[new_row, "acf_x_a"] = x_coefs[[1]] + cumulative_data[new_row, "acf_x_b"] = x_coefs[[2]] + cumulative_data[new_row, "acf_x_c"] = x_coefs[[3]] + y_coefs <- fit_velocity_acf(velocity$y, plot=TRUE, axis="y") + cumulative_data[new_row, "acf_y_a"] = y_coefs[[1]] + cumulative_data[new_row, "acf_y_b"] = y_coefs[[2]] + cumulative_data[new_row, "acf_y_c"] = y_coefs[[3]] + + direction_coefs <- fit_direction(velocity$direction, direction_mode, plot=TRUE) + print(direction_coefs) + + old_mar = par("mar") + direction_hist <- hist(velocity$direction, plot=FALSE, breaks=100) + direction_hist <- data.frame(direction=direction_hist$density, angle=direction_hist$mids) + polar.plot(direction_hist$direction,rad2deg(direction_hist$angle), + start=45,clockwise=TRUE,rp.type="polygon") + par(mar=old_mar) + + cumulative_data[new_row, "abs_x_mode"] = abs(x_mode) + cumulative_data[new_row, "x_sd"] = sd(velocity$x) + cumulative_data[new_row, "y_mean"] = mean(velocity$y) + i <- i + 1 + setTxtProgressBar(pb, i) +} +close(pb) + +print(cumulative_data) +print(summary(cumulative_data)) +model <- nls(x_sd ~ a*speed+b, + data=cumulative_data, + control=list(warnOnly=TRUE), + start=list(a=1,b=0)) +coefs <- summary(model)$coefficients +print(coefs) +x_sd_est <- sapply(cumulative_data$speed, function (x) { coefs[[1]]*x + coefs[[2]] }) +plot(cumulative_data$speed, cumulative_data$x_sd) +lines(cumulative_data$speed, x_sd_est, col='red') + +plot(cumulative_data$abs_x_mode, cumulative_data$acf_x_b) +#plot(cumulative_data$acf_x_b, cumulative_data$y_mean/tan(cumulative_data$direction)) +#plot(cumulative_data$speed, cumulative_data$acf_x_b) +#plot(cumulative_data$direction, cumulative_data$acf_x_b) +model <- nls(acf_x_b ~ a1*abs_x_mode+b1, + data=cumulative_data, + control=list(warnOnly=TRUE), + start=list(a1=1,b1=0), + algorithm="port", + lower=c(-1000,-1000), upper=c(1000,1000)) +coefs <- summary(model)$coefficients +print(coefs) +b_est <- sapply(cumulative_data$abs_x_mode, function (x) { coefs[[1]]*x + coefs[[2]] }) +lines(cumulative_data$abs_x_mode, b_est, col='red') + + +cumulative_data$abs_x_mode_acf_x_c <- cumulative_data$abs_x_mode**-cumulative_data$acf_x_c +plot(cumulative_data$abs_x_mode_acf_x_c, exp(-cumulative_data$acf_x_b**(cumulative_data$acf_x_c))) +model <- nls(exp(-acf_x_b**acf_x_c) ~ abs(a1*abs_x_mode_acf_x_c+b1), + data=cumulative_data, + control=list(warnOnly=TRUE), + start=list(a1=1,b1=0), + algorithm="port", + lower=c(-1000,-1000), upper=c(1000,1000)) +coefs <- summary(model)$coefficients +print(coefs) +#bc_est <- sapply(cumulative_data$abs_x_mode, function (x) { (coefs[[1]]*x + coefs[[2]]) }) +cumulative_data <- cumulative_data[order(cumulative_data$abs_x_mode_acf_x_c), ] +bc_est <- with (cumulative_data, { + (coefs[[1]]*abs_x_mode_acf_x_c + coefs[[2]]) +}) +lines(cumulative_data$abs_x_mode_acf_x_c, bc_est, col='red') + + + +#plot(cumulative_data$x_mode, cumulative_data$c) +#plot(cumulative_data$x_mode, cumulative_data$acf_x_b**cumulative_data$c) + +#plot(sign(cumulative_data$x_mode)*(cumulative_data$x_mode)**2, cumulative_data$c) +#plot(sign(cumulative_data$x_mode)*sqrt(abs(cumulative_data$x_mode)), cumulative_data$c) +#plot(log(cumulative_data$speed), cumulative_data$c) +#plot(cumulative_data$direction, cumulative_data$x_b) +#plot(cumulative_data$direction, cumulative_data$y_b) +#plot(cumulative_data$direction, cumulative_data$acf_x_b) +#plot(cumulative_data$direction, cumulative_data$acf_y_b) +plot(cumulative_data$abs_x_mode, cumulative_data$x_c) +plot(cumulative_data$abs_x_mode, cumulative_data$acf_x_c) +#cumulative_data$x_b <- ifelse(cumulative_data$x_b > 10, 1, cumulative_data$x_b) +#print(summary(cumulative_data$x_b)) +with (cumulative_data, { + plot((abs_x_mode**-acf_x_c), exp(-x_b**(x_c))) + plot((abs_x_mode**-acf_x_c), exp(-acf_x_b**(acf_x_c))) + plot(direction, direction(acf_x_b**acf_x_c, acf_y_b**acf_x_c)) + plot(direction, direction(x_b**acf_x_c, y_b**acf_x_c)) +}) + +dbDisconnect(mydb) diff --git a/R/calibrate.R b/R/calibrate.R @@ -0,0 +1,36 @@ +# https://stackoverflow.com/questions/13023274/how-to-do-printf-in-r +printf <- function(...) cat(sprintf(...)) + +reference_value <- 2.045 # measured with commercial anemometer + +calc_origin <- function (filename="anemometer-no-wind") { + data <- read.table(filename, sep="", header=FALSE) + names(data) <- c("t", "x", "y", "z", "sx", "sy", "sz") + origin = list(x=mean(data$x), y=mean(data$y), z=mean(data$z)) + origin +} + +my_sqrt <- function (x) { sign(x) * sqrt(abs(x)) } + +calc_coefficient <- function (filename, axis) { + origin <- calc_origin(sprintf("%s-origin",filename)) + data <- read.table(filename, sep="", header=FALSE) + names(data) <- c("t", "x", "y", "z", "sx", "sy", "sz") + sign <- data[1,sprintf("s%s",axis)] + sign*my_sqrt(mean(data[[axis]])-origin[[axis]])/reference_value +} + +coefficient_x <- calc_coefficient("build/x", "x") +coefficient_x_reverse <- calc_coefficient("build/x-reverse", "x") +coefficient_y <- calc_coefficient("build/y", "y") +coefficient_y_reverse <- calc_coefficient("build/y-reverse", "y") +coefficient_z <- calc_coefficient("build/z", "z") +coefficient_z_reverse <- calc_coefficient("build/z-reverse", "z") +printf("-1 m/s is x %f y %f z %f\n", coefficient_x, coefficient_y, coefficient_z) +printf("1 m/s is x %f y %f z %f\n", coefficient_x_reverse, coefficient_y_reverse, coefficient_z_reverse) + +weight_0 = (calc_origin("build/z-fan")$z - calc_origin("build/z-fan-origin")$z) +weight_1 = (calc_origin("build/z-fan-and-wind")$z - calc_origin("build/z-fan-and-wind-origin")$z) +print(weight_0) +print(weight_1) +print(my_sqrt(weight_1-weight_0)/reference_value) diff --git a/anemometer-wind/2/x b/anemometer-wind/2/x @@ -0,0 +1,46 @@ +20.840448 8366354 8411877 8577167 1 -1 -1 +21.938175 8366219 8411824 8577157 1 -1 -1 +23.035904 8366279 8411848 8577154 1 -1 -1 +24.133633 8366375 8411824 8577146 1 -1 -1 +25.231359 8366245 8411822 8577157 1 -1 -1 +26.329088 8366274 8411868 8577111 1 -1 -1 +27.426817 8366309 8411829 8577174 1 -1 -1 +28.524544 8366298 8411835 8577115 1 -1 -1 +29.622272 8366348 8411846 8577131 1 -1 -1 +30.719999 8366163 8411828 8577166 1 -1 -1 +31.817728 8366128 8411826 8577140 1 -1 -1 +32.915455 8366286 8411862 8577141 1 -1 -1 +34.013184 8366272 8411849 8577123 1 -1 -1 +35.110912 8366259 8411876 8577145 1 -1 -1 +36.208641 8366317 8411894 8577174 1 -1 -1 +37.306370 8366264 8411869 8577087 1 -1 -1 +38.404095 8366254 8411837 8577117 1 -1 -1 +39.501823 8366294 8411817 8577133 1 -1 -1 +40.599552 8366204 8411869 8577096 1 -1 -1 +41.697281 8366284 8411835 8577136 1 -1 -1 +42.795010 8366302 8411839 8577113 1 -1 -1 +43.892735 8366319 8411879 8577145 1 -1 -1 +44.990463 8366296 8411816 8577133 1 -1 -1 +46.088192 8366350 8411848 8577142 1 -1 -1 +47.185921 8366375 8411876 8577158 1 -1 -1 +48.283649 8366312 8411852 8577099 1 -1 -1 +49.381374 8366303 8411834 8577100 1 -1 -1 +50.479103 8366326 8411826 8577114 1 -1 -1 +51.576832 8366300 8411853 8577132 1 -1 -1 +52.674561 8366250 8411851 8577127 1 -1 -1 +53.772289 8366306 8411913 8577103 1 -1 -1 +54.861824 8366290 8411837 8577128 1 -1 -1 +55.959549 8366276 8411846 8577137 1 -1 -1 +57.057281 8366335 8411825 8577143 1 -1 -1 +58.155006 8366288 8411868 8577164 1 -1 -1 +59.252739 8366327 8411879 8577145 1 -1 -1 +60.342274 8366287 8411821 8577110 1 -1 -1 +61.439999 8366279 8411861 8577107 1 -1 -1 +62.537727 8366321 8411828 8577116 1 -1 -1 +63.635456 8366338 8411829 8577162 1 -1 -1 +64.733185 8366274 8411842 8577117 1 -1 -1 +65.830910 8366274 8411867 8577133 1 -1 -1 +66.928642 8366267 8411840 8577123 1 -1 -1 +68.026367 8366289 8411861 8577143 1 -1 -1 +69.124100 8366328 8411784 8577123 1 -1 -1 +70.221825 8366288 8411840 8577112 1 -1 -1 diff --git a/anemometer-wind/2/x-origin b/anemometer-wind/2/x-origin @@ -0,0 +1,39 @@ +1.081344 8366744 8411845 8577191 1 -1 -1 +2.179072 8366759 8411836 8577133 1 -1 -1 +3.276800 8366728 8411859 8577121 1 -1 -1 +4.374528 8366731 8411855 8577157 1 -1 -1 +5.472256 8366724 8411791 8577130 1 -1 -1 +6.569984 8366733 8411807 8577161 1 -1 -1 +7.667712 8366700 8411850 8577121 1 -1 -1 +8.765440 8366747 8411875 8577134 1 -1 -1 +9.863168 8366759 8411834 8577153 1 -1 -1 +10.960896 8366738 8411890 8577143 1 -1 -1 +12.058624 8366732 8411861 8577142 1 -1 -1 +13.156352 8366786 8411842 8577203 1 -1 -1 +14.254080 8366760 8411840 8577121 1 -1 -1 +15.351808 8366745 8411852 8577147 1 -1 -1 +16.449535 8366755 8411849 8577164 1 -1 -1 +17.547264 8366744 8411868 8577159 1 -1 -1 +18.644993 8366739 8411890 8577174 1 -1 -1 +19.742720 8366733 8411848 8577115 1 -1 -1 +71.319550 8366702 8411813 8577135 1 -1 -1 +72.417282 8366763 8411838 8577111 1 -1 -1 +73.515007 8366777 8411875 8577094 1 -1 -1 +74.612740 8366762 8411855 8577126 1 -1 -1 +75.710464 8366731 8411888 8577131 1 -1 -1 +76.808189 8366744 8411849 8577094 1 -1 -1 +77.905922 8366759 8411821 8577150 1 -1 -1 +79.003647 8366774 8411852 8577131 1 -1 -1 +80.101379 8366764 8411836 8577087 1 -1 -1 +81.199104 8366742 8411850 8577111 1 -1 -1 +82.296829 8366775 8411881 8577111 1 -1 -1 +83.394562 8366760 8411891 8577082 1 -1 -1 +84.492287 8366765 8411882 8577120 1 -1 -1 +85.590019 8366770 8411871 8577138 1 -1 -1 +86.687744 8366785 8411818 8577094 1 -1 -1 +87.785469 8366759 8411851 8577072 1 -1 -1 +88.883202 8366735 8411864 8577107 1 -1 -1 +89.980927 8366789 8411870 8577097 1 -1 -1 +91.078659 8366766 8411835 8577105 1 -1 -1 +92.176384 8366813 8411862 8577128 1 -1 -1 +93.274109 8366749 8411877 8577102 1 -1 -1 diff --git a/anemometer-wind/2/x-reverse b/anemometer-wind/2/x-reverse @@ -0,0 +1,25 @@ +37.306370 8367369 8411869 8576835 1 -1 -1 +38.404095 8367246 8411874 8576800 1 -1 -1 +39.501823 8367240 8411905 8576812 1 -1 -1 +40.599552 8367321 8411871 8576880 1 -1 -1 +41.697281 8367461 8411887 8576891 1 -1 -1 +42.795010 8367275 8411854 8576837 1 -1 -1 +43.892735 8367442 8411871 8576812 1 -1 -1 +44.990463 8367464 8411901 8576826 1 -1 -1 +46.088192 8367419 8411935 8576823 1 -1 -1 +47.185921 8367364 8411866 8576879 1 -1 -1 +48.283649 8367441 8411847 8576837 1 -1 -1 +49.381374 8367461 8411869 8576892 1 -1 -1 +50.479103 8367417 8411905 8576868 1 -1 -1 +51.576832 8367301 8411885 8576870 1 -1 -1 +52.674561 8367492 8411881 8576849 1 -1 -1 +53.772289 8367448 8411905 8576869 1 -1 -1 +54.861824 8367467 8411879 8576862 1 -1 -1 +55.959549 8367307 8411909 8576836 1 -1 -1 +57.057281 8367352 8411895 8576861 1 -1 -1 +58.155006 8367291 8411866 8576881 1 -1 -1 +59.252739 8367164 8411889 8576872 1 -1 -1 +60.342274 8367443 8411871 8576854 1 -1 -1 +61.439999 8367601 8411900 8576807 1 -1 -1 +62.537727 8367483 8411903 8576868 1 -1 -1 +63.635456 8367457 8411915 8576848 1 -1 -1 diff --git a/anemometer-wind/2/x-reverse-origin b/anemometer-wind/2/x-reverse-origin @@ -0,0 +1,41 @@ +1.081344 8366885 8411846 8576840 1 -1 -1 +2.179072 8366932 8411877 8576906 1 -1 -1 +3.276800 8366861 8411892 8576907 1 -1 -1 +4.374528 8366833 8411893 8576885 1 -1 -1 +5.472256 8366873 8411863 8576883 1 -1 -1 +6.569984 8366834 8411892 8576859 1 -1 -1 +7.667712 8366842 8411882 8576868 1 -1 -1 +8.765440 8366833 8411859 8576867 1 -1 -1 +9.863168 8366895 8411879 8576873 1 -1 -1 +10.960896 8366860 8411860 8576862 1 -1 -1 +12.058624 8366842 8411876 8576823 1 -1 -1 +13.156352 8366816 8411870 8576874 1 -1 -1 +14.254080 8366839 8411852 8576878 1 -1 -1 +15.351808 8366902 8411845 8576842 1 -1 -1 +16.449535 8366909 8411865 8576896 1 -1 -1 +17.547264 8366851 8411860 8576875 1 -1 -1 +18.644993 8366923 8411880 8576892 1 -1 -1 +19.742720 8366889 8411859 8576870 1 -1 -1 +20.840448 8366843 8411876 8576906 1 -1 -1 +21.938175 8366887 8411862 8576888 1 -1 -1 +23.035904 8366846 8411868 8576896 1 -1 -1 +24.133633 8366897 8411899 8576853 1 -1 -1 +25.231359 8366926 8411859 8576890 1 -1 -1 +26.329088 8366827 8411818 8576890 1 -1 -1 +27.426817 8366886 8411897 8576844 1 -1 -1 +28.524544 8366866 8411868 8576818 1 -1 -1 +29.622272 8366887 8411887 8576891 1 -1 -1 +30.719999 8366846 8411904 8576879 1 -1 -1 +31.817728 8366894 8411857 8576832 1 -1 -1 +32.915455 8366857 8411888 8576884 1 -1 -1 +34.013184 8366896 8411867 8576884 1 -1 -1 +35.110912 8366867 8411916 8576885 1 -1 -1 +36.208641 8367040 8411883 8576860 1 -1 -1 +64.733185 8366904 8411863 8576821 1 -1 -1 +65.830910 8366916 8411884 8576850 1 -1 -1 +66.928642 8366825 8411845 8576830 1 -1 -1 +68.026367 8366850 8411863 8576850 1 -1 -1 +69.124100 8366880 8411820 8576834 1 -1 -1 +70.221825 8366876 8411882 8576837 1 -1 -1 +71.319550 8366860 8411910 8576846 1 -1 -1 +72.417282 8366880 8411844 8576812 1 -1 -1 diff --git a/anemometer-wind/2/y b/anemometer-wind/2/y @@ -0,0 +1,27 @@ +44.990463 8366983 8412261 8576655 1 -1 -1 +46.088192 8366993 8412328 8576602 1 -1 -1 +47.185921 8367032 8412420 8576608 1 -1 -1 +48.283649 8366954 8412511 8576650 1 -1 -1 +49.381374 8366965 8412454 8576636 1 -1 -1 +50.479103 8366951 8412487 8576635 1 -1 -1 +51.576832 8366994 8412478 8576631 1 -1 -1 +52.674561 8366931 8412523 8576597 1 -1 -1 +53.772289 8366983 8412410 8576606 1 -1 -1 +54.870014 8366954 8412310 8576629 1 -1 -1 +55.959549 8366961 8412306 8576616 1 -1 -1 +57.057281 8366964 8412592 8576627 1 -1 -1 +58.155006 8367002 8412543 8576617 1 -1 -1 +59.252739 8366963 8412423 8576615 1 -1 -1 +60.342274 8366961 8412593 8576583 1 -1 -1 +61.439999 8366965 8412502 8576634 1 -1 -1 +62.537727 8366973 8412378 8576634 1 -1 -1 +63.635456 8366958 8412453 8576588 1 -1 -1 +64.733185 8366949 8412454 8576619 1 -1 -1 +65.830910 8366963 8412419 8576595 1 -1 -1 +66.928642 8366958 8412411 8576613 1 -1 -1 +68.026367 8366961 8412333 8576572 1 -1 -1 +69.124100 8367008 8412300 8576574 1 -1 -1 +70.221825 8366916 8412319 8576633 1 -1 -1 +71.319550 8366939 8412335 8576591 1 -1 -1 +72.417282 8366962 8412430 8576620 1 -1 -1 +73.515007 8367047 8412404 8576611 1 -1 -1 diff --git a/anemometer-wind/2/y-origin b/anemometer-wind/2/y-origin @@ -0,0 +1,48 @@ +1.081344 8366951 8411893 8576667 1 -1 -1 +2.179072 8366951 8411936 8576680 1 -1 -1 +3.276800 8366952 8411900 8576665 1 -1 -1 +4.374528 8366953 8411904 8576692 1 -1 -1 +5.472256 8366952 8411873 8576641 1 -1 -1 +6.569984 8366956 8411912 8576649 1 -1 -1 +7.667712 8366969 8411884 8576645 1 -1 -1 +8.765440 8366964 8411895 8576630 1 -1 -1 +9.863168 8366975 8411906 8576616 1 -1 -1 +10.960896 8366932 8411927 8576604 1 -1 -1 +12.058624 8366973 8411908 8576678 1 -1 -1 +13.156352 8366939 8411933 8576639 1 -1 -1 +14.254080 8366996 8411902 8576660 1 -1 -1 +15.351808 8367022 8411870 8576712 1 -1 -1 +16.449535 8366975 8411911 8576630 1 -1 -1 +17.547264 8366946 8411874 8576663 1 -1 -1 +18.644993 8366949 8411875 8576665 1 -1 -1 +19.742720 8366948 8411857 8576625 1 -1 -1 +20.840448 8366956 8411901 8576640 1 -1 -1 +21.938175 8366959 8411901 8576616 1 -1 -1 +23.035904 8366947 8411910 8576607 1 -1 -1 +24.133633 8366950 8411922 8576668 1 -1 -1 +25.231359 8366920 8411909 8576645 1 -1 -1 +26.329088 8366936 8411933 8576633 1 -1 -1 +27.426817 8366997 8411891 8576657 1 -1 -1 +28.524544 8367004 8411898 8576629 1 -1 -1 +29.622272 8366942 8411880 8576635 1 -1 -1 +30.719999 8366975 8411847 8576672 1 -1 -1 +31.817728 8366955 8411895 8576656 1 -1 -1 +32.915455 8366906 8411924 8576666 1 -1 -1 +34.013184 8366993 8411891 8576619 1 -1 -1 +35.110912 8366955 8411894 8576629 1 -1 -1 +36.208641 8366999 8411888 8576692 1 -1 -1 +37.306370 8366948 8411940 8576642 1 -1 -1 +38.404095 8366990 8411920 8576623 1 -1 -1 +39.501823 8366976 8411918 8576646 1 -1 -1 +40.599552 8366981 8411883 8576684 1 -1 -1 +41.697281 8366970 8411933 8576621 1 -1 -1 +42.795010 8366943 8411926 8576644 1 -1 -1 +43.892735 8366967 8411859 8576623 1 -1 -1 +74.612740 8366979 8411883 8576639 1 -1 -1 +75.710464 8366941 8411954 8576581 1 -1 -1 +76.808189 8366985 8411865 8576590 1 -1 -1 +77.905922 8366979 8411893 8576595 1 -1 -1 +79.003647 8366945 8411934 8576566 1 -1 -1 +80.101379 8366964 8411863 8576599 1 -1 -1 +81.199104 8366977 8411895 8576586 1 -1 -1 +82.296829 8366981 8411909 8576602 1 -1 -1 diff --git a/anemometer-wind/2/y-reverse b/anemometer-wind/2/y-reverse @@ -0,0 +1,40 @@ +37.306370 8366966 8411396 8576527 1 -1 -1 +38.404095 8367017 8411473 8576570 1 -1 -1 +39.501823 8366994 8411571 8576558 1 -1 -1 +40.599552 8366997 8411442 8576454 1 -1 -1 +41.697281 8366988 8411575 8576509 1 -1 -1 +42.795010 8367012 8411507 8576545 1 -1 -1 +43.892735 8366989 8411386 8576522 1 -1 -1 +44.990463 8367022 8411348 8576525 1 -1 -1 +46.088192 8366988 8411461 8576541 1 -1 -1 +47.185921 8367004 8411613 8576512 1 -1 -1 +48.283649 8366983 8411457 8576522 1 -1 -1 +49.381374 8367000 8411347 8576516 1 -1 -1 +50.479103 8367059 8411344 8576533 1 -1 -1 +51.576832 8367049 8411392 8576485 1 -1 -1 +52.674561 8367026 8411456 8576550 1 -1 -1 +53.772289 8366988 8411404 8576517 1 -1 -1 +54.861824 8366997 8411502 8576510 1 -1 -1 +55.959549 8366990 8411539 8576509 1 -1 -1 +57.057281 8366990 8411342 8576485 1 -1 -1 +58.155006 8367019 8411394 8576531 1 -1 -1 +59.252739 8366966 8411370 8576495 1 -1 -1 +60.342274 8366973 8411311 8576522 1 -1 -1 +61.439999 8367047 8411293 8576497 1 -1 -1 +62.537727 8367014 8411397 8576482 1 -1 -1 +63.635456 8367020 8411304 8576527 1 -1 -1 +64.733185 8367018 8411298 8576508 1 -1 -1 +65.830910 8366957 8411274 8576498 1 -1 -1 +66.928642 8367006 8411306 8576491 1 -1 -1 +68.026367 8367015 8411286 8576529 1 -1 -1 +69.124100 8367039 8411345 8576470 1 -1 -1 +70.221825 8367039 8411401 8576486 1 -1 -1 +71.319550 8367042 8411409 8576493 1 -1 -1 +72.417282 8367020 8411362 8576470 1 -1 -1 +73.515007 8367020 8411360 8576475 1 -1 -1 +74.612740 8367026 8411527 8576508 1 -1 -1 +75.710464 8366977 8411504 8576492 1 -1 -1 +76.808189 8367003 8411361 8576508 1 -1 -1 +77.905922 8367053 8411462 8576527 1 -1 -1 +79.003647 8367003 8411301 8576488 1 -1 -1 +80.101379 8366997 8411332 8576461 1 -1 -1 diff --git a/anemometer-wind/2/y-reverse-origin b/anemometer-wind/2/y-reverse-origin @@ -0,0 +1,42 @@ +1.081344 8366994 8411890 8576572 1 -1 -1 +2.179072 8366986 8411895 8576554 1 -1 -1 +3.276800 8366986 8411925 8576564 1 -1 -1 +4.374528 8366955 8411933 8576506 1 -1 -1 +5.472256 8366992 8411955 8576552 1 -1 -1 +6.569984 8366990 8411892 8576535 1 -1 -1 +7.667712 8366971 8411904 8576556 1 -1 -1 +8.765440 8367036 8411906 8576561 1 -1 -1 +9.863168 8367002 8411889 8576544 1 -1 -1 +10.960896 8366984 8411911 8576555 1 -1 -1 +12.058624 8367030 8411864 8576537 1 -1 -1 +13.156352 8366986 8411896 8576555 1 -1 -1 +14.254080 8366964 8411906 8576551 1 -1 -1 +15.351808 8367035 8411955 8576581 1 -1 -1 +16.449535 8366992 8411918 8576569 1 -1 -1 +17.547264 8367036 8411936 8576533 1 -1 -1 +18.644993 8367022 8411934 8576574 1 -1 -1 +19.742720 8367030 8411923 8576523 1 -1 -1 +20.840448 8367001 8411920 8576524 1 -1 -1 +21.938175 8366966 8411891 8576538 1 -1 -1 +23.035904 8366997 8411893 8576541 1 -1 -1 +24.133633 8367008 8411929 8576522 1 -1 -1 +25.231359 8366983 8411913 8576586 1 -1 -1 +26.329088 8367031 8411943 8576512 1 -1 -1 +27.426817 8367025 8411916 8576517 1 -1 -1 +28.524544 8367001 8411939 8576532 1 -1 -1 +29.622272 8366993 8411950 8576524 1 -1 -1 +30.719999 8367023 8411892 8576532 1 -1 -1 +31.817728 8366942 8411908 8576551 1 -1 -1 +32.915455 8367030 8411920 8576551 1 -1 -1 +34.013184 8367028 8411950 8576577 1 -1 -1 +35.110912 8367022 8411915 8576513 1 -1 -1 +36.208641 8367055 8411592 8576514 1 -1 -1 +81.199104 8367009 8411832 8576488 1 -1 -1 +82.296829 8366989 8411854 8576490 1 -1 -1 +83.394562 8367049 8411908 8576478 1 -1 -1 +84.492287 8367022 8411907 8576477 1 -1 -1 +85.590019 8366990 8411914 8576449 1 -1 -1 +86.687744 8366987 8411937 8576498 1 -1 -1 +87.785469 8367012 8411928 8576504 1 -1 -1 +88.883202 8367037 8411908 8576493 1 -1 -1 +89.980927 8366996 8411911 8576537 1 -1 -1 diff --git a/anemometer-wind/2/z b/anemometer-wind/2/z @@ -0,0 +1,22 @@ +35.110912 8367040 8411969 8577306 1 -1 -1 +36.208641 8367060 8411907 8577325 1 -1 -1 +37.306370 8367035 8411958 8577262 1 -1 -1 +38.404095 8367019 8411899 8577268 1 -1 -1 +39.501823 8367049 8411929 8577265 1 -1 -1 +40.599552 8367064 8411972 8577190 1 -1 -1 +41.697281 8367003 8411899 8577280 1 -1 -1 +42.795010 8367014 8411944 8577277 1 -1 -1 +43.892735 8367010 8411912 8577316 1 -1 -1 +44.990463 8367070 8412002 8577290 1 -1 -1 +46.088192 8367046 8411955 8577272 1 -1 -1 +47.185921 8367101 8411944 8577307 1 -1 -1 +48.283649 8367114 8411962 8577236 1 -1 -1 +49.381374 8367035 8412003 8577218 1 -1 -1 +50.479103 8367075 8411936 8577317 1 -1 -1 +51.576832 8367051 8411942 8577234 1 -1 -1 +52.674561 8367082 8411985 8577207 1 -1 -1 +53.772289 8367007 8411952 8577266 1 -1 -1 +54.870014 8367053 8411976 8577263 1 -1 -1 +55.959549 8367112 8411932 8577192 1 -1 -1 +57.057281 8367074 8411895 8577305 1 -1 -1 +58.155006 8367035 8411973 8577211 1 -1 -1 diff --git a/anemometer-wind/2/z-origin b/anemometer-wind/2/z-origin @@ -0,0 +1,32 @@ +7.667712 8367076 8411930 8576338 1 -1 -1 +1.081344 8367029 8411947 8576334 1 -1 -1 +2.179072 8367065 8411910 8576379 1 -1 -1 +3.276800 8367121 8411921 8576373 1 -1 -1 +4.374528 8367025 8411967 8576333 1 -1 -1 +5.472256 8367042 8411921 8576343 1 -1 -1 +6.569984 8367100 8411952 8576345 1 -1 -1 +7.667712 8367053 8411973 8576331 1 -1 -1 +8.765440 8367041 8411965 8576351 1 -1 -1 +9.863168 8367093 8411958 8576344 1 -1 -1 +10.960896 8367072 8411969 8576380 1 -1 -1 +12.058624 8367081 8411960 8576314 1 -1 -1 +13.156352 8367087 8411969 8576347 1 -1 -1 +14.254080 8367105 8411955 8576304 1 -1 -1 +15.351808 8367107 8411984 8576421 1 -1 -1 +16.449535 8367093 8411957 8576314 1 -1 -1 +17.547264 8367095 8411951 8576356 1 -1 -1 +18.644993 8367048 8411949 8576340 1 -1 -1 +19.742720 8367052 8411965 8576275 1 -1 -1 +20.840448 8367076 8411964 8576326 1 -1 -1 +21.938175 8367088 8411974 8576354 1 -1 -1 +23.035904 8367094 8411942 8576335 1 -1 -1 +24.133633 8367131 8411963 8576334 1 -1 -1 +25.231359 8367078 8411932 8576343 1 -1 -1 +26.329088 8367053 8411962 8576324 1 -1 -1 +27.426817 8367062 8411968 8576361 1 -1 -1 +28.524544 8367073 8411958 8576325 1 -1 -1 +29.622272 8367093 8411976 8576279 1 -1 -1 +30.719999 8367055 8411979 8576360 1 -1 -1 +31.817728 8367072 8411986 8576315 1 -1 -1 +32.915455 8367060 8411946 8576323 1 -1 -1 +34.013184 8367039 8411959 8576854 1 -1 -1 diff --git a/anemometer-wind/2/z-reverse b/anemometer-wind/2/z-reverse @@ -0,0 +1,25 @@ +31.817728 8367078 8411978 8575763 1 -1 -1 +32.915455 8367064 8411974 8575379 1 -1 -1 +34.013184 8367105 8411953 8575377 1 -1 -1 +35.110912 8367104 8411930 8575320 1 -1 -1 +36.208641 8367106 8412002 8575264 1 -1 -1 +37.306370 8367046 8411928 8575251 1 -1 -1 +38.404095 8367065 8411925 8575219 1 -1 -1 +39.501823 8367161 8411970 8575249 1 -1 -1 +40.599552 8367081 8411937 8575320 1 -1 -1 +41.697281 8367098 8411990 8575276 1 -1 -1 +42.795010 8367034 8411979 8575307 1 -1 -1 +43.892735 8367093 8411931 8575327 1 -1 -1 +44.990463 8367106 8411961 8575343 1 -1 -1 +46.088192 8367079 8411927 8575367 1 -1 -1 +47.185921 8367089 8411970 8575421 1 -1 -1 +48.283649 8367042 8411977 8575473 1 -1 -1 +49.381374 8367056 8411955 8575551 1 -1 -1 +50.479103 8367072 8411905 8575529 1 -1 -1 +51.576832 8367074 8411949 8575567 1 -1 -1 +52.674561 8367101 8411983 8575640 1 -1 -1 +53.772289 8367102 8411966 8575526 1 -1 -1 +54.861824 8367058 8411964 8575462 1 -1 -1 +55.959549 8367061 8411957 8575476 1 -1 -1 +57.057281 8367101 8411933 8575505 1 -1 -1 +58.155006 8367073 8411967 8575505 1 -1 -1 diff --git a/anemometer-wind/2/z-reverse-origin b/anemometer-wind/2/z-reverse-origin @@ -0,0 +1,28 @@ +1.081344 8367118 8411970 8576324 1 -1 -1 +2.179072 8367108 8411961 8576274 1 -1 -1 +3.276800 8367087 8411945 8576288 1 -1 -1 +4.374528 8367099 8411975 8576266 1 -1 -1 +5.472256 8367092 8411926 8576254 1 -1 -1 +6.569984 8367074 8411941 8576303 1 -1 -1 +7.667712 8367087 8411931 8576305 1 -1 -1 +8.765440 8367090 8411964 8576280 1 -1 -1 +9.863168 8367022 8411948 8576247 1 -1 -1 +10.960896 8367039 8411962 8576257 1 -1 -1 +12.058624 8367100 8411970 8576290 1 -1 -1 +13.156352 8367068 8411976 8576328 1 -1 -1 +14.254080 8367093 8412008 8576259 1 -1 -1 +15.351808 8367092 8411976 8576301 1 -1 -1 +16.449535 8367110 8412005 8576274 1 -1 -1 +17.547264 8367096 8411946 8576252 1 -1 -1 +18.644993 8367053 8411978 8576309 1 -1 -1 +19.742720 8367080 8411959 8576308 1 -1 -1 +20.840448 8367068 8411978 8576306 1 -1 -1 +21.938175 8367086 8411947 8576318 1 -1 -1 +23.035904 8367103 8411983 8576243 1 -1 -1 +24.133633 8367108 8411941 8576291 1 -1 -1 +25.231359 8367113 8411920 8576284 1 -1 -1 +26.329088 8367065 8411987 8576298 1 -1 -1 +27.426817 8367016 8411950 8576272 1 -1 -1 +28.524544 8367066 8411973 8576293 1 -1 -1 +29.622272 8367080 8411994 8576293 1 -1 -1 +30.719999 8367056 8411899 8576299 1 -1 -1 diff --git a/anemometer-wind/3/x b/anemometer-wind/3/x @@ -0,0 +1,25 @@ +31.817728 8366931 8411949 8576191 1 -1 -1 +32.915455 8366718 8412027 8576183 1 -1 -1 +34.013184 8366748 8412023 8576178 1 -1 -1 +35.110912 8366718 8411971 8576221 1 -1 -1 +36.208641 8366793 8412005 8576183 1 -1 -1 +37.306370 8366465 8411949 8576180 1 -1 -1 +38.404095 8366495 8411973 8576173 1 -1 -1 +39.501823 8366506 8411981 8576168 1 -1 -1 +40.599552 8366517 8411960 8576180 1 -1 -1 +41.697281 8366517 8411954 8576150 1 -1 -1 +42.795010 8366578 8411992 8576219 1 -1 -1 +43.892735 8366480 8412030 8576172 1 -1 -1 +44.990463 8366593 8411920 8576176 1 -1 -1 +46.088192 8366561 8411940 8576156 1 -1 -1 +47.185921 8366551 8411972 8576201 1 -1 -1 +48.283649 8366557 8411975 8576221 1 -1 -1 +49.381374 8366574 8411983 8576158 1 -1 -1 +50.479103 8366587 8411965 8576155 1 -1 -1 +51.576832 8366577 8411990 8576184 1 -1 -1 +52.674561 8366595 8411924 8576173 1 -1 -1 +53.772289 8366581 8411984 8576224 1 -1 -1 +54.861824 8366519 8411954 8576126 1 -1 -1 +55.959549 8366535 8411989 8576214 1 -1 -1 +57.057281 8366490 8411989 8576195 1 -1 -1 +58.155006 8366523 8411956 8576178 1 -1 -1 diff --git a/anemometer-wind/3/x-origin b/anemometer-wind/3/x-origin @@ -0,0 +1,28 @@ +1.081344 8367076 8411991 8576216 1 -1 -1 +2.179072 8367087 8411966 8576196 1 -1 -1 +3.276800 8367110 8411960 8576205 1 -1 -1 +4.374528 8367134 8412012 8576224 1 -1 -1 +5.472256 8367068 8411925 8576216 1 -1 -1 +6.569984 8367066 8411967 8576220 1 -1 -1 +7.667712 8367143 8411978 8576189 1 -1 -1 +8.765440 8367078 8411965 8576166 1 -1 -1 +9.863168 8367119 8412020 8576213 1 -1 -1 +10.960896 8367095 8411941 8576157 1 -1 -1 +12.058624 8367160 8412047 8576217 1 -1 -1 +13.156352 8367144 8411943 8576170 1 -1 -1 +14.254080 8367052 8411946 8576212 1 -1 -1 +15.351808 8367123 8411969 8576160 1 -1 -1 +16.449535 8367123 8411964 8576178 1 -1 -1 +17.547264 8367105 8411986 8576205 1 -1 -1 +18.644993 8367096 8411945 8576210 1 -1 -1 +19.742720 8367125 8411922 8576220 1 -1 -1 +20.840448 8367123 8411939 8576190 1 -1 -1 +21.938175 8367106 8411951 8576149 1 -1 -1 +23.035904 8367176 8412014 8576222 1 -1 -1 +24.133633 8367055 8411950 8576190 1 -1 -1 +25.231359 8367125 8411979 8576201 1 -1 -1 +26.329088 8367134 8411965 8576207 1 -1 -1 +27.426817 8367120 8411990 8576162 1 -1 -1 +28.524544 8367086 8411962 8576179 1 -1 -1 +29.622272 8367089 8411992 8576157 1 -1 -1 +30.719999 8367097 8412014 8576168 1 -1 -1 diff --git a/anemometer-wind/3/x-reverse b/anemometer-wind/3/x-reverse @@ -0,0 +1,25 @@ +31.817728 8367728 8412012 8576054 1 -1 -1 +32.915455 8367788 8411947 8576035 1 -1 -1 +34.013184 8367708 8412021 8576080 1 -1 -1 +35.110912 8367794 8412018 8576113 1 -1 -1 +36.208641 8367874 8411992 8576062 1 -1 -1 +37.306370 8367764 8411973 8576041 1 -1 -1 +38.404095 8367718 8412042 8576049 1 -1 -1 +39.501823 8367695 8411987 8576065 1 -1 -1 +40.599552 8367771 8412012 8576084 1 -1 -1 +41.697281 8367690 8412002 8576091 1 -1 -1 +42.795010 8367660 8412016 8576067 1 -1 -1 +43.892735 8367677 8411993 8576034 1 -1 -1 +44.990463 8367668 8412024 8576080 1 -1 -1 +46.088192 8367642 8411990 8576065 1 -1 -1 +47.185921 8367603 8412040 8576066 1 -1 -1 +48.283649 8367684 8411994 8576070 1 -1 -1 +49.381374 8367695 8412004 8576042 1 -1 -1 +50.479103 8367743 8411995 8576054 1 -1 -1 +51.576832 8367721 8411962 8576103 1 -1 -1 +52.674561 8367722 8411971 8576064 1 -1 -1 +53.772289 8367747 8412005 8576055 1 -1 -1 +54.861824 8367730 8411958 8576104 1 -1 -1 +55.959549 8367902 8412019 8576077 1 -1 -1 +57.057281 8367864 8411953 8576087 1 -1 -1 +58.155006 8367798 8412042 8576046 1 -1 -1 diff --git a/anemometer-wind/3/x-reverse-origin b/anemometer-wind/3/x-reverse-origin @@ -0,0 +1,28 @@ +1.081344 8367114 8411964 8576095 1 -1 -1 +2.179072 8367094 8411993 8576117 1 -1 -1 +3.276800 8367149 8412014 8576075 1 -1 -1 +4.374528 8367126 8412029 8576059 1 -1 -1 +5.472256 8367125 8412016 8576092 1 -1 -1 +6.569984 8367116 8411985 8576103 1 -1 -1 +7.667712 8367132 8412028 8576067 1 -1 -1 +8.765440 8367140 8411997 8576087 1 -1 -1 +9.863168 8367207 8411992 8576071 1 -1 -1 +10.960896 8367131 8412023 8576085 1 -1 -1 +12.058624 8367164 8412064 8576080 1 -1 -1 +13.156352 8367114 8412041 8576030 1 -1 -1 +14.254080 8367119 8412036 8576046 1 -1 -1 +15.351808 8367112 8412021 8576059 1 -1 -1 +16.449535 8367120 8412013 8576077 1 -1 -1 +17.547264 8367144 8412005 8576092 1 -1 -1 +18.644993 8367129 8412039 8576081 1 -1 -1 +19.742720 8367136 8412015 8576088 1 -1 -1 +20.840448 8367168 8412013 8576113 1 -1 -1 +21.938175 8367094 8412028 8576064 1 -1 -1 +23.035904 8367129 8412030 8576040 1 -1 -1 +24.133633 8367159 8411999 8576092 1 -1 -1 +25.231359 8367118 8412013 8576053 1 -1 -1 +26.329088 8367140 8412009 8576116 1 -1 -1 +27.426817 8367150 8411957 8576110 1 -1 -1 +28.524544 8367149 8412003 8576089 1 -1 -1 +29.622272 8367123 8412028 8576098 1 -1 -1 +30.719999 8367152 8412061 8576051 1 -1 -1 diff --git a/anemometer-wind/3/y b/anemometer-wind/3/y @@ -0,0 +1,23 @@ +34.013184 8366410 8412517 8575484 1 -1 -1 +35.110912 8366723 8412567 8575486 1 -1 -1 +36.208641 8366819 8412702 8575465 1 -1 -1 +37.306370 8366835 8412831 8575454 1 -1 -1 +38.404095 8366728 8412820 8575450 1 -1 -1 +39.501823 8366890 8412673 8575449 1 -1 -1 +40.599552 8366896 8412644 8575459 1 -1 -1 +41.697281 8366830 8412594 8575456 1 -1 -1 +42.795010 8366838 8412623 8575417 1 -1 -1 +43.892735 8366877 8412655 8575445 1 -1 -1 +44.990463 8366704 8412652 8575444 1 -1 -1 +46.088192 8366864 8412686 8575448 1 -1 -1 +47.185921 8366750 8412683 8575445 1 -1 -1 +48.283649 8366731 8412735 8575394 1 -1 -1 +49.381374 8366505 8412726 8575465 1 -1 -1 +50.479103 8366751 8412723 8575456 1 -1 -1 +51.576832 8366749 8412863 8575448 1 -1 -1 +52.674561 8366799 8412769 8575464 1 -1 -1 +53.772289 8366852 8412666 8575468 1 -1 -1 +54.861824 8366889 8412706 8575472 1 -1 -1 +55.959549 8366802 8412714 8575428 1 -1 -1 +57.057281 8366752 8412660 8575428 1 -1 -1 +58.155006 8366749 8412724 8575446 1 -1 -1 diff --git a/anemometer-wind/3/y-origin b/anemometer-wind/3/y-origin @@ -0,0 +1,30 @@ +1.081344 8367158 8412113 8575510 1 -1 -1 +2.179072 8367202 8412143 8575476 1 -1 -1 +3.276800 8367227 8412141 8575471 1 -1 -1 +4.374528 8367193 8412202 8575500 1 -1 -1 +5.472256 8367200 8412119 8575499 1 -1 -1 +6.569984 8367208 8412178 8575490 1 -1 -1 +7.667712 8367238 8412140 8575447 1 -1 -1 +8.765440 8367227 8412180 8575472 1 -1 -1 +9.863168 8367227 8412123 8575457 1 -1 -1 +10.960896 8367195 8412168 8575471 1 -1 -1 +12.058624 8367220 8412172 8575472 1 -1 -1 +13.156352 8367199 8412177 8575449 1 -1 -1 +14.254080 8367189 8412164 8575455 1 -1 -1 +15.351808 8367184 8412214 8575474 1 -1 -1 +16.449535 8367212 8412176 8575478 1 -1 -1 +17.547264 8367194 8412180 8575475 1 -1 -1 +18.644993 8367179 8412216 8575466 1 -1 -1 +19.742720 8367236 8412171 8575479 1 -1 -1 +20.840448 8367169 8412182 8575473 1 -1 -1 +21.938175 8367178 8412167 8575407 1 -1 -1 +23.035904 8367167 8412124 8575455 1 -1 -1 +24.133633 8367186 8412163 8575491 1 -1 -1 +25.231359 8367238 8412139 8575455 1 -1 -1 +26.329088 8367189 8412176 8575468 1 -1 -1 +27.426817 8367234 8412218 8575425 1 -1 -1 +28.524544 8367208 8412193 8575463 1 -1 -1 +29.622272 8367213 8412117 8575449 1 -1 -1 +30.719999 8367174 8412192 8575460 1 -1 -1 +31.817728 8367219 8412199 8575452 1 -1 -1 +32.915455 8367239 8412256 8575496 1 -1 -1 diff --git a/anemometer-wind/3/y-reverse b/anemometer-wind/3/y-reverse @@ -0,0 +1,23 @@ +34.013184 8367174 8411898 8575375 1 -1 -1 +35.110912 8367215 8411698 8575410 1 -1 -1 +36.208641 8367201 8411615 8575393 1 -1 -1 +37.306370 8367154 8411536 8575415 1 -1 -1 +38.404095 8367239 8411739 8575371 1 -1 -1 +39.501823 8367270 8411674 8575402 1 -1 -1 +40.599552 8367195 8411672 8575414 1 -1 -1 +41.697281 8367211 8411600 8575374 1 -1 -1 +42.795010 8367212 8411563 8575402 1 -1 -1 +43.892735 8367199 8411652 8575378 1 -1 -1 +44.990463 8367181 8411643 8575401 1 -1 -1 +46.088192 8367196 8411596 8575387 1 -1 -1 +47.185921 8367206 8411530 8575404 1 -1 -1 +48.283649 8367199 8411502 8575452 1 -1 -1 +49.381374 8367239 8411666 8575416 1 -1 -1 +50.479103 8367216 8411632 8575378 1 -1 -1 +51.576832 8367252 8411571 8575374 1 -1 -1 +52.674561 8367226 8411643 8575348 1 -1 -1 +53.772289 8367196 8411618 8575382 1 -1 -1 +54.861824 8367259 8411650 8575377 1 -1 -1 +55.959549 8367204 8411636 8575388 1 -1 -1 +57.057281 8367219 8411621 8575394 1 -1 -1 +58.155006 8367193 8411611 8575395 1 -1 -1 diff --git a/anemometer-wind/3/y-reverse-origin b/anemometer-wind/3/y-reverse-origin @@ -0,0 +1,30 @@ +1.081344 8367266 8412188 8575420 1 -1 -1 +2.179072 8367244 8412204 8575405 1 -1 -1 +3.276800 8367241 8412136 8575414 1 -1 -1 +4.374528 8367191 8412188 8575396 1 -1 -1 +5.472256 8367215 8412184 8575401 1 -1 -1 +6.569984 8367204 8412196 8575459 1 -1 -1 +7.667712 8367200 8412184 8575453 1 -1 -1 +8.765440 8367207 8412189 8575433 1 -1 -1 +9.863168 8367222 8412205 8575437 1 -1 -1 +10.960896 8367213 8412190 8575426 1 -1 -1 +12.058624 8367199 8412159 8575414 1 -1 -1 +13.156352 8367193 8412110 8575409 1 -1 -1 +14.254080 8367182 8412197 8575422 1 -1 -1 +15.351808 8367188 8412202 8575402 1 -1 -1 +16.449535 8367207 8412178 8575459 1 -1 -1 +17.547264 8367207 8412182 8575469 1 -1 -1 +18.644993 8367236 8412213 8575394 1 -1 -1 +19.742720 8367227 8412164 8575401 1 -1 -1 +20.840448 8367194 8412151 8575407 1 -1 -1 +21.938175 8367198 8412144 8575415 1 -1 -1 +23.035904 8367216 8412241 8575366 1 -1 -1 +24.133633 8367187 8412188 8575389 1 -1 -1 +25.231359 8367164 8412228 8575367 1 -1 -1 +26.329088 8367234 8412205 8575452 1 -1 -1 +27.426817 8367228 8412182 8575455 1 -1 -1 +28.524544 8367221 8412204 8575417 1 -1 -1 +29.622272 8367210 8412238 8575453 1 -1 -1 +30.719999 8367234 8412137 8575419 1 -1 -1 +31.817728 8367212 8412214 8575437 1 -1 -1 +32.915455 8367184 8412229 8575430 1 -1 -1 diff --git a/anemometer-wind/3/z b/anemometer-wind/3/z @@ -0,0 +1,24 @@ +32.915455 8367291 8412240 8576121 1 -1 -1 +34.013184 8367211 8412263 8576159 1 -1 -1 +35.110912 8367250 8412171 8576149 1 -1 -1 +36.208641 8367244 8412225 8576225 1 -1 -1 +37.306370 8367205 8412195 8576199 1 -1 -1 +38.404095 8367211 8412199 8576201 1 -1 -1 +39.501823 8367176 8412189 8576288 1 -1 -1 +40.599552 8367182 8412210 8576169 1 -1 -1 +41.697281 8367203 8412230 8576196 1 -1 -1 +42.795010 8367161 8412208 8576185 1 -1 -1 +43.892735 8367124 8412203 8576219 1 -1 -1 +44.990463 8367207 8412234 8576209 1 -1 -1 +46.088192 8367190 8412217 8576199 1 -1 -1 +47.185921 8367167 8412261 8576193 1 -1 -1 +48.283649 8367145 8412248 8576245 1 -1 -1 +49.381374 8367230 8412246 8576246 1 -1 -1 +50.479103 8367185 8412241 8576137 1 -1 -1 +51.576832 8367219 8412223 8576163 1 -1 -1 +52.674561 8367184 8412231 8576258 1 -1 -1 +53.772289 8367200 8412210 8576159 1 -1 -1 +54.861824 8367223 8412144 8576149 1 -1 -1 +55.959549 8367197 8412194 8576164 1 -1 -1 +57.057281 8367183 8412185 8576175 1 -1 -1 +58.155006 8367192 8412239 8576224 1 -1 -1 diff --git a/anemometer-wind/3/z-origin b/anemometer-wind/3/z-origin @@ -0,0 +1,29 @@ +1.081344 8367218 8412153 8575357 1 -1 -1 +2.179072 8367266 8412208 8575405 1 -1 -1 +3.276800 8367221 8412179 8575371 1 -1 -1 +4.374528 8367210 8412214 8575330 1 -1 -1 +5.472256 8367194 8412198 8575364 1 -1 -1 +6.569984 8367208 8412234 8575365 1 -1 -1 +7.667712 8367230 8412255 8575362 1 -1 -1 +8.765440 8367205 8412238 8575359 1 -1 -1 +9.863168 8367218 8412171 8575407 1 -1 -1 +10.960896 8367148 8412226 8575345 1 -1 -1 +12.058624 8367176 8412209 8575387 1 -1 -1 +13.156352 8367219 8412217 8575337 1 -1 -1 +14.254080 8367243 8412230 8575396 1 -1 -1 +15.351808 8367210 8412230 8575419 1 -1 -1 +16.449535 8367182 8412205 8575393 1 -1 -1 +17.547264 8367230 8412221 8575351 1 -1 -1 +18.644993 8367206 8412237 8575365 1 -1 -1 +19.742720 8367214 8412245 8575384 1 -1 -1 +20.840448 8367212 8412208 8575423 1 -1 -1 +21.938175 8367247 8412200 8575348 1 -1 -1 +23.035904 8367225 8412205 8575367 1 -1 -1 +24.133633 8367219 8412192 8575369 1 -1 -1 +25.231359 8367234 8412229 8575385 1 -1 -1 +26.329088 8367231 8412186 8575348 1 -1 -1 +27.426817 8367223 8412161 8575386 1 -1 -1 +28.524544 8367193 8412214 8575364 1 -1 -1 +29.622272 8367174 8412212 8575303 1 -1 -1 +30.719999 8367197 8412173 8575386 1 -1 -1 +31.817728 8367226 8412184 8575507 1 -1 -1 diff --git a/anemometer-wind/3/z-reverse b/anemometer-wind/3/z-reverse @@ -0,0 +1,49 @@ +31.817728 8367220 8412217 8574669 1 -1 -1 +32.915455 8367239 8412200 8574417 1 -1 -1 +34.013184 8367194 8412206 8574524 1 -1 -1 +35.110912 8367286 8412196 8574462 1 -1 -1 +36.208641 8367257 8412221 8574397 1 -1 -1 +37.306370 8367186 8412215 8574440 1 -1 -1 +38.404095 8367187 8412233 8574460 1 -1 -1 +39.501823 8367201 8412236 8574483 1 -1 -1 +40.599552 8367230 8412177 8574519 1 -1 -1 +41.697281 8367226 8412219 8574561 1 -1 -1 +42.795010 8367186 8412237 8574438 1 -1 -1 +43.892735 8367191 8412241 8574409 1 -1 -1 +44.990463 8367248 8412209 8574436 1 -1 -1 +46.088192 8367206 8412213 8574481 1 -1 -1 +47.185921 8367201 8412252 8574452 1 -1 -1 +48.283649 8367230 8412226 8574428 1 -1 -1 +49.381374 8367213 8412235 8574447 1 -1 -1 +50.479103 8367198 8412209 8574418 1 -1 -1 +51.576832 8367229 8412233 8574411 1 -1 -1 +52.674561 8367194 8412255 8574398 1 -1 -1 +53.772289 8367213 8412239 8574450 1 -1 -1 +54.861824 8367245 8412190 8574398 1 -1 -1 +55.959549 8367221 8412222 8574394 1 -1 -1 +57.057281 8367227 8412209 8574385 1 -1 -1 +58.155006 8367175 8412191 8574396 1 -1 -1 +59.252739 8367228 8412210 8574395 1 -1 -1 +60.342274 8367207 8412190 8574443 1 -1 -1 +61.439999 8367244 8412192 8574398 1 -1 -1 +62.537727 8367211 8412238 8574425 1 -1 -1 +63.635456 8367253 8412198 8574472 1 -1 -1 +64.733185 8367218 8412217 8574376 1 -1 -1 +65.830910 8367215 8412175 8574409 1 -1 -1 +66.928642 8367222 8412215 8574471 1 -1 -1 +68.026367 8367236 8412175 8574518 1 -1 -1 +69.124100 8367226 8412239 8574479 1 -1 -1 +70.221825 8367224 8412247 8574500 1 -1 -1 +71.319550 8367256 8412194 8574514 1 -1 -1 +72.417282 8367236 8412190 8574476 1 -1 -1 +73.515007 8367208 8412238 8574499 1 -1 -1 +74.612740 8367199 8412201 8574486 1 -1 -1 +75.710464 8367202 8412185 8574496 1 -1 -1 +76.808189 8367252 8412232 8574533 1 -1 -1 +77.905922 8367202 8412176 8574442 1 -1 -1 +79.003647 8367224 8412235 8574473 1 -1 -1 +80.101379 8367243 8412213 8574492 1 -1 -1 +81.199104 8367242 8412195 8574477 1 -1 -1 +82.296829 8367205 8412232 8574538 1 -1 -1 +83.394562 8367252 8412249 8574615 1 -1 -1 +84.492287 8367231 8412222 8574685 1 -1 -1 diff --git a/anemometer-wind/3/z-reverse-origin b/anemometer-wind/3/z-reverse-origin @@ -0,0 +1,36 @@ +1.081344 8367226 8412241 8575346 1 -1 -1 +2.179072 8367210 8412255 8575280 1 -1 -1 +3.276800 8367183 8412171 8575340 1 -1 -1 +4.374528 8367216 8412221 8575340 1 -1 -1 +5.472256 8367197 8412196 8575380 1 -1 -1 +6.569984 8367232 8412223 8575382 1 -1 -1 +7.667712 8367206 8412184 8575360 1 -1 -1 +8.765440 8367220 8412224 8575308 1 -1 -1 +9.863168 8367224 8412248 8575366 1 -1 -1 +10.960896 8367242 8412235 8575345 1 -1 -1 +12.058624 8367270 8412224 8575343 1 -1 -1 +13.156352 8367210 8412226 8575334 1 -1 -1 +14.254080 8367221 8412213 8575355 1 -1 -1 +15.351808 8367178 8412169 8575384 1 -1 -1 +16.449535 8367197 8412192 8575327 1 -1 -1 +17.547264 8367280 8412264 8575336 1 -1 -1 +18.644993 8367164 8412148 8575352 1 -1 -1 +19.742720 8367207 8412215 8575356 1 -1 -1 +20.840448 8367212 8412248 8575338 1 -1 -1 +21.938175 8367205 8412245 8575342 1 -1 -1 +23.035904 8367206 8412214 8575325 1 -1 -1 +24.133633 8367207 8412191 8575390 1 -1 -1 +25.231359 8367213 8412196 8575363 1 -1 -1 +26.329088 8367210 8412200 8575335 1 -1 -1 +27.426817 8367252 8412206 8575336 1 -1 -1 +28.524544 8367179 8412232 8575332 1 -1 -1 +29.622272 8367194 8412194 8575325 1 -1 -1 +30.719999 8367232 8412219 8575339 1 -1 -1 +85.590019 8367262 8412263 8575143 1 -1 -1 +86.687744 8367210 8412232 8575343 1 -1 -1 +87.785469 8367218 8412267 8575311 1 -1 -1 +88.883202 8367170 8412223 8575272 1 -1 -1 +89.980927 8367225 8412198 8575311 1 -1 -1 +91.078659 8367229 8412224 8575307 1 -1 -1 +92.176384 8367216 8412240 8575340 1 -1 -1 +93.274109 8367243 8412235 8575308 1 -1 -1 diff --git a/anemometer-wind/4/x b/anemometer-wind/4/x @@ -0,0 +1,25 @@ +31.817728 8366796 8412010 8576050 1 -1 -1 +32.915455 8366603 8412033 8576064 1 -1 -1 +34.013184 8366607 8412001 8576052 1 -1 -1 +35.110912 8366663 8412003 8576056 1 -1 -1 +36.208641 8366686 8412024 8576018 1 -1 -1 +37.306370 8366629 8412013 8576035 1 -1 -1 +38.404095 8366579 8412014 8576003 1 -1 -1 +39.501823 8366546 8412026 8576020 1 -1 -1 +40.599552 8366637 8412028 8576029 1 -1 -1 +41.697281 8366752 8411993 8576004 1 -1 -1 +42.795010 8366705 8412010 8576014 1 -1 -1 +43.892735 8366689 8412027 8576043 1 -1 -1 +44.990463 8366650 8412012 8576055 1 -1 -1 +46.088192 8366675 8412018 8576021 1 -1 -1 +47.185921 8366688 8412047 8576008 1 -1 -1 +48.283649 8366682 8412013 8576018 1 -1 -1 +49.381374 8366679 8412023 8576047 1 -1 -1 +50.479103 8366659 8412047 8575967 1 -1 -1 +51.576832 8366674 8411988 8576016 1 -1 -1 +52.674561 8366713 8411989 8576022 1 -1 -1 +53.772289 8366734 8412043 8576032 1 -1 -1 +54.861824 8366755 8412029 8575985 1 -1 -1 +55.959549 8366769 8412019 8576007 1 -1 -1 +57.057281 8366781 8411975 8576030 1 -1 -1 +58.155006 8366788 8412040 8575985 1 -1 -1 diff --git a/anemometer-wind/4/x-origin b/anemometer-wind/4/x-origin @@ -0,0 +1,28 @@ +1.081344 8367145 8412046 8576060 1 -1 -1 +2.179072 8367127 8412048 8576063 1 -1 -1 +3.276800 8367141 8412027 8576012 1 -1 -1 +4.374528 8367140 8412038 8576056 1 -1 -1 +5.472256 8367094 8412010 8576016 1 -1 -1 +6.569984 8367136 8412002 8576054 1 -1 -1 +7.667712 8367109 8412038 8576057 1 -1 -1 +8.765440 8367162 8412047 8576004 1 -1 -1 +9.863168 8367141 8411965 8576056 1 -1 -1 +10.960896 8367137 8412063 8575991 1 -1 -1 +12.058624 8367181 8412011 8576020 1 -1 -1 +13.156352 8367139 8411985 8575996 1 -1 -1 +14.254080 8367153 8412010 8576032 1 -1 -1 +15.351808 8367130 8412011 8576032 1 -1 -1 +16.449535 8367115 8412006 8575982 1 -1 -1 +17.547264 8367085 8412053 8576068 1 -1 -1 +18.644993 8367113 8411992 8576048 1 -1 -1 +19.742720 8367155 8412042 8576012 1 -1 -1 +20.840448 8367154 8411987 8576018 1 -1 -1 +21.938175 8367131 8412040 8576079 1 -1 -1 +23.035904 8367130 8412003 8576026 1 -1 -1 +24.133633 8367186 8411953 8576013 1 -1 -1 +25.231359 8367180 8412032 8576040 1 -1 -1 +26.329088 8367109 8411992 8576021 1 -1 -1 +27.426817 8367149 8412024 8575996 1 -1 -1 +28.524544 8367125 8412023 8576017 1 -1 -1 +29.622272 8367128 8411992 8576018 1 -1 -1 +30.719999 8367180 8411968 8576035 1 -1 -1 diff --git a/anemometer-wind/4/x-reverse b/anemometer-wind/4/x-reverse @@ -0,0 +1,25 @@ +31.817728 8367658 8412048 8575995 1 -1 -1 +32.915455 8367742 8411960 8575998 1 -1 -1 +34.013184 8367931 8412001 8575992 1 -1 -1 +35.110912 8367870 8412025 8575986 1 -1 -1 +36.208641 8367908 8411979 8575994 1 -1 -1 +37.306370 8367921 8412033 8575952 1 -1 -1 +38.404095 8367906 8411977 8575978 1 -1 -1 +39.501823 8367889 8412067 8575940 1 -1 -1 +40.599552 8367941 8412033 8575933 1 -1 -1 +41.697281 8367899 8412001 8575970 1 -1 -1 +42.795010 8367926 8412027 8575954 1 -1 -1 +43.892735 8367900 8412064 8575970 1 -1 -1 +44.990463 8367864 8411990 8575972 1 -1 -1 +46.088192 8367882 8412035 8575954 1 -1 -1 +47.185921 8367792 8412023 8575974 1 -1 -1 +48.283649 8367746 8412030 8575971 1 -1 -1 +49.381374 8367788 8412048 8575940 1 -1 -1 +50.479103 8367854 8412002 8575973 1 -1 -1 +51.576832 8367857 8411968 8575981 1 -1 -1 +52.674561 8367873 8412002 8575967 1 -1 -1 +53.772289 8367867 8411968 8575972 1 -1 -1 +54.861824 8367794 8412024 8575889 1 -1 -1 +55.959549 8367864 8412011 8575970 1 -1 -1 +57.057281 8367853 8412038 8576030 1 -1 -1 +58.155006 8367801 8411975 8576015 1 -1 -1 diff --git a/anemometer-wind/4/x-reverse-origin b/anemometer-wind/4/x-reverse-origin @@ -0,0 +1,28 @@ +1.081344 8367165 8411988 8575995 1 -1 -1 +2.179072 8367191 8412011 8575995 1 -1 -1 +3.276800 8367173 8412008 8575990 1 -1 -1 +4.374528 8367100 8412009 8575974 1 -1 -1 +5.472256 8367159 8411997 8575995 1 -1 -1 +6.569984 8367154 8412023 8575973 1 -1 -1 +7.667712 8367174 8412009 8575964 1 -1 -1 +8.765440 8367141 8412017 8575989 1 -1 -1 +9.863168 8367188 8411958 8575992 1 -1 -1 +10.960896 8367154 8412014 8575990 1 -1 -1 +12.058624 8367110 8412031 8575978 1 -1 -1 +13.156352 8367125 8412034 8575954 1 -1 -1 +14.254080 8367203 8412053 8575964 1 -1 -1 +15.351808 8367186 8412060 8576005 1 -1 -1 +16.449535 8367194 8412009 8575971 1 -1 -1 +17.547264 8367114 8412069 8575943 1 -1 -1 +18.644993 8367132 8412014 8575992 1 -1 -1 +19.742720 8367132 8412067 8576008 1 -1 -1 +20.840448 8367133 8412015 8575962 1 -1 -1 +21.938175 8367118 8411995 8576008 1 -1 -1 +23.035904 8367140 8412090 8575994 1 -1 -1 +24.133633 8367123 8412018 8575964 1 -1 -1 +25.231359 8367164 8412026 8575995 1 -1 -1 +26.329088 8367087 8412046 8575983 1 -1 -1 +27.426817 8367096 8412047 8576016 1 -1 -1 +28.524544 8367144 8411975 8575988 1 -1 -1 +29.622272 8367153 8412054 8575999 1 -1 -1 +30.719999 8367158 8412065 8575909 1 -1 -1 diff --git a/anemometer-wind/4/y b/anemometer-wind/4/y @@ -0,0 +1,24 @@ +32.915455 8367218 8412558 8575329 1 -1 -1 +34.013184 8367239 8412891 8575298 1 -1 -1 +35.110912 8367235 8412803 8575278 1 -1 -1 +36.208641 8367237 8412751 8575316 1 -1 -1 +37.306370 8367192 8412769 8575215 1 -1 -1 +38.404095 8367216 8412651 8575295 1 -1 -1 +39.501823 8367206 8412731 8575303 1 -1 -1 +40.599552 8367249 8412683 8575246 1 -1 -1 +41.697281 8367236 8412744 8575291 1 -1 -1 +42.795010 8367198 8412677 8575283 1 -1 -1 +43.892735 8367187 8412730 8575249 1 -1 -1 +44.990463 8367211 8412688 8575199 1 -1 -1 +46.088192 8367169 8412632 8575281 1 -1 -1 +47.185921 8367232 8412687 8575229 1 -1 -1 +48.283649 8367219 8412656 8575269 1 -1 -1 +49.381374 8367208 8412640 8575262 1 -1 -1 +50.479103 8367227 8412619 8575242 1 -1 -1 +51.576832 8367213 8412658 8575249 1 -1 -1 +52.674561 8367228 8412666 8575265 1 -1 -1 +53.772289 8367195 8412584 8575250 1 -1 -1 +54.870014 8367219 8412638 8575253 1 -1 -1 +55.959549 8367179 8412619 8575234 1 -1 -1 +57.057281 8367244 8412640 8575279 1 -1 -1 +58.155006 8367197 8412661 8575282 1 -1 -1 diff --git a/anemometer-wind/4/y-origin b/anemometer-wind/4/y-origin @@ -0,0 +1,29 @@ +1.081344 8367182 8412241 8575255 1 -1 -1 +2.179072 8367179 8412205 8575306 1 -1 -1 +3.276800 8367244 8412209 8575288 1 -1 -1 +4.374528 8367172 8412231 8575285 1 -1 -1 +5.472256 8367209 8412246 8575314 1 -1 -1 +6.569984 8367210 8412217 8575294 1 -1 -1 +7.667712 8367226 8412262 8575281 1 -1 -1 +8.765440 8367208 8412217 8575253 1 -1 -1 +9.863168 8367278 8412242 8575280 1 -1 -1 +10.960896 8367258 8412255 8575274 1 -1 -1 +12.058624 8367209 8412246 8575269 1 -1 -1 +13.156352 8367249 8412214 8575235 1 -1 -1 +14.254080 8367226 8412231 8575261 1 -1 -1 +15.351808 8367216 8412266 8575266 1 -1 -1 +16.449535 8367196 8412243 8575269 1 -1 -1 +17.547264 8367224 8412235 8575278 1 -1 -1 +18.644993 8367210 8412211 8575234 1 -1 -1 +19.742720 8367207 8412267 8575295 1 -1 -1 +20.840448 8367247 8412241 8575299 1 -1 -1 +21.938175 8367211 8412225 8575281 1 -1 -1 +23.035904 8367213 8412233 8575309 1 -1 -1 +24.133633 8367239 8412218 8575297 1 -1 -1 +25.231359 8367204 8412269 8575256 1 -1 -1 +26.329088 8367177 8412205 8575302 1 -1 -1 +27.426817 8367215 8412200 8575297 1 -1 -1 +28.524544 8367180 8412232 8575267 1 -1 -1 +29.622272 8367188 8412279 8575264 1 -1 -1 +30.719999 8367220 8412214 8575270 1 -1 -1 +31.817728 8366994 8412287 8575212 1 -1 -1 diff --git a/anemometer-wind/4/y-reverse b/anemometer-wind/4/y-reverse @@ -0,0 +1,24 @@ +32.915455 8367225 8411899 8575188 1 -1 -1 +34.013184 8367227 8411800 8575220 1 -1 -1 +35.110912 8367217 8411790 8575149 1 -1 -1 +36.208641 8367205 8411799 8575155 1 -1 -1 +37.306370 8367229 8411783 8575217 1 -1 -1 +38.404095 8367227 8411759 8575161 1 -1 -1 +39.501823 8367226 8411756 8575193 1 -1 -1 +40.599552 8367204 8411768 8575175 1 -1 -1 +41.697281 8367210 8411796 8575136 1 -1 -1 +42.795010 8367190 8411775 8575173 1 -1 -1 +43.892735 8367162 8411715 8575161 1 -1 -1 +44.990463 8367195 8411733 8575132 1 -1 -1 +46.088192 8367236 8411747 8575186 1 -1 -1 +47.185921 8367207 8411784 8575144 1 -1 -1 +48.283649 8367220 8411753 8575158 1 -1 -1 +49.381374 8367234 8411729 8575147 1 -1 -1 +50.479103 8367190 8411762 8575137 1 -1 -1 +51.576832 8367199 8411740 8575108 1 -1 -1 +52.674561 8367198 8411730 8575173 1 -1 -1 +53.772289 8367242 8411740 8575151 1 -1 -1 +54.861824 8367219 8411741 8575163 1 -1 -1 +55.959549 8367192 8411758 8575137 1 -1 -1 +57.057281 8367206 8411787 8575194 1 -1 -1 +58.155006 8367178 8411719 8575147 1 -1 -1 diff --git a/anemometer-wind/4/y-reverse-origin b/anemometer-wind/4/y-reverse-origin @@ -0,0 +1,29 @@ +1.081344 8367227 8412308 8575170 1 -1 -1 +2.179072 8367168 8412268 8575148 1 -1 -1 +3.276800 8367264 8412306 8575179 1 -1 -1 +4.374528 8367253 8412253 8575191 1 -1 -1 +5.472256 8367249 8412281 8575200 1 -1 -1 +6.569984 8367228 8412257 8575181 1 -1 -1 +7.667712 8367207 8412237 8575168 1 -1 -1 +8.765440 8367191 8412280 8575185 1 -1 -1 +9.863168 8367224 8412241 8575227 1 -1 -1 +10.960896 8367221 8412260 8575178 1 -1 -1 +12.058624 8367208 8412249 8575181 1 -1 -1 +13.156352 8367242 8412237 8575142 1 -1 -1 +14.254080 8367187 8412238 8575196 1 -1 -1 +15.351808 8367218 8412299 8575227 1 -1 -1 +16.449535 8367237 8412274 8575149 1 -1 -1 +17.547264 8367252 8412307 8575181 1 -1 -1 +18.644993 8367196 8412227 8575164 1 -1 -1 +19.742720 8367236 8412253 8575215 1 -1 -1 +20.840448 8367158 8412238 8575191 1 -1 -1 +21.938175 8367203 8412260 8575199 1 -1 -1 +23.035904 8367220 8412291 8575192 1 -1 -1 +24.133633 8367206 8412275 8575192 1 -1 -1 +25.231359 8367238 8412303 8575153 1 -1 -1 +26.329088 8367229 8412267 8575202 1 -1 -1 +27.426817 8367245 8412311 8575158 1 -1 -1 +28.524544 8367176 8412292 8575169 1 -1 -1 +29.622272 8367279 8412270 8575183 1 -1 -1 +30.719999 8367205 8412285 8575192 1 -1 -1 +31.817728 8367197 8412260 8575222 1 -1 -1 diff --git a/anemometer-wind/4/z b/anemometer-wind/4/z @@ -0,0 +1,25 @@ +31.817728 8367222 8412284 8575692 1 -1 -1 +32.915455 8367197 8412285 8575894 1 -1 -1 +34.013184 8367238 8412325 8575773 1 -1 -1 +35.110912 8367212 8412282 8575966 1 -1 -1 +36.208641 8367224 8412324 8575948 1 -1 -1 +37.306370 8367257 8412293 8575964 1 -1 -1 +38.404095 8367194 8412314 8575964 1 -1 -1 +39.501823 8367176 8412255 8575920 1 -1 -1 +40.599552 8367222 8412333 8575932 1 -1 -1 +41.697281 8367194 8412253 8576004 1 -1 -1 +42.795010 8367189 8412312 8575881 1 -1 -1 +43.892735 8367200 8412340 8575924 1 -1 -1 +44.990463 8367209 8412306 8575905 1 -1 -1 +46.088192 8367158 8412314 8575914 1 -1 -1 +47.185921 8367173 8412305 8575864 1 -1 -1 +48.283649 8367151 8412301 8575847 1 -1 -1 +49.381374 8367218 8412334 8575861 1 -1 -1 +50.479103 8367225 8412321 8575866 1 -1 -1 +51.576832 8367153 8412340 8575863 1 -1 -1 +52.674561 8367229 8412307 8575901 1 -1 -1 +53.772289 8367177 8412327 8575861 1 -1 -1 +54.861824 8367177 8412310 8575865 1 -1 -1 +55.959549 8367226 8412296 8575744 1 -1 -1 +57.057281 8367205 8412361 8575735 1 -1 -1 +58.155006 8367185 8412323 8575903 1 -1 -1 diff --git a/anemometer-wind/4/z-origin b/anemometer-wind/4/z-origin @@ -0,0 +1,28 @@ +1.081344 8367238 8412282 8575103 1 -1 -1 +2.179072 8367227 8412308 8575100 1 -1 -1 +3.276800 8367223 8412316 8575102 1 -1 -1 +4.374528 8367229 8412302 8575133 1 -1 -1 +5.472256 8367174 8412284 8575114 1 -1 -1 +6.569984 8367213 8412310 8575089 1 -1 -1 +7.667712 8367234 8412279 8575140 1 -1 -1 +8.765440 8367196 8412330 8575162 1 -1 -1 +9.863168 8367231 8412324 8575133 1 -1 -1 +10.960896 8367205 8412279 8575118 1 -1 -1 +12.058624 8367242 8412298 8575100 1 -1 -1 +13.156352 8367265 8412316 8575089 1 -1 -1 +14.254080 8367203 8412320 8575098 1 -1 -1 +15.351808 8367209 8412302 8575110 1 -1 -1 +16.449535 8367223 8412263 8575165 1 -1 -1 +17.547264 8367233 8412348 8575136 1 -1 -1 +18.644993 8367187 8412309 8575137 1 -1 -1 +19.742720 8367223 8412306 8575107 1 -1 -1 +20.840448 8367244 8412319 8575077 1 -1 -1 +21.938175 8367174 8412320 8575136 1 -1 -1 +23.035904 8367215 8412294 8575161 1 -1 -1 +24.133633 8367189 8412288 8575108 1 -1 -1 +25.231359 8367157 8412324 8575123 1 -1 -1 +26.329088 8367237 8412321 8575086 1 -1 -1 +27.426817 8367217 8412290 8575145 1 -1 -1 +28.524544 8367171 8412331 8575093 1 -1 -1 +29.622272 8367194 8412327 8575101 1 -1 -1 +30.719999 8367250 8412322 8575143 1 -1 -1 diff --git a/anemometer-wind/4/z-reverse b/anemometer-wind/4/z-reverse @@ -0,0 +1,21 @@ +36.208641 8367215 8412330 8574668 1 -1 -1 +37.306370 8367226 8412353 8574475 1 -1 -1 +38.404095 8367234 8412317 8574470 1 -1 -1 +39.501823 8367222 8412289 8574518 1 -1 -1 +40.599552 8367207 8412265 8574489 1 -1 -1 +41.697281 8367186 8412336 8574430 1 -1 -1 +42.795010 8367184 8412324 8574483 1 -1 -1 +43.892735 8367197 8412364 8574463 1 -1 -1 +44.990463 8367219 8412325 8574408 1 -1 -1 +46.088192 8367196 8412326 8574487 1 -1 -1 +47.185921 8367187 8412315 8574474 1 -1 -1 +48.283649 8367213 8412288 8574414 1 -1 -1 +49.381374 8367206 8412326 8574427 1 -1 -1 +50.479103 8367224 8412312 8574387 1 -1 -1 +51.576832 8367178 8412311 8574457 1 -1 -1 +52.674561 8367240 8412318 8574448 1 -1 -1 +53.772289 8367196 8412316 8574499 1 -1 -1 +54.861824 8367235 8412295 8574466 1 -1 -1 +55.959549 8367217 8412281 8574440 1 -1 -1 +57.057281 8367225 8412312 8574472 1 -1 -1 +58.155006 8367186 8412344 8574467 1 -1 -1 diff --git a/anemometer-wind/4/z-reverse-origin b/anemometer-wind/4/z-reverse-origin @@ -0,0 +1,32 @@ +1.081344 8367208 8412283 8575082 1 -1 -1 +2.179072 8367258 8412295 8575056 1 -1 -1 +3.276800 8367164 8412274 8575085 1 -1 -1 +4.374528 8367202 8412313 8575123 1 -1 -1 +5.472256 8367190 8412279 8575090 1 -1 -1 +6.569984 8367183 8412274 8575072 1 -1 -1 +7.667712 8367221 8412313 8575090 1 -1 -1 +8.765440 8367210 8412335 8575062 1 -1 -1 +9.863168 8367212 8412289 8575088 1 -1 -1 +10.960896 8367181 8412312 8575065 1 -1 -1 +12.058624 8367211 8412319 8575145 1 -1 -1 +13.156352 8367263 8412322 8575071 1 -1 -1 +14.254080 8367215 8412327 8575082 1 -1 -1 +15.351808 8367205 8412309 8575082 1 -1 -1 +16.449535 8367208 8412360 8575080 1 -1 -1 +17.547264 8367148 8412280 8575097 1 -1 -1 +18.644993 8367175 8412308 8575095 1 -1 -1 +19.742720 8367187 8412270 8575103 1 -1 -1 +20.840448 8367183 8412300 8575058 1 -1 -1 +21.938175 8367252 8412319 8575069 1 -1 -1 +23.035904 8367180 8412289 8575076 1 -1 -1 +24.133633 8367205 8412320 8575099 1 -1 -1 +25.231359 8367232 8412330 8575076 1 -1 -1 +26.329088 8367213 8412356 8575074 1 -1 -1 +27.426817 8367166 8412351 8575074 1 -1 -1 +28.524544 8367249 8412334 8575045 1 -1 -1 +29.622272 8367183 8412353 8575052 1 -1 -1 +30.719999 8367177 8412302 8575107 1 -1 -1 +31.817728 8367206 8412270 8575051 1 -1 -1 +32.915455 8367230 8412324 8575057 1 -1 -1 +34.013184 8367149 8412330 8575082 1 -1 -1 +35.110912 8367215 8412345 8574896 1 -1 -1 diff --git a/anemometer-wind/5/x b/anemometer-wind/5/x @@ -0,0 +1,24 @@ +32.915455 8366479 8412114 8575770 1 -1 -1 +34.013184 8366575 8412069 8575745 1 -1 -1 +35.110912 8366607 8412072 8575772 1 -1 -1 +36.208641 8366582 8412094 8575753 1 -1 -1 +37.306370 8366574 8412118 8575812 1 -1 -1 +38.404095 8366544 8412098 8575775 1 -1 -1 +39.501823 8366555 8412092 8575767 1 -1 -1 +40.599552 8366469 8412103 8575780 1 -1 -1 +41.697281 8366493 8412101 8575790 1 -1 -1 +42.795010 8366534 8412086 8575744 1 -1 -1 +43.892735 8366565 8412104 8575785 1 -1 -1 +44.990463 8366648 8412098 8575779 1 -1 -1 +46.088192 8366618 8412071 8575799 1 -1 -1 +47.185921 8366586 8412036 8575734 1 -1 -1 +48.283649 8366608 8412050 8575808 1 -1 -1 +49.381374 8366625 8412054 8575777 1 -1 -1 +50.479103 8366682 8412058 8575789 1 -1 -1 +51.576832 8366608 8412072 8575742 1 -1 -1 +52.674561 8366607 8412088 8575742 1 -1 -1 +53.772289 8366567 8412027 8575739 1 -1 -1 +54.861824 8366612 8412045 8575749 1 -1 -1 +55.959549 8366643 8412064 8575796 1 -1 -1 +57.057281 8366670 8412065 8575696 1 -1 -1 +58.155006 8366609 8412034 8575733 1 -1 -1 diff --git a/anemometer-wind/5/x-origin b/anemometer-wind/5/x-origin @@ -0,0 +1,29 @@ +1.081344 8367158 8412108 8575802 1 -1 -1 +2.179072 8367201 8412068 8575787 1 -1 -1 +3.276800 8367194 8412079 8575777 1 -1 -1 +4.374528 8367155 8412042 8575803 1 -1 -1 +5.472256 8367147 8412104 8575795 1 -1 -1 +6.569984 8367140 8412046 8575779 1 -1 -1 +7.667712 8367161 8412080 8575786 1 -1 -1 +8.765440 8367127 8412086 8575835 1 -1 -1 +9.863168 8367152 8412021 8575783 1 -1 -1 +10.960896 8367201 8412091 8575791 1 -1 -1 +12.058624 8367201 8412019 8575808 1 -1 -1 +13.156352 8367164 8412092 8575775 1 -1 -1 +14.254080 8367180 8412070 8575823 1 -1 -1 +15.351808 8367187 8412115 8575780 1 -1 -1 +16.449535 8367168 8412044 8575809 1 -1 -1 +17.547264 8367233 8412059 8575786 1 -1 -1 +18.644993 8367181 8412020 8575806 1 -1 -1 +19.742720 8367179 8412060 8575803 1 -1 -1 +20.840448 8367176 8412106 8575759 1 -1 -1 +21.938175 8367194 8412086 8575749 1 -1 -1 +23.035904 8367193 8412098 8575796 1 -1 -1 +24.133633 8367140 8412064 8575772 1 -1 -1 +25.231359 8367141 8412082 8575789 1 -1 -1 +26.329088 8367171 8412088 8575749 1 -1 -1 +27.426817 8367178 8412071 8575793 1 -1 -1 +28.524544 8367197 8412097 8575812 1 -1 -1 +29.622272 8367161 8412036 8575778 1 -1 -1 +30.719999 8367145 8412115 8575789 1 -1 -1 +31.817728 8367068 8412057 8575806 1 -1 -1 diff --git a/anemometer-wind/5/x-reverse b/anemometer-wind/5/x-reverse @@ -0,0 +1,25 @@ +31.817728 8367665 8412067 8575770 1 -1 -1 +32.915455 8367775 8412082 8575730 1 -1 -1 +34.013184 8367752 8412068 8575681 1 -1 -1 +35.110912 8367758 8412062 8575710 1 -1 -1 +36.208641 8367825 8412121 8575716 1 -1 -1 +37.306370 8367760 8412121 8575685 1 -1 -1 +38.404095 8367833 8412112 8575788 1 -1 -1 +39.501823 8367825 8412078 8575748 1 -1 -1 +40.599552 8367780 8412111 8575745 1 -1 -1 +41.697281 8367797 8412103 8575721 1 -1 -1 +42.795010 8367840 8412097 8575733 1 -1 -1 +43.892735 8367873 8412011 8575723 1 -1 -1 +44.990463 8367758 8412083 8575724 1 -1 -1 +46.088192 8367832 8412059 8575715 1 -1 -1 +47.185921 8367787 8412050 8575685 1 -1 -1 +48.283649 8367796 8412075 8575715 1 -1 -1 +49.381374 8367784 8412073 8575704 1 -1 -1 +50.479103 8367807 8412115 8575672 1 -1 -1 +51.576832 8367858 8412089 8575681 1 -1 -1 +52.674561 8367926 8412113 8575744 1 -1 -1 +53.772289 8367892 8412127 8575700 1 -1 -1 +54.861824 8367895 8412085 8575754 1 -1 -1 +55.959549 8367855 8412088 8575710 1 -1 -1 +57.057281 8367918 8412102 8575675 1 -1 -1 +58.155006 8367927 8412094 8575729 1 -1 -1 diff --git a/anemometer-wind/5/x-reverse-origin b/anemometer-wind/5/x-reverse-origin @@ -0,0 +1,28 @@ +1.081344 8367219 8412058 8575754 1 -1 -1 +2.179072 8367173 8412080 8575744 1 -1 -1 +3.276800 8367218 8412084 8575729 1 -1 -1 +4.374528 8367222 8412054 8575784 1 -1 -1 +5.472256 8367171 8412073 8575733 1 -1 -1 +6.569984 8367215 8412072 8575710 1 -1 -1 +7.667712 8367173 8412064 8575761 1 -1 -1 +8.765440 8367206 8412099 8575669 1 -1 -1 +9.863168 8367196 8412060 8575703 1 -1 -1 +10.960896 8367119 8412073 8575790 1 -1 -1 +12.058624 8367162 8412080 8575745 1 -1 -1 +13.156352 8367205 8412052 8575766 1 -1 -1 +14.254080 8367216 8412139 8575736 1 -1 -1 +15.351808 8367166 8412124 8575771 1 -1 -1 +16.449535 8367172 8412066 8575730 1 -1 -1 +17.547264 8367205 8412024 8575726 1 -1 -1 +18.644993 8367239 8412107 8575732 1 -1 -1 +19.742720 8367199 8412064 8575728 1 -1 -1 +20.840448 8367201 8412050 8575752 1 -1 -1 +21.938175 8367169 8412091 8575722 1 -1 -1 +23.035904 8367162 8412050 8575731 1 -1 -1 +24.133633 8367175 8412081 8575759 1 -1 -1 +25.231359 8367186 8412103 8575709 1 -1 -1 +26.329088 8367213 8412107 8575729 1 -1 -1 +27.426817 8367177 8412043 8575734 1 -1 -1 +28.524544 8367231 8412056 8575779 1 -1 -1 +29.622272 8367252 8412097 8575768 1 -1 -1 +30.719999 8367228 8412106 8575735 1 -1 -1 diff --git a/anemometer-wind/5/y b/anemometer-wind/5/y @@ -0,0 +1,25 @@ +31.817728 8367224 8412549 8575046 1 -1 -1 +32.915455 8367201 8412882 8575021 1 -1 -1 +34.013184 8367193 8412907 8575029 1 -1 -1 +35.110912 8367175 8412845 8575036 1 -1 -1 +36.208641 8367182 8412946 8575003 1 -1 -1 +37.306370 8367188 8413015 8574996 1 -1 -1 +38.404095 8367207 8412809 8575039 1 -1 -1 +39.501823 8367244 8412808 8574987 1 -1 -1 +40.599552 8367193 8412881 8575047 1 -1 -1 +41.697281 8367207 8412860 8575036 1 -1 -1 +42.795010 8367203 8412859 8575009 1 -1 -1 +43.892735 8367240 8412975 8575001 1 -1 -1 +44.990463 8367200 8412886 8575023 1 -1 -1 +46.088192 8367175 8412909 8575002 1 -1 -1 +47.185921 8367237 8412991 8575026 1 -1 -1 +48.283649 8367172 8413018 8575033 1 -1 -1 +49.381374 8367157 8412944 8574990 1 -1 -1 +50.479103 8367243 8413058 8574997 1 -1 -1 +51.576832 8367222 8412955 8575068 1 -1 -1 +52.674561 8367212 8412902 8575045 1 -1 -1 +53.772289 8367232 8412813 8575002 1 -1 -1 +54.861824 8367215 8412925 8575053 1 -1 -1 +55.959549 8367170 8412996 8575025 1 -1 -1 +57.057281 8367198 8413145 8574999 1 -1 -1 +58.155006 8367204 8413054 8575023 1 -1 -1 diff --git a/anemometer-wind/5/y-origin b/anemometer-wind/5/y-origin @@ -0,0 +1,28 @@ +1.081344 8367166 8412331 8575062 1 -1 -1 +2.179072 8367199 8412322 8575049 1 -1 -1 +3.276800 8367230 8412354 8575022 1 -1 -1 +4.374528 8367200 8412371 8575010 1 -1 -1 +5.472256 8367178 8412306 8575059 1 -1 -1 +6.569984 8367189 8412312 8575000 1 -1 -1 +7.667712 8367214 8412319 8575038 1 -1 -1 +8.765440 8367168 8412318 8575030 1 -1 -1 +9.863168 8367203 8412337 8575043 1 -1 -1 +10.960896 8367202 8412341 8575065 1 -1 -1 +12.058624 8367209 8412343 8575012 1 -1 -1 +13.156352 8367176 8412326 8575052 1 -1 -1 +14.254080 8367167 8412336 8575046 1 -1 -1 +15.351808 8367245 8412325 8575050 1 -1 -1 +16.449535 8367205 8412383 8575007 1 -1 -1 +17.547264 8367248 8412346 8575007 1 -1 -1 +18.644993 8367199 8412343 8575060 1 -1 -1 +19.742720 8367182 8412372 8574993 1 -1 -1 +20.840448 8367222 8412316 8574980 1 -1 -1 +21.938175 8367202 8412332 8575033 1 -1 -1 +23.035904 8367218 8412387 8574993 1 -1 -1 +24.133633 8367203 8412344 8575008 1 -1 -1 +25.231359 8367242 8412309 8575069 1 -1 -1 +26.329088 8367221 8412350 8575075 1 -1 -1 +27.426817 8367197 8412371 8575020 1 -1 -1 +28.524544 8367222 8412347 8575009 1 -1 -1 +29.622272 8367260 8412362 8575013 1 -1 -1 +30.719999 8367192 8412352 8575003 1 -1 -1 diff --git a/anemometer-wind/6/z-fan b/anemometer-wind/6/z-fan @@ -0,0 +1,32 @@ +21.938175 8367195 8412379 8616064 1 -1 -1 +25.231359 8367241 8412384 8616022 1 -1 -1 +26.329088 8367156 8412382 8615995 1 -1 -1 +27.426817 8367197 8412337 8616036 1 -1 -1 +28.524544 8367209 8412364 8616082 1 -1 -1 +29.622272 8367200 8412434 8616103 1 -1 -1 +30.719999 8367203 8412389 8616126 1 -1 -1 +31.817728 8367203 8412393 8616077 1 -1 -1 +32.915455 8367284 8412381 8616087 1 -1 -1 +34.013184 8367213 8412363 8616045 1 -1 -1 +35.110912 8367170 8412406 8616084 1 -1 -1 +36.208641 8367199 8412390 8616062 1 -1 -1 +37.306370 8367242 8412422 8616096 1 -1 -1 +38.404095 8367223 8412363 8616030 1 -1 -1 +39.501823 8367203 8412431 8616064 1 -1 -1 +40.599552 8367224 8412414 8616085 1 -1 -1 +41.697281 8367198 8412404 8616065 1 -1 -1 +42.795010 8367202 8412327 8616138 1 -1 -1 +43.892735 8367245 8412360 8616081 1 -1 -1 +44.990463 8367213 8412416 8616108 1 -1 -1 +46.088192 8367211 8412402 8616074 1 -1 -1 +47.185921 8367230 8412406 8616040 1 -1 -1 +48.283649 8367242 8412396 8616106 1 -1 -1 +49.381374 8367234 8412399 8616084 1 -1 -1 +50.479103 8367202 8412376 8616096 1 -1 -1 +51.576832 8367262 8412368 8616086 1 -1 -1 +52.674561 8367231 8412423 8616086 1 -1 -1 +53.772289 8367211 8412368 8616083 1 -1 -1 +54.861824 8367251 8412410 8616106 1 -1 -1 +55.959549 8367244 8412436 8616040 1 -1 -1 +57.057281 8367245 8412385 8616089 1 -1 -1 +58.155006 8367200 8412381 8616090 1 -1 -1 diff --git a/anemometer-wind/6/z-fan-and-wind b/anemometer-wind/6/z-fan-and-wind @@ -0,0 +1,25 @@ +31.817728 8367224 8412374 8615354 1 -1 -1 +32.915455 8367218 8412342 8615737 1 -1 -1 +34.013184 8367250 8412371 8615744 1 -1 -1 +35.110912 8367224 8412349 8616088 1 -1 -1 +36.208641 8367250 8412275 8616142 1 -1 -1 +37.306370 8367166 8412413 8616042 1 -1 -1 +38.404095 8367200 8412365 8616113 1 -1 -1 +39.501823 8367170 8412415 8616133 1 -1 -1 +40.599552 8367228 8412402 8616178 1 -1 -1 +41.697281 8367241 8412363 8616187 1 -1 -1 +42.795010 8367238 8412412 8616199 1 -1 -1 +43.892735 8367183 8412383 8616205 1 -1 -1 +44.990463 8367222 8412350 8616192 1 -1 -1 +46.088192 8367140 8412367 8616216 1 -1 -1 +47.185921 8367241 8412397 8616189 1 -1 -1 +48.283649 8367195 8412391 8616222 1 -1 -1 +49.381374 8367212 8412349 8616192 1 -1 -1 +50.479103 8367230 8412393 8616209 1 -1 -1 +51.576832 8367180 8412322 8616187 1 -1 -1 +52.674561 8367265 8412312 8616246 1 -1 -1 +53.772289 8367243 8412369 8616148 1 -1 -1 +54.861824 8367205 8412366 8616174 1 -1 -1 +55.959549 8367185 8412359 8616211 1 -1 -1 +57.057281 8367242 8412397 8616197 1 -1 -1 +58.155006 8367199 8412411 8616204 1 -1 -1 diff --git a/anemometer-wind/6/z-fan-and-wind-origin b/anemometer-wind/6/z-fan-and-wind-origin @@ -0,0 +1,27 @@ +1.081344 8367191 8412324 8575000 1 -1 -1 +2.179072 8367233 8412367 8574982 1 -1 -1 +3.276800 8367239 8412395 8574974 1 -1 -1 +4.374528 8367152 8412322 8574961 1 -1 -1 +5.472256 8367197 8412333 8575015 1 -1 -1 +6.569984 8367218 8412351 8574937 1 -1 -1 +7.667712 8367209 8412385 8575003 1 -1 -1 +8.765440 8367216 8412353 8574969 1 -1 -1 +9.863168 8367205 8412345 8574970 1 -1 -1 +10.960896 8367201 8412381 8574968 1 -1 -1 +12.058624 8367155 8412383 8574993 1 -1 -1 +13.156352 8367225 8412369 8574931 1 -1 -1 +14.254080 8367242 8412387 8574955 1 -1 -1 +15.351808 8367186 8412392 8574953 1 -1 -1 +16.449535 8367228 8412375 8574953 1 -1 -1 +17.547264 8367209 8412412 8574965 1 -1 -1 +18.644993 8367208 8412354 8574972 1 -1 -1 +19.742720 8367155 8412374 8574993 1 -1 -1 +20.840448 8367216 8412414 8574950 1 -1 -1 +21.938175 8367162 8412333 8574942 1 -1 -1 +23.035904 8367180 8412382 8574963 1 -1 -1 +24.133633 8367222 8412377 8574934 1 -1 -1 +26.329088 8367182 8412351 8574932 1 -1 -1 +27.426817 8367141 8412384 8575011 1 -1 -1 +28.524544 8367191 8412354 8574956 1 -1 -1 +29.622272 8367208 8412362 8574998 1 -1 -1 +30.719999 8367203 8412345 8575281 1 -1 -1 diff --git a/anemometer-wind/6/z-fan-origin b/anemometer-wind/6/z-fan-origin @@ -0,0 +1,18 @@ +1.081344 8367180 8412338 8574897 1 -1 -1 +2.179072 8367205 8412409 8574931 1 -1 -1 +3.276800 8367198 8412386 8574894 1 -1 -1 +4.374528 8367165 8412435 8574935 1 -1 -1 +5.472256 8367214 8412408 8574907 1 -1 -1 +6.569984 8367195 8412422 8574936 1 -1 -1 +7.667712 8367200 8412359 8574931 1 -1 -1 +8.765440 8367204 8412380 8574937 1 -1 -1 +9.863168 8367162 8412392 8574890 1 -1 -1 +10.960896 8367189 8412404 8574920 1 -1 -1 +12.058624 8367191 8412354 8574887 1 -1 -1 +13.156352 8367193 8412441 8574929 1 -1 -1 +14.254080 8367140 8412405 8574940 1 -1 -1 +15.351808 8367216 8412371 8574927 1 -1 -1 +16.449535 8367195 8412373 8574916 1 -1 -1 +17.547264 8367215 8412354 8574945 1 -1 -1 +18.644993 8367202 8412396 8574865 1 -1 -1 +19.742720 8367147 8412396 8574915 1 -1 -1 diff --git a/anemometer-wind/merge.sh b/anemometer-wind/merge.sh @@ -0,0 +1,25 @@ +#!/bin/sh + +mkdir -p build +for i in x y z +do + rm -f build/$i + rm -f build/$i-reverse + rm -f build/$i-origin + rm -f build/$i-reverse-origin + rm -f build/$i-fan + rm -f build/$i-fan-origin + rm -f build/$i-fan-and-wind + rm -f build/$i-fan-and-wind-origin +done +for i in $(seq 2 100) +do + for j in x y z + do + f=anemometer-wind/$i/$j + for suffix in "" -origin -reverse -reverse-origin -fan -fan-origin -fan-and-wind -fan-and-wind-origin + do + test -f $f$suffix && cat $f$suffix >> build/$j$suffix + done + done +done diff --git a/gnuplot/daily-stats.gnuplot b/gnuplot/daily-stats.gnuplot @@ -0,0 +1,13 @@ +set terminal svg size 1920,1680 dynamic font 'Liberation Sans, 20' + +set datafile separator '|' +set xtics nomirror out rotate 90 +set ytics nomirror out +set border 1+2 +set output 'build/daily-stats.svg' +plot 'build/daily-stats' using 2:xtic(1) with linespoints title 'Max X',\ + 'build/daily-stats' using 3:xtic(1) with linespoints title 'Max Y',\ + 'build/daily-stats' using 4:xtic(1) with linespoints title 'Max Z',\ + 'build/daily-stats' using 5:xtic(1) with linespoints title 'Avg. X',\ + 'build/daily-stats' using 6:xtic(1) with linespoints title 'Avg. Y',\ + 'build/daily-stats' using 7:xtic(1) with linespoints title 'Avg. Z' diff --git a/guix/manifest.scm b/guix/manifest.scm @@ -0,0 +1,10 @@ +(packages->manifest + (list + (@ (gnu packages statistics) r-dbi) + (@ (gnu packages statistics) r-rsqlite) + (@ (gnu packages statistics) r-sn) + (@ (gnu packages statistics) r-plotrix) + (@ (gnu packages cran) r-fitdistrplus) + (@ (gnu packages statistics) r) + (@ (gnu packages maths) gnuplot) + (@ (gnu packages tex) texlive))) diff --git a/manifest.scm b/manifest.scm @@ -1,7 +0,0 @@ -(use-package-modules tex textutils) - -(use-modules (stables packages texlive)) -(use-modules (gnu packages maths)) - -(packages->manifest - (list gnuplot texlive)) diff --git a/mchs.txt b/mchs.txt @@ -0,0 +1,7 @@ +2021-03-01 +2021-03-06 +2021-03-12 +2021-03-20 +2021-03-21 +2021-03-22 +2021-03-24 diff --git a/sh/properties b/sh/properties @@ -0,0 +1,32 @@ +#!/bin/sh + +db=samples/load-cell.sqlite3 +mkdir -p build + +print_errors() { +sqlite3 $db "SELECT timestamp-(LAG(timestamp,1,0) OVER win) AS dt +FROM samples WHERE ABS(x-$x_mean)>=10000 OR ABS(y-$y_mean)>=10000 OR ABS(z-$z_mean)>=10000 +WINDOW win AS (ORDER BY timestamp) +" > build/errors +sqlite3 $db "SELECT timestamp +FROM samples WHERE ABS(x-$x_mean)>=10000 OR ABS(y-$y_mean)>=10000 OR ABS(z-$z_mean)>=10000 " > build/errors2 +} + +sqlite3 $db "SELECT DATETIME(MIN(timestamp),'unixepoch'),DATETIME(MAX(timestamp),'unixepoch') FROM samples" +sqlite3 $db "SELECT PRINTF('Time span: %d days', (MAX(timestamp)-MIN(timestamp))/(60*60*24)) FROM samples" +sqlite3 $db "SELECT PRINTF('Samples size: %d mb', SUM(pgsize)/1024/1024) FROM dbstat WHERE name='samples'" +sqlite3 $db "SELECT PRINTF('Sample count: %d', COUNT(*)) FROM samples" +x_mean=$(sqlite3 $db "SELECT AVG(x) FROM samples") +y_mean=$(sqlite3 $db "SELECT AVG(y) FROM samples") +z_mean=$(sqlite3 $db "SELECT AVG(z) FROM samples") +echo "X mean = $x_mean" +echo "Y mean = $y_mean" +echo "z mean = $z_mean" +echo -n "Sample count after filtering: " +sqlite3 $db "SELECT COUNT(*) FROM samples WHERE ABS(x-$x_mean)<10000 AND ABS(y-$y_mean)<10000 AND ABS(z-$z_mean)<10000" +sqlite3 $db " +SELECT strftime('%Y-%m-%d', datetime(timestamp,'unixepoch')) AS d, MAX(x),MAX(y),MAX(z), AVG(x),AVG(y),AVG(z) +FROM samples +WHERE ABS(x-$x_mean)<10000 AND ABS(y-$y_mean)<10000 AND ABS(z-$z_mean)<10000 +GROUP BY d +" > build/daily-stats