--- trunk/OOPSE-3.0/src/UseTheForce/doForces.F90 2005/05/18 18:31:40 2231 +++ trunk/OOPSE-3.0/src/UseTheForce/doForces.F90 2005/10/12 18:59:16 2355 @@ -45,7 +45,7 @@ !! @author Charles F. Vardeman II !! @author Matthew Meineke -!! @version $Id: doForces.F90,v 1.18 2005-05-18 18:31:40 chrisfen Exp $, $Date: 2005-05-18 18:31:40 $, $Name: not supported by cvs2svn $, $Revision: 1.18 $ +!! @version $Id: doForces.F90,v 1.54 2005-10-12 18:59:16 chuckv Exp $, $Date: 2005-10-12 18:59:16 $, $Name: not supported by cvs2svn $, $Revision: 1.54 $ module doForces @@ -58,7 +58,7 @@ module doForces use lj use sticky use electrostatic_module - use reaction_field + use reaction_field_module use gb_pair use shapes use vector_class @@ -73,53 +73,45 @@ module doForces #define __FORTRAN90 #include "UseTheForce/fSwitchingFunction.h" +#include "UseTheForce/fCutoffPolicy.h" +#include "UseTheForce/DarkSide/fInteractionMap.h" +#include "UseTheForce/DarkSide/fElectrostaticSummationMethod.h" + INTEGER, PARAMETER:: PREPAIR_LOOP = 1 INTEGER, PARAMETER:: PAIR_LOOP = 2 - logical, save :: haveRlist = .false. logical, save :: haveNeighborList = .false. logical, save :: haveSIMvariables = .false. - logical, save :: havePropertyMap = .false. logical, save :: haveSaneForceField = .false. + logical, save :: haveInteractionHash = .false. + logical, save :: haveGtypeCutoffMap = .false. + logical, save :: haveDefaultCutoffs = .false. + logical, save :: haveRlist = .false. logical, save :: FF_uses_DirectionalAtoms - logical, save :: FF_uses_LennardJones - logical, save :: FF_uses_Electrostatics - logical, save :: FF_uses_Charges logical, save :: FF_uses_Dipoles - logical, save :: FF_uses_Quadrupoles - logical, save :: FF_uses_Sticky - logical, save :: FF_uses_StickyPower logical, save :: FF_uses_GayBerne logical, save :: FF_uses_EAM - logical, save :: FF_uses_Shapes - logical, save :: FF_uses_FLARB - logical, save :: FF_uses_RF logical, save :: SIM_uses_DirectionalAtoms - logical, save :: SIM_uses_LennardJones - logical, save :: SIM_uses_Electrostatics - logical, save :: SIM_uses_Charges - logical, save :: SIM_uses_Dipoles - logical, save :: SIM_uses_Quadrupoles - logical, save :: SIM_uses_Sticky - logical, save :: SIM_uses_StickyPower - logical, save :: SIM_uses_GayBerne logical, save :: SIM_uses_EAM - logical, save :: SIM_uses_Shapes - logical, save :: SIM_uses_FLARB - logical, save :: SIM_uses_RF logical, save :: SIM_requires_postpair_calc logical, save :: SIM_requires_prepair_calc logical, save :: SIM_uses_PBC - logical, save :: SIM_uses_molecular_cutoffs - real(kind=dp), save :: rlist, rlistsq + integer, save :: electrostaticSummationMethod public :: init_FF + public :: setDefaultCutoffs public :: do_force_loop - public :: setRlistDF + public :: createInteractionHash + public :: createGtypeCutoffMap + public :: getStickyCut + public :: getStickyPowerCut + public :: getGayBerneCut + public :: getEAMCut + public :: getShapeCut #ifdef PROFILE public :: getforcetime @@ -127,112 +119,457 @@ module doForces real :: forceTimeInitial, forceTimeFinal integer :: nLoops #endif + + !! Variables for cutoff mapping and interaction mapping + ! Bit hash to determine pair-pair interactions. + integer, dimension(:,:), allocatable :: InteractionHash + real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff + real(kind=dp), dimension(:), allocatable, target :: groupMaxCutoffRow + real(kind=dp), dimension(:), pointer :: groupMaxCutoffCol - type :: Properties - logical :: is_Directional = .false. - logical :: is_LennardJones = .false. - logical :: is_Electrostatic = .false. - logical :: is_Charge = .false. - logical :: is_Dipole = .false. - logical :: is_Quadrupole = .false. - logical :: is_Sticky = .false. - logical :: is_StickyPower = .false. - logical :: is_GayBerne = .false. - logical :: is_EAM = .false. - logical :: is_Shape = .false. - logical :: is_FLARB = .false. - end type Properties + integer, dimension(:), allocatable, target :: groupToGtypeRow + integer, dimension(:), pointer :: groupToGtypeCol => null() - type(Properties), dimension(:),allocatable :: PropertyMap + real(kind=dp), dimension(:), allocatable,target :: gtypeMaxCutoffRow + real(kind=dp), dimension(:), pointer :: gtypeMaxCutoffCol + type ::gtypeCutoffs + real(kind=dp) :: rcut + real(kind=dp) :: rcutsq + real(kind=dp) :: rlistsq + end type gtypeCutoffs + type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap + integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY + real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist + real(kind=dp),save :: listSkin + contains - subroutine setRlistDF( this_rlist ) - - real(kind=dp) :: this_rlist - - rlist = this_rlist - rlistsq = rlist * rlist - - haveRlist = .true. - - end subroutine setRlistDF - - subroutine createPropertyMap(status) + subroutine createInteractionHash(status) integer :: nAtypes - integer :: status + integer, intent(out) :: status integer :: i - logical :: thisProperty - real (kind=DP) :: thisDPproperty + integer :: j + integer :: iHash + !! Test Types + logical :: i_is_LJ + logical :: i_is_Elect + logical :: i_is_Sticky + logical :: i_is_StickyP + logical :: i_is_GB + logical :: i_is_EAM + logical :: i_is_Shape + logical :: j_is_LJ + logical :: j_is_Elect + logical :: j_is_Sticky + logical :: j_is_StickyP + logical :: j_is_GB + logical :: j_is_EAM + logical :: j_is_Shape + real(kind=dp) :: myRcut - status = 0 + status = 0 + if (.not. associated(atypes)) then + call handleError("atype", "atypes was not present before call of createInteractionHash!") + status = -1 + return + endif + nAtypes = getSize(atypes) - + if (nAtypes == 0) then status = -1 return end if - if (.not. allocated(PropertyMap)) then - allocate(PropertyMap(nAtypes)) + if (.not. allocated(InteractionHash)) then + allocate(InteractionHash(nAtypes,nAtypes)) + else + deallocate(InteractionHash) + allocate(InteractionHash(nAtypes,nAtypes)) endif + if (.not. allocated(atypeMaxCutoff)) then + allocate(atypeMaxCutoff(nAtypes)) + else + deallocate(atypeMaxCutoff) + allocate(atypeMaxCutoff(nAtypes)) + endif + do i = 1, nAtypes - call getElementProperty(atypes, i, "is_Directional", thisProperty) - PropertyMap(i)%is_Directional = thisProperty + call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ) + call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect) + call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky) + call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP) + call getElementProperty(atypes, i, "is_GayBerne", i_is_GB) + call getElementProperty(atypes, i, "is_EAM", i_is_EAM) + call getElementProperty(atypes, i, "is_Shape", i_is_Shape) - call getElementProperty(atypes, i, "is_LennardJones", thisProperty) - PropertyMap(i)%is_LennardJones = thisProperty + do j = i, nAtypes - call getElementProperty(atypes, i, "is_Electrostatic", thisProperty) - PropertyMap(i)%is_Electrostatic = thisProperty + iHash = 0 + myRcut = 0.0_dp - call getElementProperty(atypes, i, "is_Charge", thisProperty) - PropertyMap(i)%is_Charge = thisProperty + call getElementProperty(atypes, j, "is_LennardJones", j_is_LJ) + call getElementProperty(atypes, j, "is_Electrostatic", j_is_Elect) + call getElementProperty(atypes, j, "is_Sticky", j_is_Sticky) + call getElementProperty(atypes, j, "is_StickyPower", j_is_StickyP) + call getElementProperty(atypes, j, "is_GayBerne", j_is_GB) + call getElementProperty(atypes, j, "is_EAM", j_is_EAM) + call getElementProperty(atypes, j, "is_Shape", j_is_Shape) - call getElementProperty(atypes, i, "is_Dipole", thisProperty) - PropertyMap(i)%is_Dipole = thisProperty + if (i_is_LJ .and. j_is_LJ) then + iHash = ior(iHash, LJ_PAIR) + endif + + if (i_is_Elect .and. j_is_Elect) then + iHash = ior(iHash, ELECTROSTATIC_PAIR) + endif + + if (i_is_Sticky .and. j_is_Sticky) then + iHash = ior(iHash, STICKY_PAIR) + endif - call getElementProperty(atypes, i, "is_Quadrupole", thisProperty) - PropertyMap(i)%is_Quadrupole = thisProperty + if (i_is_StickyP .and. j_is_StickyP) then + iHash = ior(iHash, STICKYPOWER_PAIR) + endif - call getElementProperty(atypes, i, "is_Sticky", thisProperty) - PropertyMap(i)%is_Sticky = thisProperty - - call getElementProperty(atypes, i, "is_StickyPower", thisProperty) - PropertyMap(i)%is_StickyPower = thisProperty + if (i_is_EAM .and. j_is_EAM) then + iHash = ior(iHash, EAM_PAIR) + endif - call getElementProperty(atypes, i, "is_GayBerne", thisProperty) - PropertyMap(i)%is_GayBerne = thisProperty + if (i_is_GB .and. j_is_GB) iHash = ior(iHash, GAYBERNE_PAIR) + if (i_is_GB .and. j_is_LJ) iHash = ior(iHash, GAYBERNE_LJ) + if (i_is_LJ .and. j_is_GB) iHash = ior(iHash, GAYBERNE_LJ) - call getElementProperty(atypes, i, "is_EAM", thisProperty) - PropertyMap(i)%is_EAM = thisProperty + if (i_is_Shape .and. j_is_Shape) iHash = ior(iHash, SHAPE_PAIR) + if (i_is_Shape .and. j_is_LJ) iHash = ior(iHash, SHAPE_LJ) + if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ) - call getElementProperty(atypes, i, "is_Shape", thisProperty) - PropertyMap(i)%is_Shape = thisProperty - call getElementProperty(atypes, i, "is_FLARB", thisProperty) - PropertyMap(i)%is_FLARB = thisProperty + InteractionHash(i,j) = iHash + InteractionHash(j,i) = iHash + + end do + end do - havePropertyMap = .true. + haveInteractionHash = .true. + end subroutine createInteractionHash - end subroutine createPropertyMap + subroutine createGtypeCutoffMap(stat) + + integer, intent(out), optional :: stat + logical :: i_is_LJ + logical :: i_is_Elect + logical :: i_is_Sticky + logical :: i_is_StickyP + logical :: i_is_GB + logical :: i_is_EAM + logical :: i_is_Shape + logical :: GtypeFound + + integer :: myStatus, nAtypes, i, j, istart, iend, jstart, jend + integer :: n_in_i, me_i, ia, g, atom1, ja, n_in_j,me_j + integer :: nGroupsInRow + integer :: nGroupsInCol + integer :: nGroupTypesRow,nGroupTypesCol + real(kind=dp):: thisSigma, bigSigma, thisRcut, tradRcut, tol, skin + real(kind=dp) :: biggestAtypeCutoff + + stat = 0 + if (.not. haveInteractionHash) then + call createInteractionHash(myStatus) + if (myStatus .ne. 0) then + write(default_error, *) 'createInteractionHash failed in doForces!' + stat = -1 + return + endif + endif +#ifdef IS_MPI + nGroupsInRow = getNgroupsInRow(plan_group_row) + nGroupsInCol = getNgroupsInCol(plan_group_col) +#endif + nAtypes = getSize(atypes) +! Set all of the initial cutoffs to zero. + atypeMaxCutoff = 0.0_dp + do i = 1, nAtypes + if (SimHasAtype(i)) then + call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ) + call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect) + call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky) + call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP) + call getElementProperty(atypes, i, "is_GayBerne", i_is_GB) + call getElementProperty(atypes, i, "is_EAM", i_is_EAM) + call getElementProperty(atypes, i, "is_Shape", i_is_Shape) + + + if (haveDefaultCutoffs) then + atypeMaxCutoff(i) = defaultRcut + else + if (i_is_LJ) then + thisRcut = getSigma(i) * 2.5_dp + if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut + endif + if (i_is_Elect) then + thisRcut = defaultRcut + if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut + endif + if (i_is_Sticky) then + thisRcut = getStickyCut(i) + if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut + endif + if (i_is_StickyP) then + thisRcut = getStickyPowerCut(i) + if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut + endif + if (i_is_GB) then + thisRcut = getGayBerneCut(i) + if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut + endif + if (i_is_EAM) then + thisRcut = getEAMCut(i) + if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut + endif + if (i_is_Shape) then + thisRcut = getShapeCut(i) + if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut + endif + endif + + + if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then + biggestAtypeCutoff = atypeMaxCutoff(i) + endif + + endif + enddo + + + + istart = 1 + jstart = 1 +#ifdef IS_MPI + iend = nGroupsInRow + jend = nGroupsInCol +#else + iend = nGroups + jend = nGroups +#endif + + !! allocate the groupToGtype and gtypeMaxCutoff here. + if(.not.allocated(groupToGtypeRow)) then + ! allocate(groupToGtype(iend)) + allocate(groupToGtypeRow(iend)) + else + deallocate(groupToGtypeRow) + allocate(groupToGtypeRow(iend)) + endif + if(.not.allocated(groupMaxCutoffRow)) then + allocate(groupMaxCutoffRow(iend)) + else + deallocate(groupMaxCutoffRow) + allocate(groupMaxCutoffRow(iend)) + end if + + if(.not.allocated(gtypeMaxCutoffRow)) then + allocate(gtypeMaxCutoffRow(iend)) + else + deallocate(gtypeMaxCutoffRow) + allocate(gtypeMaxCutoffRow(iend)) + endif + + +#ifdef IS_MPI + ! We only allocate new storage if we are in MPI because Ncol /= Nrow + if(.not.associated(groupToGtypeCol)) then + allocate(groupToGtypeCol(jend)) + else + deallocate(groupToGtypeCol) + allocate(groupToGtypeCol(jend)) + end if + + if(.not.associated(groupToGtypeCol)) then + allocate(groupToGtypeCol(jend)) + else + deallocate(groupToGtypeCol) + allocate(groupToGtypeCol(jend)) + end if + if(.not.associated(gtypeMaxCutoffCol)) then + allocate(gtypeMaxCutoffCol(jend)) + else + deallocate(gtypeMaxCutoffCol) + allocate(gtypeMaxCutoffCol(jend)) + end if + + groupMaxCutoffCol = 0.0_dp + gtypeMaxCutoffCol = 0.0_dp + +#endif + groupMaxCutoffRow = 0.0_dp + gtypeMaxCutoffRow = 0.0_dp + + + !! first we do a single loop over the cutoff groups to find the + !! largest cutoff for any atypes present in this group. We also + !! create gtypes at this point. + + tol = 1.0d-6 + nGroupTypesRow = 0 + + do i = istart, iend + n_in_i = groupStartRow(i+1) - groupStartRow(i) + groupMaxCutoffRow(i) = 0.0_dp + do ia = groupStartRow(i), groupStartRow(i+1)-1 + atom1 = groupListRow(ia) +#ifdef IS_MPI + me_i = atid_row(atom1) +#else + me_i = atid(atom1) +#endif + if (atypeMaxCutoff(me_i).gt.groupMaxCutoffRow(i)) then + groupMaxCutoffRow(i)=atypeMaxCutoff(me_i) + endif + enddo + + if (nGroupTypesRow.eq.0) then + nGroupTypesRow = nGroupTypesRow + 1 + gtypeMaxCutoffRow(nGroupTypesRow) = groupMaxCutoffRow(i) + groupToGtypeRow(i) = nGroupTypesRow + else + GtypeFound = .false. + do g = 1, nGroupTypesRow + if ( abs(groupMaxCutoffRow(i) - gtypeMaxCutoffRow(g)).lt.tol) then + groupToGtypeRow(i) = g + GtypeFound = .true. + endif + enddo + if (.not.GtypeFound) then + nGroupTypesRow = nGroupTypesRow + 1 + gtypeMaxCutoffRow(nGroupTypesRow) = groupMaxCutoffRow(i) + groupToGtypeRow(i) = nGroupTypesRow + endif + endif + enddo + +#ifdef IS_MPI + do j = jstart, jend + n_in_j = groupStartCol(j+1) - groupStartCol(j) + groupMaxCutoffCol(j) = 0.0_dp + do ja = groupStartCol(j), groupStartCol(j+1)-1 + atom1 = groupListCol(ja) + + me_j = atid_col(atom1) + + if (atypeMaxCutoff(me_j).gt.groupMaxCutoffCol(j)) then + groupMaxCutoffCol(j)=atypeMaxCutoff(me_j) + endif + enddo + + if (nGroupTypesCol.eq.0) then + nGroupTypesCol = nGroupTypesCol + 1 + gtypeMaxCutoffCol(nGroupTypesCol) = groupMaxCutoffCol(j) + groupToGtypeCol(j) = nGroupTypesCol + else + GtypeFound = .false. + do g = 1, nGroupTypesCol + if ( abs(groupMaxCutoffCol(j) - gtypeMaxCutoffCol(g)).lt.tol) then + groupToGtypeCol(j) = g + GtypeFound = .true. + endif + enddo + if (.not.GtypeFound) then + nGroupTypesCol = nGroupTypesCol + 1 + gtypeMaxCutoffCol(nGroupTypesCol) = groupMaxCutoffCol(j) + groupToGtypeCol(j) = nGroupTypesCol + endif + endif + enddo +#else +! Set pointers to information we just found + nGroupTypesCol = nGroupTypesRow + groupToGtypeCol => groupToGtypeRow + gtypeMaxCutoffCol => gtypeMaxCutoffRow + groupMaxCutoffCol => groupMaxCutoffRow +#endif + + + + + + !! allocate the gtypeCutoffMap here. + allocate(gtypeCutoffMap(nGroupTypesRow,nGroupTypesCol)) + !! then we do a double loop over all the group TYPES to find the cutoff + !! map between groups of two types + tradRcut = max(maxval(gtypeMaxCutoffRow),maxval(gtypeMaxCutoffCol)) + + do i = 1, nGroupTypesRow + do j = 1, nGroupTypesCol + + select case(cutoffPolicy) + case(TRADITIONAL_CUTOFF_POLICY) + thisRcut = tradRcut + case(MIX_CUTOFF_POLICY) + thisRcut = 0.5_dp * (gtypeMaxCutoffRow(i) + gtypeMaxCutoffCol(j)) + case(MAX_CUTOFF_POLICY) + thisRcut = max(gtypeMaxCutoffRow(i), gtypeMaxCutoffCol(j)) + case default + call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy") + return + end select + gtypeCutoffMap(i,j)%rcut = thisRcut + gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut + skin = defaultRlist - defaultRcut + listSkin = skin ! set neighbor list skin thickness + gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2 + + ! sanity check + + if (haveDefaultCutoffs) then + if (abs(gtypeCutoffMap(i,j)%rcut - defaultRcut).gt.0.0001) then + call handleError("createGtypeCutoffMap", "user-specified rCut does not match computed group Cutoff") + endif + endif + enddo + enddo + if(allocated(gtypeMaxCutoffRow)) deallocate(gtypeMaxCutoffRow) + if(allocated(groupMaxCutoffRow)) deallocate(groupMaxCutoffRow) + if(allocated(atypeMaxCutoff)) deallocate(atypeMaxCutoff) +#ifdef IS_MPI + if(associated(groupMaxCutoffCol)) deallocate(groupMaxCutoffCol) + if(associated(gtypeMaxCutoffCol)) deallocate(gtypeMaxCutoffCol) +#endif + groupMaxCutoffCol => null() + gtypeMaxCutoffCol => null() + + haveGtypeCutoffMap = .true. + end subroutine createGtypeCutoffMap + + subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy) + real(kind=dp),intent(in) :: defRcut, defRsw, defRlist + integer, intent(in) :: cutPolicy + + defaultRcut = defRcut + defaultRsw = defRsw + defaultRlist = defRlist + cutoffPolicy = cutPolicy + + haveDefaultCutoffs = .true. + end subroutine setDefaultCutoffs + + subroutine setCutoffPolicy(cutPolicy) + + integer, intent(in) :: cutPolicy + cutoffPolicy = cutPolicy + call createGtypeCutoffMap() + end subroutine setCutoffPolicy + + subroutine setSimVariables() SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms() - SIM_uses_LennardJones = SimUsesLennardJones() - SIM_uses_Electrostatics = SimUsesElectrostatics() - SIM_uses_Charges = SimUsesCharges() - SIM_uses_Dipoles = SimUsesDipoles() - SIM_uses_Sticky = SimUsesSticky() - SIM_uses_StickyPower = SimUsesStickyPower() - SIM_uses_GayBerne = SimUsesGayBerne() SIM_uses_EAM = SimUsesEAM() - SIM_uses_Shapes = SimUsesShapes() - SIM_uses_FLARB = SimUsesFLARB() - SIM_uses_RF = SimUsesRF() SIM_requires_postpair_calc = SimRequiresPostpairCalc() SIM_requires_prepair_calc = SimRequiresPrepairCalc() SIM_uses_PBC = SimUsesPBC() @@ -249,14 +586,21 @@ contains error = 0 - if (.not. havePropertyMap) then + if (.not. haveInteractionHash) then + myStatus = 0 + call createInteractionHash(myStatus) + if (myStatus .ne. 0) then + write(default_error, *) 'createInteractionHash failed in doForces!' + error = -1 + return + endif + endif - myStatus = 0 - - call createPropertyMap(myStatus) - + if (.not. haveGtypeCutoffMap) then + myStatus = 0 + call createGtypeCutoffMap(myStatus) if (myStatus .ne. 0) then - write(default_error, *) 'createPropertyMap failed in doForces!' + write(default_error, *) 'createGtypeCutoffMap failed in doForces!' error = -1 return endif @@ -266,11 +610,11 @@ contains call setSimVariables() endif - if (.not. haveRlist) then - write(default_error, *) 'rList has not been set in doForces!' - error = -1 - return - endif + ! if (.not. haveRlist) then + ! write(default_error, *) 'rList has not been set in doForces!' + ! error = -1 + ! return + ! endif if (.not. haveNeighborList) then write(default_error, *) 'neighbor list has not been initialized in doForces!' @@ -295,10 +639,9 @@ contains end subroutine doReadyCheck - subroutine init_FF(use_RF_c, thisStat) + subroutine init_FF(thisESM, thisStat) - logical, intent(in) :: use_RF_c - + integer, intent(in) :: thisESM integer, intent(out) :: thisStat integer :: my_status, nMatches integer, pointer :: MatchList(:) => null() @@ -307,8 +650,7 @@ contains !! assume things are copacetic, unless they aren't thisStat = 0 - !! Fortran's version of a cast: - FF_uses_RF = use_RF_c + electrostaticSummationMethod = thisESM !! init_FF is called *after* all of the atom types have been !! defined in atype_module using the new_atype subroutine. @@ -317,101 +659,37 @@ contains !! interactions are used by the force field. FF_uses_DirectionalAtoms = .false. - FF_uses_LennardJones = .false. - FF_uses_Electrostatics = .false. - FF_uses_Charges = .false. FF_uses_Dipoles = .false. - FF_uses_Sticky = .false. - FF_uses_StickyPower = .false. FF_uses_GayBerne = .false. FF_uses_EAM = .false. - FF_uses_Shapes = .false. - FF_uses_FLARB = .false. call getMatchingElementList(atypes, "is_Directional", .true., & nMatches, MatchList) if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true. - call getMatchingElementList(atypes, "is_LennardJones", .true., & - nMatches, MatchList) - if (nMatches .gt. 0) FF_uses_LennardJones = .true. - - call getMatchingElementList(atypes, "is_Electrostatic", .true., & - nMatches, MatchList) - if (nMatches .gt. 0) then - FF_uses_Electrostatics = .true. - endif - - call getMatchingElementList(atypes, "is_Charge", .true., & - nMatches, MatchList) - if (nMatches .gt. 0) then - FF_uses_Charges = .true. - FF_uses_Electrostatics = .true. - endif - call getMatchingElementList(atypes, "is_Dipole", .true., & nMatches, MatchList) - if (nMatches .gt. 0) then - FF_uses_Dipoles = .true. - FF_uses_Electrostatics = .true. - FF_uses_DirectionalAtoms = .true. - endif - - call getMatchingElementList(atypes, "is_Quadrupole", .true., & - nMatches, MatchList) - if (nMatches .gt. 0) then - FF_uses_Quadrupoles = .true. - FF_uses_Electrostatics = .true. - FF_uses_DirectionalAtoms = .true. - endif - - call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, & - MatchList) - if (nMatches .gt. 0) then - FF_uses_Sticky = .true. - FF_uses_DirectionalAtoms = .true. - endif - - call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, & - MatchList) - if (nMatches .gt. 0) then - FF_uses_StickyPower = .true. - FF_uses_DirectionalAtoms = .true. - endif + if (nMatches .gt. 0) FF_uses_Dipoles = .true. call getMatchingElementList(atypes, "is_GayBerne", .true., & nMatches, MatchList) - if (nMatches .gt. 0) then - FF_uses_GayBerne = .true. - FF_uses_DirectionalAtoms = .true. - endif + if (nMatches .gt. 0) FF_uses_GayBerne = .true. call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList) if (nMatches .gt. 0) FF_uses_EAM = .true. - call getMatchingElementList(atypes, "is_Shape", .true., & - nMatches, MatchList) - if (nMatches .gt. 0) then - FF_uses_Shapes = .true. - FF_uses_DirectionalAtoms = .true. - endif - call getMatchingElementList(atypes, "is_FLARB", .true., & - nMatches, MatchList) - if (nMatches .gt. 0) FF_uses_FLARB = .true. - - !! Assume sanity (for the sake of argument) haveSaneForceField = .true. - !! check to make sure the FF_uses_RF setting makes sense + !! check to make sure the reaction field setting makes sense - if (FF_uses_dipoles) then - if (FF_uses_RF) then + if (FF_uses_Dipoles) then + if (electrostaticSummationMethod == REACTION_FIELD) then dielect = getDielect() call initialize_rf(dielect) endif else - if (FF_uses_RF) then + if (electrostaticSummationMethod == REACTION_FIELD) then write(default_error,*) 'Using Reaction Field with no dipoles? Huh?' thisStat = -1 haveSaneForceField = .false. @@ -419,16 +697,6 @@ contains endif endif - !sticky module does not contain check_sticky_FF anymore - !if (FF_uses_sticky) then - ! call check_sticky_FF(my_status) - ! if (my_status /= 0) then - ! thisStat = -1 - ! haveSaneForceField = .false. - ! return - ! end if - !endif - if (FF_uses_EAM) then call init_EAM_FF(my_status) if (my_status /= 0) then @@ -448,9 +716,6 @@ contains endif endif - if (FF_uses_GayBerne .and. FF_uses_LennardJones) then - endif - if (.not. haveNeighborList) then !! Create neighbor lists call expandNeighborList(nLocal, my_status) @@ -484,13 +749,13 @@ contains !! Stress Tensor real( kind = dp), dimension(9) :: tau - real ( kind = dp ) :: pot + real ( kind = dp ),dimension(POT_ARRAY_SIZE) :: pot logical ( kind = 2) :: do_pot_c, do_stress_c logical :: do_pot logical :: do_stress logical :: in_switching_region #ifdef IS_MPI - real( kind = DP ) :: pot_local + real( kind = DP ), dimension(POT_ARRAY_SIZE) :: pot_local integer :: nAtomsInRow integer :: nAtomsInCol integer :: nprocs @@ -514,9 +779,9 @@ contains integer :: localError integer :: propPack_i, propPack_j integer :: loopStart, loopEnd, loop + integer :: iHash + - real(kind=dp) :: listSkin = 1.0 - !! initialize local variables #ifdef IS_MPI @@ -633,14 +898,16 @@ contains endif #ifdef IS_MPI + me_j = atid_col(j) call get_interatomic_vector(q_group_Row(:,i), & q_group_Col(:,j), d_grp, rgrpsq) #else + me_j = atid(j) call get_interatomic_vector(q_group(:,i), & q_group(:,j), d_grp, rgrpsq) -#endif +#endif - if (rgrpsq < rlistsq) then + if (rgrpsq < gtypeCutoffMap(groupToGtypeRow(i),groupToGtypeCol(j))%rListsq) then if (update_nlist) then nlist = nlist + 1 @@ -761,6 +1028,7 @@ contains endif end if enddo + enddo outer if (update_nlist) then @@ -840,7 +1108,7 @@ contains if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then - if (FF_uses_RF .and. SIM_uses_RF) then + if (electrostaticSummationMethod == REACTION_FIELD) then #ifdef IS_MPI call scatter(rf_Row,rf,plan_atom_row_3d) @@ -858,9 +1126,10 @@ contains #else me_i = atid(i) #endif + iHash = InteractionHash(me_i,me_j) + + if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then - if (PropertyMap(me_i)%is_Dipole) then - mu_i = getDipoleMoment(me_i) !! The reaction field needs to include a self contribution @@ -870,9 +1139,9 @@ contains !! potential and torques: call reaction_field_final(i, mu_i, eFrame, rfpot, t, do_pot) #ifdef IS_MPI - pot_local = pot_local + rfpot + pot_local(RF_POT) = pot_local(RF_POT) + rfpot #else - pot = pot + rfpot + pot(RF_POT) = pot(RF_POT) + rfpot #endif endif @@ -884,7 +1153,8 @@ contains #ifdef IS_MPI if (do_pot) then - pot = pot + pot_local + pot(1:SIZE_POT_ARRAY) = pot(1:SIZE_POT_ARRAY) & + + pot_local(1:SIZE_POT_ARRAY) !! we assume the c code will do the allreduce to get the total potential !! we could do it right here if we needed to... endif @@ -910,7 +1180,8 @@ contains subroutine do_pair(i, j, rijsq, d, sw, do_pot, & eFrame, A, f, t, pot, vpair, fpair) - real( kind = dp ) :: pot, vpair, sw + real( kind = dp ) :: vpair, sw + real( kind = dp ), dimension(POT_ARRAY_SIZE) :: pot real( kind = dp ), dimension(3) :: fpair real( kind = dp ), dimension(nLocal) :: mfact real( kind = dp ), dimension(9,nLocal) :: eFrame @@ -923,9 +1194,10 @@ contains real ( kind = dp ), intent(inout) :: rijsq real ( kind = dp ) :: r real ( kind = dp ), intent(inout) :: d(3) - real ( kind = dp ) :: ebalance integer :: me_i, me_j + integer :: iHash + r = sqrt(rijsq) vpair = 0.0d0 fpair(1:3) = 0.0d0 @@ -938,97 +1210,67 @@ contains me_j = atid(j) #endif - ! write(*,*) i, j, me_i, me_j + iHash = InteractionHash(me_i, me_j) - if (FF_uses_LennardJones .and. SIM_uses_LennardJones) then - - if ( PropertyMap(me_i)%is_LennardJones .and. & - PropertyMap(me_j)%is_LennardJones ) then - call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot) - endif - + if ( iand(iHash, LJ_PAIR).ne.0 ) then + call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot(LJ_POT), f, do_pot) endif - if (FF_uses_Electrostatics .and. SIM_uses_Electrostatics) then + if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then + call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, & + pot(ELECTROSTATIC_POT), eFrame, f, t, do_pot) - if (PropertyMap(me_i)%is_Electrostatic .and. & - PropertyMap(me_j)%is_Electrostatic) then - call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, & - pot, eFrame, f, t, do_pot, ebalance) - endif + if (electrostaticSummationMethod == REACTION_FIELD) then - if (FF_uses_dipoles .and. SIM_uses_dipoles) then - if ( PropertyMap(me_i)%is_Dipole .and. & - PropertyMap(me_j)%is_Dipole) then - if (FF_uses_RF .and. SIM_uses_RF) then - call accumulate_rf(i, j, r, eFrame, sw) - call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair) - endif - endif + ! CHECK ME (RF needs to know about all electrostatic types) + call accumulate_rf(i, j, r, eFrame, sw) + call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair) endif + endif - - if (FF_uses_Sticky .and. SIM_uses_sticky) then - - if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then - call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, & - pot, A, f, t, do_pot) - endif - + if ( iand(iHash, STICKY_PAIR).ne.0 ) then + call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, & + pot(STICKY_POT), A, f, t, do_pot) endif - if (FF_uses_StickyPower .and. SIM_uses_stickypower) then - if ( PropertyMap(me_i)%is_StickyPower .and. & - PropertyMap(me_j)%is_StickyPower) then - call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, & - pot, A, f, t, do_pot, ebalance) - endif + if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then + call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, & + pot(STICKYPOWER_POT), A, f, t, do_pot) endif - - if (FF_uses_GayBerne .and. SIM_uses_GayBerne) then - if ( PropertyMap(me_i)%is_GayBerne .and. & - PropertyMap(me_j)%is_GayBerne) then - call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, & - pot, A, f, t, do_pot) - endif - + if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then + call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, & + pot(GAYBERNE_POT), A, f, t, do_pot) endif + + if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then + ! call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, & + ! pot(GAYBERNE_LJ_POT), A, f, t, do_pot) + endif - if (FF_uses_EAM .and. SIM_uses_EAM) then - - if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then - call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, & - do_pot) - endif - + if ( iand(iHash, EAM_PAIR).ne.0 ) then + call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot(EAM_POT), f, & + do_pot) endif - - ! write(*,*) PropertyMap(me_i)%is_Shape,PropertyMap(me_j)%is_Shape - - if (FF_uses_Shapes .and. SIM_uses_Shapes) then - if ( PropertyMap(me_i)%is_Shape .and. & - PropertyMap(me_j)%is_Shape ) then - call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, & - pot, A, f, t, do_pot) - endif - if ( (PropertyMap(me_i)%is_Shape .and. & - PropertyMap(me_j)%is_LennardJones) .or. & - (PropertyMap(me_i)%is_LennardJones .and. & - PropertyMap(me_j)%is_Shape) ) then - call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, & - pot, A, f, t, do_pot) - endif + if ( iand(iHash, SHAPE_PAIR).ne.0 ) then + call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, & + pot(SHAPE_POT), A, f, t, do_pot) endif + if ( iand(iHash, SHAPE_LJ).ne.0 ) then + call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, & + pot(SHAPE_LJ_POT), A, f, t, do_pot) + endif + end subroutine do_pair subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, & do_pot, do_stress, eFrame, A, f, t, pot) - real( kind = dp ) :: pot, sw + real( kind = dp ) :: sw + real( kind = dp ), dimension(POT_ARRAY_SIZE) :: pot real( kind = dp ), dimension(9,nLocal) :: eFrame real (kind=dp), dimension(9,nLocal) :: A real (kind=dp), dimension(3,nLocal) :: f @@ -1040,19 +1282,10 @@ contains real ( kind = dp ) :: r, rc real ( kind = dp ), intent(inout) :: d(3), dc(3) - logical :: is_EAM_i, is_EAM_j + integer :: me_i, me_j, iHash - integer :: me_i, me_j - - r = sqrt(rijsq) - if (SIM_uses_molecular_cutoffs) then - rc = sqrt(rcijsq) - else - rc = r - endif - #ifdef IS_MPI me_i = atid_row(i) me_j = atid_col(j) @@ -1061,22 +1294,21 @@ contains me_j = atid(j) #endif - if (FF_uses_EAM .and. SIM_uses_EAM) then + iHash = InteractionHash(me_i, me_j) - if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) & + if ( iand(iHash, EAM_PAIR).ne.0 ) then call calc_EAM_prepair_rho(i, j, d, r, rijsq ) - endif - + end subroutine do_prepair subroutine do_preforce(nlocal,pot) integer :: nlocal - real( kind = dp ) :: pot + real( kind = dp ),dimension(POT_ARRAY_SIZE) :: pot if (FF_uses_EAM .and. SIM_uses_EAM) then - call calc_EAM_preforce_Frho(nlocal,pot) + call calc_EAM_preforce_Frho(nlocal,pot(EAM_POT)) endif @@ -1261,9 +1493,7 @@ contains function FF_UsesDirectionalAtoms() result(doesit) logical :: doesit - doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. & - FF_uses_Quadrupoles .or. FF_uses_Sticky .or. & - FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes + doesit = FF_uses_DirectionalAtoms end function FF_UsesDirectionalAtoms function FF_RequiresPrepairCalc() result(doesit) @@ -1273,7 +1503,7 @@ contains function FF_RequiresPostpairCalc() result(doesit) logical :: doesit - doesit = FF_uses_RF + if (electrostaticSummationMethod == REACTION_FIELD) doesit = .true. end function FF_RequiresPostpairCalc #ifdef PROFILE