[R-SIG-Finance] Réf. : Re: Importing from Excel

guillaume.nicoulaud at halbis.com guillaume.nicoulaud at halbis.com
Tue Feb 5 08:33:06 CET 2008


All,

Here my modest contribution (not sure it will actually solve the issue).
Comments are welcome !

Rgds

# ############################################################################
# RXLS
# ############################################################################

# Description
# Functions to manipulate Excel from R.

# Author:        Guillaume Nicoulaud
# Date:          2008-02-05
# Version:       2
# Requirements:  rcom

# Contents
# xlStart --------- Creates a COM object against Excel's API
# xlIsRunning ----- Checks if Excel is running
# xlStop ---------- Removes the COM object (does not always shut Excel down)
# xlVisible ------- Set or get Excel's 'Visible' property
# xlAddWorkbook --- Add a new workbook
# xlIsWorkbook ---- Checks if an R object refers to a workbook
# xlCloseWorkbook - Closes a workbook
# xlOpenWorkbook -- Opens a workbook
# xlPutArray ------ Writes an R array in Excel
# xlRange --------- Points to a range in Excel
# xlGetArray ------ Retrieves an Excel array in R
# xlClearContents - Clears the contents of an Excel range
# xlPutTable ------ Exports a nice table in Excel
# .RXLS ----------- Contents

# ----------------------------------------------------------------------------
# xlStart
# ----------------------------------------------------------------------------

# Description
# Creates a COM object against Excel's API

# Arguments
# None

# Details
# Returns TRUE on success

xlStart = function() {
      if( ! "rcom" %in% .packages() ) library("rcom")
      xl <<- comCreateObject("Excel.Application")
      xlIsRunning() -> ans
      return(ans)
}

# ----------------------------------------------------------------------------
# xlIsRunning
# ----------------------------------------------------------------------------

# Description
# Checks if Excel is running

# Arguments
# None

# Details
# Returns TRUE on success

xlIsRunning = function() {
      ans = FALSE
      if( "xl" %in% ls(.GlobalEnv) & "rcom" %in% .packages() ) {
            if( comIsValidHandle(xl) ) {
                  xl[["Application"]][["Name"]] -> x
                  if( ! is.null(x) ) ans <- x == "Microsoft Excel"
            }
      }
      return(ans)
}

# ----------------------------------------------------------------------------
# xlStop
# ----------------------------------------------------------------------------

# Description
# Removes the COM object (does not always shut Excel down)

# Arguments
# None

# Details
# TRUE means that the COM object has been removed but Excel may still be
# running (even invisibly).

xlStop = function() {
      if( ! xlIsRunning() ) stop("Excel is not running. Use xlStart().")
      if( xlVisible() ) xlVisible(FALSE) -> silent
      xl <<- NULL
      rm( list = "xl", envir = .GlobalEnv )
      gc( verbose = FALSE )
      gc( verbose = FALSE )
      ! xlIsRunning() -> ans
      return(ans)
}

# ----------------------------------------------------------------------------
# xlVisible
# ----------------------------------------------------------------------------

# Description
# Set or get Excel's 'Visible' property

# Arguments
# v --------------- Logical. If NA (the default) returns the current status

# Details
# Returns the status of the 'Visible' property (TRUE or FALSE)

xlVisible = function(v = NA) {
      if( ! xlIsRunning() ) stop("Excel is not running. Use xlStart().")
      if( is.na(v) ) xl[["Visible"]] -> v
      if( ! is.logical(v) ) stop("v must be either TRUE or FALSE")
      xl[["Visible"]] <- v
      xl[["Visible"]] -> ans
      return(ans)
}


# ----------------------------------------------------------------------------
# xlAddWorkbook
# ----------------------------------------------------------------------------

# Description
# Add a new workbook

# Arguments
# path ------------ Full path to the new workbook to be created
# sheets ---------- A vector of sheet names (defaults to Sheet1... Sheet5)

# Details
# Returns an 'xlWorkbook' object - e.g. a list which first element is the
# COM object representing the workbook itself and each of the followings
# beein pointers to the sheets.

