pikaia_class Derived Type

type, public :: pikaia_class

Main class for using the Pikaia algorithm. INIT and SOLVE are the only public methods.


Inherits

type~~pikaia_class~~InheritsGraph type~pikaia_class pikaia_class mt19937 mt19937 type~pikaia_class->mt19937 rand

Components

Type Visibility Attributes Name Initial
integer, private :: n = 0
real(kind=wp), private, dimension(:), allocatable :: xl

lower bounds of x

real(kind=wp), private, dimension(:), allocatable :: xu

upper bound of x

real(kind=wp), private, dimension(:), allocatable :: del
integer, private :: np = 100
integer, private :: ngen = 500
integer, private :: nd = 5
real(kind=wp), private :: pcross = 0.85_wp
integer, private :: imut = 2
real(kind=wp), private :: pmuti = 0.005_wp

initial value of pmut

real(kind=wp), private :: pmutmn = 0.0005_wp
real(kind=wp), private :: pmutmx = 0.25_wp
real(kind=wp), private :: fdif = 1.0_wp
integer, private :: irep = 1
integer, private :: ielite = 1
integer, private :: ivrb = 0
real(kind=wp), private :: convergence_tol = 0.0001_wp
integer, private :: convergence_window = 20
integer, private :: iseed = 999
real(kind=wp), private :: initial_guess_frac = 0.1_wp
real(kind=wp), private :: pmut = -huge(1.0_wp)
real(kind=wp), private :: bestft = huge(1.0_wp)
real(kind=wp), private :: pmutpv = huge(1.0_wp)
type(mt19937), private :: rand

random number generator

procedure(pikaia_func), private, pointer :: user_f => null()

fitness function

procedure(iter_func), private, pointer :: iter_f => null()

reporting function (best member of population)


Type-Bound Procedures

procedure, public, non_overridable :: init => set_inputs

  • private subroutine set_inputs(me, n, xl, xu, f, status, iter_f, np, ngen, nd, pcross, pmutmn, pmutmx, pmut, imut, fdif, irep, ielite, ivrb, convergence_tol, convergence_window, initial_guess_frac, iseed)

    Author
    Jacob Williams

    Constructor for the pikaia_class. The routine must be called before the solve routine can be used.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(out) :: me

    pikaia class

    integer, intent(in) :: n

    the parameter space dimension, i.e., the number of adjustable parameters (size of the x vector).

    real(kind=wp), intent(in), dimension(n) :: xl

    vector of lower bounds for x

    real(kind=wp), intent(in), dimension(n) :: xu

    vector of upper bounds for x

    procedure(pikaia_func) :: f

    user-supplied scalar function of n variables, which must have the pikaia_func procedure interface. By convention, f should return higher values for more optimal parameter values (i.e., individuals which are more "fit"). For example, in fitting a function through data points, f could return the inverse of chi**2.

    integer, intent(out) :: status

    status output flag (0 if there were no errors)

    procedure(iter_func), optional :: iter_f

    user-supplied subroutine that will report the best solution for each generation. It must have the iter_func procedure interface. If not present, then it is not used. (note: this is independent of ivrb).

    integer, intent(in), optional :: np

    number of individuals in a population (default is 100)

    integer, intent(in), optional :: ngen

    maximum number of iterations

    integer, intent(in), optional :: nd

    number of significant digits (i.e., number of genes) retained in chromosomal encoding (default is 6).

    real(kind=wp), intent(in), optional :: pcross

    crossover probability; must be <= 1.0 (default is 0.85). If crossover takes place, either one or two splicing points are used, with equal probabilities

    real(kind=wp), intent(in), optional :: pmutmn

    minimum mutation rate; must be >= 0.0 (default is 0.0005)

    real(kind=wp), intent(in), optional :: pmutmx

    maximum mutation rate; must be <= 1.0 (default is 0.25)

    real(kind=wp), intent(in), optional :: pmut

    initial mutation rate; should be small (default is 0.005) (Note: the mutation rate is the probability that any one gene locus will mutate in any one generation.)

    integer, intent(in), optional :: imut

    mutation mode; 1/2/3/4/5 (default is 2). 1=one-point mutation, fixed rate. 2=one-point, adjustable rate based on fitness. 3=one-point, adjustable rate based on distance. 4=one-point+creep, fixed rate. 5=one-point+creep, adjustable rate based on fitness. 6=one-point+creep, adjustable rate based on distance.

    real(kind=wp), intent(in), optional :: fdif

    relative fitness differential; range from 0 (none) to 1 (maximum). (default is 1.0)

    integer, intent(in), optional :: irep

    reproduction plan; 1/2/3=Full generational replacement/Steady-state-replace-random/Steady- state-replace-worst (default is 3)

    integer, intent(in), optional :: ielite

    elitism flag; 0/1=off/on (default is 0) (Applies only to reproduction plans 1 and 2)

    integer, intent(in), optional :: ivrb

    printed output 0/1/2=None/Minimal/Verbose (default is 0)

    real(kind=wp), intent(in), optional :: convergence_tol

    convergence tolerance; must be > 0.0 (default is 0.0001)

    integer, intent(in), optional :: convergence_window

    convergence window; must be >= 0 This is the number of consecutive solutions within the tolerance for convergence to be declared (default is 20)

    real(kind=wp), intent(in), optional :: initial_guess_frac

    fraction of the initial population to set equal to the initial guess. Range from 0 (none) to 1.0 (all). (default is 0.1 or 10%).

    integer, intent(in), optional :: iseed

    random seed value; must be > 0 (default is 999)

