[R] Time Series ts() Objects

Adrian Trapletti adrian.trapletti at lmttrading.com
Fri Feb 15 13:10:24 CET 2002


> Date: Mon, 11 Feb 2002 15:08:55 +1300 (NZDT)
> From: Ko-Kang Kevin Wang <kwan022 at stat.auckland.ac.nz>
> Subject: [R] Time Series ts() Objects
>
> Hi,
>
> Is it possible to create a ts() object, whose data is daily based BUT
> measured only on working days?
>
> In other words, suppose I have a data set with 255 observations, measured
> from 29 June 1959 to 30 June 1960.  How would I create such a data?  I
> tried something like:
>    ts(c(...), start(1959, 180))
> but I'm not sure what to use for frequency.  In other words I don't know
> how to "ignore" Saturdays and Sundays.
>
> Many thanks in advance,
>
> Ko-Kang Wang
>
> - ------------------------------------------------------------------------------
> Ko-Kang Kevin Wang
> Postgraduate PGDipSci Student (Summer Research Assistant)
> Department of Statistics
> University of Auckland
> New Zealand

I have a PRELIMINARY package for very basic operations with irregular time series. Maybe this is useful for you. It´s attached. Since it´s
undocumentated I prepared a small example:

source("irts.R")
x <- read.irts("data")
x

times<- seq.irts(x$times[1],x$times[32],60*5)
times

interpolate.irts(x, times, method="constant")

best
Adrian



-------------- next part --------------
irts <- function(times, data)
{
  if (!is.vector(times))
    stop("times is not a vector of times")
  if (length(times) != NROW(data))
    stop("times and data have not the same number of rows")
  class(times) <- c("POSIXt", "POSIXct")
  irts <- list(times = times, data = data)
  class(irts) <- "irts"
  return(irts)
}

data.irts <- function(x)
{
  return(x$data)
}

times.irts <- function(x)
{
  return(x$times)
}

print.irts <- function(x, format = "%Y-%m-%d %H:%M:%S", tz = "GMT", usetz = TRUE)
{
  n <- length(x$times)
  for (i in 1:n)
  {
    cat(format(x$times[i], format=format, tz = tz, usetz = usetz))
    cat(" ")
    if (is.vector(x$data))
      cat(as.character(x$data[i]))
    else
      cat(as.character(x$data[i,]))
    cat("\n")
  }
}

read.irts <- function(file, format = "%Y-%m-%d %H:%M:%S", tz = "GMT", ...)
{
  x <- read.table(file, as.is = TRUE, ...)
  times <- as.numeric(as.POSIXct(strptime(paste(x[,1], x[,2]), format = format), tz = tz))
  data <- x[,-(1:2)] 
  irts(times, data)
}

is.businessday.irts <- function(x, tz = "GMT")
{
  wday <- as.POSIXlt(x$times, tz = tz)$wday
  return ((0 < wday) & (wday < 6))
}

is.weekend.irts <- function(x, tz = "GMT")
{
  wday <- as.POSIXlt(tt$times, tz = tz)$wday
  return ((0 == wday) | (wday == 6))
}

"[.irts" <- function(x, i)
{
  if (is.vector(x$data))
    return (irts(as.numeric(x$times)[i], x$data[i]))
  else
    return (irts(as.numeric(x$times)[i], x$data[i,]))
}

seq.irts <- function(from, to, by)
{
  from <- as.numeric(from)
  to <- as.numeric(to)
  times <- seq(from, to, by=by)
  class(times) <- c("POSIXt", "POSIXct")
  return(times)
}

interpolate.irts <- function(x, times, ...)
{
  xdata <- as.matrix(x$data)
  xtimes <- as.numeric(x$times)
  times <- as.numeric(times)
  data <- matrix(0, NROW(times), NCOL(xdata))
  for (i in 1:NCOL(xdata))
  {
    result <- approx(xtimes, xdata[,i,drop=T], times, ...)
    data[,i] <- result$y
  }
  irts(times, data[,,drop=T])
}
-------------- next part --------------
 1996-06-02 20:23:30 1.5230 1.5232 
 1996-06-02 20:24:56 1.5230 1.5232 
 1996-06-02 20:26:02 1.5230 1.5235 
 1996-06-02 20:26:18 1.5233 1.5235 
 1996-06-02 20:26:56 1.5232 1.5237 
 1996-06-02 20:28:16 1.5233 1.5235 
 1996-06-02 20:28:22 1.5235 1.5240 
 1996-06-02 20:29:26 1.5230 1.5240 
 1996-06-02 20:30:58 1.5232 1.5242 
 1996-06-02 20:34:54 1.5235 1.5240 
 1996-06-02 20:35:14 1.5236 1.5240 
 1996-06-02 20:36:30 1.5238 1.5243 
 1996-06-02 20:36:34 1.5238 1.5240 
 1996-06-02 20:37:38 1.5240 1.5244 
 1996-06-02 20:38:52 1.5236 1.5241 
 1996-06-02 20:39:00 1.5237 1.5241 
 1996-06-02 20:40:12 1.5237 1.5241 
 1996-06-02 20:40:26 1.5238 1.5241 
 1996-06-02 20:41:44 1.5238 1.5241 
 1996-06-02 20:41:46 1.5238 1.5241 
 1996-06-02 20:42:24 1.5235 1.5245 
 1996-06-02 20:43:54 1.5237 1.5240 
 1996-06-02 20:45:32 1.5237 1.5240 
 1996-06-02 20:46:36 1.5237 1.5240 
 1996-06-02 20:46:38 1.5237 1.5240 
 1996-06-02 20:47:06 1.5233 1.5243 
 1996-06-02 20:47:44 1.5237 1.5240 
 1996-06-02 20:49:06 1.5237 1.5240 
 1996-06-02 20:50:10 1.5237 1.5240 
 1996-06-02 20:51:18 1.5237 1.5240 
 1996-06-02 20:52:20 1.5232 1.5239 
 1996-06-02 20:53:04 1.5232 1.5242 


More information about the R-help mailing list