[R-pkg-devel] How to make S3-method for the "format" generic for class inheriting from "AsIs"

Erik Bulow erik.bulow at rccvast.se
Tue Dec 8 15:38:57 CET 2015


Thank you very much Hadley for your fast response!


I do however find the following lines (102-113) from "data.frame" a little
problematic here:

  [...]
  if (is.vector(xi1) || is.factor(xi1))
    xi[[j]] <- rep(xi1, length.out = nr)
  else if (is.character(xi1) && inherits(xi1, "AsIs"))
    xi[[j]] <- structure(rep(xi1, length.out = nr),
      class = class(xi1))
  else if (inherits(xi1, "Date") || inherits(xi1,
    "POSIXct")) 
    xi[[j]] <- rep(xi1, length.out = nr)
  else {
    fixed <- FALSE
    break
  }
  [...]


With the "as.data.frame.pin" as suggested, I will here get "fixed <-
FALSE" which will result in:

  > data.frame(1:2, structure("191212121212", class = c("pin",
"character")))
  Error in data.frame(1:2, structure("191212121212", class = c("pin",
"character"))) : 
  arguments imply differing number of rows: 2, 1



As a big fan of your work, I know your arguments against R¹s recycling
rules (and I do agree) but I would like to allow recycling at least when
(as above) the length of my pin vector is only 1 (I do know of course that
dplyr::data_frame does just that :-).

Best Regards!
Erik B






On 2015-12-08 14:09, "Hadley Wickham" <h.wickham at gmail.com> wrote:

>Why not just make your own as.data.frame method? e.g.
>
>as.data.frame.pin <- function(x, ...) {
>  structure(
>    list(x),
>    class = "data.frame",
>    row.names = .set_row_names(length(x))
>  )
>}
>
>data.frame() calls as.data.frame() on all of its arguments.
>
>Hadley
>
>On Tue, Dec 8, 2015 at 5:13 AM, Erik Bulow <erik.bulow at rccvast.se> wrote:
>> Dear list!
>>
>> I am one of two authors to the package "sweidnumbr"
>> (https://cran.r-project.org/web/packages/sweidnumbr/index.html). This
>> package introduce an S3-class called "pin" and methods etc for handling
>> personal identification numbers.
>>
>> An object might look like:
>> x <- structure("1912121212", class = c("AsIs", "pin", "character"))
>>
>> We want the "AsIs" class to allow for example recycling when the object
>>is
>> put into a data.frame. Problem is that we would also like to have our
>>own
>> format.pin-method. This is problematic since base::format.AsIs does not
>> use "NextMethod" (which all other xxx.AsIs methods do).
>>
>> We can think of two possible solutions:
>>
>> 1. We can redefine the format-function to handle this but will then get
>>a
>> check note for masking base::format.
>> 2. We could skip the format.pin method and introduce a stand alone
>> function called "pin_format" or similair (but our method is very
>>similair
>> to base::format.Date and we would like to benefit from that).
>>
>> We can not skip the "AsIs" class inheritence. If we do, we need to
>>rewrite
>> "data.frame" (which is a function and not an S3 generic in opposite to
>> as.data.frame for which we could just add as.data.frame.pin). If we do,
>>we
>> still get the same check note as above but for masking base::data.frame
>> instead.
>>
>> Is it possible to use both the benefits of the AsIs-class but to also
>> define our own format-method without masking anything from other
>>packages?
>>
>> Best regards
>> Erik Bülow
>>
>> ______________________________________________
>> R-package-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-package-devel
>
>
>
>-- 
>http://had.co.nz/



More information about the R-package-devel mailing list