xlAddWorkbook = function(path, sheets = paste("Sheet", 1:5, sep ="") ) {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")
      if( ! is.character(sheets) )
            stop("sheets must be a vector of names")

      length(sheets) -> n
      xl[["SheetsInNewWorkbook"]] -> save
      xl[["SheetsInNewWorkbook"]] <- n

      xl[["Workbooks"]]$Add() -> wb
      lapply(1:n, function(i) {
            wb[["Worksheets", i]] -> ws
            ws[["Name"]] <- sheets[i]
            return(ws)
            ws <- NULL
      } ) -> Sheets
      names(Sheets) <- sheets

      xl[["SheetsInNewWorkbook"]] <- save

      wb$SaveAs( normalizePath(path) ) -> ans
      if(!ans) stop("could not create ", sQuote(path))

      c( list(wb = wb), Sheets ) -> res
      attr(res, "class") <- "xlWorkbook"
      wb <- NULL

      return(res)
}

# ----------------------------------------------------------------------------
# xlIsWorkbook
# ----------------------------------------------------------------------------

# Description
# Checks if an R object refers to a workbook

# Arguments
# wb -------------- An R object

# Details
# Returns TRUE on success.

xlIsWorkbook = function(wb) {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")
      class(wb) == "xlWorkbook" -> ans
      wb <- NULL
      return(ans)
}

# ----------------------------------------------------------------------------
# xlCloseWorkbook
# ----------------------------------------------------------------------------

# Description
# Closes a workbook

# Arguments
# wb -------------- An R object
# save ------------ Logical. Defaults to TRUE.

# Details
# Returns TRUE on success. Will also remove the xlWorkbook object.

xlCloseWorkbook = function(wb, save = TRUE) {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")
      if( ! xlIsWorkbook(wb) )
            stop("wb is not a workbook.")
      wb[["wb"]]$Close(save) -> ans
      rm(wb, envir = .GlobalEnv)
      wb <- NULL
      return(ans)
}

# ----------------------------------------------------------------------------
# xlOpenWorkbook
# ----------------------------------------------------------------------------

# Description
# Opens a workbook

# Arguments
# path ------------ Full path to the workbook to be openned

# Details
# Returns an 'xlWorkbook' object - e.g. a list which first element is the
# COM object representing the workbook itself and each of the followings
# beein pointers to the sheets.

xlOpenWorkbook = function(path) {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")

      xl[["Workbooks"]]$Open( normalizePath(path) ) -> wb
      wb[["Sheets"]][["Count"]] -> n
      lapply(1:n, function(i) wb[["Worksheets", i]]) -> Sheets
      sapply(Sheets, function(x) x[["Name"]]) -> names(Sheets)

      c( list(wb = wb), Sheets ) -> res
      attr(res, "class") <- "xlWorkbook"
      wb <- Sheets <- NULL

      return(res)
}

# ----------------------------------------------------------------------------
# xlPutArray
# ----------------------------------------------------------------------------

# Description
# Writes an R array in Excel

# Arguments
# x --------------- An R array or vector
# ws -------------- A pointer to the worksheet where to write the data
# cs -------------- Upper-left cell's reference as a numeric of length 2
# rownames -------- Logical. Should the function export row names?
# colnames -------- Logical. Should the function export column names?
# date.format ----- A string representing user's prefered Excel date format

# Details
# In this function, cs only refers to the upper-left cell of the range where
# to export data.
# The function will perform date conversion automatically provided dates are
# given as standard R Date objects.

xlPutArray = function(x, ws, cs, rownames = FALSE, colnames = FALSE,
      date.format = "aaaa-mm-jj") {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")

      if( ! is.numeric(cs[1]) | ! is.numeric(cs[2]) | length(cs) != 2 )
            stop("cs must be a numeric vector of length 2")

      if( is.null( dim(x) ) ) as.matrix(x) -> x
      nrow(x) -> nrx
      ncol(x) -> ncx

      if(rownames) data.frame(x = rownames(x), x) -> x

      if(colnames) {

            ws[["Range", ws[["Cells", cs[1], cs[2]]],
                  ws[["Cells", cs[1], cs[2] + ncx - 1 ]] ]] -> rr
            temp <- if( is.null(colnames(x)) ) {
                  paste("c", 1:ncx, sep = "")
                  } else { colnames(x) }
            rr[["Value2"]] <- t(temp)
            cs[1] + 1 -> cs[1]
            rr <- NULL

      }

      lapply(1:ncx, function(i) {

            x[, i] -> xi
            ws[["Range", ws[["Cells", cs[1], cs[2] + i - 1 ]],
                  ws[["Cells", cs[1] + nrx - 1, cs[2] + i - 1 ]] ]] -> rr

            class(xi) -> case
            if( case != "numeric" ) {

                  if( case == "Date") {
                        julian(xi, origin = as.Date("1899-12-30")) -> xx
                        rr[["Value2"]] <- as.matrix(xx)
                        rr[["NumberFormat"]] <- date.format
                  }

                  if( case %in% c("character", "factor") ) {
                        rr[["Value2"]] <- as.matrix( as.character(xi) )
                  }

            } else {
                  rr[["Value2"]] <- as.matrix(xi)
            }

            rr <- NULL

      } ) -> silent

      ws <- NULL
      length(silent) == ncx -> ans
      return(ans)
}

# ----------------------------------------------------------------------------
# xlRange
# ----------------------------------------------------------------------------

# Description
# Points to a range in Excel

# Arguments
# ws -------------- A pointer to the worksheet
# cs -------------- Range's references as list of length 2 (see details)
# xlDown ---------- Logical. Should non-empty cells below cs be included ?
# xlToRight ------- Logical. Should non-empty cells next to cs be included ?
# check ----------- Logical. If TRUE returns details on the Excel range

# Details
# The cs argument must be a list of 2 numerical vectors of length 2 giving
# the coordinates of the range to be defined:
# cs = list( upper.left = c(row, col), lower.right = c(row, col) )
# With upper.left being the coordinates (row, col) of the upper-left cell
# of the Excel range and lower.right, the coordinates of the lower-right cell
# of the range. For example cs = list(c(1, 2), c(3, 5)) refers to the A2:C5
# range.
# The function will only xlDown (resp xlToRight) from a horizontal (resp
# vertical) range.

xlRange = function(ws, cs, xlDown = FALSE, xlToRight = FALSE, check = FALSE) {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")

      if( ! is.list(cs) ) {

            if( length(cs) != 2 ) stop("cs must be of length 2")

            ws[["Cells", cs[1], cs[2] ]] -> rr

            if( ! xlDown & ! xlToRight ) rr -> res

            if( xlDown & ! xlToRight ) {
                  ws[["Range", rr, rr[["End", -4121]] ]] -> res
            }

            if( !xlDown & xlToRight ) {
                  ws[["Range", rr, rr[["End", -4161]] ]] -> res
            }

            if( xlDown & xlToRight ) {
                  ws[["Range", rr,
                        rr[["End", -4121]][["End", -4161]] ]] -> res
            }

            rr <- NULL

      } else {

            if( any( sapply(cs, length) != 2 ) )
                  stop("elements of cs must be of length 2.")

            ws[["Range", ws[["Cells", cs[[1]][1], cs[[1]][2] ]],
                  ws[["Cells", cs[[2]][1], cs[[2]][2] ]] ]] -> rr

            rr[["Columns"]][["Count"]] -> nc
            rr[["Rows"]][["Count"]] -> nr

            if( ! xlDown & ! xlToRight ) rr -> res

            if( xlDown & ! xlToRight ) {
                  if( nr != 1 & xlDown )
                    stop("will not xlDown from an horizontal range")
                  ws[["Range", rr, rr[["End", -4121]] ]] -> res
            }

            if( ! xlDown & xlToRight ) {
                  if( nc != 1 )
                    stop("will not xlToRight from a vertical range")
                  ws[["Range", rr, rr[["End", -4161]] ]] -> res
            }

            if( xlDown & xlToRight ) {
                  if( nr != 1 | nc != 1 )
                    stop("will only xlDown & xlToRight from a single cell")
                  ws[["Range", rr,
                        rr[["End", -4121]][["End", -4161]] ]] -> res
            }

            rr <- NULL
      }

      if(check) list(   Pointer = res,
                        Adress = paste(ws[["Name"]], res[["Address"]],
                              sep = "!"),
                        Rows = res[["Rows"]][["Count"]],
                        Columns = res[["Columns"]][["Count"]] ) -> res

      ws <- NULL
      return(res)
}

# ----------------------------------------------------------------------------
# xlGetArray
# ----------------------------------------------------------------------------

# Description
# Retrieves an array from Excel

# Arguments
# ws -------------- A pointer to the worksheet
# cs -------------- A pointer to the range to be exported (see details)
# xlDown ---------- Logical. Should non-empty cells below cs be exported ?
# xlToRight ------- Logical. Should non-empty cells next to cs be exported ?
# rownames -------- Logical. Does the first column contain row names ?
# colnames -------- Logical. Does the first row contain column names ?
# date.format ----- Excel format to be interpreted as dates

