! E05SAF Example Program Text ! Mark 24 Release. NAG Copyright 2012. Module e05safe_mod ! E05SAF Example Program Module: ! Parameters and User-defined Routines ! .. Use Statements .. Use nag_library, Only: nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Real (Kind=nag_wp), Parameter :: & f_target = -837.9657745448674_nag_wp Real (Kind=nag_wp), Parameter :: zero = 0.0_nag_wp Integer, Parameter :: detail_level = 0, liopts = 100, & liuser = 1, lopts = 100, & lruser = 1, ndim = 2, nout = 6, & npar = 5, report_freq = 100 Real (Kind=nag_wp), Parameter :: & x_target(ndim) = -420.9687463599820_nag_wp Contains Subroutine objfun_schwefel(mode,ndim,x,objf,vecout,nstate,iuser,ruser) ! Objfun routine for the Schwefel function for E05SAF. ! .. Scalar Arguments .. Real (Kind=nag_wp), Intent (Inout) :: objf Integer, Intent (Inout) :: mode Integer, Intent (In) :: ndim, nstate ! .. Array Arguments .. Real (Kind=nag_wp), Intent (Inout) :: ruser(*), vecout(ndim) Real (Kind=nag_wp), Intent (In) :: x(ndim) Integer, Intent (Inout) :: iuser(*) ! .. Local Scalars .. Logical :: evalobjf, evalobjg ! .. Intrinsic Procedures .. Intrinsic :: abs, cos, sin, sqrt, sum ! .. Executable Statements .. ! Test NSTATE to indicate what stage of computation has been reached. Select Case (nstate) Case (2) ! OBJFUN is called for the very first time. Case (1) ! OBJFUN is called on entry to a NAG local minimizer. Case Default ! This will be the normal value of NSTATE. End Select ! Test MODE to determine whether to calculate OBJF and/or OBJGRD. evalobjf = .False. evalobjg = .False. Select Case (mode) Case (0,5) ! Only the value of the objective function is needed. evalobjf = .True. Case (1,6) ! Only the values of the NDIM gradients are required. evalobjg = .True. Case (2,7) ! Both the objective function and the NDIM gradients are required. evalobjf = .True. evalobjg = .True. End Select If (evalobjf) Then ! Evaluate the objective function. objf = sum(x(1:ndim)*sin(sqrt(abs(x(1:ndim))))) End If If (evalobjg) Then ! Calculate the gradient of the objective function, ! and return the result in VECOUT. vecout = sqrt(abs(x)) vecout = sin(vecout) + 0.5E0_nag_wp*vecout*cos(vecout) End If Return End Subroutine objfun_schwefel Subroutine monmod(ndim,npar,x,xb,fb,xbest,fbest,itt,iuser,ruser,inform) ! .. Scalar Arguments .. Real (Kind=nag_wp), Intent (In) :: fb Integer, Intent (Inout) :: inform Integer, Intent (In) :: ndim, npar ! .. Array Arguments .. Real (Kind=nag_wp), Intent (In) :: fbest(npar), xb(ndim), & xbest(ndim,npar) Real (Kind=nag_wp), Intent (Inout) :: ruser(*), x(ndim,npar) Integer, Intent (In) :: itt(6) Integer, Intent (Inout) :: iuser(*) ! .. Local Scalars .. Integer :: k ! .. Intrinsic Procedures .. Intrinsic :: modulo ! .. Executable Statements .. If (detail_level>=2) Then ! Report on the first iteration, and every report_freq iterations. If (itt(1)==1 .Or. modulo(itt(1),report_freq)==0) Then Write (nout,*) Write (nout,*) '* Current global optimum candidate:' Do k = 1, ndim Write (nout,99999) k, xb(k) End Do Write (nout,*) '* Current global optimum value:' Write (nout,99998) fb End If End If ! If required set INFORM<0 to force exit inform = 0 Flush (nout) Return 99999 Format (1X,'* xb(',I3,') = ',F9.2) 99998 Format (1X,'* fb = ',F9.5) End Subroutine monmod Subroutine display_option(optstr,optype,ivalue,rvalue,cvalue) ! Subroutine to query optype and print the appropriate option values ! .. Scalar Arguments .. Real (Kind=nag_wp), Intent (In) :: rvalue Integer, Intent (In) :: ivalue, optype Character (*), Intent (In) :: cvalue, optstr ! .. Executable Statements .. Select Case (optype) Case (1) Write (nout,99999) optstr, ivalue Case (2) Write (nout,99998) optstr, rvalue Case (3) Write (nout,99997) optstr, cvalue Case (4) Write (nout,99996) optstr, ivalue, cvalue Case (5) Write (nout,99995) optstr, rvalue, cvalue Case Default End Select Flush (nout) Return 99999 Format (3X,A36,' : ',I13) 99998 Format (3X,A36,' : ',F13.4) 99997 Format (3X,A36,' : ',16X,A16) 99996 Format (3X,A36,' : ',I13,3X,A16) 99995 Format (3X,A36,' : ',F13.4,3X,A16) End Subroutine display_option Subroutine display_result(ndim,xb,fb,itt,inform) ! Display final results in comparison to known global optimum. ! .. Use Statements .. Use nag_library, Only: x04cbf ! .. Parameters .. Integer, Parameter :: indent = 1, ncols = 79 Character (10), Parameter :: clabs(1:2) = (/ & 'x_target ','xb ' /) Character (1), Parameter :: diag = 'N', labcol = 'C', & labrow = 'I', matrix = 'G' Character (5), Parameter :: form = 'F12.2' ! .. Scalar Arguments .. Real (Kind=nag_wp), Intent (In) :: fb Integer, Intent (In) :: inform, ndim ! .. Array Arguments .. Real (Kind=nag_wp), Intent (In) :: xb(ndim) Integer, Intent (In) :: itt(6) ! .. Local Scalars .. Integer :: ifail, ldxcom Character (ncols) :: title ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: xcom(:,:) ! .. Executable Statements .. ! Display final counters. Write (nout,*) ' Algorithm Statistics' Write (nout,*) ' --------------------' Write (nout,99997) 'Total complete iterations : ', itt(1) Write (nout,99997) 'Complete iterations since improvement : ', itt(2) Write (nout,99997) 'Total particles converged to xb : ', itt(3) Write (nout,99997) 'Total improvements to global optimum : ', itt(4) Write (nout,99997) 'Total function evaluations : ', itt(5) Write (nout,99997) 'Total particles re-initialized : ', itt(6) ! Display why finalization occurred. Write (nout,*) Select Case (inform) Case (1) Write (nout,99996) 'Target value achieved' Case (2) Write (nout,99996) 'Minimum swarm standard deviation obtained' Case (3) Write (nout,99996) 'Sufficient particles converged' Case (4) Write (nout,99996) 'Maximum static iterations attained' Case (5) Write (nout,99996) 'Maximum complete iterations attained' Case (6) Write (nout,99996) 'Maximum function evaluations exceeded' Case (:-1) Write (nout,99995) inform Case Default End Select ! Display final objective value and location. Write (nout,*) Write (nout,99999) f_target Write (nout,99998) fb Flush (nout) ldxcom = ndim Allocate (xcom(ldxcom,2)) xcom(1:ndim,1) = x_target(1:ndim) xcom(1:ndim,2) = xb(1:ndim) Write (nout,*) title = 'Comparison between known and achieved optima.' ifail = 0 Call x04cbf(matrix,diag,ndim,2,xcom,ldxcom,form,title,labrow,clabs, & labcol,clabs,ncols,indent,ifail) Deallocate (xcom) Write (nout,*) Return 99999 Format (' Known objective optimum ',13X,' : ',F13.5) 99998 Format (' Achieved objective value',13X,' : ',F13.5) 99997 Format (2X,A40,I13) 99996 Format (2X,'Solution Status : ',A43) 99995 Format (' User termination case :',I16) End Subroutine display_result End Module e05safe_mod Program e05safe ! E05SAF Example Main Program ! This example program demonstrates how to use E05SAF in standard ! execution, and with a selection of coupled local minimizers. ! The non-default option 'REPEATABILITY ON' is used here, giving ! repeatable results. ! .. Use Statements .. Use nag_library, Only: e05saf, e05zkf, e05zlf, nag_wp Use e05safe_mod, Only: display_option, display_result, f_target, liopts, & liuser, lopts, lruser, monmod, ndim, nout, npar, & objfun_schwefel ! .. Implicit None Statement .. Implicit None ! .. Local Scalars .. Real (Kind=nag_wp) :: fb, rvalue Integer :: ifail, inform, ivalue, optype Character (16) :: cvalue Character (80) :: optstr ! .. Local Arrays .. Real (Kind=nag_wp) :: bl(ndim), bu(ndim), opts(lopts), & ruser(lruser), xb(ndim) Integer :: iopts(liopts), itt(6), & iuser(liuser) ! .. Executable Statements .. ! Print advisory information. Write (nout,*) 'E05SAF Example Program Results' Write (nout,*) Write (nout,*) 'Minimization of the Schwefel function.' Write (nout,*) ! Set problem specific values. ! Set box bounds. bl(1:ndim) = -500.0_nag_wp bu(1:ndim) = 500.0_nag_wp ! Initialize the option arrays for E05SAF. ifail = 0 Call e05zkf('Initialize = E05SAF',iopts,liopts,opts,lopts,ifail) ! Query some default option values. Write (nout,*) ' Default Option Queries:' Write (nout,*) ifail = 0 optstr = 'Boundary' Call e05zlf(optstr,ivalue,rvalue,cvalue,optype,iopts,opts,ifail) Call display_option(optstr,optype,ivalue,rvalue,cvalue) ifail = 0 optstr = 'Maximum Iterations Completed' Call e05zlf(optstr,ivalue,rvalue,cvalue,optype,iopts,opts,ifail) Call display_option(optstr,optype,ivalue,rvalue,cvalue) ifail = 0 optstr = 'Distance Tolerance' Call e05zlf(optstr,ivalue,rvalue,cvalue,optype,iopts,opts,ifail) Call display_option(optstr,optype,ivalue,rvalue,cvalue) Write (nout,*) ! ------------------------------------------------------------------ Write (nout,*) '1. Solution without using coupled local minimizer.' Write (nout,*) ! Set various options to non-default values if required. ifail = 0 Call e05zkf('Repeatability = On',iopts,liopts,opts,lopts,ifail) ifail = 0 Call e05zkf('Verify Gradients = Off',iopts,liopts,opts,lopts,ifail) ifail = 0 Call e05zkf('Boundary = Hyperspherical',iopts,liopts,opts,lopts,ifail) ifail = 0 Call e05zkf('Maximum iterations static = 150',iopts,liopts,opts,lopts, & ifail) ifail = 0 Call e05zkf('Repulsion Initialize = 30',iopts,liopts,opts,lopts,ifail) ifail = 0 Call e05zkf('Repulsion Finalize = 30',iopts,liopts,opts,lopts,ifail) ! Call E05SAF to search for the global optimum. ! Non-zero IFAIL expected on exit here, so use IFAIL=1 (quiet) on entry. ifail = 1 Call e05saf(ndim,npar,xb,fb,bl,bu,objfun_schwefel,monmod,iopts,opts, & iuser,ruser,itt,inform,ifail) ! It is essential to test IFAIL on exit. Select Case (ifail) Case (0,1) ! No errors, best found optimum at xb returned in fb. Call display_result(ndim,xb,fb,itt,inform) Case (3) ! Exit flag set in OBJFUN or MONMOD and returned in INFORM. Call display_result(ndim,xb,fb,itt,inform) Case Default ! An error was detected. Print message since IFAIL=1 on entry. Write (nout,99998) '** E05SAF returned with an error, IFAIL = ', ifail Continue End Select ! ------------------------------------------------------------------ Write (nout,*) '2. Solution using coupled local minimizer E04CBF' Write (nout,*) ! Set an objective target. ifail = 0 Write (optstr,99999) 'Target Objective Value', f_target Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail) ifail = 0 Write (optstr,99999) 'Target Objective Tolerance', 1.0E-5_nag_wp Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail) ifail = 0 Write (optstr,99999) 'Target Objective Safeguard', 1.0E-8_nag_wp Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail) ! Set the local minimizer to be E04CBF and set corresponding options. ifail = 0 Call e05zkf('Local Minimizer = E04CBF',iopts,liopts,opts,lopts,ifail) ifail = 0 Call e05zkf('Local Interior Iterations = 10',iopts,liopts,opts,lopts, & ifail) ifail = 0 Call e05zkf('Local Exterior Iterations = 20',iopts,liopts,opts,lopts, & ifail) ifail = 0 Write (optstr,99999) 'Local Interior Tolerance', 1.0E-4_nag_wp Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail) ifail = 0 Write (optstr,99999) 'Local Exterior Tolerance', 1.0E-4_nag_wp Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail) ! Call E05SAF to search for the global optimum. ifail = -1 Call e05saf(ndim,npar,xb,fb,bl,bu,objfun_schwefel,monmod,iopts,opts, & iuser,ruser,itt,inform,ifail) ! It is essential to test IFAIL on exit. Select Case (ifail) Case (0,1) ! No errors, best found optimum at xb returned in fb. Call display_result(ndim,xb,fb,itt,inform) Case (3) ! Exit flag set in OBJFUN or MONMOD and returned in INFORM. Call display_result(ndim,xb,fb,itt,inform) Case Default ! An error was detected. Continue End Select ! ----------------------------------------------------------------- Write (nout,*) '3. Solution using coupled local minimizer E04DGF' Write (nout,*) ! Set the local minimizer to be E04DGF and set corresponding options. ifail = 0 Call e05zkf('Local Minimizer = E04DGF',iopts,liopts,opts,lopts,ifail) ifail = 0 Call e05zkf('Local Interior Iterations = 5',iopts,liopts,opts,lopts, & ifail) ifail = 0 Call e05zkf('Local Exterior Iterations = 20',iopts,liopts,opts,lopts, & ifail) ! Call E05SAF to search for the global optimum. ifail = -1 Call e05saf(ndim,npar,xb,fb,bl,bu,objfun_schwefel,monmod,iopts,opts, & iuser,ruser,itt,inform,ifail) ! It is essential to test IFAIL on exit. Select Case (ifail) Case (0,1) ! No errors, best found optimum at xb returned in fb. Call display_result(ndim,xb,fb,itt,inform) Case (3) ! Exit flag set in OBJFUN or MONMOD and returned in INFORM. Call display_result(ndim,xb,fb,itt,inform) Case Default ! An error was detected. Continue End Select 99999 Format (A,' = ',E32.16) 99998 Format (1X,A,I6) End Program e05safe