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

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/suttonchen.F90 (file contents):
Revision 2401 by chuckv, Tue Nov 1 18:29:57 2005 UTC vs.
Revision 2434 by chuckv, Tue Nov 15 16:18:36 2005 UTC

# Line 63 | Line 63 | module suttonchen
63    integer, save :: SC_Mixing_Policy
64    real(kind = dp), save :: SC_rcut
65    logical, save :: haveRcut = .false.
66 +  logical, save :: haveMixingMap = .false.
67 +  logical, save :: useGeometricDistanceMixing = .false.
68  
69 +
70 +
71 +
72    character(len = statusMsgSize) :: errMesg
73 <  integer :: eam_err
73 >  integer :: sc_err
74  
75    character(len = 200) :: errMsg
76    character(len=*), parameter :: RoutineName =  "Sutton-Chen MODULE"
# Line 76 | Line 81 | module suttonchen
81  
82    type, private :: SCtype
83       integer           :: atid      
84 <     real(kind=dp)     :: c
84 >     real(kind=dp)     :: c
85       real(kind=dp)     :: m
86       real(kind=dp)     :: n
87       real(kind=dp)     :: alpha
88       real(kind=dp)     :: epsilon
89 +     real(kind=dp)     :: sc_rcut
90    end type SCtype
91  
92  
93    !! Arrays for derivatives used in force calculation
88  real( kind = dp), dimension(:), allocatable :: frho
94    real( kind = dp), dimension(:), allocatable :: rho
95 <
95 >  real( kind = dp), dimension(:), allocatable :: frho
96    real( kind = dp), dimension(:), allocatable :: dfrhodrho
92  real( kind = dp), dimension(:), allocatable :: d2frhodrhodrho
97  
98  
99 +
100    !! Arrays for MPI storage
101   #ifdef IS_MPI
102    real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_col
# Line 101 | Line 106 | module suttonchen
106    real( kind = dp),save, dimension(:), allocatable :: rho_row
107    real( kind = dp),save, dimension(:), allocatable :: rho_col
108    real( kind = dp),save, dimension(:), allocatable :: rho_tmp
104  real( kind = dp),save, dimension(:), allocatable :: d2frhodrhodrho_col
105  real( kind = dp),save, dimension(:), allocatable :: d2frhodrhodrho_row
109   #endif
110  
111    type, private :: SCTypeList
# Line 113 | Line 116 | module suttonchen
116       integer, pointer         :: atidToSCtype(:) => null()
117    end type SCTypeList
118  
116
119    type (SCTypeList), save :: SCList
120  
119  !! standard eam stuff  
121  
122  
123 <  public :: init_SC_FF
123 >
124 > type :: MixParameters
125 >     real(kind=DP) :: alpha
126 >     real(kind=DP) :: epsilon
127 >     real(kind=DP) :: m
128 >     real(Kind=DP) :: n
129 >     real(kind=DP) :: vpair_pot
130 >     real(kind=dp) :: rCut
131 >     logical       :: rCutWasSet = .false.
132 >
133 >  end type MixParameters
134 >
135 >  type(MixParameters), dimension(:,:), allocatable :: MixingMap
136 >
137 >
138 >
139    public :: setCutoffSC
140    public :: do_SC_pair
141    public :: newSCtype
142    public :: calc_SC_prepair_rho
143 +  public :: calc_SC_preforce_Frho
144    public :: clean_SC
145    public :: destroySCtypes
146    public :: getSCCut
147 + ! public :: setSCDefaultCutoff
148 + ! public :: setSCUniformCutoff
149 +  public :: useGeometricMixing
150  
151   contains
152  
153  
154 <  subroutine newEAMtype(lattice_constant,eam_nrho,eam_drho,eam_nr,&
155 <       eam_dr,rcut,eam_Z_r,eam_rho_r,eam_F_rho,&
156 <       c_ident,status)
157 <    real (kind = dp )                      :: lattice_constant
158 <    integer                                :: eam_nrho
159 <    real (kind = dp )                      :: eam_drho
160 <    integer                                :: eam_nr
161 <    real (kind = dp )                      :: eam_dr
142 <    real (kind = dp )                      :: rcut
143 <    real (kind = dp ), dimension(eam_nr)   :: eam_Z_r
144 <    real (kind = dp ), dimension(eam_nr)   :: eam_rho_r
145 <    real (kind = dp ), dimension(eam_nrho) :: eam_F_rho
154 >  subroutine newSCtype(c_ident,c,m,n,alpha,epsilon,status)
155 >    real (kind = dp )                      :: c ! Density Scaling
156 >    real (kind = dp )                      :: m ! Density Exponent
157 >    real (kind = dp )                      :: n ! Pair Potential Exponent
158 >    real (kind = dp )                      :: alpha ! Length Scaling
159 >    real (kind = dp )                      :: epsilon ! Energy Scaling
160 >
161 >
162      integer                                :: c_ident
163      integer                                :: status
164  
165 <    integer                                :: nAtypes,nEAMTypes,myATID
165 >    integer                                :: nAtypes,nSCTypes,myATID
166      integer                                :: maxVals
167      integer                                :: alloc_stat
168      integer                                :: current
# Line 156 | Line 172 | contains
172  
173  
174      !! Assume that atypes has already been set and get the total number of types in atypes
159    !! Also assume that every member of atypes is a EAM model.
175  
176  
177      ! check to see if this is the first time into
178 <    if (.not.associated(EAMList%EAMParams)) then
179 <       call getMatchingElementList(atypes, "is_EAM", .true., nEAMtypes, MatchList)
180 <       EAMList%n_eam_types = nEAMtypes
181 <       allocate(EAMList%EAMParams(nEAMTypes))
178 >    if (.not.associated(SCList%SCTypes)) then
179 >       call getMatchingElementList(atypes, "is_SuttonChen", .true., nSCtypes, MatchList)
180 >       SCList%nSCtypes = nSCtypes
181 >       allocate(SCList%SCTypes(nSCTypes))
182         nAtypes = getSize(atypes)
183 <       allocate(EAMList%atidToEAMType(nAtypes))
183 >       allocate(SCList%atidToSCType(nAtypes))
184      end if
185  
186 <    EAMList%currentAddition = EAMList%currentAddition + 1
187 <    current = EAMList%currentAddition
186 >    SCList%currentSCType = SCList%currentSCType + 1
187 >    current = SCList%currentSCType
188  
189      myATID =  getFirstMatchingElement(atypes, "c_ident", c_ident)
190 <    EAMList%atidToEAMType(myATID) = current
190 >    SCList%atidToSCType(myATID) = current
191  
177    call allocate_EAMType(eam_nrho,eam_nr,EAMList%EAMParams(current),stat=alloc_stat)
178    if (alloc_stat /= 0) then
179       status = -1
180       return
181    end if
192  
193    
194 <    EAMList%EAMParams(current)%eam_atype    = c_ident
195 <    EAMList%EAMParams(current)%eam_lattice  = lattice_constant
196 <    EAMList%EAMParams(current)%eam_nrho     = eam_nrho
197 <    EAMList%EAMParams(current)%eam_drho     = eam_drho
198 <    EAMList%EAMParams(current)%eam_nr       = eam_nr
199 <    EAMList%EAMParams(current)%eam_dr       = eam_dr
200 <    EAMList%EAMParams(current)%eam_rcut     = rcut
191 <    EAMList%EAMParams(current)%eam_Z_r      = eam_Z_r
192 <    EAMList%EAMParams(current)%eam_rho_r    = eam_rho_r
193 <    EAMList%EAMParams(current)%eam_F_rho    = eam_F_rho
194 <
195 <  end subroutine newEAMtype
196 <
197 <
198 <  ! kills all eam types entered and sets simulation to uninitalized
199 <  subroutine destroyEAMtypes()
200 <    integer :: i
201 <    type(EAMType), pointer :: tempEAMType=>null()
202 <
203 <    do i = 1, EAMList%n_eam_types
204 <       tempEAMType => eamList%EAMParams(i)
205 <       call deallocate_EAMType(tempEAMType)
206 <    end do
207 <    if(associated( eamList%EAMParams)) deallocate( eamList%EAMParams)
208 <    eamList%EAMParams => null()
209 <
210 <    eamList%n_eam_types = 0
211 <    eamList%currentAddition = 0
212 <
213 <  end subroutine destroyEAMtypes
194 >    SCList%SCTypes(current)%atid         = c_ident
195 >    SCList%SCTypes(current)%alpha        = alpha
196 >    SCList%SCTypes(current)%c            = c
197 >    SCList%SCTypes(current)%m            = m
198 >    SCList%SCTypes(current)%n            = n
199 >    SCList%SCTypes(current)%epsilon      = epsilon
200 >  end subroutine newSCtype
201  
202 <  function getEAMCut(atomID) result(cutValue)
202 >  
203 >  subroutine destroySCTypes()
204 >    if (associated(SCList%SCtypes)) then
205 >       deallocate(SCList%SCTypes)
206 >       SCList%SCTypes=>null()
207 >    end if
208 >    if (associated(SCList%atidToSCtype)) then
209 >       deallocate(SCList%atidToSCtype)
210 >       SCList%atidToSCtype=>null()
211 >    end if
212 >
213 >
214 >  end subroutine destroySCTypes
215 >
216 >
217 >
218 >  function getSCCut(atomID) result(cutValue)
219      integer, intent(in) :: atomID
220 <    integer :: eamID
220 >    integer :: scID
221      real(kind=dp) :: cutValue
222      
223 <    eamID = EAMList%atidToEAMType(atomID)
224 <    cutValue = EAMList%EAMParams(eamID)%eam_rcut
225 <  end function getEAMCut
223 >    scID = SCList%atidToSCType(atomID)
224 >    cutValue = SCList%SCTypes(scID)%sc_rcut
225 >  end function getSCCut
226  
224  subroutine init_EAM_FF(status)
225    integer :: status
226    integer :: i,j
227    real(kind=dp) :: current_rcut_max
228    integer :: alloc_stat
229    integer :: number_r, number_rho
227  
228  
229 <    status = 0
230 <    if (EAMList%currentAddition == 0) then
231 <       call handleError("init_EAM_FF","No members in EAMList")
232 <       status = -1
229 >
230 >  subroutine createMixingMap()
231 >    integer :: nSCtypes, i, j
232 >    real ( kind = dp ) :: e1, e2,m1,m2,alpha1,alpha2,n1,n2
233 >    real ( kind = dp ) :: rcut6, tp6, tp12
234 >    logical :: isSoftCore1, isSoftCore2, doShift
235 >
236 >    if (SCList%currentSCtype == 0) then
237 >       call handleError("SuttonChen", "No members in SCMap")
238         return
239      end if
240  
241 +    nSCtypes = SCList%nSCtypes
242  
243 <    do i = 1, EAMList%currentAddition
243 >    if (.not. allocated(MixingMap)) then
244 >       allocate(MixingMap(nSCtypes, nSCtypes))
245 >    endif
246  
247 <       ! Build array of r values
247 >    do i = 1, nSCtypes
248  
249 <       do j = 1,EAMList%EAMParams(i)%eam_nr
250 <          EAMList%EAMParams(i)%eam_rvals(j) = &
251 <               real(j-1,kind=dp)* &
252 <               EAMList%EAMParams(i)%eam_dr
248 <       end do
249 <       ! Build array of rho values
250 <       do j = 1,EAMList%EAMParams(i)%eam_nrho
251 <          EAMList%EAMParams(i)%eam_rhovals(j) = &
252 <               real(j-1,kind=dp)* &
253 <               EAMList%EAMParams(i)%eam_drho
254 <       end do
255 <       ! convert from eV to kcal / mol:
256 <       EAMList%EAMParams(i)%eam_F_rho = EAMList%EAMParams(i)%eam_F_rho * 23.06054E0_DP
249 >       e1 = SCList%SCtypes(i)%epsilon
250 >       m1 = SCList%SCtypes(i)%m
251 >       n1 = SCList%SCtypes(i)%n
252 >       alpha1 = SCList%SCtypes(i)%alpha
253  
254 <       ! precompute the pair potential and get it into kcal / mol:
255 <       EAMList%EAMParams(i)%eam_phi_r(1) = 0.0E0_DP
260 <       do j = 2, EAMList%EAMParams(i)%eam_nr
261 <          EAMList%EAMParams(i)%eam_phi_r(j) = (EAMList%EAMParams(i)%eam_Z_r(j)**2)/EAMList%EAMParams(i)%eam_rvals(j)
262 <          EAMList%EAMParams(i)%eam_phi_r(j) =  EAMList%EAMParams(i)%eam_phi_r(j)*331.999296E0_DP
263 <       enddo
264 <    end do
254 >       do j = i, nSCtypes
255 >          
256  
257 +          e2 = SCList%SCtypes(j)%epsilon
258 +          m2 = SCList%SCtypes(j)%m
259 +          n2 = SCList%SCtypes(j)%n
260 +          alpha2 = SCList%SCtypes(j)%alpha
261  
262 <    do i = 1,  EAMList%currentAddition
263 <       number_r   = EAMList%EAMParams(i)%eam_nr
264 <       number_rho = EAMList%EAMParams(i)%eam_nrho
262 >          if (useGeometricDistanceMixing) then
263 >             MixingMap(i,j)%alpha = sqrt(alpha1 * alpha2) !SC formulation
264 >          else
265 >             MixingMap(i,j)%alpha = 0.5_dp * (alpha1 + alpha2) ! Goddard formulation
266 >          endif
267  
268 <       call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
269 <            EAMList%EAMParams(i)%eam_rho_r, &
270 <            EAMList%EAMParams(i)%eam_rho_r_pp, &
271 <            0.0E0_DP, 0.0E0_DP, 'N')
272 <       call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
273 <            EAMList%EAMParams(i)%eam_Z_r, &
274 <            EAMList%EAMParams(i)%eam_Z_r_pp, &
275 <            0.0E0_DP, 0.0E0_DP, 'N')
276 <       call eam_spline(number_rho, EAMList%EAMParams(i)%eam_rhovals, &
277 <            EAMList%EAMParams(i)%eam_F_rho, &
278 <            EAMList%EAMParams(i)%eam_F_rho_pp, &
279 <            0.0E0_DP, 0.0E0_DP, 'N')
280 <       call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
281 <            EAMList%EAMParams(i)%eam_phi_r, &
282 <            EAMList%EAMParams(i)%eam_phi_r_pp, &
283 <            0.0E0_DP, 0.0E0_DP, 'N')
268 >          MixingMap(i,j)%epsilon = sqrt(e1 * e2)
269 >          MixingMap(i,j)%m = 0.5_dp*(m1+m2)
270 >          MixingMap(i,j)%n = 0.5_dp*(n1+n2)
271 >          MixingMap(i,j)%alpha = 0.5_dp*(alpha1+alpha2)
272 >          MixingMap(i,j)%rcut = 2.0_dp *MixingMap(i,j)%alpha
273 >          MixingMap(i,j)%vpair_pot = MixingMap(i,j)%epsilon* &
274 >               (MixingMap(i,j)%alpha/MixingMap(i,j)%rcut)**MixingMap(i,j)%n
275 >          if (i.ne.j) then
276 >             MixingMap(j,i)%epsilon    = MixingMap(i,j)%epsilon
277 >             MixingMap(j,i)%m          = MixingMap(i,j)%m
278 >             MixingMap(j,i)%n          = MixingMap(i,j)%n
279 >             MixingMap(j,i)%alpha      = MixingMap(i,j)%alpha
280 >             MixingMap(j,i)%rcut = MixingMap(i,j)%rcut
281 >             MixingMap(j,i)%vpair_pot = MixingMap(i,j)%vpair_pot
282 >          endif
283 >       enddo
284      enddo
285 +    
286 +    haveMixingMap = .true.
287 +    
288 +  end subroutine createMixingMap
289 +  
290  
289    !       current_rcut_max = EAMList%EAMParams(1)%eam_rcut
290    !! find the smallest rcut for any eam atype
291    !       do i = 2, EAMList%currentAddition
292    !          current_rcut_max =max(current_rcut_max,EAMList%EAMParams(i)%eam_rcut)
293    !       end do
294
295    !       EAM_rcut = current_rcut_max
296    !       EAM_rcut_orig = current_rcut_max
297    !       do i = 1, EAMList%currentAddition
298    !          EAMList%EAMParam(i)s%eam_atype_map(eam_atype(i)) = i
299    !       end do
300    !! Allocate arrays for force calculation
301
302    call allocateEAM(alloc_stat)
303    if (alloc_stat /= 0 ) then
304       write(*,*) "allocateEAM failed"
305       status = -1
306       return
307    endif
308
309  end subroutine init_EAM_FF
310
291    !! routine checks to see if array is allocated, deallocates array if allocated
292    !! and then creates the array to the required size
293 <  subroutine allocateEAM(status)
293 >  subroutine allocateSC(status)
294      integer, intent(out) :: status
295  
296   #ifdef IS_MPI
# Line 326 | Line 306 | contains
306      nAtomsInCol = getNatomsInCol(plan_atom_col)
307   #endif
308  
309 +
310 +
311      if (allocated(frho)) deallocate(frho)
312      allocate(frho(nlocal),stat=alloc_stat)
313 <    if (alloc_stat /= 0) then
313 >    if (alloc_stat /= 0) then
314         status = -1
315         return
316      end if
317 +
318      if (allocated(rho)) deallocate(rho)
319      allocate(rho(nlocal),stat=alloc_stat)
320      if (alloc_stat /= 0) then
# Line 346 | Line 329 | contains
329         return
330      end if
331  
349    if (allocated(d2frhodrhodrho)) deallocate(d2frhodrhodrho)
350    allocate(d2frhodrhodrho(nlocal),stat=alloc_stat)
351    if (alloc_stat /= 0) then
352       status = -1
353       return
354    end if
355
332   #ifdef IS_MPI
333  
334      if (allocated(rho_tmp)) deallocate(rho_tmp)
# Line 381 | Line 357 | contains
357         status = -1
358         return
359      end if
384    if (allocated(d2frhodrhodrho_row)) deallocate(d2frhodrhodrho_row)
385    allocate(d2frhodrhodrho_row(nAtomsInRow),stat=alloc_stat)
386    if (alloc_stat /= 0) then
387       status = -1
388       return
389    end if
360  
361  
362      ! Now do column arrays
# Line 409 | Line 379 | contains
379         status = -1
380         return
381      end if
412    if (allocated(d2frhodrhodrho_col)) deallocate(d2frhodrhodrho_col)
413    allocate(d2frhodrhodrho_col(nAtomsInCol),stat=alloc_stat)
414    if (alloc_stat /= 0) then
415       status = -1
416       return
417    end if
382  
383   #endif
384  
385 <  end subroutine allocateEAM
385 >  end subroutine allocateSC
386  
387    !! C sets rcut to be the largest cutoff of any atype
388    !! present in this simulation. Doesn't include all atypes
389    !! sim knows about, just those in the simulation.
390 <  subroutine setCutoffEAM(rcut, status)
390 >  subroutine setCutoffSC(rcut, status)
391      real(kind=dp) :: rcut
392      integer :: status
393      status = 0
394  
395 <    EAM_rcut = rcut
395 >    SC_rcut = rcut
396  
397 <  end subroutine setCutoffEAM
397 >  end subroutine setCutoffSC
398  
399 +  subroutine useGeometricMixing()
400 +    useGeometricDistanceMixing = .true.
401 +    haveMixingMap = .false.
402 +    return
403 +  end subroutine useGeometricMixing
404 +  
405  
406  
437  subroutine clean_EAM()
407  
408 +
409 +
410 +
411 +
412 +
413 +  subroutine clean_SC()
414 +
415      ! clean non-IS_MPI first
416      frho = 0.0_dp
417      rho  = 0.0_dp
# Line 450 | Line 426 | contains
426      dfrhodrho_row = 0.0_dp
427      dfrhodrho_col = 0.0_dp
428   #endif
429 <  end subroutine clean_EAM
429 >  end subroutine clean_SC
430  
431  
432  
457  subroutine allocate_EAMType(eam_n_rho,eam_n_r,thisEAMType,stat)
458    integer, intent(in)          :: eam_n_rho
459    integer, intent(in)          :: eam_n_r
460    type (EAMType)               :: thisEAMType
461    integer, optional   :: stat
462    integer             :: alloc_stat
463
464
465
466    if (present(stat)) stat = 0
467
468    allocate(thisEAMType%eam_rvals(eam_n_r),stat=alloc_stat)  
469    if (alloc_stat /= 0 ) then
470       if (present(stat)) stat = -1
471       return
472    end if
473    allocate(thisEAMType%eam_rhovals(eam_n_rho),stat=alloc_stat)  
474    if (alloc_stat /= 0 ) then
475       if (present(stat)) stat = -1
476       return
477    end if
478    allocate(thisEAMType%eam_F_rho(eam_n_rho),stat=alloc_stat)  
479    if (alloc_stat /= 0 ) then
480       if (present(stat)) stat = -1
481       return
482    end if
483    allocate(thisEAMType%eam_Z_r(eam_n_r),stat=alloc_stat)        
484    if (alloc_stat /= 0 ) then
485       if (present(stat)) stat = -1
486       return
487    end if
488    allocate(thisEAMType%eam_rho_r(eam_n_r),stat=alloc_stat)      
489    if (alloc_stat /= 0 ) then
490       if (present(stat)) stat = -1
491       return
492    end if
493    allocate(thisEAMType%eam_phi_r(eam_n_r),stat=alloc_stat)      
494    if (alloc_stat /= 0 ) then
495       if (present(stat)) stat = -1
496       return
497    end if
498    allocate(thisEAMType%eam_F_rho_pp(eam_n_rho),stat=alloc_stat)  
499    if (alloc_stat /= 0 ) then
500       if (present(stat)) stat = -1
501       return
502    end if
503    allocate(thisEAMType%eam_Z_r_pp(eam_n_r),stat=alloc_stat)  
504    if (alloc_stat /= 0 ) then
505       if (present(stat)) stat = -1
506       return
507    end if
508    allocate(thisEAMType%eam_rho_r_pp(eam_n_r),stat=alloc_stat)  
509    if (alloc_stat /= 0 ) then
510       if (present(stat)) stat = -1
511       return
512    end if
513    allocate(thisEAMType%eam_phi_r_pp(eam_n_r),stat=alloc_stat)
514    if (alloc_stat /= 0 ) then
515       if (present(stat)) stat = -1
516       return
517    end if
518
519
520  end subroutine allocate_EAMType
521
522
523  subroutine deallocate_EAMType(thisEAMType)
524    type (EAMtype), pointer :: thisEAMType
525
526    ! free Arrays in reverse order of allocation...
527    if(associated(thisEAMType%eam_phi_r_pp)) deallocate(thisEAMType%eam_phi_r_pp)      
528    if(associated(thisEAMType%eam_rho_r_pp)) deallocate(thisEAMType%eam_rho_r_pp)  
529    if(associated(thisEAMType%eam_Z_r_pp)) deallocate(thisEAMType%eam_Z_r_pp)  
530    if(associated(thisEAMType%eam_F_rho_pp)) deallocate(thisEAMType%eam_F_rho_pp)  
531    if(associated(thisEAMType%eam_phi_r)) deallocate(thisEAMType%eam_phi_r)      
532    if(associated(thisEAMType%eam_rho_r)) deallocate(thisEAMType%eam_rho_r)      
533    if(associated(thisEAMType%eam_Z_r)) deallocate(thisEAMType%eam_Z_r)  
534    if(associated(thisEAMType%eam_F_rho)) deallocate(thisEAMType%eam_F_rho)
535    if(associated(thisEAMType%eam_rhovals)) deallocate(thisEAMType%eam_rhovals)
536    if(associated(thisEAMType%eam_rvals)) deallocate(thisEAMType%eam_rvals)
537
538  end subroutine deallocate_EAMType
539
433    !! Calculates rho_r
434 <  subroutine calc_eam_prepair_rho(atom1,atom2,d,r,rijsq)
434 >  subroutine calc_sc_prepair_rho(atom1,atom2,d,r,rijsq)
435      integer :: atom1,atom2
436      real(kind = dp), dimension(3) :: d
437      real(kind = dp), intent(inout)               :: r
# Line 549 | Line 442 | contains
442      real(kind = dp) :: rho_j_at_i
443  
444      ! we don't use the derivatives, dummy variables
445 <    real( kind = dp) :: drho,d2rho
446 <    integer :: eam_err
445 >    real( kind = dp) :: drho
446 >    integer :: sc_err
447      
448      integer :: atid1,atid2 ! Global atid    
449      integer :: myid_atom1 ! EAM atid
# Line 570 | Line 463 | contains
463      Atid2 = Atid(Atom2)
464   #endif
465  
466 <    Myid_atom1 = Eamlist%atidtoeamtype(Atid1)
467 <    Myid_atom2 = Eamlist%atidtoeamtype(Atid2)
575 <
576 <    if (r.lt.EAMList%EAMParams(myid_atom1)%eam_rcut) then
466 >    Myid_atom1 = SCList%atidtoSCtype(Atid1)
467 >    Myid_atom2 = SCList%atidtoSCtype(Atid2)
468  
469  
470  
471 <       call eam_splint(EAMList%EAMParams(myid_atom1)%eam_nr, &
472 <            EAMList%EAMParams(myid_atom1)%eam_rvals, &
473 <            EAMList%EAMParams(myid_atom1)%eam_rho_r, &
583 <            EAMList%EAMParams(myid_atom1)%eam_rho_r_pp, &
584 <            r, rho_i_at_j,drho,d2rho)
471 >       rho_i_at_j = (MixingMap(Myid_atom1,Myid_atom2)%alpha/r)&
472 >            **MixingMap(Myid_atom1,Myid_atom2)%m
473 >       rho_j_at_i = rho_i_at_j
474  
586
587
475   #ifdef  IS_MPI
476         rho_col(atom2) = rho_col(atom2) + rho_i_at_j
590 #else
591       rho(atom2) = rho(atom2) + rho_i_at_j
592 #endif
593             ! write(*,*) atom1,atom2,r,rho_i_at_j
594    endif
595
596    if (r.lt.EAMList%EAMParams(myid_atom2)%eam_rcut) then
597       call eam_splint(EAMList%EAMParams(myid_atom2)%eam_nr, &
598            EAMList%EAMParams(myid_atom2)%eam_rvals, &
599            EAMList%EAMParams(myid_atom2)%eam_rho_r, &
600            EAMList%EAMParams(myid_atom2)%eam_rho_r_pp, &
601            r, rho_j_at_i,drho,d2rho)
602
603
604
605
606 #ifdef  IS_MPI
477         rho_row(atom1) = rho_row(atom1) + rho_j_at_i
478   #else
479 +       rho(atom2) = rho(atom2) + rho_i_at_j
480         rho(atom1) = rho(atom1) + rho_j_at_i
481   #endif
611    endif
482  
483 +  end subroutine calc_sc_prepair_rho
484  
485  
486 <
487 <
617 <
618 <  end subroutine calc_eam_prepair_rho
619 <
620 <
621 <
622 <
623 <  !! Calculate the functional F(rho) for all local atoms
624 <  subroutine calc_eam_preforce_Frho(nlocal,pot)
486 > !! Calculate the rho_a for all local atoms
487 >  subroutine calc_sc_preforce_Frho(nlocal,pot)
488      integer :: nlocal
489      real(kind=dp) :: pot
490      integer :: i,j
491      integer :: atom
492      real(kind=dp) :: U,U1,U2
493      integer :: atype1
494 <    integer :: me,atid1
495 <    integer :: n_rho_points
494 >    integer :: atid1
495 >    integer :: myid
496  
497  
498      cleanme = .true.
499      !! Scatter the electron density from  pre-pair calculation back to local atoms
500   #ifdef IS_MPI
501 <    call scatter(rho_row,rho,plan_atom_row,eam_err)
502 <    if (eam_err /= 0 ) then
501 >    call scatter(rho_row,rho,plan_atom_row,sc_err)
502 >    if (sc_err /= 0 ) then
503         write(errMsg,*) " Error scattering rho_row into rho"
504         call handleError(RoutineName,errMesg)
505      endif
506 <    call scatter(rho_col,rho_tmp,plan_atom_col,eam_err)
507 <    if (eam_err /= 0 ) then
506 >    call scatter(rho_col,rho_tmp,plan_atom_col,sc_err)
507 >    if (sc_err /= 0 ) then
508         write(errMsg,*) " Error scattering rho_col into rho"
509         call handleError(RoutineName,errMesg)
510 +
511      endif
512  
513      rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
# Line 651 | Line 515 | contains
515  
516  
517  
518 <    !! Calculate F(rho) and derivative
518 >    !! Calculate F(rho) and derivative
519      do atom = 1, nlocal
520 <       atid1 = atid(atom)
521 <       me = eamList%atidToEAMtype(atid1)
522 <       n_rho_points = EAMList%EAMParams(me)%eam_nrho
659 <       !  Check to see that the density is not greater than the larges rho we have calculated
660 <       if (rho(atom) < EAMList%EAMParams(me)%eam_rhovals(n_rho_points)) then
661 <          call eam_splint(n_rho_points, &
662 <               EAMList%EAMParams(me)%eam_rhovals, &
663 <               EAMList%EAMParams(me)%eam_f_rho, &
664 <               EAMList%EAMParams(me)%eam_f_rho_pp, &
665 <               rho(atom), & ! Actual Rho
666 <               u, u1, u2)
667 <       else
668 <          ! Calculate F(rho with the largest available rho value
669 <          call eam_splint(n_rho_points, &
670 <               EAMList%EAMParams(me)%eam_rhovals, &
671 <               EAMList%EAMParams(me)%eam_f_rho, &
672 <               EAMList%EAMParams(me)%eam_f_rho_pp, &
673 <               EAMList%EAMParams(me)%eam_rhovals(n_rho_points), & ! Largest rho
674 <               u,u1,u2)
675 <       end if
520 >       Myid = SCList%atidtoSctype(Atid(atom))
521 >       frho(atom) = -SCList%SCTypes(Myid)%c * &
522 >            SCList%SCTypes(Myid)%epsilon * sqrt(rho(i))
523  
524 <
678 <       frho(atom) = u
679 <       dfrhodrho(atom) = u1
680 <       d2frhodrhodrho(atom) = u2
524 >       dfrhodrho(atom) = 0.5_dp*frho(atom)/rho(atom)
525         pot = pot + u
682
526      enddo
527  
685
686
528   #ifdef IS_MPI
529      !! communicate f(rho) and derivatives back into row and column arrays
530 <    call gather(frho,frho_row,plan_atom_row, eam_err)
531 <    if (eam_err /=  0) then
530 >    call gather(frho,frho_row,plan_atom_row, sc_err)
531 >    if (sc_err /=  0) then
532         call handleError("cal_eam_forces()","MPI gather frho_row failure")
533      endif
534 <    call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, eam_err)
535 <    if (eam_err /=  0) then
534 >    call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, sc_err)
535 >    if (sc_err /=  0) then
536         call handleError("cal_eam_forces()","MPI gather dfrhodrho_row failure")
537      endif
538 <    call gather(frho,frho_col,plan_atom_col, eam_err)
539 <    if (eam_err /=  0) then
538 >    call gather(frho,frho_col,plan_atom_col, sc_err)
539 >    if (sc_err /=  0) then
540         call handleError("cal_eam_forces()","MPI gather frho_col failure")
541      endif
542 <    call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, eam_err)
543 <    if (eam_err /=  0) then
542 >    call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, sc_err)
543 >    if (sc_err /=  0) then
544         call handleError("cal_eam_forces()","MPI gather dfrhodrho_col failure")
545      endif
705
706
707
708
709
710    if (nmflag) then
711       call gather(d2frhodrhodrho,d2frhodrhodrho_row,plan_atom_row)
712       call gather(d2frhodrhodrho,d2frhodrhodrho_col,plan_atom_col)
713    endif
546   #endif
547 +    
548 +    
549 +  end subroutine calc_sc_preforce_Frho
550  
551  
552 <  end subroutine calc_eam_preforce_Frho
553 <
719 <
720 <
721 <
722 <  !! Does EAM pairwise Force calculation.  
723 <  subroutine do_eam_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
552 >  !! Does Sutton-Chen  pairwise Force calculation.  
553 >  subroutine do_sc_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
554         pot, f, do_pot)
555      !Arguments    
556      integer, intent(in) ::  atom1, atom2
# Line 733 | Line 563 | contains
563      logical, intent(in) :: do_pot
564  
565      real( kind = dp ) :: drdx,drdy,drdz
566 <    real( kind = dp ) :: d2
567 <    real( kind = dp ) :: phab,pha,dvpdr,d2vpdrdr
738 <    real( kind = dp ) :: rha,drha,d2rha, dpha
739 <    real( kind = dp ) :: rhb,drhb,d2rhb, dphb
566 >    real( kind = dp ) :: dvpdr
567 >    real( kind = dp ) :: drhodr
568      real( kind = dp ) :: dudr
569 <    real( kind = dp ) :: rci,rcj
569 >    real( kind = dp ) :: rcij
570      real( kind = dp ) :: drhoidr,drhojdr
743    real( kind = dp ) :: d2rhoidrdr
744    real( kind = dp ) :: d2rhojdrdr
571      real( kind = dp ) :: Fx,Fy,Fz
572      real( kind = dp ) :: r,d2pha,phb,d2phb
573 <
573 >    real( kind = dp ) :: pot_temp,vptmp
574 >    real( kind = dp ) :: epsilonij,aij,nij,mij,vcij
575      integer :: id1,id2
576      integer  :: mytype_atom1
577      integer  :: mytype_atom2
# Line 753 | Line 580 | contains
580  
581      ! write(*,*) "Frho: ", Frho(atom1)
582  
583 <    phab = 0.0E0_DP
583 >
584      dvpdr = 0.0E0_DP
758    d2vpdrdr = 0.0E0_DP
585  
760    if (rij .lt. EAM_rcut) then
586  
587   #ifdef IS_MPI
588         atid1 = atid_row(atom1)
# Line 767 | Line 592 | contains
592         atid2 = atid(atom2)
593   #endif
594  
595 <       mytype_atom1 = EAMList%atidToEAMType(atid1)
596 <       mytype_atom2 = EAMList%atidTOEAMType(atid2)
595 >       mytype_atom1 = SCList%atidToSCType(atid1)
596 >       mytype_atom2 = SCList%atidTOSCType(atid2)
597  
773
774       ! get cutoff for atom 1
775       rci = EAMList%EAMParams(mytype_atom1)%eam_rcut
776       ! get type specific cutoff for atom 2
777       rcj = EAMList%EAMParams(mytype_atom2)%eam_rcut
778
598         drdx = d(1)/rij
599         drdy = d(2)/rij
600         drdz = d(3)/rij
601  
602 <       if (rij.lt.rci) then
603 <          call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
604 <               EAMList%EAMParams(mytype_atom1)%eam_rvals, &
605 <               EAMList%EAMParams(mytype_atom1)%eam_rho_r, &
606 <               EAMList%EAMParams(mytype_atom1)%eam_rho_r_pp, &
607 <               rij, rha,drha,d2rha)
789 <          !! Calculate Phi(r) for atom1.
790 <          call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
791 <               EAMList%EAMParams(mytype_atom1)%eam_rvals, &
792 <               EAMList%EAMParams(mytype_atom1)%eam_phi_r, &
793 <               EAMList%EAMParams(mytype_atom1)%eam_phi_r_pp, &
794 <               rij, pha,dpha,d2pha)
795 <       endif
602 >                
603 >       epsilonij = MixingMap(mytype_atom1,mytype_atom2)%epsilon
604 >       aij       = MixingMap(mytype_atom1,mytype_atom2)%alpha
605 >       nij       = MixingMap(mytype_atom1,mytype_atom2)%n
606 >       mij       = MixingMap(mytype_atom1,mytype_atom2)%m
607 >       vcij      = MixingMap(mytype_atom1,mytype_atom2)%vpair_pot              
608  
609 <       if (rij.lt.rcj) then      
798 <          ! Calculate rho,drho and d2rho for atom1
799 <          call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
800 <               EAMList%EAMParams(mytype_atom2)%eam_rvals, &
801 <               EAMList%EAMParams(mytype_atom2)%eam_rho_r, &
802 <               EAMList%EAMParams(mytype_atom2)%eam_rho_r_pp, &
803 <               rij, rhb,drhb,d2rhb)
609 >       vptmp = epsilonij*((aij/r)**nij)
610  
805          !! Calculate Phi(r) for atom2.
806          call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
807               EAMList%EAMParams(mytype_atom2)%eam_rvals, &
808               EAMList%EAMParams(mytype_atom2)%eam_phi_r, &
809               EAMList%EAMParams(mytype_atom2)%eam_phi_r_pp, &
810               rij, phb,dphb,d2phb)
811       endif
611  
612 <       if (rij.lt.rci) then
613 <          phab = phab + 0.5E0_DP*(rhb/rha)*pha
815 <          dvpdr = dvpdr + 0.5E0_DP*((rhb/rha)*dpha + &
816 <               pha*((drhb/rha) - (rhb*drha/rha/rha)))
817 <          d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rhb/rha)*d2pha + &
818 <               2.0E0_DP*dpha*((drhb/rha) - (rhb*drha/rha/rha)) + &
819 <               pha*((d2rhb/rha) - 2.0E0_DP*(drhb*drha/rha/rha) + &
820 <               (2.0E0_DP*rhb*drha*drha/rha/rha/rha) - (rhb*d2rha/rha/rha)))
821 <       endif
612 >       dvpdr = -nij*vptmp/r
613 >       drhodr = -mij*((aij/r)**mij)/r
614  
615 <       if (rij.lt.rcj) then
616 <          phab = phab + 0.5E0_DP*(rha/rhb)*phb
617 <          dvpdr = dvpdr + 0.5E0_DP*((rha/rhb)*dphb + &
618 <               phb*((drha/rhb) - (rha*drhb/rhb/rhb)))
619 <          d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rha/rhb)*d2phb + &
620 <               2.0E0_DP*dphb*((drha/rhb) - (rha*drhb/rhb/rhb)) + &
829 <               phb*((d2rha/rhb) - 2.0E0_DP*(drha*drhb/rhb/rhb) + &
830 <               (2.0E0_DP*rha*drhb*drhb/rhb/rhb/rhb) - (rha*d2rhb/rhb/rhb)))
831 <       endif
615 >      
616 >       dudr = drhodr*(dfrhodrho(atom1)+dfrhodrho(atom2)) &
617 >            + dvpdr
618 >      
619 >       pot_temp = vptmp + vcij
620 >
621  
833       drhoidr = drha
834       drhojdr = drhb
835
836       d2rhoidrdr = d2rha
837       d2rhojdrdr = d2rhb
838
839
622   #ifdef IS_MPI
623 <       dudr = drhojdr*dfrhodrho_row(atom1)+drhoidr*dfrhodrho_col(atom2) &
623 >       dudr = drhodr*(dfrhodrho_row(atom1)+dfrhodrho_col(atom2)) &
624              + dvpdr
625  
626   #else
627 <       dudr = drhojdr*dfrhodrho(atom1)+drhoidr*dfrhodrho(atom2) &
627 >       dudr = drhodr*(dfrhodrho(atom1)+dfrhodrho(atom2)) &
628              + dvpdr
847       ! write(*,*) "Atom1,Atom2, dfrhodrho(atom1) dfrhodrho(atom2): ", atom1,atom2,dfrhodrho(atom1),dfrhodrho(atom2)
629   #endif
630  
631 +
632         fx = dudr * drdx
633         fy = dudr * drdy
634         fz = dudr * drdz
# Line 854 | Line 636 | contains
636  
637   #ifdef IS_MPI
638         if (do_pot) then
639 <          pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + phab*0.5
640 <          pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + phab*0.5
639 >          pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + (pot_temp)*0.5
640 >          pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + (pot_temp)*0.5
641         end if
642  
643         f_Row(1,atom1) = f_Row(1,atom1) + fx
# Line 868 | Line 650 | contains
650   #else
651  
652         if(do_pot) then
653 <          pot = pot + phab
653 >          pot = pot + pot_temp
654         end if
655  
656         f(1,atom1) = f(1,atom1) + fx
# Line 880 | Line 662 | contains
662         f(3,atom2) = f(3,atom2) - fz
663   #endif
664  
665 <       vpair = vpair + phab
665 >      
666   #ifdef IS_MPI
667         id1 = AtomRowToGlobal(atom1)
668         id2 = AtomColToGlobal(atom2)
# Line 897 | Line 679 | contains
679  
680         endif
681  
900       if (nmflag) then
682  
683 <          drhoidr = drha
903 <          drhojdr = drhb
904 <          d2rhoidrdr = d2rha
905 <          d2rhojdrdr = d2rhb
683 >  end subroutine do_sc_pair
684  
907 #ifdef IS_MPI
908          d2 = d2vpdrdr + &
909               d2rhoidrdr*dfrhodrho_col(atom2) + &
910               d2rhojdrdr*dfrhodrho_row(atom1) + &
911               drhoidr*drhoidr*d2frhodrhodrho_col(atom2) + &
912               drhojdr*drhojdr*d2frhodrhodrho_row(atom1)
685  
914 #else
686  
687 <          d2 = d2vpdrdr + &
917 <               d2rhoidrdr*dfrhodrho(atom2) + &
918 <               d2rhojdrdr*dfrhodrho(atom1) + &
919 <               drhoidr*drhoidr*d2frhodrhodrho(atom2) + &
920 <               drhojdr*drhojdr*d2frhodrhodrho(atom1)
921 < #endif
922 <       end if
923 <
924 <    endif
925 <  end subroutine do_eam_pair
926 <
927 <
928 <  subroutine eam_splint(nx, xa, ya, yppa, x, y, dy, d2y)
929 <
930 <    integer :: atype, nx, j
931 <    real( kind = DP ), dimension(:) :: xa
932 <    real( kind = DP ), dimension(:) :: ya
933 <    real( kind = DP ), dimension(:) :: yppa
934 <    real( kind = DP ) :: x, y
935 <    real( kind = DP ) :: dy, d2y
936 <    real( kind = DP ) :: del, h, a, b, c, d
937 <    integer :: pp_arraySize
938 <
939 <
940 <    ! this spline code assumes that the x points are equally spaced
941 <    ! do not attempt to use this code if they are not.
942 <
943 <
944 <    ! find the closest point with a value below our own:
945 <    j = FLOOR(real((nx-1),kind=dp) * (x - xa(1)) / (xa(nx) - xa(1))) + 1
946 <
947 <    ! check to make sure we're inside the spline range:
948 <    if ((j.gt.nx).or.(j.lt.1)) then
949 <       write(errMSG,*) "EAM_splint: x is outside bounds of spline: ",x,j
950 <       call handleError(routineName,errMSG)
951 <    endif
952 <    ! check to make sure we haven't screwed up the calculation of j:
953 <    if ((x.lt.xa(j)).or.(x.gt.xa(j+1))) then
954 <       if (j.ne.nx) then
955 <          write(errMSG,*) "EAM_splint:",x," x is outside bounding range"
956 <          call handleError(routineName,errMSG)
957 <       endif
958 <    endif
959 <
960 <    del = xa(j+1) - x
961 <    h = xa(j+1) - xa(j)
962 <
963 <    a = del / h
964 <    b = 1.0E0_DP - a
965 <    c = a*(a*a - 1.0E0_DP)*h*h/6.0E0_DP
966 <    d = b*(b*b - 1.0E0_DP)*h*h/6.0E0_DP
967 <
968 <    y = a*ya(j) + b*ya(j+1) + c*yppa(j) + d*yppa(j+1)
969 <
970 <    dy = (ya(j+1)-ya(j))/h &
971 <         - (3.0E0_DP*a*a - 1.0E0_DP)*h*yppa(j)/6.0E0_DP &
972 <         + (3.0E0_DP*b*b - 1.0E0_DP)*h*yppa(j+1)/6.0E0_DP
973 <
974 <
975 <    d2y = a*yppa(j) + b*yppa(j+1)
976 <
977 <
978 <  end subroutine eam_splint
979 <
980 <
981 <  subroutine eam_spline(nx, xa, ya, yppa, yp1, ypn, boundary)
982 <
983 <
984 <    ! yp1 and ypn are the first derivatives of y at the two endpoints
985 <    ! if boundary is 'L' the lower derivative is used
986 <    ! if boundary is 'U' the upper derivative is used
987 <    ! if boundary is 'B' then both derivatives are used
988 <    ! if boundary is anything else, then both derivatives are assumed to be 0
989 <
990 <    integer :: nx, i, k, max_array_size
991 <
992 <    real( kind = DP ), dimension(:)        :: xa
993 <    real( kind = DP ), dimension(:)        :: ya
994 <    real( kind = DP ), dimension(:)        :: yppa
995 <    real( kind = DP ), dimension(size(xa)) :: u
996 <    real( kind = DP ) :: yp1,ypn,un,qn,sig,p
997 <    character(len=*) :: boundary
998 <
999 <    ! make sure the sizes match
1000 <    if ((nx /= size(xa)) .or. (nx /= size(ya))) then
1001 <       call handleWarning("EAM_SPLINE","Array size mismatch")
1002 <    end if
1003 <
1004 <    if ((boundary.eq.'l').or.(boundary.eq.'L').or. &
1005 <         (boundary.eq.'b').or.(boundary.eq.'B')) then
1006 <       yppa(1) = -0.5E0_DP
1007 <       u(1) = (3.0E0_DP/(xa(2)-xa(1)))*((ya(2)-&
1008 <            ya(1))/(xa(2)-xa(1))-yp1)
1009 <    else
1010 <       yppa(1) = 0.0E0_DP
1011 <       u(1)  = 0.0E0_DP
1012 <    endif
1013 <
1014 <    do i = 2, nx - 1
1015 <       sig = (xa(i) - xa(i-1)) / (xa(i+1) - xa(i-1))
1016 <       p = sig * yppa(i-1) + 2.0E0_DP
1017 <       yppa(i) = (sig - 1.0E0_DP) / p
1018 <       u(i) = (6.0E0_DP*((ya(i+1)-ya(i))/(xa(i+1)-xa(i)) - &
1019 <            (ya(i)-ya(i-1))/(xa(i)-xa(i-1)))/ &
1020 <            (xa(i+1)-xa(i-1)) - sig * u(i-1))/p
1021 <    enddo
1022 <
1023 <    if ((boundary.eq.'u').or.(boundary.eq.'U').or. &
1024 <         (boundary.eq.'b').or.(boundary.eq.'B')) then
1025 <       qn = 0.5E0_DP
1026 <       un = (3.0E0_DP/(xa(nx)-xa(nx-1)))* &
1027 <            (ypn-(ya(nx)-ya(nx-1))/(xa(nx)-xa(nx-1)))
1028 <    else
1029 <       qn = 0.0E0_DP
1030 <       un = 0.0E0_DP
1031 <    endif
1032 <
1033 <    yppa(nx)=(un-qn*u(nx-1))/(qn*yppa(nx-1)+1.0E0_DP)
1034 <
1035 <    do k = nx-1, 1, -1
1036 <       yppa(k)=yppa(k)*yppa(k+1)+u(k)
1037 <    enddo
1038 <
1039 <  end subroutine eam_spline
1040 <
1041 < end module eam
687 > end module suttonchen

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines