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

    r6650a56 r32289cd  
    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
     
    1010! **************************************************************
    1111
    12      
     12
    1313      real*8 function enysol(nmol)
    1414
     
    1919!
    2020!     Double Cubic Lattice algorithm for calculating the
    21 !     solvation energy of proteins using 
     21!     solvation energy of proteins using
    2222!     solvent accessible area method.
    2323!
     
    2626!
    2727! -------------------------------------------------------------
    28 ! TODO: Check the solvent energy for multiple molecules     
     28! TODO: Check the solvent energy for multiple molecules
     29      double precision startwtime, avr_x, avr_y, avr_z, xmin, ymin, zmin
     30      double precision xmax, ymax, zmax, rmax, diamax, sizex, sizey
     31      double precision sizez, shiftx, shifty, shiftz, boxpp, trad, dx
     32      double precision dy, dz, dd, akrad, dr, xyz, radb, radb2, sdd, sdr
     33      double precision area, volume, eyslsum, endwtime
     34
     35      integer nmol, nrslow, nrshi, nlow, nup, i, numat, inbox, j, ndx
     36      integer ndy, ndz, nqxy, ncbox, mx, my, mz, nboxj, numbox, jj
     37      integer indsort, iboxmin, iboxmax, ibox, iz, iy, ix, lbn, nsx, nsy
     38      integer nsz, nex, ney, nez, jcnt, jz, jy, jx, jbox, ii, look, ia
     39      integer jbi, nnei, ib, jtk, il, lst, ilk, ik, icount, jres, nursat
     40      integer ierror, nhx, mhx, nbt, mbt
     41
    2942      dimension numbox(mxat),inbox(mxbox+1),indsort(mxat),look(mxat)
    3043      dimension xyz(mxinbox,3),radb(mxinbox),radb2(mxinbox)
     
    3346
    3447!       common/ressurf/surfres(mxrs)
    35       real*8 tsurfres(mxrs) 
     48      real*8 tsurfres(mxrs)
    3649      startwtime = MPI_Wtime()
    3750      root = 0
     
    5063      do i=nrslow,nrshi
    5164       surfres(i) = 0.0d0
    52       end do 
     65      end do
    5366
    5467      numat= nup - nlow + 1
     
    5770         inbox(i)=0
    5871      end do
    59      
     72
    6073      asa=0.0d0
    6174      vdvol=0.0d0
     
    124137       stop
    125138      end if
    126        
     139
    127140! Let us shift the borders to home all boxes
    128141
     
    164177        inbox(i+1)=inbox(i+1)+inbox(i)
    165178      end do
    166          
    167        
     179
     180
    168181!   Sorting the atoms by the their box numbers
    169182
     
    173186         indsort(jj)=i
    174187         inbox(j)=jj-1
    175       end do   
    176          
     188      end do
     189
    177190!    Getting started
    178191!    We have to loop over ncbox boxes and have no processors available
     
    202215             ney=min(iy+1,ndy-1)
    203216             nez=min(iz+1,ndz-1)
    204                      
     217
    205218!  Atoms in the boxes around
    206219
     
    218231               end do
    219232              end do
    220              end do     
    221                              
     233             end do
     234
    222235             do  ia=inbox(ibox)+1,inbox(ibox+1)
    223236               jbi=indsort(ia)
     
    271284                     end do
    272285 99                  continue
    273    
     286
    274287                     if(ik.gt.nnei)then
    275288                       surfc(il)=.true.
     
    313326                 surfres(jres) = surfres(jres) + area
    314327               end if
    315              end do 
     328             end do
    316329           end if
    317330!           end do
    318331!          end do
    319332       end do
    320       call MPI_ALLREDUCE(eysl, eyslsum, 1, MPI_DOUBLE_PRECISION, 
     333      call MPI_ALLREDUCE(eysl, eyslsum, 1, MPI_DOUBLE_PRECISION,
    321334     &      MPI_SUM,my_mpi_comm, ierror)
    322335!       write(*,*) 'enysol>', myrank, eysl, eyslsum
    323336      tsurfres = surfres
    324       call MPI_ALLREDUCE(tsurfres, surfres, mxrs, MPI_DOUBLE_PRECISION, 
     337      call MPI_ALLREDUCE(tsurfres, surfres, mxrs, MPI_DOUBLE_PRECISION,
    325338     &      MPI_SUM,my_mpi_comm, ierror)
    326339      eysl = eyslsum
    327      
     340
    328341      endwtime = MPI_Wtime()
    329342      if (myrank.le.-1) then
     
    349362      subroutine tessel
    350363      include 'INCL.H'
     364      integer i
     365
    351366      character lin*80
    352367
    353 !    Skipping comment lines, which begin with '!' 
     368!    Skipping comment lines, which begin with '!'
    354369
    355370      read(20,'(a)') lin
     
    363378!        write(*,'(a,i5)') 'the number of points---->',npnt
    364379
    365 !    Read the surface points   
     380!    Read the surface points
    366381
    367382      do i=1,npnt
    368383         read(20,'(3f20.10)') spoint(i,1),spoint(i,2),spoint(i,3)
    369          
     384
    370385!        write(31,'(3f20.10)') spoint(i,1),spoint(i,2),spoint(i,3)
    371386      end do
    372  
     387
    373388      return
    374  
     389
    375390      end
    376391
Note: See TracChangeset for help on using the changeset viewer.