# Details
# Arguments work pretty much the same than in xlRange except that cs may be a
# numeric vector of length 2 refering to a unique cell.
# The date.format argument allows the function to identify and convert dates.
# It should be given as a character string representing a date format using
# your local Excel convention (you may wish to re-set the default to
# "yyyy-mm-dd").

# ToDos
# The function fails when cells in the same column have different formats.

xlGetArray = function(ws, cs, xlDown = FALSE, xlToRight = FALSE,
      rownames = FALSE, colnames = FALSE, date.format = "aaaa-mm-jj") {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")

      if( ! is.list(cs) ) list(cs, cs) -> cs
      xlRange(ws, cs, xlDown, xlToRight) -> rr
      rr[["Columns"]][["Count"]] -> ncol
      rr[["Rows"]][["Count"]] -> nrow

      cs[[2]] <- c(cs[[1]][1] + nrow - 1, cs[[1]][2] + ncol - 1)

      if(colnames) {
            if( nrow < 2 )
                  stop("can't extract colnames with less than 2 rows")
            cs -> cs.c
            cs.c[[2]][1] <- cs.c[[1]][1]
            xlRange(ws, cs.c) -> rr
            drop( unlist( rr[["Value2"]] ) ) -> cnames
            if( is.null( rr[["NumberFormat"]] ) ) {
                  rr[["NumberFormat"]] <- "Standard"
            }
            if( rr[["NumberFormat"]] %in% date.format ) {
                  as.character( as.Date("1899-12-30") + cnames ) -> cnames
            }
            if(rownames) cnames[2:length(cnames)] -> cnames
            cs[[1]][1] <- cs[[1]][1] + 1
            rr <- NULL
      }

      if(rownames) {
            if( ncol < 2 )
                  stop("can't extract rownames with less than 2 columns")
            cs -> cs.r
            cs.r[[2]][2] <- cs.r[[1]][2]
            xlRange(ws, cs.r) -> rr
            drop( unlist( rr[["Value2"]] ) ) -> rnames
            if( rr[["NumberFormat"]] %in% date.format ) {
                  as.character( as.Date("1899-12-30") + rnames ) -> rnames
            }
            cs[[1]][2] <- cs[[1]][2] + 1
            rr <- NULL
      }

      lapply(cs[[1]][2]:cs[[2]][2], function(i) {
            cs.d <- cs
            cs.d[[1]][2] <- cs.d[[2]][2] <- i
            xlRange(ws, cs.d) -> rr
            drop( unlist( rr[["Value2"]] ) ) -> out
            if( rr[["NumberFormat"]] %in% date.format ) {
                  as.Date("1899-12-30") + out -> out
            }
            rr <- NULL
            return(out)
      } ) -> out
      data.frame(out) -> res

      colnames(res) <- if(colnames) { cnames
            } else { paste("c", 1:ncol(res), sep = "") }
      rownames(res) <- if(rownames) rnames

      ws <- NULL
      return(res)
}

# ----------------------------------------------------------------------------
# xlClearContents
# ----------------------------------------------------------------------------

# Description
# Clears the content of a range

# Arguments
# ws -------------- A pointer to the worksheet
# cs -------------- Range's references as list of length 2 (see details)
# xlDown ---------- Logical. Should non-empty cells below cs be included?
# xlToRight ------- Logical. Should non-empty cells next to cs be included?
# format ---------- Logical. Should formats be removed too?

# Details
# See xlRange for more information.

xlClearContents = function(ws, cs, xlDown = FALSE, xlToRight = FALSE,
      format = FALSE) {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")

      if( is.null(cs) ) {
            ws[["Cells"]] -> rr
      } else {
            xlRange(ws, cs, xlDown, xlToRight) -> rr
      }

      rr$ClearContents() -> ans
      if(format) rr$ClearFormats() -> ans2; ans & ans2 -> ans

      ws <- rr <- NULL
      return(ans)
}

# ----------------------------------------------------------------------------
# xlPutTable
# ----------------------------------------------------------------------------

# Description
# Exports a formated table to Excel.

# Arguments
# x --------------- An R array or vector
# ws -------------- A pointer to the worksheet where to write the data
# cs -------------- Upper-left cell's reference as a numeric of length 2
# title ----------- Title. If set to NA, no title is exported.
# bline ----------- Logical. Should the bottom line be bold?
# align ----------- A string indicating how columns should be aligned.
# format ----------
# rownames -------- Logical. Should the function export row names?

