Changeset 32289cd for enyshe_p.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
  • enyshe_p.f

    r6650a56 r32289cd  
    11! **************************************************************
    22!
    3 ! This file contains the subroutines: enyshe 
     3! This file contains the subroutines: enyshe
    44!
    55! Copyright 2003-2005  Frank Eisenmenger, U.H.E. Hansmann,
    6 !                      Shura Hayryan, Chin-Ku 
     6!                      Shura Hayryan, Chin-Ku
    77! Copyright 2007       Frank Eisenmenger, U.H.E. Hansmann,
    88!                      Jan H. Meinke, Sandipan Mohanty
     
    1414
    1515!     ............................................................................
    16 !     
     16!
    1717!     PURPOSE: Calculate internal energy of molecule 'nml' with ECEPP parameters
    18 !     
     18!
    1919!     CALLS: none
    20 !     
     20!
    2121!     The function loops over all moving sets within the molecule. Within
    22 !     this loop it loops over the van-der-Waals domains of each atom in the 
     22!     this loop it loops over the van-der-Waals domains of each atom in the
    2323!     moving set and finally over the atoms that belong to the 1-4 interaction
    2424!     set.
     
    3131
    3232! If nml == 0 calculate the interaction between all pairs.
     33      double precision eysmsum, teysm, teyel, teyvw, teyhb, teyvr
     34      double precision startwtime, e0, vr, cqi, xi, yi, zi, xij, yij
     35      double precision zij, rij2, rij4, rij6, rij, sr, ep, endwtime
     36
     37      integer nml, ntlvr, ifivr, i1s, iend, istart, loopcounter, io, iv
     38      integer ia, it, ic, i2s, ims, i1, i2, i, ity, ivw, j, jty, i14
     39      integer ierror
     40
    3341      if (nml.eq.0) then
    3442         ntlvr = nvr
     
    3644         ntlvr=nvrml(nml)
    3745      endif
    38      
     46
    3947      if (ntlvr.eq.0) then
    4048         write (*,'(a,i4)')
     
    5664         ifivr = ivrml1(1)
    5765         i1s = imsml1(ntlml) + nmsml(ntlml)
    58       else 
     66      else
    5967!     Index of first variable in molecule.
    6068         ifivr=ivrml1(nml)
     
    6270         i1s=imsml1(nml)+nmsml(nml)
    6371      endif
    64 !     Loop over variables in reverse order     
     72!     Loop over variables in reverse order
    6573!     This is the first loop to parallize. We'll just split the moving sets
    6674!     over the number of available processors and sum the energy up in the end.
     
    7280      startwtime = MPI_Wtime()
    7381      loopcounter = 0
    74 !      do io=ifivr+ntlvr-1,ifivr,-1 
    75       do io = workPerProcessor(nml, myrank) - 1, 
     82!      do io=ifivr+ntlvr-1,ifivr,-1
     83      do io = workPerProcessor(nml, myrank) - 1,
    7684     &        workPerProcessor(nml, myrank+1), -1
    7785         if (io.lt.istart) then
     
    7987         endif
    8088!     The array iorvr contains the variables in an "apropriate" order.
    81          iv=iorvr(io)       
     89         iv=iorvr(io)
    8290!     Index of the primary moving atom for the variable with index iv
    83          ia=iatvr(iv)       
     91         ia=iatvr(iv)
    8492!     Get the type of variable iv (valence length, valence angle, dihedral angle)
    85          it=ityvr(iv)       
     93         it=ityvr(iv)
    8694!     Class of variable iv's potential  (Q: What are they)
    87          ic=iclvr(iv)       
     95         ic=iclvr(iv)
    8896!     If iv is a dihedral angle ...
    89          if (it.eq.3) then     
     97         if (it.eq.3) then
    9098!     Barrier height * 1/2 of the potential of iv.
    9199            e0=e0to(ic)
    92100!     Calculate the periodic potential term. sgto is the sign of the barrier, rnto is
    93101!     the periodicity and toat is torsion angle(?) associate with atom ia.
    94             if (e0.ne.0.) 
     102            if (e0.ne.0.)
    95103     &           teyvr=teyvr+e0*(1.0+sgto(ic)*cos(toat(ia)*rnto(ic)))
    96104!     else if iv is a valence angle ...
    97          elseif (it.eq.2) then 
     105         elseif (it.eq.2) then
    98106!     vr is the valence angle of ia
    99107            vr=baat(ia)
    100108!     else if iv is a valence length...
    101          elseif (it.eq.1) then 
     109         elseif (it.eq.1) then
    102110!     vr is the length of the valence bond
    103111            vr=blat(ia)
     
    108116         i2s=i1s-1
    109117!     index of first moving set associated with iv
    110          i1s=imsvr1(iv) 
     118         i1s=imsvr1(iv)
    111119!     Loop over all moving sets starting from the one associated with vr to the end.
    112          do ims=i1s,i2s 
     120         do ims=i1s,i2s
    113121!     First atom of the current moving set
    114122            i1=latms1(ims)
     
    116124            i2=latms2(ims)
    117125!     Loop over all atoms of the current moving set.
    118             do i=i1,i2 
     126            do i=i1,i2
    119127!     Atom class of current atom
    120128               ity=ityat(i)
     
    126134               zi=zat(i)
    127135!     Loop over the atoms of the van der Waals domain belonging to atom i
    128                do ivw=ivwat1(i),ivwat2(i) 
    129 !     Loop over the atoms of the van der Waals domain of the atoms of the 
     136               do ivw=ivwat1(i),ivwat2(i)
     137!     Loop over the atoms of the van der Waals domain of the atoms of the
    130138!     van der Waals domain of atom i
    131139!     Q: Which atoms are in these domains?
    132                   do j=lvwat1(ivw),lvwat2(ivw) 
     140                  do j=lvwat1(ivw),lvwat2(ivw)
    133141
    134142                     loopcounter = loopcounter + 1
     
    163171                     endif
    164172
    165                   enddo 
    166                enddo 
    167                
     173                  enddo
     174               enddo
     175
    168176!     Loop over 1-4 interaction partners
    169177!     The interactions between atoms that are three bonds apart in the protein are
    170178!     dominated by quantum mechanical effects. They are treated separately.
    171                do i14=i14at1(i),i14at2(i)   
     179               do i14=i14at1(i),i14at2(i)
    172180                  loopcounter = loopcounter + 1
    173181                  j=l14at(i14)
     
    210218
    211219!     Collect energies from all nodes and sum them up
    212       call MPI_ALLREDUCE(teysm, eysmsum, 1, MPI_DOUBLE_PRECISION, 
     220      call MPI_ALLREDUCE(teysm, eysmsum, 1, MPI_DOUBLE_PRECISION,
    213221     &     MPI_SUM, my_mpi_comm, ierror)
    214222      call MPI_ALLREDUCE(teyel, eyel, 1, MPI_DOUBLE_PRECISION, MPI_SUM,
    215223     &     my_mpi_comm, ierror)
    216       call MPI_ALLREDUCE(teyvw, eyvw, 1, MPI_DOUBLE_PRECISION, MPI_SUM, 
    217      &     my_mpi_comm, ierror)
    218       call MPI_ALLREDUCE(teyhb, eyhb, 1, MPI_DOUBLE_PRECISION, MPI_SUM, 
    219      &     my_mpi_comm, ierror)
    220       call MPI_ALLREDUCE(teyvr, eyvr, 1, MPI_DOUBLE_PRECISION, MPI_SUM, 
     224      call MPI_ALLREDUCE(teyvw, eyvw, 1, MPI_DOUBLE_PRECISION, MPI_SUM,
     225     &     my_mpi_comm, ierror)
     226      call MPI_ALLREDUCE(teyhb, eyhb, 1, MPI_DOUBLE_PRECISION, MPI_SUM,
     227     &     my_mpi_comm, ierror)
     228      call MPI_ALLREDUCE(teyvr, eyvr, 1, MPI_DOUBLE_PRECISION, MPI_SUM,
    221229     &     my_mpi_comm, ierror)
    222230
Note: See TracChangeset for help on using the changeset viewer.