diff --git a/R/greedyMix.R b/R/greedyMix.R index 1826d50..8923eab 100644 --- a/R/greedyMix.R +++ b/R/greedyMix.R @@ -27,7 +27,7 @@ #' data <- system.file("extdata", "FASTA_clustering_haploid.fasta", package = "rBAPS") #' greedyMix(data, "fasta") greedyMix <- function( - data, format, partitionCompare = NULL, ninds = NULL, npops = 1L, + data, format, partitionCompare = NULL, ninds = 1L, npops = 1L, counts = NULL, sumcounts = NULL, max_iter = 100L, alleleCodes = NULL, inp = NULL, popnames = NULL, fixedK = FALSE, verbose = FALSE ) { @@ -52,6 +52,8 @@ greedyMix <- function( # Generating partition summary =============================================== + ekat <- seq(1L, c[["rowsFromInd"]], ninds * c[["rowsFromInd"]]) # ekat = (1:rowsFromInd:ninds*rowsFromInd)'; + c[["rows"]] <- c(ekat, ekat + c[["rowsFromInd"]] - 1L) # c.rows = [ekat ekat+rowsFromInd-1] logml_npops_partitionSummary <- indMixWrapper(c, npops, counts, sumcounts, max_iter, fixedK, verbose); logml <- logml_npops_partitionSummary[["logml"]] npops <- logml_npops_partitionSummary[["npops"]] @@ -59,10 +61,11 @@ greedyMix <- function( # Generating output object =================================================== out <- list( - "alleleCodes" = alleleCodes, "adjprior" = c[["adjprior"]], "popnames" = popnames, - "rowsFromInd" = c[["rowsFromInd"]], "data" = data, "npops" = npops, - "noalle" = c[["noalle"]], "mixtureType" = "mix", "logml" = logml - ) + "alleleCodes" = alleleCodes, "adjprior" = c[["adjprior"]], + "popnames" = popnames, "rowsFromInd" = c[["rowsFromInd"]], + "data" = c[["data"]], "npops" = npops, "noalle" = c[["noalle"]], + "mixtureType" = "mix", "logml" = logml + ) if (logml == 1) { return(out) } diff --git a/R/indMix.R b/R/indMix.R index 394eef2..30e21e6 100644 --- a/R/indMix.R +++ b/R/indMix.R @@ -145,8 +145,8 @@ indMix <- function(c, npops, counts = NULL, sumcounts = NULL, max_iter = 100L, d if (kokeiltu[round] == 1) { # Askelta kokeiltu viime muutoksen j�lkeen } else if (round == 0 | round == 1) { # Yksil�n siirt�minen toiseen populaatioon. inds <- seq_len(ninds) - aputaulu <- cbind(inds, rand(ninds, 1)) - aputaulu <- sortrows(aputaulu, 2) + aputaulu <- cbind(t(inds), rand(ninds, 1)) + aputaulu <- matrix(sortrows(aputaulu, 2), nrow = nrow(aputaulu)) inds <- t(aputaulu[, 1]) muutosNyt <- 0 diff --git a/R/laskeMuutokset12345.R b/R/laskeMuutokset12345.R index df9bf11..78d2276 100644 --- a/R/laskeMuutokset12345.R +++ b/R/laskeMuutokset12345.R @@ -349,12 +349,15 @@ greedyMix_muutokset <- R6Class( i1_logml <- POP_LOGML[i1] muutokset[i1] <- 0 - rows <- globalRows[ind, 1]:globalRows[ind, 2] + if (is.null(dim(globalRows))) { + rows <- globalRows[1]:globalRows[2] + } else { + rows <- globalRows[ind, 1]:globalRows[ind, 2] + } diffInCounts <- computeDiffInCounts( rows, size(COUNTS, 1), size(COUNTS, 2), data ) diffInSumCounts <- colSums(diffInCounts) - COUNTS[, , i1] <- COUNTS[, , i1] - diffInCounts SUMCOUNTS[i1, ] <- SUMCOUNTS[i1, ] - diffInSumCounts new_i1_logml <- computePopulationLogml(i1, adjprior, priorTerm)