1
0
Fork 0
mirror of https://github.com/sensebox/opensensmapr synced 2025-02-22 06:23:57 +01:00
This commit is contained in:
noerw 2017-08-14 18:10:16 +02:00
parent af7215fa86
commit f5454c7292
8 changed files with 42 additions and 31 deletions

View file

@ -15,7 +15,7 @@ Suggests:
rmarkdown rmarkdown
Author: Norwin Roosen Author: Norwin Roosen
Maintainer: Norwin Roosen <noerw@gmx.de> Maintainer: Norwin Roosen <noerw@gmx.de>
Description: This packages ingests data (measurements, sensorstations) from the Description: This package ingests data (measurements, sensorstations) from the
API of opensensemap.org for analysis in R. API of opensensemap.org for analysis in R.
The package aims to be compatible with sf and the tidyverse. The package aims to be compatible with sf and the tidyverse.
License: GPL-2 License: GPL-2

View file

@ -4,8 +4,6 @@
# for CSV responses (get_measurements) the readr package is a hidden dependency # for CSV responses (get_measurements) the readr package is a hidden dependency
# ============================================================================== # ==============================================================================
# does not actually get called by the user. ... contains all the query parameters.
# the proxy is just for parameter autocompletion, filtering out the endpoint
get_boxes_ = function (..., endpoint) { get_boxes_ = function (..., endpoint) {
response = httr::GET(endpoint, path = c('boxes'), query = list(...)) %>% response = httr::GET(endpoint, path = c('boxes'), query = list(...)) %>%
httr::content() %>% httr::content() %>%

22
R/box.R
View file

@ -25,7 +25,15 @@
#' @seealso \code{\link{osem_phenomena}} #' @seealso \code{\link{osem_phenomena}}
#' @export #' @export
#' @examples #' @examples
#' # TODO #' # get *all* boxes available on the API
#' b = osem_boxes()
#'
#' # get all boxes with grouptag 'ifgi' that are placed outdoors
#' b = osem_boxes(grouptag = 'ifgi', exposure = 'outdoor')
#'
#' # get all boxes that have measured PM2.5 in the last 4 hours
#' b = osem_boxes(date = Sys.time(), phenomenon = 'PM2.5')
#'
osem_boxes = function (exposure = NA, model = NA, grouptag = NA, osem_boxes = function (exposure = NA, model = NA, grouptag = NA,
date = NA, from = NA, to = NA, phenomenon = NA, date = NA, from = NA, to = NA, phenomenon = NA,
endpoint = 'https://api.opensensemap.org') { endpoint = 'https://api.opensensemap.org') {
@ -52,14 +60,10 @@ osem_boxes = function (exposure = NA, model = NA, grouptag = NA,
if (!is.na(grouptag)) query$grouptag = grouptag if (!is.na(grouptag)) query$grouptag = grouptag
if (!is.na(phenomenon)) query$phenomenon = phenomenon if (!is.na(phenomenon)) query$phenomenon = phenomenon
if (!is.na(to) && !is.na(from)) { if (!is.na(to) && !is.na(from))
# error, if from is after to
# convert dates to commaseparated UTC ISOdates
query$date = parse_dateparams(from, to) %>% paste(collapse = ',') query$date = parse_dateparams(from, to) %>% paste(collapse = ',')
else if (!is.na(date))
} else if (!is.na(date)) {
query$date = utc_date(date) %>% date_as_isostring() query$date = utc_date(date) %>% date_as_isostring()
}
do.call(get_boxes_, query) do.call(get_boxes_, query)
} }
@ -76,7 +80,9 @@ osem_boxes = function (exposure = NA, model = NA, grouptag = NA,
#' @seealso \code{\link{osem_phenomena}} #' @seealso \code{\link{osem_phenomena}}
#' @export #' @export
#' @examples #' @examples
#' # TODO #' # get a specific box by ID
#' b = osem_box('593bcd656ccf3b0011791f5a')
#'
osem_box = function (boxId, endpoint = 'https://api.opensensemap.org') { osem_box = function (boxId, endpoint = 'https://api.opensensemap.org') {
get_box_(boxId, endpoint = endpoint) get_box_(boxId, endpoint = endpoint)
} }

View file

@ -14,7 +14,7 @@ plot.sensebox = function (x, ...) {
#' @export #' @export
print.sensebox = function(x, ...) { print.sensebox = function(x, ...) {
important_columns = c('name', 'exposure', 'lastMeasurement', 'phenomena') important_columns = c('name', 'exposure', 'lastMeasurement', 'phenomena')
data = as.data.frame(x) # to get rid of the sf::`<-[` override.. data = as.data.frame(x)
print(data[important_columns], ...) print(data[important_columns], ...)
invisible(x) invisible(x)
@ -39,8 +39,7 @@ summary.sensebox = function(object, ...) {
'365d' = nrow(object[diffNow <= 8760, ]) - neverActive, '365d' = nrow(object[diffNow <= 8760, ]) - neverActive,
'never' = neverActive 'never' = neverActive
) )
) %>% ) %>% print()
print()
oldest = object[object$createdAt == min(object$createdAt), ] oldest = object[object$createdAt == min(object$createdAt), ]
newest = object[object$createdAt == max(object$createdAt), ] newest = object[object$createdAt == max(object$createdAt), ]

View file

@ -53,7 +53,7 @@ osem_measurements.default = function (x, ...) {
#' bbox = structure(c(7, 51, 8, 52), class = 'bbox') #' bbox = structure(c(7, 51, 8, 52), class = 'bbox')
#' osem_measurements(bbox, 'Temperatur') #' osem_measurements(bbox, 'Temperatur')
#' #'
#' points = sf::st_multipoint(x = matrix(c(7,8,51,52),2,2)) #' points = sf::st_multipoint(matrix(c(7, 8, 51, 52), 2, 2))
#' bbox2 = sf::st_bbox(points) #' bbox2 = sf::st_bbox(points)
#' osem_measurements(bbox2, 'Temperatur', exposure = 'outdoor') #' osem_measurements(bbox2, 'Temperatur', exposure = 'outdoor')
#' #'
@ -98,7 +98,10 @@ osem_measurements.sensebox = function (x, phenomenon, exposure = NA,
parse_get_measurements_params = function (params) { parse_get_measurements_params = function (params) {
if (is.null(params$phenomenon) | is.na(params$phenomenon)) if (is.null(params$phenomenon) | is.na(params$phenomenon))
stop('Parameter "phenomenon" is required') stop('Parameter "phenomenon" is required')
if (!is.na(params$from) && is.na(params$to)) stop('specify "from" only together with "to"')
if (!is.na(params$from) && is.na(params$to))
stop('specify "from" only together with "to"')
if ( if (
(!is.null(params$bbox) && !is.null(params$boxes)) || (!is.null(params$bbox) && !is.null(params$boxes)) ||
(is.null(params$bbox) && is.null(params$boxes)) (is.null(params$bbox) && is.null(params$boxes))
@ -113,6 +116,7 @@ parse_get_measurements_params = function (params) {
query$`from-date` = utc_date(params$from) %>% date_as_isostring() query$`from-date` = utc_date(params$from) %>% date_as_isostring()
if (!is.na(params$to)) if (!is.na(params$to))
query$`to-date` = utc_date(params$to) %>% date_as_isostring() query$`to-date` = utc_date(params$to) %>% date_as_isostring()
if (!is.na(params$exposure)) query$exposure = params$exposure if (!is.na(params$exposure)) query$exposure = params$exposure
if (!is.na(params$columns)) query$columns = paste(params$columns, collapse = ',') if (!is.na(params$columns)) query$columns = paste(params$columns, collapse = ',')

View file

@ -1,3 +1,5 @@
# ==============================================================================
#
#' Convert a \code{sensebox} or \code{osem_measurements} dataframe to an #' Convert a \code{sensebox} or \code{osem_measurements} dataframe to an
#' \code{\link[sf]{st_sf}} object. #' \code{\link[sf]{st_sf}} object.
#' #'
@ -18,6 +20,7 @@ osem_remote_error = function (response) {
invisible(response) invisible(response)
} }
# parses from/to params for get_measurements_ and get_boxes_
parse_dateparams = function (from, to) { parse_dateparams = function (from, to) {
from = utc_date(from) from = utc_date(from)
to = utc_date(to) to = utc_date(to)
@ -35,4 +38,4 @@ utc_date = function (date) {
} }
# NOTE: cannot handle mixed vectors of POSIXlt and POSIXct # NOTE: cannot handle mixed vectors of POSIXlt and POSIXct
date_as_isostring = function (date) format(date, format = '%FT%TZ') date_as_isostring = function (date) format.Date(date, format = '%FT%TZ')

View file

@ -16,7 +16,7 @@ knitr::opts_chunk$set(echo = TRUE)
## Analyzing environmental sensor data from openSenseMap.org in R ## Analyzing environmental sensor data from openSenseMap.org in R
This package provides data ingestion functions for almost any data stored on the This package provides data ingestion functions for almost any data stored on the
open data platform <https://opensensemap.org>. open data platform for environemental sensordata <https://opensensemap.org>.
Its main goals are to provide means for: Its main goals are to provide means for:
- big data analysis of the measurements stored on the platform - big data analysis of the measurements stored on the platform
@ -24,7 +24,7 @@ Its main goals are to provide means for:
> *Please note:* The openSenseMap API is sometimes a bit unstable when streaming > *Please note:* The openSenseMap API is sometimes a bit unstable when streaming
long responses, which results in `curl` complaining about `Unexpected EOF`. This long responses, which results in `curl` complaining about `Unexpected EOF`. This
bug is beeing worked on upstream. Meanwhile you have to retry the request when bug is being worked on upstream. Meanwhile you have to retry the request when
this occurs. this occurs.
### Exploring the dataset ### Exploring the dataset
@ -40,8 +40,8 @@ summary(all_sensors)
``` ```
This gives a good overview already: As of writing this, there are more than 600 This gives a good overview already: As of writing this, there are more than 600
sensor stations, of which ~50% are running. Most of them are placed outdoors and sensor stations, of which ~50% are currently running. Most of them are placed
have around 5 sensors each. outdoors and have around 5 sensors each.
The oldest station is from May 2014, while the latest station was registered a The oldest station is from May 2014, while the latest station was registered a
couple of minutes ago. couple of minutes ago.
@ -52,7 +52,7 @@ can help us out here:
plot(all_sensors) plot(all_sensors)
``` ```
Seems like we have to reduce our area of interest to Germany. It seems we have to reduce our area of interest to Germany.
But what do these sensor stations actually measure? Lets find out. But what do these sensor stations actually measure? Lets find out.
`osem_phenomena()` gives us a named list of of the counts of each observed `osem_phenomena()` gives us a named list of of the counts of each observed
@ -66,14 +66,14 @@ str(phenoms)
Thats quite some noise there, with many phenomena being measured by a single Thats quite some noise there, with many phenomena being measured by a single
sensor only, or many duplicated phenomena due to slightly different spellings. sensor only, or many duplicated phenomena due to slightly different spellings.
We should clean that up, but for now let's just filter out the noise and find We should clean that up, but for now let's just filter out the noise and find
those phenomena with the high sensor numbers: those phenomena with high sensor numbers:
```{r} ```{r}
phenoms[phenoms > 20] phenoms[phenoms > 20]
``` ```
Alright, temperature it is! PM2.5 seems to be more interesting to analyze though. Alright, temperature it is! Fine particulate matter (PM2.5) seems to be more
interesting to analyze though.
We should check how many sensor stations provide useful data: We want only those We should check how many sensor stations provide useful data: We want only those
boxes with a PM2.5 sensor, that are placed outdoors and are currently submitting boxes with a PM2.5 sensor, that are placed outdoors and are currently submitting
measurements: measurements:
@ -94,11 +94,12 @@ Thats still more than 200 measuring stations, we can work with that.
### Analyzing sensor data ### Analyzing sensor data
Having analyzed the available data sources, let's finally get some measurements. Having analyzed the available data sources, let's finally get some measurements.
We could call `osem_measurements(pm25_sensors)` now, however we are focussing on We could call `osem_measurements(pm25_sensors)` now, however we are focussing on
a restricted area of interest, the city of Berlin a restricted area of interest, the city of Berlin.
Luckily we can get the measurements filtered by a bounding box as well: Luckily we can get the measurements filtered by a bounding box:
```{r} ```{r}
library(sf) library(sf)
library(units)
library(lubridate) library(lubridate)
# construct a bounding box: 12 kilometers around Berlin # construct a bounding box: 12 kilometers around Berlin
@ -141,7 +142,7 @@ build_osem_counts_timeseries = function (existing_data) {
osem_counts() %>% osem_counts() %>%
list(time = Sys.time()) %>% # attach a timestamp list(time = Sys.time()) %>% # attach a timestamp
as.data.frame() %>% # make it a dataframe. as.data.frame() %>% # make it a dataframe.
dplyr::bind_rows(existing_data) # combine with existing data rbind(existing_data) # combine with existing data
} }
``` ```
@ -163,7 +164,7 @@ Further analysis: `TODO`
### Outlook ### Outlook
Next iterations of this package could include the following features Next iterations of this package could include the following features:
- improved utility functions (`plot`, `summary`) for measurements and boxes - improved utility functions (`plot`, `summary`) for measurements and boxes
- better integration of `sf` for spatial analysis - better integration of `sf` for spatial analysis