ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/suttonchen.F90
Revision: 2413
Committed: Thu Nov 3 23:06:00 2005 UTC (18 years, 9 months ago) by chuckv
File size: 20259 byte(s)
Log Message:
More work on SC.

File Contents

# User Rev Content
1 chuckv 2401 !!
2     !! Copyright (c) 2005 The University of Notre Dame. All Rights Reserved.
3     !!
4     !! The University of Notre Dame grants you ("Licensee") a
5     !! non-exclusive, royalty free, license to use, modify and
6     !! redistribute this software in source and binary code form, provided
7     !! that the following conditions are met:
8     !!
9     !! 1. Acknowledgement of the program authors must be made in any
10     !! publication of scientific results based in part on use of the
11     !! program. An acceptable form of acknowledgement is citation of
12     !! the article in which the program was described (Matthew
13     !! A. Meineke, Charles F. Vardeman II, Teng Lin, Christopher
14     !! J. Fennell and J. Daniel Gezelter, "OOPSE: An Object-Oriented
15     !! Parallel Simulation Engine for Molecular Dynamics,"
16     !! J. Comput. Chem. 26, pp. 252-271 (2005))
17     !!
18     !! 2. Redistributions of source code must retain the above copyright
19     !! notice, this list of conditions and the following disclaimer.
20     !!
21     !! 3. Redistributions in binary form must reproduce the above copyright
22     !! notice, this list of conditions and the following disclaimer in the
23     !! documentation and/or other materials provided with the
24     !! distribution.
25     !!
26     !! This software is provided "AS IS," without a warranty of any
27     !! kind. All express or implied conditions, representations and
28     !! warranties, including any implied warranty of merchantability,
29     !! fitness for a particular purpose or non-infringement, are hereby
30     !! excluded. The University of Notre Dame and its licensors shall not
31     !! be liable for any damages suffered by licensee as a result of
32     !! using, modifying or distributing the software or its
33     !! derivatives. In no event will the University of Notre Dame or its
34     !! licensors be liable for any lost revenue, profit or data, or for
35     !! direct, indirect, special, consequential, incidental or punitive
36     !! damages, however caused and regardless of the theory of liability,
37     !! arising out of the use of or inability to use software, even if the
38     !! University of Notre Dame has been advised of the possibility of
39     !! such damages.
40     !!
41    
42     !! Impliments Sutton-Chen Metallic Potential
43     !! See A.P.SUTTON and J.CHEN,PHIL MAG LETT 61,139-146,1990
44    
45    
46     module suttonchen
47     use simulation
48     use force_globals
49     use status
50     use atype_module
51     use vector_class
52     #ifdef IS_MPI
53     use mpiSimulation
54     #endif
55     implicit none
56     PRIVATE
57     #define __FORTRAN90
58     #include "UseTheForce/DarkSide/fInteractionMap.h"
59    
60     INTEGER, PARAMETER :: DP = selected_real_kind(15)
61    
62     logical, save :: SC_FF_initialized = .false.
63     integer, save :: SC_Mixing_Policy
64     real(kind = dp), save :: SC_rcut
65     logical, save :: haveRcut = .false.
66 chuckv 2412 logical, save,:: haveMixingMap = .false.
67 chuckv 2401
68     character(len = statusMsgSize) :: errMesg
69 chuckv 2413 integer :: sc_err
70 chuckv 2401
71     character(len = 200) :: errMsg
72     character(len=*), parameter :: RoutineName = "Sutton-Chen MODULE"
73     !! Logical that determines if eam arrays should be zeroed
74     logical :: cleanme = .true.
75     logical :: nmflag = .false.
76    
77    
78     type, private :: SCtype
79     integer :: atid
80 chuckv 2406 real(kind=dp) :: c
81 chuckv 2401 real(kind=dp) :: m
82     real(kind=dp) :: n
83     real(kind=dp) :: alpha
84     real(kind=dp) :: epsilon
85     end type SCtype
86    
87    
88     !! Arrays for derivatives used in force calculation
89 chuckv 2412 real( kind = dp), dimension(:), allocatable :: rho
90 chuckv 2401 real( kind = dp), dimension(:), allocatable :: frho
91     real( kind = dp), dimension(:), allocatable :: dfrhodrho
92     real( kind = dp), dimension(:), allocatable :: d2frhodrhodrho
93    
94    
95     !! Arrays for MPI storage
96     #ifdef IS_MPI
97     real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_col
98     real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_row
99     real( kind = dp),save, dimension(:), allocatable :: frho_row
100     real( kind = dp),save, dimension(:), allocatable :: frho_col
101     real( kind = dp),save, dimension(:), allocatable :: rho_row
102     real( kind = dp),save, dimension(:), allocatable :: rho_col
103     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
106     #endif
107    
108     type, private :: SCTypeList
109     integer :: nSCTypes = 0
110     integer :: currentSCtype = 0
111    
112     type (SCtype), pointer :: SCtypes(:) => null()
113     integer, pointer :: atidToSCtype(:) => null()
114     end type SCTypeList
115    
116     type (SCTypeList), save :: SCList
117    
118    
119    
120 chuckv 2406
121     type :: MixParameters
122     real(kind=DP) :: alpha
123     real(kind=DP) :: epsilon
124     real(kind=dp) :: sigma6
125     real(kind=dp) :: rCut
126 chuckv 2412 real(kind=dp) :: vpair_pot
127 chuckv 2406 logical :: rCutWasSet = .false.
128     logical :: shiftedPot
129     logical :: isSoftCore = .false.
130     end type MixParameters
131    
132     type(MixParameters), dimension(:,:), allocatable :: MixingMap
133    
134    
135    
136 chuckv 2401 public :: init_SC_FF
137     public :: setCutoffSC
138     public :: do_SC_pair
139     public :: newSCtype
140     public :: calc_SC_prepair_rho
141     public :: clean_SC
142     public :: destroySCtypes
143     public :: getSCCut
144 chuckv 2412 public :: setSCDefaultCutoff
145     public :: setSCUniformCutoff
146 chuckv 2401
147     contains
148    
149    
150 chuckv 2406 subroutine newSCtype(c,m,n,alpha,epsilon,c_ident,status)
151 chuckv 2401 real (kind = dp ) :: lattice_constant
152     integer :: eam_nrho
153     real (kind = dp ) :: eam_drho
154     integer :: eam_nr
155     real (kind = dp ) :: eam_dr
156     real (kind = dp ) :: rcut
157     real (kind = dp ), dimension(eam_nr) :: eam_Z_r
158     real (kind = dp ), dimension(eam_nr) :: eam_rho_r
159     real (kind = dp ), dimension(eam_nrho) :: eam_F_rho
160     integer :: c_ident
161     integer :: status
162    
163 chuckv 2412 integer :: nAtypes,nSCTypes,myATID
164 chuckv 2401 integer :: maxVals
165     integer :: alloc_stat
166     integer :: current
167     integer,pointer :: Matchlist(:) => null()
168    
169     status = 0
170    
171    
172     !! Assume that atypes has already been set and get the total number of types in atypes
173     !! Also assume that every member of atypes is a EAM model.
174    
175    
176     ! check to see if this is the first time into
177 chuckv 2413 if (.not.associated(SCTypeList%EAMParams)) then
178 chuckv 2412 call getMatchingElementList(atypes, "is_SuttonChen", .true., nSCtypes, MatchList)
179     SCTypeList%nSCtypes = nSCtypes
180     allocate(SCTypeList%SCTypes(nSCTypes))
181 chuckv 2401 nAtypes = getSize(atypes)
182 chuckv 2412 allocate(SCTypeList%atidToSCType(nAtypes))
183 chuckv 2401 end if
184    
185 chuckv 2412 SCTypeList%currentSCType = SCTypeList%currentSCType + 1
186     current = SCTypeList%currentSCType
187 chuckv 2401
188     myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
189 chuckv 2412 SCTypeList%atidToSCType(myATID) = current
190 chuckv 2401
191    
192    
193 chuckv 2412 SCTypeList%SCTypes(current)%atid = c_ident
194     SCTypeList%SCTypes(current)%alpha = alpha
195     SCTypeList%SCTypes(current)%c = c
196     SCTypeList%SCTypes(current)%m = m
197     SCTypeList%SCTypes(current)%n = n
198     SCTypeList%SCTypes(current)%epsilon = epsilon
199     end subroutine newSCtype
200 chuckv 2401
201 chuckv 2412
202     subroutine destroySCTypes()
203 chuckv 2401
204 chuckv 2412
205     if(allocated(SCTypeList)) deallocate(SCTypeList)
206 chuckv 2401
207    
208    
209 chuckv 2412 end subroutine destroySCTypes
210 chuckv 2401
211    
212 chuckv 2412
213     function getSCCut(atomID) result(cutValue)
214 chuckv 2401 integer, intent(in) :: atomID
215     integer :: eamID
216     real(kind=dp) :: cutValue
217    
218 chuckv 2413 eamID = SCTypeList%atidToEAMType(atomID)
219     cutValue = SCTypeList%EAMParams(eamID)%eam_rcut
220 chuckv 2412 end function getSCCut
221 chuckv 2401
222    
223    
224 chuckv 2412
225     subroutine createMixingMap()
226     integer :: nSCtypes, i, j
227     real ( kind = dp ) :: e1, e2,m1,m2,alpha1,alpha2,n1,n2
228     real ( kind = dp ) :: rcut6, tp6, tp12
229     logical :: isSoftCore1, isSoftCore2, doShift
230    
231     if (SCList%currentSCtype == 0) then
232     call handleError("SuttonChen", "No members in SCMap")
233 chuckv 2401 return
234     end if
235    
236 chuckv 2412 nSCtypes = SCList%nSCtypes
237 chuckv 2401
238 chuckv 2412 if (.not. allocated(MixingMap)) then
239     allocate(MixingMap(nSCtypes, nSCtypes))
240     endif
241 chuckv 2401
242 chuckv 2412 do i = 1, nSCtypes
243 chuckv 2401
244 chuckv 2412 e1 = SCList%SCtypes(i)%epsilon
245     m1 = SCList%SCtypes(i)%m
246     n1 = SCList%SCtypes(i)%n
247     alpha1 = SCList%SCtypes(i)%alpha
248 chuckv 2401
249 chuckv 2412 do j = i, nSCtypes
250    
251 chuckv 2401
252 chuckv 2412 e2 = SCList%SCtypes(j)%epsilon
253     m2 = SCList%SCtypes(j)%m
254     n2 = SCList%SCtypes(j)%n
255     alpha2 = SCList%SCtypes(j)%alpha
256 chuckv 2401
257 chuckv 2412 MixingMap(i,j)%epsilon = dsqrt(e1 * e2)
258     MixingMap(i,j)%m = 0.5_dp*(m1+m2)
259     MixingMap(i,j)%n = 0.5_dp*(n1+n2)
260     MixingMap(i,j)%alpha = 0.5_dp*(alpha1+alpha2)
261     MixingMap(i,j)%rcut = 2.0_dp *MixingMap(i,j)%alpha
262     MixingMap(i,j)%vpair_rcut = MixingMap%epsilon(i,j)* &
263     (MixingMap%alpha(i,j)/MixingMap(i,j)%rcut)**MixingMap(i,j)%n
264 chuckv 2401
265 chuckv 2412 enddo
266 chuckv 2401 enddo
267 chuckv 2412
268     haveMixingMap = .true.
269    
270     end subroutine createMixingMap
271    
272 chuckv 2401
273     !! routine checks to see if array is allocated, deallocates array if allocated
274     !! and then creates the array to the required size
275 chuckv 2412 subroutine allocateSC(status)
276 chuckv 2401 integer, intent(out) :: status
277    
278     #ifdef IS_MPI
279     integer :: nAtomsInRow
280     integer :: nAtomsInCol
281     #endif
282     integer :: alloc_stat
283    
284    
285     status = 0
286     #ifdef IS_MPI
287     nAtomsInRow = getNatomsInRow(plan_atom_row)
288     nAtomsInCol = getNatomsInCol(plan_atom_col)
289     #endif
290    
291 chuckv 2412
292    
293 chuckv 2401 if (allocated(frho)) deallocate(frho)
294     allocate(frho(nlocal),stat=alloc_stat)
295 chuckv 2412 if (alloc_stat /= 0) then
296 chuckv 2401 status = -1
297     return
298     end if
299 chuckv 2412
300 chuckv 2401 if (allocated(rho)) deallocate(rho)
301     allocate(rho(nlocal),stat=alloc_stat)
302     if (alloc_stat /= 0) then
303     status = -1
304     return
305     end if
306    
307     if (allocated(dfrhodrho)) deallocate(dfrhodrho)
308     allocate(dfrhodrho(nlocal),stat=alloc_stat)
309     if (alloc_stat /= 0) then
310     status = -1
311     return
312     end if
313    
314     if (allocated(d2frhodrhodrho)) deallocate(d2frhodrhodrho)
315     allocate(d2frhodrhodrho(nlocal),stat=alloc_stat)
316     if (alloc_stat /= 0) then
317     status = -1
318     return
319     end if
320    
321     #ifdef IS_MPI
322    
323     if (allocated(rho_tmp)) deallocate(rho_tmp)
324     allocate(rho_tmp(nlocal),stat=alloc_stat)
325     if (alloc_stat /= 0) then
326     status = -1
327     return
328     end if
329    
330    
331     if (allocated(frho_row)) deallocate(frho_row)
332     allocate(frho_row(nAtomsInRow),stat=alloc_stat)
333     if (alloc_stat /= 0) then
334     status = -1
335     return
336     end if
337     if (allocated(rho_row)) deallocate(rho_row)
338     allocate(rho_row(nAtomsInRow),stat=alloc_stat)
339     if (alloc_stat /= 0) then
340     status = -1
341     return
342     end if
343     if (allocated(dfrhodrho_row)) deallocate(dfrhodrho_row)
344     allocate(dfrhodrho_row(nAtomsInRow),stat=alloc_stat)
345     if (alloc_stat /= 0) then
346     status = -1
347     return
348     end if
349     if (allocated(d2frhodrhodrho_row)) deallocate(d2frhodrhodrho_row)
350     allocate(d2frhodrhodrho_row(nAtomsInRow),stat=alloc_stat)
351     if (alloc_stat /= 0) then
352     status = -1
353     return
354     end if
355    
356    
357     ! Now do column arrays
358    
359     if (allocated(frho_col)) deallocate(frho_col)
360     allocate(frho_col(nAtomsInCol),stat=alloc_stat)
361     if (alloc_stat /= 0) then
362     status = -1
363     return
364     end if
365     if (allocated(rho_col)) deallocate(rho_col)
366     allocate(rho_col(nAtomsInCol),stat=alloc_stat)
367     if (alloc_stat /= 0) then
368     status = -1
369     return
370     end if
371     if (allocated(dfrhodrho_col)) deallocate(dfrhodrho_col)
372     allocate(dfrhodrho_col(nAtomsInCol),stat=alloc_stat)
373     if (alloc_stat /= 0) then
374     status = -1
375     return
376     end if
377     if (allocated(d2frhodrhodrho_col)) deallocate(d2frhodrhodrho_col)
378     allocate(d2frhodrhodrho_col(nAtomsInCol),stat=alloc_stat)
379     if (alloc_stat /= 0) then
380     status = -1
381     return
382     end if
383    
384     #endif
385    
386 chuckv 2412 end subroutine allocateSC
387 chuckv 2401
388     !! C sets rcut to be the largest cutoff of any atype
389     !! present in this simulation. Doesn't include all atypes
390     !! sim knows about, just those in the simulation.
391 chuckv 2412 subroutine setCutoffSC(rcut, status)
392 chuckv 2401 real(kind=dp) :: rcut
393     integer :: status
394     status = 0
395    
396 chuckv 2412 SC_rcut = rcut
397 chuckv 2401
398 chuckv 2412 end subroutine setCutoffSC
399 chuckv 2401
400    
401    
402     subroutine clean_EAM()
403    
404     ! clean non-IS_MPI first
405     frho = 0.0_dp
406     rho = 0.0_dp
407     dfrhodrho = 0.0_dp
408     ! clean MPI if needed
409     #ifdef IS_MPI
410     frho_row = 0.0_dp
411     frho_col = 0.0_dp
412     rho_row = 0.0_dp
413     rho_col = 0.0_dp
414     rho_tmp = 0.0_dp
415     dfrhodrho_row = 0.0_dp
416     dfrhodrho_col = 0.0_dp
417     #endif
418     end subroutine clean_EAM
419    
420    
421    
422     !! Calculates rho_r
423 chuckv 2412 subroutine calc_sc_prepair_rho(atom1,atom2,d,r,rijsq)
424 chuckv 2401 integer :: atom1,atom2
425     real(kind = dp), dimension(3) :: d
426     real(kind = dp), intent(inout) :: r
427     real(kind = dp), intent(inout) :: rijsq
428     ! value of electron density rho do to atom i at atom j
429     real(kind = dp) :: rho_i_at_j
430     ! value of electron density rho do to atom j at atom i
431     real(kind = dp) :: rho_j_at_i
432    
433     ! we don't use the derivatives, dummy variables
434     real( kind = dp) :: drho,d2rho
435 chuckv 2413 integer :: sc_err
436 chuckv 2401
437     integer :: atid1,atid2 ! Global atid
438     integer :: myid_atom1 ! EAM atid
439     integer :: myid_atom2
440    
441    
442     ! check to see if we need to be cleaned at the start of a force loop
443    
444    
445    
446    
447     #ifdef IS_MPI
448     Atid1 = Atid_row(Atom1)
449     Atid2 = Atid_col(Atom2)
450     #else
451     Atid1 = Atid(Atom1)
452     Atid2 = Atid(Atom2)
453     #endif
454    
455 chuckv 2412 Myid_atom1 = SCTypeList%atidtoSCtype(Atid1)
456     Myid_atom2 = SCTypeList%atidtoSCtype(Atid2)
457 chuckv 2401
458    
459    
460 chuckv 2412 rho_i_at_j = (MixingMap(Myid_atom1,Myid_atom2)%alpha/r)&
461     **MixingMap(Myid_atom1,Myid_atom2)%m
462     rho_j_at_i = rho_i_at_j
463 chuckv 2401
464     #ifdef IS_MPI
465     rho_col(atom2) = rho_col(atom2) + rho_i_at_j
466 chuckv 2412 rho_row(atom1) = rho_row(atom1) + rho_j_at_i
467 chuckv 2401 #else
468     rho(atom2) = rho(atom2) + rho_i_at_j
469     rho(atom1) = rho(atom1) + rho_j_at_i
470     #endif
471    
472 chuckv 2412 end subroutine calc_sc_prepair_rho
473 chuckv 2401
474    
475 chuckv 2413 !! Calculate the rho_a for all local atoms
476 chuckv 2401 subroutine calc_eam_preforce_Frho(nlocal,pot)
477     integer :: nlocal
478     real(kind=dp) :: pot
479     integer :: i,j
480     integer :: atom
481     real(kind=dp) :: U,U1,U2
482     integer :: atype1
483     integer :: me,atid1
484     integer :: n_rho_points
485    
486    
487     cleanme = .true.
488     !! Scatter the electron density from pre-pair calculation back to local atoms
489     #ifdef IS_MPI
490 chuckv 2413 call scatter(rho_row,rho,plan_atom_row,sc_err)
491     if (sc_err /= 0 ) then
492 chuckv 2401 write(errMsg,*) " Error scattering rho_row into rho"
493     call handleError(RoutineName,errMesg)
494     endif
495 chuckv 2413 call scatter(rho_col,rho_tmp,plan_atom_col,sc_err)
496     if (sc_err /= 0 ) then
497 chuckv 2401 write(errMsg,*) " Error scattering rho_col into rho"
498     call handleError(RoutineName,errMesg)
499 chuckv 2412
500 chuckv 2401 endif
501    
502     rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
503     #endif
504    
505    
506    
507 chuckv 2412 !! Calculate F(rho) and derivative
508 chuckv 2401 do atom = 1, nlocal
509 chuckv 2412 Myid = ScTypeList%atidtoSctype(Atid(atom))
510     frho(atom) = -MixingMap(Myid,Myid)%c * MixingMap(Myid,Myid)%epsilon &
511     * sqrt(rho(i))
512     dfrhodrho(atom) = 0.5_dp*frho(atom)/rho(atom)
513     d2frhodrhodrho(atom) = -0.5_dp*dfrhodrho(atom)/rho(atom)
514 chuckv 2401 pot = pot + u
515     enddo
516    
517 chuckv 2412 #ifdef IS_MPI
518 chuckv 2401 !! communicate f(rho) and derivatives back into row and column arrays
519 chuckv 2413 call gather(frho,frho_row,plan_atom_row, sc_err)
520     if (sc_err /= 0) then
521 chuckv 2401 call handleError("cal_eam_forces()","MPI gather frho_row failure")
522     endif
523 chuckv 2413 call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, sc_err)
524     if (sc_err /= 0) then
525 chuckv 2401 call handleError("cal_eam_forces()","MPI gather dfrhodrho_row failure")
526     endif
527 chuckv 2413 call gather(frho,frho_col,plan_atom_col, sc_err)
528     if (sc_err /= 0) then
529 chuckv 2401 call handleError("cal_eam_forces()","MPI gather frho_col failure")
530     endif
531 chuckv 2413 call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, sc_err)
532     if (sc_err /= 0) then
533 chuckv 2401 call handleError("cal_eam_forces()","MPI gather dfrhodrho_col failure")
534     endif
535    
536     if (nmflag) then
537     call gather(d2frhodrhodrho,d2frhodrhodrho_row,plan_atom_row)
538     call gather(d2frhodrhodrho,d2frhodrhodrho_col,plan_atom_col)
539     endif
540     #endif
541 chuckv 2412
542    
543 chuckv 2401 end subroutine calc_eam_preforce_Frho
544    
545    
546 chuckv 2412 !! Does Sutton-Chen pairwise Force calculation.
547 chuckv 2401 subroutine do_eam_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
548     pot, f, do_pot)
549     !Arguments
550     integer, intent(in) :: atom1, atom2
551     real( kind = dp ), intent(in) :: rij, r2
552     real( kind = dp ) :: pot, sw, vpair
553     real( kind = dp ), dimension(3,nLocal) :: f
554     real( kind = dp ), intent(in), dimension(3) :: d
555     real( kind = dp ), intent(inout), dimension(3) :: fpair
556    
557     logical, intent(in) :: do_pot
558    
559     real( kind = dp ) :: drdx,drdy,drdz
560     real( kind = dp ) :: d2
561     real( kind = dp ) :: phab,pha,dvpdr,d2vpdrdr
562     real( kind = dp ) :: rha,drha,d2rha, dpha
563     real( kind = dp ) :: rhb,drhb,d2rhb, dphb
564     real( kind = dp ) :: dudr
565 chuckv 2413 real( kind = dp ) :: rcij
566 chuckv 2401 real( kind = dp ) :: drhoidr,drhojdr
567     real( kind = dp ) :: d2rhoidrdr
568     real( kind = dp ) :: d2rhojdrdr
569     real( kind = dp ) :: Fx,Fy,Fz
570     real( kind = dp ) :: r,d2pha,phb,d2phb
571    
572     integer :: id1,id2
573     integer :: mytype_atom1
574     integer :: mytype_atom2
575     integer :: atid1,atid2
576     !Local Variables
577    
578     ! write(*,*) "Frho: ", Frho(atom1)
579    
580     phab = 0.0E0_DP
581     dvpdr = 0.0E0_DP
582     d2vpdrdr = 0.0E0_DP
583    
584    
585     #ifdef IS_MPI
586     atid1 = atid_row(atom1)
587     atid2 = atid_col(atom2)
588     #else
589     atid1 = atid(atom1)
590     atid2 = atid(atom2)
591     #endif
592    
593 chuckv 2413 mytype_atom1 = SCTypeList%atidToSCType(atid1)
594     mytype_atom2 = SCTypeList%atidTOSCType(atid2)
595 chuckv 2401
596     drdx = d(1)/rij
597     drdy = d(2)/rij
598     drdz = d(3)/rij
599    
600 chuckv 2413
601     epsilonij = MixingMap(mytype_atom1,mytype_atom2)%epsilon
602     aij = MixingMap(mytype_atom1,mytype_atom2)%alpha
603     nij = MixingMap(mytype_atom1,mytype_atom2)%n
604     mij = MixingMap(mytype_atom1,mytype_atom2)%m
605     vcij = MixingMap(mytype_atom1,mytype_atom2)%vpair_pot
606 chuckv 2401
607 chuckv 2413 vptmp = dij*((aij/r)**nij)
608 chuckv 2401
609    
610 chuckv 2413 dvpdr = -nij*vptmp/r
611     d2vpdrdr = -dvpdr*(nij+1.0d0)/r
612    
613     drhodr = -mij*((aij/r)**mij)/r
614     d2rhodrdr = -drhodr*(mij+1.0d0)/r
615    
616     dudr = drhodr*(dfrhodrho(i)+dfrhodrho(j)) &
617     + dvpdr
618    
619    
620 chuckv 2401
621     #ifdef IS_MPI
622 chuckv 2413 dudr = drhodr*(dfrhodrho_row(atom1)+dfrhodrho_col(atom2)) &
623 chuckv 2401 + dvpdr
624    
625     #else
626 chuckv 2413 dudr = drhodr*(dfrhodrho(atom1)+dfrhodrho(atom2)) &
627 chuckv 2401 + dvpdr
628     #endif
629    
630 chuckv 2413
631 chuckv 2401 fx = dudr * drdx
632     fy = dudr * drdy
633     fz = dudr * drdz
634    
635    
636     #ifdef IS_MPI
637     if (do_pot) then
638     pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + phab*0.5
639     pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + phab*0.5
640     end if
641    
642     f_Row(1,atom1) = f_Row(1,atom1) + fx
643     f_Row(2,atom1) = f_Row(2,atom1) + fy
644     f_Row(3,atom1) = f_Row(3,atom1) + fz
645    
646     f_Col(1,atom2) = f_Col(1,atom2) - fx
647     f_Col(2,atom2) = f_Col(2,atom2) - fy
648     f_Col(3,atom2) = f_Col(3,atom2) - fz
649     #else
650    
651     if(do_pot) then
652     pot = pot + phab
653     end if
654    
655     f(1,atom1) = f(1,atom1) + fx
656     f(2,atom1) = f(2,atom1) + fy
657     f(3,atom1) = f(3,atom1) + fz
658    
659     f(1,atom2) = f(1,atom2) - fx
660     f(2,atom2) = f(2,atom2) - fy
661     f(3,atom2) = f(3,atom2) - fz
662     #endif
663    
664     vpair = vpair + phab
665     #ifdef IS_MPI
666     id1 = AtomRowToGlobal(atom1)
667     id2 = AtomColToGlobal(atom2)
668     #else
669     id1 = atom1
670     id2 = atom2
671     #endif
672    
673     if (molMembershipList(id1) .ne. molMembershipList(id2)) then
674    
675     fpair(1) = fpair(1) + fx
676     fpair(2) = fpair(2) + fy
677     fpair(3) = fpair(3) + fz
678    
679     endif
680    
681     if (nmflag) then
682    
683     drhoidr = drha
684     drhojdr = drhb
685     d2rhoidrdr = d2rha
686     d2rhojdrdr = d2rhb
687    
688     #ifdef IS_MPI
689     d2 = d2vpdrdr + &
690     d2rhoidrdr*dfrhodrho_col(atom2) + &
691     d2rhojdrdr*dfrhodrho_row(atom1) + &
692     drhoidr*drhoidr*d2frhodrhodrho_col(atom2) + &
693     drhojdr*drhojdr*d2frhodrhodrho_row(atom1)
694    
695     #else
696    
697     d2 = d2vpdrdr + &
698     d2rhoidrdr*dfrhodrho(atom2) + &
699     d2rhojdrdr*dfrhodrho(atom1) + &
700     drhoidr*drhoidr*d2frhodrhodrho(atom2) + &
701     drhojdr*drhojdr*d2frhodrhodrho(atom1)
702     #endif
703     end if
704    
705     endif
706     end subroutine do_eam_pair
707    
708    
709    
710 chuckv 2412 end module suttonchen