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 900 by chuckv, Tue Jan 6 18:54:57 2004 UTC vs.
Revision 1217 by gezelter, Tue Jun 1 21:45:22 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.45 2004-01-06 18:54:57 chuckv Exp $, $Date: 2004-01-06 18:54:57 $, $Name: not supported by cvs2svn $, $Revision: 1.45 $
7 > !! @version $Id: do_Forces.F90,v 1.68 2004-06-01 21:45:22 gezelter Exp $, $Date: 2004-06-01 21:45:22 $, $Name: not supported by cvs2svn $, $Revision: 1.68 $
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
# Line 29 | Line 31 | module do_Forces
31  
32   #define __FORTRAN90
33   #include "fForceField.h"
34 + #include "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 :: havePolicies = .false.
# Line 38 | Line 44 | module do_Forces
44    logical, save :: haveSaneForceField = .false.
45    logical, save :: FF_uses_LJ
46    logical, save :: FF_uses_sticky
47 +  logical, save :: FF_uses_charges
48    logical, save :: FF_uses_dipoles
49    logical, save :: FF_uses_RF
50    logical, save :: FF_uses_GB
51    logical, save :: FF_uses_EAM
52    logical, save :: SIM_uses_LJ
53    logical, save :: SIM_uses_sticky
54 +  logical, save :: SIM_uses_charges
55    logical, save :: SIM_uses_dipoles
56    logical, save :: SIM_uses_RF
57    logical, save :: SIM_uses_GB
# Line 52 | Line 60 | module do_Forces
60    logical, save :: SIM_requires_prepair_calc
61    logical, save :: SIM_uses_directional_atoms
62    logical, save :: SIM_uses_PBC
63 +  logical, save :: SIM_uses_molecular_cutoffs
64  
65    real(kind=dp), save :: rlist, rlistsq
66  
# Line 59 | Line 68 | module do_Forces
68    public :: do_force_loop
69    public :: setRlistDF
70  
62
71   #ifdef PROFILE
72    public :: getforcetime
73    real, save :: forceTime = 0
# Line 73 | Line 81 | module do_Forces
81       logical :: is_dp     = .false.
82       logical :: is_gb     = .false.
83       logical :: is_eam    = .false.
84 +     logical :: is_charge = .false.
85 +     real(kind=DP) :: charge = 0.0_DP
86       real(kind=DP) :: dipole_moment = 0.0_DP
87    end type Properties
88  
# Line 114 | Line 124 | contains
124      do i = 1, nAtypes
125         call getElementProperty(atypes, i, "is_LJ", thisProperty)
126         PropertyMap(i)%is_LJ = thisProperty
127 +
128 +       call getElementProperty(atypes, i, "is_Charge", thisProperty)
129 +       PropertyMap(i)%is_Charge = thisProperty
130 +      
131 +       if (thisProperty) then
132 +          call getElementProperty(atypes, i, "charge", thisDPproperty)
133 +          PropertyMap(i)%charge = thisDPproperty
134 +       endif
135 +
136         call getElementProperty(atypes, i, "is_DP", thisProperty)
137         PropertyMap(i)%is_DP = thisProperty
138  
# Line 137 | Line 156 | contains
156    subroutine setSimVariables()
157      SIM_uses_LJ = SimUsesLJ()
158      SIM_uses_sticky = SimUsesSticky()
159 +    SIM_uses_charges = SimUsesCharges()
160      SIM_uses_dipoles = SimUsesDipoles()
161      SIM_uses_RF = SimUsesRF()
162      SIM_uses_GB = SimUsesGB()
# Line 145 | Line 165 | contains
165      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
166      SIM_uses_directional_atoms = SimUsesDirectionalAtoms()
167      SIM_uses_PBC = SimUsesPBC()
168 +    !SIM_uses_molecular_cutoffs = SimUsesMolecularCutoffs()
169  
170      haveSIMvariables = .true.
171  
# Line 236 | Line 257 | contains
257    
258      FF_uses_LJ = .false.
259      FF_uses_sticky = .false.
260 +    FF_uses_charges = .false.
261      FF_uses_dipoles = .false.
262      FF_uses_GB = .false.
263      FF_uses_EAM = .false.
264      
265      call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
266      if (nMatches .gt. 0) FF_uses_LJ = .true.
267 <    
267 >
268 >    call getMatchingElementList(atypes, "is_Charge", .true., nMatches, MatchList)
269 >    if (nMatches .gt. 0) FF_uses_charges = .true.  
270 >
271      call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
272      if (nMatches .gt. 0) FF_uses_dipoles = .true.
273      
# Line 337 | Line 362 | contains
362         endif
363         haveNeighborList = .true.
364      endif
365 +
366      
367 +    
368    end subroutine init_FF
369    
370  
371    !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
372    !------------------------------------------------------------->
373 <  subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
374 <       error)
373 >  subroutine do_force_loop(q, q_group, A, u_l, f, t, tau, pot, &
374 >       do_pot_c, do_stress_c, error)
375      !! Position array provided by C, dimensioned by getNlocal
376 <    real ( kind = dp ), dimension(3,nLocal) :: q
376 >    real ( kind = dp ), dimension(3, nLocal) :: q
377 >    !! molecular center-of-mass position array
378 >    real ( kind = dp ), dimension(3, nGroups) :: q_group
379      !! Rotation Matrix for each long range particle in simulation.
380 <    real( kind = dp), dimension(9,nLocal) :: A    
380 >    real( kind = dp), dimension(9, nLocal) :: A    
381      !! Unit vectors for dipoles (lab frame)
382      real( kind = dp ), dimension(3,nLocal) :: u_l
383      !! Force array provided by C, dimensioned by getNlocal
# Line 362 | Line 391 | contains
391      logical ( kind = 2) :: do_pot_c, do_stress_c
392      logical :: do_pot
393      logical :: do_stress
394 +    logical :: in_switching_region
395   #ifdef IS_MPI
396      real( kind = DP ) :: pot_local
397 <    integer :: nrow
398 <    integer :: ncol
397 >    integer :: nAtomsInRow
398 >    integer :: nAtomsInCol
399      integer :: nprocs
400 +    integer :: nGroupsInRow
401 +    integer :: nGroupsInCol
402   #endif
403      integer :: natoms    
404      logical :: update_nlist  
405 <    integer :: i, j, jbeg, jend, jnab
405 >    integer :: i, j, jstart, jend, jnab
406 >    integer :: istart, iend
407 >    integer :: ia, jb, atom1, atom2
408      integer :: nlist
409 <    real( kind = DP ) ::  rijsq
410 <    real(kind=dp),dimension(3) :: d
409 >    real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vij
410 >    real( kind = DP ) :: sw, dswdr, swderiv, mf
411 >    real(kind=dp),dimension(3) :: d_atm, d_grp, fpair, fij
412      real(kind=dp) :: rfpot, mu_i, virial
413 <    integer :: me_i, me_j
413 >    integer :: me_i, me_j, n_in_i, n_in_j
414      logical :: is_dp_i
415      integer :: neighborListSize
416      integer :: listerror, error
417      integer :: localError
418      integer :: propPack_i, propPack_j
419 +    integer :: loopStart, loopEnd, loop
420  
421      real(kind=dp) :: listSkin = 1.0  
422 <
422 >    
423      !! initialize local variables  
424 <
424 >    
425   #ifdef IS_MPI
426      pot_local = 0.0_dp
427 <    nrow   = getNrow(plan_row)
428 <    ncol   = getNcol(plan_col)
427 >    nAtomsInRow   = getNatomsInRow(plan_atom_row)
428 >    nAtomsInCol   = getNatomsInCol(plan_atom_col)
429 >    nGroupsInRow  = getNgroupsInRow(plan_group_row)
430 >    nGroupsInCol  = getNgroupsInCol(plan_group_col)
431   #else
432      natoms = nlocal
433   #endif
434 <
434 >    
435      call doReadyCheck(localError)
436      if ( localError .ne. 0 ) then
437         call handleError("do_force_loop", "Not Initialized")
# Line 401 | Line 439 | contains
439         return
440      end if
441      call zero_work_arrays()
442 <
442 >        
443      do_pot = do_pot_c
444      do_stress = do_stress_c
445 <
445 >    
446      ! Gather all information needed by all force loops:
447      
448   #ifdef IS_MPI    
449 +    
450 +    call gather(q, q_Row, plan_atom_row_3d)
451 +    call gather(q, q_Col, plan_atom_col_3d)
452  
453 <    call gather(q,q_Row,plan_row3d)
454 <    call gather(q,q_Col,plan_col3d)
453 >    call gather(q_group, q_group_Row, plan_group_row_3d)
454 >    call gather(q_group, q_group_Col, plan_group_col_3d)
455          
456      if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
457 <       call gather(u_l,u_l_Row,plan_row3d)
458 <       call gather(u_l,u_l_Col,plan_col3d)
457 >       call gather(u_l, u_l_Row, plan_atom_row_3d)
458 >       call gather(u_l, u_l_Col, plan_atom_col_3d)
459        
460 <       call gather(A,A_Row,plan_row_rotation)
461 <       call gather(A,A_Col,plan_col_rotation)
460 >       call gather(A, A_Row, plan_atom_row_rotation)
461 >       call gather(A, A_Col, plan_atom_col_rotation)
462      endif
463      
464   #endif
465 <
466 < !! Begin force loop timing:
465 >    
466 >    !! Begin force loop timing:
467   #ifdef PROFILE
468      call cpu_time(forceTimeInitial)
469      nloops = nloops + 1
470   #endif
471 <  
471 >    
472 >    loopEnd = PAIR_LOOP
473      if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
474 <       !! See if we need to update neighbor lists
475 <       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
476 <       !! if_mpi_gather_stuff_for_prepair
477 <       !! do_prepair_loop_if_needed
478 <       !! if_mpi_scatter_stuff_from_prepair
479 <       !! if_mpi_gather_stuff_from_prepair_to_main_loop
480 <    
481 < !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
474 >       loopStart = PREPAIR_LOOP
475 >    else
476 >       loopStart = PAIR_LOOP
477 >    endif
478 >
479 >    do loop = loopStart, loopEnd
480 >
481 >       ! See if we need to update neighbor lists
482 >       ! (but only on the first time through):
483 >       if (loop .eq. loopStart) then
484   #ifdef IS_MPI
485 <    
486 <    if (update_nlist) then
485 >          call checkNeighborList(nGroupsInRow, q_group_row, listSkin, &
486 >             update_nlist)
487 > #else
488 >          call checkNeighborList(nGroups, q_group, listSkin, &
489 >             update_nlist)
490 > #endif
491 >       endif
492        
493 <       !! save current configuration, construct neighbor list,
494 <       !! and calculate forces
495 <       call saveNeighborList(nlocal, q)
493 >       if (update_nlist) then
494 >          !! save current configuration and construct neighbor list
495 > #ifdef IS_MPI
496 >          call saveNeighborList(nGroupsInRow, q_group_row)
497 > #else
498 >          call saveNeighborList(nGroups, q_group)
499 > #endif        
500 >          neighborListSize = size(list)
501 >          nlist = 0
502 >       endif
503        
504 <       neighborListSize = size(list)
505 <       nlist = 0      
506 <      
507 <       do i = 1, nrow
508 <          point(i) = nlist + 1
504 >       istart = 1
505 > #ifdef IS_MPI
506 >       iend = nGroupsInRow
507 > #else
508 >       iend = nGroups - 1
509 > #endif
510 >       outer: do i = istart, iend
511 >
512 >          if (update_nlist) point(i) = nlist + 1
513            
514 <          prepair_inner: do j = 1, ncol
515 <            
516 <             if (skipThisPair(i,j)) cycle prepair_inner
517 <            
518 <             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
519 <            
520 <             if (rijsq < rlistsq) then            
521 <                
522 <                nlist = nlist + 1
523 <                
524 <                if (nlist > neighborListSize) then
525 <                   call expandNeighborList(nlocal, listerror)
526 <                   if (listerror /= 0) then
527 <                      error = -1
528 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
529 <                      return
530 <                   end if
531 <                   neighborListSize = size(list)
532 <                endif
533 <                
534 <                list(nlist) = j
535 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot_local)                      
514 >          n_in_i = groupStartRow(i+1) - groupStartRow(i)
515 >          
516 >          if (update_nlist) then
517 > #ifdef IS_MPI
518 >             jstart = 1
519 >             jend = nGroupsInCol
520 > #else
521 >             jstart = i+1
522 >             jend = nGroups
523 > #endif
524 >          else            
525 >             jstart = point(i)
526 >             jend = point(i+1) - 1
527 >             ! make sure group i has neighbors
528 >             if (jstart .gt. jend) cycle outer
529 >          endif
530 >          
531 >          do jnab = jstart, jend
532 >             if (update_nlist) then
533 >                j = jnab
534 >             else
535 >                j = list(jnab)
536               endif
477          enddo prepair_inner
478       enddo
537  
538 <       point(nrow + 1) = nlist + 1
539 <      
540 <    else  !! (of update_check)
483 <
484 <       ! use the list to find the neighbors
485 <       do i = 1, nrow
486 <          JBEG = POINT(i)
487 <          JEND = POINT(i+1) - 1
488 <          ! check thiat molecule i has neighbors
489 <          if (jbeg .le. jend) then
490 <            
491 <             do jnab = jbeg, jend
492 <                j = list(jnab)
493 <
494 <                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
495 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
496 <                     u_l, A, f, t, pot_local)
497 <
498 <             enddo
499 <          endif
500 <       enddo
501 <    endif
502 <    
538 > #ifdef IS_MPI
539 >             call get_interatomic_vector(q_group_Row(:,i), &
540 >                  q_group_Col(:,j), d_grp, rgrpsq)
541   #else
542 <    
543 <    if (update_nlist) then
544 <      
507 <       ! save current configuration, contruct neighbor list,
508 <       ! and calculate forces
509 <       call saveNeighborList(natoms, q)
510 <      
511 <       neighborListSize = size(list)
512 <  
513 <       nlist = 0
542 >             call get_interatomic_vector(q_group(:,i), &
543 >                  q_group(:,j), d_grp, rgrpsq)
544 > #endif
545  
546 <       do i = 1, natoms-1
547 <          point(i) = nlist + 1
548 <          
549 <          prepair_inner: do j = i+1, natoms
550 <            
551 <             if (skipThisPair(i,j))  cycle prepair_inner
552 <                          
553 <             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
554 <          
555 <
556 <             if (rijsq < rlistsq) then
557 <
558 <          
559 <                nlist = nlist + 1
560 <              
561 <                if (nlist > neighborListSize) then
562 <                   call expandNeighborList(natoms, listerror)
563 <                   if (listerror /= 0) then
564 <                      error = -1
534 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
535 <                      return
536 <                   end if
537 <                   neighborListSize = size(list)
546 >             if (rgrpsq < rlistsq) then
547 >                if (update_nlist) then
548 >                   nlist = nlist + 1
549 >                  
550 >                   if (nlist > neighborListSize) then
551 > #ifdef IS_MPI                
552 >                      call expandNeighborList(nGroupsInRow, listerror)
553 > #else
554 >                      call expandNeighborList(nGroups, listerror)
555 > #endif
556 >                      if (listerror /= 0) then
557 >                         error = -1
558 >                         write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
559 >                         return
560 >                      end if
561 >                      neighborListSize = size(list)
562 >                   endif
563 >                  
564 >                   list(nlist) = j
565                  endif
566                  
567 <                list(nlist) = j
567 >                if (loop .eq. PAIR_LOOP) then
568 >                   vij = 0.0d0
569 >                   fij(1:3) = 0.0d0
570 >                endif
571                  
572 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
573 <                        u_l, A, f, t, pot)
572 >                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
573 >                     in_switching_region)
574                  
575 <             endif
576 <          enddo prepair_inner
577 <       enddo
578 <      
579 <       point(natoms) = nlist + 1
580 <      
581 <    else !! (update)
582 <  
583 <       ! use the list to find the neighbors
584 <       do i = 1, natoms-1
585 <          JBEG = POINT(i)
556 <          JEND = POINT(i+1) - 1
557 <          ! check thiat molecule i has neighbors
558 <          if (jbeg .le. jend) then
559 <            
560 <             do jnab = jbeg, jend
561 <                j = list(jnab)
562 <
563 <                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
564 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
565 <                     u_l, A, f, t, pot)
566 <
567 <             enddo
568 <          endif
569 <       enddo
570 <    endif    
571 < #endif
572 <    !! Do rest of preforce calculations
573 <    !! do necessary preforce calculations  
574 <    call do_preforce(nlocal,pot)
575 <   ! we have already updated the neighbor list set it to false...
576 <   update_nlist = .false.
577 <    else
578 <       !! See if we need to update neighbor lists for non pre-pair
579 <       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
580 <    endif
581 <
582 <
583 <
584 <
585 <
586 < !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>>>>>>>>>>>>>>>>
575 >                n_in_j = groupStartCol(j+1) - groupStartCol(j)
576 >                
577 >                do ia = groupStartRow(i), groupStartRow(i+1)-1
578 >                  
579 >                   atom1 = groupListRow(ia)
580 >                  
581 >                   inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
582 >                      
583 >                      atom2 = groupListCol(jb)
584 >                      
585 >                      if (skipThisPair(atom1, atom2)) cycle inner
586  
587 <
588 <
589 <
590 <  
587 >                      if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
588 >                         d_atm(1:3) = d_grp(1:3)
589 >                         ratmsq = rgrpsq
590 >                      else
591   #ifdef IS_MPI
592 <    
593 <    if (update_nlist) then
594 <       !! save current configuration, construct neighbor list,
595 <       !! and calculate forces
596 <       call saveNeighborList(nlocal, q)
597 <      
598 <       neighborListSize = size(list)
600 <       nlist = 0      
601 <      
602 <       do i = 1, nrow
592 >                         call get_interatomic_vector(q_Row(:,atom1), &
593 >                              q_Col(:,atom2), d_atm, ratmsq)
594 > #else
595 >                         call get_interatomic_vector(q(:,atom1), &
596 >                              q(:,atom2), d_atm, ratmsq)
597 > #endif
598 >                      endif
599  
600 <          point(i) = nlist + 1
601 <          
602 <          inner: do j = 1, ncol
603 <            
604 <             if (skipThisPair(i,j)) cycle inner
609 <            
610 <             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
611 <            
612 <             if (rijsq < rlistsq) then            
613 <                
614 <                nlist = nlist + 1
615 <                
616 <                if (nlist > neighborListSize) then
617 <                   call expandNeighborList(nlocal, listerror)
618 <                   if (listerror /= 0) then
619 <                      error = -1
620 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
621 <                      return
622 <                   end if
623 <                   neighborListSize = size(list)
624 <                endif
625 <                
626 <                list(nlist) = j
627 <                                
628 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
629 <                     u_l, A, f, t, pot_local)
630 <                
631 <             endif
632 <          enddo inner
633 <       enddo
634 <
635 <       point(nrow + 1) = nlist + 1
636 <      
637 <    else  !! (of update_check)
638 <
639 <       ! use the list to find the neighbors
640 <       do i = 1, nrow
641 <          JBEG = POINT(i)
642 <          JEND = POINT(i+1) - 1
643 <          ! check thiat molecule i has neighbors
644 <          if (jbeg .le. jend) then
645 <            
646 <             do jnab = jbeg, jend
647 <                j = list(jnab)
648 <
649 <                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
650 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
651 <                     u_l, A, f, t, pot_local)
652 <
653 <             enddo
654 <          endif
655 <       enddo
656 <    endif
657 <    
600 >                      if (loop .eq. PREPAIR_LOOP) then
601 > #ifdef IS_MPI                      
602 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
603 >                              rgrpsq, d_grp, do_pot, do_stress, &
604 >                              u_l, A, f, t, pot_local)
605   #else
606 <    
607 <    if (update_nlist) then
606 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
607 >                              rgrpsq, d_grp, do_pot, do_stress, &
608 >                              u_l, A, f, t, pot)
609 > #endif                                              
610 >                      else
611 > #ifdef IS_MPI                      
612 >                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
613 >                              do_pot, &
614 >                              u_l, A, f, t, pot_local, vpair, fpair)
615 > #else
616 >                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
617 >                              do_pot,  &
618 >                              u_l, A, f, t, pot, vpair, fpair)
619 > #endif
620  
621 <       ! save current configuration, contruct neighbor list,
622 <       ! and calculate forces
623 <       call saveNeighborList(natoms, q)
624 <      
625 <       neighborListSize = size(list)
667 <  
668 <       nlist = 0
669 <      
670 <       do i = 1, natoms-1
671 <          point(i) = nlist + 1
672 <          
673 <          inner: do j = i+1, natoms
674 <            
675 <             if (skipThisPair(i,j))  cycle inner
676 <                          
677 <             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
678 <          
679 <
680 <             if (rijsq < rlistsq) then
621 >                         vij = vij + vpair
622 >                         fij(1:3) = fij(1:3) + fpair(1:3)
623 >                      endif
624 >                   enddo inner
625 >                enddo
626                  
627 <                nlist = nlist + 1
628 <              
629 <                if (nlist > neighborListSize) then
630 <                   call expandNeighborList(natoms, listerror)
631 <                   if (listerror /= 0) then
632 <                      error = -1
633 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
634 <                      return
635 <                   end if
636 <                   neighborListSize = size(list)
627 >                if (loop .eq. PAIR_LOOP) then
628 >                   if (in_switching_region) then
629 >                      swderiv = vij*dswdr/rgrp
630 >                      fij(1) = fij(1) + swderiv*d_grp(1)
631 >                      fij(2) = fij(2) + swderiv*d_grp(2)
632 >                      fij(3) = fij(3) + swderiv*d_grp(3)
633 >                      
634 >                      do ia=groupStartRow(i), groupStartRow(i+1)-1
635 >                         atom1=groupListRow(ia)
636 >                         mf = mfactRow(atom1)
637 > #ifdef IS_MPI
638 >                         f_Row(1,atom1) = f_Row(1,atom1) + swderiv*d_grp(1)*mf
639 >                         f_Row(2,atom1) = f_Row(2,atom1) + swderiv*d_grp(2)*mf
640 >                         f_Row(3,atom1) = f_Row(3,atom1) + swderiv*d_grp(3)*mf
641 > #else
642 >                         f(1,atom1) = f(1,atom1) + swderiv*d_grp(1)*mf
643 >                         f(2,atom1) = f(2,atom1) + swderiv*d_grp(2)*mf
644 >                         f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
645 > #endif
646 >                      enddo
647 >                      
648 >                      do jb=groupStartCol(j), groupStartCol(j+1)-1
649 >                         atom2=groupListCol(jb)
650 >                         mf = mfactCol(atom2)
651 > #ifdef IS_MPI
652 >                         f_Col(1,atom2) = f_Col(1,atom2) - swderiv*d_grp(1)*mf
653 >                         f_Col(2,atom2) = f_Col(2,atom2) - swderiv*d_grp(2)*mf
654 >                         f_Col(3,atom2) = f_Col(3,atom2) - swderiv*d_grp(3)*mf
655 > #else
656 >                         f(1,atom2) = f(1,atom2) - swderiv*d_grp(1)*mf
657 >                         f(2,atom2) = f(2,atom2) - swderiv*d_grp(2)*mf
658 >                         f(3,atom2) = f(3,atom2) - swderiv*d_grp(3)*mf
659 > #endif
660 >                      enddo
661 >                   endif
662 >                  
663 >                   if (do_stress) call add_stress_tensor(d_grp, fij)
664                  endif
665 <                
666 <                list(nlist) = j
667 <                
696 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
697 <                        u_l, A, f, t, pot)
698 <                
699 <             endif
700 <          enddo inner
701 <       enddo
665 >             end if
666 >          enddo
667 >       enddo outer
668        
669 <       point(natoms) = nlist + 1
670 <      
671 <    else !! (update)
672 <      
673 <       ! use the list to find the neighbors
674 <       do i = 1, natoms-1
675 <          JBEG = POINT(i)
676 <          JEND = POINT(i+1) - 1
677 <          ! check thiat molecule i has neighbors
678 <          if (jbeg .le. jend) then
679 <            
714 <             do jnab = jbeg, jend
715 <                j = list(jnab)
716 <
717 <                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
718 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
719 <                     u_l, A, f, t, pot)
720 <
721 <             enddo
669 >       if (update_nlist) then
670 > #ifdef IS_MPI
671 >          point(nGroupsInRow + 1) = nlist + 1
672 > #else
673 >          point(nGroups) = nlist + 1
674 > #endif
675 >          if (loop .eq. PREPAIR_LOOP) then
676 >             ! we just did the neighbor list update on the first
677 >             ! pass, so we don't need to do it
678 >             ! again on the second pass
679 >             update_nlist = .false.                              
680            endif
681 <       enddo
682 <    endif
681 >       endif
682 >            
683 >       if (loop .eq. PREPAIR_LOOP) then
684 >          call do_preforce(nlocal, pot)
685 >       endif
686 >      
687 >    enddo
688      
689 < #endif
727 <    
728 <    ! phew, done with main loop.
729 <
730 < !! Do timing
689 >    !! Do timing
690   #ifdef PROFILE
691      call cpu_time(forceTimeFinal)
692      forceTime = forceTime + forceTimeFinal - forceTimeInitial
693 < #endif
694 <
736 <
693 > #endif    
694 >    
695   #ifdef IS_MPI
696      !!distribute forces
697 <  
697 >    
698      f_temp = 0.0_dp
699 <    call scatter(f_Row,f_temp,plan_row3d)
699 >    call scatter(f_Row,f_temp,plan_atom_row_3d)
700      do i = 1,nlocal
701         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
702      end do
703 <
703 >    
704      f_temp = 0.0_dp
705 <    call scatter(f_Col,f_temp,plan_col3d)
705 >    call scatter(f_Col,f_temp,plan_atom_col_3d)
706      do i = 1,nlocal
707         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
708      end do
709      
710      if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
711         t_temp = 0.0_dp
712 <       call scatter(t_Row,t_temp,plan_row3d)
712 >       call scatter(t_Row,t_temp,plan_atom_row_3d)
713         do i = 1,nlocal
714            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
715         end do
716         t_temp = 0.0_dp
717 <       call scatter(t_Col,t_temp,plan_col3d)
717 >       call scatter(t_Col,t_temp,plan_atom_col_3d)
718        
719         do i = 1,nlocal
720            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
# Line 765 | Line 723 | contains
723      
724      if (do_pot) then
725         ! scatter/gather pot_row into the members of my column
726 <       call scatter(pot_Row, pot_Temp, plan_row)
727 <
726 >       call scatter(pot_Row, pot_Temp, plan_atom_row)
727 >      
728         ! scatter/gather pot_local into all other procs
729         ! add resultant to get total pot
730         do i = 1, nlocal
# Line 774 | Line 732 | contains
732         enddo
733        
734         pot_Temp = 0.0_DP
735 <
736 <       call scatter(pot_Col, pot_Temp, plan_col)
735 >      
736 >       call scatter(pot_Col, pot_Temp, plan_atom_col)
737         do i = 1, nlocal
738            pot_local = pot_local + pot_Temp(i)
739         enddo
740 <
741 <    endif    
740 >      
741 >    endif
742   #endif
743 <
743 >    
744      if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
745        
746         if (FF_uses_RF .and. SIM_uses_RF) then
747            
748   #ifdef IS_MPI
749 <          call scatter(rf_Row,rf,plan_row3d)
750 <          call scatter(rf_Col,rf_Temp,plan_col3d)
749 >          call scatter(rf_Row,rf,plan_atom_row_3d)
750 >          call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
751            do i = 1,nlocal
752               rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
753            end do
754   #endif
755            
756            do i = 1, nLocal
757 <
757 >            
758               rfpot = 0.0_DP
759   #ifdef IS_MPI
760               me_i = atid_row(i)
761   #else
762               me_i = atid(i)
763   #endif
764 <
764 >            
765               if (PropertyMap(me_i)%is_DP) then
766 <
766 >                
767                  mu_i = PropertyMap(me_i)%dipole_moment
768 <
768 >                
769                  !! The reaction field needs to include a self contribution
770                  !! to the field:
771                  call accumulate_self_rf(i, mu_i, u_l)
# Line 824 | Line 782 | contains
782            enddo
783         endif
784      endif
785 <
786 <
785 >    
786 >    
787   #ifdef IS_MPI
788 <
788 >    
789      if (do_pot) then
790         pot = pot + pot_local
791         !! we assume the c code will do the allreduce to get the total potential
792         !! we could do it right here if we needed to...
793      endif
794 <
794 >    
795      if (do_stress) then
796 <      call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
796 >       call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
797              mpi_comm_world,mpi_err)
798         call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
799              mpi_comm_world,mpi_err)
800      endif
801 <
801 >    
802   #else
803 <
803 >    
804      if (do_stress) then
805         tau = tau_Temp
806         virial = virial_Temp
807      endif
808      
809   #endif
810 <    
853 <    
854 <    
810 >      
811    end subroutine do_force_loop
812 <
813 <  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
814 <
815 <    real( kind = dp ) :: pot
812 >  
813 >  subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
814 >       u_l, A, f, t, pot, vpair, fpair)
815 >
816 >    real( kind = dp ) :: pot, vpair, sw
817 >    real( kind = dp ), dimension(3) :: fpair
818 >    real( kind = dp ), dimension(nLocal)   :: mfact
819      real( kind = dp ), dimension(3,nLocal) :: u_l
820 <    real (kind=dp), dimension(9,nLocal) :: A
821 <    real (kind=dp), dimension(3,nLocal) :: f
822 <    real (kind=dp), dimension(3,nLocal) :: t
820 >    real( kind = dp ), dimension(9,nLocal) :: A
821 >    real( kind = dp ), dimension(3,nLocal) :: f
822 >    real( kind = dp ), dimension(3,nLocal) :: t
823  
824 <    logical, intent(inout) :: do_pot, do_stress
824 >    logical, intent(inout) :: do_pot
825      integer, intent(in) :: i, j
826 <    real ( kind = dp ), intent(inout)    :: rijsq
826 >    real ( kind = dp ), intent(inout) :: rijsq
827      real ( kind = dp )                :: r
828      real ( kind = dp ), intent(inout) :: d(3)
870    logical :: is_LJ_i, is_LJ_j
871    logical :: is_DP_i, is_DP_j
872    logical :: is_GB_i, is_GB_j
873    logical :: is_EAM_i,is_EAM_j
874    logical :: is_Sticky_i, is_Sticky_j
829      integer :: me_i, me_j
830 <    integer :: propPack_i
877 <    integer :: propPack_j
830 >
831      r = sqrt(rijsq)
832 +    vpair = 0.0d0
833 +    fpair(1:3) = 0.0d0
834  
835   #ifdef IS_MPI
881    if (tagRow(i) .eq. tagColumn(j)) then
882       write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
883    endif
884
836      me_i = atid_row(i)
837      me_j = atid_col(j)
887
838   #else
889
839      me_i = atid(i)
840      me_j = atid(j)
892
841   #endif
842      
843      if (FF_uses_LJ .and. SIM_uses_LJ) then
844 <
845 <       if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) &
846 <            call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
847 <
844 >      
845 >       if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
846 >          call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
847 >       endif
848 >      
849      endif
850 <
850 >    
851 >    if (FF_uses_charges .and. SIM_uses_charges) then
852 >      
853 >       if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
854 >          call do_charge_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
855 >       endif
856 >      
857 >    endif
858 >    
859      if (FF_uses_dipoles .and. SIM_uses_dipoles) then
860        
861         if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
862 <          call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
863 <               do_pot, do_stress)
862 >          call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
863 >               do_pot)
864            if (FF_uses_RF .and. SIM_uses_RF) then
865 <             call accumulate_rf(i, j, r, u_l)
866 <             call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
867 <          endif
911 <          
865 >             call accumulate_rf(i, j, r, u_l, sw)
866 >             call rf_correct_forces(i, j, d, r, u_l, sw, f, fpair)
867 >          endif          
868         endif
869 +
870      endif
871  
872      if (FF_uses_Sticky .and. SIM_uses_sticky) then
873  
874         if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
875 <          call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
876 <               do_pot, do_stress)
875 >          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, A, f, t, &
876 >               do_pot)
877         endif
878 +
879      endif
880  
881  
882      if (FF_uses_GB .and. SIM_uses_GB) then
883        
884         if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
885 <          call do_gb_pair(i, j, d, r, rijsq, u_l, pot, f, t, &
886 <               do_pot, do_stress)          
885 >          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
886 >               do_pot)
887         endif
888  
889      endif
890 <    
891 <
892 <  
893 <   if (FF_uses_EAM .and. SIM_uses_EAM) then
894 <      
895 <      if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
896 <         call do_eam_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
897 <      endif
898 <
899 <   endif
942 <
890 >      
891 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
892 >      
893 >       if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
894 >          call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
895 >               do_pot)
896 >       endif
897 >      
898 >    endif
899 >    
900    end subroutine do_pair
901  
902 +  subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
903 +       do_pot, do_stress, u_l, A, f, t, pot)
904  
905 <
947 <  subroutine do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
948 <   real( kind = dp ) :: pot
905 >   real( kind = dp ) :: pot, sw
906     real( kind = dp ), dimension(3,nLocal) :: u_l
907     real (kind=dp), dimension(9,nLocal) :: A
908     real (kind=dp), dimension(3,nLocal) :: f
# Line 953 | Line 910 | contains
910    
911     logical, intent(inout) :: do_pot, do_stress
912     integer, intent(in) :: i, j
913 <   real ( kind = dp ), intent(inout)    :: rijsq
914 <   real ( kind = dp )                :: r
915 <   real ( kind = dp ), intent(inout) :: d(3)
913 >   real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
914 >   real ( kind = dp )                :: r, rc
915 >   real ( kind = dp ), intent(inout) :: d(3), dc(3)
916    
917     logical :: is_EAM_i, is_EAM_j
918    
919     integer :: me_i, me_j
920    
964   r = sqrt(rijsq)
965  
921  
922 < #ifdef IS_MPI
923 <   if (tagRow(i) .eq. tagColumn(j)) then
924 <      write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
925 <   endif
922 >    r = sqrt(rijsq)
923 >    if (SIM_uses_molecular_cutoffs) then
924 >       rc = sqrt(rcijsq)
925 >    else
926 >       rc = r
927 >    endif
928    
929 +
930 + #ifdef IS_MPI  
931     me_i = atid_row(i)
932 <   me_j = atid_col(j)
933 <  
975 < #else
976 <  
932 >   me_j = atid_col(j)  
933 > #else  
934     me_i = atid(i)
935 <   me_j = atid(j)
979 <  
935 >   me_j = atid(j)  
936   #endif
937 <    
937 >  
938     if (FF_uses_EAM .and. SIM_uses_EAM) then
939 <
939 >      
940        if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
941             call calc_EAM_prepair_rho(i, j, d, r, rijsq )
942 <
942 >      
943     endif
944    
945   end subroutine do_prepair
990
991
992
993
994  subroutine do_preforce(nlocal,pot)
995    integer :: nlocal
996    real( kind = dp ) :: pot
997
998    if (FF_uses_EAM .and. SIM_uses_EAM) then
999       call calc_EAM_preforce_Frho(nlocal,pot)
1000    endif
1001
1002
1003  end subroutine do_preforce
1004  
1005  
1006  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1007    
1008    real (kind = dp), dimension(3) :: q_i
1009    real (kind = dp), dimension(3) :: q_j
1010    real ( kind = dp ), intent(out) :: r_sq
1011    real( kind = dp ) :: d(3), scaled(3)
1012    integer i
1013
1014    d(1:3) = q_j(1:3) - q_i(1:3)
1015
1016    ! Wrap back into periodic box if necessary
1017    if ( SIM_uses_PBC ) then
1018      
1019       if( .not.boxIsOrthorhombic ) then
1020          ! calc the scaled coordinates.
1021          
1022          scaled = matmul(HmatInv, d)
1023          
1024          ! wrap the scaled coordinates
1025
1026          scaled = scaled  - anint(scaled)
1027          
1028
1029          ! calc the wrapped real coordinates from the wrapped scaled
1030          ! coordinates
1031
1032          d = matmul(Hmat,scaled)
1033
1034       else
1035          ! calc the scaled coordinates.
1036          
1037          do i = 1, 3
1038             scaled(i) = d(i) * HmatInv(i,i)
1039            
1040             ! wrap the scaled coordinates
1041            
1042             scaled(i) = scaled(i) - anint(scaled(i))
1043            
1044             ! calc the wrapped real coordinates from the wrapped scaled
1045             ! coordinates
1046
1047             d(i) = scaled(i)*Hmat(i,i)
1048          enddo
1049       endif
1050      
1051    endif
1052    
1053    r_sq = dot_product(d,d)
1054    
1055  end subroutine get_interatomic_vector
1056  
1057  subroutine zero_work_arrays()
1058    
1059 #ifdef IS_MPI
1060
1061    q_Row = 0.0_dp
1062    q_Col = 0.0_dp  
1063    
1064    u_l_Row = 0.0_dp
1065    u_l_Col = 0.0_dp
1066    
1067    A_Row = 0.0_dp
1068    A_Col = 0.0_dp
1069    
1070    f_Row = 0.0_dp
1071    f_Col = 0.0_dp
1072    f_Temp = 0.0_dp
1073      
1074    t_Row = 0.0_dp
1075    t_Col = 0.0_dp
1076    t_Temp = 0.0_dp
946  
1078    pot_Row = 0.0_dp
1079    pot_Col = 0.0_dp
1080    pot_Temp = 0.0_dp
1081
1082    rf_Row = 0.0_dp
1083    rf_Col = 0.0_dp
1084    rf_Temp = 0.0_dp
1085
1086 #endif
1087
947  
948 <    if (FF_uses_EAM .and. SIM_uses_EAM) then
949 <       call clean_EAM()
950 <    endif
951 <
952 <
953 <
954 <
955 <
956 <    rf = 0.0_dp
957 <    tau_Temp = 0.0_dp
958 <    virial_Temp = 0.0_dp
959 <  end subroutine zero_work_arrays
960 <  
961 <  function skipThisPair(atom1, atom2) result(skip_it)
962 <    integer, intent(in) :: atom1
963 <    integer, intent(in), optional :: atom2
964 <    logical :: skip_it
965 <    integer :: unique_id_1, unique_id_2
966 <    integer :: me_i,me_j
967 <    integer :: i
968 <
969 <    skip_it = .false.
970 <    
971 <    !! there are a number of reasons to skip a pair or a particle
972 <    !! mostly we do this to exclude atoms who are involved in short
973 <    !! range interactions (bonds, bends, torsions), but we also need
974 <    !! to exclude some overcounted interactions that result from
975 <    !! the parallel decomposition
976 <    
977 < #ifdef IS_MPI
978 <    !! in MPI, we have to look up the unique IDs for each atom
979 <    unique_id_1 = tagRow(atom1)
980 < #else
981 <    !! in the normal loop, the atom numbers are unique
982 <    unique_id_1 = atom1
983 < #endif
984 <
985 <    !! We were called with only one atom, so just check the global exclude
986 <    !! list for this atom
987 <    if (.not. present(atom2)) then
988 <       do i = 1, nExcludes_global
989 <          if (excludesGlobal(i) == unique_id_1) then
990 <             skip_it = .true.
991 <             return
992 <          end if
993 <       end do
994 <       return
995 <    end if
996 <    
997 < #ifdef IS_MPI
998 <    unique_id_2 = tagColumn(atom2)
999 < #else
1000 <    unique_id_2 = atom2
1001 < #endif
948 > subroutine do_preforce(nlocal,pot)
949 >   integer :: nlocal
950 >   real( kind = dp ) :: pot
951 >  
952 >   if (FF_uses_EAM .and. SIM_uses_EAM) then
953 >      call calc_EAM_preforce_Frho(nlocal,pot)
954 >   endif
955 >  
956 >  
957 > end subroutine do_preforce
958 >
959 >
960 > subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
961 >  
962 >   real (kind = dp), dimension(3) :: q_i
963 >   real (kind = dp), dimension(3) :: q_j
964 >   real ( kind = dp ), intent(out) :: r_sq
965 >   real( kind = dp ) :: d(3), scaled(3)
966 >   integer i
967 >  
968 >   d(1:3) = q_j(1:3) - q_i(1:3)
969 >  
970 >   ! Wrap back into periodic box if necessary
971 >   if ( SIM_uses_PBC ) then
972 >      
973 >      if( .not.boxIsOrthorhombic ) then
974 >         ! calc the scaled coordinates.
975 >        
976 >         scaled = matmul(HmatInv, d)
977 >        
978 >         ! wrap the scaled coordinates
979 >        
980 >         scaled = scaled  - anint(scaled)
981 >        
982 >        
983 >         ! calc the wrapped real coordinates from the wrapped scaled
984 >         ! coordinates
985 >        
986 >         d = matmul(Hmat,scaled)
987 >        
988 >      else
989 >         ! calc the scaled coordinates.
990 >        
991 >         do i = 1, 3
992 >            scaled(i) = d(i) * HmatInv(i,i)
993 >            
994 >            ! wrap the scaled coordinates
995 >            
996 >            scaled(i) = scaled(i) - anint(scaled(i))
997 >            
998 >            ! calc the wrapped real coordinates from the wrapped scaled
999 >            ! coordinates
1000 >            
1001 >            d(i) = scaled(i)*Hmat(i,i)
1002 >         enddo
1003 >      endif
1004 >      
1005 >   endif
1006 >  
1007 >   r_sq = dot_product(d,d)
1008 >  
1009 > end subroutine get_interatomic_vector
1010 >
1011 > subroutine zero_work_arrays()
1012 >  
1013 > #ifdef IS_MPI
1014 >  
1015 >   q_Row = 0.0_dp
1016 >   q_Col = 0.0_dp
1017  
1018 +   q_group_Row = 0.0_dp
1019 +   q_group_Col = 0.0_dp  
1020 +  
1021 +   u_l_Row = 0.0_dp
1022 +   u_l_Col = 0.0_dp
1023 +  
1024 +   A_Row = 0.0_dp
1025 +   A_Col = 0.0_dp
1026 +  
1027 +   f_Row = 0.0_dp
1028 +   f_Col = 0.0_dp
1029 +   f_Temp = 0.0_dp
1030 +  
1031 +   t_Row = 0.0_dp
1032 +   t_Col = 0.0_dp
1033 +   t_Temp = 0.0_dp
1034 +  
1035 +   pot_Row = 0.0_dp
1036 +   pot_Col = 0.0_dp
1037 +   pot_Temp = 0.0_dp
1038 +  
1039 +   rf_Row = 0.0_dp
1040 +   rf_Col = 0.0_dp
1041 +   rf_Temp = 0.0_dp
1042 +  
1043 + #endif
1044 +
1045 +   if (FF_uses_EAM .and. SIM_uses_EAM) then
1046 +      call clean_EAM()
1047 +   endif
1048 +  
1049 +   rf = 0.0_dp
1050 +   tau_Temp = 0.0_dp
1051 +   virial_Temp = 0.0_dp
1052 + end subroutine zero_work_arrays
1053 +
1054 + function skipThisPair(atom1, atom2) result(skip_it)
1055 +   integer, intent(in) :: atom1
1056 +   integer, intent(in), optional :: atom2
1057 +   logical :: skip_it
1058 +   integer :: unique_id_1, unique_id_2
1059 +   integer :: me_i,me_j
1060 +   integer :: i
1061 +  
1062 +   skip_it = .false.
1063 +  
1064 +   !! there are a number of reasons to skip a pair or a particle
1065 +   !! mostly we do this to exclude atoms who are involved in short
1066 +   !! range interactions (bonds, bends, torsions), but we also need
1067 +   !! to exclude some overcounted interactions that result from
1068 +   !! the parallel decomposition
1069 +  
1070   #ifdef IS_MPI
1071 <    !! this situation should only arise in MPI simulations
1072 <    if (unique_id_1 == unique_id_2) then
1073 <       skip_it = .true.
1074 <       return
1075 <    end if
1150 <    
1151 <    !! this prevents us from doing the pair on multiple processors
1152 <    if (unique_id_1 < unique_id_2) then
1153 <       if (mod(unique_id_1 + unique_id_2,2) == 0) then
1154 <          skip_it = .true.
1155 <          return
1156 <       endif
1157 <    else                
1158 <       if (mod(unique_id_1 + unique_id_2,2) == 1) then
1159 <          skip_it = .true.
1160 <          return
1161 <       endif
1162 <    endif
1071 >   !! in MPI, we have to look up the unique IDs for each atom
1072 >   unique_id_1 = AtomRowToGlobal(atom1)
1073 > #else
1074 >   !! in the normal loop, the atom numbers are unique
1075 >   unique_id_1 = atom1
1076   #endif
1077 +  
1078 +   !! We were called with only one atom, so just check the global exclude
1079 +   !! list for this atom
1080 +   if (.not. present(atom2)) then
1081 +      do i = 1, nExcludes_global
1082 +         if (excludesGlobal(i) == unique_id_1) then
1083 +            skip_it = .true.
1084 +            return
1085 +         end if
1086 +      end do
1087 +      return
1088 +   end if
1089 +  
1090 + #ifdef IS_MPI
1091 +   unique_id_2 = AtomColToGlobal(atom2)
1092 + #else
1093 +   unique_id_2 = atom2
1094 + #endif
1095 +  
1096 + #ifdef IS_MPI
1097 +   !! this situation should only arise in MPI simulations
1098 +   if (unique_id_1 == unique_id_2) then
1099 +      skip_it = .true.
1100 +      return
1101 +   end if
1102 +  
1103 +   !! this prevents us from doing the pair on multiple processors
1104 +   if (unique_id_1 < unique_id_2) then
1105 +      if (mod(unique_id_1 + unique_id_2,2) == 0) then
1106 +         skip_it = .true.
1107 +         return
1108 +      endif
1109 +   else                
1110 +      if (mod(unique_id_1 + unique_id_2,2) == 1) then
1111 +         skip_it = .true.
1112 +         return
1113 +      endif
1114 +   endif
1115 + #endif
1116 +  
1117 +   !! the rest of these situations can happen in all simulations:
1118 +   do i = 1, nExcludes_global      
1119 +      if ((excludesGlobal(i) == unique_id_1) .or. &
1120 +           (excludesGlobal(i) == unique_id_2)) then
1121 +         skip_it = .true.
1122 +         return
1123 +      endif
1124 +   enddo
1125 +  
1126 +   do i = 1, nSkipsForAtom(atom1)
1127 +      if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1128 +         skip_it = .true.
1129 +         return
1130 +      endif
1131 +   end do
1132 +  
1133 +   return
1134 + end function skipThisPair
1135  
1136 <    !! the rest of these situations can happen in all simulations:
1137 <    do i = 1, nExcludes_global      
1138 <       if ((excludesGlobal(i) == unique_id_1) .or. &
1139 <            (excludesGlobal(i) == unique_id_2)) then
1140 <          skip_it = .true.
1141 <          return
1142 <       endif
1143 <    enddo
1144 <
1145 <    do i = 1, nExcludes_local
1146 <       if (excludesLocal(1,i) == unique_id_1) then
1147 <          if (excludesLocal(2,i) == unique_id_2) then
1148 <             skip_it = .true.
1149 <             return
1150 <          endif
1151 <       else
1181 <          if (excludesLocal(1,i) == unique_id_2) then
1182 <             if (excludesLocal(2,i) == unique_id_1) then
1183 <                skip_it = .true.
1184 <                return
1185 <             endif
1186 <          endif
1187 <       endif
1188 <    end do
1189 <    
1190 <    return
1191 <  end function skipThisPair
1192 <
1193 <  function FF_UsesDirectionalAtoms() result(doesit)
1194 <    logical :: doesit
1195 <    doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1196 <         FF_uses_GB .or. FF_uses_RF
1197 <  end function FF_UsesDirectionalAtoms
1198 <  
1199 <  function FF_RequiresPrepairCalc() result(doesit)
1200 <    logical :: doesit
1201 <    doesit = FF_uses_EAM
1202 <  end function FF_RequiresPrepairCalc
1203 <  
1204 <  function FF_RequiresPostpairCalc() result(doesit)
1205 <    logical :: doesit
1206 <    doesit = FF_uses_RF
1207 <  end function FF_RequiresPostpairCalc
1208 <  
1136 > function FF_UsesDirectionalAtoms() result(doesit)
1137 >   logical :: doesit
1138 >   doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1139 >        FF_uses_GB .or. FF_uses_RF
1140 > end function FF_UsesDirectionalAtoms
1141 >
1142 > function FF_RequiresPrepairCalc() result(doesit)
1143 >   logical :: doesit
1144 >   doesit = FF_uses_EAM
1145 > end function FF_RequiresPrepairCalc
1146 >
1147 > function FF_RequiresPostpairCalc() result(doesit)
1148 >   logical :: doesit
1149 >   doesit = FF_uses_RF
1150 > end function FF_RequiresPostpairCalc
1151 >
1152   #ifdef PROFILE
1153 <  function getforcetime() result(totalforcetime)
1154 <    real(kind=dp) :: totalforcetime
1155 <    totalforcetime = forcetime
1156 <  end function getforcetime
1153 > function getforcetime() result(totalforcetime)
1154 >   real(kind=dp) :: totalforcetime
1155 >   totalforcetime = forcetime
1156 > end function getforcetime
1157   #endif
1158 +
1159 + !! This cleans componets of force arrays belonging only to fortran
1160  
1161 < !! This cleans componets of force arrays belonging only to fortran
1162 <
1161 > subroutine add_stress_tensor(dpair, fpair)
1162 >  
1163 >   real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1164 >  
1165 >   ! because the d vector is the rj - ri vector, and
1166 >   ! because fx, fy, fz are the force on atom i, we need a
1167 >   ! negative sign here:  
1168 >  
1169 >   tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1170 >   tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1171 >   tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1172 >   tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1173 >   tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1174 >   tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1175 >   tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1176 >   tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1177 >   tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1178 >  
1179 >   virial_Temp = virial_Temp + &
1180 >        (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1181 >  
1182 > end subroutine add_stress_tensor
1183 >
1184   end module do_Forces
1185 +

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines