声振论坛

 找回密码
 我要加入

QQ登录

只需一步,快速开始

查看: 3280|回复: 1

[人工智能] 一个可以运行的遗传算法fortran源码

[复制链接]
发表于 2006-8-6 07:10 | 显示全部楼层 |阅读模式

马上注册,结交更多好友,享用更多功能,让你轻松玩转社区。

您需要 登录 才可以下载或查看,没有账号?我要加入

x
这是一个可以运行的遗传算法fortran源码,变量涉及得很多!

  1. module data_type
  2.   implicit none
  3.   integer(kind=4), parameter :: IB=4, RP=8
  4. end module data_type

  5. module data_Rosen
  6.   use data_type
  7.   implicit none
  8.   integer(kind=IB), parameter ::  Dim_XC=10
  9. end module data_Rosen

  10. module data_HDE
  11.         use data_type
  12.         use data_Rosen
  13.         implicit none
  14.         integer(kind=IB), parameter :: NP=20, itermax=20000, strategy=6, &
  15.                                  refresh=500, iwrite=7
  16.     integer(kind=IB), dimension(3), parameter :: method=(/0, 1, 0/)
  17.     real(kind=RP), parameter :: VTR=-1.0e-4_RP, CR_XC=0.5_RP
  18.     real(kind=RP) :: F_XC=0.8_RP, F_CR=0.8_RP
  19.         real(kind=RP), dimension(Dim_XC), parameter :: XCmin=-10.0_RP, XCmax=10.0_RP
  20.         real(kind=RP), dimension(Dim_XC) :: bestmem_XC
  21.     integer(kind=IB) :: nfeval
  22.     real(kind=RP) :: bestval
  23. end module data_HDE


  24. program Rosen
  25.   use data_type
  26.   use data_Rosen
  27.   use data_HDE
  28.   implicit none
  29.   integer(kind=IB) :: i
  30.   integer (kind=IB), dimension(8) :: time
  31.   intrinsic date_and_time
  32.   external FTN
  33.   open(iwrite,file='Rosen.txt')
  34.   call date_and_time(values=time)
  35.   write(unit=iwrite, FMT=11) time(1:3), time(5:7)

  36.   call DE_Fortran90(FTN, Dim_XC, XCmin, XCmax, VTR, NP, itermax, F_XC,&
  37.                 CR_XC, strategy, refresh, iwrite, bestmem_XC, &
  38.                                 bestval, nfeval, F_CR, method)
  39.               
  40.               write(iwrite,205) NP, nfeval, method(1:3)
  41.                           write(iwrite,FMT=201) F_XC, CR_XC, F_CR
  42.                       write(iwrite,FMT=200) bestval
  43.                           do i=1,Dim_XC
  44.                          write(iwrite,FMT=202) i,bestmem_XC(i)
  45.               end do
  46. 200            format(/2x, 'Bestval=', ES14.7)
  47. 201     format(2x, 'F_XC =',F6.3, 2x, 'CR_XC =', F6.3, 2x, 'F_CR =', F6.3)
  48. 202     format(2x, 'best_XC(',I3,') =',ES14.7)
  49. 205     format(2x, 'NP=', I4, 4x, 'No. function call =', I9, &
  50.                /2x, 'mehtod(1:3) =',3I3)
  51.         call date_and_time(values=time)
  52.         write(unit=iwrite, FMT=10)time(1:3), time(5:7)
  53. 10        format(/1x, 'End of Program. Date:', I4, '/', I2,'/', I2, ', Time: ', I2,':',I2,':',I2)
  54. 11        format(1x, 'Beginning of Program. Date:', I4, '/', I2,'/', I2, ', Time: ', I2,':',I2,':',I2)
  55. end program Rosen


  56. subroutine FTN(X, objval)
  57.   use data_type
  58.   use data_Rosen
  59.   implicit none
  60.   real(kind=RP), dimension(Dim_XC), intent(in) :: X
  61.   real(kind=RP), intent(out) :: objval
  62.   integer(kind=IB) :: i
  63.   i=Dim_XC

  64.   objval=sum(100.0*(x(1:i-1)**2-x(2:i))**2+(1.0-x(1:i-1))**2)
  65. end subroutine FTN



  66. subroutine DE_Fortran90(obj, Dim_XC, XCmin, XCmax, VTR, NP, itermax, F_XC, &
  67.            CR_XC, strategy, refresh, iwrite, bestmem_XC, bestval, nfeval, &
  68.                    F_CR, method)
  69. !.......................................................................
  70. !   
  71. ! Differential Evolution for Optimal Control Problems
  72. !
  73. !.......................................................................
  74. !  This Fortran 90 program translates from the original MATLAB
  75. !  version of differential evolution (DE). This FORTRAN 90 code
  76. !  has been tested on Compaq Visual Fortran v6.1.
  77. !  Any users new to the DE are encouraged to read the article of Storn and Price.
  78. !
  79. !  Refences:
  80. !  Storn, R., and Price, K.V., (1996). Minimizing the real function of the
  81. !    ICEC'96 contest by differential evolution. IEEE conf. on Evolutionary
  82. !    Comutation, 842-844.
  83. !
  84. !  This Fortran 90 program written by Dr. Feng-Sheng Wang
  85. !  Department of Chemical Engineering, National Chung Cheng University,
  86. !  Chia-Yi 621, Taiwan, e-mail: chmfsw@ccunix.ccu.edu.tw
  87. !.........................................................................
  88. !                obj : The user provided file for evlauting the objective function.
  89. !                      subroutine obj(xc,fitness)
  90. !                      where "xc" is the real decision parameter vector.(input)
  91. !                            "fitness" is the fitness value.(output)
  92. !             Dim_XC : Dimension of the real decision parameters.
  93. !      XCmin(Dim_XC) : The lower bound of the real decision parameters.
  94. !      XCmax(Dim_XC) : The upper bound of the real decision parameters.
  95. !                VTR : The expected fitness value to reach.
  96. !                 NP : Population size.
  97. !            itermax : The maximum number of iteration.
  98. !               F_XC : Mutation scaling factor for real decision parameters.
  99. !              CR_XC : Crossover factor for real decision parameters.
  100. !           strategy : The strategy of the mutation operations is used in HDE.
  101. !            refresh : The intermediate output will be produced after "refresh"
  102. !                      iterations. No intermediate output will be produced if
  103. !                      "refresh < 1".
  104. !             iwrite : The unit specfier for writing to an external data file.
  105. ! bestmen_XC(Dim_XC) : The best real decision parameters.
  106. !              bestval : The best objective function.
  107. !             nfeval : The number of function call.
  108. !         method(1) = 0, Fixed mutation scaling factors (F_XC)
  109. !                   = 1, Random mutation scaling factors F_XC=[0, 1]
  110. !                   = 2, Random mutation scaling factors F_XC=[-1, 1]
  111. !         method(2) = 1, Random combined factor (F_CR) used for strategy = 6
  112. !                        in the mutation operation
  113. !                   = other, fixed combined factor provided by the user
  114. !         method(3) = 1, Saving results in a data file.
  115. !                   = other, displaying results only.

  116.          use data_type, only : IB, RP
  117.          implicit none
  118.          integer(kind=IB), intent(in) :: NP, Dim_XC, itermax, strategy,   &
  119.                                          iwrite, refresh
  120.      real(kind=RP), intent(in) :: VTR, CR_XC
  121.          real(kind=RP) :: F_XC, F_CR
  122.          real(kind=RP), dimension(Dim_XC), intent(in) :: XCmin, XCmax
  123.      real(kind=RP), dimension(Dim_XC), intent(inout) :: bestmem_XC
  124.          real(kind=RP), intent(out) :: bestval
  125.          integer(kind=IB), intent(out) :: nfeval     
  126.      real(kind=RP), dimension(NP,Dim_XC) :: pop_XC, bm_XC, mui_XC, mpo_XC,   &
  127.                                                 popold_XC, rand_XC, ui_XC
  128.      integer(kind=IB) :: i, ibest, iter
  129.      integer(kind=IB), dimension(NP) :: rot, a1, a2, a3, a4, a5, rt
  130.      integer(kind=IB), dimension(4) :: ind
  131.      real(kind=RP) :: tempval
  132.          real(kind=RP), dimension(NP) :: val
  133.      real(kind=RP), dimension(Dim_XC) :: bestmemit_XC
  134.      real(kind=RP), dimension(Dim_XC) :: rand_C1
  135.          integer(kind=IB), dimension(3), intent(in) :: method
  136.          external  obj
  137.          intrinsic max, min, random_number, mod, abs, any, all, maxloc
  138.          interface
  139.         function randperm(num)
  140.                    use data_type, only : IB       
  141.                    implicit none
  142.                integer(kind=IB), intent(in) :: num
  143.            integer(kind=IB), dimension(num) :: randperm
  144.         end function randperm
  145.      end interface
  146. !!-----Initialize a population --------------------------------------------!!

  147.         pop_XC=0.0_RP
  148.         do i=1,NP
  149.            call random_number(rand_C1)
  150.            pop_XC(i,:)=XCmin+rand_C1*(XCmax-XCmin)
  151.                 end do

  152. !!--------------------------------------------------------------------------!!

  153. !!------Evaluate fitness functions and find the best member-----------------!!
  154.      val=0.0_RP
  155.      nfeval=0
  156.      ibest=1
  157.      call obj(pop_XC(1,:), val(1))
  158.      bestval=val(1)
  159.      nfeval=nfeval+1
  160.      do i=2,NP
  161.         call obj(pop_XC(i,:), val(i))
  162.         nfeval=nfeval+1
  163.         if (val(i) < bestval) then
  164.            ibest=i
  165.                bestval=val(i)
  166.         end if
  167.      end do           
  168.      bestmemit_XC=pop_XC(ibest,:)
  169.      bestmem_XC=bestmemit_XC
  170. !!--------------------------------------------------------------------------!!

  171.      bm_XC=0.0_RP
  172.      rot=(/(i,i=0,NP-1)/)
  173.      iter=1
  174. !!------Perform evolutionary computation------------------------------------!!

  175.      do while (iter <= itermax)
  176.         popold_XC=pop_XC

  177. !!------Mutation operation--------------------------------------------------!!
  178.         ind=randperm(4)
  179.         a1=randperm(NP)
  180.         rt=mod(rot+ind(1),NP)
  181.         a2=a1(rt+1)
  182.         rt=mod(rot+ind(2),NP)
  183.         a3=a2(rt+1)
  184.         rt=mod(rot+ind(3),NP)
  185.         a4=a3(rt+1)
  186.         rt=mod(rot+ind(4),NP)
  187.         a5=a4(rt+1)
  188.         bm_XC=spread(bestmemit_XC, DIM=1, NCOPIES=NP)

  189. !----- Generating a random sacling factor--------------------------------!
  190.                 select case (method(1))
  191.                 case (1)
  192.                    call random_number(F_XC)
  193.                 case(2)
  194.                    call random_number(F_XC)
  195.            F_XC=2.0_RP*F_XC-1.0_RP
  196.                 end select

  197. !---- select a mutation strategy-----------------------------------------!
  198.                 select case (strategy)
  199.         case (1)
  200.            ui_XC=bm_XC+F_XC*(popold_XC(a1,:)-popold_XC(a2,:))

  201.             case default
  202.            ui_XC=popold_XC(a3,:)+F_XC*(popold_XC(a1,:)-popold_XC(a2,:))

  203.             case (3)
  204.            ui_XC=popold_XC+F_XC*(bm_XC-popold_XC+popold_XC(a1,:)-popold_XC(a2,:))

  205.             case (4)
  206.            ui_XC=bm_XC+F_XC*(popold_XC(a1,:)-popold_XC(a2,:)+popold_XC(a3,:)-popold_XC(a4,:))

  207.                 case (5)
  208.                    ui_XC=popold_XC(a5,:)+F_XC*(popold_XC(a1,:)-popold_XC(a2,:)+popold_XC(a3,:) &
  209.                          -popold_XC(a4,:))
  210.         case (6) ! A linear crossover combination of bm_XC and popold_XC
  211.            if (method(2) == 1) call random_number(F_CR)
  212.                    ui_XC=popold_XC+F_CR*(bm_XC-popold_XC)+F_XC*(popold_XC(a1,:)-popold_XC(a2,:))

  213.         end select
  214. !!--------------------------------------------------------------------------!!
  215. !!------Crossover operation-------------------------------------------------!!
  216.         call random_number(rand_XC)
  217.            mui_XC=0.0_RP
  218.            mpo_XC=0.0_RP
  219.         where (rand_XC < CR_XC)
  220.            mui_XC=1.0_RP
  221. !           mpo_XC=0.0_RP
  222.         elsewhere
  223. !           mui_XC=0.0_RP
  224.            mpo_XC=1.0_RP
  225.         end where

  226.                 ui_XC=popold_XC*mpo_XC+ui_XC*mui_XC
  227. !!--------------------------------------------------------------------------!!
  228. !!------Evaluate fitness functions and find the best member-----------------!!
  229.         do i=1,NP
  230. !!------Confine each of feasible individuals in the lower-upper bound-------!!
  231.                    ui_XC(i,:)=max(min(ui_XC(i,:),XCmax),XCmin)
  232.            call obj(ui_XC(i,:), tempval)
  233.                nfeval=nfeval+1
  234.                if (tempval < val(i)) then
  235.                   pop_XC(i,:)=ui_XC(i,:)
  236.                   val(i)=tempval
  237.                   if (tempval < bestval) then
  238.                      bestval=tempval
  239.                          bestmem_XC=ui_XC(i,:)
  240.               end if
  241.            end if
  242.         end do
  243.         bestmemit_XC=bestmem_XC
  244.             if( (refresh > 0) .and. (mod(iter,refresh)==0)) then
  245.                         if (method(3)==1) write(unit=iwrite,FMT=203) iter
  246.                      write(unit=*, FMT=203) iter       
  247.                      do i=1,Dim_XC
  248.                          if (method(3)==1) write(unit=iwrite, FMT=202) i, bestmem_XC(i)
  249.                                  write(*,FMT=202) i,bestmem_XC(i)
  250.              end do
  251.                          if (method(3)==1) write(unit=iwrite, FMT=201) bestval
  252.                          write(unit=*, FMT=201) bestval       
  253.         end if
  254.         iter=iter+1
  255.         if ( bestval <= VTR .and. refresh > 0) then
  256.            write(unit=iwrite, FMT=*) ' The best fitness is smaller than VTR'
  257.                    write(unit=*, FMT=*) 'The best fitness is smaller than VTR'
  258.            exit
  259.         endif
  260.          end do
  261. !!------end the evolutionary computation------------------------------!!
  262. 201 format(2x, 'bestval =', ES14.7, /)
  263. 202 format(5x, 'bestmem_XC(', I3, ') =', ES12.5)
  264. 203 format(2x, 'No. of iteration  =', I8)
  265. end subroutine DE_Fortran90


  266. function randperm(num)
  267.   use data_type, only : IB, RP
  268.   implicit none
  269.   integer(kind=IB), intent(in) :: num
  270.   integer(kind=IB) :: number, i, j, k
  271.   integer(kind=IB), dimension(num) :: randperm
  272.   real(kind=RP), dimension(num) :: rand2
  273.   intrinsic random_number
  274.   call random_number(rand2)
  275.   do i=1,num
  276.      number=1
  277.      do j=1,num
  278.         if (rand2(i) > rand2(j)) then
  279.                number=number+1
  280.         end if
  281.      end do
  282.      do k=1,i-1
  283.         if (rand2(i) <= rand2(k) .and. rand2(i) >= rand2(k)) then
  284.                number=number+1
  285.         end if
  286.      end do
  287.      randperm(i)=number
  288.   end do
  289.   return
  290. end function randperm
复制代码
回复
分享到:

使用道具 举报

发表于 2006-8-22 19:56 | 显示全部楼层
谢谢
您需要登录后才可以回帖 登录 | 我要加入

本版积分规则

QQ|小黑屋|Archiver|手机版|联系我们|声振论坛

GMT+8, 2024-9-21 02:46 , Processed in 0.059624 second(s), 17 queries , Gzip On.

Powered by Discuz! X3.4

Copyright © 2001-2021, Tencent Cloud.

快速回复 返回顶部 返回列表