Skip to content

Commit de5371a

Browse files
committed
huge update: add some new function and fixed some old ones
1 parent 32df3ed commit de5371a

32 files changed

+528
-72
lines changed

.DS_Store

0 Bytes
Binary file not shown.

.Rbuildignore

+3
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,5 @@
11
^.*\.Rproj$
22
^\.Rproj\.user$
3+
^tests$
4+
^docs$
5+
^.github$

DESCRIPTION

+19-8
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,23 @@
11
Package: arduino
22
Type: Package
3-
Title: What the Package Does in One 'Title Case' Line
4-
Version: 1.0
5-
Date: 2018-02-20
6-
Author: Your Name
7-
Maintainer: Your Name <[email protected]>
8-
Description: One paragraph description of what the package does as one or more full sentences.
3+
Title: Simple Library for Reading Serial Ports
4+
Version: 0.1
5+
Authors@R: c(
6+
person('Hao', 'Zhu', email = '[email protected]', role = c('aut', 'cre'),
7+
comment = c(ORCID = '0000-0002-3386-6076')),
8+
person('Tod', 'Kurt', role = 'aut')
9+
)
10+
Description: Simple C based library for easily reading serial ports. It works
11+
on any POSIX-compatible system, including Mac OS and Linux.
912
License: GPL (>= 2)
10-
Imports: Rcpp (>= 0.12.15)
13+
Imports:
14+
Rcpp (>= 0.12.15),
15+
progress,
16+
glue,
17+
shiny,
18+
plotly
1119
LinkingTo: Rcpp
12-
RoxygenNote: 6.0.1
20+
VignetteBuilder: knitr
21+
Encoding: UTF-8
22+
RoxygenNote: 6.1.1
23+
Roxygen: list(markdown = TRUE)

NAMESPACE

+15-1
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,23 @@
11
# Generated by roxygen2: do not edit by hand
22

33
export(ar_close)
4+
export(ar_collect)
45
export(ar_flush)
6+
export(ar_flush_hard)
57
export(ar_init)
8+
export(ar_monitor)
9+
export(ar_plotter)
610
export(ar_read)
7-
export(ar_stream)
11+
export(ar_sep_comma)
12+
import(progress)
13+
import(shiny)
814
importFrom(Rcpp,sourceCpp)
15+
importFrom(glue,glue)
16+
importFrom(plotly,"%>%")
17+
importFrom(plotly,add_trace)
18+
importFrom(plotly,plot_ly)
19+
importFrom(plotly,plotlyOutput)
20+
importFrom(plotly,plotlyProxy)
21+
importFrom(plotly,plotlyProxyInvoke)
22+
importFrom(plotly,renderPlotly)
923
useDynLib(arduino)

R/RcppExports.R

+15
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,21 @@ ar_init <- function(serialport, baud = 9600L) {
2727
.Call('_arduino_ar_init', PACKAGE = 'arduino', serialport, baud)
2828
}
2929

30+
#' Check if a file descriptor is still open
31+
#'
32+
#' @description This function checks whether a stored file descriptor is still
33+
#' open.
34+
#'
35+
#' @param fd File descriptor returned by `ar_init()`. Should be an integer.
36+
#' @examples
37+
#' \dontrun{
38+
#' con <- ar_init("/dev/cu.SLAB_USBtoUART")
39+
#' ar_is_open(con)
40+
#' }
41+
ar_is_open <- function(fd) {
42+
.Call('_arduino_ar_is_open', PACKAGE = 'arduino', fd)
43+
}
44+
3045
#' Close Connection to a serial port
3146
#'
3247
#' @description This function closes the connection opened by `ar_init()`.

R/ar_collect.R

+22
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
#' Stream serial port data into R console
2+
#'
3+
#' @description This function wraps around `ar_read()` and will read serial
4+
#' port data into R console until user stop it.
5+
#'
6+
#' @param size Size
7+
#' @inheritParams ar_monitor
8+
#'
9+
#' @export
10+
ar_collect <- function(fd, size = 100, flush_time = 0.5,
11+
eolchar = "\n", buf_max = 256, timeout = 5000) {
12+
message("Flushing Port...")
13+
ar_flush_hard(fd, flush_time = flush_time)
14+
out <- character()
15+
pb <- progress::progress_bar$new(total = size)
16+
for (i in seq(size)) {
17+
out[i] <- ar_read(fd, eolchar, buf_max, timeout)
18+
pb$tick()
19+
}
20+
message("Done")
21+
return(out)
22+
}

R/ar_flush_hard.R

+18
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
#' Flush serial port in the hard way
2+
#'
3+
#' @description In theory `ar_flush` should work but it didn't work out for me
4+
#' at least. So I recreated this `flush` feature in R, which basically let the
5+
#' data flow for a short time (default 50 ms). The selection of this value
6+
#' depends of many factors including the USB port and the size of data so please
7+
#' pick this value wisely.
8+
#'
9+
#' @inheritParams ar_monitor
10+
#' @param include_c_flush T/F for whether to call ar_flush at the beginning
11+
#' @export
12+
ar_flush_hard <- function(fd, flush_time = 0.05, include_c_flush = TRUE) {
13+
if (include_c_flush) ar_flush(fd)
14+
start_time <- as.numeric(Sys.time())
15+
while ((as.numeric(Sys.time()) - start_time) < flush_time) {
16+
ar_read(fd)
17+
}
18+
}

R/ar_monitor.R

+15
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
#' Stream serial port data into R console
2+
#'
3+
#' @description This function wraps around `ar_read()` and will read serial
4+
#' port data into R console until user stop it.
5+
#' @param flush_time Time to flush buffed results in the serial channel
6+
#'
7+
#' @inheritParams ar_read
8+
#'
9+
#' @export
10+
ar_monitor <- function(fd, flush_time = 0.5,
11+
eolchar = "\n", buf_max = 256, timeout = 5000) {
12+
message("Flushing Port...")
13+
ar_flush_hard(fd, flush_time)
14+
repeat (cat(ar_read(fd, eolchar, buf_max, timeout)))
15+
}

R/ar_plotter.R

+134
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,134 @@
1+
#' Arduino Plotter
2+
#'
3+
#' @param names Labels for variables
4+
#' @param sep_fun A function that separates the inline string into different
5+
#' variables. By default, it is `ar_sep_comma`, which splits the string by
6+
#' comma. You can easily write your own function, which can even do additional
7+
#' calculation.
8+
#' @param reduce_freq T/F. It might be the case that plotly streaming API can't
9+
#' process frequency > 25 Hz (40ms delay time) or it might be the case that
10+
#' my computer doesn't have enough power. Anyway, I set this option here to
11+
#' add 40ms delay time to reduce the sampling frequency.
12+
#' @inheritParams ar_monitor
13+
#'
14+
#' @export
15+
ar_plotter <- function(fd, names = NULL, sep_fun = ar_sep_comma,
16+
reduce_freq = TRUE, flush_time = 0.05,
17+
eolchar = "\n", buf_max = 256, timeout = 5000) {
18+
shiny::runApp(
19+
ar_app(con = fd, names = names, sep_fun = sep_fun,
20+
flush_time = flush_time, reduce_freq = reduce_freq,
21+
eolchar = eolchar, buf_max = buf_max, timeout = timeout),
22+
launch.browser = rstudioapi::viewer
23+
)
24+
}
25+
26+
# con <- ar_init("/dev/cu.SLAB_USBtoUART", baud = 57600)
27+
28+
ar_app <- function(con, names = NULL, sep_fun = ar_sep_comma,
29+
flush_time = 0.05, reduce_freq = TRUE,
30+
eolchar = "\n", buf_max = 256, timeout = 5000) {
31+
message("Flushing Port...")
32+
ar_flush_hard(con, flush_time)
33+
first_dot <- ar_read(con, eolchar, buf_max, timeout)
34+
if (first_dot == "") {
35+
stop("Your connection is probably dead. Please use ar_init and start",
36+
" a new connection")
37+
}
38+
first_dot <- sep_fun(first_dot)
39+
signal_vars <- seq(length(first_dot))
40+
41+
if (is.null(names)) {
42+
names(signal_vars) <- paste("Var", signal_vars)
43+
names(first_dot) <- paste("Var", signal_vars)
44+
} else {
45+
if (length(names) != length(first_dot)) {
46+
stop(
47+
"The amount of names provided is different from the amount of values."
48+
)
49+
}
50+
names(signal_vars) <- names
51+
names(first_dot) <- names
52+
}
53+
54+
save_file_default <- glue("arduino_{format(Sys.time(), '%Y%m%d_%H%M%S')}.csv")
55+
56+
ui <- fluidPage(
57+
br(),
58+
actionButton("power", label = NULL, icon = icon("power-off", "text-danger"),
59+
width = NULL,
60+
style = "border-radius: 25px; position: absolute; top: 15px; right: 15px;z-index: 20;"),
61+
inline_widget(actionButton("start", icon = icon("play"),
62+
label = NULL, width = "100%"), "50px"),
63+
inline_widget(actionButton("reset", icon = icon("undo"),
64+
label = NULL, width = "100%"), "50px"),
65+
inline_widget(h5("Vars:"), "35px"),
66+
inline_widget(selectInput(
67+
"y_var", label = NULL, choices = signal_vars,
68+
selected = signal_vars, multiple = T
69+
), "calc(95% - 180px);z-index: 15;"),
70+
plotlyOutput("plot", height = "250px"),
71+
inline_widget(checkboxInput("save", strong("Save to file?")), "30%"),
72+
inline_widget(textInput("file", NULL, save_file_default), "65%")
73+
)
74+
75+
server <- function(input, output, session) {
76+
rv <- reactiveValues()
77+
rv$state <- 0
78+
79+
# first_xy <- separateXY(first_dot)
80+
81+
output$plot <- renderPlotly({
82+
req(input$y_var)
83+
input$reset
84+
p <- plot_ly(type = 'scatter', mode = 'lines', line = list(width = 3))
85+
for (y_i in sort(as.integer(input$y_var))) {
86+
p <- add_trace(p, y = first_dot[y_i], name = names(first_dot[y_i]))
87+
}
88+
return(p)
89+
})
90+
91+
observeEvent(input$start, {
92+
rv$state <- 1 - rv$state
93+
start_icon <- icon(c("play", "pause")[rv$state + 1])
94+
updateActionButton(session, "start", icon = start_icon)
95+
ar_flush_hard(con, flush_time)
96+
})
97+
98+
observeEvent(input$reset, {
99+
rv$state <- 0
100+
updateActionButton(session, "start", icon = icon("play"))
101+
ar_flush_hard(con, flush_time)
102+
})
103+
104+
observeEvent(input$save, {
105+
if (!file.exists(input$file)) {
106+
file.create(input$file)
107+
cat(csv_newline(names(first_dot)), file = input$file)
108+
}
109+
}, ignoreInit = TRUE)
110+
111+
observe({
112+
invalidateLater(1)
113+
if (rv$state) {
114+
ar_flush_hard(con, 0.04, FALSE)
115+
realtime <- sep_fun(ar_read(con, eolchar, buf_max, timeout))
116+
if (input$save) {
117+
cat(csv_newline(realtime), file = input$file, append = TRUE)
118+
}
119+
realtime_y <- lapply(realtime[sort(as.integer(input$y_var))], list)
120+
realtime_list <- list(y = realtime_y)
121+
to_traces <- as.list(seq(length(input$y_var)))
122+
plotlyProxy("plot", session) %>%
123+
plotlyProxyInvoke("extendTraces", realtime_list, to_traces)
124+
}
125+
})
126+
127+
observeEvent(input$power, {
128+
invisible(stopApp())
129+
})
130+
}
131+
132+
shinyApp(ui, server)
133+
}
134+

