Skip to content

Commit

Permalink
Verbose option, CRAN release
Browse files Browse the repository at this point in the history
  • Loading branch information
rosieluain committed Sep 6, 2023
1 parent 60c572c commit a5dc9d4
Show file tree
Hide file tree
Showing 23 changed files with 264 additions and 195 deletions.
182 changes: 115 additions & 67 deletions R/mort.R

Large diffs are not rendered by default.

28 changes: 14 additions & 14 deletions R/options.R
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,7 @@ backwards<-function(data,morts,ID,station,res.start,stnchange=NULL){
#' considered a single residence event. Default is `NULL`.
#' @param cutoff.units the units of the cutoff. Options are "secs", "mins", "hours",
#' "days", and "weeks".
#' @param progress.bar option to display progress bar as `drift` is applied.
#' @param verbose option to display progress bar as `drift` is applied.
#' Default is TRUE.
#'
#' @return A data frame with one row for each residence event. Format is the
Expand All @@ -145,17 +145,17 @@ backwards<-function(data,morts,ID,station,res.start,stnchange=NULL){
#'
#' drift.events<-drift(data=events[events$ID=="A",],type="mort",ID="ID",
#' station="Station.Name",ddd=ddd,from.station="From",to.station="To",
#' progress.bar=FALSE)
#' verbose=FALSE)
#' head(drift.events)
#'
#' # With cutoff:
#' drift.events<-drift(data=events[events$ID=="A",],type="mort",ID="ID",
#' station="Station.Name",ddd=ddd,from.station="From",to.station="To",
#' cutoff=1,cutoff.units="days",progress.bar=FALSE)
#' cutoff=1,cutoff.units="days",verbose=FALSE)
#' head(drift.events)
drift<-function(data,type,ID,station,res.start="auto",res.end="auto",
residences="auto",units="auto",ddd,from.station,to.station,
cutoff=NULL,cutoff.units=NULL,progress.bar=TRUE){
cutoff=NULL,cutoff.units=NULL,verbose=TRUE){

if (type %in% c("actel","vtrack")){
data<-extractres(data=data,type=type)
Expand Down Expand Up @@ -216,7 +216,7 @@ drift<-function(data,type,ID,station,res.start="auto",res.end="auto",

res.drift<-data[0,]

if (progress.bar==TRUE){
if (verbose==TRUE){
pb<-txtProgressBar(1,length(tag),style=3)
}
for (i in 1:length(tag)){
Expand Down Expand Up @@ -257,7 +257,7 @@ drift<-function(data,type,ID,station,res.start="auto",res.end="auto",
}
}
res.drift[(nrow(res.drift)+1):(nrow(res.drift)+nrow(res.temp)),]<-res.temp[,]
if (progress.bar==TRUE){
if (verbose==TRUE){
setTxtProgressBar(pb,i)
}
}
Expand Down Expand Up @@ -310,8 +310,8 @@ drift<-function(data,type,ID,station,res.start="auto",res.end="auto",
#' residence events that is within the period of interest will be retained,
#' and `residences` will be recalculated, using specified `units`.
#' Default is `TRUE`.
#' @param progress.bar option to display progress bar as function is run. Default
#' is TRUE.
#' @param verbose option to display updates and progress bars as
#' functions is run. Default is TRUE.
#'
#' @return a dataframe in the same format as the input data, with residence
#' events limited to the period(s) of interest.
Expand All @@ -321,18 +321,18 @@ drift<-function(data,type,ID,station,res.start="auto",res.end="auto",
#' # Seasons in format dd-mm
#' season.events<-season(data=events,type="mort",ID="ID",
#' station="Station.Name",season.start="01-06",season.end="31-10",
#' progress.bar=FALSE)
#' verbose=FALSE)
#' head(season.events)
#'
#' # Seasons in format YYYY-mm-dd HH:MM:SS
#' season.start<-c("2003-06-15","2004-06-21")
#' season.end<-c("2003-10-15","2004-10-30")
#' season.events<-season(data=events,type="mort",ID="ID",
#' station="Station.Name",season.start=season.start,season.end=season.end,progress.bar=FALSE)
#' station="Station.Name",season.start=season.start,season.end=season.end,verbose=FALSE)
#' head(season.events)
season<-function(data,type="mort",ID,station,res.start="auto",res.end="auto",
residences="auto",units="auto",season.start,
season.end,overlap=TRUE,progress.bar=TRUE){
season.end,overlap=TRUE,verbose=TRUE){

if (type %in% c("actel","vtrack")){
data<-extractres(data=data,type=type)
Expand Down Expand Up @@ -435,11 +435,11 @@ season<-function(data,type="mort",ID,station,res.start="auto",res.end="auto",
data.season<-data[0,]

for (i in 1:length(season.start)){
if (progress.bar==TRUE){
if (verbose==TRUE){
print(paste("season/period",i,"of",length(season.start)))
}
if (length(tag)>1){
if (progress.bar==TRUE){
if (verbose==TRUE){
pb<-txtProgressBar(1,length(tag),style=3)
}
}
Expand Down Expand Up @@ -483,7 +483,7 @@ season<-function(data,type="mort",ID,station,res.start="auto",res.end="auto",
}
data.season<-rbind(data.season,data.temp)
if (length(tag)>1){
if (progress.bar==TRUE){
if (verbose==TRUE){
setTxtProgressBar(pb,j)
}
}
Expand Down
16 changes: 9 additions & 7 deletions R/plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,8 +44,8 @@
#' `facet.by="year"`.
#' @param facet.by option to facet by "season" (as defined with `season.start`
#' and `season.end`) or "year". Default is "season".
#' @param progress.bar option to display progress bar as function is run. Default
#' is TRUE.
#' @param verbose option to display updates and progress bar as function is run.
#' Default is TRUE.
#'
#' @return a ggplot2 plot. Additional arguments (e.g., formatting axes,
#' legend, aes, manual colour scales) can be added as for any ggplot2 plot.
Expand All @@ -60,7 +60,7 @@
#'
#' # With mortalities plotted over residences:
#' morts<-morts(data=events,type="mort",ID="ID",station="Station.Name",
#' method="any",progress.bar=FALSE)
#' method="any",verbose=FALSE)
#'
#' plot<-mortsplot(data=events,type="mort",ID="ID",station="Station.Name",
#' morts=morts)
Expand All @@ -70,7 +70,7 @@ mortsplot<-function(data,type,ID,station,res.start="auto",res.end="auto",
units=NULL,
season.start=NULL,season.end=NULL,facet=FALSE,
facet.axis="x",facet.by="season",
progress.bar=TRUE){
verbose=TRUE){

if (!requireNamespace("ggplot2", quietly = TRUE)) {
stop("Package \"ggplot2\" must be installed to use this function.",
Expand Down Expand Up @@ -176,7 +176,7 @@ mortsplot<-function(data,type,ID,station,res.start="auto",res.end="auto",
if (units=="auto"){
units<-autofield(type=type,field="units",data=data)
}
if (progress.bar==TRUE){
if (verbose==TRUE){
print("Extracting data from the period/season(s) of interest")
}
if (is.null(season.start)&is.null(season.end)&facet.by=="year"){
Expand All @@ -185,7 +185,7 @@ mortsplot<-function(data,type,ID,station,res.start="auto",res.end="auto",
}
data<-season(data=data,type=type,ID=ID,station=station,res.start=res.start,res.end=res.end,
residences=residences,units=units,season.start=season.start,
season.end=season.end,overlap=FALSE,progress.bar=progress.bar)
season.end=season.end,overlap=FALSE,verbose=verbose)
data<-data[data[[station]]!="Break",]
if (!is(season.start,"POSIXt")){
try(season.start<-as.POSIXct(season.start,tz="UTC"),silent=TRUE)
Expand Down Expand Up @@ -214,7 +214,9 @@ mortsplot<-function(data,type,ID,station,res.start="auto",res.end="auto",
ssn<-data.frame(Start=season.start,End=season.end)
ssn<-ssn[order(ssn$Start),]
if (!is.null(morts)){
print("Extracting morts from the period/season(s) of interest")
if (verbose==TRUE){
print("Extracting morts from the period/season(s) of interest")
}
morts.ssn<-season(data=morts,ID=ID,station=station,res.start=res.start,
res.end=res.end,
residences=residences,units=units,season.start=season.start,
Expand Down
10 changes: 5 additions & 5 deletions R/residences.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
#' @param ID a string of the name of the column in `data` that holds the tag or sample IDs.
#' @param datetime a string of the name of the column in `data` that holds the date and time.
#' @param station a string of the name of the column in `data` that holds the station name or receiver location.
#' @param progress.bar option to display progress bar as residences are generated.
#' @param verbose option to display progress bar as residences are generated.
#' Default is TRUE.
#'
#' @return A data frame with one row for each residence event, including date/time of
Expand All @@ -27,10 +27,10 @@
#' @examples
#' head(detections)
#' res.events<-residences(data=detections[1:500,],ID="ID",station="Station.Name",
#' datetime="DateTimeUTC",cutoff=1,units="days",progress.bar=FALSE)
#' datetime="DateTimeUTC",cutoff=1,units="days",verbose=FALSE)
#' head(res.events)

residences<-function(data,ID,station,datetime,cutoff,units,progress.bar=TRUE){
residences<-function(data,ID,station,datetime,cutoff,units,verbose=TRUE){
# Create list of unique IDs
tag<-unique(na.omit(data[[ID]]))

Expand All @@ -55,7 +55,7 @@ residences<-function(data,ID,station,datetime,cutoff,units,progress.bar=TRUE){
# Set up res
res<-cbind(data[0,],ResidenceEnd=as.POSIXct(as.character()))

if (progress.bar==TRUE){
if (verbose==TRUE){
pb<-txtProgressBar(1,length(tag),style=3)
}
for (i in 1:length(tag)){
Expand Down Expand Up @@ -115,7 +115,7 @@ residences<-function(data,ID,station,datetime,cutoff,units,progress.bar=TRUE){
break
}
}
if (progress.bar==TRUE){
if (verbose==TRUE){
setTxtProgressBar(pb,i)
}
}
Expand Down
10 changes: 5 additions & 5 deletions R/review.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@
#' @param residences an optional character string with the name of the column
#' in `morts` and `new.data` that holds the duration of the residence events.
#' Only needed if drift is applied.
#' @param progress.bar option to display progress bar as function and called
#' @param verbose option to display progress bar as function and called
#' functions are run. Default is TRUE.
#'
#' @return A dataframe with one row for each tag ID from `morts`
Expand All @@ -51,14 +51,14 @@
#'
#' @examples
#' morts<-morts(data=events,type="mort",ID="ID",station="Station.Name",
#' method="any",progress.bar=FALSE)
#' method="any",verbose=FALSE)
#'
#' undead<-review(morts=morts,new.data=new.data,
#' type="mort",ID="ID",station="Station.Name",progress.bar=FALSE)
#' type="mort",ID="ID",station="Station.Name",verbose=FALSE)
review<-function(morts,new.data,old.data=NULL,type,ID,station,res.start="auto",
res.end=NULL,residences=NULL,units=NULL,
ddd=NULL,from.station=NULL,to.station=NULL,
progress.bar=TRUE){
verbose=TRUE){

if (type %in% c("actel","vtrack")){
new.data<-extractres(data=new.data,type=type)
Expand Down Expand Up @@ -202,7 +202,7 @@ review<-function(morts,new.data,old.data=NULL,type,ID,station,res.start="auto",
res.start=res.start,res.end=res.end,
ddd=ddd,from.station=from.station,to.station=to.station,
residences=residences,
units=units,progress.bar=progress.bar)
units=units,verbose=verbose)
for (i in 1:nrow(morts)){
res.temp<-data[data[[ID]]==morts[[ID]][i],]
j<-1
Expand Down
36 changes: 18 additions & 18 deletions R/stationchange.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@
#' @param to.station a string of the name of the column in `ddd` that contains
#' the station/location names where drifting detections may move to. Must
#' be identical to the station/location names in `data`.
#' @param progress.bar option to display progress bar as function is run. Default
#' @param verbose option to display progress bar as function is run. Default
#' is TRUE.
#'
#' @return a dataframe with one row for each tag ID, including the date/time of
Expand All @@ -44,12 +44,12 @@
#' @export
#'
#' @examples
#' stn.change<-stationchange(data=events,type="mort",ID="ID",station="Station.Name",progress.bar=FALSE)
#' stn.change<-stationchange(data=events,type="mort",ID="ID",station="Station.Name",verbose=FALSE)
#' head(stn.change)
stationchange<-function(data,type="mort",ID,station,res.start="auto",
res.end="auto",residences="auto",
singles=TRUE,drift=FALSE,ddd=NULL,units=NULL,from.station=NULL,
to.station=NULL,progress.bar=TRUE){
to.station=NULL,verbose=TRUE){

if (type %in% c("actel","vtrack")&is(data,"list")){
data<-extractres(data=data,type=type)
Expand Down Expand Up @@ -93,7 +93,7 @@ stationchange<-function(data,type="mort",ID,station,res.start="auto",

if (drift==FALSE&
!is(data[[station]],"list")){
if (progress.bar==TRUE){
if (verbose==TRUE){
pb<-txtProgressBar(1,length(tag),style=3)
}
for (i in 1:length(tag)){
Expand Down Expand Up @@ -134,7 +134,7 @@ stationchange<-function(data,type="mort",ID,station,res.start="auto",
else if (nrow(res.temp)==1){
stn.change[nrow(stn.change)+1,]<-res.temp[1,]
}
if (progress.bar==TRUE){
if (verbose==TRUE){
setTxtProgressBar(pb,i)
}
}
Expand All @@ -145,7 +145,7 @@ stationchange<-function(data,type="mort",ID,station,res.start="auto",
data.drift<-drift(data=data,type=type,ID=ID,station=station,
res.start=res.start,res.end=res.end,residences=residences,
units=units,ddd=ddd,from.station=from.station,to.station=to.station,
progress.bar=progress.bar)
verbose=verbose)
}
else {data.drift<-data}
pb<-txtProgressBar(1,length(tag),style=3)
Expand Down Expand Up @@ -214,7 +214,7 @@ stationchange<-function(data,type="mort",ID,station,res.start="auto",
#' recent station or location change. Must use the same column names as `data`.
#' @param drift indicates if drift residence events should be included in
#' determining the maximum residence duration
#' @param progress.bar option to display progress bar as function is run. Default
#' @param verbose option to display progress bar as function is run. Default
#' is TRUE.
#'
#' @return a dataframe with the residence information for the longest residence
Expand All @@ -224,17 +224,17 @@ stationchange<-function(data,type="mort",ID,station,res.start="auto",
#' @examples
#' # Identify most recent station change
#' station.change<-stationchange(data=events,type="mort",ID="ID",
#' station="Station.Name",progress.bar=FALSE)
#' station="Station.Name",verbose=FALSE)
#'
#' longest_res_events<-resmax(data=events,ID="ID",station="Station.Name",
#' res.start="ResidenceStart",residences="ResidenceLength.days",
#' stnchange=station.change,progress.bar=FALSE)
#' stnchange=station.change,verbose=FALSE)
#' head(longest_res_events)
resmax<-function(data,ID,station,res.start,
residences,stnchange,drift=FALSE,progress.bar=TRUE){
residences,stnchange,drift=FALSE,verbose=TRUE){
res.max<-data[0,]

if (progress.bar==TRUE){
if (verbose==TRUE){
pb<-txtProgressBar(1,nrow(stnchange),style=3)
}
for (i in 1:nrow(stnchange)){
Expand All @@ -261,7 +261,7 @@ resmax<-function(data,ID,station,res.start,
}
}
}
if (progress.bar==TRUE){
if (verbose==TRUE){
setTxtProgressBar(pb,i)
}
}
Expand Down Expand Up @@ -293,7 +293,7 @@ resmax<-function(data,ID,station,res.start,
#' @param units units of the duration of the residence events in `data`.
#' @param stnchange a dataframe with the start time and location of the most
#' recent station or location change. Must use the same column names as `data`.
#' @param progress.bar option to display progress bar as function is run. Default
#' @param verbose option to display progress bar as function is run. Default
#' is TRUE.
#'
#' @return a dataframe with the cumulative residence information for each
Expand All @@ -305,17 +305,17 @@ resmax<-function(data,ID,station,res.start,
#' @examples
#' # Identify most recent station change
#' station.change<-stationchange(data=events[events$ID=="A",],type="mort",
#' ID="ID",station="Station.Name",progress.bar=FALSE)
#' ID="ID",station="Station.Name",verbose=FALSE)
#'
#' cumulative_events<-resmaxcml(data=events[events$ID=="A",],ID="ID",
#' station="Station.Name",res.start="ResidenceStart",res.end="ResidenceEnd",
#' residences="ResidenceLength.days",units="days",
#' stnchange=station.change,progress.bar=FALSE)
#' stnchange=station.change,verbose=FALSE)
resmaxcml<-function(data,ID,station,res.start,res.end,
residences,units,stnchange,progress.bar=TRUE){
residences,units,stnchange,verbose=TRUE){
res.maxcml<-data[0,]

if (progress.bar==TRUE){
if (verbose==TRUE){
pb<-txtProgressBar(1,nrow(stnchange),style=3)
}
for (i in 1:nrow(stnchange)){
Expand Down Expand Up @@ -402,7 +402,7 @@ resmaxcml<-function(data,ID,station,res.start,res.end,
else {break}
}
}
if (progress.bar==TRUE){
if (verbose==TRUE){
setTxtProgressBar(pb,i)
}
}
Expand Down
12 changes: 8 additions & 4 deletions README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,13 @@ mort uses thresholds from the dataset itself, use-defined thresholds, and severa

### Installation

You can install mort from [GitHub](https://github.com/) with the line below. Note that you must have the package `devtools` installed.
You can install mort from CRAN with the line below.

``` r
install.packages("mort")
```

To install mort directly from GitHub, including any updates that might not be released on CRAN yet, use the line below. Note that you must have the package `devtools` installed.

``` r
devtools::install_github("rosieluain/mort")
Expand All @@ -41,8 +47,6 @@ Please see the package vignettes for more details, as well as guidelines and tip

`mortsplot` generates plots of residence events using `ggplot2`. Plots are automatically formatted to maximize visibility of the dataset, and can be further modified using `ggplot2` commands. Interactive plots can also be generated using `plotly`.

<!-- ### Should make an example plot from example dataset when ready -->

#### Identifying potential mortalities or expelled tags

`morts` identifies potential mortalities or expelled tags, based on the duration of single residence events or cumulative residence events (see vignettes for a complete explanation). Thresholds are derived from the input dataset.
Expand All @@ -67,5 +71,5 @@ These are functions that may be called by `morts` and/or `infrequent`, depending
`backwards` shifts the start time of a flagged mortality earlier, if the residence event that triggered the flag was not the earliest consecutive residence event at that station/location.

### Disclaimer
mort is brand new. Although it is has been tested extensively on a complex dataset, we expect that issues will arise as mort is applied to other datasets and systems. If you run into any issues or have any suggestions for improvements, please post an issue, and we'll see what we can do!
mort is brand new. Although it is has been tested extensively on a complex dataset, we expect that issues will arise as mort is applied to other datasets and systems. If you run into any issues or have any suggestions for improvements, please post an issue on [GitHub](https://github.com/rosieluain/mort/issues), and we'll see what we can do!

Loading

0 comments on commit a5dc9d4

Please sign in to comment.