ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/calc_dipole_dipole.F90
(Generate patch)

Comparing:
branches/mmeineke/OOPSE/libmdtools/calc_dipole_dipole.F90 (file contents), Revision 377 by mmeineke, Fri Mar 21 17:42:12 2003 UTC vs.
trunk/OOPSE/libmdtools/calc_dipole_dipole.F90 (file contents), Revision 901 by chuckv, Tue Jan 6 19:49:18 2004 UTC

# Line 4 | Line 4 | module dipole_dipole
4    use definitions
5    use atype_module
6    use vector_class
7 +  use simulation
8 +  use status
9   #ifdef IS_MPI
10    use mpiSimulation
11   #endif
12    implicit none
13  
14 <  real(kind=dp), save :: rrf
15 <  real(kind=dp), save :: rt  
16 <  real(kind=dp), save :: rrfsq
17 <  real(kind=dp), save :: pre
18 <  logical, save :: dipole_initialized = .false.
14 >  PRIVATE
15 >  real(kind=dp), save :: rrf = 0.0
16 >  real(kind=dp), save :: rt  = 0.0
17 >   real(kind=dp), save :: pre = 0.0
18 >  logical, save :: haveCutoffs = .false.
19 >  logical, save :: haveMomentMap = .false.
20  
21 +  public::setCutoffsDipole
22 +  public::do_dipole_pair
23 +
24 +  type :: MomentList
25 +     real(kind=DP) :: dipole_moment = 0.0_DP
26 +  end type MomentList
27 +
28 +  type(MomentList), dimension(:),allocatable :: MomentMap
29 +
30   contains
31      
32 <  subroutine initialize_dipole(this_rrf, this_rt)
32 >  subroutine setCutoffsDipole(this_rrf, this_rt)
33      real(kind=dp), intent(in) :: this_rrf, this_rt
34      rrf = this_rrf
35      rt = this_rt    
36 <    rrfsq = rrf * rrf
37 <    ! pre converts from mu in units of debye to kcal/mol
38 <    pre = 14.38362d0
36 >
37 >      ! pre converts from mu in units of debye to kcal/mol
38 >    pre = 14.38362_dp
39 >
40 >    haveCutoffs = .true.
41      
28    dipole_initialized = .true.
29    
42      return
43 <  end subroutine initialize_dipole
43 >  end subroutine setCutoffsDipole
44  
45 +  subroutine createMomentMap(status)
46 +    integer :: nAtypes
47 +    integer :: status
48 +    integer :: i
49 +    real (kind=DP) :: thisDP
50 +    logical :: thisProperty
51  
52 +    status = 0
53 +
54 +    nAtypes = getSize(atypes)
55 +    
56 +    if (nAtypes == 0) then
57 +       status = -1
58 +       return
59 +    end if
60 +    
61 +    if (.not. allocated(MomentMap)) then
62 +       allocate(MomentMap(nAtypes))
63 +    endif
64 +
65 +    do i = 1, nAtypes
66 +
67 +       call getElementProperty(atypes, i, "is_DP", thisProperty)
68 +
69 +       if (thisProperty) then
70 +          call getElementProperty(atypes, i, "dipole_moment", thisDP)
71 +          MomentMap(i)%dipole_moment = thisDP
72 +       endif
73 +      
74 +    end do
75 +    
76 +    haveMomentMap = .true.
77 +    
78 +  end subroutine createMomentMap
79 +  
80 +  
81    subroutine do_dipole_pair(atom1, atom2, d, rij, r2, pot, u_l, f, t, &
82         do_pot, do_stress)
83      
84      logical :: do_pot, do_stress
85  
86 <    integer atom1, atom2, me1, me2
86 >    integer atom1, atom2, me1, me2, id1, id2
87 >    integer :: localError
88      real(kind=dp) :: rij, mu1, mu2
89 <    real(kind=dp) :: dfact1, dfact2, dip2, r2, r3, r5, pre
89 >    real(kind=dp) :: dfact1, dfact2, dip2, r2, r3, r5
90      real(kind=dp) :: dudx, dudy, dudz, dudu1x, dudu1y, dudu1z
91      real(kind=dp) :: dudu2x, dudu2y, dudu2z, rdotu1, rdotu2, u1dotu2
92      real(kind=dp) :: taper, dtdr, vterm
93  
94      real( kind = dp ) :: pot
95      real( kind = dp ), dimension(3) :: d
96 <    real( kind = dp ), dimension(:,:) :: u_l
97 <    real( kind = dp ), dimension(:,:) :: f
98 <    real( kind = dp ), dimension(:,:) :: t
96 >    real( kind = dp ), dimension(3,nLocal) :: u_l
97 >    real( kind = dp ), dimension(3,nLocal) :: f
98 >    real( kind = dp ), dimension(3,nLocal) :: t
99      
100      real (kind = dp), dimension(3) :: ul1
101      real (kind = dp), dimension(3) :: ul2
102  
103 <    if (.not.dipole_initialized) then
104 <       write(default_error,*) 'Dipole-dipole not initialized!'
103 >    if (.not. haveCutoffs) then
104 >       write(default_error,*) 'Dipole-dipole does not have cutoffs set!'
105         return
106      endif
107 <    
107 >
108 >    if (.not.haveMomentMap) then
109 >       localError = 0
110 >       call createMomentMap(localError)
111 >       if ( localError .ne. 0 ) then
112 >          call handleError("dipole-dipole", "MomentMap creation failed!")
113 >          return
114 >       end if
115 >    endif
116 >
117   #ifdef IS_MPI
118      me1 = atid_Row(atom1)
119      ul1(1) = u_l_Row(1,atom1)
# Line 79 | Line 136 | contains
136      ul2(3) = u_l(3,atom2)
137   #endif
138  
139 <    call getElementProperty(atypes, me1, "dipole_moment", mu1)
140 <    call getElementProperty(atypes, me2, "dipole_moment", mu2)
141 <    
139 >    mu1 = MomentMap(me1)%dipole_moment
140 >    mu2 = MomentMap(me2)%dipole_moment
141 >
142      if (rij.le.rrf) then
143        
144         if (rij.lt.rt) then
# Line 100 | Line 157 | contains
157         u1dotu2 = ul1(1)*ul2(1) + ul1(2)*ul2(2) + ul1(3)*ul2(3)
158        
159         dip2 = pre * mu1 * mu2
103      
160         dfact1 = 3.0d0*dip2 / r2
161         dfact2 = 3.0d0*dip2 / r5
162        
# Line 129 | Line 185 | contains
185              (5.0d0*(rdotu1*rdotu2)/r5)) -  &
186              dfact2*(ul1(3)*rdotu2 + ul2(3)*rdotu1))*taper +  &
187              vterm*dtdr*d(3)/rij
188 <      
188 >
189         dudu1x = (dip2*((ul2(1)/r3) - (3.0d0*d(1)*rdotu2/r5)))*taper
190         dudu1y = (dip2*((ul2(2)/r3) - (3.0d0*d(2)*rdotu2/r5)))*taper
191         dudu1z = (dip2*((ul2(3)/r3) - (3.0d0*d(3)*rdotu2/r5)))*taper
192 <      
192 >
193         dudu2x = (dip2*((ul1(1)/r3) - (3.0d0*d(1)*rdotu1/r5)))*taper
194         dudu2y = (dip2*((ul1(2)/r3) - (3.0d0*d(2)*rdotu1/r5)))*taper
195         dudu2z = (dip2*((ul1(3)/r3) - (3.0d0*d(3)*rdotu1/r5)))*taper
196        
197 <      
197 >
198   #ifdef IS_MPI
199         f_Row(1,atom1) = f_Row(1,atom1) + dudx
200         f_Row(2,atom1) = f_Row(2,atom1) + dudy
# Line 172 | Line 228 | contains
228         t(2,atom2) = t(2,atom2) - ul2(3)*dudu2x + ul2(1)*dudu2z
229         t(3,atom2) = t(3,atom2) - ul2(1)*dudu2y + ul2(2)*dudu2x
230   #endif
231 <      
231 >
232         if (do_stress) then          
233 <          tau_Temp(1) = tau_Temp(1) + dudx * d(1)
234 <          tau_Temp(2) = tau_Temp(2) + dudx * d(2)
235 <          tau_Temp(3) = tau_Temp(3) + dudx * d(3)
236 <          tau_Temp(4) = tau_Temp(4) + dudy * d(1)
237 <          tau_Temp(5) = tau_Temp(5) + dudy * d(2)
238 <          tau_Temp(6) = tau_Temp(6) + dudy * d(3)
239 <          tau_Temp(7) = tau_Temp(7) + dudz * d(1)
240 <          tau_Temp(8) = tau_Temp(8) + dudz * d(2)
241 <          tau_Temp(9) = tau_Temp(9) + dudz * d(3)
242 <          virial_Temp = virial_Temp + (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
233 >
234 > #ifdef IS_MPI
235 >          id1 = tagRow(atom1)
236 >          id2 = tagColumn(atom2)
237 > #else
238 >          id1 = atom1
239 >          id2 = atom2
240 > #endif                
241 >          if (molMembershipList(id1) .ne. molMembershipList(id2)) then
242 >
243 >             ! because the d vector is the rj - ri vector, and
244 >             ! because dudx, dudy, dudz are the (positive) force on
245 >             ! atom i (negative on atom j) we need a negative sign here:
246 >
247 >             tau_Temp(1) = tau_Temp(1) - d(1) * dudx
248 >             tau_Temp(2) = tau_Temp(2) - d(1) * dudy
249 >             tau_Temp(3) = tau_Temp(3) - d(1) * dudz
250 >             tau_Temp(4) = tau_Temp(4) - d(2) * dudx
251 >             tau_Temp(5) = tau_Temp(5) - d(2) * dudy
252 >             tau_Temp(6) = tau_Temp(6) - d(2) * dudz
253 >             tau_Temp(7) = tau_Temp(7) - d(3) * dudx
254 >             tau_Temp(8) = tau_Temp(8) - d(3) * dudy
255 >             tau_Temp(9) = tau_Temp(9) - d(3) * dudz
256 >
257 >             virial_Temp = virial_Temp + &
258 >                  (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
259 >
260 >          endif          
261         endif
262        
263      endif

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines