ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/suttonchen.F90
Revision: 2412
Committed: Wed Nov 2 23:50:56 2005 UTC (18 years, 7 months ago) by chuckv
File size: 22422 byte(s)
Log Message:
More work on suttonchen.

File Contents

# Content
1 !!
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 logical, save,:: haveMixingMap = .false.
67
68 character(len = statusMsgSize) :: errMesg
69 integer :: eam_err
70
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 real(kind=dp) :: c
81 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 real( kind = dp), dimension(:), allocatable :: rho
90 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
121 type :: MixParameters
122 real(kind=DP) :: alpha
123 real(kind=DP) :: epsilon
124 real(kind=dp) :: sigma6
125 real(kind=dp) :: rCut
126 real(kind=dp) :: vpair_pot
127 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 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 public :: setSCDefaultCutoff
145 public :: setSCUniformCutoff
146
147 contains
148
149
150 subroutine newSCtype(c,m,n,alpha,epsilon,c_ident,status)
151 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 integer :: nAtypes,nSCTypes,myATID
164 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 if (.not.associated(EAMList%EAMParams)) then
178 call getMatchingElementList(atypes, "is_SuttonChen", .true., nSCtypes, MatchList)
179 SCTypeList%nSCtypes = nSCtypes
180 allocate(SCTypeList%SCTypes(nSCTypes))
181 nAtypes = getSize(atypes)
182 allocate(SCTypeList%atidToSCType(nAtypes))
183 end if
184
185 SCTypeList%currentSCType = SCTypeList%currentSCType + 1
186 current = SCTypeList%currentSCType
187
188 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
189 SCTypeList%atidToSCType(myATID) = current
190
191
192
193 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
201
202 subroutine destroySCTypes()
203
204
205 if(allocated(SCTypeList)) deallocate(SCTypeList)
206
207
208
209 end subroutine destroySCTypes
210
211
212
213 function getSCCut(atomID) result(cutValue)
214 integer, intent(in) :: atomID
215 integer :: eamID
216 real(kind=dp) :: cutValue
217
218 eamID = EAMList%atidToEAMType(atomID)
219 cutValue = EAMList%EAMParams(eamID)%eam_rcut
220 end function getSCCut
221
222
223
224
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 return
234 end if
235
236 nSCtypes = SCList%nSCtypes
237
238 if (.not. allocated(MixingMap)) then
239 allocate(MixingMap(nSCtypes, nSCtypes))
240 endif
241
242 do i = 1, nSCtypes
243
244 e1 = SCList%SCtypes(i)%epsilon
245 m1 = SCList%SCtypes(i)%m
246 n1 = SCList%SCtypes(i)%n
247 alpha1 = SCList%SCtypes(i)%alpha
248
249 do j = i, nSCtypes
250
251
252 e2 = SCList%SCtypes(j)%epsilon
253 m2 = SCList%SCtypes(j)%m
254 n2 = SCList%SCtypes(j)%n
255 alpha2 = SCList%SCtypes(j)%alpha
256
257 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
265 enddo
266 enddo
267
268 haveMixingMap = .true.
269
270 end subroutine createMixingMap
271
272
273 !! routine checks to see if array is allocated, deallocates array if allocated
274 !! and then creates the array to the required size
275 subroutine allocateSC(status)
276 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
292
293 if (allocated(frho)) deallocate(frho)
294 allocate(frho(nlocal),stat=alloc_stat)
295 if (alloc_stat /= 0) then
296 status = -1
297 return
298 end if
299
300 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 end subroutine allocateSC
387
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 subroutine setCutoffSC(rcut, status)
392 real(kind=dp) :: rcut
393 integer :: status
394 status = 0
395
396 SC_rcut = rcut
397
398 end subroutine setCutoffSC
399
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 subroutine calc_sc_prepair_rho(atom1,atom2,d,r,rijsq)
424 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 integer :: eam_err
436
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 Myid_atom1 = SCTypeList%atidtoSCtype(Atid1)
456 Myid_atom2 = SCTypeList%atidtoSCtype(Atid2)
457
458
459
460 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
464 #ifdef IS_MPI
465 rho_col(atom2) = rho_col(atom2) + rho_i_at_j
466 rho_row(atom1) = rho_row(atom1) + rho_j_at_i
467 #else
468 rho(atom2) = rho(atom2) + rho_i_at_j
469 rho(atom1) = rho(atom1) + rho_j_at_i
470 #endif
471
472
473
474 end subroutine calc_sc_prepair_rho
475
476
477 !! Calculate the functional F(rho) for all local atoms
478 subroutine calc_eam_preforce_Frho(nlocal,pot)
479 integer :: nlocal
480 real(kind=dp) :: pot
481 integer :: i,j
482 integer :: atom
483 real(kind=dp) :: U,U1,U2
484 integer :: atype1
485 integer :: me,atid1
486 integer :: n_rho_points
487
488
489 cleanme = .true.
490 !! Scatter the electron density from pre-pair calculation back to local atoms
491 #ifdef IS_MPI
492 call scatter(rho_row,rho,plan_atom_row,eam_err)
493 if (eam_err /= 0 ) then
494 write(errMsg,*) " Error scattering rho_row into rho"
495 call handleError(RoutineName,errMesg)
496 endif
497 call scatter(rho_col,rho_tmp,plan_atom_col,eam_err)
498 if (eam_err /= 0 ) then
499 write(errMsg,*) " Error scattering rho_col into rho"
500 call handleError(RoutineName,errMesg)
501
502 endif
503
504 rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
505 #endif
506
507
508
509 !! Calculate F(rho) and derivative
510 do atom = 1, nlocal
511 Myid = ScTypeList%atidtoSctype(Atid(atom))
512 frho(atom) = -MixingMap(Myid,Myid)%c * MixingMap(Myid,Myid)%epsilon &
513 * sqrt(rho(i))
514 dfrhodrho(atom) = 0.5_dp*frho(atom)/rho(atom)
515 d2frhodrhodrho(atom) = -0.5_dp*dfrhodrho(atom)/rho(atom)
516 pot = pot + u
517 enddo
518
519 #ifdef IS_MPI
520 !! communicate f(rho) and derivatives back into row and column arrays
521 call gather(frho,frho_row,plan_atom_row, eam_err)
522 if (eam_err /= 0) then
523 call handleError("cal_eam_forces()","MPI gather frho_row failure")
524 endif
525 call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, eam_err)
526 if (eam_err /= 0) then
527 call handleError("cal_eam_forces()","MPI gather dfrhodrho_row failure")
528 endif
529 call gather(frho,frho_col,plan_atom_col, eam_err)
530 if (eam_err /= 0) then
531 call handleError("cal_eam_forces()","MPI gather frho_col failure")
532 endif
533 call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, eam_err)
534 if (eam_err /= 0) then
535 call handleError("cal_eam_forces()","MPI gather dfrhodrho_col failure")
536 endif
537
538 if (nmflag) then
539 call gather(d2frhodrhodrho,d2frhodrhodrho_row,plan_atom_row)
540 call gather(d2frhodrhodrho,d2frhodrhodrho_col,plan_atom_col)
541 endif
542 #endif
543
544
545 end subroutine calc_eam_preforce_Frho
546
547
548 !! Does Sutton-Chen pairwise Force calculation.
549 subroutine do_eam_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
550 pot, f, do_pot)
551 !Arguments
552 integer, intent(in) :: atom1, atom2
553 real( kind = dp ), intent(in) :: rij, r2
554 real( kind = dp ) :: pot, sw, vpair
555 real( kind = dp ), dimension(3,nLocal) :: f
556 real( kind = dp ), intent(in), dimension(3) :: d
557 real( kind = dp ), intent(inout), dimension(3) :: fpair
558
559 logical, intent(in) :: do_pot
560
561 real( kind = dp ) :: drdx,drdy,drdz
562 real( kind = dp ) :: d2
563 real( kind = dp ) :: phab,pha,dvpdr,d2vpdrdr
564 real( kind = dp ) :: rha,drha,d2rha, dpha
565 real( kind = dp ) :: rhb,drhb,d2rhb, dphb
566 real( kind = dp ) :: dudr
567 real( kind = dp ) :: rci,rcj
568 real( kind = dp ) :: drhoidr,drhojdr
569 real( kind = dp ) :: d2rhoidrdr
570 real( kind = dp ) :: d2rhojdrdr
571 real( kind = dp ) :: Fx,Fy,Fz
572 real( kind = dp ) :: r,d2pha,phb,d2phb
573
574 integer :: id1,id2
575 integer :: mytype_atom1
576 integer :: mytype_atom2
577 integer :: atid1,atid2
578 !Local Variables
579
580 ! write(*,*) "Frho: ", Frho(atom1)
581
582 phab = 0.0E0_DP
583 dvpdr = 0.0E0_DP
584 d2vpdrdr = 0.0E0_DP
585
586 if (rij .lt. EAM_rcut) then
587
588 #ifdef IS_MPI
589 atid1 = atid_row(atom1)
590 atid2 = atid_col(atom2)
591 #else
592 atid1 = atid(atom1)
593 atid2 = atid(atom2)
594 #endif
595
596 mytype_atom1 = EAMList%atidToEAMType(atid1)
597 mytype_atom2 = EAMList%atidTOEAMType(atid2)
598
599
600 ! get cutoff for atom 1
601 rci = EAMList%EAMParams(mytype_atom1)%eam_rcut
602 ! get type specific cutoff for atom 2
603 rcj = EAMList%EAMParams(mytype_atom2)%eam_rcut
604
605 drdx = d(1)/rij
606 drdy = d(2)/rij
607 drdz = d(3)/rij
608
609 if (rij.lt.rci) then
610 call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
611 EAMList%EAMParams(mytype_atom1)%eam_rvals, &
612 EAMList%EAMParams(mytype_atom1)%eam_rho_r, &
613 EAMList%EAMParams(mytype_atom1)%eam_rho_r_pp, &
614 rij, rha,drha,d2rha)
615 !! Calculate Phi(r) for atom1.
616 call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
617 EAMList%EAMParams(mytype_atom1)%eam_rvals, &
618 EAMList%EAMParams(mytype_atom1)%eam_phi_r, &
619 EAMList%EAMParams(mytype_atom1)%eam_phi_r_pp, &
620 rij, pha,dpha,d2pha)
621 endif
622
623 if (rij.lt.rcj) then
624 ! Calculate rho,drho and d2rho for atom1
625 call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
626 EAMList%EAMParams(mytype_atom2)%eam_rvals, &
627 EAMList%EAMParams(mytype_atom2)%eam_rho_r, &
628 EAMList%EAMParams(mytype_atom2)%eam_rho_r_pp, &
629 rij, rhb,drhb,d2rhb)
630
631 !! Calculate Phi(r) for atom2.
632 call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
633 EAMList%EAMParams(mytype_atom2)%eam_rvals, &
634 EAMList%EAMParams(mytype_atom2)%eam_phi_r, &
635 EAMList%EAMParams(mytype_atom2)%eam_phi_r_pp, &
636 rij, phb,dphb,d2phb)
637 endif
638
639 if (rij.lt.rci) then
640 phab = phab + 0.5E0_DP*(rhb/rha)*pha
641 dvpdr = dvpdr + 0.5E0_DP*((rhb/rha)*dpha + &
642 pha*((drhb/rha) - (rhb*drha/rha/rha)))
643 d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rhb/rha)*d2pha + &
644 2.0E0_DP*dpha*((drhb/rha) - (rhb*drha/rha/rha)) + &
645 pha*((d2rhb/rha) - 2.0E0_DP*(drhb*drha/rha/rha) + &
646 (2.0E0_DP*rhb*drha*drha/rha/rha/rha) - (rhb*d2rha/rha/rha)))
647 endif
648
649 if (rij.lt.rcj) then
650 phab = phab + 0.5E0_DP*(rha/rhb)*phb
651 dvpdr = dvpdr + 0.5E0_DP*((rha/rhb)*dphb + &
652 phb*((drha/rhb) - (rha*drhb/rhb/rhb)))
653 d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rha/rhb)*d2phb + &
654 2.0E0_DP*dphb*((drha/rhb) - (rha*drhb/rhb/rhb)) + &
655 phb*((d2rha/rhb) - 2.0E0_DP*(drha*drhb/rhb/rhb) + &
656 (2.0E0_DP*rha*drhb*drhb/rhb/rhb/rhb) - (rha*d2rhb/rhb/rhb)))
657 endif
658
659 drhoidr = drha
660 drhojdr = drhb
661
662 d2rhoidrdr = d2rha
663 d2rhojdrdr = d2rhb
664
665
666 #ifdef IS_MPI
667 dudr = drhojdr*dfrhodrho_row(atom1)+drhoidr*dfrhodrho_col(atom2) &
668 + dvpdr
669
670 #else
671 dudr = drhojdr*dfrhodrho(atom1)+drhoidr*dfrhodrho(atom2) &
672 + dvpdr
673 ! write(*,*) "Atom1,Atom2, dfrhodrho(atom1) dfrhodrho(atom2): ", atom1,atom2,dfrhodrho(atom1),dfrhodrho(atom2)
674 #endif
675
676 fx = dudr * drdx
677 fy = dudr * drdy
678 fz = dudr * drdz
679
680
681 #ifdef IS_MPI
682 if (do_pot) then
683 pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + phab*0.5
684 pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + phab*0.5
685 end if
686
687 f_Row(1,atom1) = f_Row(1,atom1) + fx
688 f_Row(2,atom1) = f_Row(2,atom1) + fy
689 f_Row(3,atom1) = f_Row(3,atom1) + fz
690
691 f_Col(1,atom2) = f_Col(1,atom2) - fx
692 f_Col(2,atom2) = f_Col(2,atom2) - fy
693 f_Col(3,atom2) = f_Col(3,atom2) - fz
694 #else
695
696 if(do_pot) then
697 pot = pot + phab
698 end if
699
700 f(1,atom1) = f(1,atom1) + fx
701 f(2,atom1) = f(2,atom1) + fy
702 f(3,atom1) = f(3,atom1) + fz
703
704 f(1,atom2) = f(1,atom2) - fx
705 f(2,atom2) = f(2,atom2) - fy
706 f(3,atom2) = f(3,atom2) - fz
707 #endif
708
709 vpair = vpair + phab
710 #ifdef IS_MPI
711 id1 = AtomRowToGlobal(atom1)
712 id2 = AtomColToGlobal(atom2)
713 #else
714 id1 = atom1
715 id2 = atom2
716 #endif
717
718 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
719
720 fpair(1) = fpair(1) + fx
721 fpair(2) = fpair(2) + fy
722 fpair(3) = fpair(3) + fz
723
724 endif
725
726 if (nmflag) then
727
728 drhoidr = drha
729 drhojdr = drhb
730 d2rhoidrdr = d2rha
731 d2rhojdrdr = d2rhb
732
733 #ifdef IS_MPI
734 d2 = d2vpdrdr + &
735 d2rhoidrdr*dfrhodrho_col(atom2) + &
736 d2rhojdrdr*dfrhodrho_row(atom1) + &
737 drhoidr*drhoidr*d2frhodrhodrho_col(atom2) + &
738 drhojdr*drhojdr*d2frhodrhodrho_row(atom1)
739
740 #else
741
742 d2 = d2vpdrdr + &
743 d2rhoidrdr*dfrhodrho(atom2) + &
744 d2rhojdrdr*dfrhodrho(atom1) + &
745 drhoidr*drhoidr*d2frhodrhodrho(atom2) + &
746 drhojdr*drhojdr*d2frhodrhodrho(atom1)
747 #endif
748 end if
749
750 endif
751 end subroutine do_eam_pair
752
753
754
755 end module suttonchen