Hi the list,

I am writing a package in S4 and I do not manage to understand a bug.
The "R CMD check" and the "R CMD build" both work. Here is links to the package (not on CRAN yet for the raison that I explain bellow):

http://christophe.genolini.free.fr/aTelecharger/kml_0.5.zip
http://christophe.genolini.free.fr/aTelecharger/kml_0.5.tar.gz

Then I install the package and I try an example:

--- 8< --------------
library(kml)
dn <- as.cld(gald())
kml(dn)
# XXX ~ Fast KmL ~
# Erreur dans as.vector(x, mode) : argument 'mode' incorrect
--- 8< --------------


So I make some verifications:
--- 8< ----
class(dn)
# [1] "ClusterizLongData"
# attr(,"package")
# [1] "kml"

getMethod("kml","ClusterizLongData")
# Method Definition:
#
# function (Object, nbClusters = 2:6, nbRedrawing = 20, saveFreq = 100,
#   maxIt = 200, trajMinSize = 2, print.cal = FALSE, print.traj = FALSE,
# imputationMethod = "copyMean", distance, power = 2, centerMethod = meanNA, # startingCond = "allMethods", distanceStartingCond = "euclidean", # ...)
#{
#   nbIdFull <- nrow(Object["traj"])
# ...... [[[The full code is available below]]]
# }
# <environment: namespace:kml>
#
#Signatures:
# Object # target "ClusterizLongData"
# defined "ClusterizLongData"
--- 8< ----

Everything seems fine. The code is correct.
So I copy-and-paste the code that I get with getMethods("kml","ClusterizLongData") and I affect it to a function "func". Then I define again the method "kml".

Then I run again the example that does not work before and it works...
Any explanations?

Christophe Genolini

--- 8< --------------------------
###
### Affecting to func the code that getMethod("kml","ClusterizLongData") delivers
###
func <- function (Object, nbClusters = 2:6, nbRedrawing = 20, saveFreq = 100,
   maxIt = 200, trajMinSize = 2, print.cal = FALSE, print.traj = FALSE,
imputationMethod = "copyMean", distance, power = 2, centerMethod = meanNA,
   startingCond = "allMethods", distanceStartingCond = "euclidean",
   ...)
{
   nbIdFull <- nrow(Object["traj"])
   convergenceTime <- 0
   noNA <- selectSupTrajMinSize(Object, trajMinSize)
   trajNoNA <- Object["traj"][noNA, ]
   nbTime <- length(Object["time"])
   nbId <- nrow(trajNoNA)
   saveCld <- 0
   scr <- plotAll(Object, print.cal = print.cal, print.traj = print.traj,
       print.sub = FALSE, col = "black", type.mean = "n")
   if (length(startingCond) == 1) {
       if (startingCond == "allMethods") {
           startingCond <- c("maxDist", "randomAll", rep("randomK",
               nbRedrawing))[1:nbRedrawing]
       }
       else {
           startingCond <- rep(startingCond, nbRedrawing)
       }
   }
   else {
   }
   if (missing(distance)) {
       distance <- "euclidean"
   }
   if (is.character(distance)) {
       distInt <- pmatch(distance, METHODS)
   }
   else {
       distInt <- NA
   }
   if (print.traj) {
       cat(" ~ Slow KmL ~\n")
       fast <- FALSE
       screenPlot <- scr[2]
       if (!is.na(distInt)) {
           distanceSlow <- function(x, y) {
               dist(rbind(x, y), method = distance)
           }
       }
       else {
           distanceSlow <- distance
       }
   }
   else {
       screenPlot <- NA
       if (is.na(distInt)) {
           cat(" ~ Slow KmL ~\n")
           fast <- FALSE
           distanceSlow <- distance
       }
       else {
           cat(" ~ Fast KmL ~\n")
           fast <- TRUE
       }
   }
   nameObject <- deparse(substitute(Object))
   for (iRedraw in 1:nbRedrawing) {
       for (iNbClusters in nbClusters) {
           saveCld <- saveCld + 1
           clustersInit <- partitionInitialise(nbClusters = iNbClusters,
               method = startingCond[iRedraw], lengthPart = nbId,
matrixDist = as.matrix(dist(trajNoNA, method = distanceStartingCond)))
           clust <- rep(NA, nbIdFull)
           if (fast) {
               resultKml <- .C("kml1", as.double(t(trajNoNA)),
                 iNbInd = as.integer(nbId), iNbTime = as.integer(nbTime),
iNbCluster = as.integer(iNbClusters), maxIt = as.integer(maxIt), distance = as.integer(distInt), power = as.numeric(power), vClusterAffectation1 = as.integer(clustersInit["clusters"]),
                 convergenceTime = as.integer(convergenceTime),
                 NAOK = TRUE, PACKAGE = "kml")[c(8, 9)]
               clust[noNA] <- resultKml[[1]]
           }
           else {
resultKml <- trajKmlSlow(traj = trajNoNA, clusterAffectation = clustersInit,
                 nbId = nbId, nbTime = nbTime, maxIt = maxIt,
                 screenPlot = scr[2], distance = distanceSlow,
                 centerMethod = centerMethod, ...)
               clust[noNA] <- resultKml[[1]]["clusters"]
           }
           yPartition <- ordered(partition(nbClusters = iNbClusters,
               clusters = clust))
           Object["clusters"] <- clusterization(yLongData = as(Object,
"LongData"), xPartition = yPartition, convergenceTime = resultKml[[2]], imputationMethod = imputationMethod, startingCondition = startingCond[iRedraw],
               algorithmUsed = "kml")
           assign(nameObject, Object, envir = parent.frame())
           cat("*")
           if (saveCld >= saveFreq) {
               save(list = nameObject, file = paste(nameObject,
                 ".Rdata", sep = ""))
               saveCld <- 0
               cat("\n")
           }
           else {
           }
           if (print.cal) {
               screen(scr[1])
               plotCriterion(Object, all = TRUE)
           }
           else {
           }
       }
   }
   save(list = nameObject, file = paste(nameObject, ".Rdata",
       sep = ""))
   return(invisible())
}


######
### setting the kml method, using the same code
###
setMethod("kml","ClusterizLongData",func)

#######
### Same example that the one that does not work at the begining of this mail
###
kml(dn)

--- 8< --------------------------

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to