# Details
# These are the author's preferences ;)
# align must be a sequence of 'l' for left, 'c' for center and 'r' for right.
# align = 'llcr' will cause the 2 columns on the left to be aligned on the
# left, the third column to be centered and the last column to be aligned
# to the right.
# format must be given using Excel conventions (e.g. '@' for string,
# '# ##0.00'for numbers with 2 decimals etc...).

xlPutTable = function(x, ws, cs, title = NA, bline = FALSE, align = NA,
      format = NA, rownames = TRUE) {
      if( ! xlIsRunning() )
            stop("Excel is not running. Use xlStart().")

      ws[["Cells"]] -> cells
      cells[["Interior"]][["Color"]] <- 16777215 # (white)
      cells[["RowHeight"]] <- 14
      cells[["ColumnWidth"]] <- 10
      cells <- NULL

      if( ! is.na(title) ) {
            xlPutArray(title, ws, cs) -> na
            xlRange(ws, cs) -> rr
            rr[["Font"]] -> font
            font[["Color"]] <- 10040115 # (blue)
            font[["Name"]] <- "Tahoma"
            font[["Bold"]] <- TRUE
            font[["Size"]] <- 9
            rr <- NULL
            cs[1] + 2 -> cs[1]
      }

      if(rownames) {
            colnames(x) -> temp
            data.frame(rownames(x), x) -> x
            cnames <- c("'", temp)
            } else {
            cnames <- colnames(x)
      }

      nrow(x) -> nrx
      ncol(x) -> ncx

      # align

      halign = c(l = -4131, c = -4108, r = -4152)

      if( is.na(align) ) {
            do.call(paste, c(list("l"), as.list(rep("r", ncx-1)),
                  list(sep = "") ) ) -> align
            } else {
            if( nchar(align) != ncx )
                  stop("'align' must have ", ncx, " characters")
      }

      sapply(1:nchar(align), function(i) {
            halign[ substr(align, i, i) ]
      } ) -> xlalign

      # format

      c("factor", "character", "logical") -> txt

      if( is.na(format[1]) ) {
            sapply(1:ncx, function(i) class(x[, i]) ) -> cc
            cc[ ! cc %in% c("Date", txt) ] <- "# ##0.00"
            cc[ cc %in% txt ] <- "@"
            cc[ cc == "Date" ] <- "aaaa-mm-jj"
            cc -> xlformat
      } else { format -> xlformat }

      # write by column

      lapply(1:ncx, function(i) {

            xlalign[i] -> xa
            xlformat[i] -> xf

            # column headers

            xlRange(ws, c(cs[1], cs[2] + i - 1)) -> rr
            rr[["Value2"]] <- cnames[i]
            rr[["HorizontalAlignment"]] <- xa

            rr[["Borders", 8]] -> edgetop
            edgetop[["LineStyle"]] <- 1
            edgetop[["Weight"]] <- -4138
            edgetop[["Color"]] <- 10040115 # (blue)

            rr[["Borders", 9]] -> edgebot
            edgebot[["LineStyle"]] <- 1
            edgebot[["Weight"]] <- 2
            edgebot[["Color"]] <- 10040115 # (blue)

            rr[["Font"]] -> font
            font[["Name"]] <- "Tahoma"
            font[["Color"]] <- 10040115 # (blue)
            font[["Bold"]] <- TRUE
            font[["Size"]] <- 9

            # data

            x[, i] -> xi

            if( class(xi) == "Date" ) {
                  julian(xi, origin = as.Date("1899-12-30")) -> xi
            }

            if( class(xi) %in% txt ) as.character(xi) -> xi

            csi <- list(c(cs[1] + 1, cs[2] + i - 1),
                        c(cs[1] + nrx - 1, cs[2] + i - 1 ) )
            xlRange(ws, csi) -> rr

            rr[["Value2"]] <- as.matrix(xi)
            rr[["HorizontalAlignment"]] <- xa
            rr[["NumberFormat"]] <- xf

            rr[["Font"]] -> font
            font[["Name"]] <- "Tahoma"
            font[["Size"]] <- 9

            csy <- c(cs[1] + nrx - 1, cs[2] + i - 1)
            xlRange(ws, csy) -> rr

            rr[["Borders", 9]] -> edgebot
            edgebot[["LineStyle"]] <- 1
            edgebot[["Weight"]] <- -4138
            edgebot[["Color"]] <- 10040115 # (blue)
            edgebot <- NULL

            # bottom row

            if(bline) {

                  rr[["Borders", 8]] -> edgetop
                  edgetop[["LineStyle"]] <- 1
                  edgetop[["Weight"]] <- 2
                  edgetop[["Color"]] <- 10040115 # (blue)
                  edgetop <- NULL

                  rr[["Font"]] -> font
                  font[["Bold"]] <- TRUE
                  font <- NULL
            }

            rr <- NULL

      } ) -> silent

}

