ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90
Revision: 329
Committed: Wed Mar 12 22:27:59 2003 UTC (21 years, 6 months ago) by gezelter
File size: 16126 byte(s)
Log Message:
Stick a fork in it.  It's rare.

File Contents

# Content
1 !! do_Forces.F90
2 !! module do_Forces
3 !! Calculates Long Range forces.
4
5 !! @author Charles F. Vardeman II
6 !! @author Matthew Meineke
7 !! @version $Id: do_Forces.F90,v 1.15 2003-03-12 22:27:59 gezelter Exp $, $Date: 2003-03-12 22:27:59 $, $Name: not supported by cvs2svn $, $Revision: 1.15 $
8
9
10
11 module do_Forces
12 use simulation
13 use definitions
14 use atype_module
15 use neighborLists
16 use lj_FF
17 use sticky_FF
18 use dipole_dipole
19 use gb_FF
20
21 #ifdef IS_MPI
22 use mpiSimulation
23 #endif
24 implicit none
25 PRIVATE
26
27 logical, save :: do_forces_initialized = .false.
28 logical, save :: FF_uses_LJ
29 logical, save :: FF_uses_sticky
30 logical, save :: FF_uses_dipoles
31 logical, save :: FF_uses_RF
32 logical, save :: FF_uses_GB
33 logical, save :: FF_uses_EAM
34
35
36 public :: init_FF
37 public :: do_forces
38
39 contains
40
41 subroutine init_FF(thisStat)
42
43 integer, intent(out) :: my_status
44 integer :: thisStat = 0
45
46 ! be a smarter subroutine.
47
48
49 call init_lj_FF(my_status)
50 if (my_status /= 0) then
51 thisStat = -1
52 return
53 end if
54
55 call check_sticky_FF(my_status)
56 if (my_status /= 0) then
57 thisStat = -1
58 return
59 end if
60
61 do_forces_initialized = .true.
62
63 end subroutine init_FF
64
65
66
67 !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
68 !------------------------------------------------------------->
69 subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
70 error)
71 !! Position array provided by C, dimensioned by getNlocal
72 real ( kind = dp ), dimension(3,getNlocal()) :: q
73 !! Rotation Matrix for each long range particle in simulation.
74 real( kind = dp), dimension(9,getNlocal()) :: A
75 !! Unit vectors for dipoles (lab frame)
76 real( kind = dp ), dimension(3,getNlocal()) :: u_l
77 !! Force array provided by C, dimensioned by getNlocal
78 real ( kind = dp ), dimension(3,getNlocal()) :: f
79 !! Torsion array provided by C, dimensioned by getNlocal
80 real( kind = dp ), dimension(3,getNlocal()) :: t
81 !! Stress Tensor
82 real( kind = dp), dimension(9) :: tau
83 real ( kind = dp ) :: pot
84 logical ( kind = 2) :: do_pot_c, do_stress_c
85 logical :: do_pot
86 logical :: do_stress
87 #ifdef IS_MPI
88 real( kind = DP ) :: pot_local
89 integer :: nlocal
90 integer :: nrow
91 integer :: ncol
92 #endif
93 integer :: natoms
94 logical :: update_nlist
95 integer :: i, j, jbeg, jend, jnab
96 integer :: nlist
97 real( kind = DP ) :: rijsq, rlistsq, rcutsq, rlist, rcut
98 integer :: neighborListSize
99 integer :: listerror
100
101 !! initialize local variables
102
103 #ifdef IS_MPI
104 nlocal = getNlocal()
105 nrow = getNrow(plan_row)
106 ncol = getNcol(plan_col)
107 #else
108 nlocal = getNlocal()
109 natoms = nlocal
110 #endif
111
112 call getRcut(rcut,rcut2=rcutsq)
113 call getRlist(rlist,rlistsq)
114
115 call check_initialization()
116 call zero_work_arrays()
117
118 do_pot = do_pot_c
119 do_stress = do_stress_c
120
121 ! Gather all information needed by all force loops:
122
123 #ifdef IS_MPI
124
125 call gather(q,q_Row,plan_row3d)
126 call gather(q,q_Col,plan_col3d)
127
128 if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
129 call gather(u_l,u_l_Row,plan_row3d)
130 call gather(u_l,u_l_Col,plan_col3d)
131
132 call gather(A,A_Row,plan_row_rotation)
133 call gather(A,A_Col,plan_col_rotation)
134 endif
135
136 #endif
137
138 if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
139 !! See if we need to update neighbor lists
140 call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)
141 !! if_mpi_gather_stuff_for_prepair
142 !! do_prepair_loop_if_needed
143 !! if_mpi_scatter_stuff_from_prepair
144 !! if_mpi_gather_stuff_from_prepair_to_main_loop
145 else
146 !! See if we need to update neighbor lists
147 call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)
148 endif
149
150 #ifdef IS_MPI
151
152 if (update_nlist) then
153
154 !! save current configuration, construct neighbor list,
155 !! and calculate forces
156 call save_neighborList(q)
157
158 neighborListSize = getNeighborListSize()
159 nlist = 0
160
161 do i = 1, nrow
162 point(i) = nlist + 1
163
164 inner: do j = 1, ncol
165
166 if (check_exclude(i,j)) cycle inner:
167
168 call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
169
170 if (rijsq < rlistsq) then
171
172 nlist = nlist + 1
173
174 if (nlist > neighborListSize) then
175 call expandNeighborList(nlocal, listerror)
176 if (listerror /= 0) then
177 error = -1
178 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
179 return
180 end if
181 endif
182
183 list(nlist) = j
184
185 if (rijsq < rcutsq) then
186 call do_pair(i, j, rijsq, d, do_pot, do_stress)
187 endif
188 endif
189 enddo inner
190 enddo
191
192 point(nrow + 1) = nlist + 1
193
194 else !! (of update_check)
195
196 ! use the list to find the neighbors
197 do i = 1, nrow
198 JBEG = POINT(i)
199 JEND = POINT(i+1) - 1
200 ! check thiat molecule i has neighbors
201 if (jbeg .le. jend) then
202
203 do jnab = jbeg, jend
204 j = list(jnab)
205
206 call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
207 call do_pair(i, j, rijsq, d, do_pot, do_stress)
208
209 enddo
210 endif
211 enddo
212 endif
213
214 #else
215
216 if (update_nlist) then
217
218 ! save current configuration, contruct neighbor list,
219 ! and calculate forces
220 call save_neighborList(q)
221
222 neighborListSize = getNeighborListSize()
223 nlist = 0
224
225 do i = 1, natoms-1
226 point(i) = nlist + 1
227
228 inner: do j = i+1, natoms
229
230 if (check_exclude(i,j)) cycle inner:
231
232 call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
233
234 if (rijsq < rlistsq) then
235
236 nlist = nlist + 1
237
238 if (nlist > neighborListSize) then
239 call expandList(natoms, listerror)
240 if (listerror /= 0) then
241 error = -1
242 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
243 return
244 end if
245 endif
246
247 list(nlist) = j
248
249 if (rijsq < rcutsq) then
250 call do_pair(i, j, rijsq, d, do_pot, do_stress)
251 endif
252 endif
253 enddo inner
254 enddo
255
256 point(natoms) = nlist + 1
257
258 else !! (update)
259
260 ! use the list to find the neighbors
261 do i = 1, nrow
262 JBEG = POINT(i)
263 JEND = POINT(i+1) - 1
264 ! check thiat molecule i has neighbors
265 if (jbeg .le. jend) then
266
267 do jnab = jbeg, jend
268 j = list(jnab)
269
270 call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
271 call do_pair(i, j, rijsq, d, do_pot, do_stress)
272
273 enddo
274 endif
275 enddo
276 endif
277
278 #endif
279
280 ! phew, done with main loop.
281
282 #ifdef IS_MPI
283 !!distribute forces
284
285 call scatter(f_Row,f,plan_row3d)
286 call scatter(f_Col,f_temp,plan_col3d)
287 do i = 1,nlocal
288 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
289 end do
290
291 if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
292 call scatter(t_Row,t,plan_row3d)
293 call scatter(t_Col,t_temp,plan_col3d)
294
295 do i = 1,nlocal
296 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
297 end do
298 endif
299
300 if (do_pot) then
301 ! scatter/gather pot_row into the members of my column
302 call scatter(pot_Row, pot_Temp, plan_row)
303
304 ! scatter/gather pot_local into all other procs
305 ! add resultant to get total pot
306 do i = 1, nlocal
307 pot_local = pot_local + pot_Temp(i)
308 enddo
309
310 pot_Temp = 0.0_DP
311
312 call scatter(pot_Col, pot_Temp, plan_col)
313 do i = 1, nlocal
314 pot_local = pot_local + pot_Temp(i)
315 enddo
316
317 endif
318
319 if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
320
321 if (FF_uses_RF .and. SimUsesRF()) then
322
323 #ifdef IS_MPI
324 call scatter(rf_Row,rf,plan_row3d)
325 call scatter(rf_Col,rf_Temp,plan_col3d)
326 do i = 1,nlocal
327 rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
328 end do
329 #endif
330
331 do i = 1, getNlocal()
332
333 #ifdef IS_MPI
334 me_i = atid_row(i)
335 #else
336 me_i = atid(i)
337 #endif
338 call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
339 if ( is_DP_i ) then
340 call getElementProperty(atypes, me_i, "dipole_moment", mu_i)
341 !! The reaction field needs to include a self contribution
342 !! to the field:
343 call accumulate_self_rf(i, mu_i, u_l)
344 !! Get the reaction field contribution to the
345 !! potential and torques:
346 call reaction_field(i, mu_i, u_l, rfpot, t, do_pot)
347 #ifdef IS_MPI
348 pot_local = pot_local + rfpot
349 #else
350 pot = pot + rfpot
351 #endif
352 endif
353 enddo
354 endif
355 endif
356
357
358 #ifdef IS_MPI
359
360 if (do_pot) then
361 pot = pot_local
362 !! we assume the c code will do the allreduce to get the total potential
363 !! we could do it right here if we needed to...
364 endif
365
366 if (do_stress) then
367 mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
368 mpi_comm_world,mpi_err)
369 mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
370 mpi_comm_world,mpi_err)
371 endif
372
373 #else
374
375 if (do_stress) then
376 tau = tau_Temp
377 virial = virial_Temp
378 endif
379
380 #endif
381
382 end subroutine do_force_loop
383
384
385 !! Calculate any pre-force loop components and update nlist if necessary.
386 subroutine do_preForce(updateNlist)
387 logical, intent(inout) :: updateNlist
388
389
390
391 end subroutine do_preForce
392
393 !! Calculate any post force loop components, i.e. reaction field, etc.
394 subroutine do_postForce()
395
396
397
398 end subroutine do_postForce
399
400 subroutine do_pair(i, j, rijsq, d, do_pot, do_stress)
401
402 logical, intent(inout) :: do_pot, do_stress
403 integer, intent(in) :: i, j
404 real ( kind = dp ), intent(in) :: rijsq
405 real ( kind = dp ) :: r
406 real ( kind = dp ), intent(inout) :: d(3)
407
408 r = sqrt(rijsq)
409
410 logical :: is_LJ_i, is_LJ_j
411 logical :: is_DP_i, is_DP_j
412 logical :: is_Sticky_i, is_Sticky_j
413 integer :: me_i, me_j
414
415 #ifdef IS_MPI
416
417 me_i = atid_row(i)
418 me_j = atid_col(j)
419
420 #else
421
422 me_i = atid(i)
423 me_j = atid(j)
424
425 #endif
426
427
428 if (FF_uses_LJ .and. SimUsesLJ()) then
429 call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
430 call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
431
432 if ( is_LJ_i .and. is_LJ_j ) &
433 call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
434 endif
435
436
437 if (FF_uses_DP .and. SimUsesDP()) then
438 call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
439 call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
440
441 if ( is_DP_i .and. is_DP_j ) then
442
443 call do_dipole_pair(i, j, d, r, pot, u_l, f, t, do_pot, do_stress)
444
445 if (FF_uses_RF .and. SimUsesRF()) then
446
447 call accumulate_rf(i, j, r, u_l)
448 call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
449
450 endif
451
452 endif
453 endif
454
455 if (FF_uses_Sticky .and. SimUsesSticky()) then
456
457 call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
458 call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
459
460 if ( is_Sticky_i .and. is_Sticky_j ) then
461 call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
462 do_pot, do_stress)
463 endif
464 endif
465
466 end subroutine do_pair
467
468
469 subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
470
471 real (kind = dp), dimension(3) :: q_i
472 real (kind = dp), dimension(3) :: q_j
473 real ( kind = dp ), intent(out) :: r_sq
474 real( kind = dp ) :: d(3)
475
476 d(1:3) = q_i(1:3) - q_j(1:3)
477
478 ! Wrap back into periodic box if necessary
479 if ( isPBC() ) then
480 d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
481 int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
482 endif
483
484 r_sq = dot_product(d,d)
485
486 end subroutine get_interatomic_vector
487
488 subroutine check_initialization(error)
489 integer, intent(out) :: error
490
491 error = 0
492 ! Make sure we are properly initialized.
493 if (.not. do_Forces_initialized) then
494 write(default_error,*) "ERROR: do_Forces has not been initialized!"
495 error = -1
496 return
497 endif
498 #ifdef IS_MPI
499 if (.not. isMPISimSet()) then
500 write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
501 error = -1
502 return
503 endif
504 #endif
505
506 return
507 end subroutine check_initialization
508
509
510 subroutine zero_work_arrays()
511
512 #ifdef IS_MPI
513
514 q_Row = 0.0_dp
515 q_Col = 0.0_dp
516
517 u_l_Row = 0.0_dp
518 u_l_Col = 0.0_dp
519
520 A_Row = 0.0_dp
521 A_Col = 0.0_dp
522
523 f_Row = 0.0_dp
524 f_Col = 0.0_dp
525 f_Temp = 0.0_dp
526
527 t_Row = 0.0_dp
528 t_Col = 0.0_dp
529 t_Temp = 0.0_dp
530
531 pot_Row = 0.0_dp
532 pot_Col = 0.0_dp
533 pot_Temp = 0.0_dp
534
535 #endif
536
537 tau_Temp = 0.0_dp
538 virial_Temp = 0.0_dp
539
540 end subroutine zero_work_arrays
541
542
543 !! Function to properly build neighbor lists in MPI using newtons 3rd law.
544 !! We don't want 2 processors doing the same i j pair twice.
545 !! Also checks to see if i and j are the same particle.
546 function checkExcludes(atom1,atom2) result(do_cycle)
547 !--------------- Arguments--------------------------
548 ! Index i
549 integer,intent(in) :: atom1
550 ! Index j
551 integer,intent(in), optional :: atom2
552 ! Result do_cycle
553 logical :: do_cycle
554 !--------------- Local variables--------------------
555 integer :: tag_i
556 integer :: tag_j
557 integer :: i
558 !--------------- END DECLARATIONS------------------
559 do_cycle = .false.
560
561 #ifdef IS_MPI
562 tag_i = tagRow(atom1)
563 #else
564 tag_i = tag(atom1)
565 #endif
566
567 !! Check global excludes first
568 if (.not. present(atom2)) then
569 do i = 1,nGlobalExcludes
570 if (excludeGlobal(i) == tag_i) then
571 do_cycle = .true.
572 return
573 end if
574 end do
575 return !! return after checking globals
576 end if
577
578 !! we return if j not present here.
579 tag_j = tagColumn(j)
580
581
582
583 if (tag_i == tag_j) then
584 do_cycle = .true.
585 return
586 end if
587
588 if (tag_i < tag_j) then
589 if (mod(tag_i + tag_j,2) == 0) do_cycle = .true.
590 return
591 else
592 if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
593 endif
594
595
596
597 do i = 1, nLocalExcludes
598 if (tag_i = excludes(1,i) .and. excludes(2,i) < 0) then
599 do_cycle = .true.
600 return
601 end if
602 end do
603
604
605 end function checkExcludes
606
607 function FF_UsesDirectionalAtoms() result(doesit)
608 logical :: doesit
609 doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
610 FF_uses_GB .or. FF_uses_RF
611 end function FF_UsesDirectionalAtoms
612
613 function FF_RequiresPrepairCalc() result(doesit)
614 logical :: doesit
615 doesit = FF_uses_EAM
616 end function FF_RequiresPrepairCalc
617
618 function FF_RequiresPostpairCalc() result(doesit)
619 logical :: doesit
620 doesit = FF_uses_RF
621 end function FF_RequiresPostpairCalc
622
623 end module do_Forces