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

Comparing trunk/OOPSE/libmdtools/calc_reaction_field.F90 (file contents):
Revision 460 by chuckv, Fri Apr 4 22:22:30 2003 UTC vs.
Revision 999 by chrisfen, Fri Jan 30 15:01:09 2004 UTC

# Line 4 | Line 4 | module reaction_field
4    use atype_module
5    use vector_class
6    use simulation
7 +  use status
8   #ifdef IS_MPI
9    use mpiSimulation
10   #endif
11    implicit none
12  
13 <  real(kind=dp), save :: rrf
13 >  PRIVATE
14 >  
15 >  real(kind=dp), save :: rrf = 1.0_dp
16    real(kind=dp), save :: rt
17 <  real(kind=dp), save :: dielect
18 <  real(kind=dp), save :: rrfsq
17 >  real(kind=dp), save :: dielect = 1.0_dp
18 >  real(kind=dp), save :: rrfsq = 1.0_dp
19    real(kind=dp), save :: pre
20 <  logical, save :: rf_initialized = .false.
20 >  logical, save :: haveCutoffs = .false.
21 >  logical, save :: haveMomentMap = .false.
22 >  logical, save :: haveDielectric = .false.
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 +  PUBLIC::initialize_rf
31 +  PUBLIC::setCutoffsRF
32 +  PUBLIC::accumulate_rf
33 +  PUBLIC::accumulate_self_rf
34 +  PUBLIC::reaction_field_final
35 +  PUBLIC::rf_correct_forces
36 +
37   contains
38    
39 <  subroutine initialize_rf(this_rrf, this_rt, this_dielect)
40 <    real(kind=dp), intent(in) :: this_rrf, this_rt, this_dielect
41 <
24 <    rrf = this_rrf
25 <    rt = this_rt
39 >  subroutine initialize_rf(this_dielect)
40 >    real(kind=dp), intent(in) :: this_dielect
41 >    
42      dielect = this_dielect
43 +
44 +    pre = 14.38362d0*2.0d0*(dielect-1.0d0)/((2.0d0*dielect+1.0d0)*rrfsq*rrf)
45      
46 +    haveDielectric = .true.
47 +
48 +    return
49 +  end subroutine initialize_rf
50 +
51 +  subroutine setCutoffsRF( this_rrf, this_rt )
52 +
53 +    real(kind=dp), intent(in) :: this_rrf, this_rt
54 +
55 +    rrf = this_rrf
56 +    rt  = this_rt
57 +
58      rrfsq = rrf * rrf
59      pre = 14.38362d0*2.0d0*(dielect-1.0d0)/((2.0d0*dielect+1.0d0)*rrfsq*rrf)
60      
61 +    haveCutoffs = .true.
62  
63 <    write(*,*) 'rrf = ', rrf
64 <    write(*,*) 'rt = ', rt
65 <    write(*,*) 'dielect = ', dielect
66 <    write(*,*) 'pre = ', pre
67 <    rf_initialized = .true.
63 >  end subroutine setCutoffsRF
64 >
65 >  subroutine createMomentMap(status)
66 >    integer :: nAtypes
67 >    integer :: status
68 >    integer :: i
69 >    real (kind=DP) :: thisDP
70 >    logical :: thisProperty
71 >
72 >    status = 0
73 >
74 >    nAtypes = getSize(atypes)
75      
76 <    return
77 <  end subroutine initialize_rf
78 <  
76 >    if (nAtypes == 0) then
77 >       status = -1
78 >       return
79 >    end if
80 >    
81 >    if (.not. allocated(MomentMap)) then
82 >       allocate(MomentMap(nAtypes))
83 >    endif
84 >
85 >    do i = 1, nAtypes
86 >
87 >       call getElementProperty(atypes, i, "is_DP", thisProperty)
88 >
89 >       if (thisProperty) then
90 >          call getElementProperty(atypes, i, "dipole_moment", thisDP)
91 >          MomentMap(i)%dipole_moment = thisDP
92 >       endif
93 >      
94 >    end do
95 >    
96 >    haveMomentMap = .true.
97 >    
98 >  end subroutine createMomentMap  
99 >
100    subroutine accumulate_rf(atom1, atom2, rij, u_l)
101  
102      integer, intent(in) :: atom1, atom2
103      real (kind = dp), intent(in) :: rij
104 <    real (kind = dp), dimension(3,getNlocal()) :: u_l    
104 >    real (kind = dp), dimension(3,nLocal) :: u_l    
105  
106      integer :: me1, me2
107      real (kind = dp) :: taper, mu1, mu2
108      real (kind = dp), dimension(3) :: ul1
109      real (kind = dp), dimension(3) :: ul2  
110  
111 <    if (.not.rf_initialized) then
111 >    integer :: localError
112 >
113 >    if ((.not.haveDielectric).or.(.not.haveCutoffs)) then
114         write(default_error,*) 'Reaction field not initialized!'
115         return
116      endif
117 +
118 +    if (.not.haveMomentMap) then
119 +       localError = 0
120 +       call createMomentMap(localError)
121 +       if ( localError .ne. 0 ) then
122 +          call handleError("reaction-field", "MomentMap creation failed!")
123 +          return
124 +       end if
125 +    endif
126      
127      if (rij.le.rrf) then
128            
129         if (rij.lt.rt) then
130            taper = 1.0d0
131         else
132 +  !        write(*,*) 'rf in taper region'
133            taper = (rrf + 2.0d0*rij - 3.0d0*rt)*(rrf-rij)**2/ ((rrf-rt)**3)
134         endif
135        
# Line 84 | Line 155 | contains
155         ul2(3) = u_l(3,atom2)
156   #endif
157        
158 <       call getElementProperty(atypes, me1, "dipole_moment", mu1)
159 <       call getElementProperty(atypes, me2, "dipole_moment", mu2)
158 >       mu1 = MomentMap(me1)%dipole_moment
159 >       mu2 = MomentMap(me2)%dipole_moment
160        
90      
161   #ifdef IS_MPI
162         rf_Row(1,atom1) = rf_Row(1,atom1) + ul2(1)*mu2*taper
163         rf_Row(2,atom1) = rf_Row(2,atom1) + ul2(2)*mu2*taper
# Line 114 | Line 184 | contains
184      
185      integer, intent(in) :: atom1
186      real(kind=dp), intent(in) :: mu1
187 <    real(kind=dp), dimension(3,getNlocal()) :: u_l
187 >    real(kind=dp), dimension(3,nLocal) :: u_l
188      
189      !! should work for both MPI and non-MPI version since this is not pairwise.
190      rf(1,atom1) = rf(1,atom1) + u_l(1,atom1)*mu1
# Line 130 | Line 200 | contains
200      real (kind=dp), intent(in) :: mu1
201      real (kind=dp), intent(inout) :: rfpot
202      logical, intent(in) :: do_pot
203 <    real (kind = dp), dimension(3,getNlocal()) :: u_l    
204 <    real (kind = dp), dimension(3,getNlocal()) :: t
203 >    real (kind = dp), dimension(3,nLocal) :: u_l    
204 >    real (kind = dp), dimension(3,nLocal) :: t
205  
206 <    if (.not.rf_initialized) then
206 >    integer :: localError
207 >
208 >    if ((.not.haveDielectric).or.(.not.haveCutoffs)) then
209         write(default_error,*) 'Reaction field not initialized!'
210         return
211      endif
212  
213 +    if (.not.haveMomentMap) then
214 +       localError = 0
215 +       call createMomentMap(localError)
216 +       if ( localError .ne. 0 ) then
217 +          call handleError("reaction-field", "MomentMap creation failed!")
218 +          return
219 +       end if
220 +    endif
221 +
222      ! compute torques on dipoles:
223      ! pre converts from mu in units of debye to kcal/mol
224      
# Line 153 | Line 234 | contains
234         rfpot = rfpot - 0.5d0 * pre * mu1 * &
235              (rf(1,a1)*u_l(1,a1) + rf(2,a1)*u_l(2,a1) + rf(3,a1)*u_l(3,a1))
236      endif
237 <    
237 >
238      return
239    end subroutine reaction_field_final
240    
# Line 162 | Line 243 | contains
243      integer, intent(in) :: atom1, atom2
244      real(kind=dp), dimension(3), intent(in) :: d
245      real(kind=dp), intent(in) :: rij
246 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
247 <    real( kind = dp ), dimension(3,getNlocal()) :: f
246 >    real( kind = dp ), dimension(3,nLocal) :: u_l
247 >    real( kind = dp ), dimension(3,nLocal) :: f
248      logical, intent(in) :: do_stress
249      
250      real (kind = dp), dimension(3) :: ul1
251      real (kind = dp), dimension(3) :: ul2
252      real (kind = dp) :: dtdr
253      real (kind = dp) :: dudx, dudy, dudz, u1dotu2
254 <    integer :: me1, me2
254 >    integer :: me1, me2, id1, id2
255      real (kind = dp) :: mu1, mu2
256      
257 <    if (.not.rf_initialized) then
257 >    integer :: localError
258 >
259 >    if ((.not.haveDielectric).or.(.not.haveCutoffs)) then
260         write(default_error,*) 'Reaction field not initialized!'
261         return
262      endif
263  
264 +    if (.not.haveMomentMap) then
265 +       localError = 0
266 +       call createMomentMap(localError)
267 +       if ( localError .ne. 0 ) then
268 +          call handleError("reaction-field", "MomentMap creation failed!")
269 +          return
270 +       end if
271 +    endif
272 +
273      if (rij.le.rrf) then
274        
275         if (rij.lt.rt) then
276            dtdr = 0.0d0
277         else
278 + !         write(*,*) 'rf correct in taper region'
279            dtdr = 6.0d0*(rij*rij - rij*rt - rij*rrf +rrf*rt)/((rrf-rt)**3)
280         endif
281        
# Line 208 | Line 301 | contains
301         ul2(3) = u_l(3,atom2)
302   #endif
303        
304 <       call getElementProperty(atypes, me1, "dipole_moment", mu1)
305 <       call getElementProperty(atypes, me2, "dipole_moment", mu2)
304 >       mu1 = MomentMap(me1)%dipole_moment
305 >       mu2 = MomentMap(me2)%dipole_moment
306        
307         u1dotu2 = ul1(1)*ul2(1) + ul1(2)*ul2(2) + ul1(3)*ul2(3)
308        
# Line 236 | Line 329 | contains
329   #endif
330        
331         if (do_stress) then          
332 <          tau_Temp(1) = tau_Temp(1) + dudx * d(1)
333 <          tau_Temp(2) = tau_Temp(2) + dudx * d(2)
334 <          tau_Temp(3) = tau_Temp(3) + dudx * d(3)
335 <          tau_Temp(4) = tau_Temp(4) + dudy * d(1)
336 <          tau_Temp(5) = tau_Temp(5) + dudy * d(2)
337 <          tau_Temp(6) = tau_Temp(6) + dudy * d(3)
338 <          tau_Temp(7) = tau_Temp(7) + dudz * d(1)
339 <          tau_Temp(8) = tau_Temp(8) + dudz * d(2)
340 <          tau_Temp(9) = tau_Temp(9) + dudz * d(3)
341 <          virial_Temp = virial_Temp + (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
332 >
333 > #ifdef IS_MPI
334 >          id1 = tagRow(atom1)
335 >          id2 = tagColumn(atom2)
336 > #else
337 >          id1 = atom1
338 >          id2 = atom2
339 > #endif
340 >
341 >          if (molMembershipList(id1) .ne. molMembershipList(id2)) then
342 >
343 >             ! because the d vector is the rj - ri vector, and
344 >             ! because dudx, dudy, and dudz are the
345 >             ! (positive) force on atom i (negative on atom j) we need
346 >             ! a negative sign here:
347 >
348 >             tau_Temp(1) = tau_Temp(1) - d(1) * dudx
349 >             tau_Temp(2) = tau_Temp(2) - d(1) * dudy
350 >             tau_Temp(3) = tau_Temp(3) - d(1) * dudz
351 >             tau_Temp(4) = tau_Temp(4) - d(2) * dudx
352 >             tau_Temp(5) = tau_Temp(5) - d(2) * dudy
353 >             tau_Temp(6) = tau_Temp(6) - d(2) * dudz
354 >             tau_Temp(7) = tau_Temp(7) - d(3) * dudx
355 >             tau_Temp(8) = tau_Temp(8) - d(3) * dudy
356 >             tau_Temp(9) = tau_Temp(9) - d(3) * dudz
357 >             virial_Temp = virial_Temp + &
358 >                  (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
359 >          endif
360         endif      
361      endif
362      

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines