Skip to content
Snippets Groups Projects
Commit 475351ad authored by Mauricio Zambrano-Bigiarini's avatar Mauricio Zambrano-Bigiarini
Browse files

updated: NEWS, hydroPSO.Rd and hydroPSO.R, going towards SPSO2011 capable

parent 4ea65323
No related branches found
No related tags found
No related merge requests found
...@@ -15,6 +15,16 @@ NEWS/ChangeLog for hydroPSO ...@@ -15,6 +15,16 @@ NEWS/ChangeLog for hydroPSO
-) argument 'npart', when missing its value depends on the value of the 'method' argument: -) argument 'npart', when missing its value depends on the value of the 'method' argument:
method == 'spso2007' => npart=10+2*[sqrt(n)] method == 'spso2007' => npart=10+2*[sqrt(n)]
method != 'spso2007' => npart=40 method != 'spso2007' => npart=40
-) in the documentation, default values are now mentioned for each argument of 'control'.
o Results obtained when running 'hydroPSO' >= 0.1-59 with default settings WILL BE DIFFERENT from those obtained with 'hydroPSO' <= 0.1-58, due to the following changes in default values:
-) npart : 10+2*[sqrt(n)] -> 40
-) Vini.type : 'lhs2007' -> 'random2011'
-) boundary.wall: 'reflecting' -> 'absorbing'
-) TVc1.type : 'non-linear' -> 'linear' (no effect, because 'use.TVc1=FALSE' by default)
-) TVc2.type : 'non-linear' -> 'linear' (no effect, because 'use.TVc2=FALSE' by default)
-) TVlambda.type: 'non-linear' -> 'linear' (no effect, because 'use.TVlambda=FALSE' by default)
0.1-58 14-Sep-2012 0.1-58 14-Sep-2012
o 'hydroPSO' : -) 'random.update' is now ONLY used when 'best.update="async". In hydroPSO 0.1-57 'random.update' was set to TRUE o 'hydroPSO' : -) 'random.update' is now ONLY used when 'best.update="async". In hydroPSO 0.1-57 'random.update' was set to TRUE
......
...@@ -934,17 +934,18 @@ InitializateV <- function(npart, param.IDs, x.MinMax, v.ini.type, Xini) { ...@@ -934,17 +934,18 @@ InitializateV <- function(npart, param.IDs, x.MinMax, v.ini.type, Xini) {
# Rows = 'npart'; # Rows = 'npart';
# Columns = 'n' (Dimension of the Solution Space) # Columns = 'n' (Dimension of the Solution Space)
# Random bounded values are assigned to each dimension # Random bounded values are assigned to each dimension
if ( v.ini.type=="random2007" ) { if ( v.ini.type=="random2011" ) {
V <- ( Random.Bounded.Matrix(npart, x.MinMax) - Xini)/2 V <- matrix(runif(n*npart, min=as.vector(x.MinMax[,1]-Xini), max=as.vector(x.MinMax[,2]-Xini)), nrow=npart, ncol=n)
} else if ( v.ini.type=="lhs2007" ) { } else if ( v.ini.type=="lhs2011" ) {
V <- ( rLHS(npart, x.MinMax) - Xini)/2 V <- rLHS(npart, x.MinMax - cbind(x.MinMax[,1]-Xini, x.MinMax[,2]-Xini) )
} else if ( v.ini.type=="zero" ) { } else if ( v.ini.type=="random2007" ) {
V <- matrix(0, ncol=n, nrow=npart, byrow=TRUE) V <- ( Random.Bounded.Matrix(npart, x.MinMax) - Xini ) / 2
} else if ( v.ini.type=="random2011" ) { } else if ( v.ini.type=="lhs2007" ) {
V <- Random.Bounded.Matrix(npart, (x.MinMax - cbind(Xini, Xini) ) ) V <- ( rLHS(npart, x.MinMax) - Xini ) / 2
} else if ( v.ini.type=="lhs2011" ) { } else if ( v.ini.type=="zero" ) {
V <- rLHS(npart, x.MinMax - cbind(Xini, Xini) ) V <- matrix(0, ncol=n, nrow=npart, byrow=TRUE)
} } # ELSE end
colnames(V) <- param.IDs colnames(V) <- param.IDs
rownames(V) <- paste("Part", 1:npart, sep="") rownames(V) <- paste("Part", 1:npart, sep="")
...@@ -1543,18 +1544,18 @@ hydroPSO <- function( ...@@ -1543,18 +1544,18 @@ hydroPSO <- function(
abstol= NULL, abstol= NULL,
reltol=sqrt(.Machine$double.eps), reltol=sqrt(.Machine$double.eps),
Xini.type=c("lhs", "random"), Xini.type=c("lhs", "random"),
Vini.type=c("lhs2007", "random2007", "zero", "lhs2011", "random2011"), Vini.type=c("random2011", "lhs2011", "random2007", "lhs2007", "zero"),
best.update=c("sync", "async"), best.update=c("sync", "async"),
random.update=TRUE, random.update=TRUE,
boundary.wall=c("reflecting", "damping", "absorbing", "invisible"), boundary.wall=c("absorbing", "reflecting", "damping", "invisible"),
topology=c("random", "gbest", "lbest", "vonNeumann"), K=3, topology=c("random", "gbest", "lbest", "vonNeumann"), K=3,
iter.ini=0, # only used when 'topology=lbest' iter.ini=0, # only used when 'topology=lbest'
ngbest=4, # only used when 'method=ipso' ngbest=4, # only used when 'method=ipso'
use.IW = TRUE, IW.type=c("linear", "non-linear", "runif", "aiwf", "GLratio"), IW.w=1/(2*log(2)), IW.exp= 1, use.IW = TRUE, IW.w=1/(2*log(2)), IW.type=c("linear", "non-linear", "runif", "aiwf", "GLratio"), IW.exp= 1,
use.TVc1= FALSE, TVc1.type=c("non-linear", "linear", "GLratio"), TVc1.rng= c(1.28, 1.05), TVc1.exp= 1.5, use.TVc1= FALSE, TVc1.rng= c(1.28, 1.05), TVc1.type=c("linear", "non-linear", "GLratio"), TVc1.exp= 1.5,
use.TVc2= FALSE, TVc2.type=c("non-linear", "linear"), TVc2.rng= c(1.05, 1.28), TVc2.exp= 1.5, use.TVc2= FALSE, TVc2.rng= c(1.05, 1.28), TVc2.type=c("linear", "non-linear"), TVc2.exp= 1.5,
use.TVlambda=FALSE, TVlambda.type=c("non-linear", "linear"), TVlambda.rng= c(1, 0.25), TVlambda.exp= 1, use.TVlambda=FALSE, TVlambda.rng= c(1, 0.25), TVlambda.type=c("linear", "non-linear"), TVlambda.exp= 1,
use.RG = FALSE, RG.thr= 1.1e-4, RG.r= 0.8, RG.miniter= 5, # RG.r not used in reagrouping use.RG = FALSE, RG.thr= 1.1e-4, RG.r= 0.8, RG.miniter= 5, # RG.r not used in reagrouping
plot=FALSE, plot=FALSE,
...@@ -1586,10 +1587,13 @@ hydroPSO <- function( ...@@ -1586,10 +1587,13 @@ hydroPSO <- function(
drty.out <- con[["drty.out"]] drty.out <- con[["drty.out"]]
param.ranges <- con[["param.ranges"]] param.ranges <- con[["param.ranges"]]
digits <- con[["digits"]] digits <- con[["digits"]]
#npart <- ifelse(is.na(con[["npart"]]),
# ifelse(method %in% c("spso2007", "spso2011"),
# ifelse(method=="spso2007", ceiling(10+2*sqrt(n)), 40),
# 40),
# con[["npart"]] )
npart <- ifelse(is.na(con[["npart"]]), npart <- ifelse(is.na(con[["npart"]]),
ifelse(method %in% c("spso2007", "spso2011"), ifelse(method=="spso2007", ceiling(10+2*sqrt(n)), 40),
ifelse(method=="spso2007", ceiling(10+2*sqrt(n)), 40),
40),
con[["npart"]] ) con[["npart"]] )
maxit <- con[["maxit"]] maxit <- con[["maxit"]]
maxfn <- con[["maxfn"]] maxfn <- con[["maxfn"]]
...@@ -1742,10 +1746,10 @@ hydroPSO <- function( ...@@ -1742,10 +1746,10 @@ hydroPSO <- function(
} # IF end } # IF end
} # IF end } # IF end
if (Vini.type=="lhs") { if (Vini.type %in% c("lhs2011", "lhs2007")) {
if ( is.na( match("lhs", installed.packages()[,"Package"] ) ) ) { if ( is.na( match("lhs", installed.packages()[,"Package"] ) ) ) {
warning("[ Package 'lhs' is not installed => Vini.type='random' ]") warning("[ Package 'lhs' is not installed => Vini.type='random2011' ]")
Vini.type <- "random" Vini.type <- "random2011"
} # IF end } # IF end
} # IF end } # IF end
...@@ -1979,10 +1983,10 @@ hydroPSO <- function( ...@@ -1979,10 +1983,10 @@ hydroPSO <- function(
if (use.TVc1) { if (use.TVc1) {
writeLines(c("use.TVc1 :", use.TVc1), PSOparam.TextFile, sep=" ") writeLines(c("use.TVc1 :", use.TVc1), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
writeLines(c("TVc1.type :", TVc1.type), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile)
writeLines(c("TVc1.rng :", TVc1.rng), PSOparam.TextFile, sep=" ") writeLines(c("TVc1.rng :", TVc1.rng), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
writeLines(c("TVc1.type :", TVc1.type), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile)
writeLines(c("TVc1.exp :", TVc1.exp), PSOparam.TextFile, sep=" ") writeLines(c("TVc1.exp :", TVc1.exp), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
} else { } else {
...@@ -1992,10 +1996,10 @@ hydroPSO <- function( ...@@ -1992,10 +1996,10 @@ hydroPSO <- function(
if (use.TVc2) { if (use.TVc2) {
writeLines(c("use.TVc2 :", use.TVc2), PSOparam.TextFile, sep=" ") writeLines(c("use.TVc2 :", use.TVc2), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
writeLines(c("TVc2.type :", TVc2.type), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile)
writeLines(c("TVc2.rng :", TVc2.rng), PSOparam.TextFile, sep=" ") writeLines(c("TVc2.rng :", TVc2.rng), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
writeLines(c("TVc2.type :", TVc2.type), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile)
writeLines(c("TVc2.exp :", TVc2.exp), PSOparam.TextFile, sep=" ") writeLines(c("TVc2.exp :", TVc2.exp), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
} else { } else {
...@@ -2005,10 +2009,10 @@ hydroPSO <- function( ...@@ -2005,10 +2009,10 @@ hydroPSO <- function(
if (use.TVlambda) { if (use.TVlambda) {
writeLines(c("use.TVlambda :", use.TVlambda), PSOparam.TextFile, sep=" ") writeLines(c("use.TVlambda :", use.TVlambda), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
writeLines(c("TVlambda.type :", TVlambda.type), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile)
writeLines(c("TVlambda.rng :", TVlambda.rng), PSOparam.TextFile, sep=" ") writeLines(c("TVlambda.rng :", TVlambda.rng), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
writeLines(c("TVlambda.type :", TVlambda.type), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile)
writeLines(c("TVlambda.exp :", TVlambda.exp), PSOparam.TextFile, sep=" ") writeLines(c("TVlambda.exp :", TVlambda.exp), PSOparam.TextFile, sep=" ")
writeLines("", PSOparam.TextFile) writeLines("", PSOparam.TextFile)
} else { } else {
......
This diff is collapsed.
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment