ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/do_Forces.F90
(Generate patch)

Comparing trunk/OOPSE/libmdtools/do_Forces.F90 (file contents):
Revision 650 by chuckv, Thu Jul 24 19:57:35 2003 UTC vs.
Revision 1163 by gezelter, Wed May 12 14:30:12 2004 UTC

# Line 4 | Line 4
4  
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.25 2003-07-24 19:57:35 chuckv Exp $, $Date: 2003-07-24 19:57:35 $, $Name: not supported by cvs2svn $, $Revision: 1.25 $
7 > !! @version $Id: do_Forces.F90,v 1.56 2004-05-12 14:29:24 gezelter Exp $, $Date: 2004-05-12 14:29:24 $, $Name: not supported by cvs2svn $, $Revision: 1.56 $
8  
9   module do_Forces
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    use vector_class
23    use eam
24 +  use status
25   #ifdef IS_MPI
26    use mpiSimulation
27   #endif
# Line 28 | Line 31 | module do_Forces
31  
32   #define __FORTRAN90
33   #include "fForceField.h"
34 + #include "fSwitchingFunction.h"
35  
36 <  logical, save :: do_forces_initialized = .false., haveRlist = .false.
36 >  logical, save :: haveRlist = .false.
37 >  logical, save :: haveNeighborList = .false.
38    logical, save :: havePolicies = .false.
39 +  logical, save :: haveSIMvariables = .false.
40 +  logical, save :: havePropertyMap = .false.
41 +  logical, save :: haveSaneForceField = .false.
42    logical, save :: FF_uses_LJ
43    logical, save :: FF_uses_sticky
44 +  logical, save :: FF_uses_charges
45    logical, save :: FF_uses_dipoles
46    logical, save :: FF_uses_RF
47    logical, save :: FF_uses_GB
48    logical, save :: FF_uses_EAM
49 +  logical, save :: SIM_uses_LJ
50 +  logical, save :: SIM_uses_sticky
51 +  logical, save :: SIM_uses_charges
52 +  logical, save :: SIM_uses_dipoles
53 +  logical, save :: SIM_uses_RF
54 +  logical, save :: SIM_uses_GB
55 +  logical, save :: SIM_uses_EAM
56 +  logical, save :: SIM_requires_postpair_calc
57 +  logical, save :: SIM_requires_prepair_calc
58 +  logical, save :: SIM_uses_directional_atoms
59 +  logical, save :: SIM_uses_PBC
60 +  logical, save :: SIM_uses_molecular_cutoffs
61  
62    real(kind=dp), save :: rlist, rlistsq
63  
# Line 44 | Line 65 | contains
65    public :: do_force_loop
66    public :: setRlistDF
67  
68 + #ifdef PROFILE
69 +  public :: getforcetime
70 +  real, save :: forceTime = 0
71 +  real :: forceTimeInitial, forceTimeFinal
72 +  integer :: nLoops
73 + #endif
74 +
75 +  type :: Properties
76 +     logical :: is_lj     = .false.
77 +     logical :: is_sticky = .false.
78 +     logical :: is_dp     = .false.
79 +     logical :: is_gb     = .false.
80 +     logical :: is_eam    = .false.
81 +     logical :: is_charge = .false.
82 +     real(kind=DP) :: charge = 0.0_DP
83 +     real(kind=DP) :: dipole_moment = 0.0_DP
84 +  end type Properties
85 +
86 +  type(Properties), dimension(:),allocatable :: PropertyMap
87 +
88   contains
89  
90    subroutine setRlistDF( this_rlist )
# Line 54 | Line 95 | contains
95      rlistsq = rlist * rlist
96      
97      haveRlist = .true.
57    if( havePolicies ) do_forces_initialized = .true.
98  
99    end subroutine setRlistDF    
100  
101 +  subroutine createPropertyMap(status)
102 +    integer :: nAtypes
103 +    integer :: status
104 +    integer :: i
105 +    logical :: thisProperty
106 +    real (kind=DP) :: thisDPproperty
107 +
108 +    status = 0
109 +
110 +    nAtypes = getSize(atypes)
111 +
112 +    if (nAtypes == 0) then
113 +       status = -1
114 +       return
115 +    end if
116 +        
117 +    if (.not. allocated(PropertyMap)) then
118 +       allocate(PropertyMap(nAtypes))
119 +    endif
120 +
121 +    do i = 1, nAtypes
122 +       call getElementProperty(atypes, i, "is_LJ", thisProperty)
123 +       PropertyMap(i)%is_LJ = thisProperty
124 +
125 +       call getElementProperty(atypes, i, "is_Charge", thisProperty)
126 +       PropertyMap(i)%is_Charge = thisProperty
127 +      
128 +       if (thisProperty) then
129 +          call getElementProperty(atypes, i, "charge", thisDPproperty)
130 +          PropertyMap(i)%charge = thisDPproperty
131 +       endif
132 +
133 +       call getElementProperty(atypes, i, "is_DP", thisProperty)
134 +       PropertyMap(i)%is_DP = thisProperty
135 +
136 +       if (thisProperty) then
137 +          call getElementProperty(atypes, i, "dipole_moment", thisDPproperty)
138 +          PropertyMap(i)%dipole_moment = thisDPproperty
139 +       endif
140 +
141 +       call getElementProperty(atypes, i, "is_Sticky", thisProperty)
142 +       PropertyMap(i)%is_Sticky = thisProperty
143 +       call getElementProperty(atypes, i, "is_GB", thisProperty)
144 +       PropertyMap(i)%is_GB = thisProperty
145 +       call getElementProperty(atypes, i, "is_EAM", thisProperty)
146 +       PropertyMap(i)%is_EAM = thisProperty
147 +    end do
148 +
149 +    havePropertyMap = .true.
150 +
151 +  end subroutine createPropertyMap
152 +
153 +  subroutine setSimVariables()
154 +    SIM_uses_LJ = SimUsesLJ()
155 +    SIM_uses_sticky = SimUsesSticky()
156 +    SIM_uses_charges = SimUsesCharges()
157 +    SIM_uses_dipoles = SimUsesDipoles()
158 +    SIM_uses_RF = SimUsesRF()
159 +    SIM_uses_GB = SimUsesGB()
160 +    SIM_uses_EAM = SimUsesEAM()
161 +    SIM_requires_postpair_calc = SimRequiresPostpairCalc()
162 +    SIM_requires_prepair_calc = SimRequiresPrepairCalc()
163 +    SIM_uses_directional_atoms = SimUsesDirectionalAtoms()
164 +    SIM_uses_PBC = SimUsesPBC()
165 +    !SIM_uses_molecular_cutoffs = SimUsesMolecularCutoffs()
166 +
167 +    haveSIMvariables = .true.
168 +
169 +    return
170 +  end subroutine setSimVariables
171 +
172 +  subroutine doReadyCheck(error)
173 +    integer, intent(out) :: error
174 +
175 +    integer :: myStatus
176 +
177 +    error = 0
178 +    
179 +    if (.not. havePropertyMap) then
180 +
181 +       myStatus = 0
182 +
183 +       call createPropertyMap(myStatus)
184 +
185 +       if (myStatus .ne. 0) then
186 +          write(default_error, *) 'createPropertyMap failed in do_Forces!'
187 +          error = -1
188 +          return
189 +       endif
190 +    endif
191 +
192 +    if (.not. haveSIMvariables) then
193 +       call setSimVariables()
194 +    endif
195 +
196 +    if (.not. haveRlist) then
197 +       write(default_error, *) 'rList has not been set in do_Forces!'
198 +       error = -1
199 +       return
200 +    endif
201 +
202 +    if (SIM_uses_LJ .and. FF_uses_LJ) then
203 +       if (.not. havePolicies) then
204 +          write(default_error, *) 'LJ mixing Policies have not been set in do_Forces!'
205 +          error = -1
206 +          return
207 +       endif
208 +    endif
209 +
210 +    if (.not. haveNeighborList) then
211 +       write(default_error, *) 'neighbor list has not been initialized in do_Forces!'
212 +       error = -1
213 +       return
214 +    end if
215 +
216 +    if (.not. haveSaneForceField) then
217 +       write(default_error, *) 'Force Field is not sane in do_Forces!'
218 +       error = -1
219 +       return
220 +    end if
221 +
222 + #ifdef IS_MPI
223 +    if (.not. isMPISimSet()) then
224 +       write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
225 +       error = -1
226 +       return
227 +    endif
228 + #endif
229 +    return
230 +  end subroutine doReadyCheck
231 +    
232 +
233    subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
234  
235      integer, intent(in) :: LJMIXPOLICY
# Line 82 | Line 254 | contains
254    
255      FF_uses_LJ = .false.
256      FF_uses_sticky = .false.
257 +    FF_uses_charges = .false.
258      FF_uses_dipoles = .false.
259      FF_uses_GB = .false.
260      FF_uses_EAM = .false.
261      
262      call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
263      if (nMatches .gt. 0) FF_uses_LJ = .true.
264 <    
264 >
265 >    call getMatchingElementList(atypes, "is_Charge", .true., nMatches, MatchList)
266 >    if (nMatches .gt. 0) FF_uses_charges = .true.  
267 >
268      call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
269      if (nMatches .gt. 0) FF_uses_dipoles = .true.
270      
# Line 102 | Line 278 | contains
278      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
279      if (nMatches .gt. 0) FF_uses_EAM = .true.
280      
281 +    !! Assume sanity (for the sake of argument)
282 +    haveSaneForceField = .true.
283 +
284      !! check to make sure the FF_uses_RF setting makes sense
285      
286      if (FF_uses_dipoles) then
# Line 113 | Line 292 | contains
292         if (FF_uses_RF) then          
293            write(default_error,*) 'Using Reaction Field with no dipoles?  Huh?'
294            thisStat = -1
295 +          haveSaneForceField = .false.
296            return
297         endif
298      endif
# Line 127 | Line 307 | contains
307         case default
308            write(default_error,*) 'unknown LJ Mixing Policy!'
309            thisStat = -1
310 +          haveSaneForceField = .false.
311            return            
312         end select
313         if (my_status /= 0) then
314            thisStat = -1
315 +          haveSaneForceField = .false.
316            return
317         end if
318 +       havePolicies = .true.
319      endif
320  
321      if (FF_uses_sticky) then
322         call check_sticky_FF(my_status)
323         if (my_status /= 0) then
324            thisStat = -1
325 +          haveSaneForceField = .false.
326            return
327         end if
328      endif
329 <    
329 >
330 >
331 >    if (FF_uses_EAM) then
332 >         call init_EAM_FF(my_status)
333 >       if (my_status /= 0) then
334 >          write(default_error, *) "init_EAM_FF returned a bad status"
335 >          thisStat = -1
336 >          haveSaneForceField = .false.
337 >          return
338 >       end if
339 >    endif
340 >
341      if (FF_uses_GB) then
342         call check_gb_pair_FF(my_status)
343         if (my_status .ne. 0) then
344            thisStat = -1
345 +          haveSaneForceField = .false.
346            return
347         endif
348      endif
349  
350      if (FF_uses_GB .and. FF_uses_LJ) then
351      endif
352 <    if (.not. do_forces_initialized) then
352 >    if (.not. haveNeighborList) then
353         !! Create neighbor lists
354 <       call expandNeighborList(getNlocal(), my_status)
354 >       call expandNeighborList(nLocal, my_status)
355         if (my_Status /= 0) then
356            write(default_error,*) "SimSetup: ExpandNeighborList returned error."
357            thisStat = -1
358            return
359         endif
360 +       haveNeighborList = .true.
361      endif
362  
363 <    havePolicies = .true.
364 <    if( haveRlist ) do_forces_initialized = .true.
168 <    
363 >    
364 >    
365    end subroutine init_FF
366    
367  
368    !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
369    !------------------------------------------------------------->
370 <  subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
371 <       error)
372 <    !! Position array provided by C, dimensioned by getNlocal
373 <    real ( kind = dp ), dimension(3,getNlocal()) :: q
370 >  subroutine do_force_loop(q, q_group, A, u_l, f, t, tau, pot, &
371 >       do_pot_c, do_stress_c, error)
372 >    !! Position array provided by C, dimensioned by getNlocal
373 >    real ( kind = dp ), dimension(3,nLocal) :: q
374 >    !! molecular center-of-mass position array
375 >    real ( kind = dp ), dimension(3,nGroup) :: q_group
376      !! Rotation Matrix for each long range particle in simulation.
377 <    real( kind = dp), dimension(9,getNlocal()) :: A    
377 >    real( kind = dp), dimension(9,nLocal) :: A    
378      !! Unit vectors for dipoles (lab frame)
379 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
379 >    real( kind = dp ), dimension(3,nLocal) :: u_l
380      !! Force array provided by C, dimensioned by getNlocal
381 <    real ( kind = dp ), dimension(3,getNlocal()) :: f
381 >    real ( kind = dp ), dimension(3,nLocal) :: f
382      !! Torsion array provided by C, dimensioned by getNlocal
383 <    real( kind = dp ), dimension(3,getNlocal()) :: t    
383 >    real( kind = dp ), dimension(3,nLocal) :: t    
384 >
385      !! Stress Tensor
386      real( kind = dp), dimension(9) :: tau  
387      real ( kind = dp ) :: pot
388      logical ( kind = 2) :: do_pot_c, do_stress_c
389      logical :: do_pot
390      logical :: do_stress
391 +    logical :: in_switching_region
392   #ifdef IS_MPI
393      real( kind = DP ) :: pot_local
394      integer :: nrow
395      integer :: ncol
396 +    integer :: nprocs
397 +    integer :: nrow_group
398 +    integer :: ncol_group
399   #endif
197    integer :: nlocal
400      integer :: natoms    
401      logical :: update_nlist  
402      integer :: i, j, jbeg, jend, jnab
403 +    integer :: ia, jb, atom1, atom2
404      integer :: nlist
405 <    real( kind = DP ) ::  rijsq
406 <    real(kind=dp),dimension(3) :: d
405 >    real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vab
406 >    real( kind = DP ) :: sw, dswdr, swderiv, mf
407 >    real(kind=dp),dimension(3) :: d_atm, d_grp
408      real(kind=dp) :: rfpot, mu_i, virial
409 <    integer :: me_i
409 >    integer :: me_i, me_j
410      logical :: is_dp_i
411      integer :: neighborListSize
412      integer :: listerror, error
413      integer :: localError
414 +    integer :: propPack_i, propPack_j
415  
416 <    real(kind=dp) :: listSkin = 1.0
416 >    real(kind=dp) :: listSkin = 1.0  
417      
213
418      !! initialize local variables  
419 <
419 >    
420   #ifdef IS_MPI
421      pot_local = 0.0_dp
218    nlocal = getNlocal()
422      nrow   = getNrow(plan_row)
423      ncol   = getNcol(plan_col)
424 +    nrow_group   = getNrowGroup(plan_row)
425 +    ncol_group   = getNcolGroup(plan_col)
426   #else
222    nlocal = getNlocal()
427      natoms = nlocal
428   #endif
429 <  
430 <    call check_initialization(localError)
429 >    
430 >    call doReadyCheck(localError)
431      if ( localError .ne. 0 ) then
432 +       call handleError("do_force_loop", "Not Initialized")
433         error = -1
434         return
435      end if
436      call zero_work_arrays()
437 <
437 >        
438      do_pot = do_pot_c
439      do_stress = do_stress_c
440 <
440 >    
441      ! Gather all information needed by all force loops:
442      
443   #ifdef IS_MPI    
444 +    
445 +    call gather(q, q_Row, plan_row3d)
446 +    call gather(q, q_Col, plan_col3d)
447  
448 <    call gather(q,q_Row,plan_row3d)
449 <    call gather(q,q_Col,plan_col3d)
448 >    call gather(q_group, q_group_Row, plan_row_Group_3d)
449 >    call gather(q_group, q_group_Col, plan_col_Group_3d)
450          
451 <    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
451 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
452         call gather(u_l,u_l_Row,plan_row3d)
453         call gather(u_l,u_l_Col,plan_col3d)
454        
# Line 250 | Line 458 | contains
458      
459   #endif
460      
461 <    if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
461 >    !! Begin force loop timing:
462 > #ifdef PROFILE
463 >    call cpu_time(forceTimeInitial)
464 >    nloops = nloops + 1
465 > #endif
466 >    
467 >    if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
468         !! See if we need to update neighbor lists
469 <       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
469 >
470 >       call checkNeighborList(nGroup, q_group, listSkin, update_nlist)
471 >
472         !! if_mpi_gather_stuff_for_prepair
473         !! do_prepair_loop_if_needed
474         !! if_mpi_scatter_stuff_from_prepair
475         !! if_mpi_gather_stuff_from_prepair_to_main_loop
476 <
477 < !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
476 >      
477 >       !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
478   #ifdef IS_MPI
263    
264    if (update_nlist) then
479        
480 <       !! save current configuration, construct neighbor list,
267 <       !! and calculate forces
268 <       call saveNeighborList(nlocal, q)
269 <      
270 <       neighborListSize = size(list)
271 <       nlist = 0      
272 <      
273 <       do i = 1, nrow
274 <          point(i) = nlist + 1
480 >       if (update_nlist) then
481            
482 <          prepair_inner: do j = 1, ncol
482 >          !! save current configuration, construct neighbor list,
483 >          !! and calculate forces
484 >
485 >          call saveNeighborList(nGroup, q_group)
486 >          
487 >          neighborListSize = size(list)
488 >          nlist = 0      
489 >          
490 >          do i = 1, nrow_group
491 >             point(i) = nlist + 1
492              
493 <             if (skipThisPair(i,j)) cycle prepair_inner
279 <            
280 <             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
281 <            
282 <             if (rijsq < rlistsq) then            
493 >             do j = 1, ncol_group
494                  
495 <                nlist = nlist + 1
495 >                call get_interatomic_vector(q_group_Row(:,i), &
496 >                     q_group_Col(:,j), d_grp, rgrpsq)
497                  
498 <                if (nlist > neighborListSize) then
499 <                   call expandNeighborList(nlocal, listerror)
500 <                   if (listerror /= 0) then
501 <                      error = -1
502 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
503 <                      return
504 <                   end if
505 <                   neighborListSize = size(list)
506 <                endif
507 <                
508 <                list(nlist) = j
509 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot_local)                      
510 <             endif
511 <          enddo prepair_inner
512 <       enddo
498 >                if (rgrpsq < rlistsq) then
499 >                   nlist = nlist + 1
500 >                  
501 >                   if (nlist > neighborListSize) then
502 >                      call expandNeighborList(nGroup, listerror)
503 >                      if (listerror /= 0) then
504 >                         error = -1
505 >                         write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
506 >                         return
507 >                      end if
508 >                      neighborListSize = size(list)
509 >                   endif
510 >                  
511 >                   list(nlist) = j
512 >                  
513 >                   do ia = groupStart(i), groupStart(i+1)-1
514 >                      atom1 = groupList(ia)
515  
516 <       point(nrow + 1) = nlist + 1
517 <      
518 <    else  !! (of update_check)
516 >                      prepair_inner: do jb = groupStart(j), groupStart(j+1)-1
517 >                         atom2 = groupList(jb)
518 >                        
519 >                         if (skipThisPair(atom1, atom2)) cycle prepair_inner
520 >                        
521 >                         call get_interatomic_vector(q_Row(:,atom1), &
522 >                              q_Col(:,atom2), d_atm, ratmsq)
523 >                        
524 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, &
525 >                              rgrpsq, d_grp, do_pot, do_stress, &
526 >                              u_l, A, f, t, pot_local)
527  
528 <       ! use the list to find the neighbors
529 <       do i = 1, nrow
530 <          JBEG = POINT(i)
531 <          JEND = POINT(i+1) - 1
532 <          ! check thiat molecule i has neighbors
533 <          if (jbeg .le. jend) then
534 <            
535 <             do jnab = jbeg, jend
536 <                j = list(jnab)
528 >                      enddo prepair_inner
529 >                   enddo
530 >                end if
531 >             enddo
532 >          enddo
533 >          point(nrow_group + 1) = nlist + 1          
534 >                          
535 >       else  !! (of update_check)
536 >          
537 >          ! use the list to find the neighbors
538 >          do i = 1, nrow_group
539 >             JBEG = POINT(i)
540 >             JEND = POINT(i+1) - 1
541 >             ! check that group i has neighbors
542 >             if (jbeg .le. jend) then
543 >                
544 >                do jnab = jbeg, jend
545 >                   j = list(jnab)
546 >                  
547 >                   do ia = groupStart(i), groupStart(i+1)-1
548 >                      atom1 = groupList(ia)
549  
550 <                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
551 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
552 <                     u_l, A, f, t, pot_local)
553 <
554 <             enddo
555 <          endif
556 <       enddo
557 <    endif
558 <    
559 < #else
560 <    
561 <    if (update_nlist) then
550 >                      do jb = groupStart(j), groupStart(j+1)-1
551 >                         atom2 = groupList(jb)                        
552 >                        
553 >                         call get_interatomic_vector(q_Row(:,atom1), &
554 >                              q_Col(:,atom2), d_atm, ratmsq)
555 >                        
556 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, &
557 >                              rgrpsq, d_grp, do_pot, do_stress, &
558 >                              u_l, A, f, t, pot_local)
559 >                        
560 >                      enddo
561 >                   enddo
562 >                enddo
563 >             endif
564 >          enddo
565 >       endif
566        
567 <       ! save current configuration, contruct neighbor list,
568 <       ! and calculate forces
569 <       call saveNeighborList(natoms, q)
332 <      
333 <       neighborListSize = size(list)
334 <  
335 <       nlist = 0
336 <      
337 <       do i = 1, natoms-1
338 <          point(i) = nlist + 1
567 > #else
568 >
569 >       if (update_nlist) then
570            
571 <          prepair_inner: do j = i+1, natoms
571 >          !! save current configuration, construct neighbor list,
572 >          !! and calculate forces
573 >          
574 >          call saveNeighborList(nGroup, q_group)
575 >          
576 >          neighborListSize = size(list)
577 >          nlist = 0      
578 >          
579 >          do i = 1, nGroup-1
580 >             point(i) = nlist + 1
581              
582 <             if (skipThisPair(i,j))  cycle prepair_inner
343 <                          
344 <             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
345 <          
346 <
347 <             if (rijsq < rlistsq) then
582 >             do j = i+1, nGroup
583                  
584 <                nlist = nlist + 1
585 <              
351 <                if (nlist > neighborListSize) then
352 <                   call expandNeighborList(natoms, listerror)
353 <                   if (listerror /= 0) then
354 <                      error = -1
355 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
356 <                      return
357 <                   end if
358 <                   neighborListSize = size(list)
359 <                endif
584 >                call get_interatomic_vector(q_group(:,i), &
585 >                     q_group(:,j), d_grp, rgrpsq)
586                  
587 <                list(nlist) = j
587 >                if (rgrpsq < rlistsq) then
588 >                   nlist = nlist + 1
589 >                  
590 >                   if (nlist > neighborListSize) then
591 >                      call expandNeighborList(nGroup, listerror)
592 >                      if (listerror /= 0) then
593 >                         error = -1
594 >                         write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
595 >                         return
596 >                      end if
597 >                      neighborListSize = size(list)
598 >                   endif
599 >                  
600 >                   list(nlist) = j
601 >                  
602 >                   do ia = groupStart(i), groupStart(i+1)-1
603 >                      atom1 = groupList(ia)
604 >                      
605 >                      prepair_inner: do jb = groupStart(j), groupStart(j+1)-1
606 >                         atom2 = groupList(jb)
607 >                        
608 >                         if (skipThisPair(atom1, atom2)) cycle prepair_inner
609 >                        
610 >                         call get_interatomic_vector(q(:,atom1), &
611 >                              q(:,atom2), d_atm, ratmsq)
612 >                        
613 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, &
614 >                              rgrpsq, d_grp, do_pot, do_stress, &
615 >                              u_l, A, f, t, pot)
616 >                        
617 >                      enddo prepair_inner
618 >                   enddo
619 >                end if
620 >             enddo
621 >          enddo
622 >          point(nGroup) = nlist + 1          
623 >                          
624 >       else  !! (of update_check)
625 >          
626 >          ! use the list to find the neighbors
627 >          do i = 1, nGroup-1
628 >             JBEG = POINT(i)
629 >             JEND = POINT(i+1) - 1
630 >             ! check that group i has neighbors
631 >             if (jbeg .le. jend) then
632                  
633 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
634 <                        u_l, A, f, t, pot)
635 <                
633 >                do jnab = jbeg, jend
634 >                   j = list(jnab)
635 >                  
636 >                   do ia = groupStart(i), groupStart(i+1)-1
637 >                      atom1 = groupList(ia)
638 >
639 >                      do jb = groupStart(j), groupStart(j+1)-1
640 >                         atom2 = groupList(jb)                        
641 >                        
642 >                         call get_interatomic_vector(q(:,atom1), &
643 >                              q(:,atom2), d_atm, ratmsq)
644 >                        
645 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, &
646 >                              rgrpsq, d_grp, do_pot, do_stress, &
647 >                              u_l, A, f, t, pot)
648 >                        
649 >                      enddo
650 >                   enddo
651 >                enddo
652               endif
653 <          enddo prepair_inner
654 <       enddo
653 >          enddo
654 >       endif
655        
370       point(natoms) = nlist + 1
371      
372    else !! (update)
373      
374       ! use the list to find the neighbors
375       do i = 1, natoms-1
376          JBEG = POINT(i)
377          JEND = POINT(i+1) - 1
378          ! check thiat molecule i has neighbors
379          if (jbeg .le. jend) then
380            
381             do jnab = jbeg, jend
382                j = list(jnab)
383
384                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
385                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
386                     u_l, A, f, t, pot)
387
388             enddo
389          endif
390       enddo
391    endif    
656   #endif
657 <    !! Do rest of preforce calculations
658 <   call do_preforce(nlocal,pot)
657 >      
658 >       !! Do rest of preforce calculations
659 >       !! do necessary preforce calculations  
660 >       call do_preforce(nlocal,pot)
661 >       ! we have already updated the neighbor list set it to false...
662 >       update_nlist = .false.
663      else
664         !! See if we need to update neighbor lists for non pre-pair
665 <       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
665 >       call checkNeighborList(nGroup, q_group, listSkin, update_nlist)  
666      endif
667 <
668 <
669 <
402 <
403 <
404 < !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>>>>>>>>>>>>>>>>
405 <
406 <
407 <
408 <
409 <  
667 >    
668 >    !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>
669 >    
670   #ifdef IS_MPI
671      
672      if (update_nlist) then
673        
674         !! save current configuration, construct neighbor list,
675         !! and calculate forces
416       call saveNeighborList(nlocal, q)
676        
677 +       call saveNeighborList(nGroup, q_group)
678 +      
679         neighborListSize = size(list)
680         nlist = 0      
681        
682 <       do i = 1, nrow
682 >       do i = 1, nrow_group
683            point(i) = nlist + 1
684            
685 <          inner: do j = 1, ncol
685 >          do j = 1, ncol_group
686              
687 <             if (skipThisPair(i,j)) cycle inner
688 <            
428 <             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
687 >             call get_interatomic_vector(q_group_Row(:,i), &
688 >                  q_group_Col(:,j), d_grp, rgrpsq)
689              
690 <             if (rijsq < rlistsq) then            
431 <                
690 >             if (rgrpsq < rlistsq) then
691                  nlist = nlist + 1
692                  
693                  if (nlist > neighborListSize) then
694 <                   call expandNeighborList(nlocal, listerror)
694 >                   call expandNeighborList(nGroup, listerror)
695                     if (listerror /= 0) then
696                        error = -1
697                        write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
# Line 442 | Line 701 | contains
701                  endif
702                  
703                  list(nlist) = j
445                                
446                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
447                     u_l, A, f, t, pot_local)
704                  
705 <             endif
706 <          enddo inner
707 <       enddo
705 >                vab = 0.0d0
706 >                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
707 >                     in_switching_region)
708 >                
709 >                do ia = groupStart(i), groupStart(i+1)-1
710 >                   atom1 = groupList(ia)
711 >                  
712 >                   inner: do jb = groupStart(j), groupStart(j+1)-1
713 >                      atom2 = groupList(jb)                    
714  
715 <       point(nrow + 1) = nlist + 1
715 >                      if (skipThisPair(atom1, atom2)) cycle inner
716 >                      
717 >                      call get_interatomic_vector(q_Row(:,atom1), &
718 >                           q_Col(:,atom2), d_atm, ratmsq)
719 >                      
720 >                      call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
721 >                           do_pot, do_stress, &
722 >                           u_l, A, f, t, pot_local, vpair)
723 >                      
724 >                      vab = vab + vpair
725 >                   enddo inner
726 >                enddo
727 >
728 >                if (in_switching_region) then
729 >                   swderiv = vab*dswdr/rgrp
730 >                  
731 >                   do ia=groupStart(i), groupStart(i+1)-1
732 >                      atom1=groupList(ia)
733 >                      mf = mfact(atom1)                  
734 >                      f_Row(1,atom1) = f_Row(1,atom1) - swderiv*d_grp(1)*mf
735 >                      f_Row(2,atom1) = f_Row(2,atom1) - swderiv*d_grp(2)*mf
736 >                      f_Row(3,atom1) = f_Row(3,atom1) - swderiv*d_grp(3)*mf
737 >                   enddo
738 >                  
739 >                   do jb=groupStart(j), groupStart(j+1)-1
740 >                      atom2=groupList(jb)
741 >                      mf = mfact(atom2)
742 >                      f_Col(1,atom2) = f_Col(1,atom2) + swderiv*d_grp(1)*mf
743 >                      f_Col(2,atom2) = f_Col(2,atom2) + swderiv*d_grp(2)*mf
744 >                      f_Col(3,atom2) = f_Col(3,atom2) + swderiv*d_grp(3)*mf
745 >                   enddo                        
746 >                endif
747 >
748 >             end if
749 >          enddo
750 >       enddo
751 >       point(nrow_group + 1) = nlist + 1          
752        
753      else  !! (of update_check)
754 <
754 >      
755         ! use the list to find the neighbors
756 <       do i = 1, nrow
756 >       do i = 1, nrow_group
757            JBEG = POINT(i)
758            JEND = POINT(i+1) - 1
759 <          ! check thiat molecule i has neighbors
759 >          ! check that group i has neighbors
760            if (jbeg .le. jend) then
761              
762               do jnab = jbeg, jend
763                  j = list(jnab)
764 +                              
765 +                call get_interatomic_vector(q_group_Row(:,i), &
766 +                     q_group_Col(:,j), d_grp, rgrpsq)
767 +                
768 +                vab = 0.0d0
769 +                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
770 +                     in_switching_region)
771 +                
772 +                do ia = groupStart(i), groupStart(i+1)-1
773 +                   atom1 = groupList(ia)
774 +                  
775 +                   do jb = groupStart(j), groupStart(j+1)-1
776 +                      atom2 = groupList(jb)                        
777 +                      write(*,*) 'doing ', atom1, atom2
778 +                      
779 +                      call get_interatomic_vector(q_Row(:,atom1), &
780 +                           q_Col(:,atom2), d_atm, ratmsq)
781 +                                            
782 +                      call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
783 +                           do_pot, do_stress, &
784 +                           u_l, A, f, t, pot_local, vpair)
785 +                      
786 +                      vab = vab + vpair
787 +                                            
788 +                   enddo
789 +                enddo
790 +                
791 +                if (in_switching_region) then
792 +                   swderiv = vab*dswdr/rgrp
793 +  
794 +                   do ia=groupStart(i), groupStart(i+1)-1
795 +                      atom1=groupList(ia)
796 +                      mf = mfact(atom1)                  
797 +                      f_Row(1,atom1) = f_Row(1,atom1) - swderiv*d_grp(1)*mf
798 +                      f_Row(2,atom1) = f_Row(2,atom1) - swderiv*d_grp(2)*mf
799 +                      f_Row(3,atom1) = f_Row(3,atom1) - swderiv*d_grp(3)*mf
800 +                   enddo
801 +                  
802 +                   do jb=groupStart(j), groupStart(j+1)-1
803 +                      atom2=groupList(jb)
804 +                      mf = mfact(atom2)
805 +                      f_Col(1,atom2) = f_Col(1,atom2) + swderiv*d_grp(1)*mf
806 +                      f_Col(2,atom2) = f_Col(2,atom2) + swderiv*d_grp(2)*mf
807 +                      f_Col(3,atom2) = f_Col(3,atom2) + swderiv*d_grp(3)*mf
808 +                   enddo
809 +                endif
810  
467                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
468                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
469                     u_l, A, f, t, pot_local)
470
811               enddo
812            endif
813         enddo
814      endif
815      
816   #else
817 <    
817 >
818      if (update_nlist) then
819        
820 <       ! save current configuration, contruct neighbor list,
821 <       ! and calculate forces
482 <       call saveNeighborList(natoms, q)
820 >       !! save current configuration, construct neighbor list,
821 >       !! and calculate forces
822        
823 +       call saveNeighborList(nGroup, q_group)
824 +      
825         neighborListSize = size(list)
826 <  
486 <       nlist = 0
826 >       nlist = 0      
827        
828 <       do i = 1, natoms-1
828 >       do i = 1, nGroup-1
829            point(i) = nlist + 1
830            
831 <          inner: do j = i+1, natoms
831 >          do j = i+1, nGroup
832              
833 <             if (skipThisPair(i,j))  cycle inner
834 <                          
835 <             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
836 <          
497 <
498 <             if (rijsq < rlistsq) then
499 <                
833 >             call get_interatomic_vector(q_group(:,i), &
834 >                  q_group(:,j), d_grp, rgrpsq)
835 >            
836 >             if (rgrpsq < rlistsq) then
837                  nlist = nlist + 1
838 <              
838 >                
839                  if (nlist > neighborListSize) then
840 <                   call expandNeighborList(natoms, listerror)
840 >                   call expandNeighborList(nGroup, listerror)
841                     if (listerror /= 0) then
842                        error = -1
843                        write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
# Line 510 | Line 847 | contains
847                  endif
848                  
849                  list(nlist) = j
850 +
851 +                vab = 0.0d0
852 +                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
853 +                     in_switching_region)
854                  
855 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
856 <                        u_l, A, f, t, pot)
857 <                
858 <             endif
859 <          enddo inner
855 >                do ia = groupStart(i), groupStart(i+1)-1
856 >                   atom1 = groupList(ia)
857 >                  
858 >                   inner: do jb = groupStart(j), groupStart(j+1)-1
859 >                      atom2 = groupList(jb)
860 >                      
861 >                      if (skipThisPair(atom1, atom2)) cycle inner
862 >                      
863 >                      call get_interatomic_vector(q(:,atom1), &
864 >                           q(:,atom2), d_atm, ratmsq)
865 >                      
866 >                      call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
867 >                           do_pot, do_stress, &
868 >                           u_l, A, f, t, pot, vpair)
869 >                      
870 >                      vab = vab + vpair
871 >                      
872 >                   enddo inner
873 >                enddo
874 >
875 >                if (in_switching_region) then
876 >                   swderiv = vab*dswdr/rgrp
877 >                   do ia=groupStart(i), groupStart(i+1)-1
878 >                      atom1=groupList(ia)
879 >                      mf = mfact(atom1)                  
880 >                      f(1,atom1) = f(1,atom1) - swderiv*d_grp(1)*mf
881 >                      f(2,atom1) = f(2,atom1) - swderiv*d_grp(2)*mf
882 >                      f(3,atom1) = f(3,atom1) - swderiv*d_grp(3)*mf
883 >                   enddo
884 >                  
885 >                   do jb=groupStart(j), groupStart(j+1)-1
886 >                      atom2=groupList(jb)
887 >                      mf = mfact(atom2)
888 >                      f(1,atom2) = f(1,atom2) + swderiv*d_grp(1)*mf
889 >                      f(2,atom2) = f(2,atom2) + swderiv*d_grp(2)*mf
890 >                      f(3,atom2) = f(3,atom2) + swderiv*d_grp(3)*mf
891 >                   enddo
892 >                endif
893 >
894 >             end if
895 >          enddo
896         enddo
897 +       point(nGroup) = nlist + 1          
898        
899 <       point(natoms) = nlist + 1
899 >    else  !! (of update_check)
900        
523    else !! (update)
524      
901         ! use the list to find the neighbors
902 <       do i = 1, natoms-1
902 >       do i = 1, nGroup-1
903            JBEG = POINT(i)
904            JEND = POINT(i+1) - 1
905 <          ! check thiat molecule i has neighbors
905 >          ! check that group i has neighbors
906            if (jbeg .le. jend) then
907              
908               do jnab = jbeg, jend
909                  j = list(jnab)
910  
911 <                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
912 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
537 <                     u_l, A, f, t, pot)
911 >                call get_interatomic_vector(q_group(:,i), &
912 >                     q_group(:,j), d_grp, rgrpsq)
913  
914 +                vab = 0.0d0    
915 +              
916 +                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
917 +                     in_switching_region)
918 +                                
919 +                do ia = groupStart(i), groupStart(i+1)-1
920 +                   atom1 = groupList(ia)
921 +                  
922 +                   do jb = groupStart(j), groupStart(j+1)-1
923 +                      atom2 = groupList(jb)                        
924 +                      
925 +                      call get_interatomic_vector(q(:,atom1), &
926 +                           q(:,atom2), d_atm, ratmsq)
927 +                      
928 +                      call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
929 +                           do_pot, do_stress, &
930 +                           u_l, A, f, t, pot, vpair)
931 +                      
932 +                      vab = vab + vpair
933 +
934 +                   enddo
935 +                enddo
936 +                
937 +                if (in_switching_region) then
938 +                   swderiv = vab*dswdr/rgrp
939 +                  
940 +                   do ia=groupStart(i), groupStart(i+1)-1
941 +                      atom1=groupList(ia)
942 +                      mf = mfact(atom1)                  
943 +                      f(1,atom1) = f(1,atom1) - swderiv*d_grp(1)*mf
944 +                      f(2,atom1) = f(2,atom1) - swderiv*d_grp(2)*mf
945 +                      f(3,atom1) = f(3,atom1) - swderiv*d_grp(3)*mf
946 +                   enddo
947 +                  
948 +                   do jb=groupStart(j), groupStart(j+1)-1
949 +                      atom2=groupList(jb)
950 +                      mf = mfact(atom2)
951 +                      f(1,atom2) = f(1,atom2) + swderiv*d_grp(1)*mf
952 +                      f(2,atom2) = f(2,atom2) + swderiv*d_grp(2)*mf
953 +                      f(3,atom2) = f(3,atom2) + swderiv*d_grp(3)*mf
954 +                   enddo
955 +                endif
956               enddo
957            endif
958         enddo
959      endif
960 <    
960 >        
961   #endif
962      
963      ! phew, done with main loop.
964      
965 +    !! Do timing
966 + #ifdef PROFILE
967 +    call cpu_time(forceTimeFinal)
968 +    forceTime = forceTime + forceTimeFinal - forceTimeInitial
969 + #endif    
970 +    
971   #ifdef IS_MPI
972      !!distribute forces
973 <  
973 >    
974      f_temp = 0.0_dp
975      call scatter(f_Row,f_temp,plan_row3d)
976      do i = 1,nlocal
977         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
978      end do
979 <
979 >    
980      f_temp = 0.0_dp
981      call scatter(f_Col,f_temp,plan_col3d)
982      do i = 1,nlocal
983         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
984      end do
985      
986 <    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
986 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
987         t_temp = 0.0_dp
988         call scatter(t_Row,t_temp,plan_row3d)
989         do i = 1,nlocal
# Line 577 | Line 1000 | contains
1000      if (do_pot) then
1001         ! scatter/gather pot_row into the members of my column
1002         call scatter(pot_Row, pot_Temp, plan_row)
1003 <
1003 >      
1004         ! scatter/gather pot_local into all other procs
1005         ! add resultant to get total pot
1006         do i = 1, nlocal
# Line 585 | Line 1008 | contains
1008         enddo
1009        
1010         pot_Temp = 0.0_DP
1011 <
1011 >      
1012         call scatter(pot_Col, pot_Temp, plan_col)
1013         do i = 1, nlocal
1014            pot_local = pot_local + pot_Temp(i)
1015         enddo
1016 <
1017 <    endif    
1016 >      
1017 >    endif
1018   #endif
1019 <
1020 <    if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
1019 >    
1020 >    if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
1021        
1022 <       if (FF_uses_RF .and. SimUsesRF()) then
1022 >       if (FF_uses_RF .and. SIM_uses_RF) then
1023            
1024   #ifdef IS_MPI
1025            call scatter(rf_Row,rf,plan_row3d)
# Line 606 | Line 1029 | contains
1029            end do
1030   #endif
1031            
1032 <          do i = 1, getNlocal()
1033 <
1032 >          do i = 1, nLocal
1033 >            
1034               rfpot = 0.0_DP
1035   #ifdef IS_MPI
1036               me_i = atid_row(i)
1037   #else
1038               me_i = atid(i)
1039   #endif
1040 <             call getElementProperty(atypes, me_i, "is_DP", is_DP_i)      
1041 <             if ( is_DP_i ) then
1042 <                call getElementProperty(atypes, me_i, "dipole_moment", mu_i)
1040 >            
1041 >             if (PropertyMap(me_i)%is_DP) then
1042 >                
1043 >                mu_i = PropertyMap(me_i)%dipole_moment
1044 >                
1045                  !! The reaction field needs to include a self contribution
1046                  !! to the field:
1047 <                call accumulate_self_rf(i, mu_i, u_l)            
1047 >                call accumulate_self_rf(i, mu_i, u_l)
1048                  !! Get the reaction field contribution to the
1049                  !! potential and torques:
1050                  call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
# Line 633 | Line 1058 | contains
1058            enddo
1059         endif
1060      endif
1061 <
1062 <
1061 >    
1062 >    
1063   #ifdef IS_MPI
1064 <
1064 >    
1065      if (do_pot) then
1066         pot = pot + pot_local
1067         !! we assume the c code will do the allreduce to get the total potential
1068         !! we could do it right here if we needed to...
1069      endif
1070 <
1070 >    
1071      if (do_stress) then
1072 <      call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
1072 >       call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
1073              mpi_comm_world,mpi_err)
1074         call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
1075              mpi_comm_world,mpi_err)
1076      endif
1077 <
1077 >    
1078   #else
1079 <
1079 >    
1080      if (do_stress) then
1081         tau = tau_Temp
1082         virial = virial_Temp
1083      endif
1084 <
1084 >    
1085   #endif
1086      
1087 +    
1088    end subroutine do_force_loop
1089  
1090 <  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
1090 >  
1091 >  subroutine do_pair(i, j, rijsq, d, sw, do_pot, do_stress, &
1092 >       u_l, A, f, t, pot, vpair)
1093  
1094 <    real( kind = dp ) :: pot
1095 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
1096 <    real (kind=dp), dimension(9,getNlocal()) :: A
1097 <    real (kind=dp), dimension(3,getNlocal()) :: f
1098 <    real (kind=dp), dimension(3,getNlocal()) :: t
1094 >    real( kind = dp ) :: pot, vpair, sw
1095 >    real( kind = dp ), dimension(nLocal)   :: mfact
1096 >    real( kind = dp ), dimension(3,nLocal) :: u_l
1097 >    real( kind = dp ), dimension(9,nLocal) :: A
1098 >    real( kind = dp ), dimension(3,nLocal) :: f
1099 >    real( kind = dp ), dimension(3,nLocal) :: t
1100  
1101      logical, intent(inout) :: do_pot, do_stress
1102      integer, intent(in) :: i, j
1103 <    real ( kind = dp ), intent(inout)    :: rijsq
1103 >    real ( kind = dp ), intent(inout) :: rijsq
1104      real ( kind = dp )                :: r
1105      real ( kind = dp ), intent(inout) :: d(3)
677    logical :: is_LJ_i, is_LJ_j
678    logical :: is_DP_i, is_DP_j
679    logical :: is_GB_i, is_GB_j
680    logical :: is_EAM_i,is_EAM_j
681    logical :: is_Sticky_i, is_Sticky_j
1106      integer :: me_i, me_j
1107  
1108      r = sqrt(rijsq)
1109 +    vpair = 0.0d0
1110  
1111   #ifdef IS_MPI
1112      if (tagRow(i) .eq. tagColumn(j)) then
1113         write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
1114      endif
690
1115      me_i = atid_row(i)
1116      me_j = atid_col(j)
693
1117   #else
695
1118      me_i = atid(i)
1119      me_j = atid(j)
698
1120   #endif
1121 +    
1122 +    if (FF_uses_LJ .and. SIM_uses_LJ) then
1123 +      
1124 +       if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
1125 +          !write(*,*) 'calling lj with'
1126 +          !write(*,*) i, j, r, rijsq
1127 +          !write(*,'(3es12.3)') d(1), d(2), d(3)
1128 +          !write(*,'(3es12.3)') sw, vpair, pot
1129 +          !write(*,*)
1130  
1131 <    if (FF_uses_LJ .and. SimUsesLJ()) then
1132 <       call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
1133 <       call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
704 <
705 <       if ( is_LJ_i .and. is_LJ_j ) &
706 <            call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
707 <    endif
708 <
709 <    if (FF_uses_dipoles .and. SimUsesDipoles()) then
710 <       call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
711 <       call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
1131 >          call do_lj_pair(i, j, d, r, rijsq, sw, vpair, pot, f, do_pot, &
1132 >               do_stress)
1133 >       endif
1134        
1135 <       if ( is_DP_i .and. is_DP_j ) then
1136 <          
1137 <          call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
1135 >    endif
1136 >    
1137 >    if (FF_uses_charges .and. SIM_uses_charges) then
1138 >      
1139 >       if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
1140 >          call do_charge_pair(i, j, d, r, rijsq, sw, vpair, pot, f, do_pot, &
1141 >               do_stress)
1142 >       endif
1143 >      
1144 >    endif
1145 >    
1146 >    if (FF_uses_dipoles .and. SIM_uses_dipoles) then
1147 >      
1148 >       if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
1149 >          call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, pot, u_l, f, t, &
1150                 do_pot, do_stress)
1151 <          if (FF_uses_RF .and. SimUsesRF()) then
1152 <             call accumulate_rf(i, j, r, u_l)
1153 <             call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
1154 <          endif
721 <          
1151 >          if (FF_uses_RF .and. SIM_uses_RF) then
1152 >             call accumulate_rf(i, j, r, u_l, sw)
1153 >             call rf_correct_forces(i, j, d, r, u_l, sw, f, do_stress)
1154 >          endif          
1155         endif
1156 +
1157      endif
1158  
1159 <    if (FF_uses_Sticky .and. SimUsesSticky()) then
1159 >    if (FF_uses_Sticky .and. SIM_uses_sticky) then
1160  
1161 <       call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
1162 <       call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
729 <
730 <       if ( is_Sticky_i .and. is_Sticky_j ) then
731 <          call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
1161 >       if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
1162 >          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, pot, A, f, t, &
1163                 do_pot, do_stress)
1164         endif
1165 +
1166      endif
1167  
1168  
1169 <    if (FF_uses_GB .and. SimUsesGB()) then
738 <
739 <       call getElementProperty(atypes, me_i, "is_GB", is_GB_i)
740 <       call getElementProperty(atypes, me_j, "is_GB", is_GB_j)
1169 >    if (FF_uses_GB .and. SIM_uses_GB) then
1170        
1171 <       if ( is_GB_i .and. is_GB_j ) then
1172 <          call do_gb_pair(i, j, d, r, rijsq, u_l, pot, f, t, &
1171 >       if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
1172 >          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, pot, u_l, f, t, &
1173                 do_pot, do_stress)          
1174         endif
746    endif
747    
1175  
1176 <  
1177 <   if (FF_uses_EAM .and. SimUsesEAM()) then
1178 <      call getElementProperty(atypes, me_i, "is_EAM", is_EAM_i)
1179 <      call getElementProperty(atypes, me_j, "is_EAM", is_EAM_j)
1180 <      
1181 <      if ( is_EAM_i .and. is_EAM_j ) &
1182 <           call do_eam_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
1183 <   endif
1184 <
1185 <
1186 <
760 <
1176 >    endif
1177 >      
1178 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
1179 >      
1180 >       if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
1181 >          call do_eam_pair(i, j, d, r, rijsq, sw, vpair, pot, f, &
1182 >               do_pot, do_stress)
1183 >       endif
1184 >      
1185 >    endif
1186 >    
1187    end subroutine do_pair
1188  
1189 <
1190 <
765 <  subroutine do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
1189 >  subroutine do_prepair(i, j, rijsq, d, rcijsq, dc, &
1190 >       do_pot, do_stress, u_l, A, f, t, pot)
1191     real( kind = dp ) :: pot
1192 <   real( kind = dp ), dimension(3,getNlocal()) :: u_l
1193 <   real (kind=dp), dimension(9,getNlocal()) :: A
1194 <   real (kind=dp), dimension(3,getNlocal()) :: f
1195 <   real (kind=dp), dimension(3,getNlocal()) :: t
1192 >   real( kind = dp ), dimension(3,nLocal) :: u_l
1193 >   real (kind=dp), dimension(9,nLocal) :: A
1194 >   real (kind=dp), dimension(3,nLocal) :: f
1195 >   real (kind=dp), dimension(3,nLocal) :: t
1196    
1197     logical, intent(inout) :: do_pot, do_stress
1198     integer, intent(in) :: i, j
1199 <   real ( kind = dp ), intent(inout)    :: rijsq
1200 <   real ( kind = dp )                :: r
1201 <   real ( kind = dp ), intent(inout) :: d(3)
1199 >   real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
1200 >   real ( kind = dp )                :: r, rc
1201 >   real ( kind = dp ), intent(inout) :: d(3), dc(3)
1202    
1203     logical :: is_EAM_i, is_EAM_j
1204    
1205     integer :: me_i, me_j
1206    
1207 <   r = sqrt(rijsq)
1207 >
1208 >    r = sqrt(rijsq)
1209 >    if (SIM_uses_molecular_cutoffs) then
1210 >       rc = sqrt(rcijsq)
1211 >    else
1212 >       rc = r
1213 >    endif
1214    
1215 +
1216   #ifdef IS_MPI
1217     if (tagRow(i) .eq. tagColumn(j)) then
1218        write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
# Line 795 | Line 1227 | contains
1227     me_j = atid(j)
1228    
1229   #endif
1230 <  
1231 <   if (FF_uses_EAM .and. SimUsesEAM()) then
1232 <      call getElementProperty(atypes, me_i, "is_EAM", is_EAM_i)
1233 <      call getElementProperty(atypes, me_j, "is_EAM", is_EAM_j)
802 <      
803 <      if ( is_EAM_i .and. is_EAM_j ) &
1230 >    
1231 >   if (FF_uses_EAM .and. SIM_uses_EAM) then
1232 >
1233 >      if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1234             call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1235 +
1236     endif
1237 <  end subroutine do_prepair
1237 >  
1238 > end subroutine do_prepair
1239  
1240  
1241  
1242  
1243 <  subroutine do_preforce(nlocal,pot)
1244 <    integer :: nlocal
1245 <    real( kind = dp ) :: pot
1246 <
1247 <   if (FF_uses_EAM .and. SimUsesEAM()) then
1243 > subroutine do_preforce(nlocal,pot)
1244 >   integer :: nlocal
1245 >   real( kind = dp ) :: pot
1246 >  
1247 >   if (FF_uses_EAM .and. SIM_uses_EAM) then
1248        call calc_EAM_preforce_Frho(nlocal,pot)
1249     endif
1250 <
1251 <
1252 <  end subroutine do_preforce
1253 <  
1254 <  
1255 <  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1256 <    
1257 <    real (kind = dp), dimension(3) :: q_i
1258 <    real (kind = dp), dimension(3) :: q_j
1259 <    real ( kind = dp ), intent(out) :: r_sq
1260 <    real( kind = dp ) :: d(3), scaled(3)
1261 <    integer i
1262 <
1263 <    d(1:3) = q_j(1:3) - q_i(1:3)
1264 <
1265 <    ! Wrap back into periodic box if necessary
1266 <    if ( SimUsesPBC() ) then
835 <      
836 <       if( .not.boxIsOrthorhombic ) then
837 <          ! calc the scaled coordinates.
838 <          
839 <          scaled = matmul(HmatInv, d)
840 <          
841 <          ! wrap the scaled coordinates
842 <
843 <          scaled = scaled  - anint(scaled)
844 <          
845 <
846 <          ! calc the wrapped real coordinates from the wrapped scaled
847 <          ! coordinates
848 <
849 <          d = matmul(Hmat,scaled)
850 <
851 <       else
852 <          ! calc the scaled coordinates.
853 <          
854 <          do i = 1, 3
855 <             scaled(i) = d(i) * HmatInv(i,i)
856 <            
857 <             ! wrap the scaled coordinates
858 <            
859 <             scaled(i) = scaled(i) - anint(scaled(i))
860 <            
861 <             ! calc the wrapped real coordinates from the wrapped scaled
862 <             ! coordinates
863 <
864 <             d(i) = scaled(i)*Hmat(i,i)
865 <          enddo
866 <       endif
867 <      
868 <    endif
869 <    
870 <    r_sq = dot_product(d,d)
871 <    
872 <  end subroutine get_interatomic_vector
873 <  
874 <  subroutine check_initialization(error)
875 <    integer, intent(out) :: error
876 <    
877 <    error = 0
878 <    ! Make sure we are properly initialized.
879 <    if (.not. do_forces_initialized) then
880 <       error = -1
881 <       return
882 <    endif
883 <
884 < #ifdef IS_MPI
885 <    if (.not. isMPISimSet()) then
886 <       write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
887 <       error = -1
888 <       return
889 <    endif
890 < #endif
891 <    
892 <    return
893 <  end subroutine check_initialization
894 <
895 <  
896 <  subroutine zero_work_arrays()
897 <    
898 < #ifdef IS_MPI
899 <
900 <    q_Row = 0.0_dp
901 <    q_Col = 0.0_dp  
902 <    
903 <    u_l_Row = 0.0_dp
904 <    u_l_Col = 0.0_dp
905 <    
906 <    A_Row = 0.0_dp
907 <    A_Col = 0.0_dp
908 <    
909 <    f_Row = 0.0_dp
910 <    f_Col = 0.0_dp
911 <    f_Temp = 0.0_dp
1250 >  
1251 >  
1252 > end subroutine do_preforce
1253 >
1254 >
1255 > subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1256 >  
1257 >   real (kind = dp), dimension(3) :: q_i
1258 >   real (kind = dp), dimension(3) :: q_j
1259 >   real ( kind = dp ), intent(out) :: r_sq
1260 >   real( kind = dp ) :: d(3), scaled(3)
1261 >   integer i
1262 >  
1263 >   d(1:3) = q_j(1:3) - q_i(1:3)
1264 >  
1265 >   ! Wrap back into periodic box if necessary
1266 >   if ( SIM_uses_PBC ) then
1267        
1268 <    t_Row = 0.0_dp
1269 <    t_Col = 0.0_dp
1270 <    t_Temp = 0.0_dp
1268 >      if( .not.boxIsOrthorhombic ) then
1269 >         ! calc the scaled coordinates.
1270 >        
1271 >         scaled = matmul(HmatInv, d)
1272 >        
1273 >         ! wrap the scaled coordinates
1274 >        
1275 >         scaled = scaled  - anint(scaled)
1276 >        
1277 >        
1278 >         ! calc the wrapped real coordinates from the wrapped scaled
1279 >         ! coordinates
1280 >        
1281 >         d = matmul(Hmat,scaled)
1282 >        
1283 >      else
1284 >         ! calc the scaled coordinates.
1285 >        
1286 >         do i = 1, 3
1287 >            scaled(i) = d(i) * HmatInv(i,i)
1288 >            
1289 >            ! wrap the scaled coordinates
1290 >            
1291 >            scaled(i) = scaled(i) - anint(scaled(i))
1292 >            
1293 >            ! calc the wrapped real coordinates from the wrapped scaled
1294 >            ! coordinates
1295 >            
1296 >            d(i) = scaled(i)*Hmat(i,i)
1297 >         enddo
1298 >      endif
1299 >      
1300 >   endif
1301 >  
1302 >   r_sq = dot_product(d,d)
1303 >  
1304 > end subroutine get_interatomic_vector
1305  
1306 <    pot_Row = 0.0_dp
1307 <    pot_Col = 0.0_dp
1308 <    pot_Temp = 0.0_dp
1306 > subroutine zero_work_arrays()
1307 >  
1308 > #ifdef IS_MPI
1309 >  
1310 >   q_Row = 0.0_dp
1311 >   q_Col = 0.0_dp
1312  
1313 <    rf_Row = 0.0_dp
1314 <    rf_Col = 0.0_dp
1315 <    rf_Temp = 0.0_dp
1316 <
1313 >   q_group_Row = 0.0_dp
1314 >   q_group_Col = 0.0_dp  
1315 >  
1316 >   u_l_Row = 0.0_dp
1317 >   u_l_Col = 0.0_dp
1318 >  
1319 >   A_Row = 0.0_dp
1320 >   A_Col = 0.0_dp
1321 >  
1322 >   f_Row = 0.0_dp
1323 >   f_Col = 0.0_dp
1324 >   f_Temp = 0.0_dp
1325 >  
1326 >   t_Row = 0.0_dp
1327 >   t_Col = 0.0_dp
1328 >   t_Temp = 0.0_dp
1329 >  
1330 >   pot_Row = 0.0_dp
1331 >   pot_Col = 0.0_dp
1332 >   pot_Temp = 0.0_dp
1333 >  
1334 >   rf_Row = 0.0_dp
1335 >   rf_Col = 0.0_dp
1336 >   rf_Temp = 0.0_dp
1337 >  
1338   #endif
1339 <
1340 <    rf = 0.0_dp
1341 <    tau_Temp = 0.0_dp
1342 <    virial_Temp = 0.0_dp
1343 <  end subroutine zero_work_arrays
1344 <  
1345 <  function skipThisPair(atom1, atom2) result(skip_it)
1346 <    integer, intent(in) :: atom1
1347 <    integer, intent(in), optional :: atom2
1348 <    logical :: skip_it
1349 <    integer :: unique_id_1, unique_id_2
1350 <    integer :: me_i,me_j
1351 <    integer :: i
1352 <
1353 <    skip_it = .false.
1354 <    
1355 <    !! there are a number of reasons to skip a pair or a particle
1356 <    !! mostly we do this to exclude atoms who are involved in short
1357 <    !! range interactions (bonds, bends, torsions), but we also need
1358 <    !! to exclude some overcounted interactions that result from
1359 <    !! the parallel decomposition
1360 <    
1339 >
1340 >   if (FF_uses_EAM .and. SIM_uses_EAM) then
1341 >      call clean_EAM()
1342 >   endif
1343 >  
1344 >   rf = 0.0_dp
1345 >   tau_Temp = 0.0_dp
1346 >   virial_Temp = 0.0_dp
1347 > end subroutine zero_work_arrays
1348 >
1349 > function skipThisPair(atom1, atom2) result(skip_it)
1350 >   integer, intent(in) :: atom1
1351 >   integer, intent(in), optional :: atom2
1352 >   logical :: skip_it
1353 >   integer :: unique_id_1, unique_id_2
1354 >   integer :: me_i,me_j
1355 >   integer :: i
1356 >  
1357 >   skip_it = .false.
1358 >  
1359 >   !! there are a number of reasons to skip a pair or a particle
1360 >   !! mostly we do this to exclude atoms who are involved in short
1361 >   !! range interactions (bonds, bends, torsions), but we also need
1362 >   !! to exclude some overcounted interactions that result from
1363 >   !! the parallel decomposition
1364 >  
1365   #ifdef IS_MPI
1366 <    !! in MPI, we have to look up the unique IDs for each atom
1367 <    unique_id_1 = tagRow(atom1)
1366 >   !! in MPI, we have to look up the unique IDs for each atom
1367 >   unique_id_1 = tagRow(atom1)
1368   #else
1369 <    !! in the normal loop, the atom numbers are unique
1370 <    unique_id_1 = atom1
1369 >   !! in the normal loop, the atom numbers are unique
1370 >   unique_id_1 = atom1
1371   #endif
1372 <
1373 <    !! We were called with only one atom, so just check the global exclude
1374 <    !! list for this atom
1375 <    if (.not. present(atom2)) then
1376 <       do i = 1, nExcludes_global
1377 <          if (excludesGlobal(i) == unique_id_1) then
1378 <             skip_it = .true.
1379 <             return
1380 <          end if
1381 <       end do
1382 <       return
1383 <    end if
1384 <    
1372 >  
1373 >   !! We were called with only one atom, so just check the global exclude
1374 >   !! list for this atom
1375 >   if (.not. present(atom2)) then
1376 >      do i = 1, nExcludes_global
1377 >         if (excludesGlobal(i) == unique_id_1) then
1378 >            skip_it = .true.
1379 >            return
1380 >         end if
1381 >      end do
1382 >      return
1383 >   end if
1384 >  
1385   #ifdef IS_MPI
1386 <    unique_id_2 = tagColumn(atom2)
1386 >   unique_id_2 = tagColumn(atom2)
1387   #else
1388 <    unique_id_2 = atom2
1388 >   unique_id_2 = atom2
1389   #endif
1390 <
1390 >  
1391   #ifdef IS_MPI
1392 <    !! this situation should only arise in MPI simulations
1393 <    if (unique_id_1 == unique_id_2) then
1394 <       skip_it = .true.
1395 <       return
1396 <    end if
1397 <    
1398 <    !! this prevents us from doing the pair on multiple processors
1399 <    if (unique_id_1 < unique_id_2) then
1400 <       if (mod(unique_id_1 + unique_id_2,2) == 0) then
1401 <          skip_it = .true.
1402 <          return
1403 <       endif
1404 <    else                
1405 <       if (mod(unique_id_1 + unique_id_2,2) == 1) then
1406 <          skip_it = .true.
1407 <          return
1408 <       endif
1409 <    endif
1392 >   !! this situation should only arise in MPI simulations
1393 >   if (unique_id_1 == unique_id_2) then
1394 >      skip_it = .true.
1395 >      return
1396 >   end if
1397 >  
1398 >   !! this prevents us from doing the pair on multiple processors
1399 >   if (unique_id_1 < unique_id_2) then
1400 >      if (mod(unique_id_1 + unique_id_2,2) == 0) then
1401 >         skip_it = .true.
1402 >         return
1403 >      endif
1404 >   else                
1405 >      if (mod(unique_id_1 + unique_id_2,2) == 1) then
1406 >         skip_it = .true.
1407 >         return
1408 >      endif
1409 >   endif
1410   #endif
1411 +  
1412 +   !! the rest of these situations can happen in all simulations:
1413 +   do i = 1, nExcludes_global      
1414 +      if ((excludesGlobal(i) == unique_id_1) .or. &
1415 +           (excludesGlobal(i) == unique_id_2)) then
1416 +         skip_it = .true.
1417 +         return
1418 +      endif
1419 +   enddo
1420 +  
1421 +   do i = 1, nExcludes_local
1422 +      if (excludesLocal(1,i) == unique_id_1) then
1423 +         if (excludesLocal(2,i) == unique_id_2) then
1424 +            skip_it = .true.
1425 +            return
1426 +         endif
1427 +      else
1428 +         if (excludesLocal(1,i) == unique_id_2) then
1429 +            if (excludesLocal(2,i) == unique_id_1) then
1430 +               skip_it = .true.
1431 +               return
1432 +            endif
1433 +         endif
1434 +      endif
1435 +   end do
1436 +  
1437 +   return
1438 + end function skipThisPair
1439  
1440 <    !! the rest of these situations can happen in all simulations:
1441 <    do i = 1, nExcludes_global      
1442 <       if ((excludesGlobal(i) == unique_id_1) .or. &
1443 <            (excludesGlobal(i) == unique_id_2)) then
1444 <          skip_it = .true.
1445 <          return
1446 <       endif
1447 <    enddo
1448 <
1449 <    do i = 1, nExcludes_local
1450 <       if (excludesLocal(1,i) == unique_id_1) then
1451 <          if (excludesLocal(2,i) == unique_id_2) then
1452 <             skip_it = .true.
1453 <             return
1454 <          endif
1455 <       else
1456 <          if (excludesLocal(1,i) == unique_id_2) then
1457 <             if (excludesLocal(2,i) == unique_id_1) then
1458 <                skip_it = .true.
1459 <                return
1460 <             endif
1461 <          endif
1462 <       endif
1463 <    end do
1464 <    
1020 <    return
1021 <  end function skipThisPair
1022 <
1023 <  function FF_UsesDirectionalAtoms() result(doesit)
1024 <    logical :: doesit
1025 <    doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1026 <         FF_uses_GB .or. FF_uses_RF
1027 <  end function FF_UsesDirectionalAtoms
1028 <  
1029 <  function FF_RequiresPrepairCalc() result(doesit)
1030 <    logical :: doesit
1031 <    doesit = FF_uses_EAM
1032 <  end function FF_RequiresPrepairCalc
1033 <  
1034 <  function FF_RequiresPostpairCalc() result(doesit)
1035 <    logical :: doesit
1036 <    doesit = FF_uses_RF
1037 <  end function FF_RequiresPostpairCalc
1038 <  
1440 > function FF_UsesDirectionalAtoms() result(doesit)
1441 >   logical :: doesit
1442 >   doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1443 >        FF_uses_GB .or. FF_uses_RF
1444 > end function FF_UsesDirectionalAtoms
1445 >
1446 > function FF_RequiresPrepairCalc() result(doesit)
1447 >   logical :: doesit
1448 >   doesit = FF_uses_EAM
1449 > end function FF_RequiresPrepairCalc
1450 >
1451 > function FF_RequiresPostpairCalc() result(doesit)
1452 >   logical :: doesit
1453 >   doesit = FF_uses_RF
1454 > end function FF_RequiresPostpairCalc
1455 >
1456 > #ifdef PROFILE
1457 > function getforcetime() result(totalforcetime)
1458 >   real(kind=dp) :: totalforcetime
1459 >   totalforcetime = forcetime
1460 > end function getforcetime
1461 > #endif
1462 >
1463 > !! This cleans componets of force arrays belonging only to fortran
1464 >
1465   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines