ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/suttonchen.F90
Revision: 2406
Committed: Tue Nov 1 23:32:25 2005 UTC (18 years, 8 months ago) by chuckv
File size: 32490 byte(s)
Log Message:
Added suppport to atypes for MEAM and sutton-chen

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
67 character(len = statusMsgSize) :: errMesg
68 integer :: eam_err
69
70 character(len = 200) :: errMsg
71 character(len=*), parameter :: RoutineName = "Sutton-Chen MODULE"
72 !! Logical that determines if eam arrays should be zeroed
73 logical :: cleanme = .true.
74 logical :: nmflag = .false.
75
76
77 type, private :: SCtype
78 integer :: atid
79 real(kind=dp) :: c
80 real(kind=dp) :: m
81 real(kind=dp) :: n
82 real(kind=dp) :: alpha
83 real(kind=dp) :: epsilon
84 end type SCtype
85
86
87 !! Arrays for derivatives used in force calculation
88 real( kind = dp), dimension(:), allocatable :: frho
89 real( kind = dp), dimension(:), allocatable :: rho
90
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) :: delta
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
145 contains
146
147
148 subroutine newSCtype(c,m,n,alpha,epsilon,c_ident,status)
149 real (kind = dp ) :: lattice_constant
150 integer :: eam_nrho
151 real (kind = dp ) :: eam_drho
152 integer :: eam_nr
153 real (kind = dp ) :: eam_dr
154 real (kind = dp ) :: rcut
155 real (kind = dp ), dimension(eam_nr) :: eam_Z_r
156 real (kind = dp ), dimension(eam_nr) :: eam_rho_r
157 real (kind = dp ), dimension(eam_nrho) :: eam_F_rho
158 integer :: c_ident
159 integer :: status
160
161 integer :: nAtypes,nEAMTypes,myATID
162 integer :: maxVals
163 integer :: alloc_stat
164 integer :: current
165 integer,pointer :: Matchlist(:) => null()
166
167 status = 0
168
169
170 !! Assume that atypes has already been set and get the total number of types in atypes
171 !! Also assume that every member of atypes is a EAM model.
172
173
174 ! check to see if this is the first time into
175 if (.not.associated(EAMList%EAMParams)) then
176 call getMatchingElementList(atypes, "is_EAM", .true., nEAMtypes, MatchList)
177 EAMList%n_eam_types = nEAMtypes
178 allocate(EAMList%EAMParams(nEAMTypes))
179 nAtypes = getSize(atypes)
180 allocate(EAMList%atidToEAMType(nAtypes))
181 end if
182
183 EAMList%currentAddition = EAMList%currentAddition + 1
184 current = EAMList%currentAddition
185
186 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
187 EAMList%atidToEAMType(myATID) = current
188
189 call allocate_EAMType(eam_nrho,eam_nr,EAMList%EAMParams(current),stat=alloc_stat)
190 if (alloc_stat /= 0) then
191 status = -1
192 return
193 end if
194
195
196 EAMList%EAMParams(current)%eam_atype = c_ident
197 EAMList%EAMParams(current)%eam_lattice = lattice_constant
198 EAMList%EAMParams(current)%eam_nrho = eam_nrho
199 EAMList%EAMParams(current)%eam_drho = eam_drho
200 EAMList%EAMParams(current)%eam_nr = eam_nr
201 EAMList%EAMParams(current)%eam_dr = eam_dr
202 EAMList%EAMParams(current)%eam_rcut = rcut
203 EAMList%EAMParams(current)%eam_Z_r = eam_Z_r
204 EAMList%EAMParams(current)%eam_rho_r = eam_rho_r
205 EAMList%EAMParams(current)%eam_F_rho = eam_F_rho
206
207 end subroutine newEAMtype
208
209
210 ! kills all eam types entered and sets simulation to uninitalized
211 subroutine destroyEAMtypes()
212 integer :: i
213 type(EAMType), pointer :: tempEAMType=>null()
214
215 do i = 1, EAMList%n_eam_types
216 tempEAMType => eamList%EAMParams(i)
217 call deallocate_EAMType(tempEAMType)
218 end do
219 if(associated( eamList%EAMParams)) deallocate( eamList%EAMParams)
220 eamList%EAMParams => null()
221
222 eamList%n_eam_types = 0
223 eamList%currentAddition = 0
224
225 end subroutine destroyEAMtypes
226
227 function getEAMCut(atomID) result(cutValue)
228 integer, intent(in) :: atomID
229 integer :: eamID
230 real(kind=dp) :: cutValue
231
232 eamID = EAMList%atidToEAMType(atomID)
233 cutValue = EAMList%EAMParams(eamID)%eam_rcut
234 end function getEAMCut
235
236 subroutine init_EAM_FF(status)
237 integer :: status
238 integer :: i,j
239 real(kind=dp) :: current_rcut_max
240 integer :: alloc_stat
241 integer :: number_r, number_rho
242
243
244 status = 0
245 if (EAMList%currentAddition == 0) then
246 call handleError("init_EAM_FF","No members in EAMList")
247 status = -1
248 return
249 end if
250
251
252 do i = 1, EAMList%currentAddition
253
254 ! Build array of r values
255
256 do j = 1,EAMList%EAMParams(i)%eam_nr
257 EAMList%EAMParams(i)%eam_rvals(j) = &
258 real(j-1,kind=dp)* &
259 EAMList%EAMParams(i)%eam_dr
260 end do
261 ! Build array of rho values
262 do j = 1,EAMList%EAMParams(i)%eam_nrho
263 EAMList%EAMParams(i)%eam_rhovals(j) = &
264 real(j-1,kind=dp)* &
265 EAMList%EAMParams(i)%eam_drho
266 end do
267 ! convert from eV to kcal / mol:
268 EAMList%EAMParams(i)%eam_F_rho = EAMList%EAMParams(i)%eam_F_rho * 23.06054E0_DP
269
270 ! precompute the pair potential and get it into kcal / mol:
271 EAMList%EAMParams(i)%eam_phi_r(1) = 0.0E0_DP
272 do j = 2, EAMList%EAMParams(i)%eam_nr
273 EAMList%EAMParams(i)%eam_phi_r(j) = (EAMList%EAMParams(i)%eam_Z_r(j)**2)/EAMList%EAMParams(i)%eam_rvals(j)
274 EAMList%EAMParams(i)%eam_phi_r(j) = EAMList%EAMParams(i)%eam_phi_r(j)*331.999296E0_DP
275 enddo
276 end do
277
278
279 do i = 1, EAMList%currentAddition
280 number_r = EAMList%EAMParams(i)%eam_nr
281 number_rho = EAMList%EAMParams(i)%eam_nrho
282
283 call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
284 EAMList%EAMParams(i)%eam_rho_r, &
285 EAMList%EAMParams(i)%eam_rho_r_pp, &
286 0.0E0_DP, 0.0E0_DP, 'N')
287 call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
288 EAMList%EAMParams(i)%eam_Z_r, &
289 EAMList%EAMParams(i)%eam_Z_r_pp, &
290 0.0E0_DP, 0.0E0_DP, 'N')
291 call eam_spline(number_rho, EAMList%EAMParams(i)%eam_rhovals, &
292 EAMList%EAMParams(i)%eam_F_rho, &
293 EAMList%EAMParams(i)%eam_F_rho_pp, &
294 0.0E0_DP, 0.0E0_DP, 'N')
295 call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
296 EAMList%EAMParams(i)%eam_phi_r, &
297 EAMList%EAMParams(i)%eam_phi_r_pp, &
298 0.0E0_DP, 0.0E0_DP, 'N')
299 enddo
300
301 ! current_rcut_max = EAMList%EAMParams(1)%eam_rcut
302 !! find the smallest rcut for any eam atype
303 ! do i = 2, EAMList%currentAddition
304 ! current_rcut_max =max(current_rcut_max,EAMList%EAMParams(i)%eam_rcut)
305 ! end do
306
307 ! EAM_rcut = current_rcut_max
308 ! EAM_rcut_orig = current_rcut_max
309 ! do i = 1, EAMList%currentAddition
310 ! EAMList%EAMParam(i)s%eam_atype_map(eam_atype(i)) = i
311 ! end do
312 !! Allocate arrays for force calculation
313
314 call allocateEAM(alloc_stat)
315 if (alloc_stat /= 0 ) then
316 write(*,*) "allocateEAM failed"
317 status = -1
318 return
319 endif
320
321 end subroutine init_EAM_FF
322
323 !! routine checks to see if array is allocated, deallocates array if allocated
324 !! and then creates the array to the required size
325 subroutine allocateEAM(status)
326 integer, intent(out) :: status
327
328 #ifdef IS_MPI
329 integer :: nAtomsInRow
330 integer :: nAtomsInCol
331 #endif
332 integer :: alloc_stat
333
334
335 status = 0
336 #ifdef IS_MPI
337 nAtomsInRow = getNatomsInRow(plan_atom_row)
338 nAtomsInCol = getNatomsInCol(plan_atom_col)
339 #endif
340
341 if (allocated(frho)) deallocate(frho)
342 allocate(frho(nlocal),stat=alloc_stat)
343 if (alloc_stat /= 0) then
344 status = -1
345 return
346 end if
347 if (allocated(rho)) deallocate(rho)
348 allocate(rho(nlocal),stat=alloc_stat)
349 if (alloc_stat /= 0) then
350 status = -1
351 return
352 end if
353
354 if (allocated(dfrhodrho)) deallocate(dfrhodrho)
355 allocate(dfrhodrho(nlocal),stat=alloc_stat)
356 if (alloc_stat /= 0) then
357 status = -1
358 return
359 end if
360
361 if (allocated(d2frhodrhodrho)) deallocate(d2frhodrhodrho)
362 allocate(d2frhodrhodrho(nlocal),stat=alloc_stat)
363 if (alloc_stat /= 0) then
364 status = -1
365 return
366 end if
367
368 #ifdef IS_MPI
369
370 if (allocated(rho_tmp)) deallocate(rho_tmp)
371 allocate(rho_tmp(nlocal),stat=alloc_stat)
372 if (alloc_stat /= 0) then
373 status = -1
374 return
375 end if
376
377
378 if (allocated(frho_row)) deallocate(frho_row)
379 allocate(frho_row(nAtomsInRow),stat=alloc_stat)
380 if (alloc_stat /= 0) then
381 status = -1
382 return
383 end if
384 if (allocated(rho_row)) deallocate(rho_row)
385 allocate(rho_row(nAtomsInRow),stat=alloc_stat)
386 if (alloc_stat /= 0) then
387 status = -1
388 return
389 end if
390 if (allocated(dfrhodrho_row)) deallocate(dfrhodrho_row)
391 allocate(dfrhodrho_row(nAtomsInRow),stat=alloc_stat)
392 if (alloc_stat /= 0) then
393 status = -1
394 return
395 end if
396 if (allocated(d2frhodrhodrho_row)) deallocate(d2frhodrhodrho_row)
397 allocate(d2frhodrhodrho_row(nAtomsInRow),stat=alloc_stat)
398 if (alloc_stat /= 0) then
399 status = -1
400 return
401 end if
402
403
404 ! Now do column arrays
405
406 if (allocated(frho_col)) deallocate(frho_col)
407 allocate(frho_col(nAtomsInCol),stat=alloc_stat)
408 if (alloc_stat /= 0) then
409 status = -1
410 return
411 end if
412 if (allocated(rho_col)) deallocate(rho_col)
413 allocate(rho_col(nAtomsInCol),stat=alloc_stat)
414 if (alloc_stat /= 0) then
415 status = -1
416 return
417 end if
418 if (allocated(dfrhodrho_col)) deallocate(dfrhodrho_col)
419 allocate(dfrhodrho_col(nAtomsInCol),stat=alloc_stat)
420 if (alloc_stat /= 0) then
421 status = -1
422 return
423 end if
424 if (allocated(d2frhodrhodrho_col)) deallocate(d2frhodrhodrho_col)
425 allocate(d2frhodrhodrho_col(nAtomsInCol),stat=alloc_stat)
426 if (alloc_stat /= 0) then
427 status = -1
428 return
429 end if
430
431 #endif
432
433 end subroutine allocateEAM
434
435 !! C sets rcut to be the largest cutoff of any atype
436 !! present in this simulation. Doesn't include all atypes
437 !! sim knows about, just those in the simulation.
438 subroutine setCutoffEAM(rcut, status)
439 real(kind=dp) :: rcut
440 integer :: status
441 status = 0
442
443 EAM_rcut = rcut
444
445 end subroutine setCutoffEAM
446
447
448
449 subroutine clean_EAM()
450
451 ! clean non-IS_MPI first
452 frho = 0.0_dp
453 rho = 0.0_dp
454 dfrhodrho = 0.0_dp
455 ! clean MPI if needed
456 #ifdef IS_MPI
457 frho_row = 0.0_dp
458 frho_col = 0.0_dp
459 rho_row = 0.0_dp
460 rho_col = 0.0_dp
461 rho_tmp = 0.0_dp
462 dfrhodrho_row = 0.0_dp
463 dfrhodrho_col = 0.0_dp
464 #endif
465 end subroutine clean_EAM
466
467
468
469 subroutine allocate_EAMType(eam_n_rho,eam_n_r,thisEAMType,stat)
470 integer, intent(in) :: eam_n_rho
471 integer, intent(in) :: eam_n_r
472 type (EAMType) :: thisEAMType
473 integer, optional :: stat
474 integer :: alloc_stat
475
476
477
478 if (present(stat)) stat = 0
479
480 allocate(thisEAMType%eam_rvals(eam_n_r),stat=alloc_stat)
481 if (alloc_stat /= 0 ) then
482 if (present(stat)) stat = -1
483 return
484 end if
485 allocate(thisEAMType%eam_rhovals(eam_n_rho),stat=alloc_stat)
486 if (alloc_stat /= 0 ) then
487 if (present(stat)) stat = -1
488 return
489 end if
490 allocate(thisEAMType%eam_F_rho(eam_n_rho),stat=alloc_stat)
491 if (alloc_stat /= 0 ) then
492 if (present(stat)) stat = -1
493 return
494 end if
495 allocate(thisEAMType%eam_Z_r(eam_n_r),stat=alloc_stat)
496 if (alloc_stat /= 0 ) then
497 if (present(stat)) stat = -1
498 return
499 end if
500 allocate(thisEAMType%eam_rho_r(eam_n_r),stat=alloc_stat)
501 if (alloc_stat /= 0 ) then
502 if (present(stat)) stat = -1
503 return
504 end if
505 allocate(thisEAMType%eam_phi_r(eam_n_r),stat=alloc_stat)
506 if (alloc_stat /= 0 ) then
507 if (present(stat)) stat = -1
508 return
509 end if
510 allocate(thisEAMType%eam_F_rho_pp(eam_n_rho),stat=alloc_stat)
511 if (alloc_stat /= 0 ) then
512 if (present(stat)) stat = -1
513 return
514 end if
515 allocate(thisEAMType%eam_Z_r_pp(eam_n_r),stat=alloc_stat)
516 if (alloc_stat /= 0 ) then
517 if (present(stat)) stat = -1
518 return
519 end if
520 allocate(thisEAMType%eam_rho_r_pp(eam_n_r),stat=alloc_stat)
521 if (alloc_stat /= 0 ) then
522 if (present(stat)) stat = -1
523 return
524 end if
525 allocate(thisEAMType%eam_phi_r_pp(eam_n_r),stat=alloc_stat)
526 if (alloc_stat /= 0 ) then
527 if (present(stat)) stat = -1
528 return
529 end if
530
531
532 end subroutine allocate_EAMType
533
534
535 subroutine deallocate_EAMType(thisEAMType)
536 type (EAMtype), pointer :: thisEAMType
537
538 ! free Arrays in reverse order of allocation...
539 if(associated(thisEAMType%eam_phi_r_pp)) deallocate(thisEAMType%eam_phi_r_pp)
540 if(associated(thisEAMType%eam_rho_r_pp)) deallocate(thisEAMType%eam_rho_r_pp)
541 if(associated(thisEAMType%eam_Z_r_pp)) deallocate(thisEAMType%eam_Z_r_pp)
542 if(associated(thisEAMType%eam_F_rho_pp)) deallocate(thisEAMType%eam_F_rho_pp)
543 if(associated(thisEAMType%eam_phi_r)) deallocate(thisEAMType%eam_phi_r)
544 if(associated(thisEAMType%eam_rho_r)) deallocate(thisEAMType%eam_rho_r)
545 if(associated(thisEAMType%eam_Z_r)) deallocate(thisEAMType%eam_Z_r)
546 if(associated(thisEAMType%eam_F_rho)) deallocate(thisEAMType%eam_F_rho)
547 if(associated(thisEAMType%eam_rhovals)) deallocate(thisEAMType%eam_rhovals)
548 if(associated(thisEAMType%eam_rvals)) deallocate(thisEAMType%eam_rvals)
549
550 end subroutine deallocate_EAMType
551
552 !! Calculates rho_r
553 subroutine calc_eam_prepair_rho(atom1,atom2,d,r,rijsq)
554 integer :: atom1,atom2
555 real(kind = dp), dimension(3) :: d
556 real(kind = dp), intent(inout) :: r
557 real(kind = dp), intent(inout) :: rijsq
558 ! value of electron density rho do to atom i at atom j
559 real(kind = dp) :: rho_i_at_j
560 ! value of electron density rho do to atom j at atom i
561 real(kind = dp) :: rho_j_at_i
562
563 ! we don't use the derivatives, dummy variables
564 real( kind = dp) :: drho,d2rho
565 integer :: eam_err
566
567 integer :: atid1,atid2 ! Global atid
568 integer :: myid_atom1 ! EAM atid
569 integer :: myid_atom2
570
571
572 ! check to see if we need to be cleaned at the start of a force loop
573
574
575
576
577 #ifdef IS_MPI
578 Atid1 = Atid_row(Atom1)
579 Atid2 = Atid_col(Atom2)
580 #else
581 Atid1 = Atid(Atom1)
582 Atid2 = Atid(Atom2)
583 #endif
584
585 Myid_atom1 = Eamlist%atidtoeamtype(Atid1)
586 Myid_atom2 = Eamlist%atidtoeamtype(Atid2)
587
588 if (r.lt.EAMList%EAMParams(myid_atom1)%eam_rcut) then
589
590
591
592 call eam_splint(EAMList%EAMParams(myid_atom1)%eam_nr, &
593 EAMList%EAMParams(myid_atom1)%eam_rvals, &
594 EAMList%EAMParams(myid_atom1)%eam_rho_r, &
595 EAMList%EAMParams(myid_atom1)%eam_rho_r_pp, &
596 r, rho_i_at_j,drho,d2rho)
597
598
599
600 #ifdef IS_MPI
601 rho_col(atom2) = rho_col(atom2) + rho_i_at_j
602 #else
603 rho(atom2) = rho(atom2) + rho_i_at_j
604 #endif
605 ! write(*,*) atom1,atom2,r,rho_i_at_j
606 endif
607
608 if (r.lt.EAMList%EAMParams(myid_atom2)%eam_rcut) then
609 call eam_splint(EAMList%EAMParams(myid_atom2)%eam_nr, &
610 EAMList%EAMParams(myid_atom2)%eam_rvals, &
611 EAMList%EAMParams(myid_atom2)%eam_rho_r, &
612 EAMList%EAMParams(myid_atom2)%eam_rho_r_pp, &
613 r, rho_j_at_i,drho,d2rho)
614
615
616
617
618 #ifdef IS_MPI
619 rho_row(atom1) = rho_row(atom1) + rho_j_at_i
620 #else
621 rho(atom1) = rho(atom1) + rho_j_at_i
622 #endif
623 endif
624
625
626
627
628
629
630 end subroutine calc_eam_prepair_rho
631
632
633
634
635 !! Calculate the functional F(rho) for all local atoms
636 subroutine calc_eam_preforce_Frho(nlocal,pot)
637 integer :: nlocal
638 real(kind=dp) :: pot
639 integer :: i,j
640 integer :: atom
641 real(kind=dp) :: U,U1,U2
642 integer :: atype1
643 integer :: me,atid1
644 integer :: n_rho_points
645
646
647 cleanme = .true.
648 !! Scatter the electron density from pre-pair calculation back to local atoms
649 #ifdef IS_MPI
650 call scatter(rho_row,rho,plan_atom_row,eam_err)
651 if (eam_err /= 0 ) then
652 write(errMsg,*) " Error scattering rho_row into rho"
653 call handleError(RoutineName,errMesg)
654 endif
655 call scatter(rho_col,rho_tmp,plan_atom_col,eam_err)
656 if (eam_err /= 0 ) then
657 write(errMsg,*) " Error scattering rho_col into rho"
658 call handleError(RoutineName,errMesg)
659 endif
660
661 rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
662 #endif
663
664
665
666 !! Calculate F(rho) and derivative
667 do atom = 1, nlocal
668 atid1 = atid(atom)
669 me = eamList%atidToEAMtype(atid1)
670 n_rho_points = EAMList%EAMParams(me)%eam_nrho
671 ! Check to see that the density is not greater than the larges rho we have calculated
672 if (rho(atom) < EAMList%EAMParams(me)%eam_rhovals(n_rho_points)) then
673 call eam_splint(n_rho_points, &
674 EAMList%EAMParams(me)%eam_rhovals, &
675 EAMList%EAMParams(me)%eam_f_rho, &
676 EAMList%EAMParams(me)%eam_f_rho_pp, &
677 rho(atom), & ! Actual Rho
678 u, u1, u2)
679 else
680 ! Calculate F(rho with the largest available rho value
681 call eam_splint(n_rho_points, &
682 EAMList%EAMParams(me)%eam_rhovals, &
683 EAMList%EAMParams(me)%eam_f_rho, &
684 EAMList%EAMParams(me)%eam_f_rho_pp, &
685 EAMList%EAMParams(me)%eam_rhovals(n_rho_points), & ! Largest rho
686 u,u1,u2)
687 end if
688
689
690 frho(atom) = u
691 dfrhodrho(atom) = u1
692 d2frhodrhodrho(atom) = u2
693 pot = pot + u
694
695 enddo
696
697
698
699 #ifdef IS_MPI
700 !! communicate f(rho) and derivatives back into row and column arrays
701 call gather(frho,frho_row,plan_atom_row, eam_err)
702 if (eam_err /= 0) then
703 call handleError("cal_eam_forces()","MPI gather frho_row failure")
704 endif
705 call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, eam_err)
706 if (eam_err /= 0) then
707 call handleError("cal_eam_forces()","MPI gather dfrhodrho_row failure")
708 endif
709 call gather(frho,frho_col,plan_atom_col, eam_err)
710 if (eam_err /= 0) then
711 call handleError("cal_eam_forces()","MPI gather frho_col failure")
712 endif
713 call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, eam_err)
714 if (eam_err /= 0) then
715 call handleError("cal_eam_forces()","MPI gather dfrhodrho_col failure")
716 endif
717
718
719
720
721
722 if (nmflag) then
723 call gather(d2frhodrhodrho,d2frhodrhodrho_row,plan_atom_row)
724 call gather(d2frhodrhodrho,d2frhodrhodrho_col,plan_atom_col)
725 endif
726 #endif
727
728
729 end subroutine calc_eam_preforce_Frho
730
731
732
733
734 !! Does EAM pairwise Force calculation.
735 subroutine do_eam_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
736 pot, f, do_pot)
737 !Arguments
738 integer, intent(in) :: atom1, atom2
739 real( kind = dp ), intent(in) :: rij, r2
740 real( kind = dp ) :: pot, sw, vpair
741 real( kind = dp ), dimension(3,nLocal) :: f
742 real( kind = dp ), intent(in), dimension(3) :: d
743 real( kind = dp ), intent(inout), dimension(3) :: fpair
744
745 logical, intent(in) :: do_pot
746
747 real( kind = dp ) :: drdx,drdy,drdz
748 real( kind = dp ) :: d2
749 real( kind = dp ) :: phab,pha,dvpdr,d2vpdrdr
750 real( kind = dp ) :: rha,drha,d2rha, dpha
751 real( kind = dp ) :: rhb,drhb,d2rhb, dphb
752 real( kind = dp ) :: dudr
753 real( kind = dp ) :: rci,rcj
754 real( kind = dp ) :: drhoidr,drhojdr
755 real( kind = dp ) :: d2rhoidrdr
756 real( kind = dp ) :: d2rhojdrdr
757 real( kind = dp ) :: Fx,Fy,Fz
758 real( kind = dp ) :: r,d2pha,phb,d2phb
759
760 integer :: id1,id2
761 integer :: mytype_atom1
762 integer :: mytype_atom2
763 integer :: atid1,atid2
764 !Local Variables
765
766 ! write(*,*) "Frho: ", Frho(atom1)
767
768 phab = 0.0E0_DP
769 dvpdr = 0.0E0_DP
770 d2vpdrdr = 0.0E0_DP
771
772 if (rij .lt. EAM_rcut) then
773
774 #ifdef IS_MPI
775 atid1 = atid_row(atom1)
776 atid2 = atid_col(atom2)
777 #else
778 atid1 = atid(atom1)
779 atid2 = atid(atom2)
780 #endif
781
782 mytype_atom1 = EAMList%atidToEAMType(atid1)
783 mytype_atom2 = EAMList%atidTOEAMType(atid2)
784
785
786 ! get cutoff for atom 1
787 rci = EAMList%EAMParams(mytype_atom1)%eam_rcut
788 ! get type specific cutoff for atom 2
789 rcj = EAMList%EAMParams(mytype_atom2)%eam_rcut
790
791 drdx = d(1)/rij
792 drdy = d(2)/rij
793 drdz = d(3)/rij
794
795 if (rij.lt.rci) then
796 call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
797 EAMList%EAMParams(mytype_atom1)%eam_rvals, &
798 EAMList%EAMParams(mytype_atom1)%eam_rho_r, &
799 EAMList%EAMParams(mytype_atom1)%eam_rho_r_pp, &
800 rij, rha,drha,d2rha)
801 !! Calculate Phi(r) for atom1.
802 call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
803 EAMList%EAMParams(mytype_atom1)%eam_rvals, &
804 EAMList%EAMParams(mytype_atom1)%eam_phi_r, &
805 EAMList%EAMParams(mytype_atom1)%eam_phi_r_pp, &
806 rij, pha,dpha,d2pha)
807 endif
808
809 if (rij.lt.rcj) then
810 ! Calculate rho,drho and d2rho for atom1
811 call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
812 EAMList%EAMParams(mytype_atom2)%eam_rvals, &
813 EAMList%EAMParams(mytype_atom2)%eam_rho_r, &
814 EAMList%EAMParams(mytype_atom2)%eam_rho_r_pp, &
815 rij, rhb,drhb,d2rhb)
816
817 !! Calculate Phi(r) for atom2.
818 call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
819 EAMList%EAMParams(mytype_atom2)%eam_rvals, &
820 EAMList%EAMParams(mytype_atom2)%eam_phi_r, &
821 EAMList%EAMParams(mytype_atom2)%eam_phi_r_pp, &
822 rij, phb,dphb,d2phb)
823 endif
824
825 if (rij.lt.rci) then
826 phab = phab + 0.5E0_DP*(rhb/rha)*pha
827 dvpdr = dvpdr + 0.5E0_DP*((rhb/rha)*dpha + &
828 pha*((drhb/rha) - (rhb*drha/rha/rha)))
829 d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rhb/rha)*d2pha + &
830 2.0E0_DP*dpha*((drhb/rha) - (rhb*drha/rha/rha)) + &
831 pha*((d2rhb/rha) - 2.0E0_DP*(drhb*drha/rha/rha) + &
832 (2.0E0_DP*rhb*drha*drha/rha/rha/rha) - (rhb*d2rha/rha/rha)))
833 endif
834
835 if (rij.lt.rcj) then
836 phab = phab + 0.5E0_DP*(rha/rhb)*phb
837 dvpdr = dvpdr + 0.5E0_DP*((rha/rhb)*dphb + &
838 phb*((drha/rhb) - (rha*drhb/rhb/rhb)))
839 d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rha/rhb)*d2phb + &
840 2.0E0_DP*dphb*((drha/rhb) - (rha*drhb/rhb/rhb)) + &
841 phb*((d2rha/rhb) - 2.0E0_DP*(drha*drhb/rhb/rhb) + &
842 (2.0E0_DP*rha*drhb*drhb/rhb/rhb/rhb) - (rha*d2rhb/rhb/rhb)))
843 endif
844
845 drhoidr = drha
846 drhojdr = drhb
847
848 d2rhoidrdr = d2rha
849 d2rhojdrdr = d2rhb
850
851
852 #ifdef IS_MPI
853 dudr = drhojdr*dfrhodrho_row(atom1)+drhoidr*dfrhodrho_col(atom2) &
854 + dvpdr
855
856 #else
857 dudr = drhojdr*dfrhodrho(atom1)+drhoidr*dfrhodrho(atom2) &
858 + dvpdr
859 ! write(*,*) "Atom1,Atom2, dfrhodrho(atom1) dfrhodrho(atom2): ", atom1,atom2,dfrhodrho(atom1),dfrhodrho(atom2)
860 #endif
861
862 fx = dudr * drdx
863 fy = dudr * drdy
864 fz = dudr * drdz
865
866
867 #ifdef IS_MPI
868 if (do_pot) then
869 pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + phab*0.5
870 pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + phab*0.5
871 end if
872
873 f_Row(1,atom1) = f_Row(1,atom1) + fx
874 f_Row(2,atom1) = f_Row(2,atom1) + fy
875 f_Row(3,atom1) = f_Row(3,atom1) + fz
876
877 f_Col(1,atom2) = f_Col(1,atom2) - fx
878 f_Col(2,atom2) = f_Col(2,atom2) - fy
879 f_Col(3,atom2) = f_Col(3,atom2) - fz
880 #else
881
882 if(do_pot) then
883 pot = pot + phab
884 end if
885
886 f(1,atom1) = f(1,atom1) + fx
887 f(2,atom1) = f(2,atom1) + fy
888 f(3,atom1) = f(3,atom1) + fz
889
890 f(1,atom2) = f(1,atom2) - fx
891 f(2,atom2) = f(2,atom2) - fy
892 f(3,atom2) = f(3,atom2) - fz
893 #endif
894
895 vpair = vpair + phab
896 #ifdef IS_MPI
897 id1 = AtomRowToGlobal(atom1)
898 id2 = AtomColToGlobal(atom2)
899 #else
900 id1 = atom1
901 id2 = atom2
902 #endif
903
904 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
905
906 fpair(1) = fpair(1) + fx
907 fpair(2) = fpair(2) + fy
908 fpair(3) = fpair(3) + fz
909
910 endif
911
912 if (nmflag) then
913
914 drhoidr = drha
915 drhojdr = drhb
916 d2rhoidrdr = d2rha
917 d2rhojdrdr = d2rhb
918
919 #ifdef IS_MPI
920 d2 = d2vpdrdr + &
921 d2rhoidrdr*dfrhodrho_col(atom2) + &
922 d2rhojdrdr*dfrhodrho_row(atom1) + &
923 drhoidr*drhoidr*d2frhodrhodrho_col(atom2) + &
924 drhojdr*drhojdr*d2frhodrhodrho_row(atom1)
925
926 #else
927
928 d2 = d2vpdrdr + &
929 d2rhoidrdr*dfrhodrho(atom2) + &
930 d2rhojdrdr*dfrhodrho(atom1) + &
931 drhoidr*drhoidr*d2frhodrhodrho(atom2) + &
932 drhojdr*drhojdr*d2frhodrhodrho(atom1)
933 #endif
934 end if
935
936 endif
937 end subroutine do_eam_pair
938
939
940 subroutine eam_splint(nx, xa, ya, yppa, x, y, dy, d2y)
941
942 integer :: atype, nx, j
943 real( kind = DP ), dimension(:) :: xa
944 real( kind = DP ), dimension(:) :: ya
945 real( kind = DP ), dimension(:) :: yppa
946 real( kind = DP ) :: x, y
947 real( kind = DP ) :: dy, d2y
948 real( kind = DP ) :: del, h, a, b, c, d
949 integer :: pp_arraySize
950
951
952 ! this spline code assumes that the x points are equally spaced
953 ! do not attempt to use this code if they are not.
954
955
956 ! find the closest point with a value below our own:
957 j = FLOOR(real((nx-1),kind=dp) * (x - xa(1)) / (xa(nx) - xa(1))) + 1
958
959 ! check to make sure we're inside the spline range:
960 if ((j.gt.nx).or.(j.lt.1)) then
961 write(errMSG,*) "EAM_splint: x is outside bounds of spline: ",x,j
962 call handleError(routineName,errMSG)
963 endif
964 ! check to make sure we haven't screwed up the calculation of j:
965 if ((x.lt.xa(j)).or.(x.gt.xa(j+1))) then
966 if (j.ne.nx) then
967 write(errMSG,*) "EAM_splint:",x," x is outside bounding range"
968 call handleError(routineName,errMSG)
969 endif
970 endif
971
972 del = xa(j+1) - x
973 h = xa(j+1) - xa(j)
974
975 a = del / h
976 b = 1.0E0_DP - a
977 c = a*(a*a - 1.0E0_DP)*h*h/6.0E0_DP
978 d = b*(b*b - 1.0E0_DP)*h*h/6.0E0_DP
979
980 y = a*ya(j) + b*ya(j+1) + c*yppa(j) + d*yppa(j+1)
981
982 dy = (ya(j+1)-ya(j))/h &
983 - (3.0E0_DP*a*a - 1.0E0_DP)*h*yppa(j)/6.0E0_DP &
984 + (3.0E0_DP*b*b - 1.0E0_DP)*h*yppa(j+1)/6.0E0_DP
985
986
987 d2y = a*yppa(j) + b*yppa(j+1)
988
989
990 end subroutine eam_splint
991
992
993 subroutine eam_spline(nx, xa, ya, yppa, yp1, ypn, boundary)
994
995
996 ! yp1 and ypn are the first derivatives of y at the two endpoints
997 ! if boundary is 'L' the lower derivative is used
998 ! if boundary is 'U' the upper derivative is used
999 ! if boundary is 'B' then both derivatives are used
1000 ! if boundary is anything else, then both derivatives are assumed to be 0
1001
1002 integer :: nx, i, k, max_array_size
1003
1004 real( kind = DP ), dimension(:) :: xa
1005 real( kind = DP ), dimension(:) :: ya
1006 real( kind = DP ), dimension(:) :: yppa
1007 real( kind = DP ), dimension(size(xa)) :: u
1008 real( kind = DP ) :: yp1,ypn,un,qn,sig,p
1009 character(len=*) :: boundary
1010
1011 ! make sure the sizes match
1012 if ((nx /= size(xa)) .or. (nx /= size(ya))) then
1013 call handleWarning("EAM_SPLINE","Array size mismatch")
1014 end if
1015
1016 if ((boundary.eq.'l').or.(boundary.eq.'L').or. &
1017 (boundary.eq.'b').or.(boundary.eq.'B')) then
1018 yppa(1) = -0.5E0_DP
1019 u(1) = (3.0E0_DP/(xa(2)-xa(1)))*((ya(2)-&
1020 ya(1))/(xa(2)-xa(1))-yp1)
1021 else
1022 yppa(1) = 0.0E0_DP
1023 u(1) = 0.0E0_DP
1024 endif
1025
1026 do i = 2, nx - 1
1027 sig = (xa(i) - xa(i-1)) / (xa(i+1) - xa(i-1))
1028 p = sig * yppa(i-1) + 2.0E0_DP
1029 yppa(i) = (sig - 1.0E0_DP) / p
1030 u(i) = (6.0E0_DP*((ya(i+1)-ya(i))/(xa(i+1)-xa(i)) - &
1031 (ya(i)-ya(i-1))/(xa(i)-xa(i-1)))/ &
1032 (xa(i+1)-xa(i-1)) - sig * u(i-1))/p
1033 enddo
1034
1035 if ((boundary.eq.'u').or.(boundary.eq.'U').or. &
1036 (boundary.eq.'b').or.(boundary.eq.'B')) then
1037 qn = 0.5E0_DP
1038 un = (3.0E0_DP/(xa(nx)-xa(nx-1)))* &
1039 (ypn-(ya(nx)-ya(nx-1))/(xa(nx)-xa(nx-1)))
1040 else
1041 qn = 0.0E0_DP
1042 un = 0.0E0_DP
1043 endif
1044
1045 yppa(nx)=(un-qn*u(nx-1))/(qn*yppa(nx-1)+1.0E0_DP)
1046
1047 do k = nx-1, 1, -1
1048 yppa(k)=yppa(k)*yppa(k+1)+u(k)
1049 enddo
1050
1051 end subroutine eam_spline
1052
1053 end module eam