ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
Revision: 2367
Committed: Fri Oct 14 15:44:37 2005 UTC (18 years, 8 months ago) by kdaily
File size: 47109 byte(s)
Log Message:
Add parts for the GayBerne LJ

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