From noreply at r-forge.r-project.org Wed Apr 3 14:03:56 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 3 Apr 2013 14:03:56 +0200 (CEST) Subject: [Eventstudies-commits] r47 - in pkg: . R man tests Message-ID: <20130403120357.014911847DF@r-forge.r-project.org> Author: vikram Date: 2013-04-03 14:03:56 +0200 (Wed, 03 Apr 2013) New Revision: 47 Added: pkg/tests/inr_inference.R Removed: pkg/WISHLIST pkg/man/sp500.Rd pkg/tests/subbarao.R Modified: pkg/DESCRIPTION pkg/R/inference.Ecar.R pkg/man/identifyextremeevents.Rd pkg/man/inference.Ecar.Rd pkg/man/inr.Rd pkg/man/phys2eventtime.Rd pkg/tests/test_eventstudy.R Log: Modified documentation files; removed WISHLIST, Changelog; Added a to.plot functionality in inference.Ecar; Data: Added eventstudy data-set and removed sp500.rda Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/DESCRIPTION 2013-04-03 12:03:56 UTC (rev 47) @@ -2,11 +2,11 @@ Type: Package Title: Event study and extreme event analysis Version: 0.04 -Date: 2011-06-20 +Date: 2013-04-02 Author: Ajay Shah, Vimal Balasubramaniam, Vikram Bahure -Maintainer: Vimal Balasubramaniam , Vikram Bahure +Maintainer: Vikram Bahure Depends: R (>= 2.12.0), zoo, xts, boot Description: Implementation of short and long term event study methodology License: GPL-2 LazyLoad: yes -Packaged: 2013-02-14 10:33:06 UTC; t136 +Packaged: 2013-04-02 10:33:06 UTC; t136 Modified: pkg/R/inference.Ecar.R =================================================================== --- pkg/R/inference.Ecar.R 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/R/inference.Ecar.R 2013-04-03 12:03:56 UTC (rev 47) @@ -30,11 +30,25 @@ list(est=b$t0, lo=ci$bca[1,4], hi=ci$bca[1,5]) } +# Plotting inference +plotInference <- function(inference){ + big <- max(abs(inference)) + hilo <- c(-big,big) + width <- (nrow(inference)-1)/2 + plot(-width:width, inference[,"Mean"], type="l", lwd=2, ylim=hilo, col="blue", + xlab="Event time", ylab="Cumulative returns of response series", + main=paste("Eventstudy plot")) + points(-width:width, inference[,"Mean"]) + lines(-width:width, inference[,"2.5%"], lwd=1, lty=2, col="blue") + lines(-width:width, inference[,"97.5%"], lwd=1, lty=2, col="blue") + abline(h=0,v=0) +} + # z.e is a zoo object with certain rows (e.g. from -10 to 10) # that define the event window, and columns with data for units. # This function does bootstrap inference for the entire # Ecar, i.e. main graph of the event study. -inference.Ecar <- function(z.e) { +inference.Ecar <- function(z.e,to.plot=FALSE) { Ecar <- function(transposed, d) { colMeans(transposed[d,], na.rm=TRUE) } @@ -48,5 +62,8 @@ results <- cbind(results[,1], b$t0, results[,2]) rownames(results) <- rownames(z.e) colnames(results) <- c("2.5%","Mean","97.5%") - results + if(to.plot=TRUE){ + plotInference(inference=results) + } + return(results) } Deleted: pkg/WISHLIST =================================================================== --- pkg/WISHLIST 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/WISHLIST 2013-04-03 12:03:56 UTC (rev 47) @@ -1,11 +0,0 @@ -Some of the modifications we hope to make shortly: - -1. Introduce asymmetry in the width option in phys2eventtime -2. Add parametric tests to the system. -3. -4. -5. -6. -7. - - Modified: pkg/man/identifyextremeevents.Rd =================================================================== --- pkg/man/identifyextremeevents.Rd 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/man/identifyextremeevents.Rd 2013-04-03 12:03:56 UTC (rev 47) @@ -34,7 +34,7 @@ } \examples{ -data(sp500) -input <- diff(log(sp500)) +data(eventstudyData) +input <- eventstudyData$sp500 output <- identifyextremeevents(input, prob.value=5) } Modified: pkg/man/inference.Ecar.Rd =================================================================== --- pkg/man/inference.Ecar.Rd 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/man/inference.Ecar.Rd 2013-04-03 12:03:56 UTC (rev 47) @@ -10,11 +10,12 @@ } \usage{ -inference.Ecar(z.e) +inference.Ecar(z.e,to.plot=FALSE) } \arguments{ \item{z.e}{z.e is the first component of the list returned by the function phys2eventtime.} + \item{to.plot}{This argument will generate an eventstudy plot of the inference estimated. If to.plot is equal to TRUE then function would generate the plot else it would not. } } \value{ @@ -26,22 +27,8 @@ } \examples{ -## The function is currently defined as -function (z.e) -{ - Ecar <- function(transposed, d) { - colMeans(transposed[d, ], na.rm = TRUE) - } - tmp <- t(as.matrix(z.e)) - b <- boot(tmp, Ecar, R = 1000) - results <- NULL - for (i in 1:ncol(b$t)) { - results <- rbind(results, quantile(b$t[, i], prob = c(0.025, - 0.975))) - } - results <- cbind(results[, 1], b$t0, results[, 2]) - rownames(results) <- rownames(z.e) - colnames(results) <- c("2.5\%", "Mean", "97.5\%") - results - } +data(eventDays) +data(eventstudyData) +eventtime <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +inference.Ecar(z.e=eventtime, to.plot=FALSE) } \ No newline at end of file Modified: pkg/man/inr.Rd =================================================================== --- pkg/man/inr.Rd 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/man/inr.Rd 2013-04-03 12:03:56 UTC (rev 47) @@ -2,17 +2,16 @@ \alias{inr} \docType{data} \title{ -INR/USD +Exchange rate for Indian rupee: INR/USD } \description{ A sample of INR/USD rates from 1990 to 2011. It is stored as an xts object. } \usage{data(inr)} -\format{ It is an xts object containing daily data from 1990 to 2011. The format is: chr "inr.rda" +\format{ It is an xts object containing daily data from 1990 to 2011. The format is: chr 'inr.rda' } \examples{ data(inr) -str(inr) ## maybe str(inr.rda) ; plot(inr.rda) ... } \keyword{datasets} Modified: pkg/man/phys2eventtime.Rd =================================================================== --- pkg/man/phys2eventtime.Rd 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/man/phys2eventtime.Rd 2013-04-03 12:03:56 UTC (rev 47) @@ -28,61 +28,9 @@ \author{Ajay Shah, Vimal Balasubramaniam} \examples{ -##---- Should be DIRECTLY executable !! ---- -##-- ==> Define data, use random, -##-- or do help(data=index) for the standard data sets. - -## The function is currently defined as -function (z, events, width = 10) -{ - events$unit <- as.character(events$unit) - timeshift <- function(x, when) { - location <- findInterval(when, index(x)) - if ((location <= 1) | (location >= length(x))) { - return(list(result = NULL, outcome = "wrongspan")) - } - remapped <- zoo(as.numeric(x), order.by = (-location + - 1):(length(x) - location)) - list(result = remapped, outcome = "success") - } - outcomes <- character(nrow(events)) - z.e <- zoo(1, order.by = as.integer(1)) - for (eventnum in 1:nrow(events)) { - if (!(events$unit[eventnum] \%in\% colnames(z))) { - outcomes[eventnum] <- "unitmissing" - next - } - attempt <- timeshift(z[, events$unit[eventnum]], events$when[eventnum]) - if (attempt$outcome == "success") { - z.e <- cbind(z.e, attempt$result) - } - outcomes[eventnum] <- attempt$outcome - } - outcomes <- outcomes - z.e <- z.e[, -1] - colnames(z.e) <- which(outcomes == "success") - badcolumns <- NULL - if (width > 0) { - for (i in 1:ncol(z.e)) { - tmp <- z.e[, i] - tmp <- na.locf(tmp, na.rm = FALSE, maxgap = 4) - tmp <- na.locf(tmp, na.rm = FALSE, maxgap = 4, fromLast = TRUE) - tmp2 <- window(tmp, start = -width, end = +width) - if (any(is.na(tmp2))) { - outcomes[as.numeric(colnames(z.e)[i])] <- "wdatamissing" - badcolumns <- c(badcolumns, i) - } - else { - z.e[, i] <- tmp - } - } - if (any(outcomes == "wdatamissing")) { - z.e <- z.e[, -badcolumns] - } - } - stopifnot(sum(outcomes == "success") == NCOL(z.e)) - list(z.e = z.e, outcomes = factor(outcomes)) - } +data(eventDays) +data(eventstudyData) +phys2eventtime(z=eventstudyData, events=eventDays,width=5) } \keyword{ phys2eventime } Deleted: pkg/man/sp500.Rd =================================================================== --- pkg/man/sp500.Rd 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/man/sp500.Rd 2013-04-03 12:03:56 UTC (rev 47) @@ -1,20 +0,0 @@ -\name{sp500} - -\docType{data} - -\alias{sp500} - -\title{Times series data} - -\description{ - It is time series data for S&P 500 from 2000-02-10 to 2011-07-29. -} - -\usage{data(sp500)} - -\format{An object with class attributes \code{xts} and \code{zoo} containing a variable with 2036 observations.} - -\examples{ - data(sp500) -} -\keyword{datasets} Copied: pkg/tests/inr_inference.R (from rev 45, pkg/tests/subbarao.R) =================================================================== --- pkg/tests/inr_inference.R (rev 0) +++ pkg/tests/inr_inference.R 2013-04-03 12:03:56 UTC (rev 47) @@ -0,0 +1,18 @@ +library(eventstudies) + +data(inr) +inr_returns<-diff(log(inr))[-1] +eventslist<-data.frame(unit=rep("inr",10), + when=as.Date(c( + "2010-04-20","2010-07-02","2010-07-27", + "2010-09-16","2010-11-02","2011-01-25", + "2011-03-17","2011-05-03","2011-06-16", + "2011-07-26"))) +event_time_data<-phys2eventtime(inr_returns,eventslist,width=10) +w<-window(event_time_data$z.e,start=-10,end=10) + +all.equal(inference.Ecar(w)[,2],c(-.000015327,-.002526819,.0011990000,.001193535,.001846734, + -.000105473,-.001659772,.001644518,-0.001325236,.001546369, + -.000809734,-.001499191,-.000289414,-.000003273,-.000416662, + -.001150000,-.000759748,.002306711,-.000487299,.001122457, + .000635890)) Deleted: pkg/tests/subbarao.R =================================================================== --- pkg/tests/subbarao.R 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/tests/subbarao.R 2013-04-03 12:03:56 UTC (rev 47) @@ -1,18 +0,0 @@ -library(eventstudies) - -data(inr) -inr_returns<-diff(log(inr))[-1] -eventslist<-data.frame(unit=rep("inr",10), - when=as.Date(c( - "2010-04-20","2010-07-02","2010-07-27", - "2010-09-16","2010-11-02","2011-01-25", - "2011-03-17","2011-05-03","2011-06-16", - "2011-07-26"))) -event_time_data<-phys2eventtime(inr_returns,eventslist,width=10) -w<-window(event_time_data$z.e,start=-10,end=10) - -all.equal(inference.Ecar(w)[,2],c(-.000015327,-.002526819,.0011990000,.001193535,.001846734, - -.000105473,-.001659772,.001644518,-0.001325236,.001546369, - -.000809734,-.001499191,-.000289414,-.000003273,-.000416662, - -.001150000,-.000759748,.002306711,-.000487299,.001122457, - .000635890)) Modified: pkg/tests/test_eventstudy.R =================================================================== --- pkg/tests/test_eventstudy.R 2013-03-14 12:11:15 UTC (rev 46) +++ pkg/tests/test_eventstudy.R 2013-04-03 12:03:56 UTC (rev 47) @@ -18,12 +18,6 @@ "2004-01-02", "2004-01-08", "2004-01-14", "2005-01-15", "2004-01-01", "2005-01-01"))) eventslist$unit <- as.character(eventslist$unit) -# 1 It's fine, but prior to event date there's only 1 reading -# 2 It's fine -# 3 It's fine, but after event date there's only 1 reading -# 4 Unit is fine, date is off -# 5 Unit is fine, date is off -# 6 Unit does not exist # What we expect if we don't worry about width -- rawres <- structure(list(z.e = structure(c(NA, NA, NA, NA, NA, NA, From noreply at r-forge.r-project.org Wed Apr 3 20:59:19 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 3 Apr 2013 20:59:19 +0200 (CEST) Subject: [Eventstudies-commits] r48 - in pkg: . R data man vignettes Message-ID: <20130403185919.8B17B1849A1@r-forge.r-project.org> Author: vikram Date: 2013-04-03 20:59:19 +0200 (Wed, 03 Apr 2013) New Revision: 48 Removed: pkg/data/sp500.rda Modified: pkg/DESCRIPTION pkg/R/inference.Ecar.R pkg/man/inference.Ecar.Rd pkg/vignettes/eventstudies.Rnw Log: Corrected errors for previous commit Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2013-04-03 12:03:56 UTC (rev 47) +++ pkg/DESCRIPTION 2013-04-03 18:59:19 UTC (rev 48) @@ -1,7 +1,7 @@ Package: eventstudies Type: Package Title: Event study and extreme event analysis -Version: 0.04 +Version: 0.05 Date: 2013-04-02 Author: Ajay Shah, Vimal Balasubramaniam, Vikram Bahure Maintainer: Vikram Bahure Modified: pkg/R/inference.Ecar.R =================================================================== --- pkg/R/inference.Ecar.R 2013-04-03 12:03:56 UTC (rev 47) +++ pkg/R/inference.Ecar.R 2013-04-03 18:59:19 UTC (rev 48) @@ -62,7 +62,7 @@ results <- cbind(results[,1], b$t0, results[,2]) rownames(results) <- rownames(z.e) colnames(results) <- c("2.5%","Mean","97.5%") - if(to.plot=TRUE){ + if(to.plot==TRUE){ plotInference(inference=results) } return(results) Deleted: pkg/data/sp500.rda =================================================================== (Binary files differ) Modified: pkg/man/inference.Ecar.Rd =================================================================== --- pkg/man/inference.Ecar.Rd 2013-04-03 12:03:56 UTC (rev 47) +++ pkg/man/inference.Ecar.Rd 2013-04-03 18:59:19 UTC (rev 48) @@ -29,6 +29,8 @@ \examples{ data(eventDays) data(eventstudyData) -eventtime <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +es.w <- window(es.results$z.e, start=-5, end=+5) +eventtime <- remap.cumsum(es.w, is.pc=FALSE, base=0) inference.Ecar(z.e=eventtime, to.plot=FALSE) } \ No newline at end of file Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-03 12:03:56 UTC (rev 47) +++ pkg/vignettes/eventstudies.Rnw 2013-04-03 18:59:19 UTC (rev 48) @@ -174,8 +174,8 @@ 5\% tail on both sides. \end{enumerate} <<>>== -data(sp500) -input <- diff(log(sp500))*100 +data(eventstudyData) +input <- eventstudyData$sp500*100 output <- identifyextremeevents(input, prob.value=5) @ From noreply at r-forge.r-project.org Thu Apr 4 08:49:50 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 4 Apr 2013 08:49:50 +0200 (CEST) Subject: [Eventstudies-commits] r49 - pkg/man Message-ID: <20130404064950.C05FD183BBD@r-forge.r-project.org> Author: vikram Date: 2013-04-04 08:49:50 +0200 (Thu, 04 Apr 2013) New Revision: 49 Added: pkg/man/eventDays.Rd pkg/man/eventstudyData.Rd Modified: pkg/man/eventstudy-package.Rd pkg/man/inference.change.boot.Rd pkg/man/phys2eventtime.Rd pkg/man/remap.cumprod.Rd pkg/man/remap.cumsum.Rd pkg/man/remap.event.reindex.Rd Log: Added examples in documentation to remap; Added eventDays and eventstudyData documentation; some minor modifications Added: pkg/man/eventDays.Rd =================================================================== --- pkg/man/eventDays.Rd (rev 0) +++ pkg/man/eventDays.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -0,0 +1,20 @@ +\name{eventDays} + +\docType{data} + +\alias{eventDays} + +\title{List of event dates for S&P 500} + +\description{ + This series is an input for the examples in the eventstudy framework. It is a data frame with two columns 'unit' and 'when'. The column 'when' has event dates for S&P 500 while column 'unit' has list of response series' column names. In this data frame, 'unit' is 'nifty' which corresponds with column name of the 'eventstudyData'. Here, 1% tail values are termed as extreme events days, in this example we take upper tail events. +} + +\usage{data(eventDays)} + +\format{An object with class attributes \code{data.frame} containing event dates for eventstudy.} + +\examples{ + data(eventDays) +} +\keyword{datasets} Modified: pkg/man/eventstudy-package.Rd =================================================================== --- pkg/man/eventstudy-package.Rd 2013-04-03 18:59:19 UTC (rev 48) +++ pkg/man/eventstudy-package.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -15,7 +15,7 @@ Package: \tab eventstudy\cr Type: \tab Package\cr Version: \tab 1.0\cr -Date: \tab 2011-01-04\cr +Date: \tab 2013-04-04\cr License: \tab GPL 2\cr LazyLoad: \tab yes\cr } @@ -26,9 +26,9 @@ } \author{ -Ajay Shah,Vimal Balasubramniam, Vikram Bahure +Ajay Shah, Vimal Balasubramniam, Vikram Bahure -Maintainer: vimsaa at gmail.com +Maintainer: economics.vikram at gmail.com } \keyword{ eventstudies } Added: pkg/man/eventstudyData.Rd =================================================================== --- pkg/man/eventstudyData.Rd (rev 0) +++ pkg/man/eventstudyData.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -0,0 +1,24 @@ +\name{eventstudyData} + +\docType{data} + +\alias{eventstudyData} + +\title{It is the data-set used for event-study analysis.} + +\description{ +It is a time series object with daily series for S&P 500, Nifty and Net FII flows in India. +} + +\usage{data(eventstudyData)} + +\format{An object with class attributes \code{zoo} containing resposne series for eventstudy.} + +\seealso{ +eventDays +} + +\examples{ + data(eventstudyData) +} +\keyword{datasets} Modified: pkg/man/inference.change.boot.Rd =================================================================== --- pkg/man/inference.change.boot.Rd 2013-04-03 18:59:19 UTC (rev 48) +++ pkg/man/inference.change.boot.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -31,22 +31,9 @@ \value{It returns a list containing the mean,and the confidence intervals for the change in Ecar.} \examples{ -## The function is currently defined as -function (z.e, t1, t2, operator = "ratio", conf = 0.95) -{ - stopifnot(operator \%in\% c("ratio", "difference")) - tmp <- t(as.matrix(z.e[, c(t1, t2)])) - if (operator == "ratio") { - change <- tmp[, 2]/tmp[, 1] - } - if (operator == "difference") { - change <- tmp[, 2] - tmp[, 1] - } - mymean <- function(x, d) { - mean(x[d], na.rm = TRUE) - } - b <- boot(change, mymean, R = 1000) - ci <- boot.ci(b, type = "bca", conf = conf) - list(est = b$t0, lo = ci$bca[1, 4], hi = ci$bca[1, 5]) - } +data(eventDays) +data(eventstudyData) +es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +es.w <- window(es.results$z.e, start=-5, end=+5) +eventtime <- remap.cumsum(es.w, is.pc=FALSE, base=0) } Modified: pkg/man/phys2eventtime.Rd =================================================================== --- pkg/man/phys2eventtime.Rd 2013-04-03 18:59:19 UTC (rev 48) +++ pkg/man/phys2eventtime.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -25,7 +25,6 @@ \value{Returns a list containing 1. A zoo object indexed with event time, and having "enough data points" and 2. a vector which describes the status of each unit in the original data ( this maybe more than the no of units in 1 ).} -\author{Ajay Shah, Vimal Balasubramaniam} \examples{ data(eventDays) Modified: pkg/man/remap.cumprod.Rd =================================================================== --- pkg/man/remap.cumprod.Rd 2013-04-03 18:59:19 UTC (rev 48) +++ pkg/man/remap.cumprod.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -19,22 +19,16 @@ \value{The frame returned has each column replaced by base * the cumulative product of the column.} +\seealso{ +eventDays, eventstudyData, phys2eventtime +} \examples{ -## The function is currently defined as -function (z, is.pc = TRUE, is.returns = TRUE, base = 100) -{ - for (i in 1:ncol(z)) { - tmp <- z[, i] - if (is.returns) { - if (is.pc) { - tmp <- tmp/100 - } - tmp <- 1 + tmp - } - tmp[1] <- base - z[, i] <- cumprod(tmp) - } - } +data(eventDays) +data(eventstudyData) +es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +es.w <- window(es.results$z.e, start=-5, end=+5) +eventtime <- remap.cumprod(es.w, is.pc=FALSE, is.returns=TRUE, base=0) +eventtime } Modified: pkg/man/remap.cumsum.Rd =================================================================== --- pkg/man/remap.cumsum.Rd 2013-04-03 18:59:19 UTC (rev 48) +++ pkg/man/remap.cumsum.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -24,24 +24,13 @@ The frame returned has each column replaced by the cumulative sum of the column. } \seealso{ -phys2eventtime +eventDays, eventstudyData, phys2eventtime } \examples{ -##---- Should be DIRECTLY executable !! ---- -##-- ==> Define data, use random, -##-- or do help(data=index) for the standard data sets. - -## The function is currently defined as -function (z, is.pc = TRUE, base = 0) -{ - for (i in 1:ncol(z)) { - tmp <- z[, i] - if (is.pc) { - tmp <- tmp/100 - } - z[, i] <- base + cumsum(tmp) - } - z - } +data(eventDays) +data(eventstudyData) +es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +es.w <- window(es.results$z.e, start=-5, end=+5) +eventtime <- remap.cumsum(es.w, is.pc=FALSE, base=0) } Modified: pkg/man/remap.event.reindex.Rd =================================================================== --- pkg/man/remap.event.reindex.Rd 2013-04-03 18:59:19 UTC (rev 48) +++ pkg/man/remap.event.reindex.Rd 2013-04-04 06:49:50 UTC (rev 49) @@ -16,18 +16,13 @@ \value{The function returns a zoo object which has been rescaled.} -\seealso{phys2eventtime} - - +\seealso{ +eventDays, eventstudyData, phys2eventtime +} \examples{ -## The function is currently defined as -function (z) -{ - eventvals <- as.numeric(window(z, start = 0, end = 0)) - for (i in 1:ncol(z)) { - z[, i] <- 100 * z[, i]/eventvals[i] - } - z - } +data(eventDays) +data(eventstudyData) +es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +es.w <- window(es.results$z.e, start=-5, end=+5) +eventtime <- remap.event.reindex(es.w) } - From noreply at r-forge.r-project.org Thu Apr 4 08:52:56 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 4 Apr 2013 08:52:56 +0200 (CEST) Subject: [Eventstudies-commits] r50 - in pkg: R data man Message-ID: <20130404065256.1E459181366@r-forge.r-project.org> Author: vikram Date: 2013-04-04 08:52:55 +0200 (Thu, 04 Apr 2013) New Revision: 50 Added: pkg/data/eventDays.rda pkg/data/eventstudyData.rda Removed: pkg/man/inference.change.boot.Rd Modified: pkg/R/remap.cumprod.R Log: Corrected remap.cumprod function by adding 'return(z)'; added eventDays and eventstudyData rda files; removed inference.change.boot documentation as it is not a user required function Modified: pkg/R/remap.cumprod.R =================================================================== --- pkg/R/remap.cumprod.R 2013-04-04 06:49:50 UTC (rev 49) +++ pkg/R/remap.cumprod.R 2013-04-04 06:52:55 UTC (rev 50) @@ -17,4 +17,5 @@ tmp[1] <- base z[,i] <- cumprod(tmp) } + z } Added: pkg/data/eventDays.rda =================================================================== (Binary files differ) Property changes on: pkg/data/eventDays.rda ___________________________________________________________________ Added: svn:mime-type + application/octet-stream Added: pkg/data/eventstudyData.rda =================================================================== (Binary files differ) Property changes on: pkg/data/eventstudyData.rda ___________________________________________________________________ Added: svn:mime-type + application/octet-stream Deleted: pkg/man/inference.change.boot.Rd =================================================================== --- pkg/man/inference.change.boot.Rd 2013-04-04 06:49:50 UTC (rev 49) +++ pkg/man/inference.change.boot.Rd 2013-04-04 06:52:55 UTC (rev 50) @@ -1,39 +0,0 @@ -\name{inference.change.boot} -\alias{inference.change.boot} -\title{ -This does bootstrap inference for the difference in the -average "car" between t1 and t2 (both in event time). -} - -\description{ -z.e is a zoo object, where rows are in event time -and columns are units of observation. Sampling with replacement is done within the units of observation. Each time, the Ecar(t1) and Ecar(t2) is computed. - -By default, the statistic of interest is the ratio -Ecar(t2)/Ecar(t1) -But if operator="difference" is sent in, then the -statistic of interest shifts to Ecar(t2)-Ecar(t1). -} - -\usage{ -inference.change.boot(z.e, t1, t2, operator = "ratio", conf = 0.95) -} - -\arguments{ - \item{z.e}{z is the zoo object returned from phys2eventtime.} - \item{t1}{Start of the event period.} - \item{t2}{End of the event period.} - \item{operator}{One of ratio or difference to compute the ratio or difference -for the change in Ecar.} - \item{conf}{The level of confidence for computing the confidence intervals.} -} - -\value{It returns a list containing the mean,and the confidence intervals for the change in Ecar.} - -\examples{ -data(eventDays) -data(eventstudyData) -es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) -es.w <- window(es.results$z.e, start=-5, end=+5) -eventtime <- remap.cumsum(es.w, is.pc=FALSE, base=0) -} From noreply at r-forge.r-project.org Thu Apr 4 09:10:57 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 4 Apr 2013 09:10:57 +0200 (CEST) Subject: [Eventstudies-commits] r51 - pkg/man Message-ID: <20130404071057.E2FB6183BBD@r-forge.r-project.org> Author: vikram Date: 2013-04-04 09:10:57 +0200 (Thu, 04 Apr 2013) New Revision: 51 Modified: pkg/man/eventDays.Rd pkg/man/inr.Rd pkg/man/remap.cumprod.Rd Log: Minor modifications in documentation Modified: pkg/man/eventDays.Rd =================================================================== --- pkg/man/eventDays.Rd 2013-04-04 06:52:55 UTC (rev 50) +++ pkg/man/eventDays.Rd 2013-04-04 07:10:57 UTC (rev 51) @@ -7,7 +7,7 @@ \title{List of event dates for S&P 500} \description{ - This series is an input for the examples in the eventstudy framework. It is a data frame with two columns 'unit' and 'when'. The column 'when' has event dates for S&P 500 while column 'unit' has list of response series' column names. In this data frame, 'unit' is 'nifty' which corresponds with column name of the 'eventstudyData'. Here, 1% tail values are termed as extreme events days, in this example we take upper tail events. + This series is an input for the examples in the eventstudy framework. It is a data frame with two columns 'unit' and 'when'. The column 'when' has event dates for S&P 500 while column 'unit' has list of response series' column names. In this data frame, 'unit' is 'nifty' which corresponds with column name of the 'eventstudyData'. Here, 1\% tail values are termed as extreme events days, in this example we take upper tail events. } \usage{data(eventDays)} Modified: pkg/man/inr.Rd =================================================================== --- pkg/man/inr.Rd 2013-04-04 06:52:55 UTC (rev 50) +++ pkg/man/inr.Rd 2013-04-04 07:10:57 UTC (rev 51) @@ -12,6 +12,5 @@ } \examples{ data(inr) -## maybe str(inr.rda) ; plot(inr.rda) ... } \keyword{datasets} Modified: pkg/man/remap.cumprod.Rd =================================================================== --- pkg/man/remap.cumprod.Rd 2013-04-04 06:52:55 UTC (rev 50) +++ pkg/man/remap.cumprod.Rd 2013-04-04 07:10:57 UTC (rev 51) @@ -29,6 +29,5 @@ es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) es.w <- window(es.results$z.e, start=-5, end=+5) eventtime <- remap.cumprod(es.w, is.pc=FALSE, is.returns=TRUE, base=0) -eventtime } From noreply at r-forge.r-project.org Sat Apr 6 00:59:24 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 6 Apr 2013 00:59:24 +0200 (CEST) Subject: [Eventstudies-commits] r52 - in pkg: R vignettes Message-ID: <20130405225924.6D7741847CD@r-forge.r-project.org> Author: vikram Date: 2013-04-06 00:59:24 +0200 (Sat, 06 Apr 2013) New Revision: 52 Modified: pkg/R/identifyextremeevents.R pkg/vignettes/eventstudies.Rnw Log: Wrote vignette and updated with new funcitonality Modified: pkg/R/identifyextremeevents.R =================================================================== --- pkg/R/identifyextremeevents.R 2013-04-04 07:10:57 UTC (rev 51) +++ pkg/R/identifyextremeevents.R 2013-04-05 22:59:24 UTC (rev 52) @@ -223,7 +223,7 @@ probvalue=5, event.value="returns", response.value="returns"){ - # Getting levels in event format + # Getting levels in event format tmp <- gen.data(event.series, probvalue=probvalue, value=event.value) Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-04 07:10:57 UTC (rev 51) +++ pkg/vignettes/eventstudies.Rnw 2013-04-05 22:59:24 UTC (rev 52) @@ -5,135 +5,221 @@ \usepackage{natbib} \usepackage{float} \usepackage{tikz} +\usepackage{amsmath} \title{Introduction to the \textbf{eventstudies} package in R} -\author{} +\author{Ajay Shah, Vimal Balasubramaniam and Vikram Bahure} \begin{document} %\VignetteIndexEntry{eventstudies: A package with functionality to do Event Studies} %\VignetteDepends{} %\VignetteKeywords{event studies} %\VignettePackage{eventstudies} +\maketitle +\begin{abstract} +The structure of the package and its implementation of event study +methodology is explained in this paper. In addition to converting +physical dates to event time frame, functions for re-indexing the +event time returns, bootstrap inference estimation and identification +of extreme clustered events and futher in-depth analysis of the +same is also provided. The methods and functions are elucidated by +employing data-set for S\&P 500, Nifty and net Foreign Insitutional +Investors (FII) flow in India. +\end{abstract} -\maketitle -\newpage \SweaveOpts{engine=R,pdf=TRUE} \section{Introduction} -This is an introduction to eventstudies, a package in R which has functionality to convert a given dataset into -an event-time frame and to undertake further parametric/non-parametric analysis using various inference procedures. +Event study has a long history which dates back to 1933 (James Dolley +(1933)). It is mostly used to study the response of stock price or +value of a firm due to event such as mergers \& aquisitions, stock +splits, quarterly results and so on. It is one of the most widely +used statistical tool. -This paper describes how this package is used and provides several examples illustrating the use of -the functionality within this package. +Event study is a statistical method used to study the response or +the effect on a variable, due to similar events. Efficient and liquid +markets are basic assumption in this methodolgy. It assumes the +effect on response variable is without delay. As event study output is +further used in econometric analysis, hence significance test such as +\textit{t-test}, \textit{J-test}, \textit{Patell-test} which are +parametric and \textit{GRANK}, \textit{RANK} which are non-parametric +can also be performed. -\section{phys2eventtime} -phys2eventtime is a function which takes a zoo object containing input data, a data frame containing -the date of occurance of the events and creates a data frame which is indexed according to the event -time. +In this package, we have three major functions +\textit{phys2eventtime}, \textit{remap.cumsum} and +\textit{inference.Ecar}. \textit{phys2eventtime} function changes the +physical dates to event time frame on which event study analysis can +be done with ease. \textit{remap.cumsum} and similar other functions +can be use to convert returns to cumulative sum or product in the +event time frame. \textit{inference.Ecar} generates bootstrap +inference for the event time response of the variable. -The following illustrates the use of phys2eventtime. +\section{Converting physical dates to event time} +\subsection{Conceptual framework} +The foremost task of event study analysis is to define event dates and +generate an event window. Once the user defines event dates then this +function generates event time frame for the response series. For +example, if we are studying response of Nifty returns due to event on +S\&P 500 then this function will map together all the event day +responses cross sectionally at day 0, the days after the event would +be indexed as positive and days before the event woud be indexed as +negative. The output of this function can be further trimmed to +smaller window such as of +10 to -10 days. + + +\subsection{Usage} +\textit{phys2eventtime} has three arguments which are as follows: +\begin{enumerate} +\item \textit{z}: Time series data for which event frame is to be + generated. In this example, we have zoo object with data for S\&P + 500 returns, Nifty returns and net Foregin Institutional Invetors + (FII) flow. + +\item \textit{events}: It is a data frame with two columns: + \textit{unit} and \textit{when}. \textit{unit} has column name of + which response is to measured on the event date, while \textit{when} + has the event date.\textit{unit} has to in character format + +\item \textit{width}: For a given width, if there is any \textit{NA} in the event window + then the last observation is carried forward. +\end{enumerate} <<>>= -options(useFancyQuotes=FALSE) library(eventstudies) -input.zoo.object <- structure(c(33.16, 34.0967, 35.3683, 34.46, 34.17, 35.89, 36.19, - 37.1317, 36.7033, 37.7933, 37.8533, 285.325, 292.6, - 290.025, 286.2, 290.075, 295.05, 289.325, 285.625, - 293.7, 298.5, 289.05, 704.5438, 708.35, 735.8375, - 710.625, 711.65, 731.0125, 727.575, 715.0187, 724.2, - 713.1875, 695.1812), .Dim = c(11L, 3L), .Dimnames = - list( NULL, c("ITC", "Reliance", "Infosys")), index = - structure(c(12418, 12419, 12422, 12423, 12424, 12425, - 12426, 12429, 12430, 12431, 12432), class = "Date"), - class = "zoo") -input.zoo.object -eventslist <- data.frame(unit=c("ITC","Reliance","Infosys", - "ITC","Reliance","Junk"), - when=as.Date(c( - "2004-01-02", "2004-01-08", "2004-01-14", - "2005-01-15", "2004-01-01", "2005-01-01"))) - -eventslist$unit <- as.character(eventslist$unit) -eventslist +data(eventstudyData) +str(eventstudyData) +head(eventstudyData) +data(eventDays) +str(eventDays) +head(eventDays) @ -In this example we note the following about input.zoo.object and the data frame eventslist:- -\begin{enumerate} -\item Prior to event date(in eventslist\$when) there is only 1 reading in the corresponding unit in input.zoo.object. -\item The event date is within the range of available dates for the corresponding unit(this is the ideal case). -\item After the event date there's only 1 reading. -\item The date is not within the range. -\item There is no data prior to this date. -\item Unit does not exist in input.zoo.object. -\end{enumerate} -This is exactly what the second component of phys2eventtime namely outcomes,reports. The first component of the result of phys2eventtime -is a zoo object which is the event time data frame. -<<>>== -a <- phys2eventtime(input.zoo.object, eventslist,width=0) -str(a) -a$z.e -a$outcomes +\subsection{Output} +Output for \textit{phys2eventtime} is in a list format. The first +element of list is a time series object which is converted to event +time and the second element is \textit{outcomes} which shows if there +was any \textit{NA} in the dataset. If the outcome is \textit{success} +then all is well in the given window as specified by the +width else it gives \textit{wdatamissing} if too many NAs within the crucial event +window or \textit{wrongspan} If the event date is not placed within +the span of data for the unit or \textit{unitmissing} if a unit named +in events is not in \textit{z}. +<<>>= +es <- phys2eventtime(z=eventstudyData, events=eventDays, width=10) +str(es) +#head(es$z.e) +es$outcomes +@ -@ -phys2eventtime has a third parameter namely width which allows for checking that no more than 4 consecutive missing observations -are there within the given width from the event time. +Output of \textit{phys2eventtime} can be converted to specific frame +by using window command of time series. This event window can be +further used in inference analysis. +<<>>= +es.w <- window(es$z.e, start=-10, end=+10) +es.w[,1:2] +@ -What we expect if we don't use width handling:- -<<>>== -rawres <- structure(list(z.e = structure(c(NA, NA, NA, NA, NA, NA, - NA, NA, 33.16, 34.0967, 35.3683, 34.46, 34.17, 35.89, 36.19, - 37.1317, 36.7033, 37.7933, 37.8533, NA, NA, NA, NA, 285.325, 292.6, - 290.025, 286.2, 290.075, 295.05, 289.325, 285.625, 293.7, 298.5, - 289.05, NA, NA, NA, NA, 704.5438, 708.35, 735.8375, 710.625, 711.65, - 731.0125, 727.575, 715.0187, 724.2, 713.1875, 695.1812, NA, NA, NA, - NA, NA, NA, NA, NA), .Dim = c(19L, 3L), .Dimnames = list( NULL, - c("1", "2", "3")), index = -9:9, class = "zoo"), outcomes = - structure(c(1L, 1L, 1L, 3L, 3L, 2L), .Label = c("success", - "unitmissing", "wrongspan" ), class = "factor")), .Names = c("z.e", - "outcomes")) -rawres -@ -Check without the width handling -- -<<>>== -a <- phys2eventtime(input.zoo.object, eventslist,width=0) -a -all.equal(a, rawres) -@ -Check with width of 1 -- -<<>>== -a <- phys2eventtime(input.zoo.object, eventslist,width=1) -a -all.equal(a, rawres) -@ -But when we go to width=2, column 1 and 3 drop off because they have -only 1 obs before and after the event date respectively. +\section{Remapping} +\subsection{Conceptual framework} +Many a times, there is more information in cumulative +returns rather than just returns. Re-indexing event window helps to +represent returns in cumulative sum or cumulative product +format. -<<>>== -a <- phys2eventtime(input.zoo.object, eventslist,width=2) -a -all.equal(a, structure(list(z.e = structure(c(NA, NA, NA, NA, 285.325, - 292.6, 290.025, 286.2, 290.075, 295.05, - 289.325, 285.625, 293.7, 298.5, 289.05, - NA, NA, NA, NA), index = -9:9, class = - "zoo"), outcomes = structure(c(3L, 1L, - 3L, 4L, 4L, 2L), .Label = c("success", - "unitmissing", "wdatamissing", - "wrongspan"), class = "factor")), .Names - = c("z.e", "outcomes" ))) +\subsection{Usage} +There are three functions used to re-map data which are as follows: +\begin{itemize} +\item \textit{remap.cumsum}: This function is used to convert event + window returns to cumulative sum of returns. Arguments for the + function are as follows: + \begin{enumerate} + \item \textit{z}: This is the output of \textit{phys2eventtime} + which is further reduced to an event window of \textit{width} + equals 10 or 20. + \item \textit{is.pc}: If returns is in percentage form then + \textit{is.pc} is equal to \textit{TRUE} else \textit{FALSE} + \item \textit{base}: Using this command, the base for the + cumulative returns can be changed. It has default value as 0. + \end{enumerate} +\end{itemize} +<<>>= +es.w.cs <- remap.cumsum(z= es.w, is.pc=FALSE) +es.w.cs[,1:2] +@ +\begin{itemize} +\item \textit{remap.cumprod}: This function is used to convert event + window returns to cumulative product of returns. Arguments for the + function are as follows: + \begin{enumerate} + \item \textit{z}: This is the output of \textit{phys2eventtime} + which is further reduced to an event window of \textit{width} + equals 10 or 20. + \item \textit{is.pc}: If returns is in percentage form then + \textit{is.pc} is equal to \textit{TRUE} else \textit{FALSE} + \item \textit{is.returns}: If the data is in returns format then + \textit{is.returns} is \textit{TRUE}. + \item \textit{base}: Using this command, the base for the + cumulative returns can be changed. It has default value as 100. + \end{enumerate} +\end{itemize} + +<<>>= +es.w.cp <- remap.cumprod(z= es.w, is.pc=FALSE, is.returns=TRUE, base=100) +es.w.cp[,1:2] +@ + +\begin{itemize} +\item \textit{remap.event.reindex}: This function is used to convert event + window data to returns format. Argument for the + function is as follows: + \begin{enumerate} + \item \textit{z}: This is the output of \textit{phys2eventtime} + which is further reduced to an event window of \textit{width} + equals 10 or 20. + \end{enumerate} +\end{itemize} +<<>>= +es.w.ri <- remap.event.reindex(z= es.w) +es.w.ri[,1:2] +@ + +%\newpage +\section{Evenstudy Inference using Bootstrap} +\subsection{Conceptual framework} +Suppose there are N events. Each event is expressed as a time-series +of cumulative returns (CR) in event time, within the event window. The +overall summary statistic of interest is the $\bar{CR}$, the average of all the +CR time-series. +We do sampling with replacement at the level of the events. Each +bootstrap sample is constructed by sampling with replacement, N times, +within the dataset of N events. For each event, its corresponding CR +time-series is taken. This yields a time-series, which is one draw +from the distribution of the statistic. +This procedure is repeated 1000 times in order to obtain the full +distribution of $\bar{CR}$ . Percentiles of the distribution are shown +in the graphs reported later, giving bootstrap confidence intervals +for our estimates. This specific approach used here is based on +Davinson, Hinkley and Schectman (1986). + +\subsection{Usage} +This function has two arguments: +\begin{enumerate} +\item \textit{z.e}: This is the re-mapped output of \textit{phys2eventtime} +\item \textit{to.plot}: If the user wants inference output plot then + \textit{to.plot} is equals \textit{TRUE} +\end{enumerate} +<<>>= +result <- inference.Ecar(z.e=es.w.cs, to.plot=FALSE) +head(result) +@ +\begin{figure}[h] + \begin{center} + \caption{Event on S\&P 500 and response of Nifty} + \setkeys{Gin}{width=0.8\linewidth} + \setkeys{Gin}{height=0.8\linewidth} +<>= +<> + result <- inference.Ecar(z.e=es.w.cs, to.plot=TRUE) @ -\section{inference.Ecar} -Once we have an event time frame returned by phys2eventtime we may use inference.Ecar to do -bootstrap inference for the main graph of the event study. This is illustrated in the following example. -<<>>== -library(xts) -load(paste(system.file(package="eventstudies"),"data","inr.rda",sep="/")) -inr.returns<-diff(log(inr))[-1] -eventslist<-data.frame(unit=rep("inr",10), - when=as.Date(c( - "2010-04-20","2010-07-02","2010-07-27", - "2010-09-16","2010-11-02","2011-01-25", - "2011-03-17","2011-05-03","2011-06-16", - "2011-07-26"))) -event.time.data<-phys2eventtime(inr.returns,eventslist,width=10) -w<-window(event.time.data$z.e,start=-10,end=10) -inference.Ecar(w) -@ +\end{center} +\label{fig:one} +\end{figure} \section{identifyextremeevents} % Conceptual framework @@ -175,7 +261,7 @@ \end{enumerate} <<>>== data(eventstudyData) -input <- eventstudyData$sp500*100 +input <- eventstudyData$sp500 output <- identifyextremeevents(input, prob.value=5) @ From noreply at r-forge.r-project.org Mon Apr 8 12:08:20 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 8 Apr 2013 12:08:20 +0200 (CEST) Subject: [Eventstudies-commits] r53 - in pkg: data vignettes Message-ID: <20130408100820.797BF18427A@r-forge.r-project.org> Author: vikram Date: 2013-04-08 12:08:20 +0200 (Mon, 08 Apr 2013) New Revision: 53 Modified: pkg/data/eventDays.rda pkg/vignettes/eventstudies.Rnw Log: Made changes in the vignette Modified: pkg/data/eventDays.rda =================================================================== (Binary files differ) Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-05 22:59:24 UTC (rev 52) +++ pkg/vignettes/eventstudies.Rnw 2013-04-08 10:08:20 UTC (rev 53) @@ -1,3 +1,4 @@ + \documentclass[a4paper,11pt]{article} \usepackage{graphicx} \usepackage{a4wide} @@ -5,6 +6,7 @@ \usepackage{natbib} \usepackage{float} \usepackage{tikz} +\usepackage{parskip} \usepackage{amsmath} \title{Introduction to the \textbf{eventstudies} package in R} \author{Ajay Shah, Vimal Balasubramaniam and Vikram Bahure} @@ -18,10 +20,10 @@ The structure of the package and its implementation of event study methodology is explained in this paper. In addition to converting physical dates to event time frame, functions for re-indexing the -event time returns, bootstrap inference estimation and identification -of extreme clustered events and futher in-depth analysis of the +event time returns, bootstrap inference estimation, and identification +of extreme clustered events and further in-depth analysis of the same is also provided. The methods and functions are elucidated by -employing data-set for S\&P 500, Nifty and net Foreign Insitutional +employing data-set for S\&P 500, Nifty and net Foreign Institutional Investors (FII) flow in India. \end{abstract} @@ -29,13 +31,13 @@ \section{Introduction} Event study has a long history which dates back to 1933 (James Dolley (1933)). It is mostly used to study the response of stock price or -value of a firm due to event such as mergers \& aquisitions, stock +value of a firm due to events such as mergers \& acquisitions, stock splits, quarterly results and so on. It is one of the most widely used statistical tool. -Event study is a statistical method used to study the response or +Event study is used to study the response or the effect on a variable, due to similar events. Efficient and liquid -markets are basic assumption in this methodolgy. It assumes the +markets are basic assumption in this methodology. It assumes the effect on response variable is without delay. As event study output is further used in econometric analysis, hence significance test such as \textit{t-test}, \textit{J-test}, \textit{Patell-test} which are @@ -46,8 +48,8 @@ \textit{phys2eventtime}, \textit{remap.cumsum} and \textit{inference.Ecar}. \textit{phys2eventtime} function changes the physical dates to event time frame on which event study analysis can -be done with ease. \textit{remap.cumsum} and similar other functions -can be use to convert returns to cumulative sum or product in the +be done with ease. \textit{remap.cumsum} +can be used to convert returns to cumulative sum or product in the event time frame. \textit{inference.Ecar} generates bootstrap inference for the event time response of the variable. @@ -59,7 +61,7 @@ example, if we are studying response of Nifty returns due to event on S\&P 500 then this function will map together all the event day responses cross sectionally at day 0, the days after the event would -be indexed as positive and days before the event woud be indexed as +be indexed as positive and days before the event would be indexed as negative. The output of this function can be further trimmed to smaller window such as of +10 to -10 days. @@ -69,13 +71,13 @@ \begin{enumerate} \item \textit{z}: Time series data for which event frame is to be generated. In this example, we have zoo object with data for S\&P - 500 returns, Nifty returns and net Foregin Institutional Invetors + 500 returns, Nifty returns and net foreign institutional investors (FII) flow. \item \textit{events}: It is a data frame with two columns: \textit{unit} and \textit{when}. \textit{unit} has column name of which response is to measured on the event date, while \textit{when} - has the event date.\textit{unit} has to in character format + has the event date. \item \textit{width}: For a given width, if there is any \textit{NA} in the event window then the last observation is carried forward. @@ -89,21 +91,20 @@ str(eventDays) head(eventDays) @ - +% some problem in the output after you are printing the structure. \subsection{Output} Output for \textit{phys2eventtime} is in a list format. The first -element of list is a time series object which is converted to event +element of the list is a time series object which is converted to event time and the second element is \textit{outcomes} which shows if there was any \textit{NA} in the dataset. If the outcome is \textit{success} then all is well in the given window as specified by the -width else it gives \textit{wdatamissing} if too many NAs within the crucial event -window or \textit{wrongspan} If the event date is not placed within +width. It gives \textit{wdatamissing} if there are too many \textit{NAs} within the crucial event +window or \textit{wrongspan} if the event date is not placed within the span of data for the unit or \textit{unitmissing} if a unit named in events is not in \textit{z}. <<>>= es <- phys2eventtime(z=eventstudyData, events=eventDays, width=10) str(es) -#head(es$z.e) es$outcomes @ @@ -131,11 +132,11 @@ \begin{enumerate} \item \textit{z}: This is the output of \textit{phys2eventtime} which is further reduced to an event window of \textit{width} - equals 10 or 20. + equal to 10 or 20. \item \textit{is.pc}: If returns is in percentage form then \textit{is.pc} is equal to \textit{TRUE} else \textit{FALSE} \item \textit{base}: Using this command, the base for the - cumulative returns can be changed. It has default value as 0. + cumulative returns can be changed. The default value is 0. \end{enumerate} \end{itemize} <<>>= @@ -149,13 +150,13 @@ \begin{enumerate} \item \textit{z}: This is the output of \textit{phys2eventtime} which is further reduced to an event window of \textit{width} - equals 10 or 20. + equal to 10 or 20. \item \textit{is.pc}: If returns is in percentage form then - \textit{is.pc} is equal to \textit{TRUE} else \textit{FALSE} + \textit{is.pc} is equal to \textit{TRUE}, else \textit{FALSE} \item \textit{is.returns}: If the data is in returns format then \textit{is.returns} is \textit{TRUE}. \item \textit{base}: Using this command, the base for the - cumulative returns can be changed. It has default value as 100. + cumulative returns can be changed. The default value is 100. \end{enumerate} \end{itemize} @@ -165,9 +166,9 @@ @ \begin{itemize} -\item \textit{remap.event.reindex}: This function is used to convert event - window data to returns format. Argument for the - function is as follows: +\item \textit{remap.event.reindex}: This function is used to change + the base of event day to 100 and change the pre-event and post-event values + respectively. Argument for the function is as follows: \begin{enumerate} \item \textit{z}: This is the output of \textit{phys2eventtime} which is further reduced to an event window of \textit{width} @@ -178,24 +179,25 @@ es.w.ri <- remap.event.reindex(z= es.w) es.w.ri[,1:2] @ - -%\newpage \section{Evenstudy Inference using Bootstrap} \subsection{Conceptual framework} -Suppose there are N events. Each event is expressed as a time-series -of cumulative returns (CR) in event time, within the event window. The +Suppose there are $N$ events. Each event is expressed as a time-series +of cumulative returns $(CR)$ in event time, within the event window. The overall summary statistic of interest is the $\bar{CR}$, the average of all the -CR time-series. +$CR$ time-series. We do sampling with replacement at the level of the events. Each -bootstrap sample is constructed by sampling with replacement, N times, -within the dataset of N events. For each event, its corresponding CR +bootstrap sample is constructed by sampling with replacement, $N$ times, +within the dataset of $N$ events. For each event, its corresponding $CR$ time-series is taken. This yields a time-series, which is one draw from the distribution of the statistic. This procedure is repeated 1000 times in order to obtain the full distribution of $\bar{CR}$ . Percentiles of the distribution are shown in the graphs reported later, giving bootstrap confidence intervals -for our estimates. This specific approach used here is based on -Davinson, Hinkley and Schectman (1986). +for our estimates. +This specific approach used here is based on Davinson, Hinkley and +Schectman (1986). The \textit{inference.Ecar} function does the +bootstrap to generate distribution of $\bar{CR}$. The bootstrap +generates confidence interval at 2.5\% and 97.5\% for the estimate. \subsection{Usage} This function has two arguments: @@ -208,7 +210,7 @@ result <- inference.Ecar(z.e=es.w.cs, to.plot=FALSE) head(result) @ -\begin{figure}[h] +\begin{figure}[ht] \begin{center} \caption{Event on S\&P 500 and response of Nifty} \setkeys{Gin}{width=0.8\linewidth} @@ -221,8 +223,7 @@ \label{fig:one} \end{figure} -\section{identifyextremeevents} -% Conceptual framework +\section{Identify extreme events} \subsection{Conceptual framework} This function of the package identifies extreme event and does data analysis. The upper tail and lower tail values are defined as extreme @@ -264,7 +265,7 @@ input <- eventstudyData$sp500 output <- identifyextremeevents(input, prob.value=5) @ - +% I don't understand this output. Maybe you should explain what it means. \subsection{Output} Output is in list format. Primarily it consists of three lists, summary statistics for complete data-set, extreme event analysis for @@ -273,7 +274,7 @@ following output: \begin{enumerate} \item Extreme events dataset -\item Distribution of clustered and unclustered +\item Distribution of clustered and unclustered % events. \item Run length distribution \item Quantile values of extreme events \item Yearly distribution of extreme events @@ -292,16 +293,16 @@ @ \subsubsection{Extreme events dataset} The output for upper tail and lower tail are in the same format as -mentioned above. The data-set is an time series object which has 2 +mentioned above. The data-set is a time series object which has 2 columns. The first column is \textit{event.series} column which has returns for extreme events and the second column is \textit{cluster.pattern} which signifies the number of consecutive -days in the cluster. So, here we just show results for lower tail. +days in the cluster. Here we show results for the lower tail. <<>>= -output$lower.tail$data +str(output$lower.tail$data) @ -\subsubsection{Distribution of clustered and clustered events} +\subsubsection{Distribution of clustered and unclustered events} In the analysis we have clustered, unclustered and mixed clusters. We remove the mixed clusters and study the rest of the clusters by fusing them. Here we show, number of clustered and unclustered data used in @@ -333,9 +334,33 @@ @ \subsubsection{Yearly distribution of extreme events} -This table shows the yearly wise distribution and +This table shows the yearly distribution and the median value for extreme events data. <<>>= output$lower.tail$yearly.extreme.event @ +The yearly distribution for extreme events include unclustered event +and clustered events which are fused. While in extreme event distribution of +clustered and unclustered event, the clustered events are defined as +total evnets in a cluster. For example, if there is a clustered event +with three consecutive extreme events then yearly distribution will +treat it as one single event. Here below the relationship between the +Tables is explained through equations:\\\\ +\textit{Sum of yearly distribution for lower tail = 59 \\ +Unclustered events for lower tail = 56\\\\ +Clustered events for lower tail = 3 + 0\\ +Total events in clusters (Adding number of events in each cluster) += 3*2 + 0*3 = 6\\ +Total used events = Unclustered events for lower tail + Total events +in clusters \\ = 56 + 6 = 62 \\\\ +Sum of yearly distribution for lower tail = Unclustered events for +lower tail + Total events in clusters\\ = 56 + 3 =59} +<<>>= +sum(output$lower.tail$yearly.extreme.event[,"number.lowertail"]) +output$lower.tail$extreme.event.distribution[,"unclstr"] +output$lower.tail$runlength +@ + +%\section{Conclusion} + \end{document} From noreply at r-forge.r-project.org Mon Apr 8 13:27:37 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 8 Apr 2013 13:27:37 +0200 (CEST) Subject: [Eventstudies-commits] r54 - in pkg: R vignettes Message-ID: <20130408112737.CF9DB184503@r-forge.r-project.org> Author: vikram Date: 2013-04-08 13:27:37 +0200 (Mon, 08 Apr 2013) New Revision: 54 Modified: pkg/R/identifyextremeevents.R pkg/vignettes/eventstudies.Rnw Log: Minor modifications Modified: pkg/R/identifyextremeevents.R =================================================================== --- pkg/R/identifyextremeevents.R 2013-04-08 10:08:20 UTC (rev 53) +++ pkg/R/identifyextremeevents.R 2013-04-08 11:27:37 UTC (rev 54) @@ -4,7 +4,7 @@ # Identifying extreme events ############################ # libraries required -library(xts) +library(zoo) #---------------------------------------------------------------- # INPUT: # 'input' : Data series for which extreme events are Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-08 10:08:20 UTC (rev 53) +++ pkg/vignettes/eventstudies.Rnw 2013-04-08 11:27:37 UTC (rev 54) @@ -44,7 +44,7 @@ parametric and \textit{GRANK}, \textit{RANK} which are non-parametric can also be performed. -In this package, we have three major functions +In this package, there are three major functions \textit{phys2eventtime}, \textit{remap.cumsum} and \textit{inference.Ecar}. \textit{phys2eventtime} function changes the physical dates to event time frame on which event study analysis can @@ -361,6 +361,12 @@ output$lower.tail$runlength @ -%\section{Conclusion} +\section{Computational details} +The package code is purely written in R. It has dependencies to zoo +(\href{http://cran.r-project.org/web/packages/zoo/index.html}{Zeileis + 2012}) and boot +(\href{http://cran.r-project.org/web/packages/boot/index.html}{Rlpley + 2013}). R itself as well as these packages can be obtained from \href{http://CRAN.R-project.org/}{CRAN}. +%\section{Acknowledgments} \end{document} From noreply at r-forge.r-project.org Mon Apr 8 14:04:38 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 8 Apr 2013 14:04:38 +0200 (CEST) Subject: [Eventstudies-commits] r55 - pkg/vignettes Message-ID: <20130408120438.A20BC18501D@r-forge.r-project.org> Author: vikram Date: 2013-04-08 14:04:38 +0200 (Mon, 08 Apr 2013) New Revision: 55 Modified: pkg/vignettes/eventstudies.Rnw Log: Added eventstudy graph in vignette Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-08 11:27:37 UTC (rev 54) +++ pkg/vignettes/eventstudies.Rnw 2013-04-08 12:04:38 UTC (rev 55) @@ -199,18 +199,7 @@ bootstrap to generate distribution of $\bar{CR}$. The bootstrap generates confidence interval at 2.5\% and 97.5\% for the estimate. -\subsection{Usage} -This function has two arguments: -\begin{enumerate} -\item \textit{z.e}: This is the re-mapped output of \textit{phys2eventtime} -\item \textit{to.plot}: If the user wants inference output plot then - \textit{to.plot} is equals \textit{TRUE} -\end{enumerate} -<<>>= -result <- inference.Ecar(z.e=es.w.cs, to.plot=FALSE) -head(result) -@ -\begin{figure}[ht] +\begin{figure}[t] \begin{center} \caption{Event on S\&P 500 and response of Nifty} \setkeys{Gin}{width=0.8\linewidth} @@ -223,6 +212,19 @@ \label{fig:one} \end{figure} +\subsection{Usage} +This function has two arguments: +\begin{enumerate} +\item \textit{z.e}: This is the re-mapped output of \textit{phys2eventtime} +\item \textit{to.plot}: If the user wants inference output plot then + \textit{to.plot} is equals \textit{TRUE} +\end{enumerate} +<<>>= +result <- inference.Ecar(z.e=es.w.cs, to.plot=FALSE) +head(result) +@ + + \section{Identify extreme events} \subsection{Conceptual framework} This function of the package identifies extreme event and does data From noreply at r-forge.r-project.org Mon Apr 8 20:55:30 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 8 Apr 2013 20:55:30 +0200 (CEST) Subject: [Eventstudies-commits] r56 - pkg/man Message-ID: <20130408185530.9ADD7184D82@r-forge.r-project.org> Author: vikram Date: 2013-04-08 20:55:30 +0200 (Mon, 08 Apr 2013) New Revision: 56 Modified: pkg/man/eventstudy-package.Rd pkg/man/inference.Ecar.Rd pkg/man/phys2eventtime.Rd pkg/man/remap.cumprod.Rd pkg/man/remap.event.reindex.Rd Log: Minor modifications in documentation Modified: pkg/man/eventstudy-package.Rd =================================================================== --- pkg/man/eventstudy-package.Rd 2013-04-08 12:04:38 UTC (rev 55) +++ pkg/man/eventstudy-package.Rd 2013-04-08 18:55:30 UTC (rev 56) @@ -7,7 +7,7 @@ } \description{ -This package is used to undertake event study analyses using R. +This package is used to undertake event study analysis using R. } \details{ Modified: pkg/man/inference.Ecar.Rd =================================================================== --- pkg/man/inference.Ecar.Rd 2013-04-08 12:04:38 UTC (rev 55) +++ pkg/man/inference.Ecar.Rd 2013-04-08 18:55:30 UTC (rev 56) @@ -6,7 +6,7 @@ } \description{ -This function does bootstrap inference for the entire Ecar, i.e. main graph of the event study. +This function does bootstrap inference to generate distribution of average of all the cumulative returns time-series. } \usage{ @@ -19,7 +19,7 @@ } \value{ -A data frame with 3 columns,the lower CI,the mean and the upper CI which are the result of bootstrap inference. +A data frame with 3 columns, the lower confidence interval (CI), the mean and the upper CI which are the result of bootstrap inference. } \seealso{ Modified: pkg/man/phys2eventtime.Rd =================================================================== --- pkg/man/phys2eventtime.Rd 2013-04-08 12:04:38 UTC (rev 55) +++ pkg/man/phys2eventtime.Rd 2013-04-08 18:55:30 UTC (rev 56) @@ -14,16 +14,16 @@ } \arguments{ - \item{z}{z is a zoo object containing input data. E.g. this could be all the prices of a bunch of stocks. The column name is the unit name. -events is a data.frame containing 2 columns. The first column ("unit") is the name of the unit. The second column is the date/time ("when") when the event happened.} + \item{z}{Time series data for which event frame is to be generated.} - \item{events}{A data.frame containing unit name and corresponding event dates.} + \item{events}{It is a data frame with two columns: unit and when. unit has column name of which response is to measured on the event date, while when has the event date.} - \item{width}{Width corresponds to the number of days on each side of the event date.} + \item{width}{Width corresponds to the number of days on each side of the event date.For a given width, if there is any NA in the event window then the last observation is carried forward.} } -\value{Returns a list containing 1. A zoo object indexed with event time, and having "enough data points" and 2. a vector which describes the status of each unit in the original data ( this maybe more than the no of units in 1 ).} +\value{Output is in a list format. A zoo object indexed with event time and a vector which describes the status of each unit in the original data. +} \examples{ Modified: pkg/man/remap.cumprod.Rd =================================================================== --- pkg/man/remap.cumprod.Rd 2013-04-08 12:04:38 UTC (rev 55) +++ pkg/man/remap.cumprod.Rd 2013-04-08 18:55:30 UTC (rev 56) @@ -10,7 +10,7 @@ \arguments{ \item{z}{z is the zoo object returned from phys2eventtime.} - \item{is.pc}{Logical flag if input is a percentage} + \item{is.pc}{Logical flag if input is a percentage.} \item{is.returns}{Logical flag if input is returns.} Modified: pkg/man/remap.event.reindex.Rd =================================================================== --- pkg/man/remap.event.reindex.Rd 2013-04-08 12:04:38 UTC (rev 55) +++ pkg/man/remap.event.reindex.Rd 2013-04-08 18:55:30 UTC (rev 56) @@ -11,7 +11,7 @@ \usage{remap.event.reindex(z)} \arguments{ - \item{z}{ z is a zoo object containing input data from phys2eventtime.} + \item{z}{z is a zoo object containing input data from phys2eventtime.} } \value{The function returns a zoo object which has been rescaled.} From noreply at r-forge.r-project.org Mon Apr 29 13:54:52 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 29 Apr 2013 13:54:52 +0200 (CEST) Subject: [Eventstudies-commits] r57 - pkg/data Message-ID: <20130429115453.3ABF018517E@r-forge.r-project.org> Author: vikram Date: 2013-04-29 13:54:52 +0200 (Mon, 29 Apr 2013) New Revision: 57 Added: pkg/data/SplitDates.rda pkg/data/StockPriceReturns.rda pkg/data/identifyexeventData.rda Removed: pkg/data/eventDays.rda pkg/data/eventstudyData.rda Log: Added stock splits data Added: pkg/data/SplitDates.rda =================================================================== (Binary files differ) Property changes on: pkg/data/SplitDates.rda ___________________________________________________________________ Added: svn:mime-type + application/octet-stream Added: pkg/data/StockPriceReturns.rda =================================================================== (Binary files differ) Property changes on: pkg/data/StockPriceReturns.rda ___________________________________________________________________ Added: svn:mime-type + application/octet-stream Deleted: pkg/data/eventDays.rda =================================================================== (Binary files differ) Deleted: pkg/data/eventstudyData.rda =================================================================== (Binary files differ) Added: pkg/data/identifyexeventData.rda =================================================================== (Binary files differ) Property changes on: pkg/data/identifyexeventData.rda ___________________________________________________________________ Added: svn:mime-type + application/octet-stream From noreply at r-forge.r-project.org Mon Apr 29 13:55:54 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 29 Apr 2013 13:55:54 +0200 (CEST) Subject: [Eventstudies-commits] r58 - in pkg: man vignettes Message-ID: <20130429115554.304D3184B78@r-forge.r-project.org> Author: vikram Date: 2013-04-29 13:55:53 +0200 (Mon, 29 Apr 2013) New Revision: 58 Added: pkg/man/SplitDates.Rd pkg/man/StockPriceReturns.Rd pkg/man/identifyexeventData.Rd pkg/vignettes/identifyextremeevent.Rnw Removed: pkg/man/eventDays.Rd pkg/man/eventstudyData.Rd Modified: pkg/man/identifyextremeevents.Rd pkg/man/inference.Ecar.Rd pkg/man/phys2eventtime.Rd pkg/man/remap.cumprod.Rd pkg/man/remap.cumsum.Rd pkg/man/remap.event.reindex.Rd pkg/vignettes/eventstudies.Rnw Log: Modified vignette with stock split example Added: pkg/man/SplitDates.Rd =================================================================== --- pkg/man/SplitDates.Rd (rev 0) +++ pkg/man/SplitDates.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -0,0 +1,20 @@ +\name{SplitDates} + +\docType{data} + +\alias{SplitDates} + +\title{It is the data-set used for event-study analysis.} + +\description{ +It has stock split event dates for the BSE index firms with two columns 'unit' which has firm names and 'when' which has event date for the firm. +} + +\usage{data(SplitDates)} + +\format{An object with class attributes \code{zoo} containing resposne series for eventstudy and a data frame with stock split event dates.} + +\examples{ + data(SplitDates) +} +\keyword{datasets} Added: pkg/man/StockPriceReturns.Rd =================================================================== --- pkg/man/StockPriceReturns.Rd (rev 0) +++ pkg/man/StockPriceReturns.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -0,0 +1,20 @@ +\name{StockPriceReturns} + +\docType{data} + +\alias{StockPriceReturns} + +\title{It is the data-set used for event-study analysis.} + +\description{ +It has stock price returns for index constituents of Bombay Stock Exchange (BSE). +} + +\usage{data(StockPriceReturns)} + +\format{An object with class attributes \code{zoo} containing resposne series for eventstudy.} + +\examples{ + data(StockPriceReturns) +} +\keyword{datasets} Deleted: pkg/man/eventDays.Rd =================================================================== --- pkg/man/eventDays.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/eventDays.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -1,20 +0,0 @@ -\name{eventDays} - -\docType{data} - -\alias{eventDays} - -\title{List of event dates for S&P 500} - -\description{ - This series is an input for the examples in the eventstudy framework. It is a data frame with two columns 'unit' and 'when'. The column 'when' has event dates for S&P 500 while column 'unit' has list of response series' column names. In this data frame, 'unit' is 'nifty' which corresponds with column name of the 'eventstudyData'. Here, 1\% tail values are termed as extreme events days, in this example we take upper tail events. -} - -\usage{data(eventDays)} - -\format{An object with class attributes \code{data.frame} containing event dates for eventstudy.} - -\examples{ - data(eventDays) -} -\keyword{datasets} Deleted: pkg/man/eventstudyData.Rd =================================================================== --- pkg/man/eventstudyData.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/eventstudyData.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -1,24 +0,0 @@ -\name{eventstudyData} - -\docType{data} - -\alias{eventstudyData} - -\title{It is the data-set used for event-study analysis.} - -\description{ -It is a time series object with daily series for S&P 500, Nifty and Net FII flows in India. -} - -\usage{data(eventstudyData)} - -\format{An object with class attributes \code{zoo} containing resposne series for eventstudy.} - -\seealso{ -eventDays -} - -\examples{ - data(eventstudyData) -} -\keyword{datasets} Added: pkg/man/identifyexeventData.Rd =================================================================== --- pkg/man/identifyexeventData.Rd (rev 0) +++ pkg/man/identifyexeventData.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -0,0 +1,20 @@ +\name{identifyexeventData} + +\docType{data} + +\alias{identifyexeventData} + +\title{It is the data-set used for event-study analysis.} + +\description{ +It is a time series object with daily series for S&P 500 and Nifty (NSE index). +} + +\usage{data(identifyexeventData)} + +\format{An object with class attributes \code{zoo} containing resposne series for eventstudy.} + +\examples{ + data(identifyexeventData) +} +\keyword{datasets} Modified: pkg/man/identifyextremeevents.Rd =================================================================== --- pkg/man/identifyextremeevents.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/identifyextremeevents.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -34,7 +34,8 @@ } \examples{ -data(eventstudyData) -input <- eventstudyData$sp500 +library(eventstudies) +data(identifyexeventData) +input <- identifyexeventData$sp500 output <- identifyextremeevents(input, prob.value=5) } Modified: pkg/man/inference.Ecar.Rd =================================================================== --- pkg/man/inference.Ecar.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/inference.Ecar.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -27,9 +27,9 @@ } \examples{ -data(eventDays) -data(eventstudyData) -es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +data(StockPriceReturns) +data(SplitDates) +es.results <- phys2eventtime(z=StockPriceReturns, events=SplitDates,width=5) es.w <- window(es.results$z.e, start=-5, end=+5) eventtime <- remap.cumsum(es.w, is.pc=FALSE, base=0) inference.Ecar(z.e=eventtime, to.plot=FALSE) Modified: pkg/man/phys2eventtime.Rd =================================================================== --- pkg/man/phys2eventtime.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/phys2eventtime.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -27,9 +27,9 @@ \examples{ -data(eventDays) -data(eventstudyData) -phys2eventtime(z=eventstudyData, events=eventDays,width=5) +data(StockPriceReturns) +data(SplitDates) +phys2eventtime(z=StockPriceReturns, events=SplitDates,width=5) } \keyword{ phys2eventime } Modified: pkg/man/remap.cumprod.Rd =================================================================== --- pkg/man/remap.cumprod.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/remap.cumprod.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -20,13 +20,13 @@ \value{The frame returned has each column replaced by base * the cumulative product of the column.} \seealso{ -eventDays, eventstudyData, phys2eventtime +phys2eventtime } \examples{ -data(eventDays) -data(eventstudyData) -es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +data(StockPriceReturns) +data(SplitDates) +es.results <- phys2eventtime(z=StockPriceReturns, events=SplitDates,width=5) es.w <- window(es.results$z.e, start=-5, end=+5) eventtime <- remap.cumprod(es.w, is.pc=FALSE, is.returns=TRUE, base=0) } Modified: pkg/man/remap.cumsum.Rd =================================================================== --- pkg/man/remap.cumsum.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/remap.cumsum.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -27,9 +27,9 @@ eventDays, eventstudyData, phys2eventtime } \examples{ -data(eventDays) -data(eventstudyData) -es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +data(StockPriceReturns) +data(SplitDates) +es.results <- phys2eventtime(z=StockPriceReturns, events=SplitDates,width=5) es.w <- window(es.results$z.e, start=-5, end=+5) eventtime <- remap.cumsum(es.w, is.pc=FALSE, base=0) } Modified: pkg/man/remap.event.reindex.Rd =================================================================== --- pkg/man/remap.event.reindex.Rd 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/man/remap.event.reindex.Rd 2013-04-29 11:55:53 UTC (rev 58) @@ -17,12 +17,12 @@ \value{The function returns a zoo object which has been rescaled.} \seealso{ -eventDays, eventstudyData, phys2eventtime +phys2eventtime } \examples{ -data(eventDays) -data(eventstudyData) -es.results <- phys2eventtime(z=eventstudyData, events=eventDays,width=5) +data(StockPriceReturns) +data(SplitDates) +es.results <- phys2eventtime(z=StockPriceReturns, events=SplitDates,width=5) es.w <- window(es.results$z.e, start=-5, end=+5) eventtime <- remap.event.reindex(es.w) } Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-29 11:54:52 UTC (rev 57) +++ pkg/vignettes/eventstudies.Rnw 2013-04-29 11:55:53 UTC (rev 58) @@ -23,8 +23,7 @@ event time returns, bootstrap inference estimation, and identification of extreme clustered events and further in-depth analysis of the same is also provided. The methods and functions are elucidated by -employing data-set for S\&P 500, Nifty and net Foreign Institutional -Investors (FII) flow in India. +employing data-set of SENSEX firms. \end{abstract} \SweaveOpts{engine=R,pdf=TRUE} @@ -46,154 +45,94 @@ In this package, there are three major functions \textit{phys2eventtime}, \textit{remap.cumsum} and -\textit{inference.Ecar}. \textit{phys2eventtime} function changes the +\textit{inference.Ecar}. \textit{phys2eventtime} changes the physical dates to event time frame on which event study analysis can be done with ease. \textit{remap.cumsum} can be used to convert returns to cumulative sum or product in the event time frame. \textit{inference.Ecar} generates bootstrap inference for the event time response of the variable. -\section{Converting physical dates to event time} -\subsection{Conceptual framework} -The foremost task of event study analysis is to define event dates and -generate an event window. Once the user defines event dates then this -function generates event time frame for the response series. For -example, if we are studying response of Nifty returns due to event on -S\&P 500 then this function will map together all the event day -responses cross sectionally at day 0, the days after the event would -be indexed as positive and days before the event would be indexed as -negative. The output of this function can be further trimmed to -smaller window such as of +10 to -10 days. +In the section below, we illustrate event study analysis using the +package. We measure the impact of stock splits on the stock price of +the firm for SENSEX index constituents. +\section{Performing Eventstudy analysis} +To measure the impact of stock splits on the stock price of the firm, +we create a dataset of 30 index companies of Bombay Stock Exchange +(BSE). We have a returns of stock price for each firm from 2001 to +2013 and respective stock splits date. Once we have the data then we +use following steps to perform event study analysis using the package. -\subsection{Usage} -\textit{phys2eventtime} has three arguments which are as follows: \begin{enumerate} -\item \textit{z}: Time series data for which event frame is to be - generated. In this example, we have zoo object with data for S\&P - 500 returns, Nifty returns and net foreign institutional investors - (FII) flow. - -\item \textit{events}: It is a data frame with two columns: - \textit{unit} and \textit{when}. \textit{unit} has column name of - which response is to measured on the event date, while \textit{when} - has the event date. - -\item \textit{width}: For a given width, if there is any \textit{NA} in the event window - then the last observation is carried forward. +\item Construction of data set + \begin{itemize} + \item A time series object of stock price returns + \item Event dates object with 2 columns, \textit{unit} and + \textit{when}. + \end{itemize} + \item Converting physical dates to event frame + \item Remapping event frame + \item Estimating bootstrap inference \end{enumerate} + +\subsection{Construction of data set} +% Stock returns and event dates +We have collected data of index constituents of Bombay stock exchange +(BSE) and corresponding stock splits dates. There are 30 +firms in SENSEX and we have stock split dates for each firm from 2000 +onwards. + +A time series \textit{zoo} object is created for stock price returns +for 30 firms. For event dates, a data frame with two columns +\textit{unit} and \textit{when} is formed. \textit{unit} has name of +the response series (firm name as in column name of time series +object) along with event date in \textit{when}. \textit{unit} should +be in \textit{character} format and \textit{when} in \textit{Date} format. + <<>>= library(eventstudies) -data(eventstudyData) -str(eventstudyData) -head(eventstudyData) -data(eventDays) -str(eventDays) -head(eventDays) -@ -% some problem in the output after you are printing the structure. -\subsection{Output} -Output for \textit{phys2eventtime} is in a list format. The first -element of the list is a time series object which is converted to event -time and the second element is \textit{outcomes} which shows if there -was any \textit{NA} in the dataset. If the outcome is \textit{success} -then all is well in the given window as specified by the -width. It gives \textit{wdatamissing} if there are too many \textit{NAs} within the crucial event -window or \textit{wrongspan} if the event date is not placed within -the span of data for the unit or \textit{unitmissing} if a unit named -in events is not in \textit{z}. -<<>>= -es <- phys2eventtime(z=eventstudyData, events=eventDays, width=10) -str(es) -es$outcomes +data(StockPriceReturns) +str(StockPriceReturns) +data(SplitDates) +head(SplitDates) @ -Output of \textit{phys2eventtime} can be converted to specific frame -by using window command of time series. This event window can be -further used in inference analysis. -<<>>= -es.w <- window(es$z.e, start=-10, end=+10) -es.w[,1:2] -@ +\subsection{Converting physical dates to event frame} +After the formation of the dataset, our first step towards event study +analysis is to convert the physical dates to event time +frame. Using the \textit{phys2eventtime} function we convert the +dates in event time frame. -\section{Remapping} -\subsection{Conceptual framework} -Many a times, there is more information in cumulative -returns rather than just returns. Re-indexing event window helps to -represent returns in cumulative sum or cumulative product -format. +Here, we index the stock split date, stock price returns to day 0 and +similarly post event dates are indexed to positive and pre event +dates are indexed as negative. As we can see below the stock split dates +for BHEL, Bharti Airtel and Cipla are indexed to day 0. -\subsection{Usage} -There are three functions used to re-map data which are as follows: -\begin{itemize} -\item \textit{remap.cumsum}: This function is used to convert event - window returns to cumulative sum of returns. Arguments for the - function are as follows: - \begin{enumerate} - \item \textit{z}: This is the output of \textit{phys2eventtime} - which is further reduced to an event window of \textit{width} - equal to 10 or 20. - \item \textit{is.pc}: If returns is in percentage form then - \textit{is.pc} is equal to \textit{TRUE} else \textit{FALSE} - \item \textit{base}: Using this command, the base for the - cumulative returns can be changed. The default value is 0. - \end{enumerate} -\end{itemize} +% outcomes, example + <<>>= -es.w.cs <- remap.cumsum(z= es.w, is.pc=FALSE) -es.w.cs[,1:2] -@ -\begin{itemize} -\item \textit{remap.cumprod}: This function is used to convert event - window returns to cumulative product of returns. Arguments for the - function are as follows: - \begin{enumerate} - \item \textit{z}: This is the output of \textit{phys2eventtime} - which is further reduced to an event window of \textit{width} - equal to 10 or 20. - \item \textit{is.pc}: If returns is in percentage form then - \textit{is.pc} is equal to \textit{TRUE}, else \textit{FALSE} - \item \textit{is.returns}: If the data is in returns format then - \textit{is.returns} is \textit{TRUE}. - \item \textit{base}: Using this command, the base for the - cumulative returns can be changed. The default value is 100. - \end{enumerate} -\end{itemize} - -<<>>= -es.w.cp <- remap.cumprod(z= es.w, is.pc=FALSE, is.returns=TRUE, base=100) -es.w.cp[,1:2] -@ +es <- phys2eventtime(z=StockPriceReturns, events=SplitDates, width=10) +es.w <- window(es$z.e, start=-10, end=10) +SplitDates[1:3,] +es.w[,1:3] +@ -\begin{itemize} -\item \textit{remap.event.reindex}: This function is used to change - the base of event day to 100 and change the pre-event and post-event values - respectively. Argument for the function is as follows: - \begin{enumerate} - \item \textit{z}: This is the output of \textit{phys2eventtime} - which is further reduced to an event window of \textit{width} - equals 10 or 20. - \end{enumerate} -\end{itemize} +\subsection{Remapping event frame} +In event study analysis the variable of interest is cumulative +returns. The \textit{remap.cumsum} function is used to +convert the returns to cumulative returns. <<>>= -es.w.ri <- remap.event.reindex(z= es.w) -es.w.ri[,1:2] -@ -\section{Evenstudy Inference using Bootstrap} -\subsection{Conceptual framework} -Suppose there are $N$ events. Each event is expressed as a time-series -of cumulative returns $(CR)$ in event time, within the event window. The -overall summary statistic of interest is the $\bar{CR}$, the average of all the -$CR$ time-series. -We do sampling with replacement at the level of the events. Each -bootstrap sample is constructed by sampling with replacement, $N$ times, -within the dataset of $N$ events. For each event, its corresponding $CR$ -time-series is taken. This yields a time-series, which is one draw -from the distribution of the statistic. -This procedure is repeated 1000 times in order to obtain the full -distribution of $\bar{CR}$ . Percentiles of the distribution are shown -in the graphs reported later, giving bootstrap confidence intervals -for our estimates. +es.cs <- remap.cumsum(es.w,is.pc=FALSE,base=0) +es.cs[,1:3] +@ + +\subsection{Bootstrap inference} +After converting to event frame and estimating the interest variable, +we need to check the stability of the result and derive other +estimates like standard errors and confidence intervals. For this, +we generate the sampling distribution for the estimate using bootstrap +inference. A detailed explanation of the methodology is presented in +Shah, Patnaik and Singh (2013). This specific approach used here is based on Davinson, Hinkley and Schectman (1986). The \textit{inference.Ecar} function does the bootstrap to generate distribution of $\bar{CR}$. The bootstrap @@ -206,163 +145,13 @@ \setkeys{Gin}{height=0.8\linewidth} <>= <> - result <- inference.Ecar(z.e=es.w.cs, to.plot=TRUE) + result <- inference.Ecar(z.e=es.cs, to.plot=TRUE) @ \end{center} \label{fig:one} \end{figure} -\subsection{Usage} -This function has two arguments: -\begin{enumerate} -\item \textit{z.e}: This is the re-mapped output of \textit{phys2eventtime} -\item \textit{to.plot}: If the user wants inference output plot then - \textit{to.plot} is equals \textit{TRUE} -\end{enumerate} -<<>>= -result <- inference.Ecar(z.e=es.w.cs, to.plot=FALSE) -head(result) -@ - -\section{Identify extreme events} -\subsection{Conceptual framework} -This function of the package identifies extreme event and does data -analysis. The upper tail and lower tail values are defined as extreme -events at certain probability. - -There are two further issues to consider. First, matters are -complicated by the fact that extreme (tail) values may cluster: for -example, there may be two or three consecutive days of very high or -very low daily returns, or these extremes may occur in two out of -three days. If the extreme values are all in the same tail of the -distribution, it might make sense to consider the cluster of extreme -values as a single event. - -We approach this problem through two paths. The data has following -events: clustered, unclustered and mixed clusters. For simplicity, we -remove all the mixed clusters and deal with the rest. Unclustered or -uncontaminated events are those where there is no other event within -the event window. Clustered events are defined by fusing all -consecutive extreme events, of the same direction, into a single -event. In event time, date +1 is then the first day after the run of -extreme events, and date -1 is the last day prior to the start of the -run. This strategy avoids losing observations of some of the most -important crises, which have clustered extreme events in the same -direction. - -% Example for understanding -\subsection{Usage} -This function does extreme event analysis on the returns of the -data. Function has following two arguments: -\begin{enumerate} -\item \textit{input}: Data on which extreme event analysis is done. Note: - \textit{input} should be in returns format. -\item \textit{prob.value}: It is the tail value on basis of which the - extreme events are defined. For eg: \textit{prob.value} of 5 will consider - 5\% tail on both sides. -\end{enumerate} -<<>>== -data(eventstudyData) -input <- eventstudyData$sp500 -output <- identifyextremeevents(input, prob.value=5) -@ -% I don't understand this output. Maybe you should explain what it means. -\subsection{Output} -Output is in list format. Primarily it consists of three lists, -summary statistics for complete data-set, extreme event analysis for -lower tail and extreme event analysis for upper tail. Further, these -lower tail and upper tail list objects consists of 5 more list objects with -following output: -\begin{enumerate} -\item Extreme events dataset -\item Distribution of clustered and unclustered % events. -\item Run length distribution -\item Quantile values of extreme events -\item Yearly distribution of extreme events -\end{enumerate} -The complete set of analysis is done on the returns of S\&P500 and -these results are in tandem with Table 1,2,3,4 and 5 of Patnaik, Shah -and Singh (2013). - -\subsubsection{Summary statistics} -Here we have data summary for the complete data-set which shows -minimum, 5\%, 25\%, median, mean, 75\%, 95\%, maximum, standard -deviation (sd), inter-quartile range (IQR) and number of -observations. The output is shown below: -<<>>== -output$data.summary -@ -\subsubsection{Extreme events dataset} -The output for upper tail and lower tail are in the same format as -mentioned above. The data-set is a time series object which has 2 -columns. The first column is \textit{event.series} column which has -returns for extreme events and the second column is -\textit{cluster.pattern} which signifies the number of consecutive -days in the cluster. Here we show results for the lower tail. -<<>>= -str(output$lower.tail$data) -@ - -\subsubsection{Distribution of clustered and unclustered events} -In the analysis we have clustered, unclustered and mixed clusters. We -remove the mixed clusters and study the rest of the clusters by fusing -them. Here we show, number of clustered and unclustered data used in -the analysis. The \textit{removed.clstr} refers to mixed cluster which -are removed and not used in the analysis.\textit{Tot.used} represents -total number of extreme events used for the analysis which is sum of -\textit{unclstr} (unclustered events) and \textit{used.clstr} (Used -clustered events). \textit{Tot} -are the total number of extreme events in the data-set. -<<>>= -output$lower.tail$extreme.event.distribution -@ - -\subsubsection{Run length distribution of clusters} -Clusters used in the analysis are defined as consecutive extreme -events. Run length shows total number of clusters with \textit{n} consecutive -days. In the example below we have 3 clusters with \textit{two} -consecutive events and 0 clusters with \textit{three} consecutive -events. -<<>>= -output$lower.tail$runlength -@ - -\subsubsection{Extreme event quantile values} -Quantile values show 0\%, 25\%, median, 75\%,100\% and mean values for -the extreme events data. -<<>>= -output$lower.tail$quantile.values -@ - -\subsubsection{Yearly distribution of extreme events} -This table shows the yearly distribution and -the median value for extreme events data. -<<>>= -output$lower.tail$yearly.extreme.event -@ -The yearly distribution for extreme events include unclustered event -and clustered events which are fused. While in extreme event distribution of -clustered and unclustered event, the clustered events are defined as -total evnets in a cluster. For example, if there is a clustered event -with three consecutive extreme events then yearly distribution will -treat it as one single event. Here below the relationship between the -Tables is explained through equations:\\\\ -\textit{Sum of yearly distribution for lower tail = 59 \\ -Unclustered events for lower tail = 56\\\\ -Clustered events for lower tail = 3 + 0\\ -Total events in clusters (Adding number of events in each cluster) -= 3*2 + 0*3 = 6\\ -Total used events = Unclustered events for lower tail + Total events -in clusters \\ = 56 + 6 = 62 \\\\ -Sum of yearly distribution for lower tail = Unclustered events for -lower tail + Total events in clusters\\ = 56 + 3 =59} -<<>>= -sum(output$lower.tail$yearly.extreme.event[,"number.lowertail"]) -output$lower.tail$extreme.event.distribution[,"unclstr"] -output$lower.tail$runlength -@ - \section{Computational details} The package code is purely written in R. It has dependencies to zoo (\href{http://cran.r-project.org/web/packages/zoo/index.html}{Zeileis Added: pkg/vignettes/identifyextremeevent.Rnw =================================================================== --- pkg/vignettes/identifyextremeevent.Rnw (rev 0) +++ pkg/vignettes/identifyextremeevent.Rnw 2013-04-29 11:55:53 UTC (rev 58) @@ -0,0 +1,181 @@ + +\documentclass[a4paper,11pt]{article} +\usepackage{graphicx} +\usepackage{a4wide} +\usepackage[colorlinks,linkcolor=blue,citecolor=red]{hyperref} +\usepackage{natbib} +\usepackage{float} +\usepackage{tikz} +\usepackage{parskip} +\usepackage{amsmath} +\title{Introduction to the \textbf{eventstudies} package in R} +\author{Ajay Shah, Vimal Balasubramaniam and Vikram Bahure} +\begin{document} +%\VignetteIndexEntry{eventstudies: A package with functionality to do Event Studies} +%\VignetteDepends{} +%\VignetteKeywords{event studies} +%\VignettePackage{eventstudies} +\maketitle +\begin{abstract} +The structure of the package and its implementation of event study +methodology is explained in this paper. In addition to converting +physical dates to event time frame, functions for re-indexing the +event time returns, bootstrap inference estimation, and identification +of extreme clustered events and further in-depth analysis of the +same is also provided. The methods and functions are elucidated by +employing data-set for S\&P 500, Nifty and net Foreign Institutional +Investors (FII) flow in India. +\end{abstract} + +\SweaveOpts{engine=R,pdf=TRUE} +\section{Introduction} + + +\section{Identify extreme events} +\subsection{Conceptual framework} +This function of the package identifies extreme event and does data +analysis. The upper tail and lower tail values are defined as extreme +events at certain probability. + +There are two further issues to consider. First, matters are +complicated by the fact that extreme (tail) values may cluster: for +example, there may be two or three consecutive days of very high or +very low daily returns, or these extremes may occur in two out of +three days. If the extreme values are all in the same tail of the +distribution, it might make sense to consider the cluster of extreme +values as a single event. + +We approach this problem through two paths. The data has following +events: clustered, unclustered and mixed clusters. For simplicity, we +remove all the mixed clusters and deal with the rest. Unclustered or +uncontaminated events are those where there is no other event within +the event window. Clustered events are defined by fusing all +consecutive extreme events, of the same direction, into a single +event. In event time, date +1 is then the first day after the run of +extreme events, and date -1 is the last day prior to the start of the +run. This strategy avoids losing observations of some of the most +important crises, which have clustered extreme events in the same +direction. + +% Example for understanding +\subsection{Usage} +This function does extreme event analysis on the returns of the +data. Function has following two arguments: +\begin{enumerate} +\item \textit{input}: Data on which extreme event analysis is done. Note: + \textit{input} should be in returns format. +\item \textit{prob.value}: It is the tail value on basis of which the + extreme events are defined. For eg: \textit{prob.value} of 5 will consider + 5\% tail on both sides. +\end{enumerate} +<<>>== +library(eventstudies) +data(identifyexeventData) +input <- identifyexeventData$sp500 +output <- identifyextremeevents(input, prob.value=5) +@ +% I don't understand this output. Maybe you should explain what it means. +\subsection{Output} +Output is in list format. Primarily it consists of three lists, +summary statistics for complete data-set, extreme event analysis for +lower tail and extreme event analysis for upper tail. Further, these +lower tail and upper tail list objects consists of 5 more list objects with +following output: +\begin{enumerate} +\item Extreme events dataset +\item Distribution of clustered and unclustered % events. +\item Run length distribution +\item Quantile values of extreme events +\item Yearly distribution of extreme events +\end{enumerate} +The complete set of analysis is done on the returns of S\&P500 and +these results are in tandem with Table 1,2,3,4 and 5 of Patnaik, Shah +and Singh (2013). + +\subsubsection{Summary statistics} +Here we have data summary for the complete data-set which shows +minimum, 5\%, 25\%, median, mean, 75\%, 95\%, maximum, standard +deviation (sd), inter-quartile range (IQR) and number of +observations. The output is shown below: +<<>>== +output$data.summary +@ +\subsubsection{Extreme events dataset} +The output for upper tail and lower tail are in the same format as +mentioned above. The data-set is a time series object which has 2 +columns. The first column is \textit{event.series} column which has +returns for extreme events and the second column is +\textit{cluster.pattern} which signifies the number of consecutive +days in the cluster. Here we show results for the lower tail. +<<>>= +str(output$lower.tail$data) +@ + +\subsubsection{Distribution of clustered and unclustered events} +In the analysis we have clustered, unclustered and mixed clusters. We +remove the mixed clusters and study the rest of the clusters by fusing +them. Here we show, number of clustered and unclustered data used in +the analysis. The \textit{removed.clstr} refers to mixed cluster which +are removed and not used in the analysis.\textit{Tot.used} represents +total number of extreme events used for the analysis which is sum of +\textit{unclstr} (unclustered events) and \textit{used.clstr} (Used +clustered events). \textit{Tot} +are the total number of extreme events in the data-set. +<<>>= +output$lower.tail$extreme.event.distribution +@ + +\subsubsection{Run length distribution of clusters} +Clusters used in the analysis are defined as consecutive extreme +events. Run length shows total number of clusters with \textit{n} consecutive +days. In the example below we have 3 clusters with \textit{two} +consecutive events and 0 clusters with \textit{three} consecutive +events. +<<>>= +output$lower.tail$runlength +@ + +\subsubsection{Extreme event quantile values} +Quantile values show 0\%, 25\%, median, 75\%,100\% and mean values for +the extreme events data. +<<>>= +output$lower.tail$quantile.values +@ + +\subsubsection{Yearly distribution of extreme events} +This table shows the yearly distribution and +the median value for extreme events data. +<<>>= +output$lower.tail$yearly.extreme.event +@ +The yearly distribution for extreme events include unclustered event +and clustered events which are fused. While in extreme event distribution of +clustered and unclustered event, the clustered events are defined as +total evnets in a cluster. For example, if there is a clustered event +with three consecutive extreme events then yearly distribution will +treat it as one single event. Here below the relationship between the +Tables is explained through equations:\\\\ +\textit{Sum of yearly distribution for lower tail = 59 \\ +Unclustered events for lower tail = 56\\\\ +Clustered events for lower tail = 3 + 0\\ +Total events in clusters (Adding number of events in each cluster) += 3*2 + 0*3 = 6\\ +Total used events = Unclustered events for lower tail + Total events +in clusters \\ = 56 + 6 = 62 \\\\ +Sum of yearly distribution for lower tail = Unclustered events for +lower tail + Total events in clusters\\ = 56 + 3 =59} +<<>>= +sum(output$lower.tail$yearly.extreme.event[,"number.lowertail"]) +output$lower.tail$extreme.event.distribution[,"unclstr"] +output$lower.tail$runlength +@ + +\section{Computational details} +The package code is purely written in R. It has dependencies to zoo +(\href{http://cran.r-project.org/web/packages/zoo/index.html}{Zeileis + 2012}) and boot +(\href{http://cran.r-project.org/web/packages/boot/index.html}{Rlpley + 2013}). R itself as well as these packages can be obtained from \href{http://CRAN.R-project.org/}{CRAN}. +%\section{Acknowledgments} + +\end{document} From noreply at r-forge.r-project.org Mon Apr 29 16:23:37 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 29 Apr 2013 16:23:37 +0200 (CEST) Subject: [Eventstudies-commits] r59 - pkg/vignettes Message-ID: <20130429142337.4912C183887@r-forge.r-project.org> Author: vikram Date: 2013-04-29 16:23:37 +0200 (Mon, 29 Apr 2013) New Revision: 59 Modified: pkg/vignettes/eventstudies.Rnw pkg/vignettes/identifyextremeevent.Rnw Log: Wrote identify extreme events vignette Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-29 11:55:53 UTC (rev 58) +++ pkg/vignettes/eventstudies.Rnw 2013-04-29 14:23:37 UTC (rev 59) @@ -20,10 +20,8 @@ The structure of the package and its implementation of event study methodology is explained in this paper. In addition to converting physical dates to event time frame, functions for re-indexing the -event time returns, bootstrap inference estimation, and identification -of extreme clustered events and further in-depth analysis of the -same is also provided. The methods and functions are elucidated by -employing data-set of SENSEX firms. +event time returns and bootstrap inference estimation. The methods and +functions are elucidated by employing data-set ofSENSEX firms. \end{abstract} \SweaveOpts{engine=R,pdf=TRUE} @@ -106,14 +104,25 @@ Here, we index the stock split date, stock price returns to day 0 and similarly post event dates are indexed to positive and pre event dates are indexed as negative. As we can see below the stock split dates -for BHEL, Bharti Airtel and Cipla are indexed to day 0. +for BHEL, Bharti Airtel and Cipla are indexed to day 0. -% outcomes, example +The output for \textit{phys2eventtime} is a list. The first element of +a list is a time series object which is converted to event +time and the second element is \textit{outcomes} which shows if there +was any \textit{NA} in the dataset. If the outcome is \textit{success} +then all is well in the given window as specified by the +width. It gives \textit{wdatamissing} if there are too many \textit{NAs} within the crucial event +window or \textit{wrongspan} if the event date is not placed within +the span of data for the unit or \textit{unitmissing} if a unit named +in events is not in \textit{z}. <<>>= es <- phys2eventtime(z=StockPriceReturns, events=SplitDates, width=10) es.w <- window(es$z.e, start=-10, end=10) SplitDates[1:3,] +StockPriceReturns[SplitDates[1,2],SplitDates[1,1]] +StockPriceReturns[SplitDates[2,2],SplitDates[2,1]] +StockPriceReturns[SplitDates[3,2],SplitDates[3,1]] es.w[,1:3] @ @@ -132,7 +141,7 @@ estimates like standard errors and confidence intervals. For this, we generate the sampling distribution for the estimate using bootstrap inference. A detailed explanation of the methodology is presented in -Shah, Patnaik and Singh (2013). +Patnaik, Shah and Singh (2013). This specific approach used here is based on Davinson, Hinkley and Schectman (1986). The \textit{inference.Ecar} function does the bootstrap to generate distribution of $\bar{CR}$. The bootstrap @@ -140,7 +149,7 @@ \begin{figure}[t] \begin{center} - \caption{Event on S\&P 500 and response of Nifty} + \caption{Stock splits event and response of respective stock returns} \setkeys{Gin}{width=0.8\linewidth} \setkeys{Gin}{height=0.8\linewidth} <>= Modified: pkg/vignettes/identifyextremeevent.Rnw =================================================================== --- pkg/vignettes/identifyextremeevent.Rnw 2013-04-29 11:55:53 UTC (rev 58) +++ pkg/vignettes/identifyextremeevent.Rnw 2013-04-29 14:23:37 UTC (rev 59) @@ -8,7 +8,7 @@ \usepackage{tikz} \usepackage{parskip} \usepackage{amsmath} -\title{Introduction to the \textbf{eventstudies} package in R} +\title{Introduction to the \textbf{extreme events} functionality} \author{Ajay Shah, Vimal Balasubramaniam and Vikram Bahure} \begin{document} %\VignetteIndexEntry{eventstudies: A package with functionality to do Event Studies} @@ -17,57 +17,31 @@ %\VignettePackage{eventstudies} \maketitle \begin{abstract} -The structure of the package and its implementation of event study -methodology is explained in this paper. In addition to converting -physical dates to event time frame, functions for re-indexing the -event time returns, bootstrap inference estimation, and identification -of extreme clustered events and further in-depth analysis of the -same is also provided. The methods and functions are elucidated by -employing data-set for S\&P 500, Nifty and net Foreign Institutional -Investors (FII) flow in India. +The \textit{eventstudies} package also has extreme events +functionality. This package has \textit{identifyextremeevents} +function which does extreme event analysis by fusing the +consecutive extreme events in a single event. The methods and +functions are elucidated by employing data-set of S\&P 500 and Nifty. \end{abstract} \SweaveOpts{engine=R,pdf=TRUE} \section{Introduction} +The analysis done using this function is in tandem with Table 1,2,3,4 +and 5 of Patnaik, Shah and Singh (2013). A detail methodology is also +discussed in the paper mentioned. We use S\&P500 returns to +understand the \textit{identifyextremeevents} functionality. +Using this function, one can to understand the distribution and run +length of the clustered events, quantile values for the extreme +events and yearly distribution of the extreme events. -\section{Identify extreme events} -\subsection{Conceptual framework} -This function of the package identifies extreme event and does data -analysis. The upper tail and lower tail values are defined as extreme -events at certain probability. -There are two further issues to consider. First, matters are -complicated by the fact that extreme (tail) values may cluster: for -example, there may be two or three consecutive days of very high or -very low daily returns, or these extremes may occur in two out of -three days. If the extreme values are all in the same tail of the -distribution, it might make sense to consider the cluster of extreme -values as a single event. - -We approach this problem through two paths. The data has following -events: clustered, unclustered and mixed clusters. For simplicity, we -remove all the mixed clusters and deal with the rest. Unclustered or -uncontaminated events are those where there is no other event within -the event window. Clustered events are defined by fusing all -consecutive extreme events, of the same direction, into a single -event. In event time, date +1 is then the first day after the run of -extreme events, and date -1 is the last day prior to the start of the -run. This strategy avoids losing observations of some of the most -important crises, which have clustered extreme events in the same -direction. - -% Example for understanding -\subsection{Usage} -This function does extreme event analysis on the returns of the -data. Function has following two arguments: -\begin{enumerate} -\item \textit{input}: Data on which extreme event analysis is done. Note: - \textit{input} should be in returns format. -\item \textit{prob.value}: It is the tail value on basis of which the - extreme events are defined. For eg: \textit{prob.value} of 5 will consider - 5\% tail on both sides. -\end{enumerate} +\section{Extreme event analysis} +This function just needs input in returns format on which extreme +event analysis is to be done. Further we define tail events for given +probability value. For instance, if \textit{prob.value} is 5 then both +side 5\% tail events are considered as extreme, lower tail and upper +tail (5\% to 95\%). <<>>== library(eventstudies) data(identifyexeventData) @@ -75,8 +49,7 @@ output <- identifyextremeevents(input, prob.value=5) @ % I don't understand this output. Maybe you should explain what it means. -\subsection{Output} -Output is in list format. Primarily it consists of three lists, +The output is a list. Primarily it consists of three lists, summary statistics for complete data-set, extreme event analysis for lower tail and extreme event analysis for upper tail. Further, these lower tail and upper tail list objects consists of 5 more list objects with @@ -88,11 +61,8 @@ \item Quantile values of extreme events \item Yearly distribution of extreme events \end{enumerate} -The complete set of analysis is done on the returns of S\&P500 and -these results are in tandem with Table 1,2,3,4 and 5 of Patnaik, Shah -and Singh (2013). -\subsubsection{Summary statistics} +\subsection{Summary statistics} Here we have data summary for the complete data-set which shows minimum, 5\%, 25\%, median, mean, 75\%, 95\%, maximum, standard deviation (sd), inter-quartile range (IQR) and number of @@ -100,7 +70,7 @@ <<>>== output$data.summary @ -\subsubsection{Extreme events dataset} +\subsection{Extreme events dataset} The output for upper tail and lower tail are in the same format as mentioned above. The data-set is a time series object which has 2 columns. The first column is \textit{event.series} column which has @@ -111,7 +81,7 @@ str(output$lower.tail$data) @ -\subsubsection{Distribution of clustered and unclustered events} +\subsection{Distribution of clustered and unclustered events} In the analysis we have clustered, unclustered and mixed clusters. We remove the mixed clusters and study the rest of the clusters by fusing them. Here we show, number of clustered and unclustered data used in @@ -125,7 +95,7 @@ output$lower.tail$extreme.event.distribution @ -\subsubsection{Run length distribution of clusters} +\subsection{Run length distribution of clusters} Clusters used in the analysis are defined as consecutive extreme events. Run length shows total number of clusters with \textit{n} consecutive days. In the example below we have 3 clusters with \textit{two} @@ -135,14 +105,14 @@ output$lower.tail$runlength @ -\subsubsection{Extreme event quantile values} +\subsection{Extreme event quantile values} Quantile values show 0\%, 25\%, median, 75\%,100\% and mean values for the extreme events data. <<>>= output$lower.tail$quantile.values @ -\subsubsection{Yearly distribution of extreme events} +\subsection{Yearly distribution of extreme events} This table shows the yearly distribution and the median value for extreme events data. <<>>= From noreply at r-forge.r-project.org Mon Apr 29 22:46:01 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 29 Apr 2013 22:46:01 +0200 (CEST) Subject: [Eventstudies-commits] r60 - in pkg: . R data man vignettes Message-ID: <20130429204601.77E4B1810FE@r-forge.r-project.org> Author: vikram Date: 2013-04-29 22:46:01 +0200 (Mon, 29 Apr 2013) New Revision: 60 Added: pkg/R/ees.R pkg/data/eesData.rda pkg/man/ees.Rd pkg/man/eesData.Rd pkg/vignettes/ees.Rnw Removed: pkg/R/identifyextremeevents.R pkg/data/identifyexeventData.rda pkg/man/identifyexeventData.Rd pkg/man/identifyextremeevents.Rd pkg/vignettes/identifyextremeevent.Rnw Modified: pkg/NAMESPACE Log: Added new eesPlot functionality Modified: pkg/NAMESPACE =================================================================== --- pkg/NAMESPACE 2013-04-29 14:23:37 UTC (rev 59) +++ pkg/NAMESPACE 2013-04-29 20:46:01 UTC (rev 60) @@ -1,3 +1,3 @@ -export(inference.Ecar, phys2eventtime, remap.cumsum, remap.cumprod, remap.event.reindex, identifyextremeevents) +export(inference.Ecar, phys2eventtime, remap.cumsum, remap.cumprod, remap.event.reindex, ees, eesPlot, deprintize) Copied: pkg/R/ees.R (from rev 57, pkg/R/identifyextremeevents.R) =================================================================== --- pkg/R/ees.R (rev 0) +++ pkg/R/ees.R 2013-04-29 20:46:01 UTC (rev 60) @@ -0,0 +1,883 @@ + +# Total 16 functions +############################ +# Identifying extreme events +############################ +# libraries required +library(zoo) +#---------------------------------------------------------------- +# INPUT: +# 'input' : Data series for which extreme events are +# to be identified. More than one series +# is permissble. The 'input' should be in time +# series format. +# 'prob.value': This is the tail value for which event is +# to be defined. For eg: prob.value=5 will +# consider 5% tail on both sides +#----------------------------------------------------------------- +# OUTPUT: +# Result will be in a list of 3 with following tables: +# 1. Summary statistics +# a. Summary of whole data-set +# 2. Lower tail: Extreme event tables +# a. Distribution of extreme events +# b. Run length distribution +# c. Quantile values +# d. Yearly distribution +# e. Extreme event data +# - Clustered, Un-clustered and Both +# 3. Upper tail: Extreme event tables +# a. Distribution of extreme events +# b. Run length distribution +# c. Quantile values +# d. Yearly distribution +# e. Extreme event data +# - Clustered, Un-clustered and Both +#------------------------------------------------------------------ +# NOTE: +ees <- function(input,prob.value){ + no.var <- NCOL(input) + + #------------------------------------------------ + # Breaking the function if any input is not given + #------------------------------------------------ + # For one variable + # If class of data is not time series + class.input <- class(input)%in%c("xts","zoo") + if(class.input==FALSE){ + stop("Input data is not in time series format. Valid 'input' should be of class xts and zoo") + } + + # Converting an xts object to zoo series + input.class <- length(which(class(input)%in%"xts")) + if(length(input.class)==1){ + input <- zoo(input) + } + + #----------------------------------------- + # Event series: Clustered and un-clustered + #----------------------------------------- + tmp <- get.clusters.formatted(event.series=input, + response.series=input, + probvalue=prob.value, + event.value="nonreturns", + response.value="nonreturns") + tail.events <- tmp[which(tmp$left.tail==1 | tmp$right.tail==1),] + clustered.tail.events <- tmp[which(tmp$cluster.pattern>1),] + unclustered.tail.events <- tmp[-which(tmp$cluster.pattern>1),] + # Left tail data + left.tail.clustered <- clustered.tail.events[which(clustered.tail.events$left.tail==1),c("event.series","cluster.pattern")] + left.tail.unclustered <- unclustered.tail.events[which(unclustered.tail.events$left.tail==1),c("event.series","cluster.pattern")] + left.all <- tail.events[which(tail.events$left.tail==1),c("event.series","cluster.pattern")] + # Right tail data + right.tail.clustered <- clustered.tail.events[which(clustered.tail.events$right.tail==1),c("event.series","cluster.pattern")] + right.tail.unclustered <- unclustered.tail.events[which(unclustered.tail.events$right.tail==1),c("event.series","cluster.pattern")] + right.all <- tail.events[which(tail.events$right.tail==1),c("event.series","cluster.pattern")] + + #--------------------- + # Extreme event output + #--------------------- + # Summary statistics + summ.st <- sumstat(input) + + # Distribtution of events + event.dist <- extreme.events.distribution(input,prob.value) + + # Run length distribution + runlength <- runlength.dist(input,prob.value) + + # Quantile extreme values + qnt.values <- quantile.extreme.values(input,prob.value) + + # Yearly distribution of extreme event dates + yearly.exevent <- yearly.exevent.dist(input,prob.value) + + #--------------------- + # Compiling the output + #--------------------- + output <- lower.tail <- upper.tail <- list() + # Compiling lower tail and upper tail separately + # Lower tail + lower.tail$data <- list(left.all,left.tail.clustered, + left.tail.unclustered) + names(lower.tail$data) <- c("All","Clustered","Unclustered") + lower.tail$extreme.event.distribution <- event.dist$lower.tail + lower.tail$runlength <- runlength$lower.tail + lower.tail$quantile.values <- qnt.values$lower.tail + lower.tail$yearly.extreme.event <- yearly.exevent$lower.tail + # Upper tail + upper.tail$data <- list(right.all,right.tail.clustered, + right.tail.unclustered) + names(upper.tail$data) <- c("All","Clustered","Unclustered") + upper.tail$extreme.event.distribution <- event.dist$upper.tail + upper.tail$runlength <- runlength$upper.tail + upper.tail$quantile.values <- qnt.values$upper.tail + upper.tail$yearly.extreme.event <- yearly.exevent$upper.tail + # Output + output$data.summary <- summ.st + output$lower.tail <- lower.tail + output$upper.tail <- upper.tail + return(output) +} + +######################################## +# Functions used for formatting clusters +######################################## +#------------------------ +# Categorzing tail events +# for ES analysis +#------------------------ +# Generates returns for the series +# Mark left tail, right tail events +gen.data <- function(d,probvalue,value="nonreturns"){ + res <- data.frame(dates=index(d),value=coredata(d)) + if(value=="returns"){ + res$returns <- c(NA,coredata(diff(log(d))*100)) + }else{ + res$returns <- d + } + pval <- c(probvalue/100,(1-(probvalue/100))) + pval <- quantile(res$returns,prob=pval,na.rm=TRUE) + res$left.tail <- as.numeric(res$returns < pval[1]) + res$right.tail <- as.numeric(res$returns > pval[2]) + res$both.tails <- res$left.tail + res$right.tail + res <- res[complete.cases(res),] + if(value=="returns"){ + return(res[-1,]) + }else{ + return(res) + } +} + + +#------------------- +# Summarise patterns +summarise.rle <- function(oneseries){ + tp <- rle(oneseries) + tp1 <- data.frame(tp$lengths,tp$values) + tp1 <- subset(tp1,tp1[,2]==1) + summary(tp1[,1]) +} + +# Summarise the pattern of cluster +summarise.cluster <- function(obj){ + rle.both <- summarise.rle(obj$both.tail) + rle.left <- summarise.rle(obj$left.tail) + rle.right <- summarise.rle(obj$right.tail) + rbind(both=rle.both,left=rle.left,right=rle.right) +} + +# Getting location for the length +exact.pattern.location <- function(us,pt,pt.len){ + st <- rle(us) + len <- st$length + loc.cs <- cumsum(st$length) + loc <- loc.cs[which(st$values==pt & st$length==pt.len)]-pt.len+1 + return(loc) +} + +# Identify and mark mixed clusters +identify.mixedclusters <- function(m,j){ + m$remove.mixed <- 0 + rownum <- which(m$pattern==TRUE) + for(i in 1:length(rownum)){ + nextnum <- rownum[i]+j-1 + twonums <- m$returns[c(rownum[i]:nextnum)] > 0 + if(sum(twonums)==j || sum(twonums)==0){ + next + }else{ + m$remove.mixed[c(rownum[i]:nextnum)] <- 5 + } + } + m +} + +#-------------------- +# Formatting clusters +#-------------------- +# This function takes does the following transformation: +#---------------------------------------------------- +# What the function does? +# i. Get extreme events from event.series +# ii. Remove all the mixed clusters +# iii. Get different types cluster +# iv. Further club the clusters for event series and +# corresponding response series to get +# clustered returns +# v. Throw the output in timeseries format +#---------------------------------------------------- +# Input for the function +# event.series = Series in levels or returns on events +# is to be defined +# response.series = Series in levels or returns on which +# response is to be generated +# prob.value = Tail value for defining an event +# event.value = What value is to be studied +# returns or levels +# Similarly for response.value +#---------------------------------------------------- +# Output = Formatted clusters in time series format +#---------------------------------------------------- +get.clusters.formatted <- function(event.series, + response.series, + probvalue=5, + event.value="returns", + response.value="returns"){ + # Getting levels in event format + tmp <- gen.data(event.series, + probvalue=probvalue, + value=event.value) + res.ser <- gen.data(response.series, + probvalue=probvalue, + value=response.value) + # Storing old data points + tmp.old <- tmp + + # Get pattern with maximum length + res <- summarise.cluster(tmp) + max.len <- max(res[,"Max."]) + + #------------------------ + # Removing mixed clusters + #------------------------ + for(i in max.len:2){ + which.pattern <- rep(1,i) + patrn <- exact.pattern.location(tmp$both.tails,1,i) + # If pattern does not exist move to next pattern + if(length(patrn)==0){next} + tmp$pattern <- FALSE + tmp$pattern[patrn] <- TRUE + tmp <- identify.mixedclusters(m=tmp,i) + me <- length(which(tmp$remove.mixed==5)) + + if(me!=0){ + tmp <- tmp[-which(tmp$remove.mixed==5),] + cat("Pattern of:",i,";", + "Discarded event:",me/i,"\n") + } + } + tmp.nc <- tmp + + # Merging event and response series + tmp.es <- xts(tmp[,-1],as.Date(tmp$dates)) + tmp.rs <- xts(res.ser[,-1],as.Date(res.ser$dates)) + tmp.m <- merge(tmp.es,res.ser=tmp.rs[,c("value","returns")], + all=F) + + # Formatting + if(event.value=="returns"){ + which.value <- event.value + }else{ + which.value <- "value" + } + # Converting to data.frame + temp <- as.data.frame(tmp.m) + temp$dates <- rownames(temp) + n <- temp + # Get pattern with maximum length + res <- summarise.cluster(temp) + max.len <- max(res[,"Max."]) + cat("Maximum length after removing mixed clusters is", + max.len,"\n") + # Marking clusters + n$cluster.pattern <- n$both.tails + for(pt.len in max.len:1){ + mark <- exact.pattern.location(n$both.tails,1,pt.len) + if(length(mark)==0){next} + n$cluster.pattern[mark] <- pt.len + } + + #------------------- + # Clustering returns + #------------------- + print("Clustering events.") + for(pt.len in max.len:2){ + rownum <- exact.pattern.location(n$both.tails,1,pt.len) + # If pattern does not exist + if(length(rownum)==0){ + cat("Pattern",pt.len,"does not exist.","\n");next + } + # Clustering + while(length(rownum)>0){ + prevnum <- rownum[1]-1 + lastnum <- rownum[1]+pt.len-1 + # Clustering event series + if(event.value=="returns"){ + newreturns <- (n$value[lastnum]-n$value[prevnum])*100/n$value[prevnum] + n[rownum[1],c("value","returns")] <- c(n$value[lastnum],newreturns) + }else{ + newreturns <- sum(n$value[rownum[1]:lastnum],na.rm=T) + n[rownum[1],c("value","returns")] <- c(n$value[lastnum],newreturns) + } + # Clustering response series + if(response.value=="returns"){ + newreturns.rs <- (n$value.1[lastnum]-n$value.1[prevnum])*100/n$value.1[prevnum] + n[rownum[1],c("value.1","returns.1")] <- c(n$value.1[lastnum],newreturns.rs) + }else{ + newreturns <- sum(n$value.1[rownum[1]:lastnum],na.rm=T) + n[rownum[1],c("value.1","returns.1")] <- c(n$value.1[lastnum],newreturns) + } + n <- n[-c((rownum[1]+1):lastnum),] + rownum <- exact.pattern.location(n$both.tails,1,pt.len) + } + } + # Columns to keep + cn <- c(which.value,"left.tail","right.tail", + "returns.1","cluster.pattern") + tmp.ts <- zoo(n[,cn],order.by=as.Date(n$dates)) + colnames(tmp.ts) <- c("event.series","left.tail","right.tail", + "response.series","cluster.pattern") + + # Results + return(tmp.ts) +} + +############################## +# Summary statistics functions +############################## +#--------------------------------------------- +# Table 1: Summary statistics +# INPUT: Time series data-set for which +# summary statistics is to be estimated +# OUTPUT: A data frame with: +# - Values: "Minimum", 5%,"25%","Median", +# "Mean","75%","95%","Maximum", +# "Standard deviation","IQR", +# "Observations" +#---------------------------------------------- +sumstat <- function(input){ + no.var <- NCOL(input) + if(no.var==1){input <- xts(input)} + # Creating empty frame: chassis + tmp <- data.frame(matrix(NA,nrow=11,ncol=NCOL(input))) + colnames(tmp) <- "summary" + rownames(tmp) <- c("Min","5%","25%","Median","Mean","75%","95%", + "Max","sd","IQR","Obs.") + # Estimating summary statistics + tmp[1,] <- apply(input,2,function(x){min(x,na.rm=TRUE)}) + tmp[2,] <- apply(input,2,function(x){quantile(x,0.05,na.rm=TRUE)}) + tmp[3,] <- apply(input,2,function(x){quantile(x,0.25,na.rm=TRUE)}) + tmp[4,] <- apply(input,2,function(x){median(x,na.rm=TRUE)}) + tmp[5,] <- apply(input,2,function(x){mean(x,na.rm=TRUE)}) + tmp[6,] <- apply(input,2,function(x){quantile(x,0.75,na.rm=TRUE)}) + tmp[7,] <- apply(input,2,function(x){quantile(x,0.95,na.rm=TRUE)}) + tmp[8,] <- apply(input,2,function(x){max(x,na.rm=TRUE)}) + tmp[9,] <- apply(input,2,function(x){sd(x,na.rm=TRUE)}) + tmp[10,] <- apply(input,2,function(x){IQR(x,na.rm=TRUE)}) + tmp[11,] <- apply(input,2,function(x){NROW(x)}) + tmp <- round(tmp,2) + + return(tmp) +} + +###################### +# Yearly summary stats +###################### +#---------------------------- +# INPUT: +# 'input': Data series for which event cluster distribution +# is to be calculated; +# 'prob.value': Probility value for which tail is to be constructed this +# value is equivalent to one side tail for eg. if prob.value=5 +# then we have values of 5% tail on both sides +# Functions used: yearly.exevent.summary() +# OUTPUT: +# Yearly distribution of extreme events +#---------------------------- +yearly.exevent.dist <- function(input, prob.value){ + no.var <- NCOL(input) + mylist <- list() + # Estimating cluster count + #-------------------- + # Formatting clusters + #-------------------- + tmp <- get.clusters.formatted(event.series=input, + response.series=input, + probvalue=prob.value, + event.value="nonreturns", + response.value="nonreturns") + + tmp.res <- yearly.exevent.summary(tmp) + tmp.res[is.na(tmp.res)] <- 0 + # Left and right tail + lower.tail.yearly.exevent <- tmp.res[,1:2] + upper.tail.yearly.exevent <- tmp.res[,3:4] + output <- list() + output$lower.tail <- lower.tail.yearly.exevent + output$upper.tail <- upper.tail.yearly.exevent + mylist <- output + + return(mylist) +} + +#------------------------------------------------ +# Get yearly no. and median for good and bad days +#------------------------------------------------ +yearly.exevent.summary <- function(tmp){ + tmp.bad <- tmp[which(tmp[,"left.tail"]==1),] + tmp.good <- tmp[which(tmp[,"right.tail"]==1),] + # Bad days + tmp.bad.y <- apply.yearly(xts(tmp.bad),function(x)nrow(x)) + tmp.bad.y <- merge(tmp.bad.y,apply.yearly(xts(tmp.bad[,1]),function(x)median(x,na.rm=T))) + index(tmp.bad.y) <- as.yearmon(as.Date(substr(index(tmp.bad.y),1,4),"%Y")) + # Good days + tmp.good.y <- apply.yearly(xts(tmp.good),function(x)nrow(x)) + tmp.good.y <- merge(tmp.good.y,apply.yearly(xts(tmp.good[,1]),function(x)median(x,na.rm=T))) + index(tmp.good.y) <- as.yearmon(as.Date(substr(index(tmp.good.y),1,4),"%Y")) + tmp.res <- merge(tmp.bad.y,tmp.good.y) + colnames(tmp.res) <- c("number.lowertail","median.lowertail", + "number.uppertail","median.uppertail") + output <- as.data.frame(tmp.res) + cn <- rownames(output) + rownames(output) <- sapply(rownames(output), + function(x)substr(x,nchar(x)-3,nchar(x))) + return(output) +} + +############################# +# Getting event segregation +# - clustered and unclustered +############################# +#---------------------------- +# INPUT: +# 'input': Data series for which event cluster distribution +# is to be calculated; +# Note: The input series expects the input to be in levels not in returns, +# if the some the inputs are already in return formats one has to +# use the other variable 'already.return.series' +# 'already.return.series': column name is to be given which already has +# return series in the data-set +# 'prob.value': Probility value for which tail is to be constructed this +# value is equivalent to one side tail for eg. if prob.value=5 +# then we have values of 5% tail on both sides +# Functions used: get.event.count() +# OUTPUT: +# Distribution of extreme events +#---------------------------- + +extreme.events.distribution <- function(input,prob.value){ + # Creating an empty frame + no.var <- NCOL(input) + lower.tail.dist <- data.frame(matrix(NA,nrow=no.var,ncol=6)) + upper.tail.dist <- data.frame(matrix(NA,nrow=no.var,ncol=6)) + colnames(lower.tail.dist) <- c("Unclustered","Used clusters", + "Removed clusters","Total clusters", + "Total","Total used clusters") + rownames(lower.tail.dist) <- colnames(input) + colnames(upper.tail.dist) <- c("Unclustered","Used clusters", + "Removed clusters","Total clusters", + "Total","Total used clusters") + rownames(upper.tail.dist) <- colnames(input) + # Estimating cluster count + #-------------- + # Cluster count + #-------------- + # Non-returns (if it is already in return format) + tmp <- get.event.count(input,probvalue=prob.value, + value="nonreturns") + lower.tail.dist <- tmp[1,] + upper.tail.dist <- tmp[2,] + + #----------------------------- + # Naming the tail distribution + #----------------------------- + mylist <- list(lower.tail.dist,upper.tail.dist) + names(mylist) <- c("lower.tail", "upper.tail") + return(mylist) +} + +# Functions used in event count calculation +get.event.count <- function(series, + probvalue=5, + value="returns"){ + # Extracting dataset + tmp.old <- gen.data(series,probvalue,value) + tmp <- get.clusters.formatted(event.series=series, + response.series=series, + probvalue, + event.value=value, + response.value=value) + + cp <- tmp[,"cluster.pattern"] + lvl <- as.numeric(levels(as.factor(cp))) + lvl.use <- lvl[which(lvl>1)] + # Calculating Total events + tot.ev.l <- length(which(tmp.old[,"left.tail"]==1)) + tot.ev.r <- length(which(tmp.old[,"right.tail"]==1)) + # Calculating Unclustered events + un.clstr.l <- length(which(tmp[,"left.tail"]==1 & + tmp[,"cluster.pattern"]==1)) + un.clstr.r <- length(which(tmp[,"right.tail"]==1 & + tmp[,"cluster.pattern"]==1)) + # Calculating Used clusters + us.cl.l <- us.cl.r <- NULL + for(i in 1:length(lvl.use)){ + tmp1 <- length(which(tmp[,"cluster.pattern"]==lvl.use[i] & + tmp[,"left.tail"]==1))*lvl.use[i] + tmp2 <- length(which(tmp[,"cluster.pattern"]==lvl.use[i] & + tmp[,"right.tail"]==1))*lvl.use[i] + us.cl.l <- sum(us.cl.l,tmp1,na.rm=TRUE) + us.cl.r <- sum(us.cl.r,tmp2,na.rm=TRUE) + } + + # Making a table + tb <- data.frame(matrix(NA,2,6)) + colnames(tb) <- c("unclstr","used.clstr","removed.clstr","tot.clstr","tot","tot.used") + rownames(tb) <- c("lower","upper") + tb[,"tot"] <- c(tot.ev.l,tot.ev.r) + tb[,"unclstr"] <- c(un.clstr.l,un.clstr.r) + tb[,"used.clstr"] <- c(us.cl.l,us.cl.r) + tb[,"tot.used"] <- tb$unclstr+tb$used.clstr + tb[,"tot.clstr"] <- tb$tot-tb$unclstr + tb[,"removed.clstr"] <- tb$tot.clstr-tb$used.clstr + + return(tb) +} + +#################################### +# Quantile values for extreme events +#################################### +#----------------------------------- +# INPUT: +# 'input': Data series in time series format +# Note: The input series expects the input to be in levels not in returns, +# if the some the inputs are already in return formats one has to +# use the other variable 'already.return.series' +# 'already.return.series': column name is to be given which already has +# return series in the data-set +# Functions used: get.clusters.formatted() +# OUTPUT: +# Lower tail and Upper tail quantile values +#----------------------------------- +quantile.extreme.values <- function(input, prob.value){ + # Creating an empty frame + no.var <- NCOL(input) + lower.tail.qnt.value <- data.frame(matrix(NA,nrow=no.var,ncol=6)) + upper.tail.qnt.value <- data.frame(matrix(NA,nrow=no.var,ncol=6)) + colnames(lower.tail.qnt.value) <- c("Min","25%","Median","75%","Max", + "Mean") + rownames(lower.tail.qnt.value) <- "extreme.events" + colnames(upper.tail.qnt.value) <- c("Min","25%","Median","75%","Max", + "Mean") + rownames(upper.tail.qnt.value) <- "extreme.events" + # Estimating cluster count + #-------------------- + # Formatting clusters + #-------------------- + tmp <- get.clusters.formatted(event.series=input, + response.series=input, + probvalue=prob.value, + event.value="nonreturns", + response.value="nonreturns") + + # Left tail + tmp.left.tail <- tmp[which(tmp$left.tail==1), + "event.series"] + df.left <- t(data.frame(quantile(tmp.left.tail,c(0,0.25,0.5,0.75,1)))) + tmp.left <- round(cbind(df.left,mean(tmp.left.tail)),2) + rownames(tmp.left) <- "extreme.events" + colnames(tmp.left) <- c("0%","25%","Median","75%","100%","Mean") + # Right tail + tmp.right.tail <- tmp[which(tmp$right.tail==1), + "event.series"] + df.right <- t(data.frame(quantile(tmp.right.tail,c(0,0.25,0.5,0.75,1)))) + tmp.right <- round(cbind(df.right, + mean(tmp.right.tail)),2) + rownames(tmp.right) <- "extreme.events" + colnames(tmp.right) <- c("0%","25%","Median","75%","100%","Mean") + + lower.tail.qnt.value <- tmp.left + upper.tail.qnt.value <- tmp.right + + mylist <- list(lower.tail.qnt.value,upper.tail.qnt.value) + names(mylist) <- c("lower.tail", "upper.tail") + return(mylist) +} + +########################## +# Run length distribution +########################## +#----------------------------------- +# INPUT: +# 'input': Data series in time series format +# Note: The input series expects the input to be in levels not in returns, +# if the some the inputs are already in return formats one has to +# use the other variable 'already.return.series' +# 'already.return.series': column name is to be given which already has +# return series in the data-set +# Functions used: get.clusters.formatted() +# get.cluster.distribution() +# numbers2words() +# OUTPUT: +# Lower tail and Upper tail Run length distribution +#----------------------------------- +runlength.dist <- function(input, prob.value){ + + # Creating an empty frame + no.var <- NCOL(input) + + # Finding maximum Run length + # Seed value + max.runlength <- 0 + #--------------------------- + # Estimating max. Run length + #--------------------------- + tmp <- get.clusters.formatted(event.series=input, + response.series=input, + probvalue=prob.value, + event.value="nonreturns", + response.value="nonreturns") + + tmp.runlength <- get.cluster.distribution(tmp,"event.series") + max.runlength <- max(max.runlength,as.numeric(colnames(tmp.runlength)[NCOL(tmp.runlength)])) + + # Generating empty frame + col.names <- seq(2:max.runlength)+1 + lower.tail.runlength <- data.frame(matrix(NA,nrow=no.var, + ncol=length(col.names))) + upper.tail.runlength <- data.frame(matrix(NA,nrow=no.var, + ncol=length(col.names))) + colnames(lower.tail.runlength) <- col.names + rownames(lower.tail.runlength) <- "clustered.events" + colnames(upper.tail.runlength) <- col.names + rownames(upper.tail.runlength) <- "clustered.events" + + #---------------------- + # Run length estimation + #---------------------- + tmp.res <- get.cluster.distribution(tmp,"event.series") + for(j in 1:length(colnames(tmp.res))){ + col.number <- colnames(tmp.res)[j] + lower.tail.runlength[1,col.number] <- tmp.res[1,col.number] + upper.tail.runlength[1,col.number] <- tmp.res[2,col.number] + } + + # Replacing NA's with zeroes + lower.tail.runlength[is.na(lower.tail.runlength)] <- 0 + upper.tail.runlength[is.na(upper.tail.runlength)] <- 0 + + # creating column names + word.cn <- NULL + for(i in 1:length(col.names)){ + word.cn[i] <- numbers2words(col.names[i]) + } + colnames(lower.tail.runlength) <- word.cn + colnames(upper.tail.runlength) <- word.cn + mylist <- list(lower.tail.runlength,upper.tail.runlength) + names(mylist) <- c("lower.tail", "upper.tail") + return(mylist) +} + +#------------------------- +# Get cluster distribution +#------------------------- +# Input for this function is the output of get.cluster.formatted +get.cluster.distribution <- function(tmp,variable){ + # Extract cluster category + cp <- tmp[,"cluster.pattern"] + lvl <- as.numeric(levels(as.factor(cp))) + lvl.use <- lvl[which(lvl>1)] + # Get numbers for each category + tb <- data.frame(matrix(NA,2,length(lvl.use))) + colnames(tb) <- as.character(lvl.use) + rownames(tb) <- c(paste(variable,":lower tail"), + paste(variable,":upper tail")) + for(i in 1:length(lvl.use)){ + tb[1,i] <- length(which(tmp[,"cluster.pattern"]==lvl.use[i] + & tmp[,"left.tail"]==1)) + tb[2,i] <- length(which(tmp[,"cluster.pattern"]==lvl.use[i] + & tmp[,"right.tail"]==1)) + + } + return(tb) +} + +#---------------------------- +# Converting numbers to words +#---------------------------- +numbers2words <- function(x){ + helper <- function(x){ + digits <- rev(strsplit(as.character(x), "")[[1]]) + nDigits <- length(digits) + if (nDigits == 1) as.vector(ones[digits]) + else if (nDigits == 2) + if (x <= 19) as.vector(teens[digits[1]]) + else trim(paste(tens[digits[2]], + Recall(as.numeric(digits[1])))) + else if (nDigits == 3) trim(paste(ones[digits[3]], "hundred", + Recall(makeNumber(digits[2:1])))) + else { + nSuffix <- ((nDigits + 2) %/% 3) - 1 + if (nSuffix > length(suffixes)) stop(paste(x, "is too large!")) + trim(paste(Recall(makeNumber(digits[ + nDigits:(3*nSuffix + 1)])), + suffixes[nSuffix], + Recall(makeNumber(digits[(3*nSuffix):1])))) + } + } + trim <- function(text){ + gsub("^\ ", "", gsub("\ *$", "", text)) + } + makeNumber <- function(...) as.numeric(paste(..., collapse="")) + opts <- options(scipen=100) + on.exit(options(opts)) + ones <- c("", "one", "two", "three", "four", "five", "six", "seven", + "eight", "nine") + names(ones) <- 0:9 + teens <- c("ten", "eleven", "twelve", "thirteen", "fourteen", "fifteen", + "sixteen", " seventeen", "eighteen", "nineteen") + names(teens) <- 0:9 + tens <- c("twenty", "thirty", "forty", "fifty", "sixty", "seventy", + "eighty", + "ninety") + names(tens) <- 2:9 + x <- round(x) + suffixes <- c("thousand", "million", "billion", "trillion") + if (length(x) > 1) return(sapply(x, helper)) + helper(x) +} + +########################## +# Extreme event study plot +########################## +# This function generates event study plot for clustered and un-clustered data +#------------------------- +# Input for the function +# z = Data object with both the series response.series and event.series +# response.series.name = Column name of the series for which response is observed +# event.series.name = Column name of the series on which event is observed +# titlestring = Title string for the event study plot +# ylab = Y - axis label +# width = width of event window for event study plot +# prob.value = Probability value for which extreme events is determined +#------------------------- +eesPlot <- function(z, response.series.name, + event.series.name, + titlestring, ylab, width=5, + prob.value=5){ + #----------------- + # Get event dates + #----------------- + # Get both clustered and unclustered dates + e.s <- z[,event.series.name] + r.s <- z[,response.series.name] + data.use <- get.clusters.formatted(event.series=e.s, + response.series=r.s, + probvalue=prob.value, + event.value="nonreturns", + response.value="nonreturns", + result="series") + # Get only unclustered data + data.frmt <- data.use[which(data.use$cluster.pattern==1),] + data.frmt2 <- data.use[which(data.use$cluster.pattern!=0),] + + # get dates for bigdays and baddays + baddays.normal <- index(data.frmt[which(data.frmt[,"left.tail"]==1)]) + bigdays.normal <- index(data.frmt[which(data.frmt[,"right.tail"]==1)]) + baddays.purged <- index(data.frmt2[which(data.frmt2[,"left.tail"]==1)]) + bigdays.purged <- index(data.frmt2[which(data.frmt2[,"right.tail"]==1)]) + + d.good.normal <- bigdays.normal + d.bad.normal <- baddays.normal + d.good.purged <- bigdays.purged + d.bad.purged <- baddays.purged + + # ES for normal returns + es.good.normal <- corecomp(data.use,d.good.normal, + "response.series",width) + es.bad.normal <- corecomp(data.use,d.bad.normal, + "response.series",width) + + # ES for purged returns + es.good.purged <- corecomp(data.use,d.good.purged, + "response.series",width) + es.bad.purged <- corecomp(data.use,d.bad.purged, + "response.series",width) + + big.normal <- max(abs(cbind(es.good.normal,es.bad.normal))) + big.purged <- max(abs(cbind(es.good.purged,es.bad.purged))) + big <- max(big.normal,big.purged) + hilo1 <- c(-big,big) + + #--------------- + # Plotting graph + plot.es.graph.both(es.good.normal,es.bad.normal, + es.good.purged,es.bad.purged, + width,titlestring,ylab) +} +#-------------------------- +# Eventstudy analysis +# -using eventstudy package +#-------------------------- +corecomp <- function(z,dlist,seriesname,width) { + events <- data.frame(unit=rep(seriesname, length(dlist)), when=dlist) + es.results <- phys2eventtime(z, events, width=0) + es.w <- window(es.results$z.e, start=-width, end=+width) + # Replaing NA's with zeroes + es.w[is.na(es.w)] <- 0 + es.w <- remap.cumsum(es.w, is.pc=FALSE, base=0) + inference.Ecar(es.w) +} + +#---------------------------------- +# Plotting graph in es.error.metric +#---------------------------------- +plot.es.graph.both <- function(es.good.normal,es.bad.normal, + es.good.purged,es.bad.purged, + width,titlestring,ylab){ + big.normal <- max(abs(cbind(es.good.normal,es.bad.normal))) + big.purged <- max(abs(cbind(es.good.purged,es.bad.purged))) + big <- max(big.normal,big.purged) + hilo1 <- c(-big,big) + + # Plotting graph + par(mfrow=c(1,2)) + + # Plot very good days + plot(-width:width, es.good.normal[,2], type="l", lwd=2, ylim=hilo1, col="red", + xlab="Event time (days)", ylab=ylab, + main=paste("Very good", " (by ", titlestring, ")", sep="")) + lines(-width:width, es.good.purged[,2], lwd=2, lty=1,type="l", col="orange") + points(-width:width, es.good.normal[,2], pch=19,col="red") + points(-width:width, es.good.purged[,2], pch=25,col="orange") + lines(-width:width, es.good.normal[,1], lwd=0.8, lty=2, col="red") + lines(-width:width, es.good.normal[,3], lwd=0.8, lty=2, col="red") [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/eventstudies -r 60 From noreply at r-forge.r-project.org Mon Apr 29 23:04:41 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 29 Apr 2013 23:04:41 +0200 (CEST) Subject: [Eventstudies-commits] r61 - in pkg: . R man vignettes Message-ID: <20130429210441.E42CE184EAF@r-forge.r-project.org> Author: vikram Date: 2013-04-29 23:04:41 +0200 (Mon, 29 Apr 2013) New Revision: 61 Added: pkg/man/eesPlot.Rd Modified: pkg/NAMESPACE pkg/R/ees.R pkg/vignettes/ees.Rnw Log: Added eesPlot, ees functionality together in ess.R Modified: pkg/NAMESPACE =================================================================== --- pkg/NAMESPACE 2013-04-29 20:46:01 UTC (rev 60) +++ pkg/NAMESPACE 2013-04-29 21:04:41 UTC (rev 61) @@ -1,3 +1,3 @@ -export(inference.Ecar, phys2eventtime, remap.cumsum, remap.cumprod, remap.event.reindex, ees, eesPlot, deprintize) +export(inference.Ecar, phys2eventtime, remap.cumsum, remap.cumprod, remap.event.reindex, ees, eesPlot) Modified: pkg/R/ees.R =================================================================== --- pkg/R/ees.R 2013-04-29 20:46:01 UTC (rev 60) +++ pkg/R/ees.R 2013-04-29 21:04:41 UTC (rev 61) @@ -62,6 +62,7 @@ probvalue=prob.value, event.value="nonreturns", response.value="nonreturns") + tail.events <- tmp[which(tmp$left.tail==1 | tmp$right.tail==1),] clustered.tail.events <- tmp[which(tmp$cluster.pattern>1),] unclustered.tail.events <- tmp[-which(tmp$cluster.pattern>1),] @@ -765,8 +766,8 @@ response.series=r.s, probvalue=prob.value, event.value="nonreturns", - response.value="nonreturns", - result="series") + response.value="nonreturns") + # Get only unclustered data data.frmt <- data.use[which(data.use$cluster.pattern==1),] data.frmt2 <- data.use[which(data.use$cluster.pattern!=0),] Added: pkg/man/eesPlot.Rd =================================================================== --- pkg/man/eesPlot.Rd (rev 0) +++ pkg/man/eesPlot.Rd 2013-04-29 21:04:41 UTC (rev 61) @@ -0,0 +1,35 @@ +\name{eesPlot} +\alias{eesPlot} + +\title{ +Plotting clustered and unclustered extreme event study plot. +} + +\description{ +This function generates an extreme event study plot by marking extreme events and fusing clustered events together. It plots event study plot for lower tail and upper tail events. Tail events are defined as per given probability value. The value of the event series and response series should be in returns. + } + +\usage{ +eesPlot(z, response.series.name, event.series.name, titlestring, ylab, width, prob.value) +} + +\arguments{ + \item{z}{Data object with both response and event series on which event study is to be performed} + \item{response.series.name}{Column name of the series in 'z' on which response is to be observed } + \item{event.series.name}{Column name of the series in 'z' on which event is to be observed } + \item{titlestring}{Title for event study plot: Preferred to be response series name} + \item{ylab}{Y-axis label} + \item{width}{Width for event study plot} + \item{prob.value}{It is the tail value on the basis of which the + extreme event are defined. For eg: prob.value of 5 will consider 5\% tail on both sides.} +} + +\value{ + It gives an extreme event study plot for very bad (lower tail) and very good (upper tail) events on event series. +} + +\examples{ +library(eventstudies) +data(eesData) +eesPlot(z=eesData, response.series.name="nifty", event.series.name="sp500",titlestring="S&P500", ylab="(Cum.) change in NIFTY") +} Modified: pkg/vignettes/ees.Rnw =================================================================== --- pkg/vignettes/ees.Rnw 2013-04-29 20:46:01 UTC (rev 60) +++ pkg/vignettes/ees.Rnw 2013-04-29 21:04:41 UTC (rev 61) @@ -152,7 +152,11 @@ \setkeys{Gin}{height=0.8\linewidth} <>= <> -res <- deprintize(eesPlot)(z=eesData, response.series.name="nifty", event.series.name="sp500",titlestring="S&P500", ylab="(Cum.) change in NIFTY", prob.value=5, width=15 +# Suppress the messages + deprintize<-function(f){ + return(function(...) {capture.output(w<-f(...));return(w);}); + } +res <- deprintize(eesPlot)(z=eesData, response.series.name="nifty", event.series.name="sp500",titlestring="S&P500", ylab="(Cum.) change in NIFTY", prob.value=5, width=5) @ \end{center} \label{fig:one} From noreply at r-forge.r-project.org Tue Apr 30 05:18:15 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 30 Apr 2013 05:18:15 +0200 (CEST) Subject: [Eventstudies-commits] r62 - pkg/vignettes Message-ID: <20130430031815.CA7DE18388B@r-forge.r-project.org> Author: vikram Date: 2013-04-30 05:18:15 +0200 (Tue, 30 Apr 2013) New Revision: 62 Modified: pkg/vignettes/ees.Rnw Log: Added ees plot in the vignette; matched results with the Tables in the paper Modified: pkg/vignettes/ees.Rnw =================================================================== --- pkg/vignettes/ees.Rnw 2013-04-29 21:04:41 UTC (rev 61) +++ pkg/vignettes/ees.Rnw 2013-04-30 03:18:15 UTC (rev 62) @@ -33,12 +33,14 @@ Using this function, one can to understand the distribution and run length of the clustered events, quantile values for the extreme -events and yearly distribution of the extreme events. +events and yearly distribution of the extreme events. In the sections +below we replicate the analysis for S\&P 500 from the paper and we +generate the extreme event study plot for event on S\&P 500 and +response of NIFTY. - \section{Extreme event analysis} -This function just needs input in returns format on which extreme -event analysis is to be done. Further we define tail events for given +This function needs input in returns format on which extreme +event analysis is to be done. Further, we define tail events for given probability value. For instance, if \textit{prob.value} is 5 then both side 5\% tail events are considered as extreme, lower tail and upper tail (5\% to 95\%). @@ -66,7 +68,8 @@ Here we have data summary for the complete data-set which shows minimum, 5\%, 25\%, median, mean, 75\%, 95\%, maximum, standard deviation (sd), inter-quartile range (IQR) and number of -observations. The output is shown below: +observations. The output shown below mathces with the fourth column +in Table 1 of the paper. <<>>== output$data.summary @ @@ -76,7 +79,8 @@ columns. The first column is \textit{event.series} column which has returns for extreme events and the second column is \textit{cluster.pattern} which signifies the number of consecutive -days in the cluster. Here we show results for the lower tail. +days in the cluster. Here we show results for the lower tail of S\&P +500. Below is the extreme event data set on which analysis is done. <<>>= str(output$lower.tail$data) @ @@ -90,7 +94,8 @@ total number of extreme events used for the analysis which is sum of \textit{unclstr} (unclustered events) and \textit{used.clstr} (Used clustered events). \textit{Tot} -are the total number of extreme events in the data-set. +are the total number of extreme events in the data set. The results +shown below match with second row in Table 2 of the paper. <<>>= output$lower.tail$extreme.event.distribution @ @@ -100,21 +105,25 @@ events. Run length shows total number of clusters with \textit{n} consecutive days. In the example below we have 3 clusters with \textit{two} consecutive events and 0 clusters with \textit{three} consecutive -events. +events. The results shown below match with second row in Table 3 of +the paper. <<>>= output$lower.tail$runlength @ \subsection{Extreme event quantile values} Quantile values show 0\%, 25\%, median, 75\%,100\% and mean values for -the extreme events data. +the extreme events data. The results shown below match with second row +of Table 4 in the paper. <<>>= output$lower.tail$quantile.values @ \subsection{Yearly distribution of extreme events} This table shows the yearly distribution and -the median value for extreme events data. +the median value for extreme events data. The results shown below +match with third and forth column for S\&P 500 in the Table 5 of the +paper. <<>>= output$lower.tail$yearly.extreme.event @ @@ -140,11 +149,24 @@ output$lower.tail$runlength @ -\section{Extreme event} -% Quantile values +\section{Extreme event study plot} +Here, we replicate the Figure 7, from the paper Patnaik, Shah and +Singh (2013). First, we need to have a merged time series object with +event series and response series with no missing values for unerring +results. After getting the time series object we just need to use the +following function and fill the relevant arguments to generate the +extreme event study plot. -% Plot event study graph - +The function generates extreme values for the event series with the +given probability value. Once the values are generated, clustered +extreme events are fused together for the response series and +extreme evenstudy plot is generated for very bad and very good +events. The detail methodology is mentioned in the paper. +<<>>= +eesPlot(z=eesData, response.series.name="nifty", event.series.name="sp500", + titlestring="S&P500", ylab="(Cum.) change in NIFTY", prob.value=5, + width=5) +@ \begin{figure}[t] \begin{center} \caption{Extreme event on S\&P500 and response of NIFTY} From noreply at r-forge.r-project.org Tue Apr 30 06:26:35 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 30 Apr 2013 06:26:35 +0200 (CEST) Subject: [Eventstudies-commits] r63 - in pkg: . tests vignettes Message-ID: <20130430042635.8F7541853E2@r-forge.r-project.org> Author: chiraganand Date: 2013-04-30 06:26:35 +0200 (Tue, 30 Apr 2013) New Revision: 63 Modified: pkg/DESCRIPTION pkg/tests/inr_inference.R pkg/vignettes/eventstudies.Rnw Log: Fixed code formatting, removed extra line from description file. Modified: pkg/DESCRIPTION =================================================================== --- pkg/DESCRIPTION 2013-04-30 03:18:15 UTC (rev 62) +++ pkg/DESCRIPTION 2013-04-30 04:26:35 UTC (rev 63) @@ -9,4 +9,3 @@ Description: Implementation of short and long term event study methodology License: GPL-2 LazyLoad: yes -Packaged: 2013-04-02 10:33:06 UTC; t136 Modified: pkg/tests/inr_inference.R =================================================================== --- pkg/tests/inr_inference.R 2013-04-30 03:18:15 UTC (rev 62) +++ pkg/tests/inr_inference.R 2013-04-30 04:26:35 UTC (rev 63) @@ -1,16 +1,20 @@ library(eventstudies) +data(inr) -data(inr) -inr_returns<-diff(log(inr))[-1] +inr_returns <- diff(log(inr))[-1] + eventslist<-data.frame(unit=rep("inr",10), when=as.Date(c( "2010-04-20","2010-07-02","2010-07-27", "2010-09-16","2010-11-02","2011-01-25", "2011-03-17","2011-05-03","2011-06-16", - "2011-07-26"))) -event_time_data<-phys2eventtime(inr_returns,eventslist,width=10) -w<-window(event_time_data$z.e,start=-10,end=10) + "2011-07-26") + ) + ) +event_time_data <- phys2eventtime(inr_returns,eventslist,width=10) +w <- window(event_time_data$z.e,start=-10,end=10) + all.equal(inference.Ecar(w)[,2],c(-.000015327,-.002526819,.0011990000,.001193535,.001846734, -.000105473,-.001659772,.001644518,-0.001325236,.001546369, -.000809734,-.001499191,-.000289414,-.000003273,-.000416662, Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-30 03:18:15 UTC (rev 62) +++ pkg/vignettes/eventstudies.Rnw 2013-04-30 04:26:35 UTC (rev 63) @@ -33,7 +33,7 @@ used statistical tool. Event study is used to study the response or -the effect on a variable, due to similar events. Efficient and liquid +the effect on a variable due to similar events. Efficient and liquid markets are basic assumption in this methodology. It assumes the effect on response variable is without delay. As event study output is further used in econometric analysis, hence significance test such as From noreply at r-forge.r-project.org Tue Apr 30 08:29:23 2013 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 30 Apr 2013 08:29:23 +0200 (CEST) Subject: [Eventstudies-commits] r64 - pkg/vignettes Message-ID: <20130430062923.71912184271@r-forge.r-project.org> Author: vikram Date: 2013-04-30 08:29:23 +0200 (Tue, 30 Apr 2013) New Revision: 64 Modified: pkg/vignettes/eventstudies.Rnw Log: Minor modification in vingette Modified: pkg/vignettes/eventstudies.Rnw =================================================================== --- pkg/vignettes/eventstudies.Rnw 2013-04-30 04:26:35 UTC (rev 63) +++ pkg/vignettes/eventstudies.Rnw 2013-04-30 06:29:23 UTC (rev 64) @@ -147,6 +147,9 @@ bootstrap to generate distribution of $\bar{CR}$. The bootstrap generates confidence interval at 2.5\% and 97.5\% for the estimate. +<<>>= +result <- inference.Ecar(z.e=es.cs, to.plot=TRUE) +@ \begin{figure}[t] \begin{center} \caption{Stock splits event and response of respective stock returns}