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

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/eam.F90 (file contents):
Revision 1624 by chuckv, Thu Oct 21 15:25:30 2004 UTC vs.
Revision 2717 by gezelter, Mon Apr 17 21:49:12 2006 UTC

# Line 1 | Line 1
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   module eam
43    use simulation
44    use force_globals
45    use status
46    use atype_module
47 <  use Vector_class
47 >  use vector_class
48 >  use interpolation
49   #ifdef IS_MPI
50    use mpiSimulation
51   #endif
52    implicit none
53    PRIVATE
54 + #define __FORTRAN90
55 + #include "UseTheForce/DarkSide/fInteractionMap.h"
56  
57    INTEGER, PARAMETER :: DP = selected_real_kind(15)
58  
# Line 22 | Line 66 | module eam
66  
67    character(len = 200) :: errMsg
68    character(len=*), parameter :: RoutineName =  "EAM MODULE"
69 < !! Logical that determines if eam arrays should be zeroed
69 >  !! Logical that determines if eam arrays should be zeroed
70    logical :: cleanme = .true.
27  logical :: nmflag  = .false.
71  
29
72    type, private :: EAMtype
73       integer           :: eam_atype      
32     real( kind = DP ) :: eam_dr          
33     integer           :: eam_nr          
34     integer           :: eam_nrho          
74       real( kind = DP ) :: eam_lattice        
36     real( kind = DP ) :: eam_drho      
75       real( kind = DP ) :: eam_rcut    
76       integer           :: eam_atype_map
77 <    
78 <     real( kind = DP ), pointer, dimension(:) :: eam_rvals        => null()
79 <     real( kind = DP ), pointer, dimension(:) :: eam_rhovals      => null()
80 <     real( kind = DP ), pointer, dimension(:) :: eam_F_rho        => null()
43 <     real( kind = DP ), pointer, dimension(:) :: eam_Z_r          => null()
44 <     real( kind = DP ), pointer, dimension(:) :: eam_rho_r        => null()
45 <     real( kind = DP ), pointer, dimension(:) :: eam_phi_r        => null()
46 <     real( kind = DP ), pointer, dimension(:) :: eam_F_rho_pp     => null()
47 <     real( kind = DP ), pointer, dimension(:) :: eam_Z_r_pp       => null()
48 <     real( kind = DP ), pointer, dimension(:) :: eam_rho_r_pp     => null()
49 <     real( kind = DP ), pointer, dimension(:) :: eam_phi_r_pp     => null()
77 >     type(cubicSpline) :: rho
78 >     type(cubicSpline) :: Z
79 >     type(cubicSpline) :: F
80 >     type(cubicSpline) :: phi
81    end type EAMtype
82  
52
83    !! Arrays for derivatives used in force calculation
84    real( kind = dp), dimension(:), allocatable :: frho
85    real( kind = dp), dimension(:), allocatable :: rho
56
86    real( kind = dp), dimension(:), allocatable :: dfrhodrho
58  real( kind = dp), dimension(:), allocatable :: d2frhodrhodrho
87  
88 <
61 < !! Arrays for MPI storage
88 >  !! Arrays for MPI storage
89   #ifdef IS_MPI
90    real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_col
91    real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_row
# Line 67 | Line 94 | module eam
94    real( kind = dp),save, dimension(:), allocatable :: rho_row
95    real( kind = dp),save, dimension(:), allocatable :: rho_col
96    real( kind = dp),save, dimension(:), allocatable :: rho_tmp
70  real( kind = dp),save, dimension(:), allocatable :: d2frhodrhodrho_col
71  real( kind = dp),save, dimension(:), allocatable :: d2frhodrhodrho_row
97   #endif
98  
99    type, private :: EAMTypeList
100       integer           :: n_eam_types = 0
101       integer           :: currentAddition = 0
102 <    
102 >
103       type (EAMtype), pointer  :: EAMParams(:) => null()
104 +     integer, pointer         :: atidToEAMType(:) => null()
105    end type EAMTypeList
106  
81
107    type (eamTypeList), save :: EAMList
108  
109    !! standard eam stuff  
# Line 91 | Line 116 | module eam
116    public :: calc_eam_prepair_rho
117    public :: calc_eam_preforce_Frho
118    public :: clean_EAM
119 +  public :: destroyEAMTypes
120 +  public :: getEAMCut
121  
122   contains
123  
97
124    subroutine newEAMtype(lattice_constant,eam_nrho,eam_drho,eam_nr,&
125 <       eam_dr,rcut,eam_Z_r,eam_rho_r,eam_F_rho,&
100 <       eam_ident,status)
125 >       eam_dr,rcut,eam_Z_r,eam_rho_r,eam_F_rho, c_ident, status)
126      real (kind = dp )                      :: lattice_constant
127      integer                                :: eam_nrho
128      real (kind = dp )                      :: eam_drho
129      integer                                :: eam_nr
130      real (kind = dp )                      :: eam_dr
131      real (kind = dp )                      :: rcut
132 <    real (kind = dp ), dimension(eam_nr)   :: eam_Z_r
133 <    real (kind = dp ), dimension(eam_nr)   :: eam_rho_r
134 <    real (kind = dp ), dimension(eam_nrho) :: eam_F_rho
135 <    integer                                :: eam_ident
132 >    real (kind = dp ), dimension(eam_nr)   :: eam_Z_r, rvals
133 >    real (kind = dp ), dimension(eam_nr)   :: eam_rho_r, eam_phi_r
134 >    real (kind = dp ), dimension(eam_nrho) :: eam_F_rho, rhovals
135 >    integer                                :: c_ident
136      integer                                :: status
137  
138 <    integer                                :: nAtypes
138 >    integer                                :: nAtypes,nEAMTypes,myATID
139      integer                                :: maxVals
140      integer                                :: alloc_stat
141 <    integer                                :: current
141 >    integer                                :: current, j
142      integer,pointer                        :: Matchlist(:) => null()
143  
144      status = 0
145  
121
146      !! Assume that atypes has already been set and get the total number of types in atypes
147      !! Also assume that every member of atypes is a EAM model.
124  
148  
149      ! check to see if this is the first time into
150      if (.not.associated(EAMList%EAMParams)) then
151 <       call getMatchingElementList(atypes, "is_EAM", .true., nAtypes, MatchList)
152 <       EAMList%n_eam_types = nAtypes
153 <       allocate(EAMList%EAMParams(nAtypes))
151 >       call getMatchingElementList(atypes, "is_EAM", .true., nEAMtypes, MatchList)
152 >       EAMList%n_eam_types = nEAMtypes
153 >       allocate(EAMList%EAMParams(nEAMTypes))
154 >       nAtypes = getSize(atypes)
155 >       allocate(EAMList%atidToEAMType(nAtypes))
156      end if
157  
158      EAMList%currentAddition = EAMList%currentAddition + 1
159      current = EAMList%currentAddition
135    
160  
161 <    call allocate_EAMType(eam_nrho,eam_nr,EAMList%EAMParams(current),stat=alloc_stat)
162 <    if (alloc_stat /= 0) then
139 <       status = -1
140 <       return
141 <    end if
161 >    myATID =  getFirstMatchingElement(atypes, "c_ident", c_ident)
162 >    EAMList%atidToEAMType(myATID) = current
163  
164 <    ! this is a possible bug, we assume a correspondence between the vector atypes and
144 <    ! EAMAtypes
145 <      
146 <    EAMList%EAMParams(current)%eam_atype    = eam_ident
164 >    EAMList%EAMParams(current)%eam_atype    = c_ident
165      EAMList%EAMParams(current)%eam_lattice  = lattice_constant
148    EAMList%EAMParams(current)%eam_nrho     = eam_nrho
149    EAMList%EAMParams(current)%eam_drho     = eam_drho
150    EAMList%EAMParams(current)%eam_nr       = eam_nr
151    EAMList%EAMParams(current)%eam_dr       = eam_dr
166      EAMList%EAMParams(current)%eam_rcut     = rcut
153    EAMList%EAMParams(current)%eam_Z_r      = eam_Z_r
154    EAMList%EAMParams(current)%eam_rho_r    = eam_rho_r
155    EAMList%EAMParams(current)%eam_F_rho    = eam_F_rho
167  
168 +    ! Build array of r values
169 +    do j = 1, eam_nr
170 +       rvals(j) = real(j-1,kind=dp) * eam_dr
171 +    end do
172 +    
173 +    ! Build array of rho values
174 +    do j = 1, eam_nrho
175 +       rhovals(j) = real(j-1,kind=dp) * eam_drho
176 +    end do
177 +
178 +    ! convert from eV to kcal / mol:
179 +    do j = 1, eam_nrho
180 +       eam_F_rho(j) = eam_F_rho(j) * 23.06054E0_DP
181 +    end do
182 +    
183 +    ! precompute the pair potential and get it into kcal / mol:
184 +    eam_phi_r(1) = 0.0E0_DP
185 +    do j = 2, eam_nr
186 +       eam_phi_r(j) = 331.999296E0_DP * (eam_Z_r(j)**2) / rvals(j)
187 +    enddo
188 +
189 +    call newSpline(EAMList%EAMParams(current)%rho, rvals, rhovals, &
190 +         0.0d0, 0.0d0, .true.)
191 +    call newSpline(EAMList%EAMParams(current)%Z,   rvals, eam_Z_r, &
192 +         0.0d0, 0.0d0, .true.)
193 +    call newSpline(EAMList%EAMParams(current)%F, rhovals, eam_F_rho, &
194 +         0.0d0, 0.0d0, .true.)
195 +    call newSpline(EAMList%EAMParams(current)%phi, rvals, eam_phi_r, &
196 +         0.0d0, 0.0d0, .true.)
197    end subroutine newEAMtype
198  
199  
200 +  ! kills all eam types entered and sets simulation to uninitalized
201 +  subroutine destroyEAMtypes()
202 +    integer :: i
203 +    type(EAMType), pointer :: tempEAMType=>null()
204  
205 +    do i = 1, EAMList%n_eam_types
206 +       tempEAMType => eamList%EAMParams(i)
207 +       call deallocate_EAMType(tempEAMType)
208 +    end do
209 +    if(associated( eamList%EAMParams)) deallocate( eamList%EAMParams)
210 +    eamList%EAMParams => null()
211 +
212 +    eamList%n_eam_types = 0
213 +    eamList%currentAddition = 0
214 +  end subroutine destroyEAMtypes
215 +
216 +  function getEAMCut(atomID) result(cutValue)
217 +    integer, intent(in) :: atomID
218 +    integer :: eamID
219 +    real(kind=dp) :: cutValue
220 +    
221 +    eamID = EAMList%atidToEAMType(atomID)
222 +    cutValue = EAMList%EAMParams(eamID)%eam_rcut
223 +  end function getEAMCut
224 +
225    subroutine init_EAM_FF(status)
226      integer :: status
227      integer :: i,j
228      real(kind=dp) :: current_rcut_max
229 + #ifdef IS_MPI
230 +    integer :: nAtomsInRow
231 +    integer :: nAtomsInCol
232 + #endif
233      integer :: alloc_stat
234      integer :: number_r, number_rho
235  
168
236      status = 0
237      if (EAMList%currentAddition == 0) then
238         call handleError("init_EAM_FF","No members in EAMList")
239         status = -1
240         return
241      end if
175
176
177       do i = 1, EAMList%currentAddition
178
179 ! Build array of r values
180
181          do j = 1,EAMList%EAMParams(i)%eam_nr
182             EAMList%EAMParams(i)%eam_rvals(j) = &
183                  real(j-1,kind=dp)* &
184                  EAMList%EAMParams(i)%eam_dr
185              end do
186 ! Build array of rho values
187          do j = 1,EAMList%EAMParams(i)%eam_nrho
188             EAMList%EAMParams(i)%eam_rhovals(j) = &
189                  real(j-1,kind=dp)* &
190                  EAMList%EAMParams(i)%eam_drho
191          end do
192          ! convert from eV to kcal / mol:
193          EAMList%EAMParams(i)%eam_F_rho = EAMList%EAMParams(i)%eam_F_rho * 23.06054E0_DP
194
195          ! precompute the pair potential and get it into kcal / mol:
196          EAMList%EAMParams(i)%eam_phi_r(1) = 0.0E0_DP
197          do j = 2, EAMList%EAMParams(i)%eam_nr
198             EAMList%EAMParams(i)%eam_phi_r(j) = (EAMList%EAMParams(i)%eam_Z_r(j)**2)/EAMList%EAMParams(i)%eam_rvals(j)
199             EAMList%EAMParams(i)%eam_phi_r(j) =  EAMList%EAMParams(i)%eam_phi_r(j)*331.999296E0_DP
200          enddo
201       end do
202      
203
204       do i = 1,  EAMList%currentAddition
205          number_r   = EAMList%EAMParams(i)%eam_nr
206          number_rho = EAMList%EAMParams(i)%eam_nrho
207          
208          call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
209               EAMList%EAMParams(i)%eam_rho_r, &
210               EAMList%EAMParams(i)%eam_rho_r_pp, &
211               0.0E0_DP, 0.0E0_DP, 'N')
212          call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
213               EAMList%EAMParams(i)%eam_Z_r, &
214               EAMList%EAMParams(i)%eam_Z_r_pp, &
215               0.0E0_DP, 0.0E0_DP, 'N')
216          call eam_spline(number_rho, EAMList%EAMParams(i)%eam_rhovals, &
217               EAMList%EAMParams(i)%eam_F_rho, &
218               EAMList%EAMParams(i)%eam_F_rho_pp, &
219               0.0E0_DP, 0.0E0_DP, 'N')
220          call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
221               EAMList%EAMParams(i)%eam_phi_r, &
222               EAMList%EAMParams(i)%eam_phi_r_pp, &
223               0.0E0_DP, 0.0E0_DP, 'N')
224       enddo
225
226 !       current_rcut_max = EAMList%EAMParams(1)%eam_rcut
227       !! find the smallest rcut for any eam atype
228 !       do i = 2, EAMList%currentAddition
229 !          current_rcut_max =max(current_rcut_max,EAMList%EAMParams(i)%eam_rcut)
230 !       end do
231
232 !       EAM_rcut = current_rcut_max
233 !       EAM_rcut_orig = current_rcut_max
234 !       do i = 1, EAMList%currentAddition
235 !          EAMList%EAMParam(i)s%eam_atype_map(eam_atype(i)) = i
236 !       end do
237       !! Allocate arrays for force calculation
238      
239       call allocateEAM(alloc_stat)
240       if (alloc_stat /= 0 ) then
241          write(*,*) "allocateEAM failed"
242          status = -1
243          return
244       endif
242      
243 <  end subroutine init_EAM_FF
244 <
248 < !! routine checks to see if array is allocated, deallocates array if allocated
249 < !! and then creates the array to the required size
250 <  subroutine allocateEAM(status)
251 <    integer, intent(out) :: status
252 <
243 >    !! Allocate arrays for force calculation
244 >    
245   #ifdef IS_MPI
254    integer :: nAtomsInRow
255    integer :: nAtomsInCol
256 #endif
257    integer :: alloc_stat
258
259
260    status = 0
261 #ifdef IS_MPI
246      nAtomsInRow = getNatomsInRow(plan_atom_row)
247      nAtomsInCol = getNatomsInCol(plan_atom_col)
248   #endif
# Line 269 | Line 253 | contains
253         status = -1
254         return
255      end if
256 +
257      if (allocated(rho)) deallocate(rho)
258      allocate(rho(nlocal),stat=alloc_stat)
259      if (alloc_stat /= 0) then
# Line 283 | Line 268 | contains
268         return
269      end if
270  
286    if (allocated(d2frhodrhodrho)) deallocate(d2frhodrhodrho)
287    allocate(d2frhodrhodrho(nlocal),stat=alloc_stat)
288    if (alloc_stat /= 0) then
289       status = -1
290       return
291    end if
292    
271   #ifdef IS_MPI
272  
273      if (allocated(rho_tmp)) deallocate(rho_tmp)
# Line 299 | Line 277 | contains
277         return
278      end if
279  
302
280      if (allocated(frho_row)) deallocate(frho_row)
281      allocate(frho_row(nAtomsInRow),stat=alloc_stat)
282      if (alloc_stat /= 0) then
# Line 318 | Line 295 | contains
295         status = -1
296         return
297      end if
321    if (allocated(d2frhodrhodrho_row)) deallocate(d2frhodrhodrho_row)
322    allocate(d2frhodrhodrho_row(nAtomsInRow),stat=alloc_stat)
323    if (alloc_stat /= 0) then
324       status = -1
325       return
326    end if
298  
299 +    ! Now do column arrays
300  
329 ! Now do column arrays
330
301      if (allocated(frho_col)) deallocate(frho_col)
302      allocate(frho_col(nAtomsInCol),stat=alloc_stat)
303      if (alloc_stat /= 0) then
# Line 346 | Line 316 | contains
316         status = -1
317         return
318      end if
319 <    if (allocated(d2frhodrhodrho_col)) deallocate(d2frhodrhodrho_col)
350 <    allocate(d2frhodrhodrho_col(nAtomsInCol),stat=alloc_stat)
351 <    if (alloc_stat /= 0) then
352 <       status = -1
353 <       return
354 <    end if
355 <  
319 >
320   #endif
321  
322 <  end subroutine allocateEAM
322 >  end subroutine init_EAM_FF
323  
324 < !! C sets rcut to be the largest cutoff of any atype
361 < !! present in this simulation. Doesn't include all atypes
362 < !! sim knows about, just those in the simulation.
363 <  subroutine setCutoffEAM(rcut, status)
324 >  subroutine setCutoffEAM(rcut)
325      real(kind=dp) :: rcut
365    integer :: status
366    status = 0
367
326      EAM_rcut = rcut
369
327    end subroutine setCutoffEAM
328  
372
373
329    subroutine clean_EAM()
330 <  
331 <   ! clean non-IS_MPI first
330 >
331 >    ! clean non-IS_MPI first
332      frho = 0.0_dp
333      rho  = 0.0_dp
334      dfrhodrho = 0.0_dp
335 < ! clean MPI if needed
335 >    ! clean MPI if needed
336   #ifdef IS_MPI
337      frho_row = 0.0_dp
338      frho_col = 0.0_dp
# Line 389 | Line 344 | contains
344   #endif
345    end subroutine clean_EAM
346  
392
393
394  subroutine allocate_EAMType(eam_n_rho,eam_n_r,thisEAMType,stat)
395    integer, intent(in)          :: eam_n_rho
396    integer, intent(in)          :: eam_n_r
397    type (EAMType)               :: thisEAMType
398    integer, optional   :: stat
399    integer             :: alloc_stat
400
401
402
403    if (present(stat)) stat = 0
404    
405    allocate(thisEAMType%eam_rvals(eam_n_r),stat=alloc_stat)  
406    if (alloc_stat /= 0 ) then
407       if (present(stat)) stat = -1
408       return
409    end if
410    allocate(thisEAMType%eam_rhovals(eam_n_rho),stat=alloc_stat)  
411    if (alloc_stat /= 0 ) then
412       if (present(stat)) stat = -1
413       return
414    end if
415    allocate(thisEAMType%eam_F_rho(eam_n_rho),stat=alloc_stat)  
416    if (alloc_stat /= 0 ) then
417       if (present(stat)) stat = -1
418       return
419    end if
420    allocate(thisEAMType%eam_Z_r(eam_n_r),stat=alloc_stat)        
421    if (alloc_stat /= 0 ) then
422       if (present(stat)) stat = -1
423       return
424    end if
425    allocate(thisEAMType%eam_rho_r(eam_n_r),stat=alloc_stat)      
426    if (alloc_stat /= 0 ) then
427       if (present(stat)) stat = -1
428       return
429    end if
430    allocate(thisEAMType%eam_phi_r(eam_n_r),stat=alloc_stat)      
431    if (alloc_stat /= 0 ) then
432       if (present(stat)) stat = -1
433       return
434    end if
435    allocate(thisEAMType%eam_F_rho_pp(eam_n_rho),stat=alloc_stat)  
436    if (alloc_stat /= 0 ) then
437       if (present(stat)) stat = -1
438       return
439    end if
440    allocate(thisEAMType%eam_Z_r_pp(eam_n_r),stat=alloc_stat)  
441    if (alloc_stat /= 0 ) then
442       if (present(stat)) stat = -1
443       return
444    end if
445    allocate(thisEAMType%eam_rho_r_pp(eam_n_r),stat=alloc_stat)  
446    if (alloc_stat /= 0 ) then
447       if (present(stat)) stat = -1
448       return
449    end if
450    allocate(thisEAMType%eam_phi_r_pp(eam_n_r),stat=alloc_stat)
451    if (alloc_stat /= 0 ) then
452       if (present(stat)) stat = -1
453       return
454    end if
455      
456
457  end subroutine allocate_EAMType
458
459
347    subroutine deallocate_EAMType(thisEAMType)
348      type (EAMtype), pointer :: thisEAMType
349  
350 <    ! free Arrays in reverse order of allocation...
351 <    deallocate(thisEAMType%eam_phi_r_pp)      
352 <    deallocate(thisEAMType%eam_rho_r_pp)  
353 <    deallocate(thisEAMType%eam_Z_r_pp)  
354 <    deallocate(thisEAMType%eam_F_rho_pp)  
468 <    deallocate(thisEAMType%eam_phi_r)      
469 <    deallocate(thisEAMType%eam_rho_r)      
470 <    deallocate(thisEAMType%eam_Z_r)  
471 <    deallocate(thisEAMType%eam_F_rho)
472 <    deallocate(thisEAMType%eam_rhovals)
473 <    deallocate(thisEAMType%eam_rvals)
474 <  
350 >    call deleteSpline(thisEAMType%F)
351 >    call deleteSpline(thisEAMType%rho)
352 >    call deleteSpline(thisEAMType%phi)
353 >    call deleteSpline(thisEAMType%Z)
354 >
355    end subroutine deallocate_EAMType
356  
357 < !! Calculates rho_r
357 >  !! Calculates rho_r
358    subroutine calc_eam_prepair_rho(atom1,atom2,d,r,rijsq)
359 <    integer :: atom1,atom2
359 >    integer :: atom1, atom2
360      real(kind = dp), dimension(3) :: d
361      real(kind = dp), intent(inout)               :: r
362      real(kind = dp), intent(inout)               :: rijsq
# Line 484 | Line 364 | contains
364      real(kind = dp) :: rho_i_at_j
365      ! value of electron density rho do to atom j at atom i
366      real(kind = dp) :: rho_j_at_i
487
488    ! we don't use the derivatives, dummy variables
489    real( kind = dp) :: drho,d2rho
367      integer :: eam_err
368 <  
369 <    integer :: myid_atom1
370 <    integer :: myid_atom2
368 >    
369 >    integer :: atid1, atid2 ! Global atid    
370 >    integer :: myid_atom1 ! EAM atid
371 >    integer :: myid_atom2
372  
373 < ! check to see if we need to be cleaned at the start of a force loop
496 <      
373 >    ! check to see if we need to be cleaned at the start of a force loop
374  
498
499
375   #ifdef IS_MPI
376 <    myid_atom1 = atid_Row(atom1)
377 <    myid_atom2 = atid_Col(atom2)
376 >    Atid1 = Atid_row(Atom1)
377 >    Atid2 = Atid_col(Atom2)
378   #else
379 <    myid_atom1 = atid(atom1)
380 <    myid_atom2 = atid(atom2)
379 >    Atid1 = Atid(Atom1)
380 >    Atid2 = Atid(Atom2)
381   #endif
382  
383 <    if (r.lt.EAMList%EAMParams(myid_atom1)%eam_rcut) then
383 >    Myid_atom1 = Eamlist%atidtoeamtype(Atid1)
384 >    Myid_atom2 = Eamlist%atidtoeamtype(Atid2)
385  
386 <
511 <
512 <       call eam_splint(EAMList%EAMParams(myid_atom1)%eam_nr, &
513 <            EAMList%EAMParams(myid_atom1)%eam_rvals, &
514 <            EAMList%EAMParams(myid_atom1)%eam_rho_r, &
515 <            EAMList%EAMParams(myid_atom1)%eam_rho_r_pp, &
516 <            r, rho_i_at_j,drho,d2rho)
386 >    if (r.lt.EAMList%EAMParams(myid_atom1)%eam_rcut) then
387  
388 +       call lookupUniformSpline(EAMList%EAMParams(myid_atom1)%rho, r, &
389 +            rho_i_at_j)
390  
519      
391   #ifdef  IS_MPI
392         rho_col(atom2) = rho_col(atom2) + rho_i_at_j
393   #else
394         rho(atom2) = rho(atom2) + rho_i_at_j
395   #endif
396 < !       write(*,*) atom1,atom2,r,rho_i_at_j
526 <       endif
396 >    endif
397  
398 <       if (r.lt.EAMList%EAMParams(myid_atom2)%eam_rcut) then
529 <          call eam_splint(EAMList%EAMParams(myid_atom2)%eam_nr, &
530 <               EAMList%EAMParams(myid_atom2)%eam_rvals, &
531 <               EAMList%EAMParams(myid_atom2)%eam_rho_r, &
532 <               EAMList%EAMParams(myid_atom2)%eam_rho_r_pp, &
533 <               r, rho_j_at_i,drho,d2rho)
398 >    if (r.lt.EAMList%EAMParams(myid_atom2)%eam_rcut) then
399  
400 <    
401 <      
402 <      
400 >       call lookupUniformSpline(EAMList%EAMParams(myid_atom2)%rho, r, &
401 >            rho_j_at_i)
402 >
403   #ifdef  IS_MPI
404 <          rho_row(atom1) = rho_row(atom1) + rho_j_at_i
404 >       rho_row(atom1) = rho_row(atom1) + rho_j_at_i
405   #else
406 <          rho(atom1) = rho(atom1) + rho_j_at_i
406 >       rho(atom1) = rho(atom1) + rho_j_at_i
407   #endif
408 <       endif
408 >    endif
409  
545
546
547
548
549
410    end subroutine calc_eam_prepair_rho
411  
412  
553
554
413    !! Calculate the functional F(rho) for all local atoms
414 <  subroutine calc_eam_preforce_Frho(nlocal,pot)
414 >  subroutine calc_eam_preforce_Frho(nlocal, pot)
415      integer :: nlocal
416      real(kind=dp) :: pot
417 <    integer :: i,j
417 >    integer :: i, j
418      integer :: atom
419 <    real(kind=dp) :: U,U1,U2
419 >    real(kind=dp) :: U,U1
420      integer :: atype1
421 <    integer :: me
564 <    integer :: n_rho_points
421 >    integer :: me, atid1
422  
566  
423      cleanme = .true.
424 <    !! Scatter the electron density from  pre-pair calculation back to local atoms
424 >    !! Scatter the electron density from  pre-pair calculation back to
425 >    !! local atoms
426   #ifdef IS_MPI
427      call scatter(rho_row,rho,plan_atom_row,eam_err)
428      if (eam_err /= 0 ) then
429 <      write(errMsg,*) " Error scattering rho_row into rho"
430 <      call handleError(RoutineName,errMesg)
431 <   endif      
429 >       write(errMsg,*) " Error scattering rho_row into rho"
430 >       call handleError(RoutineName,errMesg)
431 >    endif
432      call scatter(rho_col,rho_tmp,plan_atom_col,eam_err)
433      if (eam_err /= 0 ) then
434 <      write(errMsg,*) " Error scattering rho_col into rho"
435 <      call handleError(RoutineName,errMesg)
436 <   endif
434 >       write(errMsg,*) " Error scattering rho_col into rho"
435 >       call handleError(RoutineName,errMesg)
436 >    endif
437  
438 <      rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
438 >    rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
439   #endif
440  
441 <
585 <
586 < !! Calculate F(rho) and derivative
441 >    !! Calculate F(rho) and derivative
442      do atom = 1, nlocal
443 <       me = atid(atom)
444 <       n_rho_points = EAMList%EAMParams(me)%eam_nrho
590 <       !  Check to see that the density is not greater than the larges rho we have calculated
591 <       if (rho(atom) < EAMList%EAMParams(me)%eam_rhovals(n_rho_points)) then
592 <          call eam_splint(n_rho_points, &
593 <               EAMList%EAMParams(me)%eam_rhovals, &
594 <               EAMList%EAMParams(me)%eam_f_rho, &
595 <               EAMList%EAMParams(me)%eam_f_rho_pp, &
596 <               rho(atom), & ! Actual Rho
597 <               u, u1, u2)
598 <       else
599 <          ! Calculate F(rho with the largest available rho value
600 <          call eam_splint(n_rho_points, &
601 <               EAMList%EAMParams(me)%eam_rhovals, &
602 <               EAMList%EAMParams(me)%eam_f_rho, &
603 <               EAMList%EAMParams(me)%eam_f_rho_pp, &
604 <               EAMList%EAMParams(me)%eam_rhovals(n_rho_points), & ! Largest rho
605 <               u,u1,u2)
606 <       end if
443 >       atid1 = atid(atom)
444 >       me = eamList%atidToEAMtype(atid1)
445  
446 <
446 >       call lookupUniformSpline1d(EAMList%EAMParams(me)%F, rho(atom), &
447 >            u, u1)
448 >      
449         frho(atom) = u
450         dfrhodrho(atom) = u1
611       d2frhodrhodrho(atom) = u2
451         pot = pot + u
613
452      enddo
453  
616  
617
454   #ifdef IS_MPI
455      !! communicate f(rho) and derivatives back into row and column arrays
456      call gather(frho,frho_row,plan_atom_row, eam_err)
# Line 633 | Line 469 | contains
469      if (eam_err /=  0) then
470         call handleError("cal_eam_forces()","MPI gather dfrhodrho_col failure")
471      endif
636
637
638
639
640
641    if (nmflag) then
642       call gather(d2frhodrhodrho,d2frhodrhodrho_row,plan_atom_row)
643       call gather(d2frhodrhodrho,d2frhodrhodrho_col,plan_atom_col)
644    endif
472   #endif
473  
647  
648  end subroutine calc_eam_preforce_Frho
474  
475 <
476 <
652 <
475 >  end subroutine calc_eam_preforce_Frho
476 >  
477    !! Does EAM pairwise Force calculation.  
478    subroutine do_eam_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
479         pot, f, do_pot)
# Line 662 | Line 486 | contains
486      real( kind = dp ), intent(inout), dimension(3) :: fpair
487  
488      logical, intent(in) :: do_pot
489 <    
490 <    real( kind = dp ) :: drdx,drdy,drdz
491 <    real( kind = dp ) :: d2
492 <    real( kind = dp ) :: phab,pha,dvpdr,d2vpdrdr
493 <    real( kind = dp ) :: rha,drha,d2rha, dpha
670 <    real( kind = dp ) :: rhb,drhb,d2rhb, dphb
489 >
490 >    real( kind = dp ) :: drdx, drdy, drdz
491 >    real( kind = dp ) :: phab, pha, dvpdr
492 >    real( kind = dp ) :: rha, drha, dpha
493 >    real( kind = dp ) :: rhb, drhb, dphb
494      real( kind = dp ) :: dudr
495 <    real( kind = dp ) :: rci,rcj
496 <    real( kind = dp ) :: drhoidr,drhojdr
497 <    real( kind = dp ) :: d2rhoidrdr
498 <    real( kind = dp ) :: d2rhojdrdr
676 <    real( kind = dp ) :: Fx,Fy,Fz
677 <    real( kind = dp ) :: r,d2pha,phb,d2phb
495 >    real( kind = dp ) :: rci, rcj
496 >    real( kind = dp ) :: drhoidr, drhojdr
497 >    real( kind = dp ) :: Fx, Fy, Fz
498 >    real( kind = dp ) :: r, phb
499  
500 <    integer :: id1,id2
500 >    integer :: id1, id2
501      integer  :: mytype_atom1
502      integer  :: mytype_atom2
503 +    integer  :: atid1, atid2
504  
683 !Local Variables
684    
685   ! write(*,*) "Frho: ", Frho(atom1)
686
505      phab = 0.0E0_DP
506      dvpdr = 0.0E0_DP
689    d2vpdrdr = 0.0E0_DP
507  
508      if (rij .lt. EAM_rcut) then
509  
510   #ifdef IS_MPI
511 <       mytype_atom1 = atid_row(atom1)
512 <       mytype_atom2 = atid_col(atom2)
511 >       atid1 = atid_row(atom1)
512 >       atid2 = atid_col(atom2)
513   #else
514 <       mytype_atom1 = atid(atom1)
515 <       mytype_atom2 = atid(atom2)
514 >       atid1 = atid(atom1)
515 >       atid2 = atid(atom2)
516   #endif
517 +
518 +       mytype_atom1 = EAMList%atidToEAMType(atid1)
519 +       mytype_atom2 = EAMList%atidTOEAMType(atid2)
520 +
521 +
522         ! get cutoff for atom 1
523         rci = EAMList%EAMParams(mytype_atom1)%eam_rcut
524         ! get type specific cutoff for atom 2
525         rcj = EAMList%EAMParams(mytype_atom2)%eam_rcut
526 <      
526 >
527         drdx = d(1)/rij
528         drdy = d(2)/rij
529         drdz = d(3)/rij
530 <      
530 >
531         if (rij.lt.rci) then
532 <          call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
533 <               EAMList%EAMParams(mytype_atom1)%eam_rvals, &
534 <               EAMList%EAMParams(mytype_atom1)%eam_rho_r, &
535 <               EAMList%EAMParams(mytype_atom1)%eam_rho_r_pp, &
536 <               rij, rha,drha,d2rha)
537 <          !! Calculate Phi(r) for atom1.
538 <          call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
539 <               EAMList%EAMParams(mytype_atom1)%eam_rvals, &
540 <               EAMList%EAMParams(mytype_atom1)%eam_phi_r, &
541 <               EAMList%EAMParams(mytype_atom1)%eam_phi_r_pp, &
542 <               rij, pha,dpha,d2pha)
532 >
533 >          ! Calculate rho and drho for atom1
534 >
535 >          call lookupUniformSpline1d(EAMList%EAMParams(mytype_atom1)%rho, &
536 >               rij, rha, drha)
537 >          
538 >          ! Calculate Phi(r) for atom1.
539 >          
540 >          call lookupUniformSpline1d(EAMList%EAMParams(mytype_atom1)%phi, &
541 >               rij, pha, dpha)
542 >
543         endif
544  
545         if (rij.lt.rcj) then      
546 <          ! Calculate rho,drho and d2rho for atom1
547 <          call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
548 <               EAMList%EAMParams(mytype_atom2)%eam_rvals, &
549 <               EAMList%EAMParams(mytype_atom2)%eam_rho_r, &
550 <               EAMList%EAMParams(mytype_atom2)%eam_rho_r_pp, &
551 <               rij, rhb,drhb,d2rhb)
552 <          
553 <          !! Calculate Phi(r) for atom2.
554 <          call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
555 <               EAMList%EAMParams(mytype_atom2)%eam_rvals, &
556 <               EAMList%EAMParams(mytype_atom2)%eam_phi_r, &
735 <               EAMList%EAMParams(mytype_atom2)%eam_phi_r_pp, &
736 <               rij, phb,dphb,d2phb)
546 >
547 >          ! Calculate rho and drho for atom2
548 >
549 >          call lookupUniformSpline1d(EAMList%EAMParams(mytype_atom2)%rho, &
550 >               rij, rhb, drhb)
551 >
552 >          ! Calculate Phi(r) for atom2.
553 >
554 >          call lookupUniformSpline1d(EAMList%EAMParams(mytype_atom2)%phi, &
555 >               rij, phb, dphb)
556 >
557         endif
558  
559         if (rij.lt.rci) then
560            phab = phab + 0.5E0_DP*(rhb/rha)*pha
561            dvpdr = dvpdr + 0.5E0_DP*((rhb/rha)*dpha + &
562                 pha*((drhb/rha) - (rhb*drha/rha/rha)))
563 <          d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rhb/rha)*d2pha + &
564 <               2.0E0_DP*dpha*((drhb/rha) - (rhb*drha/rha/rha)) + &
745 <               pha*((d2rhb/rha) - 2.0E0_DP*(drhb*drha/rha/rha) + &
746 <               (2.0E0_DP*rhb*drha*drha/rha/rha/rha) - (rhb*d2rha/rha/rha)))
747 <       endif
748 <      
563 >       endif
564 >
565         if (rij.lt.rcj) then
566            phab = phab + 0.5E0_DP*(rha/rhb)*phb
567            dvpdr = dvpdr + 0.5E0_DP*((rha/rhb)*dphb + &
568                 phb*((drha/rhb) - (rha*drhb/rhb/rhb)))
753          d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rha/rhb)*d2phb + &
754               2.0E0_DP*dphb*((drha/rhb) - (rha*drhb/rhb/rhb)) + &
755               phb*((d2rha/rhb) - 2.0E0_DP*(drha*drhb/rhb/rhb) + &
756               (2.0E0_DP*rha*drhb*drhb/rhb/rhb/rhb) - (rha*d2rhb/rhb/rhb)))
569         endif
570 <      
570 >
571         drhoidr = drha
572         drhojdr = drhb
573  
762       d2rhoidrdr = d2rha
763       d2rhojdrdr = d2rhb
764
765
574   #ifdef IS_MPI
575         dudr = drhojdr*dfrhodrho_row(atom1)+drhoidr*dfrhodrho_col(atom2) &
576              + dvpdr
# Line 770 | Line 578 | contains
578   #else
579         dudr = drhojdr*dfrhodrho(atom1)+drhoidr*dfrhodrho(atom2) &
580              + dvpdr
773      ! write(*,*) "Atom1,Atom2, dfrhodrho(atom1) dfrhodrho(atom2): ", atom1,atom2,dfrhodrho(atom1),dfrhodrho(atom2)
581   #endif
582  
583         fx = dudr * drdx
# Line 780 | Line 587 | contains
587  
588   #ifdef IS_MPI
589         if (do_pot) then
590 <          pot_Row(atom1) = pot_Row(atom1) + phab*0.5
591 <          pot_Col(atom2) = pot_Col(atom2) + phab*0.5
590 >          pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + phab*0.5
591 >          pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + phab*0.5
592         end if
593  
594         f_Row(1,atom1) = f_Row(1,atom1) + fx
595         f_Row(2,atom1) = f_Row(2,atom1) + fy
596         f_Row(3,atom1) = f_Row(3,atom1) + fz
597 <      
597 >
598         f_Col(1,atom2) = f_Col(1,atom2) - fx
599         f_Col(2,atom2) = f_Col(2,atom2) - fy
600         f_Col(3,atom2) = f_Col(3,atom2) - fz
# Line 800 | Line 607 | contains
607         f(1,atom1) = f(1,atom1) + fx
608         f(2,atom1) = f(2,atom1) + fy
609         f(3,atom1) = f(3,atom1) + fz
610 <      
610 >
611         f(1,atom2) = f(1,atom2) - fx
612         f(2,atom2) = f(2,atom2) - fy
613         f(3,atom2) = f(3,atom2) - fz
614   #endif
615 <      
615 >
616         vpair = vpair + phab
617 +
618   #ifdef IS_MPI
619         id1 = AtomRowToGlobal(atom1)
620         id2 = AtomColToGlobal(atom2)
# Line 814 | Line 622 | contains
622         id1 = atom1
623         id2 = atom2
624   #endif
625 <      
625 >
626         if (molMembershipList(id1) .ne. molMembershipList(id2)) then
627 <          
627 >
628            fpair(1) = fpair(1) + fx
629            fpair(2) = fpair(2) + fy
630            fpair(3) = fpair(3) + fz
823          
824       endif
825    
826       if (nmflag) then
631  
828          drhoidr = drha
829          drhojdr = drhb
830          d2rhoidrdr = d2rha
831          d2rhojdrdr = d2rhb
832
833 #ifdef IS_MPI
834          d2 = d2vpdrdr + &
835               d2rhoidrdr*dfrhodrho_col(atom2) + &
836               d2rhojdrdr*dfrhodrho_row(atom1) + &
837               drhoidr*drhoidr*d2frhodrhodrho_col(atom2) + &
838               drhojdr*drhojdr*d2frhodrhodrho_row(atom1)
839              
840 #else
841
842          d2 = d2vpdrdr + &
843               d2rhoidrdr*dfrhodrho(atom2) + &
844               d2rhojdrdr*dfrhodrho(atom1) + &
845               drhoidr*drhoidr*d2frhodrhodrho(atom2) + &
846               drhojdr*drhojdr*d2frhodrhodrho(atom1)
847 #endif
848       end if
849      
850    endif    
851  end subroutine do_eam_pair
852
853
854  subroutine eam_splint(nx, xa, ya, yppa, x, y, dy, d2y)
855
856    integer :: atype, nx, j
857    real( kind = DP ), dimension(:) :: xa
858    real( kind = DP ), dimension(:) :: ya
859    real( kind = DP ), dimension(:) :: yppa
860    real( kind = DP ) :: x, y
861    real( kind = DP ) :: dy, d2y
862    real( kind = DP ) :: del, h, a, b, c, d
863    integer :: pp_arraySize
864
865
866    ! this spline code assumes that the x points are equally spaced
867    ! do not attempt to use this code if they are not.
868    
869    
870    ! find the closest point with a value below our own:
871    j = FLOOR(real((nx-1),kind=dp) * (x - xa(1)) / (xa(nx) - xa(1))) + 1
872
873    ! check to make sure we're inside the spline range:
874    if ((j.gt.nx).or.(j.lt.1)) then
875       write(errMSG,*) "EAM_splint: x is outside bounds of spline: ",x,j
876       call handleError(routineName,errMSG)
877    endif
878    ! check to make sure we haven't screwed up the calculation of j:
879    if ((x.lt.xa(j)).or.(x.gt.xa(j+1))) then
880       if (j.ne.nx) then
881        write(errMSG,*) "EAM_splint:",x," x is outside bounding range"
882       call handleError(routineName,errMSG)
632         endif
633      endif
634 +  end subroutine do_eam_pair
635  
886    del = xa(j+1) - x
887    h = xa(j+1) - xa(j)
888    
889    a = del / h
890    b = 1.0E0_DP - a
891    c = a*(a*a - 1.0E0_DP)*h*h/6.0E0_DP
892    d = b*(b*b - 1.0E0_DP)*h*h/6.0E0_DP
893    
894    y = a*ya(j) + b*ya(j+1) + c*yppa(j) + d*yppa(j+1)
895  
896       dy = (ya(j+1)-ya(j))/h &
897            - (3.0E0_DP*a*a - 1.0E0_DP)*h*yppa(j)/6.0E0_DP &
898            + (3.0E0_DP*b*b - 1.0E0_DP)*h*yppa(j+1)/6.0E0_DP
899  
900  
901       d2y = a*yppa(j) + b*yppa(j+1)
902  
903
904  end subroutine eam_splint
905
906
907  subroutine eam_spline(nx, xa, ya, yppa, yp1, ypn, boundary)
908
909
910    ! yp1 and ypn are the first derivatives of y at the two endpoints
911    ! if boundary is 'L' the lower derivative is used
912    ! if boundary is 'U' the upper derivative is used
913    ! if boundary is 'B' then both derivatives are used
914    ! if boundary is anything else, then both derivatives are assumed to be 0
915    
916    integer :: nx, i, k, max_array_size
917    
918    real( kind = DP ), dimension(:)        :: xa
919    real( kind = DP ), dimension(:)        :: ya
920    real( kind = DP ), dimension(:)        :: yppa
921    real( kind = DP ), dimension(size(xa)) :: u
922    real( kind = DP ) :: yp1,ypn,un,qn,sig,p
923    character(len=*) :: boundary
924    
925    ! make sure the sizes match
926    if ((nx /= size(xa)) .or. (nx /= size(ya))) then
927       call handleWarning("EAM_SPLINE","Array size mismatch")
928    end if
929
930    if ((boundary.eq.'l').or.(boundary.eq.'L').or. &
931         (boundary.eq.'b').or.(boundary.eq.'B')) then
932       yppa(1) = -0.5E0_DP
933       u(1) = (3.0E0_DP/(xa(2)-xa(1)))*((ya(2)-&
934            ya(1))/(xa(2)-xa(1))-yp1)
935    else
936       yppa(1) = 0.0E0_DP
937       u(1)  = 0.0E0_DP
938    endif
939    
940    do i = 2, nx - 1
941       sig = (xa(i) - xa(i-1)) / (xa(i+1) - xa(i-1))
942       p = sig * yppa(i-1) + 2.0E0_DP
943       yppa(i) = (sig - 1.0E0_DP) / p
944       u(i) = (6.0E0_DP*((ya(i+1)-ya(i))/(xa(i+1)-xa(i)) - &
945            (ya(i)-ya(i-1))/(xa(i)-xa(i-1)))/ &
946            (xa(i+1)-xa(i-1)) - sig * u(i-1))/p
947    enddo
948    
949    if ((boundary.eq.'u').or.(boundary.eq.'U').or. &
950         (boundary.eq.'b').or.(boundary.eq.'B')) then
951       qn = 0.5E0_DP
952       un = (3.0E0_DP/(xa(nx)-xa(nx-1)))* &
953            (ypn-(ya(nx)-ya(nx-1))/(xa(nx)-xa(nx-1)))
954    else
955       qn = 0.0E0_DP
956       un = 0.0E0_DP
957    endif
958
959    yppa(nx)=(un-qn*u(nx-1))/(qn*yppa(nx-1)+1.0E0_DP)
960    
961    do k = nx-1, 1, -1
962       yppa(k)=yppa(k)*yppa(k+1)+u(k)
963    enddo
964
965  end subroutine eam_spline
966
967
968
969
636   end module eam
971
972  subroutine newEAMtype(lattice_constant,eam_nrho,eam_drho,eam_nr,&
973       eam_dr,rcut,eam_Z_r,eam_rho_r,eam_F_rho,&
974       eam_ident,status)
975       use definitions, ONLY : dp
976       use eam, ONLY : module_newEAMtype => newEAMtype
977    real (kind = dp )                      :: lattice_constant
978    integer                                :: eam_nrho
979    real (kind = dp )                      :: eam_drho
980    integer                                :: eam_nr
981    real (kind = dp )                     :: eam_dr
982    real (kind = dp )                      :: rcut
983    real (kind = dp ), dimension(eam_nr)    :: eam_Z_r
984    real (kind = dp ), dimension(eam_nr)   :: eam_rho_r
985    real (kind = dp ), dimension(eam_nrho) :: eam_F_rho
986    integer                                :: eam_ident
987    integer                                :: status
988
989    
990    call module_newEAMtype(lattice_constant,eam_nrho,eam_drho,eam_nr,&
991       eam_dr,rcut,eam_Z_r,eam_rho_r,eam_F_rho,&
992       eam_ident,status)
993      
994 end subroutine newEAMtype

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines