[R-SIG-Finance] Problem with RBloomberg retval argument

roger at bergande.ch roger at bergande.ch
Tue Jan 20 18:02:34 CET 2009


Hello Sergey

There seems to be a small bug in the function which returns the data.frame.

To fix it simply save the following function in a file and source it  
after you load library(RBloomberg)

It works at least on my machine.

Regards,
Roger

#######################################################
rm(list=ls(all=TRUE))
library(RBloomberg)
source("H:/ROGB/downloads/Rsource/RBloomberg/R/as.data.frame.R")

.bbfields <- blpReadFields(path = "C:/Program Files/blp/API")

start.date 	<- as.chron("1990-01-19")
end.date	<- as.chron("2009-01-19")

conn <- blpConnect(show.days="week", na.action="na", periodicity="daily")

bldata <- blpGetData(conn, c("ED4 Comdty", "ED12 Comdty") ,"PX_LAST",  
start=start.date, end=end.date, retval="data.frame")

#########################################################

as.data.frame.BlpCOMReturn <- function(x, row.names = NULL, optional =
                                        FALSE){
   bbfields <- .bbfields
   lst <- list()
   mtx <- as.matrix.BlpCOMReturn(x)
   cols <- colnames(mtx)
   flds <- attr(x, "fields")
   secs <- attr(x, "securities")
   blds <- attr(x, "barfields")
   ndat <- attr(x, "num.of.date.cols")
   ## if date column exists, convert it to chron
   if(ndat != 0){
     dtime <- as.chron.COMDate(mtx[,1])
     mtx <- matrix(mtx[, 2:ncol(mtx)], ncol=ncol(mtx) - 1)
   }
   ## convert all other columns to appropriate datatype
   if(!is.null(blds)){
     fields <- blds
   }else{
     fields <- flds
   }
   ####################### fix ############################################
   typTmp <- dataType(fields, bbfields)
   typ <- rep(typTmp,length(secs))
   ########################################################################
   for(n in seq(1, ncol(mtx))){
     # n = 2
     vec <- mtx[,n]
     if(typ[n] == "character"){
       lst <- append(lst, list(as.character(vec)))
     }else if(typ[n] == "double"){
       lst <- append(lst, list(as.numeric(vec)))
     }else if(typ[n] == "logical"){
       lst <- append(lst, list(as.logical(vec)))
     }else if(typ[n] == "chron"){
       lst <- append(lst, list(as.chron(vec)))
     }
   }
   if(ndat != 0){
     lst <- append(list(dtime), lst)
     df <- as.data.frame.list(lst)
     colnames(df) <- cols
   }else{
     df <- as.data.frame.list(lst)
     colnames(df) <- flds
     rownames(df) <- secs
   }
   return(df)
}

###################################################





>
>
> -----Original Message-----
> From: roger at bergande.ch [mailto:roger at bergande.ch]
> Sent: Dienstag, 20. Januar 2009 16:36
> To: Bergande Roger (FI/RM)
> Subject: Fwd: [R-SIG-Finance] Problem with RBloomberg retval argument
>
>
>
> ----- Weitergeleitete Nachricht von sergeyg at gmail.com -----
>       Datum: Mon, 19 Jan 2009 17:24:32 +0100
>         Von: Sergey Goriatchev <sergeyg at gmail.com>
> Antwort an: Sergey Goriatchev <sergeyg at gmail.com>
>     Betreff: [R-SIG-Finance] Problem with RBloomberg retval argument
>          An: r-sig-finance at stat.math.ethz.ch
>
> Hello everyone,
>
> I have two issues that I want to ask.
>
> 1)
> I have problems with loading data with RBloomberg.
> More precisely, I do not seem to be able to load data into a data.frame.
> I get an error message:
>
> start.date 	<- as.chron("1990-01-19")
> end.date	<- as.chron("2009-01-19")
>
> conn <- blpConnect(show.days="week", na.action="na",
> periodicity="daily")
>
>> bldata <- blpGetData(conn, c("ED4 Comdty", "ED12 Comdty"),
>> "PX_LAST", start=start.date, end=end.date, retval="data.frame")
> Error in if (typ[n] == "character") { : argument is of length zero
>
> What does that error message mean and what can I do to avoid this
> error message?
>
> 2)
> If I load data from Bloomberg in matrix format, the date is converted
> to a number. For example:
>
>> bldata <- blpGetData(conn, "ED4 Comdty", "PX_LAST",
>> start=start.date, end=end.date, retval="matrix")
>> head(bldata)
>       [DATETIME] PX_LAST
> [1,]      32892   91.36
> [2,]      32895   91.37
> [3,]      32896   91.38
> [4,]      32897   91.38
> [5,]      32898   91.34
> [6,]      32899   91.28
>
> I tried to convert the number to normal date and by trial and error I
> found the following:
>
>> as.Date(32892, "1899-12-30")
> [1] "1990-01-19"
>
> Is it really true that count starts from December 30th 1899? Why?
>
> Thank you in advance for your help!
>
> Regards,
> Sergey
>
> _______________________________________________
> R-SIG-Finance at stat.math.ethz.ch mailing list
> https://stat.ethz.ch/mailman/listinfo/r-sig-finance
> -- Subscriber-posting only.
> -- If you want to post, subscribe first.
>
>
>
> ----- Ende der weitergeleiteten Nachricht -----
>
>
>
>
>



More information about the R-SIG-Finance mailing list