filename changes
[unres.git] / source / ga / GA.f
index 13af8fe..be7bbda 100644 (file)
@@ -4,7 +4,7 @@
       include 'GA.inc'
       include 'common.inc'
       include 'io.inc'
-      real*16 :: WEIGHTS(18)
+      real*8 :: WEIGHTS(18)
       integer*4 :: i,j,m,n,iloc,pos,iter,maxiter,numarg,tmplen
       integer*4 :: WybierzOsobnika,Najlepszy,ZnajdzPodobnego,FindWorst
       integer*4 :: status
@@ -15,7 +15,6 @@
       real :: rand, r
       real*8 :: maxfcever
       real*8 :: FunkcjaCeluB, FunkcjaCeluB2, FunkcjaCeluR
-c      character*500 :: Weights2Str
       character(80),dimension(5) :: wagi
       logical :: searching = .false.
       logical :: logdata = .true.
@@ -25,9 +24,6 @@ c      character*500 :: Weights2Str
       logical :: debug = .true.
       character*200 :: text, tmptext,tmptext2
       character(len=*), parameter :: FMT = "(19F10.5,E15.7,F10.5)"
-c      character(len=*), parameter :: FMT = "(F10.5,F10.5,F10.5,F10.5,F10&
-c     &.5,F10.5,F10.5,F10.5,F10.5,F10.5,F10.5,F10.5,F10.5,F10.5,F10.5,F10&
-c     &.5,F10.5,F10.5,F10.5,F10.5,F10.5)"
       
 c =======================================================================
 c  Main program
@@ -35,7 +31,7 @@ c =======================================================================
 
 
       call ReadInput(status)
-      if ((maxminstep.gt.0).and.(generation.eq.1)) then
+      if ((maxminstep.gt.0).and.(generation.eq.0)) then
 c Do first score  
        do_fs=.true.
       endif
@@ -82,7 +78,8 @@ c No. Prepere next generation
        open(ostate,file=ostatefn) 
        read(ostate,'(I4)') generation
        read(ostate,'(L2)') do_optima
-       read(ostate,'(L2)') do_ga 
+       read(ostate,'(L2)') do_ga
+       read(ostate,'(F7.5)') avrd
        close(ostate)
        if (do_ga) then
         call write2log("Doing GA in this step")
@@ -92,33 +89,36 @@ c No. Prepere next generation
         call write2log("ZSCORE weights minimalization disabled for now")
         generation=generation+1
        endif