# ----------------------------------------------------------------------------
# Contents
# ----------------------------------------------------------------------------

# Description
# List of functions. Use rm(list = .RXLS) to remove all these functions from
# .GlobalEnv.

.RXLS <- c("xlAddWorkbook", "xlClearContents", "xlCloseWorkbook",
      "xlGetArray", "xlIsRunning", "xlIsWorkbook", "xlOpenWorkbook",
      "xlPutArray", "xlRange", "xlStart", "xlStop", "xlVisible", "xlPutTable",
      ".RXLS")








                                                                                                                                                                    
                                                                                                                                                                    
                                                        Pour :   "Spencer Graves" <spencer.graves at pdf.com>                                                          
                                                        cc :     r-sig-finance at stat.math.ethz.ch, MAB <MichelBeck at sbcglobal.net>                                    
                                                        Objet :  Re: [R-SIG-Finance] Importing from Excel                                                           
             "Gabor Grothendieck"                                                                                                                                   
             <ggrothendieck at gmail.com>                                                                                                                              
             Envoyé par :                                                                                                                                           
             r-sig-finance-bounces at stat.math.ethz.                                                                                                                  
             ch                                                                                                                                                     
                                                                                                                                                                    
                                                                                                                                                                    
             04/02/2008 21:14                                                                                                                                       
                                                                                                                                                                    
                                                                                                                                                                    




Regarding read.xls in gdata note that it passes the ... to read.csv so you
could specify na.strings= which should avoid the problem
if its just due to the #NA strings.

On Mon, Feb 4, 2008 at 2:57 PM, Spencer Graves <spencer.graves at pdf.com> wrote:
>      I've had good luck with 'read.xls{gdata}', but that could have the
> same problem.
>
>      If this still gives you problems, you could put your favorite
> 'read.*(...)' in a function that tests columns you specify to see if
> they are numeric and if not tries to replace them with
>
>           is.numeric(as.character(DF[[i]]))
>
>      for column i of data.frame DF.  You could test that to see what
> percent NAs you have and write a warning, etc., whatever you want.
>
>      hope this helps.
>      Spencer
>
>
> MAB wrote:
> > Hi!
> >
> > I am trying to diff data imported from Excel.
> > I use the package xlsReadWrite.
> >
> > After I load the following XL spreadsheet
> >
> > C_Dates C_Price C_Prices_edit         C_Return_Raw        C_Return_edit
> > 1   30405   29.40         29.40                 #N/A                 #N/A
> > 2   30406   29.29         NaN                 -0.003               -0.003
> > 3   30407      NA         29.29                    0                    0
> > (#N/A is a string in one case and the formula =NA() in another)
> >
> > and try to diff the resulting object, I get:
> >
> > Error in r[i1, , drop = FALSE] - r[-nrow(r):-(nrow(r) - lag + 1), , drop =
> > FALSE] :
> >         non-numeric argument to binary operator
> >
> > I attempt to convert to numeric using as.matrix (or data.matrix),
> > but this converts the object to all characters.
> >
> > I can then use as.numeric to get a vector and rebuild the matrix but this gets
> > tedious.
> >
> > Eventually the easiest seems to be to make sure each column in the spreadsheet
> > starts with a numeric, and replace it once the object is in R.
> >
> > There is probably a better way.
> >
> > Michel
> >
> > _______________________________________________
> > 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.
> >
>
> _______________________________________________
> 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.
>

_______________________________________________
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.




Les informations contenues dans ce message sont confidentielles et peuvent constituer des informations privilegiees. Si vous n etes pas le destinataire de ce message, il vous est interdit de le copier, de le faire suivre, de le divulguer ou d en utiliser tout ou partie. Si vous avez recu ce message par erreur, merci de le supprimer de votre systeme, ainsi que toutes ses copies, et d en avertir immediatement l expediteur par message de retour.
Il est impossible de garantir que les communications par messagerie electronique arrivent en temps utile, sont securisees ou denuees de toute erreur ou virus. En consequence, l expediteur n accepte aucune responsabilite du fait des erreurs ou omissions qui pourraient en resulter.
--- ----------------------------------------------------- ---
The information contained in this e-mail is confidential...{{dropped:9}}



More information about the R-SIG-Finance mailing list