ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
Revision: 2279
Committed: Tue Aug 30 18:23:50 2005 UTC (18 years, 10 months ago) by chrisfen
File size: 39695 byte(s)
Log Message:
made some changes for implementing the wolf potential

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