ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
Revision: 1688
Committed: Fri Oct 29 22:28:12 2004 UTC (19 years, 8 months ago) by chrisfen
File size: 36653 byte(s)
Log Message:
shapes rcut calculator added

File Contents

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