ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/trunk/src/UseTheForce/DarkSide/suttonchen.F90
Revision: 1386
Committed: Fri Oct 23 18:41:09 2009 UTC (15 years, 7 months ago) by gezelter
File size: 19719 byte(s)
Log Message:
removing MPI responsibilities from the lowest level force routines.  This is
in preparation for migrating these routines (LJ, electrostatic, eam, suttonchen,
gay-berne, sticky) to C++

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 definitions
48 use simulation
49 use force_globals
50 use status
51 use atype_module
52 use vector_class
53 use fForceOptions
54 use interpolation
55 #ifdef IS_MPI
56 use mpiSimulation
57 #endif
58 implicit none
59 PRIVATE
60 #define __FORTRAN90
61 #include "UseTheForce/DarkSide/fInteractionMap.h"
62
63 !! number of points for the spline approximations
64 INTEGER, PARAMETER :: np = 3000
65
66 logical, save :: SC_FF_initialized = .false.
67 integer, save :: SC_Mixing_Policy
68 real(kind = dp), save :: SC_rcut
69 logical, save :: haveRcut = .false.
70 logical, save :: haveMixingMap = .false.
71 logical, save :: useGeometricDistanceMixing = .false.
72 logical, save :: cleanArrays = .true.
73 logical, save :: arraysAllocated = .false.
74
75
76 character(len = statusMsgSize) :: errMesg
77 integer :: sc_err
78
79 character(len = 200) :: errMsg
80 character(len=*), parameter :: RoutineName = "Sutton-Chen MODULE"
81
82 type, private :: SCtype
83 integer :: atid
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
94 real( kind = dp), dimension(:), allocatable :: rho
95 real( kind = dp), dimension(:), allocatable :: frho
96 real( kind = dp), dimension(:), allocatable :: dfrhodrho
97
98 !! Arrays for MPI storage
99 #ifdef IS_MPI
100 real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_col
101 real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_row
102 real( kind = dp),save, dimension(:), allocatable :: frho_row
103 real( kind = dp),save, dimension(:), allocatable :: frho_col
104 real( kind = dp),save, dimension(:), allocatable :: rho_row
105 real( kind = dp),save, dimension(:), allocatable :: rho_col
106 real( kind = dp),save, dimension(:), allocatable :: rho_tmp
107 #endif
108
109 type, private :: SCTypeList
110 integer :: nSCTypes = 0
111 integer :: currentSCtype = 0
112 type (SCtype), pointer :: SCtypes(:) => null()
113 integer, pointer :: atidToSCtype(:) => null()
114 end type SCTypeList
115
116 type (SCTypeList), save :: SCList
117
118 type:: MixParameters
119 real(kind=DP) :: alpha
120 real(kind=DP) :: epsilon
121 real(kind=DP) :: m
122 real(Kind=DP) :: n
123 real(kind=dp) :: rCut
124 real(kind=dp) :: vCut
125 logical :: rCutWasSet = .false.
126 type(cubicSpline) :: V
127 type(cubicSpline) :: phi
128 end type MixParameters
129
130 type(MixParameters), dimension(:,:), allocatable :: MixingMap
131
132 public :: setCutoffSC
133 public :: do_SC_pair
134 public :: newSCtype
135 public :: calc_SC_prepair_rho
136 public :: calc_SC_preforce_Frho
137 public :: clean_SC
138 public :: destroySCtypes
139 public :: getSCCut
140 ! public :: setSCDefaultCutoff
141 ! public :: setSCUniformCutoff
142
143
144 contains
145
146
147 subroutine newSCtype(c_ident,c,m,n,alpha,epsilon,status)
148 real (kind = dp ) :: c ! Density Scaling
149 real (kind = dp ) :: m ! Density Exponent
150 real (kind = dp ) :: n ! Pair Potential Exponent
151 real (kind = dp ) :: alpha ! Length Scaling
152 real (kind = dp ) :: epsilon ! Energy Scaling
153 integer :: c_ident
154 integer :: status
155 integer :: nAtypes,nSCTypes,myATID
156 integer :: maxVals
157 integer :: alloc_stat
158 integer :: current
159 integer,pointer :: Matchlist(:) => null()
160
161 status = 0
162
163
164 !! Assume that atypes has already been set and get the total number of types in atypes
165
166
167 ! check to see if this is the first time into
168 if (.not.associated(SCList%SCTypes)) then
169 call getMatchingElementList(atypes, "is_SC", .true., nSCtypes, MatchList)
170 SCList%nSCtypes = nSCtypes
171 allocate(SCList%SCTypes(nSCTypes))
172 nAtypes = getSize(atypes)
173 allocate(SCList%atidToSCType(nAtypes))
174 SCList%atidToSCType = -1
175 end if
176
177 SCList%currentSCType = SCList%currentSCType + 1
178 current = SCList%currentSCType
179
180 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
181 SCList%atidToSCType(myATID) = current
182
183
184 SCList%SCTypes(current)%atid = c_ident
185 SCList%SCTypes(current)%alpha = alpha
186 SCList%SCTypes(current)%c = c
187 SCList%SCTypes(current)%m = m
188 SCList%SCTypes(current)%n = n
189 SCList%SCTypes(current)%epsilon = epsilon
190 end subroutine newSCtype
191
192
193 subroutine destroySCTypes()
194 if (associated(SCList%SCtypes)) then
195 deallocate(SCList%SCTypes)
196 SCList%SCTypes=>null()
197 end if
198 if (associated(SCList%atidToSCtype)) then
199 deallocate(SCList%atidToSCtype)
200 SCList%atidToSCtype=>null()
201 end if
202 ! Reset Capacity
203 SCList%nSCTypes = 0
204 SCList%currentSCtype=0
205
206 end subroutine destroySCTypes
207
208 function getSCCut(atomID) result(cutValue)
209 integer, intent(in) :: atomID
210 integer :: scID
211 real(kind=dp) :: cutValue
212
213 scID = SCList%atidToSCType(atomID)
214 cutValue = 2.0_dp * SCList%SCTypes(scID)%alpha
215 end function getSCCut
216
217 subroutine createMixingMap()
218 integer :: nSCtypes, i, j, k
219 real ( kind = dp ) :: e1, e2, m1, m2, alpha1, alpha2, n1, n2
220 real ( kind = dp ) :: epsilon, m, n, alpha, rCut, vCut, dr, r
221 real ( kind = dp ), dimension(np) :: rvals, vvals, phivals
222
223 if (SCList%currentSCtype == 0) then
224 call handleError("SuttonChen", "No members in SCMap")
225 return
226 end if
227
228 nSCtypes = SCList%nSCtypes
229
230 if (.not. allocated(MixingMap)) then
231 allocate(MixingMap(nSCtypes, nSCtypes))
232 endif
233 useGeometricDistanceMixing = usesGeometricDistanceMixing()
234 do i = 1, nSCtypes
235
236 e1 = SCList%SCtypes(i)%epsilon
237 m1 = SCList%SCtypes(i)%m
238 n1 = SCList%SCtypes(i)%n
239 alpha1 = SCList%SCtypes(i)%alpha
240
241 do j = 1, nSCtypes
242
243 e2 = SCList%SCtypes(j)%epsilon
244 m2 = SCList%SCtypes(j)%m
245 n2 = SCList%SCtypes(j)%n
246 alpha2 = SCList%SCtypes(j)%alpha
247
248 if (useGeometricDistanceMixing) then
249 alpha = sqrt(alpha1 * alpha2) !SC formulation
250 else
251 alpha = 0.5_dp * (alpha1 + alpha2) ! Goddard formulation
252 endif
253 rcut = 2.0_dp * alpha
254 epsilon = sqrt(e1 * e2)
255 m = 0.5_dp*(m1+m2)
256 n = 0.5_dp*(n1+n2)
257
258 dr = (rCut) / dble(np-1)
259 rvals(1) = 0.0_dp
260 vvals(1) = 0.0_dp
261 phivals(1) = 0.0_dp
262
263 do k = 2, np
264 r = dble(k-1)*dr
265 rvals(k) = r
266 vvals(k) = epsilon*((alpha/r)**n)
267 phivals(k) = (alpha/r)**m
268 enddo
269
270 vCut = epsilon*((alpha/rCut)**n)
271
272 call newSpline(MixingMap(i,j)%V, rvals, vvals, .true.)
273 call newSpline(MixingMap(i,j)%phi, rvals, phivals, .true.)
274
275 MixingMap(i,j)%epsilon = epsilon
276 MixingMap(i,j)%m = m
277 MixingMap(i,j)%n = n
278 MixingMap(i,j)%alpha = alpha
279 MixingMap(i,j)%rCut = rcut
280 MixingMap(i,j)%vCut = vCut
281 enddo
282 enddo
283
284 haveMixingMap = .true.
285
286 end subroutine createMixingMap
287
288
289 !! routine checks to see if array is allocated, deallocates array if allocated
290 !! and then creates the array to the required size
291 subroutine allocateSC()
292 integer :: status
293
294 #ifdef IS_MPI
295 integer :: nAtomsInRow
296 integer :: nAtomsInCol
297 #endif
298 integer :: alloc_stat
299
300
301 status = 0
302 #ifdef IS_MPI
303 nAtomsInRow = getNatomsInRow(plan_atom_row)
304 nAtomsInCol = getNatomsInCol(plan_atom_col)
305 #endif
306
307 if (allocated(frho)) deallocate(frho)
308 allocate(frho(nlocal),stat=alloc_stat)
309 if (alloc_stat /= 0) then
310 status = -1
311 end if
312
313 if (allocated(rho)) deallocate(rho)
314 allocate(rho(nlocal),stat=alloc_stat)
315 if (alloc_stat /= 0) then
316 status = -1
317 end if
318
319 if (allocated(dfrhodrho)) deallocate(dfrhodrho)
320 allocate(dfrhodrho(nlocal),stat=alloc_stat)
321 if (alloc_stat /= 0) then
322 status = -1
323 end if
324
325 #ifdef IS_MPI
326
327 if (allocated(rho_tmp)) deallocate(rho_tmp)
328 allocate(rho_tmp(nlocal),stat=alloc_stat)
329 if (alloc_stat /= 0) then
330 status = -1
331 end if
332
333
334 if (allocated(frho_row)) deallocate(frho_row)
335 allocate(frho_row(nAtomsInRow),stat=alloc_stat)
336 if (alloc_stat /= 0) then
337 status = -1
338 end if
339 if (allocated(rho_row)) deallocate(rho_row)
340 allocate(rho_row(nAtomsInRow),stat=alloc_stat)
341 if (alloc_stat /= 0) then
342 status = -1
343 end if
344 if (allocated(dfrhodrho_row)) deallocate(dfrhodrho_row)
345 allocate(dfrhodrho_row(nAtomsInRow),stat=alloc_stat)
346 if (alloc_stat /= 0) then
347 status = -1
348 end if
349
350 ! Now do column arrays
351
352 if (allocated(frho_col)) deallocate(frho_col)
353 allocate(frho_col(nAtomsInCol),stat=alloc_stat)
354 if (alloc_stat /= 0) then
355 status = -1
356 end if
357 if (allocated(rho_col)) deallocate(rho_col)
358 allocate(rho_col(nAtomsInCol),stat=alloc_stat)
359 if (alloc_stat /= 0) then
360 status = -1
361 end if
362 if (allocated(dfrhodrho_col)) deallocate(dfrhodrho_col)
363 allocate(dfrhodrho_col(nAtomsInCol),stat=alloc_stat)
364 if (alloc_stat /= 0) then
365 status = -1
366 end if
367
368 #endif
369 if (status == -1) then
370 call handleError("SuttonChen:allocateSC","Error in allocating SC arrays")
371 end if
372 arraysAllocated = .true.
373 end subroutine allocateSC
374
375 subroutine setCutoffSC(rcut)
376 real(kind=dp) :: rcut
377 SC_rcut = rcut
378 end subroutine setCutoffSC
379
380 !! This array allocates module arrays if needed and builds mixing map.
381 subroutine clean_SC()
382 if (.not.arraysAllocated) call allocateSC()
383 if (.not.haveMixingMap) call createMixingMap()
384 ! clean non-IS_MPI first
385 frho = 0.0_dp
386 rho = 0.0_dp
387 dfrhodrho = 0.0_dp
388 ! clean MPI if needed
389 #ifdef IS_MPI
390 frho_row = 0.0_dp
391 frho_col = 0.0_dp
392 rho_row = 0.0_dp
393 rho_col = 0.0_dp
394 rho_tmp = 0.0_dp
395 dfrhodrho_row = 0.0_dp
396 dfrhodrho_col = 0.0_dp
397 #endif
398 end subroutine clean_SC
399
400 !! Calculates rho_r
401 subroutine calc_sc_prepair_rho(atom1, atom2, atid1, atid2, d, r, rijsq, rcut)
402 integer :: atom1, atom2, atid1, atid2
403 real(kind = dp), dimension(3) :: d
404 real(kind = dp), intent(inout) :: r
405 real(kind = dp), intent(inout) :: rijsq, rcut
406 ! value of electron density rho do to atom i at atom j
407 real(kind = dp) :: rho_i_at_j
408 ! value of electron density rho do to atom j at atom i
409 real(kind = dp) :: rho_j_at_i
410
411 ! we don't use the derivatives, dummy variables
412 real( kind = dp) :: drho
413 integer :: sc_err
414
415 integer :: myid_atom1 ! SC atid
416 integer :: myid_atom2
417
418 ! check to see if we need to be cleaned at the start of a force loop
419
420 if (cleanArrays) call clean_SC()
421 cleanArrays = .false.
422
423 Myid_atom1 = SCList%atidtoSCtype(Atid1)
424 Myid_atom2 = SCList%atidtoSCtype(Atid2)
425
426 call lookupUniformSpline(MixingMap(myid_atom1,myid_atom2)%phi, r, &
427 rho_i_at_j)
428 rho_j_at_i = rho_i_at_j
429
430 #ifdef IS_MPI
431 rho_col(atom2) = rho_col(atom2) + rho_i_at_j
432 rho_row(atom1) = rho_row(atom1) + rho_j_at_i
433 #else
434 rho(atom2) = rho(atom2) + rho_i_at_j
435 rho(atom1) = rho(atom1) + rho_j_at_i
436 #endif
437
438 end subroutine calc_sc_prepair_rho
439
440
441 !! Calculate the rho_a for all local atoms
442 subroutine calc_sc_preforce_Frho(nlocal, pot, particle_pot)
443 integer :: nlocal
444 real(kind=dp) :: pot
445 real(kind=dp), dimension(nlocal) :: particle_pot
446 integer :: i,j
447 integer :: atom
448 integer :: atype1
449 integer :: atid1
450 integer :: myid
451
452 !! Scatter the electron density from pre-pair calculation back to
453 !! local atoms
454
455
456 if (cleanArrays) call clean_SC()
457 cleanArrays = .false.
458
459
460 #ifdef IS_MPI
461 call scatter(rho_row,rho,plan_atom_row,sc_err)
462 if (sc_err /= 0 ) then
463 write(errMsg,*) " Error scattering rho_row into rho"
464 call handleError(RoutineName,errMesg)
465 endif
466 call scatter(rho_col,rho_tmp,plan_atom_col,sc_err)
467 if (sc_err /= 0 ) then
468 write(errMsg,*) " Error scattering rho_col into rho"
469 call handleError(RoutineName,errMesg)
470
471 endif
472
473 rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
474 #endif
475
476 !! Calculate F(rho) and derivative
477 do atom = 1, nlocal
478 Myid = SCList%atidtoSctype(Atid(atom))
479 ! Myid is set to -1 for non SC atoms.
480 ! Punt if we are a non-SC atom type.
481 if (Myid == -1) then
482 frho(atom) = 0.0_dp
483 dfrhodrho(atom) = 0.0_dp
484 else
485 frho(atom) = - SCList%SCTypes(Myid)%c * &
486 SCList%SCTypes(Myid)%epsilon * sqrt(rho(atom))
487
488 dfrhodrho(atom) = 0.5_dp*frho(atom)/rho(atom)
489 end if
490
491 pot = pot + frho(atom)
492 particle_pot(atom) = particle_pot(atom) + frho(atom)
493 enddo
494
495 #ifdef IS_MPI
496 !! communicate f(rho) and derivatives back into row and column arrays
497 call gather(frho,frho_row,plan_atom_row, sc_err)
498 if (sc_err /= 0) then
499 call handleError("calc_sc_forces()","MPI gather frho_row failure")
500 endif
501 call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, sc_err)
502 if (sc_err /= 0) then
503 call handleError("calc_sc_forces()","MPI gather dfrhodrho_row failure")
504 endif
505 call gather(frho,frho_col,plan_atom_col, sc_err)
506 if (sc_err /= 0) then
507 call handleError("calc_sc_forces()","MPI gather frho_col failure")
508 endif
509 call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, sc_err)
510 if (sc_err /= 0) then
511 call handleError("calc_sc_forces()","MPI gather dfrhodrho_col failure")
512 endif
513 #endif
514
515
516 end subroutine calc_sc_preforce_Frho
517
518 !! Does Sutton-Chen pairwise Force calculation.
519 subroutine do_sc_pair(atom1, atom2, atid1, atid2, d, rij, r2, rcut, sw, vpair, &
520 particle_pot, fpair, pot, f1, do_pot)
521 !Arguments
522 integer, intent(in) :: atom1, atom2
523 real( kind = dp ), intent(in) :: rij, r2, rcut
524 real( kind = dp ) :: pot, sw, vpair
525 real( kind = dp ), dimension(nLocal) :: particle_pot
526 real( kind = dp ), dimension(3) :: f1
527 real( kind = dp ), intent(in), dimension(3) :: d
528 real( kind = dp ), intent(inout), dimension(3) :: fpair
529
530 logical, intent(in) :: do_pot
531
532 real( kind = dp ) :: drdx, drdy, drdz
533 real( kind = dp ) :: dvpdr
534 real( kind = dp ) :: rhtmp, drhodr
535 real( kind = dp ) :: dudr
536 real( kind = dp ) :: Fx,Fy,Fz
537 real( kind = dp ) :: pot_temp, vptmp
538 real( kind = dp ) :: rcij, vcij
539 real( kind = dp ) :: fshift1, fshift2
540 integer :: id1, id2
541 integer :: mytype_atom1
542 integer :: mytype_atom2
543 integer :: atid1, atid2
544 !Local Variables
545
546 cleanArrays = .true.
547
548 mytype_atom1 = SCList%atidToSCType(atid1)
549 mytype_atom2 = SCList%atidTOSCType(atid2)
550
551 drdx = d(1)/rij
552 drdy = d(2)/rij
553 drdz = d(3)/rij
554
555 rcij = MixingMap(mytype_atom1,mytype_atom2)%rCut
556 vcij = MixingMap(mytype_atom1,mytype_atom2)%vCut
557
558 call lookupUniformSpline1d(MixingMap(mytype_atom1, mytype_atom2)%phi, &
559 rij, rhtmp, drhodr)
560
561 call lookupUniformSpline1d(MixingMap(mytype_atom1, mytype_atom2)%V, &
562 rij, vptmp, dvpdr)
563
564 #ifdef IS_MPI
565 dudr = drhodr*(dfrhodrho_row(atom1) + dfrhodrho_col(atom2)) + dvpdr
566 #else
567 dudr = drhodr*(dfrhodrho(atom1)+ dfrhodrho(atom2)) + dvpdr
568 #endif
569
570 pot_temp = vptmp - vcij
571
572 vpair = vpair + pot_temp
573
574 fx = dudr * drdx
575 fy = dudr * drdy
576 fz = dudr * drdz
577
578 #ifdef IS_MPI
579 if (do_pot) then
580
581 ! particle_pot is the difference between the full potential
582 ! and the full potential without the presence of a particular
583 ! particle (atom1).
584 !
585 ! This reduces the density at other particle locations, so
586 ! we need to recompute the density at atom2 assuming atom1
587 ! didn't contribute. This then requires recomputing the
588 ! density functional for atom2 as well.
589 !
590 ! Most of the particle_pot heavy lifting comes from the
591 ! pair interaction, and will be handled by vpair.
592
593 fshift1 = -SCList%SCTypes(mytype_atom1)%c * &
594 SCList%SCTypes(mytype_atom1)%epsilon * &
595 sqrt(rho_row(atom1)-rhtmp)
596 fshift2 = -SCList%SCTypes(mytype_atom2)%c * &
597 SCList%SCTypes(mytype_atom2)%epsilon * &
598 sqrt(rho_col(atom2)-rhtmp)
599
600 ppot_row(atom1) = ppot_row(atom1) - frho_row(atom2) + fshift2
601 ppot_col(atom2) = ppot_col(atom2) - frho_col(atom1) + fshift1
602
603 end if
604
605
606 #else
607
608 if(do_pot) then
609
610 fshift1 = -SCList%SCTypes(mytype_atom1)%c * &
611 SCList%SCTypes(mytype_atom1)%epsilon * &
612 sqrt(rho(atom1)-rhtmp)
613 fshift2 = -SCList%SCTypes(mytype_atom2)%c * &
614 SCList%SCTypes(mytype_atom2)%epsilon * &
615 sqrt(rho(atom2)-rhtmp)
616
617 particle_pot(atom1) = particle_pot(atom1) - frho(atom2) + fshift2
618 particle_pot(atom2) = particle_pot(atom2) - frho(atom1) + fshift1
619
620 end if
621
622 #endif
623 pot = pot + pot_temp
624
625 f1(1) = f1(1) + fx
626 f1(2) = f1(2) + fy
627 f1(3) = f1(3) + fz
628
629 end subroutine do_sc_pair
630 end module suttonchen