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 1621 by gezelter, Wed Oct 20 21:52:20 2004 UTC vs.
Revision 2204 by gezelter, Fri Apr 15 22:04:00 2005 UTC

# Line 1 | Line 1
1 + !!
2 + !! Copyright (c) 2005 The University of Notre Dame. All Rights Reserved.
3 + !!
4 + !! The University of Notre Dame grants you ("Licensee") a
5 + !! non-exclusive, royalty free, license to use, modify and
6 + !! redistribute this software in source and binary code form, provided
7 + !! that the following conditions are met:
8 + !!
9 + !! 1. Acknowledgement of the program authors must be made in any
10 + !!    publication of scientific results based in part on use of the
11 + !!    program.  An acceptable form of acknowledgement is citation of
12 + !!    the article in which the program was described (Matthew
13 + !!    A. Meineke, Charles F. Vardeman II, Teng Lin, Christopher
14 + !!    J. Fennell and J. Daniel Gezelter, "OOPSE: An Object-Oriented
15 + !!    Parallel Simulation Engine for Molecular Dynamics,"
16 + !!    J. Comput. Chem. 26, pp. 252-271 (2005))
17 + !!
18 + !! 2. Redistributions of source code must retain the above copyright
19 + !!    notice, this list of conditions and the following disclaimer.
20 + !!
21 + !! 3. Redistributions in binary form must reproduce the above copyright
22 + !!    notice, this list of conditions and the following disclaimer in the
23 + !!    documentation and/or other materials provided with the
24 + !!    distribution.
25 + !!
26 + !! This software is provided "AS IS," without a warranty of any
27 + !! kind. All express or implied conditions, representations and
28 + !! warranties, including any implied warranty of merchantability,
29 + !! fitness for a particular purpose or non-infringement, are hereby
30 + !! excluded.  The University of Notre Dame and its licensors shall not
31 + !! be liable for any damages suffered by licensee as a result of
32 + !! using, modifying or distributing the software or its
33 + !! derivatives. In no event will the University of Notre Dame or its
34 + !! licensors be liable for any lost revenue, profit or data, or for
35 + !! direct, indirect, special, consequential, incidental or punitive
36 + !! damages, however caused and regardless of the theory of liability,
37 + !! arising out of the use of or inability to use software, even if the
38 + !! University of Notre Dame has been advised of the possibility of
39 + !! such damages.
40 + !!
41 +
42   !! This Module Calculates forces due to SSD potential and VDW interactions
43   !! [Chandra and Ichiye, J. Chem. Phys. 111, 2701 (1999)].
44  
# Line 7 | Line 48
48   !! Corresponds to the force field defined in ssd_FF.cpp
49   !! @author Charles F. Vardeman II
50   !! @author Matthew Meineke
51 < !! @author Christopher Fennel
51 > !! @author Christopher Fennell
52   !! @author J. Daniel Gezelter
53 < !! @version $Id: sticky.F90,v 1.2 2004-10-20 21:52:20 gezelter Exp $, $Date: 2004-10-20 21:52:20 $, $Name: not supported by cvs2svn $, $Revision: 1.2 $
53 > !! @version $Id: sticky.F90,v 1.7 2005-04-15 22:03:49 gezelter Exp $, $Date: 2005-04-15 22:03:49 $, $Name: not supported by cvs2svn $, $Revision: 1.7 $
54  
55 < module sticky_pair
55 > module sticky
56  
57    use force_globals
58    use definitions
59 +  use atype_module
60 +  use vector_class
61    use simulation
62 +  use status
63   #ifdef IS_MPI
64    use mpiSimulation
65   #endif
22
66    implicit none
67  
68    PRIVATE
69  
70 <  logical, save :: sticky_initialized = .false.
28 <  real( kind = dp ), save :: SSD_w0 = 0.0_dp
29 <  real( kind = dp ), save :: SSD_v0 = 0.0_dp
30 <  real( kind = dp ), save :: SSD_v0p = 0.0_dp
31 <  real( kind = dp ), save :: SSD_rl = 0.0_dp
32 <  real( kind = dp ), save :: SSD_ru = 0.0_dp
33 <  real( kind = dp ), save :: SSD_rlp = 0.0_dp
34 <  real( kind = dp ), save :: SSD_rup = 0.0_dp
35 <  real( kind = dp ), save :: SSD_rbig = 0.0_dp
36 <
37 <  public :: check_sticky_FF
38 <  public :: set_sticky_params
70 >  public :: newStickyType
71    public :: do_sticky_pair
72 +  public :: destroyStickyTypes
73  
74 +
75 +  type :: StickyList
76 +     integer :: c_ident
77 +     real( kind = dp ) :: w0 = 0.0_dp
78 +     real( kind = dp ) :: v0 = 0.0_dp
79 +     real( kind = dp ) :: v0p = 0.0_dp
80 +     real( kind = dp ) :: rl = 0.0_dp
81 +     real( kind = dp ) :: ru = 0.0_dp
82 +     real( kind = dp ) :: rlp = 0.0_dp
83 +     real( kind = dp ) :: rup = 0.0_dp
84 +     real( kind = dp ) :: rbig = 0.0_dp
85 +  end type StickyList
86 +
87 +  type(StickyList), dimension(:),allocatable :: StickyMap
88 +
89   contains
90  
91 <  subroutine check_sticky_FF(status)
44 <    integer :: status
45 <    status = -1
46 <    if (sticky_initialized) status = 0
47 <    return
48 <  end subroutine check_sticky_FF
91 >  subroutine newStickyType(c_ident, w0, v0, v0p, rl, ru, rlp, rup, isError)
92  
93 <  subroutine set_sticky_params(sticky_w0, sticky_v0, sticky_v0p, &
94 <       sticky_rl, sticky_ru, sticky_rlp, sticky_rup)
93 >    integer, intent(in) :: c_ident
94 >    integer, intent(inout) :: isError
95 >    real( kind = dp ), intent(in) :: w0, v0, v0p
96 >    real( kind = dp ), intent(in) :: rl, ru
97 >    real( kind = dp ), intent(in) :: rlp, rup
98 >    integer :: nATypes, myATID
99  
100 <    real( kind = dp ), intent(in) :: sticky_w0, sticky_v0, sticky_v0p
101 <    real( kind = dp ), intent(in) :: sticky_rl, sticky_ru
102 <    real( kind = dp ), intent(in) :: sticky_rlp, sticky_rup
103 <    
100 >
101 >    isError = 0
102 >    myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
103 >
104 >    !! Be simple-minded and assume that we need a StickyMap that
105 >    !! is the same size as the total number of atom types
106 >
107 >    if (.not.allocated(StickyMap)) then
108 >
109 >       nAtypes = getSize(atypes)
110 >
111 >       if (nAtypes == 0) then
112 >          isError = -1
113 >          return
114 >       end if
115 >
116 >       if (.not. allocated(StickyMap)) then
117 >          allocate(StickyMap(nAtypes))
118 >       endif
119 >
120 >    end if
121 >
122 >    if (myATID .gt. size(StickyMap)) then
123 >       isError = -1
124 >       return
125 >    endif
126 >
127 >    ! set the values for StickyMap for this atom type:
128 >
129 >    StickyMap(myATID)%c_ident = c_ident
130 >
131      ! we could pass all 5 parameters if we felt like it...
58    
59    SSD_w0 = sticky_w0
60    SSD_v0 = sticky_v0
61    SSD_v0p = sticky_v0p
62    SSD_rl = sticky_rl
63    SSD_ru = sticky_ru
64    SSD_rlp = sticky_rlp
65    SSD_rup = sticky_rup
132  
133 <    if (SSD_ru .gt. SSD_rup) then
134 <       SSD_rbig = SSD_ru
133 >    StickyMap(myATID)%w0 = w0
134 >    StickyMap(myATID)%v0 = v0
135 >    StickyMap(myATID)%v0p = v0p
136 >    StickyMap(myATID)%rl = rl
137 >    StickyMap(myATID)%ru = ru
138 >    StickyMap(myATID)%rlp = rlp
139 >    StickyMap(myATID)%rup = rup
140 >
141 >    if (StickyMap(myATID)%ru .gt. StickyMap(myATID)%rup) then
142 >       StickyMap(myATID)%rbig = StickyMap(myATID)%ru
143      else
144 <       SSD_rbig = SSD_rup
144 >       StickyMap(myATID)%rbig = StickyMap(myATID)%rup
145      endif
146 <  
73 <    sticky_initialized = .true.
146 >
147      return
148 <  end subroutine set_sticky_params
148 >  end subroutine newStickyType
149  
150    subroutine do_sticky_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
151         pot, A, f, t, do_pot)
152 <    
152 >
153      !! This routine does only the sticky portion of the SSD potential
154      !! [Chandra and Ichiye, J. Chem. Phys. 111, 2701 (1999)].
155      !! The Lennard-Jones and dipolar interaction must be handled separately.
156 <    
156 >
157      !! We assume that the rotation matrices have already been calculated
158      !! and placed in the A array.
159  
# Line 113 | Line 186 | contains
186      real (kind=dp) :: radcomxi, radcomyi, radcomzi
187      real (kind=dp) :: radcomxj, radcomyj, radcomzj
188      integer :: id1, id2
189 +    integer :: me1, me2
190 +    real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
191  
192 <    if (.not.sticky_initialized) then
193 <       write(*,*) 'Sticky forces not initialized!'
192 >    if (.not.allocated(StickyMap)) then
193 >       call handleError("sticky", "no StickyMap was present before first call of do_sticky_pair!")
194         return
195 <    endif
195 >    end if
196  
197 + #ifdef IS_MPI
198 +    me1 = atid_Row(atom1)
199 +    me2 = atid_Col(atom2)
200 + #else
201 +    me1 = atid(atom1)
202 +    me2 = atid(atom2)
203 + #endif
204  
205 <    if ( rij .LE. SSD_rbig ) then
205 >    if (me1.eq.me2) then
206 >       w0  = StickyMap(me1)%w0
207 >       v0  = StickyMap(me1)%v0
208 >       v0p = StickyMap(me1)%v0p
209 >       rl  = StickyMap(me1)%rl
210 >       ru  = StickyMap(me1)%ru
211 >       rlp = StickyMap(me1)%rlp
212 >       rup = StickyMap(me1)%rup
213 >       rbig = StickyMap(me1)%rbig
214 >    else
215 >       ! This is silly, but if you want 2 sticky types in your
216 >       ! simulation, we'll let you do it with the Lorentz-
217 >       ! Berthelot mixing rules.
218 >       ! (Warning: you'll be SLLLLLLLLLLLLLLLOOOOOOOOOOWWWWWWWWWWW)
219 >       rl   = 0.5_dp * ( StickyMap(me1)%rl + StickyMap(me2)%rl )
220 >       ru   = 0.5_dp * ( StickyMap(me1)%ru + StickyMap(me2)%ru )
221 >       rlp  = 0.5_dp * ( StickyMap(me1)%rlp + StickyMap(me2)%rlp )
222 >       rup  = 0.5_dp * ( StickyMap(me1)%rup + StickyMap(me2)%rup )
223 >       rbig = max(ru, rup)
224 >       w0  = sqrt( StickyMap(me1)%w0   * StickyMap(me2)%w0  )
225 >       v0  = sqrt( StickyMap(me1)%v0   * StickyMap(me2)%v0  )
226 >       v0p = sqrt( StickyMap(me1)%v0p  * StickyMap(me2)%v0p )
227 >    endif
228  
229 +    if ( rij .LE. rbig ) then
230 +
231         r3 = r2*rij
232         r5 = r3*r2
233  
# Line 165 | Line 271 | contains
271         yj2 = yj*yj
272         zj2 = zj*zj
273  
274 <       call calc_sw_fnc(rij, s, sp, dsdr, dspdr)
274 >       call calc_sw_fnc(rij, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
275  
276         wi = 2.0d0*(xi2-yi2)*zi / r3
277         wj = 2.0d0*(xj2-yj2)*zj / r3
# Line 177 | Line 283 | contains
283         zjf = zj/rij - 0.6d0
284         zjs = zj/rij + 0.8d0
285  
286 <       wip = zif*zif*zis*zis - SSD_w0
287 <       wjp = zjf*zjf*zjs*zjs - SSD_w0
286 >       wip = zif*zif*zis*zis - w0
287 >       wjp = zjf*zjf*zjs*zjs - w0
288         wp = wip + wjp
289  
290 <       vpair = vpair + 0.5d0*(SSD_v0*s*w + SSD_v0p*sp*wp)
290 >       vpair = vpair + 0.5d0*(v0*s*w + v0p*sp*wp)
291         if (do_pot) then
292   #ifdef IS_MPI
293 <          pot_row(atom1) = pot_row(atom1) + 0.25d0*(SSD_v0*s*w + SSD_v0p*sp*wp)*sw
294 <          pot_col(atom2) = pot_col(atom2) + 0.25d0*(SSD_v0*s*w + SSD_v0p*sp*wp)*sw
293 >          pot_row(atom1) = pot_row(atom1) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
294 >          pot_col(atom2) = pot_col(atom2) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
295   #else
296 <          pot = pot + 0.5d0*(SSD_v0*s*w + SSD_v0p*sp*wp)*sw
296 >          pot = pot + 0.5d0*(v0*s*w + v0p*sp*wp)*sw
297   #endif  
298         endif
299  
# Line 229 | Line 335 | contains
335         ! do the torques first since they are easy:
336         ! remember that these are still in the body fixed axes
337  
338 <       txi = 0.5d0*(SSD_v0*s*dwidux + SSD_v0p*sp*dwipdux)*sw
339 <       tyi = 0.5d0*(SSD_v0*s*dwiduy + SSD_v0p*sp*dwipduy)*sw
340 <       tzi = 0.5d0*(SSD_v0*s*dwiduz + SSD_v0p*sp*dwipduz)*sw
338 >       txi = 0.5d0*(v0*s*dwidux + v0p*sp*dwipdux)*sw
339 >       tyi = 0.5d0*(v0*s*dwiduy + v0p*sp*dwipduy)*sw
340 >       tzi = 0.5d0*(v0*s*dwiduz + v0p*sp*dwipduz)*sw
341  
342 <       txj = 0.5d0*(SSD_v0*s*dwjdux + SSD_v0p*sp*dwjpdux)*sw
343 <       tyj = 0.5d0*(SSD_v0*s*dwjduy + SSD_v0p*sp*dwjpduy)*sw
344 <       tzj = 0.5d0*(SSD_v0*s*dwjduz + SSD_v0p*sp*dwjpduz)*sw
342 >       txj = 0.5d0*(v0*s*dwjdux + v0p*sp*dwjpdux)*sw
343 >       tyj = 0.5d0*(v0*s*dwjduy + v0p*sp*dwjpduy)*sw
344 >       tzj = 0.5d0*(v0*s*dwjduz + v0p*sp*dwjpduz)*sw
345  
346         ! go back to lab frame using transpose of rotation matrix:
347  
# Line 266 | Line 372 | contains
372  
373         ! first rotate the i terms back into the lab frame:
374  
375 <       radcomxi = (SSD_v0*s*dwidx+SSD_v0p*sp*dwipdx)*sw
376 <       radcomyi = (SSD_v0*s*dwidy+SSD_v0p*sp*dwipdy)*sw
377 <       radcomzi = (SSD_v0*s*dwidz+SSD_v0p*sp*dwipdz)*sw
375 >       radcomxi = (v0*s*dwidx+v0p*sp*dwipdx)*sw
376 >       radcomyi = (v0*s*dwidy+v0p*sp*dwipdy)*sw
377 >       radcomzi = (v0*s*dwidz+v0p*sp*dwipdz)*sw
378  
379 <       radcomxj = (SSD_v0*s*dwjdx+SSD_v0p*sp*dwjpdx)*sw
380 <       radcomyj = (SSD_v0*s*dwjdy+SSD_v0p*sp*dwjpdy)*sw
381 <       radcomzj = (SSD_v0*s*dwjdz+SSD_v0p*sp*dwjpdz)*sw
379 >       radcomxj = (v0*s*dwjdx+v0p*sp*dwjpdx)*sw
380 >       radcomyj = (v0*s*dwjdy+v0p*sp*dwjpdy)*sw
381 >       radcomzj = (v0*s*dwjdz+v0p*sp*dwjpdz)*sw
382  
383   #ifdef IS_MPI    
384         fxii = a_Row(1,atom1)*(radcomxi) + &
# Line 326 | Line 432 | contains
432  
433         ! now assemble these with the radial-only terms:
434  
435 <       fxradial = 0.5d0*(SSD_v0*dsdr*drdx*w + SSD_v0p*dspdr*drdx*wp + fxii + fxji)
436 <       fyradial = 0.5d0*(SSD_v0*dsdr*drdy*w + SSD_v0p*dspdr*drdy*wp + fyii + fyji)
437 <       fzradial = 0.5d0*(SSD_v0*dsdr*drdz*w + SSD_v0p*dspdr*drdz*wp + fzii + fzji)
435 >       fxradial = 0.5d0*(v0*dsdr*drdx*w + v0p*dspdr*drdx*wp + fxii + fxji)
436 >       fyradial = 0.5d0*(v0*dsdr*drdy*w + v0p*dspdr*drdy*wp + fyii + fyji)
437 >       fzradial = 0.5d0*(v0*dsdr*drdz*w + v0p*dspdr*drdz*wp + fzii + fzji)
438  
439   #ifdef IS_MPI
440         f_Row(1,atom1) = f_Row(1,atom1) + fxradial
# Line 355 | Line 461 | contains
461         id1 = atom1
462         id2 = atom2
463   #endif
464 <      
464 >
465         if (molMembershipList(id1) .ne. molMembershipList(id2)) then
466 <          
466 >
467            fpair(1) = fpair(1) + fxradial
468            fpair(2) = fpair(2) + fyradial
469            fpair(3) = fpair(3) + fzradial
470 <          
470 >
471         endif
472      endif
473    end subroutine do_sticky_pair
474  
475    !! calculates the switching functions and their derivatives for a given
476 <  subroutine calc_sw_fnc(r, s, sp, dsdr, dspdr)
477 <    
478 <    real (kind=dp), intent(in) :: r
476 >  subroutine calc_sw_fnc(r, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
477 >
478 >    real (kind=dp), intent(in) :: r, rl, ru, rlp, rup
479      real (kind=dp), intent(inout) :: s, sp, dsdr, dspdr
480 <    
480 >
481      ! distances must be in angstroms
482 <    
483 <    if (r.lt.SSD_rl) then
482 >
483 >    if (r.lt.rl) then
484         s = 1.0d0
485         dsdr = 0.0d0
486 <    elseif (r.gt.SSD_ru) then
486 >    elseif (r.gt.ru) then
487         s = 0.0d0
488         dsdr = 0.0d0
489      else
490 <       s = ((SSD_ru + 2.0d0*r - 3.0d0*SSD_rl) * (SSD_ru-r)**2) / &
491 <            ((SSD_ru - SSD_rl)**3)
492 <       dsdr = 6.0d0*(r-SSD_ru)*(r-SSD_rl)/((SSD_ru - SSD_rl)**3)
490 >       s = ((ru + 2.0d0*r - 3.0d0*rl) * (ru-r)**2) / &
491 >            ((ru - rl)**3)
492 >       dsdr = 6.0d0*(r-ru)*(r-rl)/((ru - rl)**3)
493      endif
494  
495 <    if (r.lt.SSD_rlp) then
495 >    if (r.lt.rlp) then
496         sp = 1.0d0      
497         dspdr = 0.0d0
498 <    elseif (r.gt.SSD_rup) then
498 >    elseif (r.gt.rup) then
499         sp = 0.0d0
500         dspdr = 0.0d0
501      else
502 <       sp = ((SSD_rup + 2.0d0*r - 3.0d0*SSD_rlp) * (SSD_rup-r)**2) / &
503 <            ((SSD_rup - SSD_rlp)**3)
504 <       dspdr = 6.0d0*(r-SSD_rup)*(r-SSD_rlp)/((SSD_rup - SSD_rlp)**3)      
502 >       sp = ((rup + 2.0d0*r - 3.0d0*rlp) * (rup-r)**2) / &
503 >            ((rup - rlp)**3)
504 >       dspdr = 6.0d0*(r-rup)*(r-rlp)/((rup - rlp)**3)      
505      endif
506 <    
506 >
507      return
508    end subroutine calc_sw_fnc
403 end module sticky_pair
509  
510 <  subroutine makeStickyType(sticky_w0, sticky_v0, sticky_v0p, &
511 <       sticky_rl, sticky_ru, sticky_rlp, sticky_rup)
512 <    use definitions, ONLY : dp  
513 <    use sticky_pair, ONLY : set_sticky_params
409 <    real( kind = dp ), intent(inout) :: sticky_w0, sticky_v0, sticky_v0p
410 <    real( kind = dp ), intent(inout) :: sticky_rl, sticky_ru
411 <    real( kind = dp ), intent(inout) :: sticky_rlp, sticky_rup
412 <    
413 <    call set_sticky_params(sticky_w0, sticky_v0, sticky_v0p, &
414 <       sticky_rl, sticky_ru, sticky_rlp, sticky_rup)
415 <      
416 <  end subroutine makeStickyType
510 >  subroutine destroyStickyTypes()  
511 >    if(allocated(StickyMap)) deallocate(StickyMap)
512 >  end subroutine destroyStickyTypes
513 > end module sticky

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines