diff options
| author | Guillaume Horel <guillaume.horel@gmail.com> | 2011-10-18 02:40:30 -0400 |
|---|---|---|
| committer | Guillaume Horel <guillaume.horel@gmail.com> | 2011-10-18 02:40:30 -0400 |
| commit | 83b41368bbc072bead2b6311c7a019b40164bba4 (patch) | |
| tree | df15f140e43e38e1c7d51bcc18319be19d13be9f /utils.R | |
| parent | 08a6c748f17c8baf2c83d391341c731cb9eeef4f (diff) | |
| download | bandit-83b41368bbc072bead2b6311c7a019b40164bba4.tar.gz | |
Tons of fixes
have downloaded a complete history of the sp500 since 01/01/2000
Diffstat (limited to 'utils.R')
| -rw-r--r-- | utils.R | 123 |
1 files changed, 123 insertions, 0 deletions
@@ -0,0 +1,123 @@ +#fix bug in adjRatios +source("patch-adjRatios.R") +assignInNamespace("adjRatios",adjRatios,ns="TTR") +library(TTR) +rm(adjRatios) + +getBloombergData <- function(conn,ticker, start.date, end.date=Sys.Date()){ + ohlc <- bdh(conn,paste(ticker,"Equity"),c("PX_OPEN","PX_HIGH","PX_LOW","PX_LAST","VOLUME"),start.date,end.date,dates.as.row.names=F) + colnames(ohlc) <- c("Date","Open","High","Low","Close","Volume") + ohlc <- xts(ohlc[,-1],as.Date(ohlc$Date)) + #split information + spl <- bds(conn,paste(ticker,"Equity"),c("EQY_DVD_ADJUST_FACT")) + # bds returns NULL if there is no data. + #Adjustment Factor Operator Type + # 1 = div + # 2 = mul + # 3 = add + # 4 = sub + #Adjustment Factor Flag + # 1 = prices only + # 2 = volumes only + # 3 = prices and volume + + # can't handle 3 or 4 yet + if(NROW(spl)!=0){ + if (NROW(spl[spl[,"Adjustment Factor Operator Type"] %in% c(3, 4),])>0){ + stop("case not handled") + }else{ + spl[spl[,"Adjustment Factor Operator Type"]==1, "Adjustment Factor"] <- + 1/spl[spl[,"Adjustment Factor Operator Type"]==1, "Adjustment Factor"] + } + spl <- xts(data.frame(spl$"Adjustment Factor", + ifelse(spl$"Adjustment Factor Flag" %in% c(2,3), + spl$"Adjustment Factor",NA)), + order.by = as.Date(spl$"Adjustment Date")) + #aggregate non-unique dates + spl <- as.xts(aggregate(spl, identity, prod, na.rm=T)) + if(any( (time(spl) >= start.date) && (time(spl) <= end.date))){ + spl <- window(spl, start=start.date, end = end.date) + }else{ + spl <- NULL + } + } + #div information + #we need to override the end date as well cause the Ex-Date might be in the + #future + override_fields <- c("DVD_START_DT", "DVD_END_DT") + override_values <- c(format(start.date, "%Y%m%d"),format(end.date, "%Y%m%d")) + div <- bds(conn,paste(ticker,"Equity"), c("DVD_HIST"), override_fields, + override_values) + if(NROW(div)!=0){ + div <- xts(div$"Dividend Amount", as.Date(div$"Ex-Date")) + #aggregate non-unique dates + div <- as.xts(aggregate(div, identity, sum)) + } + + if(is.null(div) && is.null(spl)){ + divspl <- NULL + }else if(is.null(div)){ + #need to use merge.xts, otherwise spl is cast to a numeric + divspl <- merge.xts(NA, spl ,all=T) + }else if(is.null(spl)){ + divspl <- merge.xts(div ,NA, NA, all=T) + }else{ + divspl <- merge(div, spl, all=T) + } + if(!is.null(divspl)){ + colnames(divspl) <- c("Adj.Div","Split","Split2") + ohlc <- merge(ohlc, divspl, all = TRUE) + if (all(is.na(ohlc[, "Split2"]))) { + s.ratio2 <- rep(1, NROW(ohlc)) + }else { + s.ratio2 <- adjRatios(split = ohlc[, "Split2"])[, 1] + } + ohlc <- cbind(ohlc, ohlc[, "Adj.Div"] * (1/s.ratio2)) + colnames(ohlc)[NCOL(ohlc)] <- "Div" + adj <- adjRatios(ohlc[, "Split"], ohlc[, "Div"], ohlc[, "Close"]) + s.ratio <- adj[, 1] + d.ratio <- adj[, 2] + cn <- colnames(ohlc) + ohlc <- cbind(ohlc, ohlc[, "Close"]) + colnames(ohlc) <- c(cn, "Unadj.Close") + ohlc[, "Open"] <- ohlc[, "Open"] * d.ratio * s.ratio + ohlc[, "High"] <- ohlc[, "High"] * d.ratio * s.ratio + ohlc[, "Low"] <- ohlc[, "Low"] * d.ratio *s.ratio + ohlc[, "Close"] <- ohlc[, "Close"] * d.ratio * s.ratio + ohlc[, "Volume"] <- ohlc[, "Volume"] * (1/s.ratio2) + ohlc <- ohlc[, c("Open", "High", "Low", "Close", "Volume", + "Unadj.Close", "Div", "Split", "Adj.Div")] + }else{ + cn <- colnames(ohlc) + ohlc <- cbind(ohlc, ohlc[, "Close"]) + colnames(ohlc) <- c(cn, "Unadj.Close") + ohlc <- merge(ohlc,NA,NA,NA,all = TRUE) + colnames(ohlc) <- c(colnames(ohlc)[1:6],"Adj.Div","Split","Div") + } + return( ohlc ) +} + +memb <- function(index,add,date){ + #return the spx tickers at a given date using the history of changes + #index: sp500 tickers as of today + #add: tabele with list of changes + #date: date at which we make the query + toreverse <- add[add$date>=date,] + current.index <- index + for(i in 1:nrow(toreverse)){ + if(toreverse$ticker.add[i]!=""){ + current.index <- current.index[-match(toreverse$ticker.add[i],current.index)] + } + if(toreverse$ticker.del[i]!=""){ + current.index <- sort(c(current.index,toreverse$ticker.del[i])) + } + } + current.index +} + +memb.bb <- function(date){ + #return the spx tickers at a given date using bloomberg api + sp500.tickers <- bds(conn, "SPX Index", "INDX_MWEIGHT_HIST", + "END_DATE_OVERRIDE", format(date, "%Y%m%d")) + return( gsub(" [A-Z]*","",sp500.tickers[,1]) ) +} |
