From cd24b73d102997dc903dc477e2077614b0da39e8 Mon Sep 17 00:00:00 2001
From: Mauricio Zambrano-Bigiarini <hzambran@users.noreply.github.com>
Date: Tue, 6 Nov 2012 13:02:45 +0000
Subject: [PATCH] hydroPSO.Rd: improved documentation. hydroPSO.R: revised
 regrouping (still ongoing)

---
 DESCRIPTION     |  4 ++--
 R/PSO_v2012.R   | 56 ++++++++++++++++++++++++-------------------------
 man/hydroPSO.Rd |  8 +++----
 3 files changed, 33 insertions(+), 35 deletions(-)

diff --git a/DESCRIPTION b/DESCRIPTION
index 5b25060..969e8f1 100755
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -1,8 +1,8 @@
 Package: hydroPSO
 Type: Package
 Title: Model-Independent Particle Swarm Optimisation for Environmental Models
-Version: 0.1-58-17
-Date: 2012-10-31
+Version: 0.1-58-19
+Date: 2012-11-06
 Authors@R: c(person("Mauricio", "Zambrano-Bigiarini", email="mzb.devel@gmail.com", role=c("aut","cre")), person("Rodrigo", "Rojas", email="Rodrigo.RojasMujica@gmail.com", role=c("ctb")) )
 Maintainer: Mauricio Zambrano-Bigiarini <mzb.devel@gmail.com>
 Description: This package implements a state-of-the-art version of the Particle Swarm Optimisation (PSO) algorithm (SPSO-2011 and SPSO-2007 capable), with a special focus on the calibration of environmental models. hydroPSO is model-independent, allowing the user to easily interface any model code with the calibration engine (PSO). It includes a series of controlling options and PSO variants to fine-tune the performance of the calibration engine to different calibration problems. An advanced sensitivity analysis function together with user-friendly plotting summaries facilitate the interpretation and assessment of the calibration results. Bugs reports/comments/questions are very welcomed.