procedure, public, non_overridable :: solve => solve_with_pikaia

  • private subroutine solve_with_pikaia(me, x, f, status)

    Author
    Jacob Williams

    Main pikaia wrapper used by the class.

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(inout), dimension(:) :: x
    real(kind=wp), intent(out) :: f
    integer, intent(out) :: status

procedure, public, non_overridable :: ff => func_wrapper

internal pikaia function (x:[0,1])

  • private subroutine func_wrapper(me, x, f)

    Author
    Jacob Williams

    Wrapper for the user's function that is used by the main pikaia routine The x input to this function comes from pikaia, and will be between [0,1].

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(in), dimension(:) :: x
    real(kind=wp), intent(out) :: f

procedure, public, non_overridable :: newpop

  • private subroutine newpop(me, oldph, newph, ifit, jfit, fitns, nnew)

    Replaces old population by new; recomputes fitnesses & ranks

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(inout), dimension(me%n,me%np) :: oldph
    real(kind=wp), intent(inout), dimension(me%n,me%np) :: newph
    integer, intent(out), dimension(me%np) :: ifit
    integer, intent(out), dimension(me%np) :: jfit
    real(kind=wp), intent(out), dimension(me%np) :: fitns
    integer, intent(out) :: nnew

procedure, public, non_overridable :: stdrep

  • private subroutine stdrep(me, ph, fits, oldph, fitns, ifit, jfit, nnew)

    Steady-state reproduction: insert offspring pair into population only if they are fit enough (replace-random if irep=2 or replace-worst if irep=3).

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(in), dimension(me%n,2) :: ph
    real(kind=wp), intent(in), dimension(2) :: fits
    real(kind=wp), intent(inout), dimension(me%n,me%np) :: oldph
    real(kind=wp), intent(inout), dimension(me%np) :: fitns
    integer, intent(inout), dimension(me%np) :: ifit
    integer, intent(inout), dimension(me%np) :: jfit
    integer, intent(out) :: nnew

procedure, public, non_overridable :: genrep

  • private subroutine genrep(me, ip, ph, newph)

    Full generational replacement: accumulate offspring into new population array

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    integer, intent(in) :: ip
    real(kind=wp), intent(in), dimension(me%n,2) :: ph
    real(kind=wp), intent(out), dimension(me%n,me%np) :: newph

procedure, public, non_overridable :: adjmut

  • private subroutine adjmut(me, oldph, fitns, ifit)

    Dynamical adjustment of mutation rate:

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(in), dimension(me%n,me%np) :: oldph
    real(kind=wp), intent(in), dimension(me%np) :: fitns
    integer, intent(in), dimension(me%np) :: ifit

procedure, public, non_overridable :: cross

  • private subroutine cross(me, gn1, gn2)

    breeds two parent chromosomes into two offspring chromosomes. breeding occurs through crossover. If the crossover probability test yields true (crossover taking place), either one-point or two-point crossover is used, with equal probabilities.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    integer, intent(inout), dimension(me%n*me%nd) :: gn1
    integer, intent(inout), dimension(me%n*me%nd) :: gn2

procedure, public, non_overridable :: encode

  • private subroutine encode(me, ph, gn)

    Encode phenotype parameters into integer genotype ph(k) are x,y coordinates [ 0 < x,y < 1 ]

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(in) :: me
    real(kind=wp), intent(in), dimension(me%n) :: ph
    integer, intent(out), dimension(me%n*me%nd) :: gn

procedure, public, non_overridable :: mutate

  • private subroutine mutate(me, gn)

    Introduces random mutation in a genotype. Mutations occur at rate pmut at all gene loci.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    integer, intent(inout), dimension(me%n*me%nd) :: gn

procedure, public, non_overridable :: decode

  • private subroutine decode(me, gn, ph)

    decode genotype into phenotype parameters ph(k) are x,y coordinates [ 0 < x,y < 1 ]

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(in) :: me
    integer, intent(in), dimension(me%n*me%nd) :: gn
    real(kind=wp), intent(out), dimension(me%n) :: ph

