Changeset 32289cd for bgs.f


Ignore:
Timestamp:
11/19/09 11:29:41 (14 years ago)
Author:
baerbaer <baerbaer@…>
Branches:
master
Children:
38d77eb
Parents:
6650a56
Message:

Explicitly declare variables.

git-svn-id: svn+ssh://svn.berlios.de/svnroot/repos/smmp/trunk@33 26dc1dd8-5c4e-0410-9ffe-d298b4865968

File:
1 edited

Legend:

Unmodified
Added
Removed
  • bgs.f

    r6650a56 r32289cd  
    22! Trial version implementing the semi-local conformational update
    33! BGS (Biased Gaussian Steps). This file presently contains the
    4 ! functions initlund, bgsposs and bgs. 
     4! functions initlund, bgsposs and bgs.
    55!
    66! Copyright 2007       Frank Eisenmenger, U.H.E. Hansmann,
     
    99
    1010
    11 ! Checks if it is possible to perform a BGS update starting at the 
     11! Checks if it is possible to perform a BGS update starting at the
    1212! variable indexed ipos. Calls: none.
    1313      logical function bgsposs(ips)
    1414      include 'INCL.H'
    1515      include 'incl_lund.h'
     16      integer jv, ips, iaa, nursvr, nnonfx, i
     17
    1618      logical ians
    1719
     
    2022      ians=.true.
    2123!      print *,'evaluating bgs possibility for ',ips,nmvr(jv)
    22       if (nmvr(jv).ne.'phi') then 
     24      if (nmvr(jv).ne.'phi') then
    2325!         print *,'bgs not possible because variable name is ',nmvr(jv)
    2426         ians=.false.
    25       else if (iaa.gt.(irsml2(mlvr(jv))-3)) then 
     27      else if (iaa.gt.(irsml2(mlvr(jv))-3)) then
    2628!         print *,'bgs impossible, residue too close to end'
    2729!         print *,'iaa = ',iaa,' end = ',irsml2(mlvr(jv))
    2830         ians=.false.
    29       else 
    30          nnonfx=0 
     31      else
     32         nnonfx=0
    3133         do i=iaa,iaa+3
    32             if (iphi(i).gt.0) then 
     34            if (iphi(i).gt.0) then
    3335               if (.not.fxvr(iphi(i))) then
    3436                  nnonfx=nnonfx+1
    3537               endif
    3638            endif
    37             if (.not.fxvr(ipsi(i))) then 
     39            if (.not.fxvr(ipsi(i))) then
    3840               nnonfx=nnonfx+1
    3941            endif
     
    5254
    5355! Biased Gaussian Steps. Implements a semi-local conformational update
    54 ! which modifies the protein backbone locally in a certain range of 
    55 ! amino acids. The 'down-stream' parts of the molecule outside the 
     56! which modifies the protein backbone locally in a certain range of
     57! amino acids. The 'down-stream' parts of the molecule outside the
    5658! region of update get small rigid body translations and rotations.
    5759!
    58 ! Use the update sparingly. It is rather local, and is not of great 
     60! Use the update sparingly. It is rather local, and is not of great
    5961! value if we need big changes in the conformation. It is recommended
    60 ! that this update be used to refine a structure around a low energy 
     62! that this update be used to refine a structure around a low energy
    6163! candidate structure. Even at low energies, if you always
    62 ! perform BGS, the chances of coming out of that minimum are small. 
    63 ! So, there is a probability bgsprob, which decides whether BGS or the 
    64 ! normal single angle update is used. 
     64! perform BGS, the chances of coming out of that minimum are small.
     65! So, there is a probability bgsprob, which decides whether BGS or the
     66! normal single angle update is used.
    6567!
    6668! Calls: energy, dummy (function provided as argument), addang, (rand)
     
    7072      include 'INCL.H'
    7173      include 'incl_lund.h'
     74      double precision grnd, xiv, bv, ab, rv, dv, a, sum, p, r1, r2
     75      double precision ppsi, wfw, addang, enw, energy, wbw, rd, delta
     76      double precision dummy, eol1
     77
     78      integer ivar, i, nph, jv, ia, nursvr, icurraa, j, k, l
     79
    7280      external dummy
    7381      dimension xiv(8,3),bv(8,3),rv(3,3),dv(3,8,3)
     
    7684! Initialize
    7785!      print *,'using BGS on angle ',nmvr(idvr(ivar))
    78       if (bgsnvar.eq.0) then 
     86      if (bgsnvar.eq.0) then
    7987         bgs=0
    8088         goto 171
     
    9199      do i=1,4
    92100         icurraa=ia+i-1
    93          if (iphi(icurraa).gt.0.and..not.fxvr(iphi(icurraa))) then 
     101         if (iphi(icurraa).gt.0.and..not.fxvr(iphi(icurraa))) then
    94102            nph=nph+1
    95103            xiv(nph,1)=xat(iCa(icurraa))
     
    102110     &           +bv(nph,3)*bv(nph,3)
    103111            iph(nph)=iphi(icurraa)
    104          endif 
     112         endif
    105113         if (.not.fxvr(ipsi(icurraa))) then
    106114            nph=nph+1
     
    136144         enddo
    137145      enddo
    138       do i=1,nph 
     146      do i=1,nph
    139147         do j=i,nph
    140148            A(i,j)=0
     
    157165               sum=sum-A(i,k)*A(j,k)
    158166            enddo
    159             if (i.eq.j) then 
    160                p(i)=sqrt(sum) 
    161             else 
     167            if (i.eq.j) then
     168               p(i)=sqrt(sum)
     169            else
    162170               A(j,i)=sum/p(i)
    163171            endif
     
    177185         dph(i)=0
    178186      enddo
    179 ! Solve lower triangular matrix to get dphi proposals 
     187! Solve lower triangular matrix to get dphi proposals
    180188      do i=nph,1,-1
    181189         sum=ppsi(i)
     
    190198      do i=1,nph
    191199         sum=sum+ppsi(i)*ppsi(i)
    192       enddo 
     200      enddo
    193201      wfw=exp(-sum)
    194202      do i=1,nph
     
    208216      do i=1,4
    209217         icurraa=ia+i-1
    210          if (iphi(icurraa).gt.0.and..not.fxvr(iphi(icurraa))) then 
     218         if (iphi(icurraa).gt.0.and..not.fxvr(iphi(icurraa))) then
    211219            nph=nph+1
    212220            xiv(nph,1)=xat(iCa(icurraa))
     
    219227     &           +bv(nph,3)*bv(nph,3)
    220228            iph(nph)=iphi(icurraa)
    221          endif 
    222          if (.not.fxvr(ipsi(icurraa))) then 
     229         endif
     230         if (.not.fxvr(ipsi(icurraa))) then
    223231            nph=nph+1
    224232            xiv(nph,1)=xat(iC(icurraa))
     
    253261         enddo
    254262      enddo
    255       do i=1,nph 
     263      do i=1,nph
    256264         do j=i,nph
    257265            A(i,j)=0
     
    262270            enddo
    263271            A(i,j)=bbgs*A(i,j)
    264             if (i.eq.j) then 
     272            if (i.eq.j) then
    265273               A(i,j)=A(i,j)+1
    266274            endif
     
    274282               sum=sum-A(i,k)*A(j,k)
    275283            enddo
    276             if (i.eq.j) then 
    277                p(i)=sqrt(sum) 
    278             else 
     284            if (i.eq.j) then
     285               p(i)=sqrt(sum)
     286            else
    279287               A(j,i)=sum/p(i)
    280288            endif
     
    285293         do j=i+1,nph
    286294            ppsi(i)=ppsi(i)+A(j,i)*dph(j)
    287          enddo 
     295         enddo
    288296      enddo
    289297      sum=0
     
    291299         sum=sum+ppsi(i)*ppsi(i)
    292300      enddo
    293       wbw=exp(-sum) 
     301      wbw=exp(-sum)
    294302      do i=1,nph
    295303         wbw=wbw*p(i)
     
    306314!       call outpdb(0,'after.pdb')
    307315!      print *,'after outpdb for after.pdb'
    308 !      do i=1,nph 
     316!      do i=1,nph
    309317!         print *,'BGS>',i,iph(i),vlvr(iph(i)),dph(i)
    310318!      enddo
    311       if (rd.ge.delta) then 
     319      if (rd.ge.delta) then
    312320!     accept
    313321         eol1=enw
    314322         bgs=1
    315323!         print *,'BGS move accepted'
    316       else 
     324      else
    317325!     reject
    318326         vlvr = ovr
Note: See TracChangeset for help on using the changeset viewer.