Skip to content

Commit

Permalink
modifying get_vessel_info: -respecting the defaults (query, `search…
Browse files Browse the repository at this point in the history
…`) and adding error messages for vesselId search. renaming `id` to `vesselId` in `selfReportedInfo` (#146).

details: add key to last report for consistency.
  • Loading branch information
AndreaSanchezTapia committed Jun 29, 2024
1 parent fbecfeb commit 0cdff74
Show file tree
Hide file tree
Showing 7 changed files with 117 additions and 112 deletions.
2 changes: 1 addition & 1 deletion R/get_last_report.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@
#' get_last_report(key = gfw_auth())
#' }
#'
get_last_report <- function(key) {
get_last_report <- function(key = gfw_auth()) {

# Format request
endpoint <- httr2::request("https://gateway.api.globalfishingwatch.org/v3/4wings/last-report") %>%
Expand Down
42 changes: 21 additions & 21 deletions R/get_vessel_info.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,7 @@
#' @param query When `search_type = "search"`, a length-1 vector with the identity
#' variable of interest, MMSI, IMO, call sign or ship name.
#' @param where When `search_type = "search"`, an SQL expression to find the vessel of interest
#' @param ids When `search_type = "id"`, a vector with the vessel id of interest,
#' obtained after performing a search_type = "search".
#' @param ids When `search_type = "id"`, a vector with the vesselId of interest
#' @param search_type Type of vessel search to perform. Can be `"search"` or
#' `"id"`. (Note:`"advanced"` and `"basic"` are no longer in use as of gfwr 2.0.0.)
#' @param match_fields Optional. Allows to filter by `matchFields` levels.
Expand Down Expand Up @@ -65,9 +64,9 @@
#' ids = c("8c7304226-6c71-edbe-0b63-c246734b3c01"),
#' registries_info_data = c("DELTA"), key = gfw_auth())
#' @export
get_vessel_info <- function(ids = NULL,
query = NULL,
get_vessel_info <- function(query = NULL,
where = NULL,
ids = NULL,
includes = c("AUTHORIZATIONS", "OWNERSHIP", "MATCH_CRITERIA"),
match_fields = NULL,
registries_info_data = c("ALL"),
Expand All @@ -78,7 +77,7 @@ get_vessel_info <- function(ids = NULL,

if (search_type %in% c("advanced", "basic")) {
# Signal the deprecation to the user
warning("basic or advanced search are no longer in use as of gfwr 2.0.0. Options are 'search' or 'id'. Use `query` for simple queries and `where` for advanced SQL expressions")
warning("basic or advanced search are no longer in use. Options are 'search' or 'id'")
search_type <- "search"
}

Expand All @@ -104,22 +103,10 @@ dataset <- "public-global-vessel-identity:latest"
dataset <- vector_to_array(dataset, type = "datasets")
args <- c(args, dataset)

# ID search now receives a vector
if (search_type == "id") {
if (is.null(ids)) stop("parameter ids must be specified when search_type = 'id'")
ids <- vector_to_array(ids, type = "ids")

path_append <- "vessels"
if (!is.null(registries_info_data)) {
reg_info <- c(`registries-info-data` = registries_info_data)
args <- c(args, reg_info)
}
args <- c(args,
ids)
#args <- args[!names(args) %in% c('limit','offset')]
} else if (search_type == "search") {
if (is.null(query) & is.null (where)) stop("either 'query' or 'where' must be specified when search_type = 'search'")
if (!is.null(query) & !is.null (where)) stop("specify either 'query' or 'where', but not both when search_type = 'search'")
#Default is search
if (search_type == "search") {
if (is.null(query) & is.null(where)) stop("either 'query' or 'where' must be specified when search_type = 'search'")
if (!is.null(query) & !is.null(where)) stop("specify either 'query' or 'where', but not both when search_type = 'search'")
if (!is.null(query)) {
query <- c(`query` = query)
args <- c(args, query)
Expand All @@ -135,7 +122,19 @@ if (search_type == "id") {
incl <- vector_to_array(includes, type = "includes")
args <- c(args, incl)
}
}
# ID search now receives a vector
if (search_type == "id" & is.null(ids)) stop("parameter 'ids' must be specified when search_type = 'id'")
if (!is.null("ids") & is.null(where) & is.null(query) & search_type == "search") stop("search_type must be 'id' when ids are specified")
if (!is.null("ids") & search_type == "id") {
path_append <- "vessels"
ids <- vector_to_array(ids, type = "ids")
args <- c(args, ids)
if (!is.null(registries_info_data)) {
reg_info <- c(`registries-info-data` = registries_info_data)
args <- c(args, reg_info)
}
}

endpoint <- base %>%
httr2::req_url_path_append(path_append) %>%
Expand Down Expand Up @@ -174,5 +173,6 @@ if (print_request) print(endpoint)
selfReportedInfo = dplyr::bind_rows(purrr::map(response$entries$selfReportedInfo, tibble::tibble))
)

output$selfReportedInfo <- output$selfReportedInfo %>% dplyr::rename(vesselId = id)
return(output)
}
8 changes: 5 additions & 3 deletions README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -177,7 +177,7 @@ it in the `get_event()` function.
```{r example_id_event, eval = TRUE}
vessel_info <- get_vessel_info(query = 224224000, key = key)
id <- vessel_info$selfReportedInfo$id[1]
id <- vessel_info$selfReportedInfo$vesselId[1]
```

To get a list of port visits for that vessel:
Expand All @@ -190,6 +190,8 @@ get_event(event_type = 'PORT_VISIT',
)
```

> *Note*: Try narrowing your search using `start_date` and `end_date` if the request is too large and returns a time out error (524)
We can also use more than one `vessel id`:

```{r example_event_type_2, , eval = TRUE}
Expand Down Expand Up @@ -228,7 +230,7 @@ usa_trawlers <- get_vessel_info(
key = key
)
# Pass the vector of vessel ids to Events API
usa_trawler_ids <- usa_trawlers$selfReportedInfo$id[1:20]
usa_trawler_ids <- usa_trawlers$selfReportedInfo$vesselId[1:20]
```
> *Note*: `get_event()` can receive up to 20 vessel ids at a time
Expand Down Expand Up @@ -278,7 +280,7 @@ get_raster(
temporal_resolution = 'YEARLY',
group_by = 'FLAG',
start_date = '2021-01-01',
end_date = '2021-07-01',
end_date = '2021-02-01',
region = test_shape,
region_source = 'USER_JSON',
key = key
Expand Down
Loading

0 comments on commit 0cdff74

Please sign in to comment.