Skip to content

Commit

Permalink
Using a dedicated environment for globals (#24)
Browse files Browse the repository at this point in the history
  • Loading branch information
wleoncio committed Apr 10, 2024
1 parent 55d302a commit 5deadcf
Show file tree
Hide file tree
Showing 3 changed files with 31 additions and 32 deletions.
19 changes: 9 additions & 10 deletions R/globals.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,10 @@
COUNTS <- array(0, dim = c(100, 100, 100))
SUMCOUNTS <- array(0, dim = c(100, 100))
PARTITION <- array(1, dim = 100)
POP_LOGML <- array(1, dim = 100)
LOGDIFF <- array(1, dim = c(100, 100))
# If handling globas break, try other ideas from
# https://stackoverflow.com/a/65252740/1169233
baps.globals <- new.env(parent = emptyenv())

utils::globalVariables(
c("PARTITION", "COUNTS", "SUMCOUNTS", "LOGDIFF", "POP_LOGML", "GAMMA_LN")
)
assign("COUNTS", array(0, dim = c(0, 0, 0)), envir = baps.globals)
assign("SUMCOUNTS", array(0, dim = c(0, 0)), envir = baps.globals)
assign("PARTITION", array(1, dim = 0), envir = baps.globals)
assign("POP_LOGML", array(1, dim = 0), envir = baps.globals)
assign("LOGDIFF", array(1, dim = c(0, 0)), envir = baps.globals)
# If handling globas break, try other ideas from
# https://stackoverflow.com/a/65252740/1169233 and
# https://stackoverflow.com/questions/12598242/
15 changes: 7 additions & 8 deletions R/indMix.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@ indMix <- function(c, npops, counts = NULL, sumcounts = NULL, max_iter = 100L, d
# Input npops is not used if called by greedyMix or greedyPopMix.

logml <- 1
clearGlobalVars()

noalle <- c$noalle
rows <- c$rows
Expand Down Expand Up @@ -94,16 +93,16 @@ indMix <- function(c, npops, counts = NULL, sumcounts = NULL, max_iter = 100L, d
counts <- sumcounts_counts_logml$counts
logml <- sumcounts_counts_logml$logml

PARTITION <- zeros(ninds, 1)
assign("PARTITION", zeros(ninds, 1), baps.globals)
for (i in seq_len(ninds)) {
apu <- rows[i]
PARTITION[i] <- initialPartition[apu[1]]
baps.globals$PARTITION[i] <- initialPartition[apu[1]]
}

COUNTS <- counts
SUMCOUNTS <- sumcounts
POP_LOGML <- computePopulationLogml(seq_len(npops), adjprior, priorTerm)
LOGDIFF <- repmat(-Inf, c(ninds, npops))
assign("COUNTS", counts, baps.globals)
assign("SUMCOUNTS", sumcounts, baps.globals)
assign("POP_LOGML", computePopulationLogml(seq_len(npops), adjprior, priorTerm), baps.globals)
assign("LOGDIFF", matrix(-Inf, nrow = ninds, ncol = npops), baps.globals)

# PARHAAN MIXTURE-PARTITION ETSIMINEN
nRoundTypes <- 7
Expand Down Expand Up @@ -147,7 +146,7 @@ indMix <- function(c, npops, counts = NULL, sumcounts = NULL, max_iter = 100L, d
muutosNyt <- 0

for (ind in inds) {
i1 <- PARTITION[ind]
i1 <- baps.globals$PARTITION[ind]
muutokset_diffInCounts <- greedyMix_muutokset$new()
muutokset_diffInCounts <- muutokset_diffInCounts$laskeMuutokset(
ind, rows, data, adjprior, priorTerm
Expand Down
29 changes: 15 additions & 14 deletions R/laskeMuutokset12345.R
Original file line number Diff line number Diff line change
Expand Up @@ -343,10 +343,10 @@ greedyMix_muutokset <- R6Class(
#' @param priorTerm priorTerm
laskeMuutokset = function(ind, globalRows, data, adjprior, priorTerm) {
npops <- size(COUNTS, 3)
muutokset <- LOGDIFF[ind, ]
muutokset <- baps.globals$LOGDIFF[ind, ]

i1 <- PARTITION[ind]
i1_logml <- POP_LOGML[i1]
i1 <- baps.globals$PARTITION[ind]
i1_logml <- baps.globals$POP_LOGML[i1]
muutokset[i1] <- 0

if (is.null(dim(globalRows))) {
Expand All @@ -355,29 +355,30 @@ greedyMix_muutokset <- R6Class(
rows <- globalRows[ind, 1]:globalRows[ind, 2]
}
diffInCounts <- computeDiffInCounts(
rows, size(COUNTS, 1), size(COUNTS, 2), data
)
rows, size(baps.globals$COUNTS, 1), size(baps.globals$COUNTS, 2), data
diffInSumCounts <- colSums(diffInCounts)
COUNTS[, , i1] <- COUNTS[, , i1] - diffInCounts
SUMCOUNTS[i1, ] <- SUMCOUNTS[i1, ] - diffInSumCounts
new_i1_logml <- computePopulationLogml(i1, adjprior, priorTerm)
COUNTS[, , i1] <- COUNTS[, , i1] + diffInCounts
SUMCOUNTS[i1, ] <- SUMCOUNTS[i1, ] + diffInSumCounts
browser() # TEMP. Tip: browserText()
baps.globals$COUNTS[, , i1] <- baps.globals$COUNTS[, , i1] - diffInCounts
baps.globals$SUMCOUNTS[i1, ] <- baps.globals$SUMCOUNTS[i1, ] - diffInSumCounts
baps.globals$COUNTS[, , i1] <- baps.globals$COUNTS[, , i1] + diffInCounts
baps.globals$SUMCOUNTS[i1, ] <- baps.globals$SUMCOUNTS[i1, ] + diffInSumCounts

i2 <- matlab2r::find(muutokset == -Inf) # Etsit��n populaatiot jotka muuttuneet viime kerran j�lkeen. (Searching for populations that have changed since the last time)
i2 <- setdiff(i2, i1)
i2_logml <- POP_LOGML[i2]
i2_logml <- baps.globals$POP_LOGML[i2]

ni2 <- length(i2)

COUNTS[, , i2] <- COUNTS[, , i2] + repmat(diffInCounts, c(1, 1, ni2))
SUMCOUNTS[i2, ] <- SUMCOUNTS[i2, ] + repmat(diffInSumCounts, c(ni2, 1))
new_i2_logml <- computePopulationLogml(i2, adjprior, priorTerm)
COUNTS[, , i2] <- COUNTS[, , i2] - repmat(diffInCounts, c(1, 1, ni2))
SUMCOUNTS[i2, ] <- SUMCOUNTS[i2, ] - repmat(diffInSumCounts, c(ni2, 1))
baps.globals$COUNTS[, , i2] <- baps.globals$COUNTS[, , i2] + repmat(diffInCounts, c(1, 1, ni2))
baps.globals$SUMCOUNTS[i2, ] <- baps.globals$SUMCOUNTS[i2, ] + repmat(diffInSumCounts, c(ni2, 1))
baps.globals$COUNTS[, , i2] <- baps.globals$COUNTS[, , i2] - repmat(diffInCounts, c(1, 1, ni2))
baps.globals$SUMCOUNTS[i2, ] <- baps.globals$SUMCOUNTS[i2, ] - repmat(diffInSumCounts, c(ni2, 1))

muutokset[i2] <- new_i1_logml - i1_logml + new_i2_logml - i2_logml
LOGDIFF[ind, ] <- muutokset
baps.globals$LOGDIFF[ind, ] <- muutokset
return(list(muutokset = muutokset, diffInCounts = diffInCounts))
},
#' @param i1 i1
Expand Down

0 comments on commit 5deadcf

Please sign in to comment.