procedure, public, non_overridable :: select_parents

  • private subroutine select_parents(me, jfit, imom, idad)

    Selects two parents from the population, using roulette wheel algorithm with the relative fitnesses of the phenotypes as the "hit" probabilities.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    integer, intent(in), dimension(me%np) :: jfit
    integer, intent(out) :: imom
    integer, intent(out) :: idad

procedure, public, non_overridable :: report

  • private subroutine report(me, oldph, fitns, ifit, ig, nnew)

    Write generation report to standard output

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(in), dimension(me%n,me%np) :: oldph
    real(kind=wp), intent(in), dimension(me%np) :: fitns
    integer, intent(in), dimension(me%np) :: ifit
    integer, intent(in) :: ig
    integer, intent(in) :: nnew

procedure, public, non_overridable :: rnkpop

  • private subroutine rnkpop(me, arrin, indx, rank)

    Ranks initial population. Calls external sort routine to produce key index and rank order of input array arrin (which is not altered).

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(in), dimension(me%np) :: arrin
    integer, intent(out), dimension(me%np) :: indx
    integer, intent(out), dimension(me%np) :: rank

procedure, public, non_overridable :: pikaia

  • private subroutine pikaia(me, x, f, status)

    Optimization (maximization) of user-supplied "fitness" function over n-dimensional parameter space x using a basic genetic algorithm method.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me
    real(kind=wp), intent(inout), dimension(:) :: x

    Input - initial guess for solution vector. Output - the "fittest" (optimal) solution found, i.e., the solution which maximizes the fitness function.

    real(kind=wp), intent(out) :: f

    the (scalar) value of the fitness function at x

    integer, intent(out) :: status

    an indicator of the success or failure of the call to pikaia (0=success; non-zero=failure)

procedure, public, non_overridable :: rninit

  • private subroutine rninit(me)

    Initialize the random number generator with the input seed value.

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me

procedure, public, non_overridable :: urand

  • private function urand(me) result(r)

    Return the next pseudo-random deviate from a sequence which is uniformly distributed in the interval [0,1]

    Arguments

    Type IntentOptional Attributes Name
    class(pikaia_class), intent(inout) :: me

    Return Value real(kind=wp)

Source Code

    type,public :: pikaia_class

        !! Main class for using the Pikaia algorithm.
        !! INIT and SOLVE are the only public methods.

        private

        integer :: n = 0  !number of solution variables
        real(wp),dimension(:),allocatable :: xl    !! lower bounds of `x`
        real(wp),dimension(:),allocatable :: xu    !! upper bound of `x`
        real(wp),dimension(:),allocatable :: del

        !other solution inputs (with default values):
        integer  :: np                 = 100
        integer  :: ngen               = 500
        integer  :: nd                 = 5
        real(wp) :: pcross             = 0.85_wp
        integer  :: imut               = 2
        real(wp) :: pmuti              = 0.005_wp  !! initial value of `pmut`
        real(wp) :: pmutmn             = 0.0005_wp
        real(wp) :: pmutmx             = 0.25_wp
        real(wp) :: fdif               = 1.0_wp
        integer  :: irep               = 1
        integer  :: ielite             = 1
        integer  :: ivrb               = 0
        real(wp) :: convergence_tol    = 0.0001_wp
        integer  :: convergence_window = 20
        integer  :: iseed              = 999
        real(wp) :: initial_guess_frac = 0.1_wp

        !used internally:
        real(wp) :: pmut   = -huge(1.0_wp)
        real(wp) :: bestft = huge(1.0_wp)
        real(wp) :: pmutpv = huge(1.0_wp)

        type(mt19937) :: rand !! random number generator

        !user-supplied procedures:
        procedure(pikaia_func),pointer :: user_f => null()  !! fitness function
        procedure(iter_func),pointer   :: iter_f => null()  !! reporting function (best member of population)

    contains

        !public routines:
        procedure,non_overridable,public :: init   => set_inputs
        procedure,non_overridable,public :: solve  => solve_with_pikaia

        !private routines:
        procedure,non_overridable :: ff  => func_wrapper  !! internal pikaia function (x:[0,1])
        procedure,non_overridable :: newpop
        procedure,non_overridable :: stdrep
        procedure,non_overridable :: genrep
        procedure,non_overridable :: adjmut
        procedure,non_overridable :: cross
        procedure,non_overridable :: encode
        procedure,non_overridable :: mutate
        procedure,non_overridable :: decode
        procedure,non_overridable :: select_parents
        procedure,non_overridable :: report
        procedure,non_overridable :: rnkpop
        procedure,non_overridable :: pikaia
        procedure,non_overridable :: rninit
        procedure,non_overridable :: urand

    end type pikaia_class