diff --git a/R/PSO_v2012.R b/R/PSO_v2012.R
index ce08141..7521a52 100755
--- a/R/PSO_v2012.R
+++ b/R/PSO_v2012.R
@@ -1115,6 +1115,9 @@ ComputeSwarmRadiusAndDiameter <- function(x, gbest, Lmax, MinMax, pbest.fit) {
 #          local best
 ################################################################################
 RegroupingSwarm <- function(x, 
+                            xini.type, 
+                            v, 
+                            vini.type,
                             gbest, 
                             x.Range,
                             Lmax,
@@ -1132,25 +1135,6 @@ RegroupingSwarm <- function(x,
   #rf <- 6/(5*RG.thr) # Evers & Ghalia
   #rf <- (1/RG.thr)/2 # MZB
   
-##   # Removing possible attributes
-##  gbest      <- as.numeric( gbest ) 
-##  x.min.rng  <- as.numeric( x.Range[ ,1] )
-##  x.max.rng  <- as.numeric( x.Range[ ,2] )
-##  
-##  xmin <- x.min.rng + rf*abs(x.min.rng-gbest)
-##  xmax <- x.max.rng - rf*abs(x.max.rng-gbest)
-##  x.MinMax <- cbind(xmin, xmax)
-##  
-##  x <- InitializateX(npart, x.MinMax, x.ini.type="lhs")
-##  #x <- x+gbest
-##  
-##   # Maximum length of the parameter space in each dimension
-##  Lmax <- x.max.rng - x.min.rng 
-##  Lnew <- Lmax
-
-##  # name of each parameter  
-##  param.IDs <- row.names(x.Range)
-  
   # name of each parameter  
   param.IDs <- row.names(x.Range)
 
@@ -1184,16 +1168,23 @@ RegroupingSwarm <- function(x,
     # If needed, Clamping the particle positions to the minimum value 
     x[part, ] <- pmax(x[part,], x.min.rng)
   } # FOR end
-
+  
+  # Defining the new boundaries
+  xmin <- gbest - 0.5*Lnew
+  xmax <- gbest + 0.5*Lnew
+  xMinMax <- cbind(xmin, xmax)
+  
+  v <- InitializateV(npart=npart, x.MinMax=xMinMax, v.ini.type=vini.type, Xini=x)
   
   # Relative change achieved in each dimension
   rel.change        <- (Lnew-Lmax)/Lmax
   names(rel.change) <- param.IDs 
 
-  out      <- list(2)
+  out      <- list(3)
   out[[1]] <- x
-  out[[2]] <- Lnew
-  names(out)  <- c("X", "Lnew") 
+  out[[2]] <- v
+  out[[3]] <- Lnew
+  names(out)  <- c("X", "V", "Lnew") 
   
   return(out) 
   
@@ -2612,7 +2603,7 @@ hydroPSO <- function(
 		    "   Gbest:", formatC( gbest.fit, format="E", digits=digits, flag=" "), 
 		    "   Gbest_rate:", format( round(gbest.fit.rate*100, 2), width=6, nsmall=2, justify="left"), "%",
 		    "   Iter_best_fit:", formatC(pbest.fit.iter, format="E", digits=digits, flag=" "),               
-		    "   nSwarm_Radius:", formatC(NormSwarmRadius, format="E", digits=digits, flag=" "),
+		    "   nSwarm_Radius:", formatC(NormSwarmRadius, format="E", digits=2, flag=" "),
 		    "   |g-mean(p)|/mean(p):", format( round(GPbest.fit.rate*100, 2), width=6, nsmall=2, justify="left"), "%" )
 
       ##########################################################################  
@@ -2639,14 +2630,20 @@ hydroPSO <- function(
 	  if (verbose) message("[ Re-grouping particles in the swarm (iter: ", iter, ") ... ]")
 
 	  tmp <- RegroupingSwarm(x=X, 
-				 gbest= X.best.part[gbest.pos, ], 
+				 xini.type=Xini.type, 
+                                 v=V, 
+                                 vini.type=Vini.type,                            
+	                         gbest= X.best.part[gbest.pos, ], 
 				 x.Range=X.Boundaries,
 				 #x.Range=X.Boundaries.current,
 				 Lmax=Lmax,
 				 RG.thr=RG.thr,
 				 RG.r=RG.r) 
 
-	  X    <- tmp[["X"]]
+	  X <- tmp[["X"]]
+	  V <- tmp[["V"]]
+	  
+	  Lmax <- tmp[["Lnew"]]
 	  
 #	  if (topology %in% c("gbest", "random") ) {
 #	    X[gbest.pos,] <- x.bak
@@ -2661,9 +2658,6 @@ hydroPSO <- function(
 	    gbest.pos     <- gbest.pos.bak
 	  } # IF end
 
-#	  V <- InitializateV(npart=npart, x.MinMax=X.Boundaries,
-#	                     v.ini.type=Vini.type, Xini=X)
-
           pbest.fit            <- rep(fn.worst.value, npart)     
           pbest.fit.iter       <- fn.worst.value
           pbest.fit.iter.prior <- fn.worst.value*2
@@ -2672,6 +2666,10 @@ hydroPSO <- function(
           gbest.fit.iter  <- rep(gbest.fit, maxit)
           gbest.fit.prior <- gbest.fit
           gbest.pos       <- 1
+                  
+          gbest.fit     <- gbest.fit.bak
+          gbest.pos     <- gbest.pos.bak
+          X[gbest.pos,] <- x.bak
 
 	  GPbest.fit.rate <- +Inf              
 	  if (MinMax=="max") {
diff --git a/man/hydroPSO.Rd b/man/hydroPSO.Rd
index 0fa0b58..67d923a 100755
--- a/man/hydroPSO.Rd
+++ b/man/hydroPSO.Rd
@@ -135,7 +135,7 @@ numeric, absolute convergence tolerance. The algorithm stops if \code{gbest <= a
 By default it is set to \code{-Inf} or \code{+Inf} for minimisation or maximisation problems, respectively
 }
   \item{reltol}{
-numeric, relative convergence tolerance. The algorithm stops if the absolute difference between the best \sQuote{personal best} in the current iteration and the best \sQuote{personal best} in the previous iteration is lower or equal to \code{reltol}. Defaults to \code{sqrt(.Machine$double.eps)}, typically, about 1e-8\cr
+numeric, relative convergence tolerance. The algorithm stops if the absolute difference between the best \sQuote{personal best} in the current iteration and the best \sQuote{personal best} in the previous iteration is less or equal to \code{reltol}. Defaults to \code{sqrt(.Machine$double.eps)}, typically, about 1e-8\cr
 If \code{reltol} is set to \code{0}, this stopping criterion is not used 
 }
   \item{Xini.type}{
@@ -348,9 +348,9 @@ three-element vector containing the number of function evaluations, number of it
 \item{convergence}{
 integer code where \code{0} indicates that the algorithm terminated by reaching the absolute tolerance, otherwise:
 \describe{
- \item{\code{1}:}{relative tolerance reached}
- \item{\code{2}:}{maximum number of function evaluations reached}
- \item{\code{3}:}{maximum number of iterations reached}
+ \item{1}{relative tolerance reached}
+ \item{2}{maximum number of function evaluations reached}
+ \item{3}{maximum number of iterations reached}
 }
 }
 \item{message}{character string giving human-friendly information about \code{convergence}
-- 
GitLab