ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-2.0/src/UseTheForce/doForces.F90
Revision: 2350
Committed: Mon Oct 10 21:20:46 2005 UTC (18 years, 9 months ago) by chuckv
File size: 46244 byte(s)
Log Message:
Fixed MPI bug with Row and Column indexing of groupToGtype. We now have two seperate maps groupToGtypeRow and groupToGypeCol. GroupToGtypeCol is a pointer that is set to groupToGtypeRow in the single processor version.

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