9
APPENDIX III High-Performance Fortran Code The MATLAB code of Appendix II was translated into High-Performance Fortran (HPF), a version of Fortran 95 designed specifically for parallel machines. If you don’t have a parallel machine, the HPF directives all begin with !HPF$, which looks like a comment statement to other versions of Fortran. This is a master–slave parallel implementation (see Chapter 5). Note that it has been specifically tuned for a MIMD Beowulf cluster. It contains commands (e.g., FORALL) that may not be backward compatible with older versions of Fortran.The subroutine, ff, is the cost function that solves (1.1). ! Continuous Genetic Algorithm in High Performance ! Fortran ! Haupt and Haupt, 2003 ! credit to Jaymon Knight for translating and ! adapting program ! MODULE funct !Provides an explicit interface for user-defined !functions and subroutines !J. Knight June 2003 IMPLICIT NONE CONTAINS SUBROUTINE ff(A,X) !_______________________________________________________ ! Cost Function - Insert your own cost functionhere - ! This cost function is equation (1.1) ! of Haupt and Haupt, 2003 ! Practical Genetic Algorithms, Second Edition, by Randy L. Haupt and Sue Ellen Haupt. ISBN 0-471-45565-2 Copyright © 2004 John Wiley & Sons, Inc. 233

Practical Genetic Algorithms || Appendix III: High-Performance Fortran Code

Embed Size (px)

Citation preview

APPENDIX III

High-Performance Fortran Code

The MATLAB code of Appendix II was translated into High-PerformanceFortran (HPF), a version of Fortran 95 designed specifically for parallelmachines. If you don’t have a parallel machine, the HPF directives all beginwith !HPF$, which looks like a comment statement to other versions ofFortran. This is a master–slave parallel implementation (see Chapter 5). Notethat it has been specifically tuned for a MIMD Beowulf cluster. It containscommands (e.g., FORALL) that may not be backward compatible with olderversions of Fortran. The subroutine, ff, is the cost function that solves (1.1).

! Continuous Genetic Algorithm in High Performance ! Fortran! Haupt and Haupt, 2003! credit to Jaymon Knight for translating and ! adapting program!MODULE funct!Provides an explicit interface for user-defined!functions and subroutines!J. Knight June 2003

IMPLICIT NONECONTAINS

SUBROUTINE ff(A,X)!_______________________________________________________! Cost Function - Insert your own cost functionhere -! This cost function is equation (1.1)! of Haupt and Haupt, 2003!

Practical Genetic Algorithms, Second Edition, by Randy L. Haupt and Sue Ellen Haupt.ISBN 0-471-45565-2 Copyright © 2004 John Wiley & Sons, Inc.

233

!Input values are an array, output value is a vector!containing the values of A evaluated using a cost !function.!Calculates the standard deviation of a 1-d array.!J. KnightIMPLICIT NONE

REAL,INTENT(IN),DIMENSION(:,:)::A !Input array !(2-d)

REAL,INTENT(OUT),DIMENSION(:)::X!Output vector (1-!d)

!HPF$ INHERIT A!HPF$ INHERIT X

X=A(:,1)*SIN(4.*A(:,1))+1.1*A(:,2)*SIN(2.*A(:,2))

END subroutine ff

END MODULE funct!=======================================================!=======================================================PROGRAM my_cga! Main genetic algorithm program for Haupt and Haupt ! 2003 -! uses High Performance Fortran! Purpose: Optimizes variables based on a cost ! function using a! genetic algorithm. Based on pseudocode in ! Haupt and Haupt, 1998!! Date Programmer Description of Changes! ======== ============= ======================! 3July2003 Jaymon Knight Code based on seudocode! 19Nov2003 Sue Haupt Revised for 2nd ed of ! Haupt and Haupt!!USE functUSE hpf_libraryIMPLICIT NONE

!Define parameters!Define GA parameters! Use these to tune the code to your problem

234 HIGH-PERFORMANCE FORTRAN CODE

INTEGER,PARAMETER::maxit=1000 !Maximum number of !iterationsINTEGER,PARAMETER::max_same=50 !Maximum# of !consecutively equal valsINTEGER,PARAMETER::popsize=100 !Size of populationINTEGER,PARAMETER::npar=2 !Number of parametersREAL,PARAMETER::tol=.01 !Percent error for stop !criteriaREAL,PARAMETER::mutrate=0.2 !Mutation rateREAL,PARAMETER::selection=0.5 !Fraction of population !to keepREAL,PARAMETER::lo=0. !Minimum parameter !valueREAL,PARAMETER::hi=10. !Maximum parameter !value

!Define variablesINTEGER::status !Error flagINTEGER::how_big !Used in theRANDOM_SEED subroutineINTEGER::keep !Number kept from each !generationINTEGER::M !Number of matingsINTEGER::nmut !Total number of !mutationsINTEGER::iga !Generation counterINTEGER::i,j !IndicesINTEGER::same !Counter for !consecutively equal valuesINTEGER::bad_sort !Counts number of bad !sorts from hpf grade_upREAL::minc !Minimum costREAL::temp !Temporary variableREAL::xy !Mix from ma and pa

!Define matrix variablesINTEGER,ALLOCATABLE,DIMENSION(:)::vals !Contains !values from the time/date callINTEGER,ALLOCATABLE,DIMENSION(:)::seeds !Vector w/ vals !for RANDOM_SEED brtnINTEGER,ALLOCATABLE,DIMENSION(:)::ind !Sorted indices !from cost functionINTEGER,ALLOCATABLE,DIMENSION(:)::ind2 !For sorting !mutated populationINTEGER,ALLOCATABLE,DIMENSION(:)::ma,pa !Parents!(indices)

HIGH-PERFORMANCE FORTRAN CODE 235

INTEGER,ALLOCATABLE,DIMENSION(:)::xp !Crossover !pointINTEGER,ALLOCATABLE,DIMENSION(:)::ix !Index of mate !#1INTEGER,ALLOCATABLE,DIMENSION(:)::mrow,mcol !Used for !sorting mutationsREAL,ALLOCATABLE,DIMENSION(:,:)::par,par2 !Matrix of !population valuesREAL,ALLOCATABLE,DIMENSION(:)::cost !Cost function !evaluatedREAL,ALLOCATABLE,DIMENSION(:)::odds !Involved in !pairingREAL,ALLOCATABLE,DIMENSION(:)::pick1,pick2 !Mates one !and twoREAL,ALLOCATABLE,DIMENSION(:)::temp_arr_1 !Temporary !1-d arrayREAL,ALLOCATABLE,DIMENSION(:)::r !Mixing!parameter

! These HPF directives allow parallel distribution of ! arrays! They appear as comments to Fortran 90/95!HPF$ DISTRIBUTE(BLOCK)::cost,odds,ix!HPF$ ALIGN(:,*) WITH cost(:) ::par

!Calculate variables

keep=FLOOR(selection*popsize) !Number to keep !from each generationM=CEILING(REAL(popsize-keep)/2.) !Number of matingsnmut=CEILING((popsize-1)*npar*mutrate) !Number of !mutations

!Allocate arrays (block 1)

ALLOCATE(cost(popsize),par(popsize,npar),par2(popsize, &npar),ind(popsize),&odds(keep+1),vals(8),ma(M),pa(M),pick1(M),pick2(M),r(M), &xp(M), ix(CEILING(REAL(keep)/2.)),STAT=status)IF(status/=0) THENWRITE(*,*)”Error allocating arrays in main && program.”STOP

END IF

236 HIGH-PERFORMANCE FORTRAN CODE

!_______________________________________________________!Initialize random number generator!Some machines may require more care in calling the !random number generator! This program sets a seed randomly from computer !clock

CALL RANDOM_SEED(SIZE=how_big) !Finds the size !of array expected by subroutineALLOCATE(seeds(how_big),STAT=status)IF(status/=0) THEN

WRITE(*,*)”An error occurred allocating the array &‘seeds’ in the main program.”END IF

CALL DATE_AND_TIME(VALUES=vals) !These values depend !on the current timeIF(vals(8)==0) THEN !We only want a non-!zero valuevals(8)=vals(5)+vals(6)+vals(7) !Substitute in the

!case of zero (HH+MM+SS)END IF

CALL RANDOM_SEED !Initializes the seedCALL RANDOM_SEED(GET=seeds) !Gets the seedseeds=seeds*vals(8) !Adjusts seed so it is !different each timeCALL RANDOM_SEED(PUT=seeds) !Seeds the random !number generator

DEALLOCATE(vals,seeds)!_______________________________________________________!Create the initial population, evaluate costs, sort

CALL RANDOM_NUMBER(par) !Fills par matrix w/ !random numbers

par=(hi-lo)*par+lo !Normalizes values !between hi & lo

!_______________________________________________________!Start generations

iga=0minc=0.same=0bad_sort=0

HIGH-PERFORMANCE FORTRAN CODE 237

OPEN(UNIT=10,FILE=’data.dat’,STATUS=’REPLACE’,ACTION=’WR &ITE’,IOSTAT=status)IF(status/=0) THENWRITE(*,*)”Error opening file ‘out.dat’.”

END IF

DO WHILE(iga<maxit)

iga=iga+1 !Increment counter

CALL ff(par,cost) !Calculates cost using !function ff

ind=grade_up(cost,DIM=1) !Min cost in element 1, !order stored in indcost=cost(ind) !Cost in order stored in !ind

!WRITE(*,*)minc,cost(1),igaIF(ABS((cost(1)-minc)/cost(1))<tol/100.) THEN &same=same+1

ELSEsame=0

END IF

minc=cost(1)

par=par(ind,:) !Puts par in the order !stored in ind

!_______________________________________________________!Pair chromosomes and produce offspring

odds(1)=0. !first spot is zero!HPF$ INDEPENDENT !Fills remainder of !odds matrix w/ values keep-1DO i=1,keepodds(i+1)=keep+1-i

END DO

odds(2:keep+1)=SUM_PREFIX(odds(2:keep+1)) !weights !chromosomes based upon position in the listtemp=odds(keep+1)odds(2:keep+1)=odds(2:keep+1)/temp!Probablility distribution function

238 HIGH-PERFORMANCE FORTRAN CODE

CALL RANDOM_NUMBER(pick1) !mate #1CALL RANDOM_NUMBER(pick2) !mate #2

! ma and pa contain the indices of the chromosomes ! that will mate! Note: this part of code not done in parallelDO i=1,M

DO j=2,keep+1IF(pick1(i)<=odds(j) .AND. pick1(i)>odds(j-1)) THEN &ma(i)=j-1END IFIF(pick2(i)<=odds(j) .AND. pick2(i)>odds(j-1)) THEN &pa(i)=j-1END IF

END DOEND DO

!_______________________________________________________! Performs mating using single point crossover

i=0!HPF$ INDEPENDENTDO i=1,CEILING(REAL(keep)/2.)ix(i)=2*i-1END DO

!Allocate temporary array (block 2) (Subroutine !requires a real argument)ALLOCATE(temp_arr_1(M),STAT=status)IF(status/=0) THENWRITE(*,*)”Error allocating the arrays of allocation &block 2 of the main program.”STOPEND IF

CALL RANDOM_NUMBER(temp_arr_1)

xp=CEILING(temp_arr_1*REAL(npar))

DEALLOCATE(temp_arr_1)

CALL RANDOM_NUMBER(r)

par2=par

HIGH-PERFORMANCE FORTRAN CODE 239

DO i=1,Mxy=par2(ma(i),xp(i))-par2(pa(i),xp(i)) !mix from

!ma & papar2(keep+ix(i),:)=par2(ma(i),:) !first

!offspring variablepar2(keep+ix(i)+1,:)=par2(pa(i),:) !second

!offspring variablepar2(keep+ix(i),xp(i))=par2(ma(i),xp(i))-r(i)*xy

!first offspring variablepar2(keep+ix(i)+1,xp(i))=par2(pa(i),xp(i))+r(i)*xy

!second offspring variableIF(xp(i)<npar) THEN !Perform crossover when

!last variable not selectedDO j=1,xp(i)par2(keep+ix(i),j)=par2(keep+ix(i),j)par2(keep+ix(i)+1,j)=par2(keep+ix(i)+1,j)

END DODO j=xp(i)+1,nparpar2(keep+ix(i),j)=par2(keep+ix(i)+1,j)par2(keep+ix(i)+1,j)=par2(keep+ix(i),j)

END DOEND IF

END DO

par=par2!_______________________________________________________! Mutate the population

!Allocate arrays (block 3)ALLOCATE(temp_arr_1(nmut),mrow(nmut),mcol(nmut),ind2 &(nmut),STAT=status)IF(status/=0) THENWRITE(*,*)”Error allocating the arrays of allocation &block 3 of the main program.”STOPEND IF

CALL RANDOM_NUMBER(temp_arr_1)mrow=CEILING(temp_arr_1*(popsize-1))+1

ind2=grade_up(mrow,DIM=1)mrow=mrow(ind2)

CALL RANDOM_NUMBER(temp_arr_1)mcol=CEILING(temp_arr_1*npar)

240 HIGH-PERFORMANCE FORTRAN CODE

CALL RANDOM_NUMBER(temp_arr_1)temp_arr_1=(hi-lo)*temp_arr_1+lo !Normalizes values !between hi & lo

!HPF$ INDEPENDENTDO i=1,nmutpar(mrow(i),mcol(i))=temp_arr_1(i)END DO

DEALLOCATE(mrow,mcol,temp_arr_1,ind2)IF(MINVAL(cost)/=cost(1)) THENbad_sort=bad_sort+1IF(bad_sort<=1) THENWRITE(10,*)cost

END IFEND IF

END DO

!_______________________________________________________

DEALLOCATE(par,par2,cost,ind,odds,pick1,pick2,ma,pa,r,xp &,ix)CLOSE(10)

WRITE(*,*)”There were”,bad_sort,”bad sorts using the &hpf intrinsic ‘grade_up’.”WRITE(*,104)iga,same,minc104 FORMAT(I4,” iterations were required to obtain &“,I4,” consecutive values of “,F12.5)

END PROGRAM my_cga

HIGH-PERFORMANCE FORTRAN CODE 241