R/ar_sep.R

+16
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
#' Split string by special symbols
2+
#'
3+
#' @description This function determines how the plotter extracts numbers from
4+
#' the readings. By default, it trims of the "new line" symbol at the end of
5+
#' the row and split the string by special symbols (if you have used
6+
#' `tidyr::separate`, they are the same). You can write your own function if you
7+
#' need special processing.
8+
#'
9+
#' @param x Arduino Reading. Usually a string and needs to be chopped and
10+
#' converted to numbers.
11+
#'
12+
#' @export
13+
ar_sep_comma <- function(x) {
14+
x <- sub("\r\n$", "", x)
15+
return(as.numeric(strsplit(x, ",")[[1]]))
16+
}

R/ar_stream.R

-16
This file was deleted.

R/arduino-package.R

+5
Original file line numberDiff line numberDiff line change
@@ -6,4 +6,9 @@
66
#' @keywords package
77
#' @useDynLib arduino
88
#' @importFrom Rcpp sourceCpp
9+
#' @import progress
10+
#' @importFrom glue glue
11+
#' @import shiny
12+
#' @importFrom plotly plot_ly add_trace renderPlotly plotlyProxy
13+
#' plotlyProxyInvoke plotlyOutput %>%
914
NULL

R/utils.R

+9
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
inline_widget <- function(x, width = "100px") {
2+
shiny::div(
3+
style = glue("display: inline-block;vertical-align:top; width: {width};"),
4+
x)
5+
}
6+
7+
csv_newline <- function(x) {
8+
paste0(paste(x, collapse = ","), "\r\n")
9+
}

0 commit comments

Comments
 (0)