Fixed bug in add_case
This commit is contained in:
		
							parent
							
								
									f98eb36484
								
							
						
					
					
						commit
						17edadf597
					
				
							
								
								
									
										12
									
								
								R/add_case.R
									
									
									
									
									
								
							
							
						
						
									
										12
									
								
								R/add_case.R
									
									
									
									
									
								
							@ -5,13 +5,13 @@
 | 
				
			|||||||
add_case <- function(data, cutoff = 20) {
 | 
					add_case <- function(data, cutoff = 20) {
 | 
				
			||||||
# TODO: What is the best choice for the cutoff here?
 | 
					# TODO: What is the best choice for the cutoff here?
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  data$timediff   <- as.numeric(diff(c(data$date.start, utils::tail(data$date.start, 1))))
 | 
					  data$timediff  <- -c(utils::head(data$date.stop, nrow(data) - 1) - data$date.start[-1], 0)
 | 
				
			||||||
  data$timeindex  <- ifelse(data$timediff <= cutoff, 0, 1)
 | 
					  data$timeindex <- ifelse(data$timediff <= cutoff, 0, 1)
 | 
				
			||||||
  case_change     <- diff(c(0, c(which(data$timeindex == 1), nrow(data))))
 | 
					  case_change    <- diff(c(0, c(which(data$timeindex == 1), nrow(data))))
 | 
				
			||||||
  data$case       <- rep(seq_along(case_change), case_change)
 | 
					  data$case      <- rep(seq_along(case_change), case_change)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  data$timediff   <- NULL
 | 
					  data$timediff  <- NULL
 | 
				
			||||||
  data$timeindex  <- NULL
 | 
					  data$timeindex <- NULL
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  data
 | 
					  data
 | 
				
			||||||
}
 | 
					}
 | 
				
			||||||
 | 
				
			|||||||
@ -14,12 +14,13 @@
 | 
				
			|||||||
#' @param glossar Logical indicating if glossar folder is present and if it
 | 
					#' @param glossar Logical indicating if glossar folder is present and if it
 | 
				
			||||||
#' should be taken into account when preprocessing raw log files. Default
 | 
					#' should be taken into account when preprocessing raw log files. Default
 | 
				
			||||||
#' is FALSE.
 | 
					#' is FALSE.
 | 
				
			||||||
 | 
					#' @param save Temporary argument to save intermediate data frames for debugging.
 | 
				
			||||||
#' @return Data frame.
 | 
					#' @return Data frame.
 | 
				
			||||||
#' @export
 | 
					#' @export
 | 
				
			||||||
#' @examples
 | 
					#' @examples
 | 
				
			||||||
#' # tbd
 | 
					#' # tbd
 | 
				
			||||||
create_eventlogs <- function(data, xmlpath = NULL, case_cutoff = 20,
 | 
					create_eventlogs <- function(data, xmlpath = NULL, case_cutoff = 20,
 | 
				
			||||||
                             rm_nochange_moves = TRUE, glossar = FALSE) {
 | 
					                             rm_nochange_moves = TRUE, glossar = FALSE, save = FALSE) {
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  if (!lubridate::is.POSIXt(data$date)){
 | 
					  if (!lubridate::is.POSIXt(data$date)){
 | 
				
			||||||
    cat("########## Converting variable `date` to POSIXct ##########", "\n")
 | 
					    cat("########## Converting variable `date` to POSIXct ##########", "\n")
 | 
				
			||||||
@ -128,6 +129,8 @@ create_eventlogs <- function(data, xmlpath = NULL, case_cutoff = 20,
 | 
				
			|||||||
    dat7$glossar <- NULL
 | 
					    dat7$glossar <- NULL
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  if (save) save(dat, dat1, dat2, dat3, dat4, dat5, dat6, dat7, file = "../data/tmp_intermediate-df.RData")
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  dat7
 | 
					  dat7
 | 
				
			||||||
}
 | 
					}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -9,7 +9,8 @@ create_eventlogs(
 | 
				
			|||||||
  xmlpath = NULL,
 | 
					  xmlpath = NULL,
 | 
				
			||||||
  case_cutoff = 20,
 | 
					  case_cutoff = 20,
 | 
				
			||||||
  rm_nochange_moves = TRUE,
 | 
					  rm_nochange_moves = TRUE,
 | 
				
			||||||
  glossar = FALSE
 | 
					  glossar = FALSE,
 | 
				
			||||||
 | 
					  save = FALSE
 | 
				
			||||||
)
 | 
					)
 | 
				
			||||||
}
 | 
					}
 | 
				
			||||||
\arguments{
 | 
					\arguments{
 | 
				
			||||||
@ -28,6 +29,8 @@ removed. Default is TRUE.}
 | 
				
			|||||||
\item{glossar}{Logical indicating if glossar folder is present and if it
 | 
					\item{glossar}{Logical indicating if glossar folder is present and if it
 | 
				
			||||||
should be taken into account when preprocessing raw log files. Default
 | 
					should be taken into account when preprocessing raw log files. Default
 | 
				
			||||||
is FALSE.}
 | 
					is FALSE.}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					\item{save}{Temporary argument to save intermediate data frames for debugging.}
 | 
				
			||||||
}
 | 
					}
 | 
				
			||||||
\value{
 | 
					\value{
 | 
				
			||||||
Data frame.
 | 
					Data frame.
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user