ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/do_Forces.F90
Revision: 1160
Committed: Tue May 11 21:31:15 2004 UTC (21 years, 2 months ago) by gezelter
File size: 43874 byte(s)
Log Message:
Fortran-side changes for group-based cutoffs

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.55 2004-05-11 21:31:14 gezelter Exp $, $Date: 2004-05-11 21:31:14 $, $Name: not supported by cvs2svn $, $Revision: 1.55 $
8
9 module do_Forces
10 use force_globals
11 use simulation
12 use definitions
13 use atype_module
14 use switcheroo
15 use neighborLists
16 use lj
17 use sticky_pair
18 use dipole_dipole
19 use charge_charge
20 use reaction_field
21 use gb_pair
22 use vector_class
23 use eam
24 use status
25 #ifdef IS_MPI
26 use mpiSimulation
27 #endif
28
29 implicit none
30 PRIVATE
31
32 #define __FORTRAN90
33 #include "fForceField.h"
34 #include "fSwitchingFunction.h"
35
36 logical, save :: haveRlist = .false.
37 logical, save :: haveNeighborList = .false.
38 logical, save :: havePolicies = .false.
39 logical, save :: haveSIMvariables = .false.
40 logical, save :: havePropertyMap = .false.
41 logical, save :: haveSaneForceField = .false.
42 logical, save :: FF_uses_LJ
43 logical, save :: FF_uses_sticky
44 logical, save :: FF_uses_charges
45 logical, save :: FF_uses_dipoles
46 logical, save :: FF_uses_RF
47 logical, save :: FF_uses_GB
48 logical, save :: FF_uses_EAM
49 logical, save :: SIM_uses_LJ
50 logical, save :: SIM_uses_sticky
51 logical, save :: SIM_uses_charges
52 logical, save :: SIM_uses_dipoles
53 logical, save :: SIM_uses_RF
54 logical, save :: SIM_uses_GB
55 logical, save :: SIM_uses_EAM
56 logical, save :: SIM_requires_postpair_calc
57 logical, save :: SIM_requires_prepair_calc
58 logical, save :: SIM_uses_directional_atoms
59 logical, save :: SIM_uses_PBC
60 logical, save :: SIM_uses_molecular_cutoffs
61
62 real(kind=dp), save :: rlist, rlistsq
63
64 public :: init_FF
65 public :: do_force_loop
66 public :: setRlistDF
67
68 #ifdef PROFILE
69 public :: getforcetime
70 real, save :: forceTime = 0
71 real :: forceTimeInitial, forceTimeFinal
72 integer :: nLoops
73 #endif
74
75 type :: Properties
76 logical :: is_lj = .false.
77 logical :: is_sticky = .false.
78 logical :: is_dp = .false.
79 logical :: is_gb = .false.
80 logical :: is_eam = .false.
81 logical :: is_charge = .false.
82 real(kind=DP) :: charge = 0.0_DP
83 real(kind=DP) :: dipole_moment = 0.0_DP
84 end type Properties
85
86 type(Properties), dimension(:),allocatable :: PropertyMap
87
88 contains
89
90 subroutine setRlistDF( this_rlist )
91
92 real(kind=dp) :: this_rlist
93
94 rlist = this_rlist
95 rlistsq = rlist * rlist
96
97 haveRlist = .true.
98
99 end subroutine setRlistDF
100
101 subroutine createPropertyMap(status)
102 integer :: nAtypes
103 integer :: status
104 integer :: i
105 logical :: thisProperty
106 real (kind=DP) :: thisDPproperty
107
108 status = 0
109
110 nAtypes = getSize(atypes)
111
112 if (nAtypes == 0) then
113 status = -1
114 return
115 end if
116
117 if (.not. allocated(PropertyMap)) then
118 allocate(PropertyMap(nAtypes))
119 endif
120
121 do i = 1, nAtypes
122 call getElementProperty(atypes, i, "is_LJ", thisProperty)
123 PropertyMap(i)%is_LJ = thisProperty
124
125 call getElementProperty(atypes, i, "is_Charge", thisProperty)
126 PropertyMap(i)%is_Charge = thisProperty
127
128 if (thisProperty) then
129 call getElementProperty(atypes, i, "charge", thisDPproperty)
130 PropertyMap(i)%charge = thisDPproperty
131 endif
132
133 call getElementProperty(atypes, i, "is_DP", thisProperty)
134 PropertyMap(i)%is_DP = thisProperty
135
136 if (thisProperty) then
137 call getElementProperty(atypes, i, "dipole_moment", thisDPproperty)
138 PropertyMap(i)%dipole_moment = thisDPproperty
139 endif
140
141 call getElementProperty(atypes, i, "is_Sticky", thisProperty)
142 PropertyMap(i)%is_Sticky = thisProperty
143 call getElementProperty(atypes, i, "is_GB", thisProperty)
144 PropertyMap(i)%is_GB = thisProperty
145 call getElementProperty(atypes, i, "is_EAM", thisProperty)
146 PropertyMap(i)%is_EAM = thisProperty
147 end do
148
149 havePropertyMap = .true.
150
151 end subroutine createPropertyMap
152
153 subroutine setSimVariables()
154 SIM_uses_LJ = SimUsesLJ()
155 SIM_uses_sticky = SimUsesSticky()
156 SIM_uses_charges = SimUsesCharges()
157 SIM_uses_dipoles = SimUsesDipoles()
158 SIM_uses_RF = SimUsesRF()
159 SIM_uses_GB = SimUsesGB()
160 SIM_uses_EAM = SimUsesEAM()
161 SIM_requires_postpair_calc = SimRequiresPostpairCalc()
162 SIM_requires_prepair_calc = SimRequiresPrepairCalc()
163 SIM_uses_directional_atoms = SimUsesDirectionalAtoms()
164 SIM_uses_PBC = SimUsesPBC()
165 !SIM_uses_molecular_cutoffs = SimUsesMolecularCutoffs()
166
167 haveSIMvariables = .true.
168
169 return
170 end subroutine setSimVariables
171
172 subroutine doReadyCheck(error)
173 integer, intent(out) :: error
174
175 integer :: myStatus
176
177 error = 0
178
179 if (.not. havePropertyMap) then
180
181 myStatus = 0
182
183 call createPropertyMap(myStatus)
184
185 if (myStatus .ne. 0) then
186 write(default_error, *) 'createPropertyMap failed in do_Forces!'
187 error = -1
188 return
189 endif
190 endif
191
192 if (.not. haveSIMvariables) then
193 call setSimVariables()
194 endif
195
196 if (.not. haveRlist) then
197 write(default_error, *) 'rList has not been set in do_Forces!'
198 error = -1
199 return
200 endif
201
202 if (SIM_uses_LJ .and. FF_uses_LJ) then
203 if (.not. havePolicies) then
204 write(default_error, *) 'LJ mixing Policies have not been set in do_Forces!'
205 error = -1
206 return
207 endif
208 endif
209
210 if (.not. haveNeighborList) then
211 write(default_error, *) 'neighbor list has not been initialized in do_Forces!'
212 error = -1
213 return
214 end if
215
216 if (.not. haveSaneForceField) then
217 write(default_error, *) 'Force Field is not sane in do_Forces!'
218 error = -1
219 return
220 end if
221
222 #ifdef IS_MPI
223 if (.not. isMPISimSet()) then
224 write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
225 error = -1
226 return
227 endif
228 #endif
229 return
230 end subroutine doReadyCheck
231
232
233 subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
234
235 integer, intent(in) :: LJMIXPOLICY
236 logical, intent(in) :: use_RF_c
237
238 integer, intent(out) :: thisStat
239 integer :: my_status, nMatches
240 integer, pointer :: MatchList(:) => null()
241 real(kind=dp) :: rcut, rrf, rt, dielect
242
243 !! assume things are copacetic, unless they aren't
244 thisStat = 0
245
246 !! Fortran's version of a cast:
247 FF_uses_RF = use_RF_c
248
249 !! init_FF is called *after* all of the atom types have been
250 !! defined in atype_module using the new_atype subroutine.
251 !!
252 !! this will scan through the known atypes and figure out what
253 !! interactions are used by the force field.
254
255 FF_uses_LJ = .false.
256 FF_uses_sticky = .false.
257 FF_uses_charges = .false.
258 FF_uses_dipoles = .false.
259 FF_uses_GB = .false.
260 FF_uses_EAM = .false.
261
262 call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
263 if (nMatches .gt. 0) FF_uses_LJ = .true.
264
265 call getMatchingElementList(atypes, "is_Charge", .true., nMatches, MatchList)
266 if (nMatches .gt. 0) FF_uses_charges = .true.
267
268 call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
269 if (nMatches .gt. 0) FF_uses_dipoles = .true.
270
271 call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
272 MatchList)
273 if (nMatches .gt. 0) FF_uses_Sticky = .true.
274
275 call getMatchingElementList(atypes, "is_GB", .true., nMatches, MatchList)
276 if (nMatches .gt. 0) FF_uses_GB = .true.
277
278 call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
279 if (nMatches .gt. 0) FF_uses_EAM = .true.
280
281 !! Assume sanity (for the sake of argument)
282 haveSaneForceField = .true.
283
284 !! check to make sure the FF_uses_RF setting makes sense
285
286 if (FF_uses_dipoles) then
287 if (FF_uses_RF) then
288 dielect = getDielect()
289 call initialize_rf(dielect)
290 endif
291 else
292 if (FF_uses_RF) then
293 write(default_error,*) 'Using Reaction Field with no dipoles? Huh?'
294 thisStat = -1
295 haveSaneForceField = .false.
296 return
297 endif
298 endif
299
300 if (FF_uses_LJ) then
301
302 select case (LJMIXPOLICY)
303 case (LB_MIXING_RULE)
304 call init_lj_FF(LB_MIXING_RULE, my_status)
305 case (EXPLICIT_MIXING_RULE)
306 call init_lj_FF(EXPLICIT_MIXING_RULE, my_status)
307 case default
308 write(default_error,*) 'unknown LJ Mixing Policy!'
309 thisStat = -1
310 haveSaneForceField = .false.
311 return
312 end select
313 if (my_status /= 0) then
314 thisStat = -1
315 haveSaneForceField = .false.
316 return
317 end if
318 havePolicies = .true.
319 endif
320
321 if (FF_uses_sticky) then
322 call check_sticky_FF(my_status)
323 if (my_status /= 0) then
324 thisStat = -1
325 haveSaneForceField = .false.
326 return
327 end if
328 endif
329
330
331 if (FF_uses_EAM) then
332 call init_EAM_FF(my_status)
333 if (my_status /= 0) then
334 write(default_error, *) "init_EAM_FF returned a bad status"
335 thisStat = -1
336 haveSaneForceField = .false.
337 return
338 end if
339 endif
340
341 if (FF_uses_GB) then
342 call check_gb_pair_FF(my_status)
343 if (my_status .ne. 0) then
344 thisStat = -1
345 haveSaneForceField = .false.
346 return
347 endif
348 endif
349
350 if (FF_uses_GB .and. FF_uses_LJ) then
351 endif
352 if (.not. haveNeighborList) then
353 !! Create neighbor lists
354 call expandNeighborList(nLocal, my_status)
355 if (my_Status /= 0) then
356 write(default_error,*) "SimSetup: ExpandNeighborList returned error."
357 thisStat = -1
358 return
359 endif
360 haveNeighborList = .true.
361 endif
362
363
364
365 end subroutine init_FF
366
367
368 !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
369 !------------------------------------------------------------->
370 subroutine do_force_loop(q, q_group, A, u_l, f, t, tau, pot, &
371 do_pot_c, do_stress_c, error)
372 !! Position array provided by C, dimensioned by getNlocal
373 real ( kind = dp ), dimension(3,nLocal) :: q
374 !! molecular center-of-mass position array
375 real ( kind = dp ), dimension(3,nGroup) :: q_group
376 !! Rotation Matrix for each long range particle in simulation.
377 real( kind = dp), dimension(9,nLocal) :: A
378 !! Unit vectors for dipoles (lab frame)
379 real( kind = dp ), dimension(3,nLocal) :: u_l
380 !! Force array provided by C, dimensioned by getNlocal
381 real ( kind = dp ), dimension(3,nLocal) :: f
382 !! Torsion array provided by C, dimensioned by getNlocal
383 real( kind = dp ), dimension(3,nLocal) :: t
384
385 !! Stress Tensor
386 real( kind = dp), dimension(9) :: tau
387 real ( kind = dp ) :: pot
388 logical ( kind = 2) :: do_pot_c, do_stress_c
389 logical :: do_pot
390 logical :: do_stress
391 logical :: in_switching_region
392 #ifdef IS_MPI
393 real( kind = DP ) :: pot_local
394 integer :: nrow
395 integer :: ncol
396 integer :: nprocs
397 integer :: nrow_group
398 integer :: ncol_group
399 #endif
400 integer :: natoms
401 logical :: update_nlist
402 integer :: i, j, jbeg, jend, jnab
403 integer :: ia, jb, atom1, atom2
404 integer :: nlist
405 real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vab
406 real( kind = DP ) :: sw, dswdr, swderiv, mf
407 real(kind=dp),dimension(3) :: d_atm, d_grp
408 real(kind=dp) :: rfpot, mu_i, virial
409 integer :: me_i, me_j
410 logical :: is_dp_i
411 integer :: neighborListSize
412 integer :: listerror, error
413 integer :: localError
414 integer :: propPack_i, propPack_j
415
416 real(kind=dp) :: listSkin = 1.0
417
418 !! initialize local variables
419
420 #ifdef IS_MPI
421 pot_local = 0.0_dp
422 nrow = getNrow(plan_row)
423 ncol = getNcol(plan_col)
424 nrow_group = getNrowGroup(plan_row)
425 ncol_group = getNcolGroup(plan_col)
426 #else
427 natoms = nlocal
428 #endif
429
430 call doReadyCheck(localError)
431 if ( localError .ne. 0 ) then
432 call handleError("do_force_loop", "Not Initialized")
433 error = -1
434 return
435 end if
436 call zero_work_arrays()
437
438 do_pot = do_pot_c
439 do_stress = do_stress_c
440
441 ! Gather all information needed by all force loops:
442
443 #ifdef IS_MPI
444
445 call gather(q, q_Row, plan_row3d)
446 call gather(q, q_Col, plan_col3d)
447
448 call gather(q_group, q_group_Row, plan_row_Group_3d)
449 call gather(q_group, q_group_Col, plan_col_Group_3d)
450
451 if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
452 call gather(u_l,u_l_Row,plan_row3d)
453 call gather(u_l,u_l_Col,plan_col3d)
454
455 call gather(A,A_Row,plan_row_rotation)
456 call gather(A,A_Col,plan_col_rotation)
457 endif
458
459 #endif
460
461 !! Begin force loop timing:
462 #ifdef PROFILE
463 call cpu_time(forceTimeInitial)
464 nloops = nloops + 1
465 #endif
466
467 if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
468 !! See if we need to update neighbor lists
469
470 call checkNeighborList(nGroup, q_group, listSkin, update_nlist)
471
472 !! if_mpi_gather_stuff_for_prepair
473 !! do_prepair_loop_if_needed
474 !! if_mpi_scatter_stuff_from_prepair
475 !! if_mpi_gather_stuff_from_prepair_to_main_loop
476
477 !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
478 #ifdef IS_MPI
479
480 if (update_nlist) then
481
482 !! save current configuration, construct neighbor list,
483 !! and calculate forces
484
485 call saveNeighborList(nGroup, q_group)
486
487 neighborListSize = size(list)
488 nlist = 0
489
490 do i = 1, nrow_group
491 point(i) = nlist + 1
492
493 do j = 1, ncol_group
494
495 call get_interatomic_vector(q_group_Row(:,i), &
496 q_group_Col(:,j), d_grp, rgrpsq)
497
498 if (rgrpsq < rlistsq) then
499 nlist = nlist + 1
500
501 if (nlist > neighborListSize) then
502 call expandNeighborList(nGroup, listerror)
503 if (listerror /= 0) then
504 error = -1
505 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
506 return
507 end if
508 neighborListSize = size(list)
509 endif
510
511 list(nlist) = j
512
513 do ia = groupStart(i), groupStart(i+1)-1
514 atom1 = groupList(ia)
515
516 prepair_inner: do jb = groupStart(j), groupStart(j+1)-1
517 atom2 = groupList(jb)
518
519 if (skipThisPair(atom1, atom2)) cycle prepair_inner
520
521 call get_interatomic_vector(q_Row(:,atom1), &
522 q_Col(:,atom2), d_atm, ratmsq)
523
524 call do_prepair(atom1, atom2, ratmsq, d_atm, &
525 rgrpsq, d_grp, do_pot, do_stress, &
526 u_l, A, f, t, pot_local)
527
528 enddo prepair_inner
529 enddo
530 end if
531 enddo
532 enddo
533 point(nrow_group + 1) = nlist + 1
534
535 else !! (of update_check)
536
537 ! use the list to find the neighbors
538 do i = 1, nrow_group
539 JBEG = POINT(i)
540 JEND = POINT(i+1) - 1
541 ! check that group i has neighbors
542 if (jbeg .le. jend) then
543
544 do jnab = jbeg, jend
545 j = list(jnab)
546
547 do ia = groupStart(i), groupStart(i+1)-1
548 atom1 = groupList(ia)
549
550 do jb = groupStart(j), groupStart(j+1)-1
551 atom2 = groupList(jb)
552
553 call get_interatomic_vector(q_Row(:,atom1), &
554 q_Col(:,atom2), d_atm, ratmsq)
555
556 call do_prepair(atom1, atom2, ratmsq, d_atm, &
557 rgrpsq, d_grp, do_pot, do_stress, &
558 u_l, A, f, t, pot_local)
559
560 enddo
561 enddo
562 enddo
563 endif
564 enddo
565 endif
566
567 #else
568
569 if (update_nlist) then
570
571 !! save current configuration, construct neighbor list,
572 !! and calculate forces
573
574 call saveNeighborList(nGroup, q_group)
575
576 neighborListSize = size(list)
577 nlist = 0
578
579 do i = 1, nGroup-1
580 point(i) = nlist + 1
581
582 do j = i+1, nGroup
583
584 call get_interatomic_vector(q_group(:,i), &
585 q_group(:,j), d_grp, rgrpsq)
586
587 if (rgrpsq < rlistsq) then
588 nlist = nlist + 1
589
590 if (nlist > neighborListSize) then
591 call expandNeighborList(nGroup, listerror)
592 if (listerror /= 0) then
593 error = -1
594 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
595 return
596 end if
597 neighborListSize = size(list)
598 endif
599
600 list(nlist) = j
601
602 do ia = groupStart(i), groupStart(i+1)-1
603 atom1 = groupList(ia)
604
605 prepair_inner: do jb = groupStart(j), groupStart(j+1)-1
606 atom2 = groupList(jb)
607
608 if (skipThisPair(atom1, atom2)) cycle prepair_inner
609
610 call get_interatomic_vector(q(:,atom1), &
611 q(:,atom2), d_atm, ratmsq)
612
613 call do_prepair(atom1, atom2, ratmsq, d_atm, &
614 rgrpsq, d_grp, do_pot, do_stress, &
615 u_l, A, f, t, pot)
616
617 enddo prepair_inner
618 enddo
619 end if
620 enddo
621 enddo
622 point(nGroup) = nlist + 1
623
624 else !! (of update_check)
625
626 ! use the list to find the neighbors
627 do i = 1, nGroup-1
628 JBEG = POINT(i)
629 JEND = POINT(i+1) - 1
630 ! check that group i has neighbors
631 if (jbeg .le. jend) then
632
633 do jnab = jbeg, jend
634 j = list(jnab)
635
636 do ia = groupStart(i), groupStart(i+1)-1
637 atom1 = groupList(ia)
638
639 do jb = groupStart(j), groupStart(j+1)-1
640 atom2 = groupList(jb)
641
642 call get_interatomic_vector(q(:,atom1), &
643 q(:,atom2), d_atm, ratmsq)
644
645 call do_prepair(atom1, atom2, ratmsq, d_atm, &
646 rgrpsq, d_grp, do_pot, do_stress, &
647 u_l, A, f, t, pot)
648
649 enddo
650 enddo
651 enddo
652 endif
653 enddo
654 endif
655
656 #endif
657
658 !! Do rest of preforce calculations
659 !! do necessary preforce calculations
660 call do_preforce(nlocal,pot)
661 ! we have already updated the neighbor list set it to false...
662 update_nlist = .false.
663 else
664 !! See if we need to update neighbor lists for non pre-pair
665 call checkNeighborList(nGroup, q_group, listSkin, update_nlist)
666 endif
667
668 !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>
669
670 #ifdef IS_MPI
671
672 if (update_nlist) then
673
674 !! save current configuration, construct neighbor list,
675 !! and calculate forces
676
677 call saveNeighborList(nGroup, q_group)
678
679 neighborListSize = size(list)
680 nlist = 0
681
682 do i = 1, nrow_group
683 point(i) = nlist + 1
684
685 do j = 1, ncol_group
686
687 call get_interatomic_vector(q_group_Row(:,i), &
688 q_group_Col(:,j), d_grp, rgrpsq)
689
690 if (rgrpsq < rlistsq) then
691 nlist = nlist + 1
692
693 if (nlist > neighborListSize) then
694 call expandNeighborList(nGroup, listerror)
695 if (listerror /= 0) then
696 error = -1
697 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
698 return
699 end if
700 neighborListSize = size(list)
701 endif
702
703 list(nlist) = j
704
705 vab = 0.0d0
706 call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
707 in_switching_region)
708
709 do ia = groupStart(i), groupStart(i+1)-1
710 atom1 = groupList(ia)
711
712 inner: do jb = groupStart(j), groupStart(j+1)-1
713 atom2 = groupList(jb)
714
715 if (skipThisPair(atom1, atom2)) cycle inner
716
717 call get_interatomic_vector(q_Row(:,atom1), &
718 q_Col(:,atom2), d_atm, ratmsq)
719
720 call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
721 do_pot, do_stress, &
722 u_l, A, f, t, pot_local, vpair)
723
724 vab = vab + vpair
725 enddo inner
726 enddo
727
728 if (in_switching_region) then
729 swderiv = vab*dswdr/rgrp
730
731 do ia=groupStart(i), groupStart(i+1)-1
732 atom1=groupList(ia)
733 mf = mfact(atom1)
734 f_Row(1,atom1) = f_Row(1,atom1) - swderiv*d_grp(1)*mf
735 f_Row(2,atom1) = f_Row(2,atom1) - swderiv*d_grp(2)*mf
736 f_Row(3,atom1) = f_Row(3,atom1) - swderiv*d_grp(3)*mf
737 enddo
738
739 do jb=groupStart(j), groupStart(j+1)-1
740 atom2=groupList(jb)
741 mf = mfact(atom2)
742 f_Col(1,atom2) = f_Col(1,atom2) + swderiv*d_grp(1)*mf
743 f_Col(2,atom2) = f_Col(2,atom2) + swderiv*d_grp(2)*mf
744 f_Col(3,atom2) = f_Col(3,atom2) + swderiv*d_grp(3)*mf
745 enddo
746 endif
747
748 end if
749 enddo
750 enddo
751 point(nrow_group + 1) = nlist + 1
752
753 else !! (of update_check)
754
755 ! use the list to find the neighbors
756 do i = 1, nrow_group
757 JBEG = POINT(i)
758 JEND = POINT(i+1) - 1
759 ! check that group i has neighbors
760 if (jbeg .le. jend) then
761
762 do jnab = jbeg, jend
763 j = list(jnab)
764
765 call get_interatomic_vector(q_group_Row(:,i), &
766 q_group_Col(:,j), d_grp, rgrpsq)
767
768 vab = 0.0d0
769 call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
770 in_switching_region)
771
772 do ia = groupStart(i), groupStart(i+1)-1
773 atom1 = groupList(ia)
774
775 do jb = groupStart(j), groupStart(j+1)-1
776 atom2 = groupList(jb)
777
778 call get_interatomic_vector(q_Row(:,atom1), &
779 q_Col(:,atom2), d_atm, ratmsq)
780
781 call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
782 do_pot, do_stress, &
783 u_l, A, f, t, pot_local, vpair)
784
785 vab = vab + vpair
786
787 enddo
788 enddo
789
790 if (in_switching_region) then
791 swderiv = vab*dswdr/rgrp
792
793 do ia=groupStart(i), groupStart(i+1)-1
794 atom1=groupList(ia)
795 mf = mfact(atom1)
796 f_Row(1,atom1) = f_Row(1,atom1) - swderiv*d_grp(1)*mf
797 f_Row(2,atom1) = f_Row(2,atom1) - swderiv*d_grp(2)*mf
798 f_Row(3,atom1) = f_Row(3,atom1) - swderiv*d_grp(3)*mf
799 enddo
800
801 do jb=groupStart(j), groupStart(j+1)-1
802 atom2=groupList(jb)
803 mf = mfact(atom2)
804 f_Col(1,atom2) = f_Col(1,atom2) + swderiv*d_grp(1)*mf
805 f_Col(2,atom2) = f_Col(2,atom2) + swderiv*d_grp(2)*mf
806 f_Col(3,atom2) = f_Col(3,atom2) + swderiv*d_grp(3)*mf
807 enddo
808 endif
809
810 enddo
811 endif
812 enddo
813 endif
814
815 #else
816
817 if (update_nlist) then
818
819 !! save current configuration, construct neighbor list,
820 !! and calculate forces
821
822 call saveNeighborList(nGroup, q_group)
823
824 neighborListSize = size(list)
825 nlist = 0
826
827 do i = 1, nGroup-1
828 point(i) = nlist + 1
829
830 do j = i+1, nGroup
831
832 call get_interatomic_vector(q_group(:,i), &
833 q_group(:,j), d_grp, rgrpsq)
834
835 if (rgrpsq < rlistsq) then
836 nlist = nlist + 1
837
838 if (nlist > neighborListSize) then
839 call expandNeighborList(nGroup, listerror)
840 if (listerror /= 0) then
841 error = -1
842 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
843 return
844 end if
845 neighborListSize = size(list)
846 endif
847
848 list(nlist) = j
849
850 vab = 0.0d0
851 call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
852 in_switching_region)
853
854 do ia = groupStart(i), groupStart(i+1)-1
855 atom1 = groupList(ia)
856
857 inner: do jb = groupStart(j), groupStart(j+1)-1
858 atom2 = groupList(jb)
859
860 if (skipThisPair(atom1, atom2)) cycle inner
861
862 call get_interatomic_vector(q(:,atom1), &
863 q(:,atom2), d_atm, ratmsq)
864
865 call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
866 do_pot, do_stress, &
867 u_l, A, f, t, pot, vpair)
868
869 vab = vab + vpair
870
871 enddo inner
872 enddo
873
874 if (in_switching_region) then
875 swderiv = vab*dswdr/rgrp
876 do ia=groupStart(i), groupStart(i+1)-1
877 atom1=groupList(ia)
878 mf = mfact(atom1)
879 f(1,atom1) = f(1,atom1) - swderiv*d_grp(1)*mf
880 f(2,atom1) = f(2,atom1) - swderiv*d_grp(2)*mf
881 f(3,atom1) = f(3,atom1) - swderiv*d_grp(3)*mf
882 enddo
883
884 do jb=groupStart(j), groupStart(j+1)-1
885 atom2=groupList(jb)
886 mf = mfact(atom2)
887 f(1,atom2) = f(1,atom2) + swderiv*d_grp(1)*mf
888 f(2,atom2) = f(2,atom2) + swderiv*d_grp(2)*mf
889 f(3,atom2) = f(3,atom2) + swderiv*d_grp(3)*mf
890 enddo
891 endif
892
893 end if
894 enddo
895 enddo
896 point(nGroup) = nlist + 1
897
898 else !! (of update_check)
899
900 ! use the list to find the neighbors
901 do i = 1, nGroup-1
902 JBEG = POINT(i)
903 JEND = POINT(i+1) - 1
904 ! check that group i has neighbors
905 if (jbeg .le. jend) then
906
907 do jnab = jbeg, jend
908 j = list(jnab)
909
910 call get_interatomic_vector(q_group(:,i), &
911 q_group(:,j), d_grp, rgrpsq)
912
913 vab = 0.0d0
914 call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
915 in_switching_region)
916
917 do ia = groupStart(i), groupStart(i+1)-1
918 atom1 = groupList(ia)
919
920 do jb = groupStart(j), groupStart(j+1)-1
921 atom2 = groupList(jb)
922
923 call get_interatomic_vector(q(:,atom1), &
924 q(:,atom2), d_atm, ratmsq)
925
926 call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
927 do_pot, do_stress, &
928 u_l, A, f, t, pot, vpair)
929
930 vab = vab + vpair
931
932 enddo
933 enddo
934
935 if (in_switching_region) then
936 swderiv = vab*dswdr/rgrp
937
938 do ia=groupStart(i), groupStart(i+1)-1
939 atom1=groupList(ia)
940 mf = mfact(atom1)
941 f(1,atom1) = f(1,atom1) - swderiv*d_grp(1)*mf
942 f(2,atom1) = f(2,atom1) - swderiv*d_grp(2)*mf
943 f(3,atom1) = f(3,atom1) - swderiv*d_grp(3)*mf
944 enddo
945
946 do jb=groupStart(j), groupStart(j+1)-1
947 atom2=groupList(jb)
948 mf = mfact(atom2)
949 f(1,atom2) = f(1,atom2) + swderiv*d_grp(1)*mf
950 f(2,atom2) = f(2,atom2) + swderiv*d_grp(2)*mf
951 f(3,atom2) = f(3,atom2) + swderiv*d_grp(3)*mf
952 enddo
953 endif
954 enddo
955 endif
956 enddo
957 endif
958
959 #endif
960
961 ! phew, done with main loop.
962
963 !! Do timing
964 #ifdef PROFILE
965 call cpu_time(forceTimeFinal)
966 forceTime = forceTime + forceTimeFinal - forceTimeInitial
967 #endif
968
969 #ifdef IS_MPI
970 !!distribute forces
971
972 f_temp = 0.0_dp
973 call scatter(f_Row,f_temp,plan_row3d)
974 do i = 1,nlocal
975 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
976 end do
977
978 f_temp = 0.0_dp
979 call scatter(f_Col,f_temp,plan_col3d)
980 do i = 1,nlocal
981 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
982 end do
983
984 if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
985 t_temp = 0.0_dp
986 call scatter(t_Row,t_temp,plan_row3d)
987 do i = 1,nlocal
988 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
989 end do
990 t_temp = 0.0_dp
991 call scatter(t_Col,t_temp,plan_col3d)
992
993 do i = 1,nlocal
994 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
995 end do
996 endif
997
998 if (do_pot) then
999 ! scatter/gather pot_row into the members of my column
1000 call scatter(pot_Row, pot_Temp, plan_row)
1001
1002 ! scatter/gather pot_local into all other procs
1003 ! add resultant to get total pot
1004 do i = 1, nlocal
1005 pot_local = pot_local + pot_Temp(i)
1006 enddo
1007
1008 pot_Temp = 0.0_DP
1009
1010 call scatter(pot_Col, pot_Temp, plan_col)
1011 do i = 1, nlocal
1012 pot_local = pot_local + pot_Temp(i)
1013 enddo
1014
1015 endif
1016 #endif
1017
1018 if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
1019
1020 if (FF_uses_RF .and. SIM_uses_RF) then
1021
1022 #ifdef IS_MPI
1023 call scatter(rf_Row,rf,plan_row3d)
1024 call scatter(rf_Col,rf_Temp,plan_col3d)
1025 do i = 1,nlocal
1026 rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
1027 end do
1028 #endif
1029
1030 do i = 1, nLocal
1031
1032 rfpot = 0.0_DP
1033 #ifdef IS_MPI
1034 me_i = atid_row(i)
1035 #else
1036 me_i = atid(i)
1037 #endif
1038
1039 if (PropertyMap(me_i)%is_DP) then
1040
1041 mu_i = PropertyMap(me_i)%dipole_moment
1042
1043 !! The reaction field needs to include a self contribution
1044 !! to the field:
1045 call accumulate_self_rf(i, mu_i, u_l)
1046 !! Get the reaction field contribution to the
1047 !! potential and torques:
1048 call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
1049 #ifdef IS_MPI
1050 pot_local = pot_local + rfpot
1051 #else
1052 pot = pot + rfpot
1053
1054 #endif
1055 endif
1056 enddo
1057 endif
1058 endif
1059
1060
1061 #ifdef IS_MPI
1062
1063 if (do_pot) then
1064 pot = pot + pot_local
1065 !! we assume the c code will do the allreduce to get the total potential
1066 !! we could do it right here if we needed to...
1067 endif
1068
1069 if (do_stress) then
1070 call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
1071 mpi_comm_world,mpi_err)
1072 call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
1073 mpi_comm_world,mpi_err)
1074 endif
1075
1076 #else
1077
1078 if (do_stress) then
1079 tau = tau_Temp
1080 virial = virial_Temp
1081 endif
1082
1083 #endif
1084
1085
1086 end subroutine do_force_loop
1087
1088
1089 subroutine do_pair(i, j, rijsq, d, sw, do_pot, do_stress, &
1090 u_l, A, f, t, pot, vpair)
1091
1092 real( kind = dp ) :: pot, vpair, sw
1093 real( kind = dp ), dimension(nLocal) :: mfact
1094 real( kind = dp ), dimension(3,nLocal) :: u_l
1095 real( kind = dp ), dimension(9,nLocal) :: A
1096 real( kind = dp ), dimension(3,nLocal) :: f
1097 real( kind = dp ), dimension(3,nLocal) :: t
1098
1099 logical, intent(inout) :: do_pot, do_stress
1100 integer, intent(in) :: i, j
1101 real ( kind = dp ), intent(inout) :: rijsq
1102 real ( kind = dp ) :: r
1103 real ( kind = dp ), intent(inout) :: d(3)
1104 integer :: me_i, me_j
1105
1106 r = sqrt(rijsq)
1107
1108 #ifdef IS_MPI
1109 if (tagRow(i) .eq. tagColumn(j)) then
1110 write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
1111 endif
1112 me_i = atid_row(i)
1113 me_j = atid_col(j)
1114 #else
1115 me_i = atid(i)
1116 me_j = atid(j)
1117 #endif
1118
1119 if (FF_uses_LJ .and. SIM_uses_LJ) then
1120
1121 if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
1122 call do_lj_pair(i, j, d, r, rijsq, sw, vpair, pot, f, do_pot, &
1123 do_stress)
1124 endif
1125
1126 endif
1127
1128 if (FF_uses_charges .and. SIM_uses_charges) then
1129
1130 if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
1131 call do_charge_pair(i, j, d, r, rijsq, sw, vpair, pot, f, do_pot, &
1132 do_stress)
1133 endif
1134
1135 endif
1136
1137 if (FF_uses_dipoles .and. SIM_uses_dipoles) then
1138
1139 if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
1140 call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, pot, u_l, f, t, &
1141 do_pot, do_stress)
1142 if (FF_uses_RF .and. SIM_uses_RF) then
1143 call accumulate_rf(i, j, r, u_l, sw)
1144 call rf_correct_forces(i, j, d, r, u_l, sw, f, do_stress)
1145 endif
1146 endif
1147
1148 endif
1149
1150 if (FF_uses_Sticky .and. SIM_uses_sticky) then
1151
1152 if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
1153 call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, pot, A, f, t, &
1154 do_pot, do_stress)
1155 endif
1156
1157 endif
1158
1159
1160 if (FF_uses_GB .and. SIM_uses_GB) then
1161
1162 if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
1163 call do_gb_pair(i, j, d, r, rijsq, sw, vpair, pot, u_l, f, t, &
1164 do_pot, do_stress)
1165 endif
1166
1167 endif
1168
1169 if (FF_uses_EAM .and. SIM_uses_EAM) then
1170
1171 if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
1172 call do_eam_pair(i, j, d, r, rijsq, sw, vpair, pot, f, &
1173 do_pot, do_stress)
1174 endif
1175
1176 endif
1177
1178 end subroutine do_pair
1179
1180 subroutine do_prepair(i, j, rijsq, d, rcijsq, dc, &
1181 do_pot, do_stress, u_l, A, f, t, pot)
1182 real( kind = dp ) :: pot
1183 real( kind = dp ), dimension(3,nLocal) :: u_l
1184 real (kind=dp), dimension(9,nLocal) :: A
1185 real (kind=dp), dimension(3,nLocal) :: f
1186 real (kind=dp), dimension(3,nLocal) :: t
1187
1188 logical, intent(inout) :: do_pot, do_stress
1189 integer, intent(in) :: i, j
1190 real ( kind = dp ), intent(inout) :: rijsq, rcijsq
1191 real ( kind = dp ) :: r, rc
1192 real ( kind = dp ), intent(inout) :: d(3), dc(3)
1193
1194 logical :: is_EAM_i, is_EAM_j
1195
1196 integer :: me_i, me_j
1197
1198
1199 r = sqrt(rijsq)
1200 if (SIM_uses_molecular_cutoffs) then
1201 rc = sqrt(rcijsq)
1202 else
1203 rc = r
1204 endif
1205
1206
1207 #ifdef IS_MPI
1208 if (tagRow(i) .eq. tagColumn(j)) then
1209 write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
1210 endif
1211
1212 me_i = atid_row(i)
1213 me_j = atid_col(j)
1214
1215 #else
1216
1217 me_i = atid(i)
1218 me_j = atid(j)
1219
1220 #endif
1221
1222 if (FF_uses_EAM .and. SIM_uses_EAM) then
1223
1224 if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1225 call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1226
1227 endif
1228
1229 end subroutine do_prepair
1230
1231
1232
1233
1234 subroutine do_preforce(nlocal,pot)
1235 integer :: nlocal
1236 real( kind = dp ) :: pot
1237
1238 if (FF_uses_EAM .and. SIM_uses_EAM) then
1239 call calc_EAM_preforce_Frho(nlocal,pot)
1240 endif
1241
1242
1243 end subroutine do_preforce
1244
1245
1246 subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1247
1248 real (kind = dp), dimension(3) :: q_i
1249 real (kind = dp), dimension(3) :: q_j
1250 real ( kind = dp ), intent(out) :: r_sq
1251 real( kind = dp ) :: d(3), scaled(3)
1252 integer i
1253
1254 d(1:3) = q_j(1:3) - q_i(1:3)
1255
1256 ! Wrap back into periodic box if necessary
1257 if ( SIM_uses_PBC ) then
1258
1259 if( .not.boxIsOrthorhombic ) then
1260 ! calc the scaled coordinates.
1261
1262 scaled = matmul(HmatInv, d)
1263
1264 ! wrap the scaled coordinates
1265
1266 scaled = scaled - anint(scaled)
1267
1268
1269 ! calc the wrapped real coordinates from the wrapped scaled
1270 ! coordinates
1271
1272 d = matmul(Hmat,scaled)
1273
1274 else
1275 ! calc the scaled coordinates.
1276
1277 do i = 1, 3
1278 scaled(i) = d(i) * HmatInv(i,i)
1279
1280 ! wrap the scaled coordinates
1281
1282 scaled(i) = scaled(i) - anint(scaled(i))
1283
1284 ! calc the wrapped real coordinates from the wrapped scaled
1285 ! coordinates
1286
1287 d(i) = scaled(i)*Hmat(i,i)
1288 enddo
1289 endif
1290
1291 endif
1292
1293 r_sq = dot_product(d,d)
1294
1295 end subroutine get_interatomic_vector
1296
1297 subroutine zero_work_arrays()
1298
1299 #ifdef IS_MPI
1300
1301 q_Row = 0.0_dp
1302 q_Col = 0.0_dp
1303
1304 q_group_Row = 0.0_dp
1305 q_group_Col = 0.0_dp
1306
1307 u_l_Row = 0.0_dp
1308 u_l_Col = 0.0_dp
1309
1310 A_Row = 0.0_dp
1311 A_Col = 0.0_dp
1312
1313 f_Row = 0.0_dp
1314 f_Col = 0.0_dp
1315 f_Temp = 0.0_dp
1316
1317 t_Row = 0.0_dp
1318 t_Col = 0.0_dp
1319 t_Temp = 0.0_dp
1320
1321 pot_Row = 0.0_dp
1322 pot_Col = 0.0_dp
1323 pot_Temp = 0.0_dp
1324
1325 rf_Row = 0.0_dp
1326 rf_Col = 0.0_dp
1327 rf_Temp = 0.0_dp
1328
1329 #endif
1330
1331 if (FF_uses_EAM .and. SIM_uses_EAM) then
1332 call clean_EAM()
1333 endif
1334
1335 rf = 0.0_dp
1336 tau_Temp = 0.0_dp
1337 virial_Temp = 0.0_dp
1338 end subroutine zero_work_arrays
1339
1340 function skipThisPair(atom1, atom2) result(skip_it)
1341 integer, intent(in) :: atom1
1342 integer, intent(in), optional :: atom2
1343 logical :: skip_it
1344 integer :: unique_id_1, unique_id_2
1345 integer :: me_i,me_j
1346 integer :: i
1347
1348 skip_it = .false.
1349
1350 !! there are a number of reasons to skip a pair or a particle
1351 !! mostly we do this to exclude atoms who are involved in short
1352 !! range interactions (bonds, bends, torsions), but we also need
1353 !! to exclude some overcounted interactions that result from
1354 !! the parallel decomposition
1355
1356 #ifdef IS_MPI
1357 !! in MPI, we have to look up the unique IDs for each atom
1358 unique_id_1 = tagRow(atom1)
1359 #else
1360 !! in the normal loop, the atom numbers are unique
1361 unique_id_1 = atom1
1362 #endif
1363
1364 !! We were called with only one atom, so just check the global exclude
1365 !! list for this atom
1366 if (.not. present(atom2)) then
1367 do i = 1, nExcludes_global
1368 if (excludesGlobal(i) == unique_id_1) then
1369 skip_it = .true.
1370 return
1371 end if
1372 end do
1373 return
1374 end if
1375
1376 #ifdef IS_MPI
1377 unique_id_2 = tagColumn(atom2)
1378 #else
1379 unique_id_2 = atom2
1380 #endif
1381
1382 #ifdef IS_MPI
1383 !! this situation should only arise in MPI simulations
1384 if (unique_id_1 == unique_id_2) then
1385 skip_it = .true.
1386 return
1387 end if
1388
1389 !! this prevents us from doing the pair on multiple processors
1390 if (unique_id_1 < unique_id_2) then
1391 if (mod(unique_id_1 + unique_id_2,2) == 0) then
1392 skip_it = .true.
1393 return
1394 endif
1395 else
1396 if (mod(unique_id_1 + unique_id_2,2) == 1) then
1397 skip_it = .true.
1398 return
1399 endif
1400 endif
1401 #endif
1402
1403 !! the rest of these situations can happen in all simulations:
1404 do i = 1, nExcludes_global
1405 if ((excludesGlobal(i) == unique_id_1) .or. &
1406 (excludesGlobal(i) == unique_id_2)) then
1407 skip_it = .true.
1408 return
1409 endif
1410 enddo
1411
1412 do i = 1, nExcludes_local
1413 if (excludesLocal(1,i) == unique_id_1) then
1414 if (excludesLocal(2,i) == unique_id_2) then
1415 skip_it = .true.
1416 return
1417 endif
1418 else
1419 if (excludesLocal(1,i) == unique_id_2) then
1420 if (excludesLocal(2,i) == unique_id_1) then
1421 skip_it = .true.
1422 return
1423 endif
1424 endif
1425 endif
1426 end do
1427
1428 return
1429 end function skipThisPair
1430
1431 function FF_UsesDirectionalAtoms() result(doesit)
1432 logical :: doesit
1433 doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1434 FF_uses_GB .or. FF_uses_RF
1435 end function FF_UsesDirectionalAtoms
1436
1437 function FF_RequiresPrepairCalc() result(doesit)
1438 logical :: doesit
1439 doesit = FF_uses_EAM
1440 end function FF_RequiresPrepairCalc
1441
1442 function FF_RequiresPostpairCalc() result(doesit)
1443 logical :: doesit
1444 doesit = FF_uses_RF
1445 end function FF_RequiresPostpairCalc
1446
1447 #ifdef PROFILE
1448 function getforcetime() result(totalforcetime)
1449 real(kind=dp) :: totalforcetime
1450 totalforcetime = forcetime
1451 end function getforcetime
1452 #endif
1453
1454 !! This cleans componets of force arrays belonging only to fortran
1455
1456 end module do_Forces