-
+       write(tmptext,'(I4)') generation 
+       call write2log("This is genaration "//tmptext)
        call ReadOptimaW(BANK_MULTIPLIER*banksize,populacja)
 
 c Yes. Generate random zero-population
       else
        call GenPopulation(BANK_MULTIPLIER*banksize,populacja)
+       write(tmptext,'(I4)') generation 
+       call write2log("This is genaration "//tmptext)
        if (do_optima) then
         do_ga=.false.
        endif 
 
-c End of "fisrst time here?" code
+c End of "first time here?" code
       endif
 
 c
 c Do we actual use a Genetic Algorithm?
 c
 
-      if (do_ga.eq..true.) then
+      if (do_ga.eqv..true.) then
 
 c Yes. This is only done when doing second pass with ZSCORE (without weight minimalizaton)
 c or with weight minimalization disabled (maxmin=0) just to obtain final score)
 
-c \\---//================================================================
-c  \\-//           
-c   "//  Genetic Algorithm code starts here  
-c   //-\\                                        
-c =//---\\===============================================================
+c \\---//================================================================c
+c  \\-//                                                                 c
+c   "//  Genetic Algorithm code starts here                              c
+c   //-\\                                                                c
+c =//---\\===============================================================c
 
       call ReadZEnergy(BANK_MULTIPLIER*banksize,populacja)
       do i=1,BANK_MULTIPLIER*banksize
@@ -146,17 +146,17 @@ c --- debug begin ---
         write(*,*) "do_ga: ",do_ga
         write(*,*) "do_optima: ",do_optima
         write(*,*) "do_fs: ",do_fs
-        write(*,*) "cicutoff: ", cicutoff         
+c       write(*,*) "cicutoff: ", cicutoff         
        endif
 c --- debug end ---
 
-        csacutoff=cicutoff
+c        csacutoff=cicutoff
 
 c
 c  Fill the bank just after the first time we get the score 
 c
-        if (((generation.eq.2).and.(maxminstep.eq.0)).or.((generation.eq&
-     &.2).and.(maxminstep.gt.0))) then
+        if (((generation.eq.1).and.(maxminstep.eq.0)).or.((generation.eq&
+     &.1).and.(maxminstep.gt.0))) then
 
 c --- debug begin ---
         if (debug) then 
@@ -164,6 +164,20 @@ c --- debug begin ---
         endif
 c --- debug end ---
          call GetNBest(populacja,bank,banksize)
+         call CalcAvgDist(bank,avrd)
+         write(tmptext,'(F7.5)') avrd
+         call write2log("Average distance between individuals in initial&
+     & bank is "//trim(tmptext))
+c
+c Cutoff 
+c
+         csacutoff=(maxco*avrd)-generation*avrd*(maxco-minco)/maxgen
+         write(tmptext,'(F7.5)') csacutoff
+         call write2log("CSA cutoff is now set to "//trim(tmptext))
+c         csacutoff=maxco*avrd         
+
+         
+
 c --- debug begin ---
         if (debug) then
          do i=1,banksize
@@ -187,28 +201,52 @@ c --- debug begin ---
 c --- debug end ---
 
          call ReadBank(bank)
+         write(tmptext,'(F7.5)') avrd
+         call write2log("Average distance in bank is "//trim(tmptext))
 
+         csacutoff=maxco*avrd-generation*avrd*(maxco-minco)/maxgen
+         write(tmptext,'(F7.5)') csacutoff
+         call write2log("CSA cutoff is now set to "//trim(tmptext))
+  
          do i=1,BANK_MULTIPLIER*banksize
           write(tmptext,'(I4)') i
-          call write2log("Checking ind "//tmptext)  
+          call write2log("Checking ind "//trim(tmptext))  
           j=ZnajdzPodobnego(banksize,bank,populacja(i,:),csacutoff)
-          if (j.gt.0) then
+          if (j.gt.0) then  ! W banku jest podobny
            if (populacja(i,20).lt.bank(j,20)) then
             write(tmptext,'(I4)') j
             write(tmptext2,'(I4)') i
-            call write2log("Swaping ind"//trim(tmptext)//" from bank to &
-     &ind "//trim(tmptext2)//" from population")
+            call write2log("  Swaping ind"//trim(tmptext)//" from bank t&
+     &o ind "//trim(tmptext2)//" from population")
+            write(tmptext2,'(19F8.5,E15.7,F8.5)') bank(j,:)
+            call write2log("  BANK"//trim(tmptext)//":"//trim(tmptext2))
+
+            write(tmptext,'(I4)') i
+            write(tmptext2,'(19F8.5,E15.7,F8.5)') populacja(i,:)
+            call write2log("  POP "//trim(tmptext)//":"//trim(tmptext2))
+      
             bank(j,:)=populacja(i,:)
+           else
+            call write2log("  Found simialar but not better")
            endif
-          else
+          else              ! W banku nie ma podobnego 
            j=FindWorst(banksize,bank)
-           write(tmptext,'(I4)') j
-           write(tmptext2,'(I4)') i
+           write(tmptext2,'(I4)') j
            if (populacja(i,20).lt.bank(j,20)) then
-            call write2log("Worst in bank is "//trim(tmptext))
-            call write2log("Swaping worst ind in bank to "//trim(tmptext&
-     &2))
+            call write2log("  Worst in bank is "//trim(tmptext2))
+            write(tmptext,'(I4)') i
+            call write2log("  Swaping worst ind in bank to "//trim(tmpte&
+     &xt))
+            write(tmptext,'(I4)') j
+            write(tmptext2,'(19F8.5,E15.7,F8.5)') bank(j,:)
+            call write2log("  BANK"//trim(tmptext)//":"//trim(tmptext2))
+            write(tmptext,'(I4)') i
+            write(tmptext2,'(19F8.5,E15.7,F8.5)') populacja(i,:)
+            call write2log("  POP "//trim(tmptext)//":"//trim(tmptext2))
             bank(j,:)=populacja(i,:)
+           else
+            call write2log("  The worst in bank is better then this Ind"&
+     &)
            endif
           endif
          enddo
@@ -229,15 +267,10 @@ c --- debug begin ---
 c --- debug end ---
 
          call WriteBank(bank)
-         csacutoff=csacutoff-(generation*cicutoff/maxgen)
-c       csacutoff=cicutoff*(0.8**(iter-1))
-
-         write(tmptext,'(F7.5)') csacutoff
 
-         call write2log("CSA cutoff is now set to "//tmptext)
         endif
        case('cluster')
-        write(*,*) "Some stuff here in the future"
+        write(*,*) "Well this is not implemented yet"
         goto 2010
       end select
 
@@ -376,7 +409,7 @@ c
       else
        if (do_fs) then
         do_optima=.not.do_optima
-        if (generation.eq.1) then
+        if (generation.eq.0) then
          do_ga=.false.
         else
          do_ga=.not.do_ga
@@ -396,9 +429,9 @@ c      call WritePopSum()
 c
 c Create the inputs
 c 
-      write(tmptext,'(I)') generation
-      call write2log("Preparing inputs for generation "//trim(adjustl(tm&
-     &ptext)))
+      write(tmptext,'(I3)') generation+1
+      call write2log("Preparing inputs for next generation ("//trim(adju&
+     &stl(tmptext))//")")
       call CreateInputs(BANK_MULTIPLIER*banksize,populacja)
 c
 c All done? Then let's quit.
@@ -495,7 +528,7 @@ c ----------------------------------------------------------------------
 
       integer*4 function FindWorst(rozmiar,pop)
        integer*4 :: rozmiar, i, idx
-       real*16 :: pop,last
+       real*8 :: pop,last
        dimension pop(rozmiar,21)
        
        last=0.0
@@ -579,7 +612,6 @@ c ----------------------------------------------------------------------
        real*8 :: ind1(19),ind2(19),temp(19)
        integer*4 :: loc
        loc = 1 + int(rand(0)/(1/18.0))
-c       write (*,*) "Krzyzowanie pomiedzy pozycja ",(loc-1),"a",loc
        temp = ind2
        do i=(loc),19
         ind2(i)=ind1(i)
@@ -688,7 +720,7 @@ c ----------------------------------------------------------------------
        include 'TEST.inc'
        real*8 :: osobnik(20)
        integer*4 :: i
-       FunkcjaCeluB = 20 + -exp(-abs(WLONG-osobnik(1)))                 &
+       FunkcjaCeluB = 20 -exp(-abs(WLONG-osobnik(1)))                   &
      & - exp(-abs(WSCP-osobnik(2)))                                     &
      & - exp(-abs(WELEC-osobnik(3)))                                    &
      & - exp(-abs(WBOND-osobnik(4)))                                    &
@@ -810,7 +842,6 @@ c ======================================================================
       integer :: stat
       integer*4 :: status
       character*100 :: wiersz,tmp
-      !character*500 :: wiersze = ''
       inquire(FILE=inpfn,EXIST=ex) 
       if (ex) then
        status = 0
@@ -821,29 +852,31 @@ c ======================================================================
        do
          read(inp, '(A)', iostat=stat) wiersz
          if (stat /= 0) exit
-          if ((wiersz(1:4).eq.'PDB=').or.(wiersz(1:4).eq.'pdb=')) then
-           npdb=1
-            tmp = wiersz(5:len_trim(wiersz))
-            do i=1,len_trim(tmp)
-             if (tmp(i:i).eq.' ') then
-             npdb=npdb+1
-             endif
-            end do
-            if (npdb.gt.maxnpdb) then
-             call write2log("Number of input PDB exceeds maxnpdb!")
-             status = 1
-             exit
-            endif
-            do i=1,npdb
-             if (index(trim(tmp),' ').gt.0) then
-              pdbfiles(i)=tmp(1:index(trim(tmp),' '))
-             else
-              pdbfiles(i)=tmp(1:len_trim(tmp))
-             endif
-            tmp=tmp(index(trim(tmp),' ')+1:len_trim(tmp))
+c PDB=
+         if ((wiersz(1:4).eq.'PDB=').or.(wiersz(1:4).eq.'pdb=')) then
+          npdb=1
+          tmp = wiersz(5:len_trim(wiersz))
+          do i=1,len_trim(tmp)
+           if (tmp(i:i).eq.' ') then
+            npdb=npdb+1
+           endif
+          end do
+          if (npdb.gt.maxnpdb) then
+           call write2log("Number of input PDB exceeds maxnpdb!")
+           status = 1
+           exit
+          endif
+          do i=1,npdb
+           if (index(trim(tmp),' ').gt.0) then
+            pdbfiles(i)=tmp(1:index(trim(tmp),' '))
+           else
+            pdbfiles(i)=tmp(1:len_trim(tmp))
+           endif
+           tmp=tmp(index(trim(tmp),' ')+1:len_trim(tmp))
           end do
          endif ! Koniec czytania "PDB="
-  
+
+c ALG=  
          if ((wiersz(1:4).eq.'ALG=').or.(wiersz(1:4).eq.'alg=')) then
           alg=wiersz(5:len_trim(wiersz))
           select case(alg)
@@ -861,27 +894,45 @@ c ======================================================================
             alg="csa"
             call write2log ("Unknown algorithm. Using 'csa' as default")
           end select
-         endif ! Koniec czytania "ALG="
+         endif 
 
+c GENERATIONS=
          select case (wiersz(1:12))
           case('GENERATIONS=','generations=')
            tmp = wiersz(13:len_trim(wiersz))
-           read(tmp,'(I)') maxgen 
-         end select ! Koniec czytania "GENERATIONS="
+           read(tmp,'(I4)') maxgen 
+         end select 
 
 c CICUTOFF=
-         select case(wiersz(1:9))
-          case('CICUTOFF=','cicutoff=')
-          tmp = wiersz(10:len_trim(wiersz))
-          read(tmp(1:len_trim(tmp)),'(F7.5)') cicutoff
-          call write2log("Initial CSA cutoff is set to "//tmp)
+c         select case(wiersz(1:9))
+c          case('CICUTOFF=','cicutoff=')
+c          tmp = wiersz(10:len_trim(wiersz))
+c          read(tmp(1:len_trim(tmp)),'(F7.5)') cicutoff
+c          call write2log("Initial CSA cutoff is set to "//tmp)
+c         end select
+
+c MINCO=
+         select case(wiersz(1:6))
+          case('MINCO=','minco=')
+          tmp = wiersz(7:len_trim(wiersz))
+          read(tmp(1:len_trim(tmp)),'(F7.5)') minco
+          call write2log("Minimal CSA cutoff factor is set to "//tmp)
+         end select
+
+c MAXCO=
+         select case(wiersz(1:6))
+          case('MAXCO=','maxco=')
+          tmp = wiersz(7:len_trim(wiersz))
+          read(tmp(1:len_trim(tmp)),'(F7.5)') maxco
+          call write2log("Maximal CSA cutoff factor is set to "//tmp)
          end select
 
+
 c POPULATION= 
          select case(wiersz(1:11))
           case('POPULATION=','population=')
            tmp = wiersz(12:len_trim(wiersz))
-           read(tmp,'(I)') banksize
+           read(tmp,'(I4)') banksize
            call write2log("Bank size is set to "//tmp)
          end select
 
@@ -939,7 +990,7 @@ c MAXMIN=
          select case(wiersz(1:7))
           case('MAXMIN=','maxmin=')
           tmp = wiersz(8:len_trim(wiersz))
-          read(tmp,'(I)') maxminstep
+          read(tmp,'(I4)') maxminstep
           if (maxminstep.gt.0) then
            call write2log("ZSCORE weights minimalization set to "//tmp)
            do_optima=.true.
@@ -1240,30 +1291,6 @@ c     &(i,13),pop(i,14),pop(i,15),pop(i,16),pop(i,17),pop(i,18),pop(i,19)
 c        enddo
 c       close(ow)
 
-c ==========================================
-c  Testcode before WHAM+ZSCORE integration
-c ==========================================
-c
-c      plik=trim(prefix)//"/"//trim(opopsumfn)
-c      !print *,trim(plik)
-c      open(opopsum, file = plik)
-c      write(opopsum,'(200A)') "# WLONG   WSCP    WELEC   WBOND   WANG 
-c    &   WSCLOC  WTOR    WTORD   WCORRH  WCORR4  WCORR5  WCORR6  WEL_LOC&
-c     & WTURN3  WTURN4  WTURN6  WVDWPP  WHPB    WSCCOR  SCORE"
-c      do I=1,rozmiar
-c       write(opopsum,FMT) pop(i,1),pop(i,2),pop(i,3),pop(i,4), pop(i,5)&
-c     &,pop(i,6),pop(i,7),pop(i,8),pop(i,9),pop(i,10),pop(i,11),pop(i,12)&
-c     &,pop(i,13),pop(i,14),pop(i,15),pop(i,16),pop(i,17),pop(i,18),pop(i&
-c     &,19),pop(i,20)
-c      end do
-c      close(opopsum)
-c ==========================================
-
-
-c        command="mkdir zscore"
-c      call system(command)
-
-       
       end subroutine CreateInputs
 
   
@@ -1297,8 +1324,8 @@ c        call write2log("Delta is "//tmp)
         if (delta.lt.mindelta) then
           mindelta=delta
           pozycja=i
-          write(tmp,'(F7.5,X,I)') delta,pozycja
-          call write2log("Delta is "//tmp)
+          write(tmp,'(F7.5,X,I4)') delta,pozycja
+          call write2log("  Delta is "//tmp)
         endif
       end do
 
@@ -1365,6 +1392,7 @@ c ----------------------------------------------------------------------
        write(ostate,'(I4)') generation
        write(ostate,'(L2)') do_optima
        write(ostate,'(L2)') do_ga
+       write(ostate,'(F7.5)') avrd
        close(ostate)
       end subroutine WriteState
  
@@ -1614,6 +1642,37 @@ c ----------------------------------------------------------------------
       end subroutine
 
 c ======================================================================
+c  WriteBankHistory subroutine
+c ======================================================================
+c  Writes CSA BANK History to file 
+c ----------------------------------------------------------------------
+      subroutine WriteBankHistory(b)
+       include 'io.inc'
+       include 'common.inc'
+       real*8,dimension(banksize,21) :: b  
+       character*250 :: tmptext
+       character*250 :: header   
+
+
+       header="#    WLONG      WSCP     WELEC     WBOND      WANG    WSC&
+     &LOC      WTOR     WTORD    WCORRH    WCORR4    WCORR5    WCORR6   &
+     &WEL_LOC    WTURN3    WTURN4    WTURN6    WVDWPP      WHPB    WSCCO&
+     &R            FFV   FITNESS" 
+       call write2log("Writing Bank history to file "//obankhfn)
+       open(obankh, file = obankhfn)
+       write(iobank, "(A)") trim(adjustl(header))
+       
+       do i=1,banksize
+        write(obankh,'(19F10.5,E15.7,F10.5)') (b(i,j),j=1,21)
+        write(tmptext,'(19F10.5,E15.7,F10.5)') (b(i,j),j=1,21)
+        call write2log(trim(tmptext))  
+       enddo 
+       close(iobank)
+      end subroutine
+
+c
+c ======================================================================
 c  ReadBank subroutine
 c ======================================================================
 c  Read CSA BANK from file
@@ -1660,6 +1719,30 @@ c        b(i,21)=b(i,20)/fitn
        fitn=sumfitn 
       end subroutine
 
+c ======================================================================
+c  CalcAvgDist subroutine
+c ======================================================================
+c  Calculates average distance between individuals in the bank
+c ----------------------------------------------------------------------
+      subroutine CalcAvgDist(b,avgd)
+       include 'common.inc'
+       real*8,dimension(banksize,21) :: b
+       real*8 :: d,avgd
+       integer*4 :: nd,w
+
+       d=0.0                          ! distance
+       nd = (banksize-1)*banksize/2   ! number of distances to calculate
+
+       do i=1,banksize-1
+        do j=i+1,banksize
+         do w=1,19
+          d=d+(b(i,w)-b(j,w))**2
+         end do
+        end do 
+       end do
+       avgd=sqrt(d)/nd
+      end subroutine
+
 c -----------------------------------------------------------------------