R/periodogram.R

Defines functions periodogram

Documented in periodogram

## Do not edit this file manually.
## It has been automatically generated from *.org sources.

#' @title Obtain the most important period lags of a time series according to 
#'     a periodogram.
#' 
#' @details 
#' Using the \code{spectral} function, obtain spectral density estimates at a 
#'     number of frequencies and rather than plotting, obtain the rank and 
#'     period of the values. Return a given number of results based on the level
#'     of interest of the user. 
#' 
#' @param x A vector containing the time series values
#' @param ... Arguments to be passed to \code{spectrum}
#' @param no.results The number of results to be printed at the end. Defaults to 
#'    the 20 most important frequencies.
#' 
#' @return A data.frame containing the following columns:
#'     \item{rank}{numeric vector containing the ranked importance of the 
#'         frequency.}
#'     \item{spectrum}{estimates of the spectral density at frequencies 
#'         corresponding to \code{freq}.}
#'     \item{frequency}{vector at which the spectral density is estimated.}
#'     \item{period}{vector of corresponding periods.}
#'
#' @export 
periodogram <- function(x, ..., no.results = 20){
    ## the detail of the results
    if(no.results <= 0 | no.results %% 1 > 0)
        stop("'no.results' must be a positive integer")
    
    ## obtain periodogram results without plotting
    obj <- spectrum(x, ...)
    
    ## how many frequencies?
    m <- length(obj$spec)
    
    ## create a data frame containing results
         # 2022-01-19 - dropping dplyr
         #
         # res <- data.frame(rank  = seq_len(m),
         #                   order = order(obj$spec, decreasing = TRUE))
         # 
         # res <- dplyr::mutate(res,
         #                      spectrum  = obj$spec[order],
         #                      frequency = obj$freq[order],
         #                      period    = round(1/frequency))
         # res <- dplyr::select(res, -order)
    ord <- order(obj$spec, decreasing = TRUE)
    res <- data.frame(rank  = seq_len(m),
		      spectrum  = obj$spec[ord],
		      frequency = obj$freq[ord])
    res$period <- round(1 / res$frequency)
    ## @georgi: above I have rounded period - is this a good idea?
    
    ## Remove duplicate periods
    ## @georgi: Is this a good idea?
    res <- res[!duplicated(res$period), ]
    
    ## print number of required results
    res[seq_len(no.results), ]
}

Try the sarima package in your browser

Any scripts or data that you put into this service are public.

sarima documentation built on Aug. 11, 2022, 5:11 p.m.