Changeset bd2278d for opereg.f


Ignore:
Timestamp:
09/05/08 11:49:42 (16 years ago)
Author:
baerbaer <baerbaer@…>
Branches:
master
Children:
fafe4d6
Parents:
2ebb8b6
Message:

Reformatting comments and continuation marks.

Fortran 90 and higher use ! to mark comments no matter where they are in the
code. The only valid continuation marker is &.
I also added the SMMP.kdevelop.filelist to the repository to make it easier
to use kdevelop.

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • opereg.f

    r2ebb8b6 rbd2278d  
    1 c **************************************************************
    2 c
    3 c This file contains the subroutines: opereg,gdtgbl,gdtreg
    4 c
    5 c Copyright 2003-2005  Frank Eisenmenger, U.H.E. Hansmann,
    6 c                      Shura Hayryan, Chin-Ku
    7 c Copyright 2007       Frank Eisenmenger, U.H.E. Hansmann,
    8 c                      Jan H. Meinke, Sandipan Mohanty
    9 c
    10 c **************************************************************
     1! **************************************************************
     2!
     3! This file contains the subroutines: opereg,gdtgbl,gdtreg
     4!
     5! Copyright 2003-2005  Frank Eisenmenger, U.H.E. Hansmann,
     6!                      Shura Hayryan, Chin-Ku
     7! Copyright 2007       Frank Eisenmenger, U.H.E. Hansmann,
     8!                      Jan H. Meinke, Sandipan Mohanty
     9!
     10! **************************************************************
    1111
    1212      subroutine opereg(nml)
    1313
    14 c .......................................................................
    15 c PURPOSE: calculate regul. energy & it's partial derivatives
    16 c          for molecule 'nml' vs. variables 'iv'
    17 c
    18 c  NB: if the unit axis for an internal variable coincides with a
    19 c      global axis (i.e. for torsion or bond length variation round
    20 c      or along 'xrfax', respectively, and bd. angle var. round
    21 c      'zrfax'): VdW & 14 interaction partners of moving set atoms
    22 c      should be used for calculation, instead of the mov. sets,
    23 c      with opposite sign.
    24 c
    25 c      Example: By the the way the molecule-fixed system is set up,
    26 c               changes in Phi_1 affect atomic positions BEFORE the
    27 c               N-C^alpha bond relatively to the space-fixed system,
    28 c               not the moving set of Phi_1.
    29 c
    30 c CALLS:    gdtgbl, gdtreg
    31 c ......................................................................
     14! .......................................................................
     15! PURPOSE: calculate regul. energy & it's partial derivatives
     16!          for molecule 'nml' vs. variables 'iv'
     17!
     18!  NB: if the unit axis for an internal variable coincides with a
     19!      global axis (i.e. for torsion or bond length variation round
     20!      or along 'xrfax', respectively, and bd. angle var. round
     21!      'zrfax'): VdW & 14 interaction partners of moving set atoms
     22!      should be used for calculation, instead of the mov. sets,
     23!      with opposite sign.
     24!
     25!      Example: By the the way the molecule-fixed system is set up,
     26!               changes in Phi_1 affect atomic positions BEFORE the
     27!               N-C^alpha bond relatively to the space-fixed system,
     28!               not the moving set of Phi_1.
     29!
     30! CALLS:    gdtgbl, gdtreg
     31! ......................................................................
    3232
    3333      include 'INCL.H'
     
    3535
    3636      dimension xfat(mxat),yfat(mxat),zfat(mxat),
    37      #          xfrat(mxat),yfrat(mxat),zfrat(mxat),
    38 
    39      #          xfvr(mxvr),yfvr(mxvr),zfvr(mxvr),
    40      #          xfrvr(mxvr),yfrvr(mxvr),zfrvr(mxvr)
     37     &          xfrat(mxat),yfrat(mxat),zfrat(mxat),
     38
     39     &          xfvr(mxvr),yfvr(mxvr),zfvr(mxvr),
     40     &          xfrvr(mxvr),yfrvr(mxvr),zfrvr(mxvr)
    4141
    4242      logical   lnb
     
    4646      if (ntlvr.eq.0) then
    4747        write (*,'(a,i4)')
    48      #           ' opereg> No variables defined in molecule #',nml
     48     &           ' opereg> No variables defined in molecule #',nml
    4949        return
    5050      endif
     
    5555      ilavr=ifivr+ntlvr-1       ! last var. of 'nml'
    5656
    57 c --------------------------- initializations
     57! --------------------------- initializations
    5858      do i=ifivr,ilavr
    5959        gdeyrg(i)=0.d0
     
    107107          dz = 2.d0 * zji
    108108
    109 c =============================================== global pars.
     109! =============================================== global pars.
    110110
    111111          gdeygb(ii+1) = gdeygb(ii+1) - dx   ! d(E_ij) / d(x_i)
     
    113113          gdeygb(ii+3) = gdeygb(ii+3) - dz   ! d(E_ij) / d(z_i)
    114114
    115 c -------------------------- r = r_i - r_1
     115! -------------------------- r = r_i - r_1
    116116          x = xi - x1
    117117          y = yi - y1
     
    123123
    124124          gdeygb(ii+6) = gdeygb(ii+6) +dx*(zk*y-yk*z)+dy*(xk*z-zk*x)  !  d(E_ij) / d(g)
    125      #                                +dz*(yk*x-xk*y)
    126 
    127 c =============================================== for internal vars.
     125     &                                +dz*(yk*x-xk*y)
     126
     127! =============================================== for internal vars.
    128128
    129129          xfat(i) = dx
     
    164164        zb=zat(ib)
    165165
    166 c ---------------------------------------- axis for var.
     166! ---------------------------------------- axis for var.
    167167
    168168        if (it.eq.3) then      ! torsion
     
    279279
    280280          gdeyrg(iv)= (ey*zb-ez*yb)*xfiv+(ez*xb-ex*zb)*yfiv+
    281      #                (ex*yb-ey*xb)*zfiv
    282      #               +ex*xfriv+ey*yfriv+ez*zfriv
     281     &                (ex*yb-ey*xb)*zfiv
     282     &               +ex*xfriv+ey*yfriv+ez*zfriv
    283283
    284284        elseif (it.eq.1) then         ! b.length
     
    294294      return
    295295      end
    296 c **************************
     296! **************************
    297297      subroutine gdtgbl(nml)
    298 C
    299 C CALLS: bldmol,enyreg
    300 c
    301 c -------------------------- gradtest for 'gbpr'
     298!
     299! CALLS: bldmol,enyreg
     300!
     301! -------------------------- gradtest for 'gbpr'
    302302
    303303      include 'INCL.H'
     
    310310      do i = 1,6
    311311
    312 c ----------------------------- modify
     312! ----------------------------- modify
    313313        pro = gbpr(i,nml)
    314314        gbpr(i,nml) = pro+del
     
    318318
    319319        write (*,*) ' Gb. var #',(ii+i),': ',gdeygb(ii+i),gdn,
    320      #                                   abs(gdn-gdeygb(ii+i))
    321 c ----------------------------- restore
     320     &                                   abs(gdn-gdeygb(ii+i))
     321! ----------------------------- restore
    322322        gbpr(i,nml) = pro
    323323        call bldmol(nml)
     
    327327      return
    328328      end
    329 c *****************************
     329! *****************************
    330330      subroutine gdtreg(nml,iv)
    331331
    332 c .................................................................
    333 c PURPOSE: calculate partial derivative of reg. energy for molecule
    334 c          'nml' vs. variable 'iv' NUMERICALLY and compare with
    335 c          its value obtained analytically
    336 c
    337 c CALLS:  setvar, enyreg
    338 c .................................................................
     332! .................................................................
     333! PURPOSE: calculate partial derivative of reg. energy for molecule
     334!          'nml' vs. variable 'iv' NUMERICALLY and compare with
     335!          its value obtained analytically
     336!
     337! CALLS:  setvar, enyreg
     338! .................................................................
    339339
    340340      include 'INCL.H'
     
    344344      dimension vlvrx(mxvr)
    345345
    346 c ____________________________ get & save values of variables
     346! ____________________________ get & save values of variables
    347347      do i=1,ivrml1(ntlml)+nvrml(ntlml)-1
    348348        it=ityvr(i)  ! type
     
    366366
    367367      write (*,'(1x,2a,2(e12.6,a))') nmvr(iv),': ',gda,' (',
    368      #       abs(gda-gdn),')'
    369 
    370 c _________________________ restore vars
     368     &       abs(gda-gdn),')'
     369
     370! _________________________ restore vars
    371371      vlvrx(iv)=ovr
    372372      call setvar(nml,vlvrx)
Note: See TracChangeset for help on using the changeset viewer.