Merge branch 'feature-ga' of mmka:unres into feature-ga
authorDawid Jagiela <lightnir@chem.univ.gda.pl>
Mon, 12 Mar 2012 12:20:25 +0000 (13:20 +0100)
committerDawid Jagiela <lightnir@chem.univ.gda.pl>
Mon, 12 Mar 2012 12:20:25 +0000 (13:20 +0100)
source/ga/GA.f
source/ga/common.inc
source/ga/input-templates/matrix/start_all.pbs

index 13af8fe..cfb58a3 100644 (file)
@@ -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,8 +78,11 @@ 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)
+       write(tmptext,'(I4)') generation 
+       call write2log("This is genaration "//tmptext)
        if (do_ga) then
         call write2log("Doing GA in this step")
        endif
@@ -98,6 +97,8 @@ c No. Prepere next generation
 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 
@@ -146,17 +147,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 +165,14 @@ c --- debug begin ---
         endif
 c --- debug end ---
          call GetNBest(populacja,bank,banksize)
+         call CalcAvgDist(bank,avrd)
+         write(tmptext,'(F7.5)') csacutoff
+         call write2log("CSA cutoff is now set to "//tmptext)
+          csacutoff=(maxco*avrd)-generation*avrd*(maxco-minco)/maxgen
+c         csacutoff=maxco*avrd         
+
+         
+
 c --- debug begin ---
         if (debug) then
          do i=1,banksize
@@ -187,7 +196,9 @@ c --- debug begin ---
 c --- debug end ---
 
          call ReadBank(bank)
-
+         write(tmptext,'(F7.5)') avrd
+         call write2log("Average distance in bank is "//trim(tmptext))
+  
          do i=1,BANK_MULTIPLIER*banksize
           write(tmptext,'(I4)') i
           call write2log("Checking ind "//tmptext)  
@@ -229,11 +240,12 @@ c --- debug begin ---
 c --- debug end ---
 
          call WriteBank(bank)
-         csacutoff=csacutoff-(generation*cicutoff/maxgen)
+
+         csacutoff=maxco*avrd-generation*avrd*(maxco-minco)/maxgen
+c         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')
@@ -397,8 +409,8 @@ c
 c Create the inputs
 c 
       write(tmptext,'(I)') generation
-      call write2log("Preparing inputs for generation "//trim(adjustl(tm&
-     &ptext)))
+      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.
@@ -579,7 +591,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)
@@ -810,7 +821,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 +831,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,22 +873,40 @@ 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="
+         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=')
@@ -1240,30 +1270,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
 
   
@@ -1365,6 +1371,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
  
@@ -1660,6 +1667,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
+
+       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 -----------------------------------------------------------------------
 
 
index 11f004a..b392108 100644 (file)
@@ -5,12 +5,14 @@
       integer*4 :: nscripts = 0              ! number of shell scripts to copy
       integer*4 :: maxgen = 0                ! maximum number of generations
       integer*4 :: banksize = 0              ! size of bank 
-      integer*4 :: generation = 1            ! current generation
+      integer*4 :: generation = 0            ! current generation
       integer*4 :: maxminstep = 0            ! max minimalization to be done by zscore
       integer*4,parameter :: maxnpdb = 10    ! hard limit for maximum number of proteins
       integer*4,parameter :: maxscripts = 10 
-      real*8 :: cicutoff = 5.0               ! CSA initial cutoff 
       real*8 :: csacutoff = 0.0              ! CSA cutoff
+      real*8 :: minco = 0.0                  ! minimal CSA cutoff factor
+      real*8 :: maxco = 0.0                  ! maximal CSA cutoff factor
+      real*8 :: avrd = 0.0                  ! average distance between ind in first bank  
       logical :: do_optima = .false.
       logical :: do_ga = .false.
       logical :: do_fs = .false.
       character*32 :: mremdtemplate(maxnpdb)
       character*16 :: alg
       
-      common /inputy/ npdb,nscripts,ntwham,ntmremd,maxgen,banksize,cicut&
-     &off,csacutoff,alg,pdbfiles,scripts,whamtemplate,mremdtemplate,gene&
-     &ration,maxminstep,do_optima, do_ga
+      common /inputy/ npdb,nscripts,ntwham,ntmremd,maxgen,banksize,csacu&
+     &toff,avrd,minco,maxco,alg,pdbfiles,scripts,whamtemplate,mremdtempl&
+     &ate,generation,maxminstep,do_optima, do_ga
       character*7 :: version = "1.1.1"
-      character*50 :: info = "= Last modified by Lightnir 09/01/2012"
+      character*50 :: info = "= Last modified by Lightnir 09/03/2012"
       real*8,allocatable :: bank(:,:),populacja(:,:),temppopulacja(:,:)
       integer*4, allocatable :: pairs(:)
index 83d4130..3a7a92c 100755 (executable)
@@ -1,4 +1,4 @@
-#PBS -N single-test
+#PBS -N 1LE1-1LY2
 #PBS -q dque
 #PBS -l nodes=32:ppn=8
 #PBS -l walltime=1:00:00