ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/sticky.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/sticky.F90 (file contents):
Revision 2231 by chrisfen, Wed May 18 18:31:40 2005 UTC vs.
Revision 2361 by gezelter, Wed Oct 12 21:00:50 2005 UTC

# Line 50 | Line 50
50   !! @author Matthew Meineke
51   !! @author Christopher Fennell
52   !! @author J. Daniel Gezelter
53 < !! @version $Id: sticky.F90,v 1.11 2005-05-18 18:31:40 chrisfen Exp $, $Date: 2005-05-18 18:31:40 $, $Name: not supported by cvs2svn $, $Revision: 1.11 $
53 > !! @version $Id: sticky.F90,v 1.17 2005-10-12 21:00:50 gezelter Exp $, $Date: 2005-10-12 21:00:50 $, $Name: not supported by cvs2svn $, $Revision: 1.17 $
54  
55   module sticky
56  
# Line 66 | Line 66 | module sticky
66    implicit none
67  
68    PRIVATE
69 + #define __FORTRAN90
70 + #include "UseTheForce/DarkSide/fInteractionMap.h"
71  
72    public :: newStickyType
73    public :: do_sticky_pair
74    public :: destroyStickyTypes
75    public :: do_sticky_power_pair
76 +  public :: getStickyCut
77 +  public :: getStickyPowerCut
78  
75
79    type :: StickyList
80       integer :: c_ident
81       real( kind = dp ) :: w0 = 0.0_dp
# Line 147 | Line 150 | contains
150  
151      return
152    end subroutine newStickyType
153 +
154 +  function getStickyCut(atomID) result(cutValue)
155 +    integer, intent(in) :: atomID
156 +    real(kind=dp) :: cutValue
157 +
158 +    cutValue = StickyMap(atomID)%rbig
159 +  end function getStickyCut
160 +
161 +  function getStickyPowerCut(atomID) result(cutValue)
162 +    integer, intent(in) :: atomID
163 +    real(kind=dp) :: cutValue
164  
165 +    cutValue = StickyMap(atomID)%rbig
166 +  end function getStickyPowerCut
167 +
168    subroutine do_sticky_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
169         pot, A, f, t, do_pot)
170  
# Line 291 | Line 308 | contains
308         vpair = vpair + 0.5d0*(v0*s*w + v0p*sp*wp)
309         if (do_pot) then
310   #ifdef IS_MPI
311 <          pot_row(atom1) = pot_row(atom1) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
312 <          pot_col(atom2) = pot_col(atom2) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
311 >          pot_row(HB_POT,atom1) = pot_row(HB_POT,atom1) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
312 >          pot_col(HB_POT,atom2) = pot_col(HB_POT,atom2) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
313   #else
314            pot = pot + 0.5d0*(v0*s*w + v0p*sp*wp)*sw
315   #endif  
# Line 512 | Line 529 | contains
529      if(allocated(StickyMap)) deallocate(StickyMap)
530    end subroutine destroyStickyTypes
531    
532 <    subroutine do_sticky_power_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
533 <       pot, A, f, t, do_pot, ebalance)
532 >  subroutine do_sticky_power_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
533 >       pot, A, f, t, do_pot)
534      !! We assume that the rotation matrices have already been calculated
535      !! and placed in the A array.
536 <
536 >    
537      !! i and j are pointers to the two SSD atoms
538 <
538 >    
539      integer, intent(in) :: atom1, atom2
540      real (kind=dp), intent(inout) :: rij, r2
541      real (kind=dp), dimension(3), intent(in) :: d
# Line 527 | Line 544 | contains
544      real (kind=dp), dimension(9,nLocal) :: A
545      real (kind=dp), dimension(3,nLocal) :: f
546      real (kind=dp), dimension(3,nLocal) :: t
530    real (kind=dp), intent(in) :: ebalance
547      logical, intent(in) :: do_pot
548  
549      real (kind=dp) :: xi, yi, zi, xj, yj, zj, xi2, yi2, zi2, xj2, yj2, zj2
550      real (kind=dp) :: xihat, yihat, zihat, xjhat, yjhat, zjhat
551      real (kind=dp) :: rI, rI2, rI3, rI4, rI5, rI6, rI7, s, sp, dsdr, dspdr
552 <    real (kind=dp) :: wi, wj, w, wi2, wj2
552 >    real (kind=dp) :: wi, wj, w, wi2, wj2, eScale, v0scale
553      real (kind=dp) :: dwidx, dwidy, dwidz, dwjdx, dwjdy, dwjdz
554      real (kind=dp) :: dwidux, dwiduy, dwiduz, dwjdux, dwjduy, dwjduz
555      real (kind=dp) :: drdx, drdy, drdz
# Line 651 | Line 667 | contains
667        
668         call calc_sw_fnc(rij, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
669            
670 <       frac1 = 0.6d0
671 <       frac2 = 0.0d0
670 >       frac1 = 0.25d0
671 >       frac2 = 0.75d0
672        
673         wi = 2.0d0*(xi2-yi2)*zi*rI3
674         wj = 2.0d0*(xj2-yj2)*zj*rI3
# Line 660 | Line 676 | contains
676         wi2 = wi*wi
677         wj2 = wj*wj
678  
679 <       w = frac1*wi*wi2 + frac2*wi + frac1*wj*wj2 + frac2*wj
679 >       w = frac1*wi*wi2 + frac2*wi + frac1*wj*wj2 + frac2*wj + v0p
680  
681 <       vpair = vpair + 0.5d0*(v0*s*w) + ebalance
681 >       vpair = vpair + 0.5d0*(v0*s*w)
682        
683         if (do_pot) then
684   #ifdef IS_MPI
685 <         pot_row(atom1) = pot_row(atom1) + 0.25d0*(v0*s*w)*sw
686 <         pot_col(atom2) = pot_col(atom2) + 0.25d0*(v0*s*w)*sw
685 >         pot_row(HB_POT,atom1) = pot_row(HB_POT,atom1) + 0.25d0*(v0*s*w)*sw
686 >         pot_col(HB_POT,atom2) = pot_col(HB_POT,atom2) + 0.25d0*(v0*s*w)*sw
687   #else
688 <         pot = pot + 0.5d0*(v0*s*w)*sw + ebalance
688 >         pot = pot + 0.5d0*(v0*s*w)*sw
689   #endif  
690         endif
691  
# Line 805 | Line 821 | contains
821  
822         ! now assemble these with the radial-only terms:
823  
824 <       fxradial = 0.5d0*(v0*dsdr*w*drdx + fxii + fxji + ebalance*xihat)
825 <       fyradial = 0.5d0*(v0*dsdr*w*drdy + fyii + fyji + ebalance*yihat)
826 <       fzradial = 0.5d0*(v0*dsdr*w*drdz + fzii + fzji + ebalance*zihat)
824 >       fxradial = 0.5d0*(v0*dsdr*w*drdx + fxii + fxji)
825 >       fyradial = 0.5d0*(v0*dsdr*w*drdy + fyii + fyji)
826 >       fzradial = 0.5d0*(v0*dsdr*w*drdz + fzii + fzji)
827  
828   #ifdef IS_MPI
829         f_Row(1,atom1) = f_Row(1,atom1) + fxradial

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines