ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/doForces.F90 (file contents):
Revision 2309 by chrisfen, Sun Sep 18 20:45:38 2005 UTC vs.
Revision 2432 by chuckv, Tue Nov 15 16:01:06 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.46 2005-09-18 20:45:38 chrisfen Exp $, $Date: 2005-09-18 20:45:38 $, $Name: not supported by cvs2svn $, $Revision: 1.46 $
48 > !! @version $Id: doForces.F90,v 1.68 2005-11-15 16:01:06 chuckv Exp $, $Date: 2005-11-15 16:01:06 $, $Name: not supported by cvs2svn $, $Revision: 1.68 $
49  
50  
51   module doForces
# Line 58 | Line 58 | module doForces
58    use lj
59    use sticky
60    use electrostatic_module
61 <  use reaction_field_module
62 <  use gb_pair
61 >  use gayberne
62    use shapes
63    use vector_class
64    use eam
65 +  use suttonchen
66    use status
67   #ifdef IS_MPI
68    use mpiSimulation
# Line 75 | Line 75 | module doForces
75   #include "UseTheForce/fSwitchingFunction.h"
76   #include "UseTheForce/fCutoffPolicy.h"
77   #include "UseTheForce/DarkSide/fInteractionMap.h"
78 + #include "UseTheForce/DarkSide/fElectrostaticSummationMethod.h"
79  
80  
81    INTEGER, PARAMETER:: PREPAIR_LOOP = 1
# Line 85 | Line 86 | module doForces
86    logical, save :: haveSaneForceField = .false.
87    logical, save :: haveInteractionHash = .false.
88    logical, save :: haveGtypeCutoffMap = .false.
89 +  logical, save :: haveDefaultCutoffs = .false.
90    logical, save :: haveRlist = .false.
91  
92    logical, save :: FF_uses_DirectionalAtoms
93    logical, save :: FF_uses_Dipoles
94    logical, save :: FF_uses_GayBerne
95    logical, save :: FF_uses_EAM
96 +  logical, save :: FF_uses_SC
97 +  logical, save :: FF_uses_MEAM
98 +
99  
100    logical, save :: SIM_uses_DirectionalAtoms
101    logical, save :: SIM_uses_EAM
102 +  logical, save :: SIM_uses_SC
103 +  logical, save :: SIM_uses_MEAM
104    logical, save :: SIM_requires_postpair_calc
105    logical, save :: SIM_requires_prepair_calc
106    logical, save :: SIM_uses_PBC
# Line 122 | Line 129 | module doForces
129    ! Bit hash to determine pair-pair interactions.
130    integer, dimension(:,:), allocatable :: InteractionHash
131    real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
132 <  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
133 <  integer, dimension(:), allocatable :: groupToGtype
134 <  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
132 >  real(kind=dp), dimension(:), allocatable, target :: groupMaxCutoffRow
133 >  real(kind=dp), dimension(:), pointer :: groupMaxCutoffCol
134 >
135 >  integer, dimension(:), allocatable, target :: groupToGtypeRow
136 >  integer, dimension(:), pointer :: groupToGtypeCol => null()
137 >
138 >  real(kind=dp), dimension(:), allocatable,target :: gtypeMaxCutoffRow
139 >  real(kind=dp), dimension(:), pointer :: gtypeMaxCutoffCol
140    type ::gtypeCutoffs
141       real(kind=dp) :: rcut
142       real(kind=dp) :: rcutsq
# Line 134 | Line 146 | module doForces
146  
147    integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
148    real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
149 +  real(kind=dp),save :: listSkin
150    
151   contains
152  
# Line 151 | Line 164 | contains
164      logical :: i_is_GB
165      logical :: i_is_EAM
166      logical :: i_is_Shape
167 +    logical :: i_is_SC
168 +    logical :: i_is_MEAM
169      logical :: j_is_LJ
170      logical :: j_is_Elect
171      logical :: j_is_Sticky
# Line 158 | Line 173 | contains
173      logical :: j_is_GB
174      logical :: j_is_EAM
175      logical :: j_is_Shape
176 +    logical :: j_is_SC
177 +    logical :: j_is_MEAM
178      real(kind=dp) :: myRcut
179  
180 +
181      status = 0  
182  
183      if (.not. associated(atypes)) then
# Line 177 | Line 195 | contains
195  
196      if (.not. allocated(InteractionHash)) then
197         allocate(InteractionHash(nAtypes,nAtypes))
198 +    else
199 +       deallocate(InteractionHash)
200 +       allocate(InteractionHash(nAtypes,nAtypes))
201      endif
202  
203      if (.not. allocated(atypeMaxCutoff)) then
204         allocate(atypeMaxCutoff(nAtypes))
205 +    else
206 +       deallocate(atypeMaxCutoff)
207 +       allocate(atypeMaxCutoff(nAtypes))
208      endif
209          
210      do i = 1, nAtypes
# Line 191 | Line 215 | contains
215         call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
216         call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
217         call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
218 +       call getElementProperty(atypes, i, "is_SC", i_is_SC)
219 +       call getElementProperty(atypes, i, "is_MEAM", i_is_MEAM)
220  
221         do j = i, nAtypes
222  
# Line 204 | Line 230 | contains
230            call getElementProperty(atypes, j, "is_GayBerne", j_is_GB)
231            call getElementProperty(atypes, j, "is_EAM", j_is_EAM)
232            call getElementProperty(atypes, j, "is_Shape", j_is_Shape)
233 +          call getElementProperty(atypes, j, "is_SC", j_is_SC)
234 +          call getElementProperty(atypes, j, "is_MEAM", j_is_MEAM)
235  
236            if (i_is_LJ .and. j_is_LJ) then
237               iHash = ior(iHash, LJ_PAIR)            
# Line 225 | Line 253 | contains
253               iHash = ior(iHash, EAM_PAIR)
254            endif
255  
256 +          if (i_is_SC .and. j_is_SC) then
257 +             iHash = ior(iHash, SC_PAIR)
258 +          endif
259 +
260            if (i_is_GB .and. j_is_GB) iHash = ior(iHash, GAYBERNE_PAIR)
261            if (i_is_GB .and. j_is_LJ) iHash = ior(iHash, GAYBERNE_LJ)
262            if (i_is_LJ .and. j_is_GB) iHash = ior(iHash, GAYBERNE_LJ)
# Line 257 | Line 289 | contains
289      logical :: GtypeFound
290  
291      integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
292 <    integer :: n_in_i, me_i, ia, g, atom1, nGroupTypes
292 >    integer :: n_in_i, me_i, ia, g, atom1, ja, n_in_j,me_j
293      integer :: nGroupsInRow
294 <    real(kind=dp):: thisSigma, bigSigma, thisRcut, tol, skin
294 >    integer :: nGroupsInCol
295 >    integer :: nGroupTypesRow,nGroupTypesCol
296 >    real(kind=dp):: thisSigma, bigSigma, thisRcut, tradRcut, tol, skin
297      real(kind=dp) :: biggestAtypeCutoff
298  
299      stat = 0
# Line 273 | Line 307 | contains
307      endif
308   #ifdef IS_MPI
309      nGroupsInRow = getNgroupsInRow(plan_group_row)
310 +    nGroupsInCol = getNgroupsInCol(plan_group_col)
311   #endif
312      nAtypes = getSize(atypes)
313   ! Set all of the initial cutoffs to zero.
# Line 288 | Line 323 | contains
323            call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
324            
325  
326 <          if (i_is_LJ) then
327 <             thisRcut = getSigma(i) * 2.5_dp
328 <             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
329 <          endif
330 <          if (i_is_Elect) then
331 <             thisRcut = defaultRcut
332 <             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
333 <          endif
334 <          if (i_is_Sticky) then
335 <             thisRcut = getStickyCut(i)
336 <             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
337 <          endif
338 <          if (i_is_StickyP) then
339 <             thisRcut = getStickyPowerCut(i)
340 <             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
341 <          endif
342 <          if (i_is_GB) then
343 <             thisRcut = getGayBerneCut(i)
344 <             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
345 <          endif
346 <          if (i_is_EAM) then
347 <             thisRcut = getEAMCut(i)
348 <             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
349 <          endif
350 <          if (i_is_Shape) then
351 <             thisRcut = getShapeCut(i)
352 <             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
326 >          if (haveDefaultCutoffs) then
327 >             atypeMaxCutoff(i) = defaultRcut
328 >          else
329 >             if (i_is_LJ) then          
330 >                thisRcut = getSigma(i) * 2.5_dp
331 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
332 >             endif
333 >             if (i_is_Elect) then
334 >                thisRcut = defaultRcut
335 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
336 >             endif
337 >             if (i_is_Sticky) then
338 >                thisRcut = getStickyCut(i)
339 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
340 >             endif
341 >             if (i_is_StickyP) then
342 >                thisRcut = getStickyPowerCut(i)
343 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
344 >             endif
345 >             if (i_is_GB) then
346 >                thisRcut = getGayBerneCut(i)
347 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
348 >             endif
349 >             if (i_is_EAM) then
350 >                thisRcut = getEAMCut(i)
351 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
352 >             endif
353 >             if (i_is_Shape) then
354 >                thisRcut = getShapeCut(i)
355 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
356 >             endif
357            endif
358            
359 +          
360            if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
361               biggestAtypeCutoff = atypeMaxCutoff(i)
362            endif
363 +
364         endif
365      enddo
366    
367 <    nGroupTypes = 0
367 >
368      
369      istart = 1
370 +    jstart = 1
371   #ifdef IS_MPI
372      iend = nGroupsInRow
373 +    jend = nGroupsInCol
374   #else
375      iend = nGroups
376 +    jend = nGroups
377   #endif
378      
379      !! allocate the groupToGtype and gtypeMaxCutoff here.
380 <    if(.not.allocated(groupToGtype)) then
381 <       allocate(groupToGtype(iend))
382 <       allocate(groupMaxCutoff(iend))
383 <       allocate(gtypeMaxCutoff(iend))
384 <       groupMaxCutoff = 0.0_dp
385 <       gtypeMaxCutoff = 0.0_dp
380 >    if(.not.allocated(groupToGtypeRow)) then
381 >     !  allocate(groupToGtype(iend))
382 >       allocate(groupToGtypeRow(iend))
383 >    else
384 >       deallocate(groupToGtypeRow)
385 >       allocate(groupToGtypeRow(iend))
386      endif
387 +    if(.not.allocated(groupMaxCutoffRow)) then
388 +       allocate(groupMaxCutoffRow(iend))
389 +    else
390 +       deallocate(groupMaxCutoffRow)
391 +       allocate(groupMaxCutoffRow(iend))
392 +    end if
393 +
394 +    if(.not.allocated(gtypeMaxCutoffRow)) then
395 +       allocate(gtypeMaxCutoffRow(iend))
396 +    else
397 +       deallocate(gtypeMaxCutoffRow)
398 +       allocate(gtypeMaxCutoffRow(iend))
399 +    endif
400 +
401 +
402 + #ifdef IS_MPI
403 +       ! We only allocate new storage if we are in MPI because Ncol /= Nrow
404 +    if(.not.associated(groupToGtypeCol)) then
405 +       allocate(groupToGtypeCol(jend))
406 +    else
407 +       deallocate(groupToGtypeCol)
408 +       allocate(groupToGtypeCol(jend))
409 +    end if
410 +
411 +    if(.not.associated(groupToGtypeCol)) then
412 +       allocate(groupToGtypeCol(jend))
413 +    else
414 +       deallocate(groupToGtypeCol)
415 +       allocate(groupToGtypeCol(jend))
416 +    end if
417 +    if(.not.associated(gtypeMaxCutoffCol)) then
418 +       allocate(gtypeMaxCutoffCol(jend))
419 +    else
420 +       deallocate(gtypeMaxCutoffCol)      
421 +       allocate(gtypeMaxCutoffCol(jend))
422 +    end if
423 +
424 +       groupMaxCutoffCol = 0.0_dp
425 +       gtypeMaxCutoffCol = 0.0_dp
426 +
427 + #endif
428 +       groupMaxCutoffRow = 0.0_dp
429 +       gtypeMaxCutoffRow = 0.0_dp
430 +
431 +
432      !! first we do a single loop over the cutoff groups to find the
433      !! largest cutoff for any atypes present in this group.  We also
434      !! create gtypes at this point.
435      
436      tol = 1.0d-6
437 <    
437 >    nGroupTypesRow = 0
438 >
439      do i = istart, iend      
440         n_in_i = groupStartRow(i+1) - groupStartRow(i)
441 <       groupMaxCutoff(i) = 0.0_dp
441 >       groupMaxCutoffRow(i) = 0.0_dp
442         do ia = groupStartRow(i), groupStartRow(i+1)-1
443            atom1 = groupListRow(ia)
444   #ifdef IS_MPI
# Line 356 | Line 446 | contains
446   #else
447            me_i = atid(atom1)
448   #endif          
449 <          if (atypeMaxCutoff(me_i).gt.groupMaxCutoff(i)) then
450 <             groupMaxCutoff(i)=atypeMaxCutoff(me_i)
449 >          if (atypeMaxCutoff(me_i).gt.groupMaxCutoffRow(i)) then
450 >             groupMaxCutoffRow(i)=atypeMaxCutoff(me_i)
451            endif          
452         enddo
453  
454 <       if (nGroupTypes.eq.0) then
455 <          nGroupTypes = nGroupTypes + 1
456 <          gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
457 <          groupToGtype(i) = nGroupTypes
454 >       if (nGroupTypesRow.eq.0) then
455 >          nGroupTypesRow = nGroupTypesRow + 1
456 >          gtypeMaxCutoffRow(nGroupTypesRow) = groupMaxCutoffRow(i)
457 >          groupToGtypeRow(i) = nGroupTypesRow
458         else
459            GtypeFound = .false.
460 <          do g = 1, nGroupTypes
461 <             if ( abs(groupMaxCutoff(i) - gtypeMaxCutoff(g)).lt.tol) then
462 <                groupToGtype(i) = g
460 >          do g = 1, nGroupTypesRow
461 >             if ( abs(groupMaxCutoffRow(i) - gtypeMaxCutoffRow(g)).lt.tol) then
462 >                groupToGtypeRow(i) = g
463                  GtypeFound = .true.
464               endif
465            enddo
466            if (.not.GtypeFound) then            
467 <             nGroupTypes = nGroupTypes + 1
468 <             gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
469 <             groupToGtype(i) = nGroupTypes
467 >             nGroupTypesRow = nGroupTypesRow + 1
468 >             gtypeMaxCutoffRow(nGroupTypesRow) = groupMaxCutoffRow(i)
469 >             groupToGtypeRow(i) = nGroupTypesRow
470 >          endif
471 >       endif
472 >    enddo    
473 >
474 > #ifdef IS_MPI
475 >    do j = jstart, jend      
476 >       n_in_j = groupStartCol(j+1) - groupStartCol(j)
477 >       groupMaxCutoffCol(j) = 0.0_dp
478 >       do ja = groupStartCol(j), groupStartCol(j+1)-1
479 >          atom1 = groupListCol(ja)
480 >
481 >          me_j = atid_col(atom1)
482 >
483 >          if (atypeMaxCutoff(me_j).gt.groupMaxCutoffCol(j)) then
484 >             groupMaxCutoffCol(j)=atypeMaxCutoff(me_j)
485 >          endif          
486 >       enddo
487 >
488 >       if (nGroupTypesCol.eq.0) then
489 >          nGroupTypesCol = nGroupTypesCol + 1
490 >          gtypeMaxCutoffCol(nGroupTypesCol) = groupMaxCutoffCol(j)
491 >          groupToGtypeCol(j) = nGroupTypesCol
492 >       else
493 >          GtypeFound = .false.
494 >          do g = 1, nGroupTypesCol
495 >             if ( abs(groupMaxCutoffCol(j) - gtypeMaxCutoffCol(g)).lt.tol) then
496 >                groupToGtypeCol(j) = g
497 >                GtypeFound = .true.
498 >             endif
499 >          enddo
500 >          if (.not.GtypeFound) then            
501 >             nGroupTypesCol = nGroupTypesCol + 1
502 >             gtypeMaxCutoffCol(nGroupTypesCol) = groupMaxCutoffCol(j)
503 >             groupToGtypeCol(j) = nGroupTypesCol
504            endif
505         endif
506      enddo    
507  
508 + #else
509 + ! Set pointers to information we just found
510 +    nGroupTypesCol = nGroupTypesRow
511 +    groupToGtypeCol => groupToGtypeRow
512 +    gtypeMaxCutoffCol => gtypeMaxCutoffRow
513 +    groupMaxCutoffCol => groupMaxCutoffRow
514 + #endif
515 +
516 +
517 +
518 +
519 +
520      !! allocate the gtypeCutoffMap here.
521 <    allocate(gtypeCutoffMap(nGroupTypes,nGroupTypes))
521 >    allocate(gtypeCutoffMap(nGroupTypesRow,nGroupTypesCol))
522      !! then we do a double loop over all the group TYPES to find the cutoff
523      !! map between groups of two types
524 <    
525 <    do i = 1, nGroupTypes
526 <       do j = 1, nGroupTypes
524 >    tradRcut = max(maxval(gtypeMaxCutoffRow),maxval(gtypeMaxCutoffCol))
525 >
526 >    do i = 1, nGroupTypesRow
527 >       do j = 1, nGroupTypesCol
528        
529            select case(cutoffPolicy)
530            case(TRADITIONAL_CUTOFF_POLICY)
531 <             thisRcut = maxval(gtypeMaxCutoff)
531 >             thisRcut = tradRcut
532            case(MIX_CUTOFF_POLICY)
533 <             thisRcut = 0.5_dp * (gtypeMaxCutoff(i) + gtypeMaxCutoff(j))
533 >             thisRcut = 0.5_dp * (gtypeMaxCutoffRow(i) + gtypeMaxCutoffCol(j))
534            case(MAX_CUTOFF_POLICY)
535 <             thisRcut = max(gtypeMaxCutoff(i), gtypeMaxCutoff(j))
535 >             thisRcut = max(gtypeMaxCutoffRow(i), gtypeMaxCutoffCol(j))
536            case default
537               call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy")
538               return
# Line 403 | Line 540 | contains
540            gtypeCutoffMap(i,j)%rcut = thisRcut
541            gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut
542            skin = defaultRlist - defaultRcut
543 +          listSkin = skin ! set neighbor list skin thickness
544            gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2
545  
546 +          ! sanity check
547 +
548 +          if (haveDefaultCutoffs) then
549 +             if (abs(gtypeCutoffMap(i,j)%rcut - defaultRcut).gt.0.0001) then
550 +                call handleError("createGtypeCutoffMap", "user-specified rCut does not match computed group Cutoff")
551 +             endif
552 +          endif
553         enddo
554      enddo
555 +    if(allocated(gtypeMaxCutoffRow)) deallocate(gtypeMaxCutoffRow)
556 +    if(allocated(groupMaxCutoffRow)) deallocate(groupMaxCutoffRow)
557 +    if(allocated(atypeMaxCutoff)) deallocate(atypeMaxCutoff)
558 + #ifdef IS_MPI
559 +    if(associated(groupMaxCutoffCol)) deallocate(groupMaxCutoffCol)
560 +    if(associated(gtypeMaxCutoffCol)) deallocate(gtypeMaxCutoffCol)
561 + #endif
562 +    groupMaxCutoffCol => null()
563 +    gtypeMaxCutoffCol => null()
564      
565      haveGtypeCutoffMap = .true.
566     end subroutine createGtypeCutoffMap
# Line 419 | Line 573 | contains
573       defaultRsw = defRsw
574       defaultRlist = defRlist
575       cutoffPolicy = cutPolicy
576 +
577 +     haveDefaultCutoffs = .true.
578     end subroutine setDefaultCutoffs
579  
580     subroutine setCutoffPolicy(cutPolicy)
# Line 432 | Line 588 | contains
588    subroutine setSimVariables()
589      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
590      SIM_uses_EAM = SimUsesEAM()
591 +    SIM_uses_SC  = SimUsesSC()
592      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
593      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
594      SIM_uses_PBC = SimUsesPBC()
# Line 504 | Line 661 | contains
661    subroutine init_FF(thisESM, thisStat)
662  
663      integer, intent(in) :: thisESM
507    real(kind=dp), intent(in) :: dampingAlpha
664      integer, intent(out) :: thisStat  
665      integer :: my_status, nMatches
666      integer, pointer :: MatchList(:) => null()
511    real(kind=dp) :: rcut, rrf, rt, dielect
667  
668      !! assume things are copacetic, unless they aren't
669      thisStat = 0
# Line 544 | Line 699 | contains
699  
700      haveSaneForceField = .true.
701  
547    !! check to make sure the reaction field setting makes sense
548
549    if (FF_uses_Dipoles) then
550       if (electrostaticSummationMethod == 3) then
551          dielect = getDielect()
552          call initialize_rf(dielect)
553       endif
554    else
555       if (electrostaticSummationMethod == 3) then
556          write(default_error,*) 'Using Reaction Field with no dipoles?  Huh?'
557          thisStat = -1
558          haveSaneForceField = .false.
559          return
560       endif
561    endif
562
702      if (FF_uses_EAM) then
703         call init_EAM_FF(my_status)
704         if (my_status /= 0) then
# Line 570 | Line 709 | contains
709         end if
710      endif
711  
573    if (FF_uses_GayBerne) then
574       call check_gb_pair_FF(my_status)
575       if (my_status .ne. 0) then
576          thisStat = -1
577          haveSaneForceField = .false.
578          return
579       endif
580    endif
581
712      if (.not. haveNeighborList) then
713         !! Create neighbor lists
714         call expandNeighborList(nLocal, my_status)
# Line 612 | Line 742 | contains
742  
743      !! Stress Tensor
744      real( kind = dp), dimension(9) :: tau  
745 <    real ( kind = dp ) :: pot
745 >    real ( kind = dp ),dimension(LR_POT_TYPES) :: pot
746      logical ( kind = 2) :: do_pot_c, do_stress_c
747      logical :: do_pot
748      logical :: do_stress
749      logical :: in_switching_region
750   #ifdef IS_MPI
751 <    real( kind = DP ) :: pot_local
751 >    real( kind = DP ), dimension(LR_POT_TYPES) :: pot_local
752      integer :: nAtomsInRow
753      integer :: nAtomsInCol
754      integer :: nprocs
# Line 633 | Line 763 | contains
763      integer :: nlist
764      real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vij
765      real( kind = DP ) :: sw, dswdr, swderiv, mf
766 +    real( kind = DP ) :: rVal
767      real(kind=dp),dimension(3) :: d_atm, d_grp, fpair, fij
768      real(kind=dp) :: rfpot, mu_i, virial
769      integer :: me_i, me_j, n_in_i, n_in_j
# Line 643 | Line 774 | contains
774      integer :: propPack_i, propPack_j
775      integer :: loopStart, loopEnd, loop
776      integer :: iHash
777 <    real(kind=dp) :: listSkin = 1.0  
777 >    integer :: i1
778 >  
779  
780      !! initialize local variables  
781  
# Line 768 | Line 900 | contains
900               me_j = atid(j)
901               call get_interatomic_vector(q_group(:,i), &
902                    q_group(:,j), d_grp, rgrpsq)
903 < #endif
903 > #endif      
904  
905 <             if (rgrpsq < gtypeCutoffMap(groupToGtype(i),groupToGtype(j))%rListsq) then
905 >             if (rgrpsq < gtypeCutoffMap(groupToGtypeRow(i),groupToGtypeCol(j))%rListsq) then
906                  if (update_nlist) then
907                     nlist = nlist + 1
908  
# Line 790 | Line 922 | contains
922  
923                     list(nlist) = j
924                  endif
925 +                
926 +                if (rgrpsq < gtypeCutoffMap(groupToGtypeRow(i),groupToGtypeCol(j))%rCutsq) then
927  
928 <                if (loop .eq. PAIR_LOOP) then
929 <                   vij = 0.0d0
930 <                   fij(1:3) = 0.0d0
931 <                endif
932 <
933 <                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
934 <                     in_switching_region)
935 <
936 <                n_in_j = groupStartCol(j+1) - groupStartCol(j)
937 <
938 <                do ia = groupStartRow(i), groupStartRow(i+1)-1
939 <
940 <                   atom1 = groupListRow(ia)
941 <
942 <                   inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
943 <
944 <                      atom2 = groupListCol(jb)
945 <
946 <                      if (skipThisPair(atom1, atom2)) cycle inner
947 <
948 <                      if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
949 <                         d_atm(1:3) = d_grp(1:3)
950 <                         ratmsq = rgrpsq
951 <                      else
928 >                   if (loop .eq. PAIR_LOOP) then
929 >                      vij = 0.0d0
930 >                      fij(1:3) = 0.0d0
931 >                   endif
932 >                  
933 >                   call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
934 >                        in_switching_region)
935 >                  
936 >                   n_in_j = groupStartCol(j+1) - groupStartCol(j)
937 >                  
938 >                   do ia = groupStartRow(i), groupStartRow(i+1)-1
939 >                      
940 >                      atom1 = groupListRow(ia)
941 >                      
942 >                      inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
943 >                        
944 >                         atom2 = groupListCol(jb)
945 >                        
946 >                         if (skipThisPair(atom1, atom2))  cycle inner
947 >                        
948 >                         if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
949 >                            d_atm(1:3) = d_grp(1:3)
950 >                            ratmsq = rgrpsq
951 >                         else
952   #ifdef IS_MPI
953 <                         call get_interatomic_vector(q_Row(:,atom1), &
954 <                              q_Col(:,atom2), d_atm, ratmsq)
953 >                            call get_interatomic_vector(q_Row(:,atom1), &
954 >                                 q_Col(:,atom2), d_atm, ratmsq)
955   #else
956 <                         call get_interatomic_vector(q(:,atom1), &
957 <                              q(:,atom2), d_atm, ratmsq)
956 >                            call get_interatomic_vector(q(:,atom1), &
957 >                                 q(:,atom2), d_atm, ratmsq)
958   #endif
959 <                      endif
960 <
961 <                      if (loop .eq. PREPAIR_LOOP) then
959 >                         endif
960 >                        
961 >                         if (loop .eq. PREPAIR_LOOP) then
962   #ifdef IS_MPI                      
963 <                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
964 <                              rgrpsq, d_grp, do_pot, do_stress, &
965 <                              eFrame, A, f, t, pot_local)
963 >                            call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
964 >                                 rgrpsq, d_grp, do_pot, do_stress, &
965 >                                 eFrame, A, f, t, pot_local)
966   #else
967 <                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
968 <                              rgrpsq, d_grp, do_pot, do_stress, &
969 <                              eFrame, A, f, t, pot)
967 >                            call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
968 >                                 rgrpsq, d_grp, do_pot, do_stress, &
969 >                                 eFrame, A, f, t, pot)
970   #endif                                              
971 <                      else
971 >                         else
972   #ifdef IS_MPI                      
973 <                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
974 <                              do_pot, &
975 <                              eFrame, A, f, t, pot_local, vpair, fpair)
973 >                            call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
974 >                                 do_pot, eFrame, A, f, t, pot_local, vpair, &
975 >                                 fpair, d_grp, rgrp)
976   #else
977 <                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
978 <                              do_pot,  &
979 <                              eFrame, A, f, t, pot, vpair, fpair)
977 >                            call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
978 >                                 do_pot, eFrame, A, f, t, pot, vpair, fpair, &
979 >                                 d_grp, rgrp)
980   #endif
981 +                            vij = vij + vpair
982 +                            fij(1:3) = fij(1:3) + fpair(1:3)
983 +                         endif
984 +                      enddo inner
985 +                   enddo
986  
987 <                         vij = vij + vpair
988 <                         fij(1:3) = fij(1:3) + fpair(1:3)
989 <                      endif
990 <                   enddo inner
991 <                enddo
992 <
993 <                if (loop .eq. PAIR_LOOP) then
994 <                   if (in_switching_region) then
995 <                      swderiv = vij*dswdr/rgrp
996 <                      fij(1) = fij(1) + swderiv*d_grp(1)
858 <                      fij(2) = fij(2) + swderiv*d_grp(2)
859 <                      fij(3) = fij(3) + swderiv*d_grp(3)
860 <
861 <                      do ia=groupStartRow(i), groupStartRow(i+1)-1
862 <                         atom1=groupListRow(ia)
863 <                         mf = mfactRow(atom1)
987 >                   if (loop .eq. PAIR_LOOP) then
988 >                      if (in_switching_region) then
989 >                         swderiv = vij*dswdr/rgrp
990 >                         fij(1) = fij(1) + swderiv*d_grp(1)
991 >                         fij(2) = fij(2) + swderiv*d_grp(2)
992 >                         fij(3) = fij(3) + swderiv*d_grp(3)
993 >                        
994 >                         do ia=groupStartRow(i), groupStartRow(i+1)-1
995 >                            atom1=groupListRow(ia)
996 >                            mf = mfactRow(atom1)
997   #ifdef IS_MPI
998 <                         f_Row(1,atom1) = f_Row(1,atom1) + swderiv*d_grp(1)*mf
999 <                         f_Row(2,atom1) = f_Row(2,atom1) + swderiv*d_grp(2)*mf
1000 <                         f_Row(3,atom1) = f_Row(3,atom1) + swderiv*d_grp(3)*mf
998 >                            f_Row(1,atom1) = f_Row(1,atom1) + swderiv*d_grp(1)*mf
999 >                            f_Row(2,atom1) = f_Row(2,atom1) + swderiv*d_grp(2)*mf
1000 >                            f_Row(3,atom1) = f_Row(3,atom1) + swderiv*d_grp(3)*mf
1001   #else
1002 <                         f(1,atom1) = f(1,atom1) + swderiv*d_grp(1)*mf
1003 <                         f(2,atom1) = f(2,atom1) + swderiv*d_grp(2)*mf
1004 <                         f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
1002 >                            f(1,atom1) = f(1,atom1) + swderiv*d_grp(1)*mf
1003 >                            f(2,atom1) = f(2,atom1) + swderiv*d_grp(2)*mf
1004 >                            f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
1005   #endif
1006 <                      enddo
1007 <
1008 <                      do jb=groupStartCol(j), groupStartCol(j+1)-1
1009 <                         atom2=groupListCol(jb)
1010 <                         mf = mfactCol(atom2)
1006 >                         enddo
1007 >                        
1008 >                         do jb=groupStartCol(j), groupStartCol(j+1)-1
1009 >                            atom2=groupListCol(jb)
1010 >                            mf = mfactCol(atom2)
1011   #ifdef IS_MPI
1012 <                         f_Col(1,atom2) = f_Col(1,atom2) - swderiv*d_grp(1)*mf
1013 <                         f_Col(2,atom2) = f_Col(2,atom2) - swderiv*d_grp(2)*mf
1014 <                         f_Col(3,atom2) = f_Col(3,atom2) - swderiv*d_grp(3)*mf
1012 >                            f_Col(1,atom2) = f_Col(1,atom2) - swderiv*d_grp(1)*mf
1013 >                            f_Col(2,atom2) = f_Col(2,atom2) - swderiv*d_grp(2)*mf
1014 >                            f_Col(3,atom2) = f_Col(3,atom2) - swderiv*d_grp(3)*mf
1015   #else
1016 <                         f(1,atom2) = f(1,atom2) - swderiv*d_grp(1)*mf
1017 <                         f(2,atom2) = f(2,atom2) - swderiv*d_grp(2)*mf
1018 <                         f(3,atom2) = f(3,atom2) - swderiv*d_grp(3)*mf
1016 >                            f(1,atom2) = f(1,atom2) - swderiv*d_grp(1)*mf
1017 >                            f(2,atom2) = f(2,atom2) - swderiv*d_grp(2)*mf
1018 >                            f(3,atom2) = f(3,atom2) - swderiv*d_grp(3)*mf
1019   #endif
1020 <                      enddo
1021 <                   endif
1020 >                         enddo
1021 >                      endif
1022  
1023 <                   if (do_stress) call add_stress_tensor(d_grp, fij)
1023 >                      if (do_stress) call add_stress_tensor(d_grp, fij)
1024 >                   endif
1025                  endif
1026 <             end if
1026 >             endif
1027            enddo
1028 +          
1029         enddo outer
1030  
1031         if (update_nlist) then
# Line 950 | Line 1085 | contains
1085  
1086      if (do_pot) then
1087         ! scatter/gather pot_row into the members of my column
1088 <       call scatter(pot_Row, pot_Temp, plan_atom_row)
1089 <
1088 >       do i = 1,LR_POT_TYPES
1089 >          call scatter(pot_Row(i,:), pot_Temp(i,:), plan_atom_row)
1090 >       end do
1091         ! scatter/gather pot_local into all other procs
1092         ! add resultant to get total pot
1093         do i = 1, nlocal
1094 <          pot_local = pot_local + pot_Temp(i)
1094 >          pot_local(1:LR_POT_TYPES) = pot_local(1:LR_POT_TYPES) &
1095 >               + pot_Temp(1:LR_POT_TYPES,i)
1096         enddo
1097  
1098         pot_Temp = 0.0_DP
1099 <
1100 <       call scatter(pot_Col, pot_Temp, plan_atom_col)
1099 >       do i = 1,LR_POT_TYPES
1100 >          call scatter(pot_Col(i,:), pot_Temp(i,:), plan_atom_col)
1101 >       end do
1102         do i = 1, nlocal
1103 <          pot_local = pot_local + pot_Temp(i)
1103 >          pot_local(1:LR_POT_TYPES) = pot_local(1:LR_POT_TYPES)&
1104 >               + pot_Temp(1:LR_POT_TYPES,i)
1105         enddo
1106  
1107      endif
1108   #endif
1109  
1110 <    if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
1110 >    if (SIM_requires_postpair_calc) then
1111 >       do i = 1, nlocal            
1112 >          
1113 >          ! we loop only over the local atoms, so we don't need row and column
1114 >          ! lookups for the types
1115 >          
1116 >          me_i = atid(i)
1117 >          
1118 >          ! is the atom electrostatic?  See if it would have an
1119 >          ! electrostatic interaction with itself
1120 >          iHash = InteractionHash(me_i,me_i)
1121  
1122 <       if (electrostaticSummationMethod == 3) then
974 <
1122 >          if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1123   #ifdef IS_MPI
1124 <          call scatter(rf_Row,rf,plan_atom_row_3d)
1125 <          call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
978 <          do i = 1,nlocal
979 <             rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
980 <          end do
981 < #endif
982 <
983 <          do i = 1, nLocal
984 <
985 <             rfpot = 0.0_DP
986 < #ifdef IS_MPI
987 <             me_i = atid_row(i)
1124 >             call self_self(i, eFrame, pot_local(ELECTROSTATIC_POT), &
1125 >                  t, do_pot)
1126   #else
1127 <             me_i = atid(i)
1127 >             call self_self(i, eFrame, pot(ELECTROSTATIC_POT), &
1128 >                  t, do_pot)
1129   #endif
1130 <             iHash = InteractionHash(me_i,me_j)
1130 >          endif
1131 >  
1132 >          
1133 >          if (electrostaticSummationMethod.eq.REACTION_FIELD) then
1134              
1135 <             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1136 <
1137 <                mu_i = getDipoleMoment(me_i)
1138 <
1139 <                !! The reaction field needs to include a self contribution
1140 <                !! to the field:
1141 <                call accumulate_self_rf(i, mu_i, eFrame)
1142 <                !! Get the reaction field contribution to the
1143 <                !! potential and torques:
1144 <                call reaction_field_final(i, mu_i, eFrame, rfpot, t, do_pot)
1135 >             ! loop over the excludes to accumulate RF stuff we've
1136 >             ! left out of the normal pair loop
1137 >            
1138 >             do i1 = 1, nSkipsForAtom(i)
1139 >                j = skipsForAtom(i, i1)
1140 >                
1141 >                ! prevent overcounting of the skips
1142 >                if (i.lt.j) then
1143 >                   call get_interatomic_vector(q(:,i), &
1144 >                        q(:,j), d_atm, ratmsq)
1145 >                   rVal = dsqrt(ratmsq)
1146 >                   call get_switch(ratmsq, sw, dswdr, rVal, group_switch, &
1147 >                        in_switching_region)
1148   #ifdef IS_MPI
1149 <                pot_local = pot_local + rfpot
1150 < #else
1151 <                pot = pot + rfpot
1152 <
1149 >                   call rf_self_excludes(i, j, sw, eFrame, d_atm, rVal, &
1150 >                        vpair, pot_local(ELECTROSTATIC_POT), f, t, do_pot)
1151 > #else
1152 >                   call rf_self_excludes(i, j, sw, eFrame, d_atm, rVal, &
1153 >                        vpair, pot(ELECTROSTATIC_POT), f, t, do_pot)
1154   #endif
1155 <             endif
1156 <          enddo
1157 <       endif
1155 >                endif
1156 >             enddo
1157 >          endif
1158 >       enddo
1159      endif
1160 <
1014 <
1160 >    
1161   #ifdef IS_MPI
1162 <
1162 >    
1163      if (do_pot) then
1164 <       pot = pot + pot_local
1165 <       !! we assume the c code will do the allreduce to get the total potential
1020 <       !! we could do it right here if we needed to...
1164 >       call mpi_allreduce(pot_local, pot, LR_POT_TYPES,mpi_double_precision,mpi_sum, &
1165 >            mpi_comm_world,mpi_err)            
1166      endif
1167 <
1167 >    
1168      if (do_stress) then
1169         call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
1170              mpi_comm_world,mpi_err)
1171         call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
1172              mpi_comm_world,mpi_err)
1173      endif
1174 <
1174 >    
1175   #else
1176 <
1176 >    
1177      if (do_stress) then
1178         tau = tau_Temp
1179         virial = virial_Temp
1180      endif
1181 <
1181 >    
1182   #endif
1183 <
1183 >    
1184    end subroutine do_force_loop
1185  
1186    subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
1187 <       eFrame, A, f, t, pot, vpair, fpair)
1187 >       eFrame, A, f, t, pot, vpair, fpair, d_grp, r_grp)
1188  
1189 <    real( kind = dp ) :: pot, vpair, sw
1189 >    real( kind = dp ) :: vpair, sw
1190 >    real( kind = dp ), dimension(LR_POT_TYPES) :: pot
1191      real( kind = dp ), dimension(3) :: fpair
1192      real( kind = dp ), dimension(nLocal)   :: mfact
1193      real( kind = dp ), dimension(9,nLocal) :: eFrame
# Line 1052 | Line 1198 | contains
1198      logical, intent(inout) :: do_pot
1199      integer, intent(in) :: i, j
1200      real ( kind = dp ), intent(inout) :: rijsq
1201 <    real ( kind = dp )                :: r
1201 >    real ( kind = dp ), intent(inout) :: r_grp
1202      real ( kind = dp ), intent(inout) :: d(3)
1203 +    real ( kind = dp ), intent(inout) :: d_grp(3)
1204 +    real ( kind = dp ) :: r
1205      integer :: me_i, me_j
1206  
1207      integer :: iHash
# Line 1071 | Line 1219 | contains
1219   #endif
1220  
1221      iHash = InteractionHash(me_i, me_j)
1222 <
1222 >    
1223      if ( iand(iHash, LJ_PAIR).ne.0 ) then
1224 <       call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1224 >       call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1225 >            pot(VDW_POT), f, do_pot)
1226      endif
1227 <
1227 >    
1228      if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1229         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1230 <            pot, eFrame, f, t, do_pot)
1082 <
1083 <       if (electrostaticSummationMethod == 3) then
1084 <
1085 <          ! CHECK ME (RF needs to know about all electrostatic types)
1086 <          call accumulate_rf(i, j, r, eFrame, sw)
1087 <          call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
1088 <       endif
1089 <
1230 >            pot(ELECTROSTATIC_POT), eFrame, f, t, do_pot)
1231      endif
1232 <
1232 >    
1233      if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1234         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1235 <            pot, A, f, t, do_pot)
1235 >            pot(HB_POT), A, f, t, do_pot)
1236      endif
1237 <
1237 >    
1238      if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1239         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1240 <            pot, A, f, t, do_pot)
1240 >            pot(HB_POT), A, f, t, do_pot)
1241      endif
1242 <
1242 >    
1243      if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1244         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1245 <            pot, A, f, t, do_pot)
1245 >            pot(VDW_POT), A, f, t, do_pot)
1246      endif
1247      
1248      if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1249 < !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1250 < !           pot, A, f, t, do_pot)
1249 >       call do_gb_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1250 >            pot(VDW_POT), A, f, t, do_pot)
1251      endif
1252 <
1252 >    
1253      if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1254 <       call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1255 <            do_pot)
1254 >       call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1255 >            pot(METALLIC_POT), f, do_pot)
1256      endif
1257 <
1257 >    
1258      if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1259         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1260 <            pot, A, f, t, do_pot)
1260 >            pot(VDW_POT), A, f, t, do_pot)
1261      endif
1262 <
1262 >    
1263      if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1264         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1265 <            pot, A, f, t, do_pot)
1265 >            pot(VDW_POT), A, f, t, do_pot)
1266      endif
1267 +
1268 +    if ( iand(iHash, SC_PAIR).ne.0 ) then      
1269 +       call do_SC_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1270 +            pot(METALLIC_POT), f, do_pot)
1271 +    endif
1272 +
1273      
1274 +    
1275    end subroutine do_pair
1276  
1277    subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
1278         do_pot, do_stress, eFrame, A, f, t, pot)
1279  
1280 <    real( kind = dp ) :: pot, sw
1280 >    real( kind = dp ) :: sw
1281 >    real( kind = dp ), dimension(LR_POT_TYPES) :: pot
1282      real( kind = dp ), dimension(9,nLocal) :: eFrame
1283      real (kind=dp), dimension(9,nLocal) :: A
1284      real (kind=dp), dimension(3,nLocal) :: f
# Line 1158 | Line 1307 | contains
1307      if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1308              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1309      endif
1310 +
1311 +    if ( iand(iHash, SC_PAIR).ne.0 ) then      
1312 +            call calc_SC_prepair_rho(i, j, d, r, rijsq )
1313 +    endif
1314      
1315    end subroutine do_prepair
1316  
1317  
1318    subroutine do_preforce(nlocal,pot)
1319      integer :: nlocal
1320 <    real( kind = dp ) :: pot
1320 >    real( kind = dp ),dimension(LR_POT_TYPES) :: pot
1321  
1322      if (FF_uses_EAM .and. SIM_uses_EAM) then
1323 <       call calc_EAM_preforce_Frho(nlocal,pot)
1323 >       call calc_EAM_preforce_Frho(nlocal,pot(METALLIC_POT))
1324      endif
1325 +    if (FF_uses_SC .and. SIM_uses_SC) then
1326 +       call calc_SC_preforce_Frho(nlocal,pot(METALLIC_POT))
1327 +    endif
1328  
1329  
1330    end subroutine do_preforce
# Line 1253 | Line 1409 | contains
1409      pot_Col = 0.0_dp
1410      pot_Temp = 0.0_dp
1411  
1256    rf_Row = 0.0_dp
1257    rf_Col = 0.0_dp
1258    rf_Temp = 0.0_dp
1259
1412   #endif
1413  
1414      if (FF_uses_EAM .and. SIM_uses_EAM) then
1415         call clean_EAM()
1416      endif
1417  
1266    rf = 0.0_dp
1418      tau_Temp = 0.0_dp
1419      virial_Temp = 0.0_dp
1420    end subroutine zero_work_arrays
# Line 1357 | Line 1508 | contains
1508  
1509    function FF_RequiresPrepairCalc() result(doesit)
1510      logical :: doesit
1511 <    doesit = FF_uses_EAM
1511 >    doesit = FF_uses_EAM .or. FF_uses_SC &
1512 >         .or. FF_uses_MEAM
1513    end function FF_RequiresPrepairCalc
1514  
1363  function FF_RequiresPostpairCalc() result(doesit)
1364    logical :: doesit
1365    if (electrostaticSummationMethod == 3) doesit = .true.
1366  end function FF_RequiresPostpairCalc
1367
1515   #ifdef PROFILE
1516    function getforcetime() result(totalforcetime)
1517      real(kind=dp) :: totalforcetime

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines