Skip to content

Commit

Permalink
fix uniqueSpillover and example orgDate
Browse files Browse the repository at this point in the history
  • Loading branch information
Alejandro Ruete committed Jan 15, 2021
1 parent 0d98149 commit 1c41666
Show file tree
Hide file tree
Showing 4 changed files with 31 additions and 20 deletions.
5 changes: 4 additions & 1 deletion R/organizeBirds.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,10 @@ findCols <- function(pattern, df, exact=FALSE, value = TRUE){
#' @export
#' @examples
#' ymd<-as.Date(Sys.Date())+1:5
#' organizeDate(as.data.frame(ymd), "ymd")
#' id<-1:5
#' organizeDate(data.frame("id"=id,
#' "ymd"=as.character(ymd)),
#' "ymd")
#' @keywords internal
organizeDate <- function(x, columns){
if (!length(columns) %in% c(1,3)) stop("Could not create date, please specify either one or three column names")
Expand Down
5 changes: 5 additions & 0 deletions R/overlayBirds.R
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,11 @@ includeUniqueSpillover <- function(birdData, grid, visitCol){
stop("Organized data and grid do not share the same CRS")
}

## rename grids id no have integers
for(i in 1:length(grid)){
slot(slot(grid, "polygons")[[i]], "ID") <- as.character(i)
}

#Extract the unique ID from the polygons in the spdf
ids <- data.frame(
matrix(
Expand Down
36 changes: 18 additions & 18 deletions R/summarizeBirds.R
Original file line number Diff line number Diff line change
Expand Up @@ -70,21 +70,24 @@ getSpatial<-function(birdOverlay, visitCol=NULL){

cols2use<-c("scientificName", "year", "month", "day", visitCol)

dataRes<-lapply(dataList[birdOverlay$nonEmptyGridCells], function(x){

x<-x[,cols2use]
colnames(x) <- c("scientificName", "year", "month", "day", "visitCol")

return(c("nObs"=length(x[,"scientificName"]),
"nVis"=length(unique(x[,"visitCol"])),
"nSpp"=length(unique(x[,"scientificName"])),
"avgSll"= median(summarise(group_by(x, visitCol),
avgSLL=n_distinct(.data$scientificName))$avgSLL),
"nDays"=length(unique( paste0(x[,"year"],"-", as.numeric(x[,"month"]), "-", as.numeric(x[,"day"]))) ),
"nYears"=length(unique(x[,"year"])),
"visitsUID"= paste0(unique(x[,"visitCol"]), collapse = ",")
))
})
dataRes<-lapply(dataList[birdOverlay$nonEmptyGridCells],
function(x){
x<-x[,cols2use]
colnames(x) <- c("scientificName", "year", "month", "day", "visitCol")

tmp <- c("nObs"=length(x[,"scientificName"]),
"nVis"=length(unique(x[,"visitCol"])),
"nSpp"=length(unique(x[,"scientificName"])),
"avgSll"= median(summarise(group_by(x, .data$visitCol),
avgSLL=n_distinct(.data$scientificName))$avgSLL),
"nDays"=length(unique( paste0(x[,"year"],"-",
as.numeric(x[,"month"]), "-",
as.numeric(x[,"day"]))) ),
"nYears"=length(unique(x[,"year"])),
"visitsUID"= paste0(unique(x[,"visitCol"]), collapse = ",")
)
return(tmp)
})

dataRes<-data.frame(matrix(unlist(dataRes),
nrow=length(dataRes), byrow=TRUE),
Expand Down Expand Up @@ -314,15 +317,13 @@ summarizeBirds.OrganizedBirds<-function(x, grid, spillOver = NULL){
stop("The variable grid can only be of class SpatialPolygonsDataFrame, or NULL")
}
}else{

areaGrid <- OB2Polygon(x)
bTOver <- overlayBirds(x, grid=areaGrid, spillOver = spillOver)
warning("To get the most out of summarizeBirds you should have a grid.")
}

#Here we use a modifyed version of bOver where the grid is only one single cell.
temporal <- getTemporal(bTOver)

if(useSpatial){
#If we have spatial grid data:
spatial <- getSpatial(bOver)
Expand All @@ -333,7 +334,6 @@ summarizeBirds.OrganizedBirds<-function(x, grid, spillOver = NULL){
spatioTemporal <- getSpatioTemporal(bTOver, visitCol=visitCol)
wNonEmptyCells <- bTOver$nonEmptyGridCells
}

res <- list("temporal" = temporal,
"spatial" = spatial,
"spatioTemporal" = spatioTemporal$resYM,
Expand Down
5 changes: 4 additions & 1 deletion man/organizeDate.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 1c41666

Please sign in to comment.