no download progress for non-interactive sessions

also add option to disable progress info manually to
- osem_measurements()
- osem_boxes()

fixes #11
pull/17/head
Norwin 6 years ago
parent 185f668ca8
commit 628825c7f4
Signed by: norwin
GPG Key ID: 24BC059DE24C43A3

@ -25,3 +25,11 @@ dplyr_class_wrapper = function(callback) {
function(.data, ..., .dots) callback(NextMethod())
}
#' Checks for an interactive session using interactive() and a knitr process in
#' the callstack. See https://stackoverflow.com/a/33108841
#'
#' @noRd
isNonInteractive = function () {
ff <- sapply(sys.calls(), function(f) as.character(f[1]))
any(ff %in% c("knit2html", "render")) || !interactive()
}

@ -22,7 +22,7 @@ get_boxes_ = function (..., endpoint) {
}
get_box_ = function (boxId, endpoint) {
osem_request_(endpoint, path = c('boxes', boxId)) %>%
osem_request_(endpoint, path = c('boxes', boxId), progress = F) %>%
parse_senseboxdata()
}
@ -46,14 +46,14 @@ get_measurements_ = function (..., endpoint) {
}
get_stats_ = function (endpoint) {
result = osem_request_(endpoint, path = c('stats'))
result = osem_request_(endpoint, path = c('stats'), progress = F)
names(result) = c('boxes', 'measurements', 'measurements_per_minute')
result
}
osem_request_ = function (host, path, ..., type = 'parsed') {
res = httr::GET(host, httr::progress(), path = path, query = list(...))
#print(res$url)
osem_request_ = function (host, path, ..., type = 'parsed', progress) {
progress = if (progress && !isNonInteractive()) httr::progress() else NULL
res = httr::GET(host, progress, path = path, query = list(...))
if (httr::http_error(res)) {
content = httr::content(res, 'parsed', encoding = 'UTF-8')

@ -19,6 +19,7 @@
#' @param phenomenon Only return boxes that measured the given phenomenon in the
#' time interval as specified through \code{date} or \code{from / to}
#' @param endpoint The URL of the openSenseMap API instance
#' @param progress Whether to print download progress information
#' @return A \code{sensebox data.frame} containing a box in each row
#'
#' @seealso \href{https://docs.opensensemap.org/#api-Measurements-findAllBoxes}{openSenseMap API documentation (web)}
@ -37,7 +38,8 @@
#'
osem_boxes = function (exposure = NA, model = NA, grouptag = NA,
date = NA, from = NA, to = NA, phenomenon = NA,
endpoint = 'https://api.opensensemap.org') {
endpoint = 'https://api.opensensemap.org',
progress = T) {
# error, if phenomenon, but no time given
if (!is.na(phenomenon) && is.na(date) && is.na(to) && is.na(from))
@ -55,7 +57,7 @@ osem_boxes = function (exposure = NA, model = NA, grouptag = NA,
stop('Parameter "from"/"to" must be used together')
}
query = list(endpoint = endpoint)
query = list(endpoint = endpoint, progress = progress)
if (!is.na(exposure)) query$exposure = exposure
if (!is.na(model)) query$model = model
if (!is.na(grouptag)) query$grouptag = grouptag

@ -20,6 +20,7 @@
#' @param to A \code{POSIXt} like object to select a time interval
#' @param columns Select specific column in the output (see oSeM documentation)
#' @param endpoint The URL of the openSenseMap API
#' @param progress Whether to print download progress information
#'
#' @return An \code{osem_measurements data.frame} containing the
#' requested measurements
@ -60,7 +61,8 @@ osem_measurements.default = function (x, ...) {
osem_measurements.bbox = function (x, phenomenon, exposure = NA,
from = NA, to = NA, columns = NA,
...,
endpoint = 'https://api.opensensemap.org') {
endpoint = 'https://api.opensensemap.org',
progress = T) {
bbox = x
environment() %>%
as.list() %>%
@ -84,7 +86,8 @@ osem_measurements.bbox = function (x, phenomenon, exposure = NA,
osem_measurements.sensebox = function (x, phenomenon, exposure = NA,
from = NA, to = NA, columns = NA,
...,
endpoint = 'https://api.opensensemap.org') {
endpoint = 'https://api.opensensemap.org',
progress = T) {
boxes = x
environment() %>%
as.list() %>%
@ -113,7 +116,11 @@ parse_get_measurements_params = function (params) {
(is.null(params$bbox) && is.null(params$boxes))
) stop('Specify either "bbox" or "boxes"')
query = list(endpoint = params$endpoint, phenomenon = params$phenomenon)
query = list(
endpoint = params$endpoint,
phenomenon = params$phenomenon,
progress = params$progress
)
if (!is.null(params$boxes)) query$boxId = paste(params$boxes$X_id, collapse = ',')
if (!is.null(params$bbox)) query$bbox = paste(params$bbox, collapse = ',')
@ -154,8 +161,10 @@ paged_measurements_req = function (query) {
query$`from-date` = date_as_isostring(page$from)
query$`to-date` = date_as_isostring(page$to)
res = do.call(get_measurements_, query)
cat(paste(query$`from-date`, query$`to-date`, sep = ' - '))
cat('\n')
if (query$progress && !isNonInteractive())
cat(paste(query$`from-date`, query$`to-date`, sep = ' - '), '\n')
res
}) %>%
dplyr::bind_rows()

@ -6,7 +6,7 @@
\usage{
osem_boxes(exposure = NA, model = NA, grouptag = NA, date = NA,
from = NA, to = NA, phenomenon = NA,
endpoint = "https://api.opensensemap.org")
endpoint = "https://api.opensensemap.org", progress = T)
}
\arguments{
\item{exposure}{Only return boxes with the given exposure ('indoor', 'outdoor', 'mobile')}
@ -25,6 +25,8 @@ osem_boxes(exposure = NA, model = NA, grouptag = NA, date = NA,
time interval as specified through \code{date} or \code{from / to}}
\item{endpoint}{The URL of the openSenseMap API instance}
\item{progress}{Whether to print download progress information}
}
\value{
A \code{sensebox data.frame} containing a box in each row

@ -12,11 +12,12 @@ osem_measurements(x, ...)
\method{osem_measurements}{default}(x, ...)
\method{osem_measurements}{bbox}(x, phenomenon, exposure = NA, from = NA,
to = NA, columns = NA, ..., endpoint = "https://api.opensensemap.org")
to = NA, columns = NA, ..., endpoint = "https://api.opensensemap.org",
progress = T)
\method{osem_measurements}{sensebox}(x, phenomenon, exposure = NA,
from = NA, to = NA, columns = NA, ...,
endpoint = "https://api.opensensemap.org")
endpoint = "https://api.opensensemap.org", progress = T)
}
\arguments{
\item{x}{Depending on the method, either
@ -40,6 +41,8 @@ osem_measurements(x, ...)
\item{columns}{Select specific column in the output (see oSeM documentation)}
\item{endpoint}{The URL of the openSenseMap API}
\item{progress}{Whether to print download progress information}
}
\value{
An \code{osem_measurements data.frame} containing the

Loading…
Cancel
Save