Skip to content

Commit

Permalink
simplify operator interface
Browse files Browse the repository at this point in the history
  • Loading branch information
jakobbossek committed Apr 14, 2015
1 parent e730397 commit 0b77e6f
Show file tree
Hide file tree
Showing 9 changed files with 34 additions and 53 deletions.
5 changes: 3 additions & 2 deletions R/generateOffspring.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,10 +25,11 @@ generateOffspring = function(matingPool, objective.fun, control, opt.path) {

for (i in 1:n.offspring) {
parents = parentSelector(matingPool)
child = recombinator(parents)
# pass just the individuals and get a single individual
child = recombinator(parents$individuals)
mutator.control = mutationStrategyAdaptor(mutator.control, opt.path)
# pass just the individual and get a single individual
child = mutator(child, mutator.control)
child = child$individuals
offspring[[i]] = child
}
offspring = correctBounds(offspring, par.set, n.params)
Expand Down
14 changes: 5 additions & 9 deletions R/mutator.bitflip.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,15 +13,11 @@ makeBitFlipMutator = function(mutator.flip.prob = 0.1) {
defaults = list(mutator.flip.prob = mutator.flip.prob)
mutatorCheck(defaults)

mutator = function(setOfIndividuals, control = defaults) {
inds = setOfIndividuals$individuals
n = length(inds)
n.params = length(inds[[1]])
for (i in seq(n)) {
do.mutate = runif(n.params) < control$mutator.flip.prob
setOfIndividuals$individuals[[i]][do.mutate] = 1 - setOfIndividuals$individuals[[i]][do.mutate]
}
return(setOfIndividuals)
mutator = function(ind, control = defaults) {
n.params = length(ind)
do.mutate = runif(n.params) < control$mutator.flip.prob
ind[do.mutate] = 1 - ind[do.mutate]
return(ind)
}

makeMutator(
Expand Down
18 changes: 6 additions & 12 deletions R/mutator.gauss.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,18 +20,12 @@ makeGaussMutator = function(mutator.gauss.prob = 1L, mutator.gauss.sd = 0.05) {
defaults = list(mutator.gauss.prob = mutator.gauss.prob, mutator.gauss.sd = mutator.gauss.sd)
mutatorCheck(defaults)

mutator = function(setOfIndividuals, control = defaults) {
inds = setOfIndividuals$individuals
n.params = length(inds[[1]])
n = length(inds)

for (i in seq(n)) {
idx = which(runif(n.params) < control$mutator.gauss.prob)
mut = rnorm(length(idx), mean = 0, sd = control$mutator.gauss.sd)
inds[[i]][idx] = inds[[i]][idx] + mut
}
setOfIndividuals$individuals = inds
return(setOfIndividuals)
mutator = function(ind, control = defaults) {
n.params = length(ind)
idx = which(runif(n.params) < control$mutator.gauss.prob)
mut = rnorm(length(idx), mean = 0, sd = control$mutator.gauss.sd)
ind[idx] = ind[idx] + mut
return(ind)
}

makeMutator(
Expand Down
26 changes: 10 additions & 16 deletions R/mutator.swap.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,22 +3,16 @@
#' @return [\code{ecr_mutator}]
#' @export
makeSwapMutator = function() {
mutator = function(setOfIndividuals, control = list()) {
inds = setOfIndividuals$individuals
n.params = length(inds[[1]])
n = length(inds)
for (i in seq(n)) {
pos = sample(1:n.params, size = 2)
pos1 = pos[1]
pos2 = pos[2]
#catf("Positions: %i, %i", pos1, pos2)
tmp = setOfIndividuals$individuals[[i]][pos1]
setOfIndividuals$individuals[[i]][pos1] = setOfIndividuals$individuals[[i]][pos2]
setOfIndividuals$individuals[[i]][pos2] = tmp
}
#FIXME: something is inconsistent here.
setOfIndividuals$individuals = unlist(setOfIndividuals$individuals)
return(setOfIndividuals)
mutator = function(ind, control = list()) {
n.params = length(ind)
pos = sample(1:n.params, size = 2)
pos1 = pos[1]
pos2 = pos[2]
#catf("Positions: %i, %i", pos1, pos2)
tmp = ind[pos1]
ind[pos1] = ind[pos2]
ind[pos2] = tmp
return(ind)
}

makeMutator(
Expand Down
9 changes: 4 additions & 5 deletions R/recombinator.crossover.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,16 +3,15 @@
#' @return [\code{ecr_recombinator}]
#' @export
makeCrossoverRecombinator = function() {
recombinator = function(setOfIndividuals, control = list()) {
parents = setOfIndividuals$individuals
parent1 = parents[[1]]
parent2 = parents[[2]]
recombinator = function(inds, control = list()) {
parent1 = inds[[1]]
parent2 = inds[[2]]
n = length(parent1)
# at least one allele of each parent should be contained
idx = sample(0:n, size = 1L)
child = parent1
child[idx:n] = parent2[idx:n]
makePopulation(child)
return(child)
}

makeRecombinator(
Expand Down
6 changes: 2 additions & 4 deletions R/recombinator.intermediate.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,13 @@
#' @return [\code{ecr_recombinator}]
#' @export
makeIntermediateRecombinator = function() {
recombinator = function(setOfIndividuals, control = list()) {
inds = setOfIndividuals$individuals
recombinator = function(inds, control = list()) {
n = length(inds[[1]])
child = rep(0, n)
for (i in 1:length(inds)) {
child = child + inds[[i]]
}
child = child / length(inds)
makePopulation(child)
return(child / length(inds))
}

makeRecombinator(
Expand Down
5 changes: 2 additions & 3 deletions R/recombinator.null.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,8 @@
#' @return [\code{ecr_recombinator}]
#' @export
makeNullRecombinator = function() {
recombinator = function(setOfIndividuals, control=list()) {
child = list(setOfIndividuals$individuals[[1]])
makePopulation(child)
recombinator = function(inds, control=list()) {
return(inds[[1L]])
}

makeRecombinator(
Expand Down
4 changes: 2 additions & 2 deletions inst/examples/smoof_example.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,15 +39,15 @@ myMonitorStep = function(envir = parent.frame()) {
myMonitor = makeMonitor(step = myMonitorStep)

# generate objective function
obj.fun = makeRastriginFunction(dimensions = 3L)
obj.fun = makeRastriginFunction(dimensions = 1L)

# initialize control object
control = setupECRControl(
n.population = 20L,
n.offspring = 5L,
survival.strategy = "plus",
representation = "float",
n.params = 3L,
n.params = 1L,
monitor = myMonitor,
stopping.conditions = setupStoppingConditions(max.iter = 25L)
)
Expand Down
Binary file modified tests/testthat/Rplots.pdf
Binary file not shown.

0 comments on commit 0b77e6f

Please sign in to comment.