ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-3.0/src/UseTheForce/doForces.F90
Revision: 2250
Committed: Sun May 29 21:15:52 2005 UTC (19 years, 1 month ago) by chrisfen
File size: 38434 byte(s)
Log Message:
Removed balance from doForces

File Contents

# Content
1 !!
2 !! Copyright (c) 2005 The University of Notre Dame. All Rights Reserved.
3 !!
4 !! The University of Notre Dame grants you ("Licensee") a
5 !! non-exclusive, royalty free, license to use, modify and
6 !! redistribute this software in source and binary code form, provided
7 !! that the following conditions are met:
8 !!
9 !! 1. Acknowledgement of the program authors must be made in any
10 !! publication of scientific results based in part on use of the
11 !! program. An acceptable form of acknowledgement is citation of
12 !! the article in which the program was described (Matthew
13 !! A. Meineke, Charles F. Vardeman II, Teng Lin, Christopher
14 !! J. Fennell and J. Daniel Gezelter, "OOPSE: An Object-Oriented
15 !! Parallel Simulation Engine for Molecular Dynamics,"
16 !! J. Comput. Chem. 26, pp. 252-271 (2005))
17 !!
18 !! 2. Redistributions of source code must retain the above copyright
19 !! notice, this list of conditions and the following disclaimer.
20 !!
21 !! 3. Redistributions in binary form must reproduce the above copyright
22 !! notice, this list of conditions and the following disclaimer in the
23 !! documentation and/or other materials provided with the
24 !! distribution.
25 !!
26 !! This software is provided "AS IS," without a warranty of any
27 !! kind. All express or implied conditions, representations and
28 !! warranties, including any implied warranty of merchantability,
29 !! fitness for a particular purpose or non-infringement, are hereby
30 !! excluded. The University of Notre Dame and its licensors shall not
31 !! be liable for any damages suffered by licensee as a result of
32 !! using, modifying or distributing the software or its
33 !! derivatives. In no event will the University of Notre Dame or its
34 !! licensors be liable for any lost revenue, profit or data, or for
35 !! direct, indirect, special, consequential, incidental or punitive
36 !! damages, however caused and regardless of the theory of liability,
37 !! arising out of the use of or inability to use software, even if the
38 !! University of Notre Dame has been advised of the possibility of
39 !! such damages.
40 !!
41
42 !! doForces.F90
43 !! module doForces
44 !! Calculates Long Range forces.
45
46 !! @author Charles F. Vardeman II
47 !! @author Matthew Meineke
48 !! @version $Id: doForces.F90,v 1.19 2005-05-29 21:15:52 chrisfen Exp $, $Date: 2005-05-29 21:15:52 $, $Name: not supported by cvs2svn $, $Revision: 1.19 $
49
50
51 module doForces
52 use force_globals
53 use simulation
54 use definitions
55 use atype_module
56 use switcheroo
57 use neighborLists
58 use lj
59 use sticky
60 use electrostatic_module
61 use reaction_field
62 use gb_pair
63 use shapes
64 use vector_class
65 use eam
66 use status
67 #ifdef IS_MPI
68 use mpiSimulation
69 #endif
70
71 implicit none
72 PRIVATE
73
74 #define __FORTRAN90
75 #include "UseTheForce/fSwitchingFunction.h"
76
77 INTEGER, PARAMETER:: PREPAIR_LOOP = 1
78 INTEGER, PARAMETER:: PAIR_LOOP = 2
79
80 logical, save :: haveRlist = .false.
81 logical, save :: haveNeighborList = .false.
82 logical, save :: haveSIMvariables = .false.
83 logical, save :: havePropertyMap = .false.
84 logical, save :: haveSaneForceField = .false.
85
86 logical, save :: FF_uses_DirectionalAtoms
87 logical, save :: FF_uses_LennardJones
88 logical, save :: FF_uses_Electrostatics
89 logical, save :: FF_uses_Charges
90 logical, save :: FF_uses_Dipoles
91 logical, save :: FF_uses_Quadrupoles
92 logical, save :: FF_uses_Sticky
93 logical, save :: FF_uses_StickyPower
94 logical, save :: FF_uses_GayBerne
95 logical, save :: FF_uses_EAM
96 logical, save :: FF_uses_Shapes
97 logical, save :: FF_uses_FLARB
98 logical, save :: FF_uses_RF
99
100 logical, save :: SIM_uses_DirectionalAtoms
101 logical, save :: SIM_uses_LennardJones
102 logical, save :: SIM_uses_Electrostatics
103 logical, save :: SIM_uses_Charges
104 logical, save :: SIM_uses_Dipoles
105 logical, save :: SIM_uses_Quadrupoles
106 logical, save :: SIM_uses_Sticky
107 logical, save :: SIM_uses_StickyPower
108 logical, save :: SIM_uses_GayBerne
109 logical, save :: SIM_uses_EAM
110 logical, save :: SIM_uses_Shapes
111 logical, save :: SIM_uses_FLARB
112 logical, save :: SIM_uses_RF
113 logical, save :: SIM_requires_postpair_calc
114 logical, save :: SIM_requires_prepair_calc
115 logical, save :: SIM_uses_PBC
116 logical, save :: SIM_uses_molecular_cutoffs
117
118 real(kind=dp), save :: rlist, rlistsq
119
120 public :: init_FF
121 public :: do_force_loop
122 public :: setRlistDF
123
124 #ifdef PROFILE
125 public :: getforcetime
126 real, save :: forceTime = 0
127 real :: forceTimeInitial, forceTimeFinal
128 integer :: nLoops
129 #endif
130
131 type :: Properties
132 logical :: is_Directional = .false.
133 logical :: is_LennardJones = .false.
134 logical :: is_Electrostatic = .false.
135 logical :: is_Charge = .false.
136 logical :: is_Dipole = .false.
137 logical :: is_Quadrupole = .false.
138 logical :: is_Sticky = .false.
139 logical :: is_StickyPower = .false.
140 logical :: is_GayBerne = .false.
141 logical :: is_EAM = .false.
142 logical :: is_Shape = .false.
143 logical :: is_FLARB = .false.
144 end type Properties
145
146 type(Properties), dimension(:),allocatable :: PropertyMap
147
148 contains
149
150 subroutine setRlistDF( this_rlist )
151
152 real(kind=dp) :: this_rlist
153
154 rlist = this_rlist
155 rlistsq = rlist * rlist
156
157 haveRlist = .true.
158
159 end subroutine setRlistDF
160
161 subroutine createPropertyMap(status)
162 integer :: nAtypes
163 integer :: status
164 integer :: i
165 logical :: thisProperty
166 real (kind=DP) :: thisDPproperty
167
168 status = 0
169
170 nAtypes = getSize(atypes)
171
172 if (nAtypes == 0) then
173 status = -1
174 return
175 end if
176
177 if (.not. allocated(PropertyMap)) then
178 allocate(PropertyMap(nAtypes))
179 endif
180
181 do i = 1, nAtypes
182 call getElementProperty(atypes, i, "is_Directional", thisProperty)
183 PropertyMap(i)%is_Directional = thisProperty
184
185 call getElementProperty(atypes, i, "is_LennardJones", thisProperty)
186 PropertyMap(i)%is_LennardJones = thisProperty
187
188 call getElementProperty(atypes, i, "is_Electrostatic", thisProperty)
189 PropertyMap(i)%is_Electrostatic = thisProperty
190
191 call getElementProperty(atypes, i, "is_Charge", thisProperty)
192 PropertyMap(i)%is_Charge = thisProperty
193
194 call getElementProperty(atypes, i, "is_Dipole", thisProperty)
195 PropertyMap(i)%is_Dipole = thisProperty
196
197 call getElementProperty(atypes, i, "is_Quadrupole", thisProperty)
198 PropertyMap(i)%is_Quadrupole = thisProperty
199
200 call getElementProperty(atypes, i, "is_Sticky", thisProperty)
201 PropertyMap(i)%is_Sticky = thisProperty
202
203 call getElementProperty(atypes, i, "is_StickyPower", thisProperty)
204 PropertyMap(i)%is_StickyPower = thisProperty
205
206 call getElementProperty(atypes, i, "is_GayBerne", thisProperty)
207 PropertyMap(i)%is_GayBerne = thisProperty
208
209 call getElementProperty(atypes, i, "is_EAM", thisProperty)
210 PropertyMap(i)%is_EAM = thisProperty
211
212 call getElementProperty(atypes, i, "is_Shape", thisProperty)
213 PropertyMap(i)%is_Shape = thisProperty
214
215 call getElementProperty(atypes, i, "is_FLARB", thisProperty)
216 PropertyMap(i)%is_FLARB = thisProperty
217 end do
218
219 havePropertyMap = .true.
220
221 end subroutine createPropertyMap
222
223 subroutine setSimVariables()
224 SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
225 SIM_uses_LennardJones = SimUsesLennardJones()
226 SIM_uses_Electrostatics = SimUsesElectrostatics()
227 SIM_uses_Charges = SimUsesCharges()
228 SIM_uses_Dipoles = SimUsesDipoles()
229 SIM_uses_Sticky = SimUsesSticky()
230 SIM_uses_StickyPower = SimUsesStickyPower()
231 SIM_uses_GayBerne = SimUsesGayBerne()
232 SIM_uses_EAM = SimUsesEAM()
233 SIM_uses_Shapes = SimUsesShapes()
234 SIM_uses_FLARB = SimUsesFLARB()
235 SIM_uses_RF = SimUsesRF()
236 SIM_requires_postpair_calc = SimRequiresPostpairCalc()
237 SIM_requires_prepair_calc = SimRequiresPrepairCalc()
238 SIM_uses_PBC = SimUsesPBC()
239
240 haveSIMvariables = .true.
241
242 return
243 end subroutine setSimVariables
244
245 subroutine doReadyCheck(error)
246 integer, intent(out) :: error
247
248 integer :: myStatus
249
250 error = 0
251
252 if (.not. havePropertyMap) then
253
254 myStatus = 0
255
256 call createPropertyMap(myStatus)
257
258 if (myStatus .ne. 0) then
259 write(default_error, *) 'createPropertyMap failed in doForces!'
260 error = -1
261 return
262 endif
263 endif
264
265 if (.not. haveSIMvariables) then
266 call setSimVariables()
267 endif
268
269 if (.not. haveRlist) then
270 write(default_error, *) 'rList has not been set in doForces!'
271 error = -1
272 return
273 endif
274
275 if (.not. haveNeighborList) then
276 write(default_error, *) 'neighbor list has not been initialized in doForces!'
277 error = -1
278 return
279 end if
280
281 if (.not. haveSaneForceField) then
282 write(default_error, *) 'Force Field is not sane in doForces!'
283 error = -1
284 return
285 end if
286
287 #ifdef IS_MPI
288 if (.not. isMPISimSet()) then
289 write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
290 error = -1
291 return
292 endif
293 #endif
294 return
295 end subroutine doReadyCheck
296
297
298 subroutine init_FF(use_RF_c, thisStat)
299
300 logical, intent(in) :: use_RF_c
301
302 integer, intent(out) :: thisStat
303 integer :: my_status, nMatches
304 integer, pointer :: MatchList(:) => null()
305 real(kind=dp) :: rcut, rrf, rt, dielect
306
307 !! assume things are copacetic, unless they aren't
308 thisStat = 0
309
310 !! Fortran's version of a cast:
311 FF_uses_RF = use_RF_c
312
313 !! init_FF is called *after* all of the atom types have been
314 !! defined in atype_module using the new_atype subroutine.
315 !!
316 !! this will scan through the known atypes and figure out what
317 !! interactions are used by the force field.
318
319 FF_uses_DirectionalAtoms = .false.
320 FF_uses_LennardJones = .false.
321 FF_uses_Electrostatics = .false.
322 FF_uses_Charges = .false.
323 FF_uses_Dipoles = .false.
324 FF_uses_Sticky = .false.
325 FF_uses_StickyPower = .false.
326 FF_uses_GayBerne = .false.
327 FF_uses_EAM = .false.
328 FF_uses_Shapes = .false.
329 FF_uses_FLARB = .false.
330
331 call getMatchingElementList(atypes, "is_Directional", .true., &
332 nMatches, MatchList)
333 if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
334
335 call getMatchingElementList(atypes, "is_LennardJones", .true., &
336 nMatches, MatchList)
337 if (nMatches .gt. 0) FF_uses_LennardJones = .true.
338
339 call getMatchingElementList(atypes, "is_Electrostatic", .true., &
340 nMatches, MatchList)
341 if (nMatches .gt. 0) then
342 FF_uses_Electrostatics = .true.
343 endif
344
345 call getMatchingElementList(atypes, "is_Charge", .true., &
346 nMatches, MatchList)
347 if (nMatches .gt. 0) then
348 FF_uses_Charges = .true.
349 FF_uses_Electrostatics = .true.
350 endif
351
352 call getMatchingElementList(atypes, "is_Dipole", .true., &
353 nMatches, MatchList)
354 if (nMatches .gt. 0) then
355 FF_uses_Dipoles = .true.
356 FF_uses_Electrostatics = .true.
357 FF_uses_DirectionalAtoms = .true.
358 endif
359
360 call getMatchingElementList(atypes, "is_Quadrupole", .true., &
361 nMatches, MatchList)
362 if (nMatches .gt. 0) then
363 FF_uses_Quadrupoles = .true.
364 FF_uses_Electrostatics = .true.
365 FF_uses_DirectionalAtoms = .true.
366 endif
367
368 call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
369 MatchList)
370 if (nMatches .gt. 0) then
371 FF_uses_Sticky = .true.
372 FF_uses_DirectionalAtoms = .true.
373 endif
374
375 call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
376 MatchList)
377 if (nMatches .gt. 0) then
378 FF_uses_StickyPower = .true.
379 FF_uses_DirectionalAtoms = .true.
380 endif
381
382 call getMatchingElementList(atypes, "is_GayBerne", .true., &
383 nMatches, MatchList)
384 if (nMatches .gt. 0) then
385 FF_uses_GayBerne = .true.
386 FF_uses_DirectionalAtoms = .true.
387 endif
388
389 call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
390 if (nMatches .gt. 0) FF_uses_EAM = .true.
391
392 call getMatchingElementList(atypes, "is_Shape", .true., &
393 nMatches, MatchList)
394 if (nMatches .gt. 0) then
395 FF_uses_Shapes = .true.
396 FF_uses_DirectionalAtoms = .true.
397 endif
398
399 call getMatchingElementList(atypes, "is_FLARB", .true., &
400 nMatches, MatchList)
401 if (nMatches .gt. 0) FF_uses_FLARB = .true.
402
403 !! Assume sanity (for the sake of argument)
404 haveSaneForceField = .true.
405
406 !! check to make sure the FF_uses_RF setting makes sense
407
408 if (FF_uses_dipoles) then
409 if (FF_uses_RF) then
410 dielect = getDielect()
411 call initialize_rf(dielect)
412 endif
413 else
414 if (FF_uses_RF) then
415 write(default_error,*) 'Using Reaction Field with no dipoles? Huh?'
416 thisStat = -1
417 haveSaneForceField = .false.
418 return
419 endif
420 endif
421
422 !sticky module does not contain check_sticky_FF anymore
423 !if (FF_uses_sticky) then
424 ! call check_sticky_FF(my_status)
425 ! if (my_status /= 0) then
426 ! thisStat = -1
427 ! haveSaneForceField = .false.
428 ! return
429 ! end if
430 !endif
431
432 if (FF_uses_EAM) then
433 call init_EAM_FF(my_status)
434 if (my_status /= 0) then
435 write(default_error, *) "init_EAM_FF returned a bad status"
436 thisStat = -1
437 haveSaneForceField = .false.
438 return
439 end if
440 endif
441
442 if (FF_uses_GayBerne) then
443 call check_gb_pair_FF(my_status)
444 if (my_status .ne. 0) then
445 thisStat = -1
446 haveSaneForceField = .false.
447 return
448 endif
449 endif
450
451 if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
452 endif
453
454 if (.not. haveNeighborList) then
455 !! Create neighbor lists
456 call expandNeighborList(nLocal, my_status)
457 if (my_Status /= 0) then
458 write(default_error,*) "SimSetup: ExpandNeighborList returned error."
459 thisStat = -1
460 return
461 endif
462 haveNeighborList = .true.
463 endif
464
465 end subroutine init_FF
466
467
468 !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
469 !------------------------------------------------------------->
470 subroutine do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, &
471 do_pot_c, do_stress_c, error)
472 !! Position array provided by C, dimensioned by getNlocal
473 real ( kind = dp ), dimension(3, nLocal) :: q
474 !! molecular center-of-mass position array
475 real ( kind = dp ), dimension(3, nGroups) :: q_group
476 !! Rotation Matrix for each long range particle in simulation.
477 real( kind = dp), dimension(9, nLocal) :: A
478 !! Unit vectors for dipoles (lab frame)
479 real( kind = dp ), dimension(9,nLocal) :: eFrame
480 !! Force array provided by C, dimensioned by getNlocal
481 real ( kind = dp ), dimension(3,nLocal) :: f
482 !! Torsion array provided by C, dimensioned by getNlocal
483 real( kind = dp ), dimension(3,nLocal) :: t
484
485 !! Stress Tensor
486 real( kind = dp), dimension(9) :: tau
487 real ( kind = dp ) :: pot
488 logical ( kind = 2) :: do_pot_c, do_stress_c
489 logical :: do_pot
490 logical :: do_stress
491 logical :: in_switching_region
492 #ifdef IS_MPI
493 real( kind = DP ) :: pot_local
494 integer :: nAtomsInRow
495 integer :: nAtomsInCol
496 integer :: nprocs
497 integer :: nGroupsInRow
498 integer :: nGroupsInCol
499 #endif
500 integer :: natoms
501 logical :: update_nlist
502 integer :: i, j, jstart, jend, jnab
503 integer :: istart, iend
504 integer :: ia, jb, atom1, atom2
505 integer :: nlist
506 real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vij
507 real( kind = DP ) :: sw, dswdr, swderiv, mf
508 real(kind=dp),dimension(3) :: d_atm, d_grp, fpair, fij
509 real(kind=dp) :: rfpot, mu_i, virial
510 integer :: me_i, me_j, n_in_i, n_in_j
511 logical :: is_dp_i
512 integer :: neighborListSize
513 integer :: listerror, error
514 integer :: localError
515 integer :: propPack_i, propPack_j
516 integer :: loopStart, loopEnd, loop
517
518 real(kind=dp) :: listSkin = 1.0
519
520 !! initialize local variables
521
522 #ifdef IS_MPI
523 pot_local = 0.0_dp
524 nAtomsInRow = getNatomsInRow(plan_atom_row)
525 nAtomsInCol = getNatomsInCol(plan_atom_col)
526 nGroupsInRow = getNgroupsInRow(plan_group_row)
527 nGroupsInCol = getNgroupsInCol(plan_group_col)
528 #else
529 natoms = nlocal
530 #endif
531
532 call doReadyCheck(localError)
533 if ( localError .ne. 0 ) then
534 call handleError("do_force_loop", "Not Initialized")
535 error = -1
536 return
537 end if
538 call zero_work_arrays()
539
540 do_pot = do_pot_c
541 do_stress = do_stress_c
542
543 ! Gather all information needed by all force loops:
544
545 #ifdef IS_MPI
546
547 call gather(q, q_Row, plan_atom_row_3d)
548 call gather(q, q_Col, plan_atom_col_3d)
549
550 call gather(q_group, q_group_Row, plan_group_row_3d)
551 call gather(q_group, q_group_Col, plan_group_col_3d)
552
553 if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
554 call gather(eFrame, eFrame_Row, plan_atom_row_rotation)
555 call gather(eFrame, eFrame_Col, plan_atom_col_rotation)
556
557 call gather(A, A_Row, plan_atom_row_rotation)
558 call gather(A, A_Col, plan_atom_col_rotation)
559 endif
560
561 #endif
562
563 !! Begin force loop timing:
564 #ifdef PROFILE
565 call cpu_time(forceTimeInitial)
566 nloops = nloops + 1
567 #endif
568
569 loopEnd = PAIR_LOOP
570 if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
571 loopStart = PREPAIR_LOOP
572 else
573 loopStart = PAIR_LOOP
574 endif
575
576 do loop = loopStart, loopEnd
577
578 ! See if we need to update neighbor lists
579 ! (but only on the first time through):
580 if (loop .eq. loopStart) then
581 #ifdef IS_MPI
582 call checkNeighborList(nGroupsInRow, q_group_row, listSkin, &
583 update_nlist)
584 #else
585 call checkNeighborList(nGroups, q_group, listSkin, &
586 update_nlist)
587 #endif
588 endif
589
590 if (update_nlist) then
591 !! save current configuration and construct neighbor list
592 #ifdef IS_MPI
593 call saveNeighborList(nGroupsInRow, q_group_row)
594 #else
595 call saveNeighborList(nGroups, q_group)
596 #endif
597 neighborListSize = size(list)
598 nlist = 0
599 endif
600
601 istart = 1
602 #ifdef IS_MPI
603 iend = nGroupsInRow
604 #else
605 iend = nGroups - 1
606 #endif
607 outer: do i = istart, iend
608
609 if (update_nlist) point(i) = nlist + 1
610
611 n_in_i = groupStartRow(i+1) - groupStartRow(i)
612
613 if (update_nlist) then
614 #ifdef IS_MPI
615 jstart = 1
616 jend = nGroupsInCol
617 #else
618 jstart = i+1
619 jend = nGroups
620 #endif
621 else
622 jstart = point(i)
623 jend = point(i+1) - 1
624 ! make sure group i has neighbors
625 if (jstart .gt. jend) cycle outer
626 endif
627
628 do jnab = jstart, jend
629 if (update_nlist) then
630 j = jnab
631 else
632 j = list(jnab)
633 endif
634
635 #ifdef IS_MPI
636 call get_interatomic_vector(q_group_Row(:,i), &
637 q_group_Col(:,j), d_grp, rgrpsq)
638 #else
639 call get_interatomic_vector(q_group(:,i), &
640 q_group(:,j), d_grp, rgrpsq)
641 #endif
642
643 if (rgrpsq < rlistsq) then
644 if (update_nlist) then
645 nlist = nlist + 1
646
647 if (nlist > neighborListSize) then
648 #ifdef IS_MPI
649 call expandNeighborList(nGroupsInRow, listerror)
650 #else
651 call expandNeighborList(nGroups, listerror)
652 #endif
653 if (listerror /= 0) then
654 error = -1
655 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
656 return
657 end if
658 neighborListSize = size(list)
659 endif
660
661 list(nlist) = j
662 endif
663
664 if (loop .eq. PAIR_LOOP) then
665 vij = 0.0d0
666 fij(1:3) = 0.0d0
667 endif
668
669 call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
670 in_switching_region)
671
672 n_in_j = groupStartCol(j+1) - groupStartCol(j)
673
674 do ia = groupStartRow(i), groupStartRow(i+1)-1
675
676 atom1 = groupListRow(ia)
677
678 inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
679
680 atom2 = groupListCol(jb)
681
682 if (skipThisPair(atom1, atom2)) cycle inner
683
684 if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
685 d_atm(1:3) = d_grp(1:3)
686 ratmsq = rgrpsq
687 else
688 #ifdef IS_MPI
689 call get_interatomic_vector(q_Row(:,atom1), &
690 q_Col(:,atom2), d_atm, ratmsq)
691 #else
692 call get_interatomic_vector(q(:,atom1), &
693 q(:,atom2), d_atm, ratmsq)
694 #endif
695 endif
696
697 if (loop .eq. PREPAIR_LOOP) then
698 #ifdef IS_MPI
699 call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
700 rgrpsq, d_grp, do_pot, do_stress, &
701 eFrame, A, f, t, pot_local)
702 #else
703 call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
704 rgrpsq, d_grp, do_pot, do_stress, &
705 eFrame, A, f, t, pot)
706 #endif
707 else
708 #ifdef IS_MPI
709 call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
710 do_pot, &
711 eFrame, A, f, t, pot_local, vpair, fpair)
712 #else
713 call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
714 do_pot, &
715 eFrame, A, f, t, pot, vpair, fpair)
716 #endif
717
718 vij = vij + vpair
719 fij(1:3) = fij(1:3) + fpair(1:3)
720 endif
721 enddo inner
722 enddo
723
724 if (loop .eq. PAIR_LOOP) then
725 if (in_switching_region) then
726 swderiv = vij*dswdr/rgrp
727 fij(1) = fij(1) + swderiv*d_grp(1)
728 fij(2) = fij(2) + swderiv*d_grp(2)
729 fij(3) = fij(3) + swderiv*d_grp(3)
730
731 do ia=groupStartRow(i), groupStartRow(i+1)-1
732 atom1=groupListRow(ia)
733 mf = mfactRow(atom1)
734 #ifdef IS_MPI
735 f_Row(1,atom1) = f_Row(1,atom1) + swderiv*d_grp(1)*mf
736 f_Row(2,atom1) = f_Row(2,atom1) + swderiv*d_grp(2)*mf
737 f_Row(3,atom1) = f_Row(3,atom1) + swderiv*d_grp(3)*mf
738 #else
739 f(1,atom1) = f(1,atom1) + swderiv*d_grp(1)*mf
740 f(2,atom1) = f(2,atom1) + swderiv*d_grp(2)*mf
741 f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
742 #endif
743 enddo
744
745 do jb=groupStartCol(j), groupStartCol(j+1)-1
746 atom2=groupListCol(jb)
747 mf = mfactCol(atom2)
748 #ifdef IS_MPI
749 f_Col(1,atom2) = f_Col(1,atom2) - swderiv*d_grp(1)*mf
750 f_Col(2,atom2) = f_Col(2,atom2) - swderiv*d_grp(2)*mf
751 f_Col(3,atom2) = f_Col(3,atom2) - swderiv*d_grp(3)*mf
752 #else
753 f(1,atom2) = f(1,atom2) - swderiv*d_grp(1)*mf
754 f(2,atom2) = f(2,atom2) - swderiv*d_grp(2)*mf
755 f(3,atom2) = f(3,atom2) - swderiv*d_grp(3)*mf
756 #endif
757 enddo
758 endif
759
760 if (do_stress) call add_stress_tensor(d_grp, fij)
761 endif
762 end if
763 enddo
764 enddo outer
765
766 if (update_nlist) then
767 #ifdef IS_MPI
768 point(nGroupsInRow + 1) = nlist + 1
769 #else
770 point(nGroups) = nlist + 1
771 #endif
772 if (loop .eq. PREPAIR_LOOP) then
773 ! we just did the neighbor list update on the first
774 ! pass, so we don't need to do it
775 ! again on the second pass
776 update_nlist = .false.
777 endif
778 endif
779
780 if (loop .eq. PREPAIR_LOOP) then
781 call do_preforce(nlocal, pot)
782 endif
783
784 enddo
785
786 !! Do timing
787 #ifdef PROFILE
788 call cpu_time(forceTimeFinal)
789 forceTime = forceTime + forceTimeFinal - forceTimeInitial
790 #endif
791
792 #ifdef IS_MPI
793 !!distribute forces
794
795 f_temp = 0.0_dp
796 call scatter(f_Row,f_temp,plan_atom_row_3d)
797 do i = 1,nlocal
798 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
799 end do
800
801 f_temp = 0.0_dp
802 call scatter(f_Col,f_temp,plan_atom_col_3d)
803 do i = 1,nlocal
804 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
805 end do
806
807 if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
808 t_temp = 0.0_dp
809 call scatter(t_Row,t_temp,plan_atom_row_3d)
810 do i = 1,nlocal
811 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
812 end do
813 t_temp = 0.0_dp
814 call scatter(t_Col,t_temp,plan_atom_col_3d)
815
816 do i = 1,nlocal
817 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
818 end do
819 endif
820
821 if (do_pot) then
822 ! scatter/gather pot_row into the members of my column
823 call scatter(pot_Row, pot_Temp, plan_atom_row)
824
825 ! scatter/gather pot_local into all other procs
826 ! add resultant to get total pot
827 do i = 1, nlocal
828 pot_local = pot_local + pot_Temp(i)
829 enddo
830
831 pot_Temp = 0.0_DP
832
833 call scatter(pot_Col, pot_Temp, plan_atom_col)
834 do i = 1, nlocal
835 pot_local = pot_local + pot_Temp(i)
836 enddo
837
838 endif
839 #endif
840
841 if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
842
843 if (FF_uses_RF .and. SIM_uses_RF) then
844
845 #ifdef IS_MPI
846 call scatter(rf_Row,rf,plan_atom_row_3d)
847 call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
848 do i = 1,nlocal
849 rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
850 end do
851 #endif
852
853 do i = 1, nLocal
854
855 rfpot = 0.0_DP
856 #ifdef IS_MPI
857 me_i = atid_row(i)
858 #else
859 me_i = atid(i)
860 #endif
861
862 if (PropertyMap(me_i)%is_Dipole) then
863
864 mu_i = getDipoleMoment(me_i)
865
866 !! The reaction field needs to include a self contribution
867 !! to the field:
868 call accumulate_self_rf(i, mu_i, eFrame)
869 !! Get the reaction field contribution to the
870 !! potential and torques:
871 call reaction_field_final(i, mu_i, eFrame, rfpot, t, do_pot)
872 #ifdef IS_MPI
873 pot_local = pot_local + rfpot
874 #else
875 pot = pot + rfpot
876
877 #endif
878 endif
879 enddo
880 endif
881 endif
882
883
884 #ifdef IS_MPI
885
886 if (do_pot) then
887 pot = pot + pot_local
888 !! we assume the c code will do the allreduce to get the total potential
889 !! we could do it right here if we needed to...
890 endif
891
892 if (do_stress) then
893 call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
894 mpi_comm_world,mpi_err)
895 call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
896 mpi_comm_world,mpi_err)
897 endif
898
899 #else
900
901 if (do_stress) then
902 tau = tau_Temp
903 virial = virial_Temp
904 endif
905
906 #endif
907
908 end subroutine do_force_loop
909
910 subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
911 eFrame, A, f, t, pot, vpair, fpair)
912
913 real( kind = dp ) :: pot, vpair, sw
914 real( kind = dp ), dimension(3) :: fpair
915 real( kind = dp ), dimension(nLocal) :: mfact
916 real( kind = dp ), dimension(9,nLocal) :: eFrame
917 real( kind = dp ), dimension(9,nLocal) :: A
918 real( kind = dp ), dimension(3,nLocal) :: f
919 real( kind = dp ), dimension(3,nLocal) :: t
920
921 logical, intent(inout) :: do_pot
922 integer, intent(in) :: i, j
923 real ( kind = dp ), intent(inout) :: rijsq
924 real ( kind = dp ) :: r
925 real ( kind = dp ), intent(inout) :: d(3)
926 real ( kind = dp ) :: ebalance
927 integer :: me_i, me_j
928
929 r = sqrt(rijsq)
930 vpair = 0.0d0
931 fpair(1:3) = 0.0d0
932
933 #ifdef IS_MPI
934 me_i = atid_row(i)
935 me_j = atid_col(j)
936 #else
937 me_i = atid(i)
938 me_j = atid(j)
939 #endif
940
941 ! write(*,*) i, j, me_i, me_j
942
943 if (FF_uses_LennardJones .and. SIM_uses_LennardJones) then
944
945 if ( PropertyMap(me_i)%is_LennardJones .and. &
946 PropertyMap(me_j)%is_LennardJones ) then
947 call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
948 endif
949
950 endif
951
952 if (FF_uses_Electrostatics .and. SIM_uses_Electrostatics) then
953
954 if (PropertyMap(me_i)%is_Electrostatic .and. &
955 PropertyMap(me_j)%is_Electrostatic) then
956 call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
957 pot, eFrame, f, t, do_pot)
958 endif
959
960 if (FF_uses_dipoles .and. SIM_uses_dipoles) then
961 if ( PropertyMap(me_i)%is_Dipole .and. &
962 PropertyMap(me_j)%is_Dipole) then
963 if (FF_uses_RF .and. SIM_uses_RF) then
964 call accumulate_rf(i, j, r, eFrame, sw)
965 call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
966 endif
967 endif
968 endif
969 endif
970
971
972 if (FF_uses_Sticky .and. SIM_uses_sticky) then
973
974 if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
975 call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
976 pot, A, f, t, do_pot)
977 endif
978
979 endif
980
981 if (FF_uses_StickyPower .and. SIM_uses_stickypower) then
982 if ( PropertyMap(me_i)%is_StickyPower .and. &
983 PropertyMap(me_j)%is_StickyPower) then
984 call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
985 pot, A, f, t, do_pot)
986 endif
987 endif
988
989 if (FF_uses_GayBerne .and. SIM_uses_GayBerne) then
990
991 if ( PropertyMap(me_i)%is_GayBerne .and. &
992 PropertyMap(me_j)%is_GayBerne) then
993 call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
994 pot, A, f, t, do_pot)
995 endif
996
997 endif
998
999 if (FF_uses_EAM .and. SIM_uses_EAM) then
1000
1001 if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
1002 call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1003 do_pot)
1004 endif
1005
1006 endif
1007
1008
1009 ! write(*,*) PropertyMap(me_i)%is_Shape,PropertyMap(me_j)%is_Shape
1010
1011 if (FF_uses_Shapes .and. SIM_uses_Shapes) then
1012 if ( PropertyMap(me_i)%is_Shape .and. &
1013 PropertyMap(me_j)%is_Shape ) then
1014 call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1015 pot, A, f, t, do_pot)
1016 endif
1017 if ( (PropertyMap(me_i)%is_Shape .and. &
1018 PropertyMap(me_j)%is_LennardJones) .or. &
1019 (PropertyMap(me_i)%is_LennardJones .and. &
1020 PropertyMap(me_j)%is_Shape) ) then
1021 call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1022 pot, A, f, t, do_pot)
1023 endif
1024 endif
1025
1026 end subroutine do_pair
1027
1028 subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
1029 do_pot, do_stress, eFrame, A, f, t, pot)
1030
1031 real( kind = dp ) :: pot, sw
1032 real( kind = dp ), dimension(9,nLocal) :: eFrame
1033 real (kind=dp), dimension(9,nLocal) :: A
1034 real (kind=dp), dimension(3,nLocal) :: f
1035 real (kind=dp), dimension(3,nLocal) :: t
1036
1037 logical, intent(inout) :: do_pot, do_stress
1038 integer, intent(in) :: i, j
1039 real ( kind = dp ), intent(inout) :: rijsq, rcijsq
1040 real ( kind = dp ) :: r, rc
1041 real ( kind = dp ), intent(inout) :: d(3), dc(3)
1042
1043 logical :: is_EAM_i, is_EAM_j
1044
1045 integer :: me_i, me_j
1046
1047
1048 r = sqrt(rijsq)
1049 if (SIM_uses_molecular_cutoffs) then
1050 rc = sqrt(rcijsq)
1051 else
1052 rc = r
1053 endif
1054
1055
1056 #ifdef IS_MPI
1057 me_i = atid_row(i)
1058 me_j = atid_col(j)
1059 #else
1060 me_i = atid(i)
1061 me_j = atid(j)
1062 #endif
1063
1064 if (FF_uses_EAM .and. SIM_uses_EAM) then
1065
1066 if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1067 call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1068
1069 endif
1070
1071 end subroutine do_prepair
1072
1073
1074 subroutine do_preforce(nlocal,pot)
1075 integer :: nlocal
1076 real( kind = dp ) :: pot
1077
1078 if (FF_uses_EAM .and. SIM_uses_EAM) then
1079 call calc_EAM_preforce_Frho(nlocal,pot)
1080 endif
1081
1082
1083 end subroutine do_preforce
1084
1085
1086 subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1087
1088 real (kind = dp), dimension(3) :: q_i
1089 real (kind = dp), dimension(3) :: q_j
1090 real ( kind = dp ), intent(out) :: r_sq
1091 real( kind = dp ) :: d(3), scaled(3)
1092 integer i
1093
1094 d(1:3) = q_j(1:3) - q_i(1:3)
1095
1096 ! Wrap back into periodic box if necessary
1097 if ( SIM_uses_PBC ) then
1098
1099 if( .not.boxIsOrthorhombic ) then
1100 ! calc the scaled coordinates.
1101
1102 scaled = matmul(HmatInv, d)
1103
1104 ! wrap the scaled coordinates
1105
1106 scaled = scaled - anint(scaled)
1107
1108
1109 ! calc the wrapped real coordinates from the wrapped scaled
1110 ! coordinates
1111
1112 d = matmul(Hmat,scaled)
1113
1114 else
1115 ! calc the scaled coordinates.
1116
1117 do i = 1, 3
1118 scaled(i) = d(i) * HmatInv(i,i)
1119
1120 ! wrap the scaled coordinates
1121
1122 scaled(i) = scaled(i) - anint(scaled(i))
1123
1124 ! calc the wrapped real coordinates from the wrapped scaled
1125 ! coordinates
1126
1127 d(i) = scaled(i)*Hmat(i,i)
1128 enddo
1129 endif
1130
1131 endif
1132
1133 r_sq = dot_product(d,d)
1134
1135 end subroutine get_interatomic_vector
1136
1137 subroutine zero_work_arrays()
1138
1139 #ifdef IS_MPI
1140
1141 q_Row = 0.0_dp
1142 q_Col = 0.0_dp
1143
1144 q_group_Row = 0.0_dp
1145 q_group_Col = 0.0_dp
1146
1147 eFrame_Row = 0.0_dp
1148 eFrame_Col = 0.0_dp
1149
1150 A_Row = 0.0_dp
1151 A_Col = 0.0_dp
1152
1153 f_Row = 0.0_dp
1154 f_Col = 0.0_dp
1155 f_Temp = 0.0_dp
1156
1157 t_Row = 0.0_dp
1158 t_Col = 0.0_dp
1159 t_Temp = 0.0_dp
1160
1161 pot_Row = 0.0_dp
1162 pot_Col = 0.0_dp
1163 pot_Temp = 0.0_dp
1164
1165 rf_Row = 0.0_dp
1166 rf_Col = 0.0_dp
1167 rf_Temp = 0.0_dp
1168
1169 #endif
1170
1171 if (FF_uses_EAM .and. SIM_uses_EAM) then
1172 call clean_EAM()
1173 endif
1174
1175 rf = 0.0_dp
1176 tau_Temp = 0.0_dp
1177 virial_Temp = 0.0_dp
1178 end subroutine zero_work_arrays
1179
1180 function skipThisPair(atom1, atom2) result(skip_it)
1181 integer, intent(in) :: atom1
1182 integer, intent(in), optional :: atom2
1183 logical :: skip_it
1184 integer :: unique_id_1, unique_id_2
1185 integer :: me_i,me_j
1186 integer :: i
1187
1188 skip_it = .false.
1189
1190 !! there are a number of reasons to skip a pair or a particle
1191 !! mostly we do this to exclude atoms who are involved in short
1192 !! range interactions (bonds, bends, torsions), but we also need
1193 !! to exclude some overcounted interactions that result from
1194 !! the parallel decomposition
1195
1196 #ifdef IS_MPI
1197 !! in MPI, we have to look up the unique IDs for each atom
1198 unique_id_1 = AtomRowToGlobal(atom1)
1199 #else
1200 !! in the normal loop, the atom numbers are unique
1201 unique_id_1 = atom1
1202 #endif
1203
1204 !! We were called with only one atom, so just check the global exclude
1205 !! list for this atom
1206 if (.not. present(atom2)) then
1207 do i = 1, nExcludes_global
1208 if (excludesGlobal(i) == unique_id_1) then
1209 skip_it = .true.
1210 return
1211 end if
1212 end do
1213 return
1214 end if
1215
1216 #ifdef IS_MPI
1217 unique_id_2 = AtomColToGlobal(atom2)
1218 #else
1219 unique_id_2 = atom2
1220 #endif
1221
1222 #ifdef IS_MPI
1223 !! this situation should only arise in MPI simulations
1224 if (unique_id_1 == unique_id_2) then
1225 skip_it = .true.
1226 return
1227 end if
1228
1229 !! this prevents us from doing the pair on multiple processors
1230 if (unique_id_1 < unique_id_2) then
1231 if (mod(unique_id_1 + unique_id_2,2) == 0) then
1232 skip_it = .true.
1233 return
1234 endif
1235 else
1236 if (mod(unique_id_1 + unique_id_2,2) == 1) then
1237 skip_it = .true.
1238 return
1239 endif
1240 endif
1241 #endif
1242
1243 !! the rest of these situations can happen in all simulations:
1244 do i = 1, nExcludes_global
1245 if ((excludesGlobal(i) == unique_id_1) .or. &
1246 (excludesGlobal(i) == unique_id_2)) then
1247 skip_it = .true.
1248 return
1249 endif
1250 enddo
1251
1252 do i = 1, nSkipsForAtom(atom1)
1253 if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1254 skip_it = .true.
1255 return
1256 endif
1257 end do
1258
1259 return
1260 end function skipThisPair
1261
1262 function FF_UsesDirectionalAtoms() result(doesit)
1263 logical :: doesit
1264 doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1265 FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1266 FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1267 end function FF_UsesDirectionalAtoms
1268
1269 function FF_RequiresPrepairCalc() result(doesit)
1270 logical :: doesit
1271 doesit = FF_uses_EAM
1272 end function FF_RequiresPrepairCalc
1273
1274 function FF_RequiresPostpairCalc() result(doesit)
1275 logical :: doesit
1276 doesit = FF_uses_RF
1277 end function FF_RequiresPostpairCalc
1278
1279 #ifdef PROFILE
1280 function getforcetime() result(totalforcetime)
1281 real(kind=dp) :: totalforcetime
1282 totalforcetime = forcetime
1283 end function getforcetime
1284 #endif
1285
1286 !! This cleans componets of force arrays belonging only to fortran
1287
1288 subroutine add_stress_tensor(dpair, fpair)
1289
1290 real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1291
1292 ! because the d vector is the rj - ri vector, and
1293 ! because fx, fy, fz are the force on atom i, we need a
1294 ! negative sign here:
1295
1296 tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1297 tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1298 tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1299 tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1300 tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1301 tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1302 tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1303 tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1304 tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1305
1306 virial_Temp = virial_Temp + &
1307 (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1308
1309 end subroutine add_stress_tensor
1310
1311 end module doForces