ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90 (file contents):
Revision 312 by gezelter, Tue Mar 11 17:46:18 2003 UTC vs.
Revision 317 by gezelter, Tue Mar 11 23:13:06 2003 UTC

# Line 4 | Line 4
4  
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.10 2003-03-11 17:46:18 gezelter Exp $, $Date: 2003-03-11 17:46:18 $, $Name: not supported by cvs2svn $, $Revision: 1.10 $
7 > !! @version $Id: do_Forces.F90,v 1.11 2003-03-11 23:13:06 gezelter Exp $, $Date: 2003-03-11 23:13:06 $, $Name: not supported by cvs2svn $, $Revision: 1.11 $
8  
9  
10  
# Line 31 | Line 31 | contains
31  
32   contains
33  
34 < !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
35 < !------------------------------------------------------------->
34 >  !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
35 >  !------------------------------------------------------------->
36    subroutine do_force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
37 < !! Position array provided by C, dimensioned by getNlocal
37 >    !! Position array provided by C, dimensioned by getNlocal
38      real ( kind = dp ), dimension(3,getNlocal()) :: q
39 <  !! Rotation Matrix for each long range particle in simulation.
39 >    !! Rotation Matrix for each long range particle in simulation.
40      real( kind = dp), dimension(9,getNlocal()) :: A
41 <
42 <  !! Magnitude dipole moment
41 >    
42 >    !! Magnitude dipole moment
43      real( kind = dp ), dimension(3,getNlocal()) :: mu
44 <  !! Unit vectors for dipoles (lab frame)
44 >    !! Unit vectors for dipoles (lab frame)
45      real( kind = dp ), dimension(3,getNlocal()) :: u_l
46 < !! Force array provided by C, dimensioned by getNlocal
46 >    !! Force array provided by C, dimensioned by getNlocal
47      real ( kind = dp ), dimension(3,getNlocal()) :: f
48 < !! Torsion array provided by C, dimensioned by getNlocal
48 >    !! Torsion array provided by C, dimensioned by getNlocal
49      real( kind = dp ), dimension(3,getNlocal()) :: t
50 <
51 < !! Stress Tensor
50 >    
51 >    !! Stress Tensor
52      real( kind = dp), dimension(9) :: tau
53 <
53 >    
54      real ( kind = dp ) :: potE
55      logical ( kind = 2) :: do_pot
56      integer :: FFerror
57  
58 + #ifdef IS_MPI
59 +    real( kind = DP ) :: pot_local
60 + #endif
61      
62 <    type(atype), pointer :: Atype_i
63 <    type(atype), pointer :: Atype_j
62 >    real( kind = DP )   :: pe
63 >    logical             :: update_nlist
64 >    
65  
66 +    integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
67 +    integer :: nlist
68 +    integer :: j_start
69 +    
70 +    real( kind = DP ) ::  r_ij, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
71 +    
72 +    real( kind = DP ) ::  rx_ij, ry_ij, rz_ij, rijsq
73 +    real( kind = DP ) ::  rlistsq, rcutsq, rlist, rcut
74  
75 <
64 <
65 <  
66 <
75 >    ! a rig that need to be fixed.
76   #ifdef IS_MPI
77 <  real( kind = DP ) :: pot_local
78 <
70 < !! Local arrays needed for MPI
71 <
72 < #endif
73 <
74 <
75 <
76 <  real( kind = DP )   :: pe
77 <  logical             :: update_nlist
78 <
79 <
80 <  integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
81 <  integer :: nlist
82 <  integer :: j_start
83 <
84 <  real( kind = DP ) ::  r_ij, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
85 <
86 <  real( kind = DP ) ::  rx_ij, ry_ij, rz_ij, rijsq
87 <  real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
88 <
89 <  
90 <
91 < ! a rig that need to be fixed.
92 < #ifdef IS_MPI
93 <  real( kind = dp ) :: pe_local
94 <  integer :: nlocal
77 >    real( kind = dp ) :: pe_local
78 >    integer :: nlocal
79   #endif
80 <  integer :: nrow
81 <  integer :: ncol
82 <  integer :: natoms
83 <  integer :: neighborListSize
84 <  integer :: listerror
85 < !! should we calculate the stress tensor
86 <  logical  :: do_stress = .false.
80 >    integer :: nrow
81 >    integer :: ncol
82 >    integer :: natoms
83 >    integer :: neighborListSize
84 >    integer :: listerror
85 >    !! should we calculate the stress tensor
86 >    logical  :: do_stress = .false.
87 >    FFerror = 0
88  
89 <
90 <  FFerror = 0
91 <
92 < ! Make sure we are properly initialized.
93 <  if (.not. isFFInit) then
94 <     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
110 <     FFerror = -1
111 <     return
112 <  endif
89 >    ! Make sure we are properly initialized.
90 >    if (.not. isFFInit) then
91 >       write(default_error,*) "ERROR: lj_FF has not been properly initialized"
92 >       FFerror = -1
93 >       return
94 >    endif
95   #ifdef IS_MPI
96      if (.not. isMPISimSet()) then
97 <     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
98 <     FFerror = -1
99 <     return
100 <  endif
97 >       write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
98 >       FFerror = -1
99 >       return
100 >    endif
101   #endif
102 +    
103 +    !! initialize local variables  
104 +    natoms = getNlocal()
105 +    call getRcut(rcut,rcut2=rcutsq)
106 +    call getRlist(rlist,rlistsq)
107 +    
108 +    !! See if we need to update neighbor lists
109 +    call check(q, update_nlist)
110 +    
111 +    !--------------WARNING...........................
112 +    ! Zero variables, NOTE:::: Forces are zeroed in C
113 +    ! Zeroing them here could delete previously computed
114 +    ! Forces.
115 +    !------------------------------------------------
116 +    call zero_module_variables()
117  
118 < !! initialize local variables  
122 <  natoms = getNlocal()
123 <  call getRcut(rcut,rcut2=rcutsq)
124 <  call getRlist(rlist,rlistsq)
125 <
126 < !! Find ensemble
127 <  if (isEnsemble("NPT")) do_stress = .true.
128 < !! set to wrap
129 <  if (isPBC()) wrap = .true.
130 <
131 <
132 <
133 <  
134 < !! See if we need to update neighbor lists
135 <  call check(q,update_nlist)
136 <
137 < !--------------WARNING...........................
138 < ! Zero variables, NOTE:::: Forces are zeroed in C
139 < ! Zeroing them here could delete previously computed
140 < ! Forces.
141 < !------------------------------------------------
142 <  call zero_module_variables()
143 <
144 <
145 < ! communicate MPI positions
118 >    ! communicate MPI positions
119   #ifdef IS_MPI    
120      call gather(q,q_Row,plan_row3d)
121      call gather(q,q_Col,plan_col3d)
122 <
122 >    
123      call gather(u_l,u_l_Row,plan_row3d)
124      call gather(u_l,u_l_Col,plan_col3d)
125 <
125 >    
126      call gather(A,A_Row,plan_row_rotation)
127      call gather(A,A_Col,plan_col_rotation)
128   #endif
# Line 172 | Line 145 | contains
145        
146         do i = 1, nrow
147            point(i) = nlist + 1
175          Atype_i => identPtrListRow(i)%this
148            
149            inner: do j = 1, ncol
178             Atype_j => identPtrListColumn(j)%this
150              
151 <             call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
152 <                  rxij,ryij,rzij,rijsq,r)
153 <            
154 <             ! skip the loop if the atoms are identical
184 <             if (mpi_cycle_jLoop(i,j)) cycle inner:
185 <            
151 >             if (check_exclude(i,j)) cycle inner:
152 >
153 >             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
154 >            
155               if (rijsq <  rlistsq) then            
156                  
157                  nlist = nlist + 1
# Line 197 | Line 166 | contains
166                  endif
167                  
168                  list(nlist) = j
169 <                
201 <                
169 >                                
170                  if (rijsq <  rcutsq) then
171 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
171 >                   call do_pair(i, j, rijsq, d)
172                  endif
173               endif
174            enddo inner
# Line 216 | Line 184 | contains
184            JEND = POINT(i+1) - 1
185            ! check thiat molecule i has neighbors
186            if (jbeg .le. jend) then
187 <
220 <             Atype_i => identPtrListRow(i)%this
187 >            
188               do jnab = jbeg, jend
189                  j = list(jnab)
190 <                Atype_j = identPtrListColumn(j)%this
191 <                call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
192 <                     rxij,ryij,rzij,rijsq,r)
193 <                
227 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
190 >
191 >                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
192 >                call do_pair(i, j, rijsq, d)
193 >
194               enddo
195            endif
196         enddo
# Line 240 | Line 206 | contains
206        
207         neighborListSize = getNeighborListSize()
208         nlist = 0
209 <      
244 <    
209 >          
210         do i = 1, natoms-1
211            point(i) = nlist + 1
247          Atype_i   => identPtrList(i)%this
212  
213            inner: do j = i+1, natoms
214 <             Atype_j   => identPtrList(j)%this
215 <             call get_interatomic_vector(i,j,q(:,i),q(:,j),&
216 <                  rxij,ryij,rzij,rijsq,r)
214 >
215 >             if (check_exclude(i,j)) cycle inner:
216 >
217 >             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
218            
219               if (rijsq <  rlistsq) then
220 <
220 >                
221                  nlist = nlist + 1
222                  
223                  if (nlist > neighborListSize) then
# Line 265 | Line 230 | contains
230                  endif
231                  
232                  list(nlist) = j
233 <
269 <    
233 >                    
234                  if (rijsq <  rcutsq) then
235 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
235 >                   call do_pair(i, j, rijsq, d)
236                  endif
237               endif
238            enddo inner
# Line 285 | Line 249 | contains
249            ! check thiat molecule i has neighbors
250            if (jbeg .le. jend) then
251              
288             Atype_i => identPtrList(i)%this
252               do jnab = jbeg, jend
253                  j = list(jnab)
254 <                Atype_j = identPtrList(j)%this
255 <                call get_interatomic_vector(i,j,q(:,i),q(:,j),&
256 <                     rxij,ryij,rzij,rijsq,r)
257 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
254 >
255 >                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
256 >                call do_pair(i, j, rijsq, d)
257 >
258               enddo
259            endif
260         enddo
261      endif
262 <
262 >    
263   #endif
264 <
265 <
264 >    
265 >    
266   #ifdef IS_MPI
267      !! distribute all reaction field stuff (or anything for post-pair):
268      call scatter(rflRow,rflTemp1,plan_row3d)
# Line 308 | Line 271 | contains
271         rflTemp(1:3,i) = rflTemp1(1:3,i) + rflTemp2(1:3,i)
272      end do
273   #endif
274 <
274 >    
275   ! This is the post-pair loop:
276   #ifdef IS_MPI
277 <
277 >    
278      if (system_has_postpair_atoms) then
279         do i = 1, nlocal
280            Atype_i => identPtrListRow(i)%this
281            call do_postpair(i, Atype_i)
282         enddo
283      endif
284 <
284 >    
285   #else
286 <
286 >    
287      if (system_has_postpair_atoms) then
288         do i = 1, natoms
289            Atype_i => identPtr(i)%this
290            call do_postpair(i, Atype_i)
291         enddo
292      endif
293 <
293 >    
294   #endif
295 +    
296  
333
297   #ifdef IS_MPI
298      !!distribute forces
299  
# Line 394 | Line 357 | contains
357  
358    end subroutine do_preForce
359  
397
398
399
400
401
402
403
404
405
406
407
408
360   !! Calculate any post force loop components, i.e. reaction field, etc.
361    subroutine do_postForce()
362  
# Line 413 | Line 364 | contains
364  
365    end subroutine do_postForce
366  
367 +  subroutine do_pair(i, j, rijsq, d)
368  
369 +    integer, intent(in) :: i, j
370 +    real ( kind = dp ), intent(in)    :: rijsq
371 +    real ( kind = dp )                :: r
372 +    real ( kind = dp ), intent(inout) :: d(3)
373  
374 +    r = sqrt(rijsq)
375 +    
376 +    logical :: is_LJ_i, is_LJ_j
377 +    logical :: is_DP_i, is_DP_j
378 +    logical :: is_Sticky_i, is_Sticky_j
379 +    integer :: me_i, me_j
380  
381 + #ifdef IS_MPI
382  
383 +    me_i = atid_row(i)
384 +    me_j = atid_col(j)
385  
386 + #else
387  
388 +    me_i = atid(i)
389 +    me_j = atid(j)
390  
391 + #endif
392  
393 +    call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
394 +    call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
395  
396 +    if ( is_LJ_i .and. is_LJ_j ) call do_lj_pair(i, j, d, r, pot, f)
397  
398 +    call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
399 +    call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
400  
401 +    if ( is_DP_i .and. is_DP_j ) then
402  
403 +       call do_dipole_pair(i, j, d, r, pot, u_l, f, t)
404  
429
430
431
432  subroutine do_pair(atype_i,atype_j,i,j,r_ij,rx_ij,ry_ij,rz_ij)
433    type (atype ), pointer, intent(inout) :: atype_i
434    type (atype ), pointer, intent(inout) :: atype_j
435    integer :: i
436    integer :: j
437    real ( kind = dp ), intent(inout) :: rx_ij
438    real ( kind = dp ), intent(inout) :: ry_ij
439    real ( kind = dp ), intent(inout) :: rz_ij
440
441
442    real( kind = dp ) :: fx = 0.0_dp
443    real( kind = dp ) :: fy = 0.0_dp
444    real( kind = dp ) :: fz = 0.0_dp  
445  
446    real( kind = dp ) ::  drdx = 0.0_dp
447    real( kind = dp ) ::  drdy = 0.0_dp
448    real( kind = dp ) ::  drdz = 0.0_dp
449    
450
451 #ifdef IS_MPI
452
453    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
454       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
455            pot, f)
456    endif
457
458    if (Atype_i%is_dp .and. Atype_j%is_dp) then
459
460       call do_dipole_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
461            pot, u_l, f, t)
462
405         if (do_reaction_field) then
406 <          call accumulate_rf(i, j, r_ij, rt, rrf)
406 >          call accumulate_rf(i, j, r_ij)
407         endif
408  
409      endif
410  
411 <    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
412 <       call getstickyforce(r, pot, dudr, Atype_i, Atype_j)
471 <    endif
411 >    call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
412 >    call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
413  
414 < #else
415 <
475 <    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
476 <       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
477 <            pot, f)
414 >    if ( is_Sticky_i .and. is_Sticky_j ) then
415 >       call do_sticky_pair(i, j, d, r, pot, u_l, f, t)
416      endif
417  
480    if (Atype_i%is_dp .and. Atype_j%is_dp) then
481       call do_dipole_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
482            pot, u_l, f, t)
483
484       if (do_reaction_field) then
485          call accumulate_rf(i, j, r_ij, rt, rrf)
486       endif
487
488    endif
489
490    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
491       call getstickyforce(r,pot,dudr, Atype_i, Atype_j)
492    endif
493
494 #endif
495
418        
419    end subroutine do_pair
420  
421  
422 <
423 <
502 <
503 <
504 <
505 <
506 <
507 <
508 <
509 <
510 <
511 <
512 <
513 <
514 <  subroutine get_interatomic_vector(q_i,q_j,rx_ij,ry_ij,rz_ij,r_sq,r_ij)
515 < !---------------- Arguments-------------------------------
516 <   !! index i
517 <
518 <    !! Position array
422 >  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
423 >    
424      real (kind = dp), dimension(3) :: q_i
425      real (kind = dp), dimension(3) :: q_j
521    !! x component of vector between i and j
522    real ( kind = dp ), intent(out)  :: rx_ij
523    !! y component of vector between i and j
524    real ( kind = dp ), intent(out)  :: ry_ij
525    !! z component of vector between i and j
526    real ( kind = dp ), intent(out)  :: rz_ij
527    !! magnitude of r squared
426      real ( kind = dp ), intent(out) :: r_sq
529    !! magnitude of vector r between atoms i and j.
530    real ( kind = dp ), intent(out) :: r_ij
531    !! wrap into periodic box.
532    logical, intent(in) :: wrap
533
534 !--------------- Local Variables---------------------------
535    !! Distance between i and j
427      real( kind = dp ) :: d(3)
537 !---------------- END DECLARATIONS-------------------------
428  
539
540 ! Find distance between i and j
429      d(1:3) = q_i(1:3) - q_j(1:3)
430 <
431 < ! Wrap back into periodic box if necessary
432 <    if ( wrap ) then
430 >    
431 >    ! Wrap back into periodic box if necessary
432 >    if ( isPBC() ) then
433         d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
434              int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
435 <    end if
435 >    endif
436      
549 !   Find Magnitude of the vector
437      r_sq = dot_product(d,d)
438 <    r_ij = sqrt(r_sq)
552 <
553 < !   Set each component for force calculation
554 <    rx_ij = d(1)
555 <    ry_ij = d(2)
556 <    rz_ij = d(3)
557 <
558 <
438 >        
439    end subroutine get_interatomic_vector
440 <
440 >  
441    subroutine zero_module_variables()
442  
443   #ifndef IS_MPI

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines