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

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/suttonchen.F90 (file contents):
Revision 2401 by chuckv, Tue Nov 1 18:29:57 2005 UTC vs.
Revision 2530 by chuckv, Fri Dec 30 00:18:28 2005 UTC

# Line 49 | Line 49 | module suttonchen
49    use status
50    use atype_module
51    use vector_class
52 +  use fForceOptions
53   #ifdef IS_MPI
54    use mpiSimulation
55   #endif
# Line 63 | Line 64 | module suttonchen
64    integer, save :: SC_Mixing_Policy
65    real(kind = dp), save :: SC_rcut
66    logical, save :: haveRcut = .false.
67 +  logical, save :: haveMixingMap = .false.
68 +  logical, save :: useGeometricDistanceMixing = .false.
69  
70 +
71 +
72 +
73    character(len = statusMsgSize) :: errMesg
74 <  integer :: eam_err
74 >  integer :: sc_err
75  
76    character(len = 200) :: errMsg
77    character(len=*), parameter :: RoutineName =  "Sutton-Chen MODULE"
# Line 76 | Line 82 | module suttonchen
82  
83    type, private :: SCtype
84       integer           :: atid      
85 <     real(kind=dp)     :: c
85 >     real(kind=dp)     :: c
86       real(kind=dp)     :: m
87       real(kind=dp)     :: n
88       real(kind=dp)     :: alpha
89       real(kind=dp)     :: epsilon
90 +     real(kind=dp)     :: sc_rcut
91    end type SCtype
92  
93  
94    !! Arrays for derivatives used in force calculation
88  real( kind = dp), dimension(:), allocatable :: frho
95    real( kind = dp), dimension(:), allocatable :: rho
96 <
96 >  real( kind = dp), dimension(:), allocatable :: frho
97    real( kind = dp), dimension(:), allocatable :: dfrhodrho
92  real( kind = dp), dimension(:), allocatable :: d2frhodrhodrho
98  
99  
100 +
101    !! Arrays for MPI storage
102   #ifdef IS_MPI
103    real( kind = dp),save, dimension(:), allocatable :: dfrhodrho_col
# Line 101 | Line 107 | module suttonchen
107    real( kind = dp),save, dimension(:), allocatable :: rho_row
108    real( kind = dp),save, dimension(:), allocatable :: rho_col
109    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
110   #endif
111  
112    type, private :: SCTypeList
# Line 113 | Line 117 | module suttonchen
117       integer, pointer         :: atidToSCtype(:) => null()
118    end type SCTypeList
119  
116
120    type (SCTypeList), save :: SCList
121  
119  !! standard eam stuff  
122  
123  
124 <  public :: init_SC_FF
124 >
125 > type :: MixParameters
126 >     real(kind=DP) :: alpha
127 >     real(kind=DP) :: epsilon
128 >     real(kind=DP) :: m
129 >     real(Kind=DP) :: n
130 >     real(kind=DP) :: vpair_pot
131 >     real(kind=dp) :: rCut
132 >     logical       :: rCutWasSet = .false.
133 >
134 >  end type MixParameters
135 >
136 >  type(MixParameters), dimension(:,:), allocatable :: MixingMap
137 >
138 >
139 >
140    public :: setCutoffSC
141    public :: do_SC_pair
142    public :: newSCtype
143    public :: calc_SC_prepair_rho
144 +  public :: calc_SC_preforce_Frho
145    public :: clean_SC
146    public :: destroySCtypes
147    public :: getSCCut
148 + ! public :: setSCDefaultCutoff
149 + ! public :: setSCUniformCutoff
150 +
151  
152   contains
153  
154  
155 <  subroutine newEAMtype(lattice_constant,eam_nrho,eam_drho,eam_nr,&
156 <       eam_dr,rcut,eam_Z_r,eam_rho_r,eam_F_rho,&
157 <       c_ident,status)
158 <    real (kind = dp )                      :: lattice_constant
159 <    integer                                :: eam_nrho
160 <    real (kind = dp )                      :: eam_drho
161 <    integer                                :: eam_nr
162 <    real (kind = dp )                      :: eam_dr
142 <    real (kind = dp )                      :: rcut
143 <    real (kind = dp ), dimension(eam_nr)   :: eam_Z_r
144 <    real (kind = dp ), dimension(eam_nr)   :: eam_rho_r
145 <    real (kind = dp ), dimension(eam_nrho) :: eam_F_rho
155 >  subroutine newSCtype(c_ident,c,m,n,alpha,epsilon,status)
156 >    real (kind = dp )                      :: c ! Density Scaling
157 >    real (kind = dp )                      :: m ! Density Exponent
158 >    real (kind = dp )                      :: n ! Pair Potential Exponent
159 >    real (kind = dp )                      :: alpha ! Length Scaling
160 >    real (kind = dp )                      :: epsilon ! Energy Scaling
161 >
162 >
163      integer                                :: c_ident
164      integer                                :: status
165  
166 <    integer                                :: nAtypes,nEAMTypes,myATID
166 >    integer                                :: nAtypes,nSCTypes,myATID
167      integer                                :: maxVals
168      integer                                :: alloc_stat
169      integer                                :: current
# Line 156 | Line 173 | contains
173  
174  
175      !! Assume that atypes has already been set and get the total number of types in atypes
159    !! Also assume that every member of atypes is a EAM model.
176  
177  
178      ! check to see if this is the first time into
179 <    if (.not.associated(EAMList%EAMParams)) then
180 <       call getMatchingElementList(atypes, "is_EAM", .true., nEAMtypes, MatchList)
181 <       EAMList%n_eam_types = nEAMtypes
182 <       allocate(EAMList%EAMParams(nEAMTypes))
179 >    if (.not.associated(SCList%SCTypes)) then
180 >       call getMatchingElementList(atypes, "is_SC", .true., nSCtypes, MatchList)
181 >       SCList%nSCtypes = nSCtypes
182 >       allocate(SCList%SCTypes(nSCTypes))
183         nAtypes = getSize(atypes)
184 <       allocate(EAMList%atidToEAMType(nAtypes))
184 >       allocate(SCList%atidToSCType(nAtypes))
185      end if
186  
187 <    EAMList%currentAddition = EAMList%currentAddition + 1
188 <    current = EAMList%currentAddition
187 >    SCList%currentSCType = SCList%currentSCType + 1
188 >    current = SCList%currentSCType
189  
190      myATID =  getFirstMatchingElement(atypes, "c_ident", c_ident)
191 <    EAMList%atidToEAMType(myATID) = current
191 >    SCList%atidToSCType(myATID) = current
192  
177    call allocate_EAMType(eam_nrho,eam_nr,EAMList%EAMParams(current),stat=alloc_stat)
178    if (alloc_stat /= 0) then
179       status = -1
180       return
181    end if
193  
194    
195 <    EAMList%EAMParams(current)%eam_atype    = c_ident
196 <    EAMList%EAMParams(current)%eam_lattice  = lattice_constant
197 <    EAMList%EAMParams(current)%eam_nrho     = eam_nrho
198 <    EAMList%EAMParams(current)%eam_drho     = eam_drho
199 <    EAMList%EAMParams(current)%eam_nr       = eam_nr
200 <    EAMList%EAMParams(current)%eam_dr       = eam_dr
201 <    EAMList%EAMParams(current)%eam_rcut     = rcut
191 <    EAMList%EAMParams(current)%eam_Z_r      = eam_Z_r
192 <    EAMList%EAMParams(current)%eam_rho_r    = eam_rho_r
193 <    EAMList%EAMParams(current)%eam_F_rho    = eam_F_rho
194 <
195 <  end subroutine newEAMtype
196 <
197 <
198 <  ! kills all eam types entered and sets simulation to uninitalized
199 <  subroutine destroyEAMtypes()
200 <    integer :: i
201 <    type(EAMType), pointer :: tempEAMType=>null()
202 <
203 <    do i = 1, EAMList%n_eam_types
204 <       tempEAMType => eamList%EAMParams(i)
205 <       call deallocate_EAMType(tempEAMType)
206 <    end do
207 <    if(associated( eamList%EAMParams)) deallocate( eamList%EAMParams)
208 <    eamList%EAMParams => null()
209 <
210 <    eamList%n_eam_types = 0
211 <    eamList%currentAddition = 0
212 <
213 <  end subroutine destroyEAMtypes
195 >    SCList%SCTypes(current)%atid         = c_ident
196 >    SCList%SCTypes(current)%alpha        = alpha
197 >    SCList%SCTypes(current)%c            = c
198 >    SCList%SCTypes(current)%m            = m
199 >    SCList%SCTypes(current)%n            = n
200 >    SCList%SCTypes(current)%epsilon      = epsilon
201 >  end subroutine newSCtype
202  
203 <  function getEAMCut(atomID) result(cutValue)
203 >  
204 >  subroutine destroySCTypes()
205 >    if (associated(SCList%SCtypes)) then
206 >       deallocate(SCList%SCTypes)
207 >       SCList%SCTypes=>null()
208 >    end if
209 >    if (associated(SCList%atidToSCtype)) then
210 >       deallocate(SCList%atidToSCtype)
211 >       SCList%atidToSCtype=>null()
212 >    end if
213 >
214 >
215 >  end subroutine destroySCTypes
216 >
217 >
218 >
219 >  function getSCCut(atomID) result(cutValue)
220      integer, intent(in) :: atomID
221 <    integer :: eamID
221 >    integer :: scID
222      real(kind=dp) :: cutValue
223      
224 <    eamID = EAMList%atidToEAMType(atomID)
225 <    cutValue = EAMList%EAMParams(eamID)%eam_rcut
226 <  end function getEAMCut
224 >    scID = SCList%atidToSCType(atomID)
225 >    cutValue = 2.0_dp * SCList%SCTypes(scID)%alpha
226 >  end function getSCCut
227  
224  subroutine init_EAM_FF(status)
225    integer :: status
226    integer :: i,j
227    real(kind=dp) :: current_rcut_max
228    integer :: alloc_stat
229    integer :: number_r, number_rho
228  
229  
230 <    status = 0
231 <    if (EAMList%currentAddition == 0) then
232 <       call handleError("init_EAM_FF","No members in EAMList")
233 <       status = -1
230 >
231 >  subroutine createMixingMap()
232 >    integer :: nSCtypes, i, j
233 >    real ( kind = dp ) :: e1, e2,m1,m2,alpha1,alpha2,n1,n2
234 >    real ( kind = dp ) :: rcut6, tp6, tp12
235 >    logical :: isSoftCore1, isSoftCore2, doShift
236 >
237 >    if (SCList%currentSCtype == 0) then
238 >       call handleError("SuttonChen", "No members in SCMap")
239         return
240      end if
241  
242 +    nSCtypes = SCList%nSCtypes
243  
244 <    do i = 1, EAMList%currentAddition
244 >    if (.not. allocated(MixingMap)) then
245 >       allocate(MixingMap(nSCtypes, nSCtypes))
246 >    endif
247 >    useGeometricDistanceMixing = usesGeometricDistanceMixing()
248 >    do i = 1, nSCtypes
249  
250 <       ! Build array of r values
250 >       e1 = SCList%SCtypes(i)%epsilon
251 >       m1 = SCList%SCtypes(i)%m
252 >       n1 = SCList%SCtypes(i)%n
253 >       alpha1 = SCList%SCtypes(i)%alpha
254  
255 <       do j = 1,EAMList%EAMParams(i)%eam_nr
256 <          EAMList%EAMParams(i)%eam_rvals(j) = &
246 <               real(j-1,kind=dp)* &
247 <               EAMList%EAMParams(i)%eam_dr
248 <       end do
249 <       ! Build array of rho values
250 <       do j = 1,EAMList%EAMParams(i)%eam_nrho
251 <          EAMList%EAMParams(i)%eam_rhovals(j) = &
252 <               real(j-1,kind=dp)* &
253 <               EAMList%EAMParams(i)%eam_drho
254 <       end do
255 <       ! convert from eV to kcal / mol:
256 <       EAMList%EAMParams(i)%eam_F_rho = EAMList%EAMParams(i)%eam_F_rho * 23.06054E0_DP
255 >       do j = i, nSCtypes
256 >          
257  
258 <       ! precompute the pair potential and get it into kcal / mol:
259 <       EAMList%EAMParams(i)%eam_phi_r(1) = 0.0E0_DP
260 <       do j = 2, EAMList%EAMParams(i)%eam_nr
261 <          EAMList%EAMParams(i)%eam_phi_r(j) = (EAMList%EAMParams(i)%eam_Z_r(j)**2)/EAMList%EAMParams(i)%eam_rvals(j)
262 <          EAMList%EAMParams(i)%eam_phi_r(j) =  EAMList%EAMParams(i)%eam_phi_r(j)*331.999296E0_DP
263 <       enddo
264 <    end do
258 >          e2 = SCList%SCtypes(j)%epsilon
259 >          m2 = SCList%SCtypes(j)%m
260 >          n2 = SCList%SCtypes(j)%n
261 >          alpha2 = SCList%SCtypes(j)%alpha
262  
263 +          if (useGeometricDistanceMixing) then
264 +             MixingMap(i,j)%alpha = sqrt(alpha1 * alpha2) !SC formulation
265 +          else
266 +             MixingMap(i,j)%alpha = 0.5_dp * (alpha1 + alpha2) ! Goddard formulation
267 +          endif
268  
269 <    do i = 1,  EAMList%currentAddition
270 <       number_r   = EAMList%EAMParams(i)%eam_nr
271 <       number_rho = EAMList%EAMParams(i)%eam_nrho
272 <
273 <       call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
274 <            EAMList%EAMParams(i)%eam_rho_r, &
275 <            EAMList%EAMParams(i)%eam_rho_r_pp, &
276 <            0.0E0_DP, 0.0E0_DP, 'N')
277 <       call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
278 <            EAMList%EAMParams(i)%eam_Z_r, &
279 <            EAMList%EAMParams(i)%eam_Z_r_pp, &
280 <            0.0E0_DP, 0.0E0_DP, 'N')
281 <       call eam_spline(number_rho, EAMList%EAMParams(i)%eam_rhovals, &
282 <            EAMList%EAMParams(i)%eam_F_rho, &
283 <            EAMList%EAMParams(i)%eam_F_rho_pp, &
284 <            0.0E0_DP, 0.0E0_DP, 'N')
283 <       call eam_spline(number_r, EAMList%EAMParams(i)%eam_rvals, &
284 <            EAMList%EAMParams(i)%eam_phi_r, &
285 <            EAMList%EAMParams(i)%eam_phi_r_pp, &
286 <            0.0E0_DP, 0.0E0_DP, 'N')
269 >          MixingMap(i,j)%epsilon = sqrt(e1 * e2)
270 >          MixingMap(i,j)%m = 0.5_dp*(m1+m2)
271 >          MixingMap(i,j)%n = 0.5_dp*(n1+n2)
272 >          MixingMap(i,j)%alpha = 0.5_dp*(alpha1+alpha2)
273 >          MixingMap(i,j)%rcut = 2.0_dp *MixingMap(i,j)%alpha
274 >          MixingMap(i,j)%vpair_pot = MixingMap(i,j)%epsilon* &
275 >               (MixingMap(i,j)%alpha/MixingMap(i,j)%rcut)**MixingMap(i,j)%n
276 >          if (i.ne.j) then
277 >             MixingMap(j,i)%epsilon    = MixingMap(i,j)%epsilon
278 >             MixingMap(j,i)%m          = MixingMap(i,j)%m
279 >             MixingMap(j,i)%n          = MixingMap(i,j)%n
280 >             MixingMap(j,i)%alpha      = MixingMap(i,j)%alpha
281 >             MixingMap(j,i)%rcut = MixingMap(i,j)%rcut
282 >             MixingMap(j,i)%vpair_pot = MixingMap(i,j)%vpair_pot
283 >          endif
284 >       enddo
285      enddo
286 +    
287 +    haveMixingMap = .true.
288 +    
289 +  end subroutine createMixingMap
290 +  
291  
289    !       current_rcut_max = EAMList%EAMParams(1)%eam_rcut
290    !! find the smallest rcut for any eam atype
291    !       do i = 2, EAMList%currentAddition
292    !          current_rcut_max =max(current_rcut_max,EAMList%EAMParams(i)%eam_rcut)
293    !       end do
294
295    !       EAM_rcut = current_rcut_max
296    !       EAM_rcut_orig = current_rcut_max
297    !       do i = 1, EAMList%currentAddition
298    !          EAMList%EAMParam(i)s%eam_atype_map(eam_atype(i)) = i
299    !       end do
300    !! Allocate arrays for force calculation
301
302    call allocateEAM(alloc_stat)
303    if (alloc_stat /= 0 ) then
304       write(*,*) "allocateEAM failed"
305       status = -1
306       return
307    endif
308
309  end subroutine init_EAM_FF
310
292    !! routine checks to see if array is allocated, deallocates array if allocated
293    !! and then creates the array to the required size
294 <  subroutine allocateEAM(status)
294 >  subroutine allocateSC(status)
295      integer, intent(out) :: status
296  
297   #ifdef IS_MPI
# Line 326 | Line 307 | contains
307      nAtomsInCol = getNatomsInCol(plan_atom_col)
308   #endif
309  
310 +
311 +
312      if (allocated(frho)) deallocate(frho)
313      allocate(frho(nlocal),stat=alloc_stat)
314 <    if (alloc_stat /= 0) then
314 >    if (alloc_stat /= 0) then
315         status = -1
316         return
317      end if
318 +
319      if (allocated(rho)) deallocate(rho)
320      allocate(rho(nlocal),stat=alloc_stat)
321      if (alloc_stat /= 0) then
# Line 346 | Line 330 | contains
330         return
331      end if
332  
349    if (allocated(d2frhodrhodrho)) deallocate(d2frhodrhodrho)
350    allocate(d2frhodrhodrho(nlocal),stat=alloc_stat)
351    if (alloc_stat /= 0) then
352       status = -1
353       return
354    end if
355
333   #ifdef IS_MPI
334  
335      if (allocated(rho_tmp)) deallocate(rho_tmp)
# Line 381 | Line 358 | contains
358         status = -1
359         return
360      end if
384    if (allocated(d2frhodrhodrho_row)) deallocate(d2frhodrhodrho_row)
385    allocate(d2frhodrhodrho_row(nAtomsInRow),stat=alloc_stat)
386    if (alloc_stat /= 0) then
387       status = -1
388       return
389    end if
361  
362  
363      ! Now do column arrays
# Line 409 | Line 380 | contains
380         status = -1
381         return
382      end if
412    if (allocated(d2frhodrhodrho_col)) deallocate(d2frhodrhodrho_col)
413    allocate(d2frhodrhodrho_col(nAtomsInCol),stat=alloc_stat)
414    if (alloc_stat /= 0) then
415       status = -1
416       return
417    end if
383  
384   #endif
385  
386 <  end subroutine allocateEAM
386 >  end subroutine allocateSC
387  
388    !! C sets rcut to be the largest cutoff of any atype
389    !! present in this simulation. Doesn't include all atypes
390    !! sim knows about, just those in the simulation.
391 <  subroutine setCutoffEAM(rcut, status)
391 >  subroutine setCutoffSC(rcut, status)
392      real(kind=dp) :: rcut
393      integer :: status
394      status = 0
395  
396 <    EAM_rcut = rcut
396 >    SC_rcut = rcut
397  
398 <  end subroutine setCutoffEAM
398 >  end subroutine setCutoffSC
399  
400 +  subroutine clean_SC()
401  
436
437  subroutine clean_EAM()
438
402      ! clean non-IS_MPI first
403      frho = 0.0_dp
404      rho  = 0.0_dp
# Line 450 | Line 413 | contains
413      dfrhodrho_row = 0.0_dp
414      dfrhodrho_col = 0.0_dp
415   #endif
416 <  end subroutine clean_EAM
416 >  end subroutine clean_SC
417  
418  
419  
457  subroutine allocate_EAMType(eam_n_rho,eam_n_r,thisEAMType,stat)
458    integer, intent(in)          :: eam_n_rho
459    integer, intent(in)          :: eam_n_r
460    type (EAMType)               :: thisEAMType
461    integer, optional   :: stat
462    integer             :: alloc_stat
463
464
465
466    if (present(stat)) stat = 0
467
468    allocate(thisEAMType%eam_rvals(eam_n_r),stat=alloc_stat)  
469    if (alloc_stat /= 0 ) then
470       if (present(stat)) stat = -1
471       return
472    end if
473    allocate(thisEAMType%eam_rhovals(eam_n_rho),stat=alloc_stat)  
474    if (alloc_stat /= 0 ) then
475       if (present(stat)) stat = -1
476       return
477    end if
478    allocate(thisEAMType%eam_F_rho(eam_n_rho),stat=alloc_stat)  
479    if (alloc_stat /= 0 ) then
480       if (present(stat)) stat = -1
481       return
482    end if
483    allocate(thisEAMType%eam_Z_r(eam_n_r),stat=alloc_stat)        
484    if (alloc_stat /= 0 ) then
485       if (present(stat)) stat = -1
486       return
487    end if
488    allocate(thisEAMType%eam_rho_r(eam_n_r),stat=alloc_stat)      
489    if (alloc_stat /= 0 ) then
490       if (present(stat)) stat = -1
491       return
492    end if
493    allocate(thisEAMType%eam_phi_r(eam_n_r),stat=alloc_stat)      
494    if (alloc_stat /= 0 ) then
495       if (present(stat)) stat = -1
496       return
497    end if
498    allocate(thisEAMType%eam_F_rho_pp(eam_n_rho),stat=alloc_stat)  
499    if (alloc_stat /= 0 ) then
500       if (present(stat)) stat = -1
501       return
502    end if
503    allocate(thisEAMType%eam_Z_r_pp(eam_n_r),stat=alloc_stat)  
504    if (alloc_stat /= 0 ) then
505       if (present(stat)) stat = -1
506       return
507    end if
508    allocate(thisEAMType%eam_rho_r_pp(eam_n_r),stat=alloc_stat)  
509    if (alloc_stat /= 0 ) then
510       if (present(stat)) stat = -1
511       return
512    end if
513    allocate(thisEAMType%eam_phi_r_pp(eam_n_r),stat=alloc_stat)
514    if (alloc_stat /= 0 ) then
515       if (present(stat)) stat = -1
516       return
517    end if
518
519
520  end subroutine allocate_EAMType
521
522
523  subroutine deallocate_EAMType(thisEAMType)
524    type (EAMtype), pointer :: thisEAMType
525
526    ! free Arrays in reverse order of allocation...
527    if(associated(thisEAMType%eam_phi_r_pp)) deallocate(thisEAMType%eam_phi_r_pp)      
528    if(associated(thisEAMType%eam_rho_r_pp)) deallocate(thisEAMType%eam_rho_r_pp)  
529    if(associated(thisEAMType%eam_Z_r_pp)) deallocate(thisEAMType%eam_Z_r_pp)  
530    if(associated(thisEAMType%eam_F_rho_pp)) deallocate(thisEAMType%eam_F_rho_pp)  
531    if(associated(thisEAMType%eam_phi_r)) deallocate(thisEAMType%eam_phi_r)      
532    if(associated(thisEAMType%eam_rho_r)) deallocate(thisEAMType%eam_rho_r)      
533    if(associated(thisEAMType%eam_Z_r)) deallocate(thisEAMType%eam_Z_r)  
534    if(associated(thisEAMType%eam_F_rho)) deallocate(thisEAMType%eam_F_rho)
535    if(associated(thisEAMType%eam_rhovals)) deallocate(thisEAMType%eam_rhovals)
536    if(associated(thisEAMType%eam_rvals)) deallocate(thisEAMType%eam_rvals)
537
538  end subroutine deallocate_EAMType
539
420    !! Calculates rho_r
421 <  subroutine calc_eam_prepair_rho(atom1,atom2,d,r,rijsq)
421 >  subroutine calc_sc_prepair_rho(atom1,atom2,d,r,rijsq, rcut)
422      integer :: atom1,atom2
423      real(kind = dp), dimension(3) :: d
424      real(kind = dp), intent(inout)               :: r
425 <    real(kind = dp), intent(inout)               :: rijsq
425 >    real(kind = dp), intent(inout)               :: rijsq, rcut
426      ! value of electron density rho do to atom i at atom j
427      real(kind = dp) :: rho_i_at_j
428      ! value of electron density rho do to atom j at atom i
429      real(kind = dp) :: rho_j_at_i
430  
431      ! we don't use the derivatives, dummy variables
432 <    real( kind = dp) :: drho,d2rho
433 <    integer :: eam_err
432 >    real( kind = dp) :: drho
433 >    integer :: sc_err
434      
435      integer :: atid1,atid2 ! Global atid    
436      integer :: myid_atom1 ! EAM atid
# Line 570 | Line 450 | contains
450      Atid2 = Atid(Atom2)
451   #endif
452  
453 <    Myid_atom1 = Eamlist%atidtoeamtype(Atid1)
454 <    Myid_atom2 = Eamlist%atidtoeamtype(Atid2)
453 >    Myid_atom1 = SCList%atidtoSCtype(Atid1)
454 >    Myid_atom2 = SCList%atidtoSCtype(Atid2)
455  
576    if (r.lt.EAMList%EAMParams(myid_atom1)%eam_rcut) then
456  
457  
458 <
459 <       call eam_splint(EAMList%EAMParams(myid_atom1)%eam_nr, &
460 <            EAMList%EAMParams(myid_atom1)%eam_rvals, &
582 <            EAMList%EAMParams(myid_atom1)%eam_rho_r, &
583 <            EAMList%EAMParams(myid_atom1)%eam_rho_r_pp, &
584 <            r, rho_i_at_j,drho,d2rho)
458 >       rho_i_at_j = (MixingMap(Myid_atom1,Myid_atom2)%alpha/r)&
459 >            **MixingMap(Myid_atom1,Myid_atom2)%m
460 >       rho_j_at_i = rho_i_at_j
461  
586
587
462   #ifdef  IS_MPI
463         rho_col(atom2) = rho_col(atom2) + rho_i_at_j
590 #else
591       rho(atom2) = rho(atom2) + rho_i_at_j
592 #endif
593             ! write(*,*) atom1,atom2,r,rho_i_at_j
594    endif
595
596    if (r.lt.EAMList%EAMParams(myid_atom2)%eam_rcut) then
597       call eam_splint(EAMList%EAMParams(myid_atom2)%eam_nr, &
598            EAMList%EAMParams(myid_atom2)%eam_rvals, &
599            EAMList%EAMParams(myid_atom2)%eam_rho_r, &
600            EAMList%EAMParams(myid_atom2)%eam_rho_r_pp, &
601            r, rho_j_at_i,drho,d2rho)
602
603
604
605
606 #ifdef  IS_MPI
464         rho_row(atom1) = rho_row(atom1) + rho_j_at_i
465   #else
466 +       rho(atom2) = rho(atom2) + rho_i_at_j
467         rho(atom1) = rho(atom1) + rho_j_at_i
468   #endif
611    endif
469  
470 +  end subroutine calc_sc_prepair_rho
471  
472  
473 <
474 <
617 <
618 <  end subroutine calc_eam_prepair_rho
619 <
620 <
621 <
622 <
623 <  !! Calculate the functional F(rho) for all local atoms
624 <  subroutine calc_eam_preforce_Frho(nlocal,pot)
473 > !! Calculate the rho_a for all local atoms
474 >  subroutine calc_sc_preforce_Frho(nlocal,pot)
475      integer :: nlocal
476      real(kind=dp) :: pot
477      integer :: i,j
478      integer :: atom
479      real(kind=dp) :: U,U1,U2
480      integer :: atype1
481 <    integer :: me,atid1
482 <    integer :: n_rho_points
481 >    integer :: atid1
482 >    integer :: myid
483  
484  
485      cleanme = .true.
486      !! Scatter the electron density from  pre-pair calculation back to local atoms
487   #ifdef IS_MPI
488 <    call scatter(rho_row,rho,plan_atom_row,eam_err)
489 <    if (eam_err /= 0 ) then
488 >    call scatter(rho_row,rho,plan_atom_row,sc_err)
489 >    if (sc_err /= 0 ) then
490         write(errMsg,*) " Error scattering rho_row into rho"
491         call handleError(RoutineName,errMesg)
492      endif
493 <    call scatter(rho_col,rho_tmp,plan_atom_col,eam_err)
494 <    if (eam_err /= 0 ) then
493 >    call scatter(rho_col,rho_tmp,plan_atom_col,sc_err)
494 >    if (sc_err /= 0 ) then
495         write(errMsg,*) " Error scattering rho_col into rho"
496         call handleError(RoutineName,errMesg)
497 +
498      endif
499  
500      rho(1:nlocal) = rho(1:nlocal) + rho_tmp(1:nlocal)
# Line 651 | Line 502 | contains
502  
503  
504  
505 <    !! Calculate F(rho) and derivative
505 >    !! Calculate F(rho) and derivative
506      do atom = 1, nlocal
507 <       atid1 = atid(atom)
508 <       me = eamList%atidToEAMtype(atid1)
509 <       n_rho_points = EAMList%EAMParams(me)%eam_nrho
659 <       !  Check to see that the density is not greater than the larges rho we have calculated
660 <       if (rho(atom) < EAMList%EAMParams(me)%eam_rhovals(n_rho_points)) then
661 <          call eam_splint(n_rho_points, &
662 <               EAMList%EAMParams(me)%eam_rhovals, &
663 <               EAMList%EAMParams(me)%eam_f_rho, &
664 <               EAMList%EAMParams(me)%eam_f_rho_pp, &
665 <               rho(atom), & ! Actual Rho
666 <               u, u1, u2)
667 <       else
668 <          ! Calculate F(rho with the largest available rho value
669 <          call eam_splint(n_rho_points, &
670 <               EAMList%EAMParams(me)%eam_rhovals, &
671 <               EAMList%EAMParams(me)%eam_f_rho, &
672 <               EAMList%EAMParams(me)%eam_f_rho_pp, &
673 <               EAMList%EAMParams(me)%eam_rhovals(n_rho_points), & ! Largest rho
674 <               u,u1,u2)
675 <       end if
507 >       Myid = SCList%atidtoSctype(Atid(atom))
508 >       frho(atom) = -SCList%SCTypes(Myid)%c * &
509 >            SCList%SCTypes(Myid)%epsilon * sqrt(rho(i))
510  
511 <
678 <       frho(atom) = u
679 <       dfrhodrho(atom) = u1
680 <       d2frhodrhodrho(atom) = u2
511 >       dfrhodrho(atom) = 0.5_dp*frho(atom)/rho(atom)
512         pot = pot + u
682
513      enddo
514  
685
686
515   #ifdef IS_MPI
516      !! communicate f(rho) and derivatives back into row and column arrays
517 <    call gather(frho,frho_row,plan_atom_row, eam_err)
518 <    if (eam_err /=  0) then
517 >    call gather(frho,frho_row,plan_atom_row, sc_err)
518 >    if (sc_err /=  0) then
519         call handleError("cal_eam_forces()","MPI gather frho_row failure")
520      endif
521 <    call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, eam_err)
522 <    if (eam_err /=  0) then
521 >    call gather(dfrhodrho,dfrhodrho_row,plan_atom_row, sc_err)
522 >    if (sc_err /=  0) then
523         call handleError("cal_eam_forces()","MPI gather dfrhodrho_row failure")
524      endif
525 <    call gather(frho,frho_col,plan_atom_col, eam_err)
526 <    if (eam_err /=  0) then
525 >    call gather(frho,frho_col,plan_atom_col, sc_err)
526 >    if (sc_err /=  0) then
527         call handleError("cal_eam_forces()","MPI gather frho_col failure")
528      endif
529 <    call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, eam_err)
530 <    if (eam_err /=  0) then
529 >    call gather(dfrhodrho,dfrhodrho_col,plan_atom_col, sc_err)
530 >    if (sc_err /=  0) then
531         call handleError("cal_eam_forces()","MPI gather dfrhodrho_col failure")
532      endif
705
706
707
708
709
710    if (nmflag) then
711       call gather(d2frhodrhodrho,d2frhodrhodrho_row,plan_atom_row)
712       call gather(d2frhodrhodrho,d2frhodrhodrho_col,plan_atom_col)
713    endif
533   #endif
534 +    
535 +    
536 +  end subroutine calc_sc_preforce_Frho
537  
538  
539 <  end subroutine calc_eam_preforce_Frho
540 <
719 <
720 <
721 <
722 <  !! Does EAM pairwise Force calculation.  
723 <  subroutine do_eam_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
539 >  !! Does Sutton-Chen  pairwise Force calculation.  
540 >  subroutine do_sc_pair(atom1, atom2, d, rij, r2, rcut, sw, vpair, fpair, &
541         pot, f, do_pot)
542      !Arguments    
543      integer, intent(in) ::  atom1, atom2
544 <    real( kind = dp ), intent(in) :: rij, r2
544 >    real( kind = dp ), intent(in) :: rij, r2, rcut
545      real( kind = dp ) :: pot, sw, vpair
546      real( kind = dp ), dimension(3,nLocal) :: f
547      real( kind = dp ), intent(in), dimension(3) :: d
# Line 733 | Line 550 | contains
550      logical, intent(in) :: do_pot
551  
552      real( kind = dp ) :: drdx,drdy,drdz
553 <    real( kind = dp ) :: d2
554 <    real( kind = dp ) :: phab,pha,dvpdr,d2vpdrdr
738 <    real( kind = dp ) :: rha,drha,d2rha, dpha
739 <    real( kind = dp ) :: rhb,drhb,d2rhb, dphb
553 >    real( kind = dp ) :: dvpdr
554 >    real( kind = dp ) :: drhodr
555      real( kind = dp ) :: dudr
556 <    real( kind = dp ) :: rci,rcj
556 >    real( kind = dp ) :: rcij
557      real( kind = dp ) :: drhoidr,drhojdr
743    real( kind = dp ) :: d2rhoidrdr
744    real( kind = dp ) :: d2rhojdrdr
558      real( kind = dp ) :: Fx,Fy,Fz
559      real( kind = dp ) :: r,d2pha,phb,d2phb
560 <
560 >    real( kind = dp ) :: pot_temp,vptmp
561 >    real( kind = dp ) :: epsilonij,aij,nij,mij,vcij
562      integer :: id1,id2
563      integer  :: mytype_atom1
564      integer  :: mytype_atom2
# Line 753 | Line 567 | contains
567  
568      ! write(*,*) "Frho: ", Frho(atom1)
569  
570 <    phab = 0.0E0_DP
570 >
571      dvpdr = 0.0E0_DP
758    d2vpdrdr = 0.0E0_DP
572  
760    if (rij .lt. EAM_rcut) then
573  
574   #ifdef IS_MPI
575         atid1 = atid_row(atom1)
# Line 767 | Line 579 | contains
579         atid2 = atid(atom2)
580   #endif
581  
582 <       mytype_atom1 = EAMList%atidToEAMType(atid1)
583 <       mytype_atom2 = EAMList%atidTOEAMType(atid2)
582 >       mytype_atom1 = SCList%atidToSCType(atid1)
583 >       mytype_atom2 = SCList%atidTOSCType(atid2)
584  
773
774       ! get cutoff for atom 1
775       rci = EAMList%EAMParams(mytype_atom1)%eam_rcut
776       ! get type specific cutoff for atom 2
777       rcj = EAMList%EAMParams(mytype_atom2)%eam_rcut
778
585         drdx = d(1)/rij
586         drdy = d(2)/rij
587         drdz = d(3)/rij
588  
589 <       if (rij.lt.rci) then
590 <          call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
591 <               EAMList%EAMParams(mytype_atom1)%eam_rvals, &
592 <               EAMList%EAMParams(mytype_atom1)%eam_rho_r, &
593 <               EAMList%EAMParams(mytype_atom1)%eam_rho_r_pp, &
594 <               rij, rha,drha,d2rha)
789 <          !! Calculate Phi(r) for atom1.
790 <          call eam_splint(EAMList%EAMParams(mytype_atom1)%eam_nr, &
791 <               EAMList%EAMParams(mytype_atom1)%eam_rvals, &
792 <               EAMList%EAMParams(mytype_atom1)%eam_phi_r, &
793 <               EAMList%EAMParams(mytype_atom1)%eam_phi_r_pp, &
794 <               rij, pha,dpha,d2pha)
795 <       endif
589 >                
590 >       epsilonij = MixingMap(mytype_atom1,mytype_atom2)%epsilon
591 >       aij       = MixingMap(mytype_atom1,mytype_atom2)%alpha
592 >       nij       = MixingMap(mytype_atom1,mytype_atom2)%n
593 >       mij       = MixingMap(mytype_atom1,mytype_atom2)%m
594 >       vcij      = MixingMap(mytype_atom1,mytype_atom2)%vpair_pot              
595  
596 <       if (rij.lt.rcj) then      
798 <          ! Calculate rho,drho and d2rho for atom1
799 <          call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
800 <               EAMList%EAMParams(mytype_atom2)%eam_rvals, &
801 <               EAMList%EAMParams(mytype_atom2)%eam_rho_r, &
802 <               EAMList%EAMParams(mytype_atom2)%eam_rho_r_pp, &
803 <               rij, rhb,drhb,d2rhb)
596 >       vptmp = epsilonij*((aij/r)**nij)
597  
805          !! Calculate Phi(r) for atom2.
806          call eam_splint(EAMList%EAMParams(mytype_atom2)%eam_nr, &
807               EAMList%EAMParams(mytype_atom2)%eam_rvals, &
808               EAMList%EAMParams(mytype_atom2)%eam_phi_r, &
809               EAMList%EAMParams(mytype_atom2)%eam_phi_r_pp, &
810               rij, phb,dphb,d2phb)
811       endif
598  
599 <       if (rij.lt.rci) then
600 <          phab = phab + 0.5E0_DP*(rhb/rha)*pha
815 <          dvpdr = dvpdr + 0.5E0_DP*((rhb/rha)*dpha + &
816 <               pha*((drhb/rha) - (rhb*drha/rha/rha)))
817 <          d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rhb/rha)*d2pha + &
818 <               2.0E0_DP*dpha*((drhb/rha) - (rhb*drha/rha/rha)) + &
819 <               pha*((d2rhb/rha) - 2.0E0_DP*(drhb*drha/rha/rha) + &
820 <               (2.0E0_DP*rhb*drha*drha/rha/rha/rha) - (rhb*d2rha/rha/rha)))
821 <       endif
599 >       dvpdr = -nij*vptmp/r
600 >       drhodr = -mij*((aij/r)**mij)/r
601  
602 <       if (rij.lt.rcj) then
603 <          phab = phab + 0.5E0_DP*(rha/rhb)*phb
604 <          dvpdr = dvpdr + 0.5E0_DP*((rha/rhb)*dphb + &
605 <               phb*((drha/rhb) - (rha*drhb/rhb/rhb)))
606 <          d2vpdrdr = d2vpdrdr + 0.5E0_DP*((rha/rhb)*d2phb + &
607 <               2.0E0_DP*dphb*((drha/rhb) - (rha*drhb/rhb/rhb)) + &
829 <               phb*((d2rha/rhb) - 2.0E0_DP*(drha*drhb/rhb/rhb) + &
830 <               (2.0E0_DP*rha*drhb*drhb/rhb/rhb/rhb) - (rha*d2rhb/rhb/rhb)))
831 <       endif
602 >      
603 >       dudr = drhodr*(dfrhodrho(atom1)+dfrhodrho(atom2)) &
604 >            + dvpdr
605 >      
606 >       pot_temp = vptmp + vcij
607 >
608  
833       drhoidr = drha
834       drhojdr = drhb
835
836       d2rhoidrdr = d2rha
837       d2rhojdrdr = d2rhb
838
839
609   #ifdef IS_MPI
610 <       dudr = drhojdr*dfrhodrho_row(atom1)+drhoidr*dfrhodrho_col(atom2) &
610 >       dudr = drhodr*(dfrhodrho_row(atom1)+dfrhodrho_col(atom2)) &
611              + dvpdr
612  
613   #else
614 <       dudr = drhojdr*dfrhodrho(atom1)+drhoidr*dfrhodrho(atom2) &
614 >       dudr = drhodr*(dfrhodrho(atom1)+dfrhodrho(atom2)) &
615              + dvpdr
847       ! write(*,*) "Atom1,Atom2, dfrhodrho(atom1) dfrhodrho(atom2): ", atom1,atom2,dfrhodrho(atom1),dfrhodrho(atom2)
616   #endif
617  
618 +
619         fx = dudr * drdx
620         fy = dudr * drdy
621         fz = dudr * drdz
# Line 854 | Line 623 | contains
623  
624   #ifdef IS_MPI
625         if (do_pot) then
626 <          pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + phab*0.5
627 <          pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + phab*0.5
626 >          pot_Row(METALLIC_POT,atom1) = pot_Row(METALLIC_POT,atom1) + (pot_temp)*0.5
627 >          pot_Col(METALLIC_POT,atom2) = pot_Col(METALLIC_POT,atom2) + (pot_temp)*0.5
628         end if
629  
630         f_Row(1,atom1) = f_Row(1,atom1) + fx
# Line 868 | Line 637 | contains
637   #else
638  
639         if(do_pot) then
640 <          pot = pot + phab
640 >          pot = pot + pot_temp
641         end if
642  
643         f(1,atom1) = f(1,atom1) + fx
# Line 880 | Line 649 | contains
649         f(3,atom2) = f(3,atom2) - fz
650   #endif
651  
652 <       vpair = vpair + phab
652 >      
653   #ifdef IS_MPI
654         id1 = AtomRowToGlobal(atom1)
655         id2 = AtomColToGlobal(atom2)
# Line 897 | Line 666 | contains
666  
667         endif
668  
900       if (nmflag) then
669  
670 <          drhoidr = drha
903 <          drhojdr = drhb
904 <          d2rhoidrdr = d2rha
905 <          d2rhojdrdr = d2rhb
670 >  end subroutine do_sc_pair
671  
907 #ifdef IS_MPI
908          d2 = d2vpdrdr + &
909               d2rhoidrdr*dfrhodrho_col(atom2) + &
910               d2rhojdrdr*dfrhodrho_row(atom1) + &
911               drhoidr*drhoidr*d2frhodrhodrho_col(atom2) + &
912               drhojdr*drhojdr*d2frhodrhodrho_row(atom1)
672  
914 #else
673  
674 <          d2 = d2vpdrdr + &
917 <               d2rhoidrdr*dfrhodrho(atom2) + &
918 <               d2rhojdrdr*dfrhodrho(atom1) + &
919 <               drhoidr*drhoidr*d2frhodrhodrho(atom2) + &
920 <               drhojdr*drhojdr*d2frhodrhodrho(atom1)
921 < #endif
922 <       end if
923 <
924 <    endif
925 <  end subroutine do_eam_pair
926 <
927 <
928 <  subroutine eam_splint(nx, xa, ya, yppa, x, y, dy, d2y)
929 <
930 <    integer :: atype, nx, j
931 <    real( kind = DP ), dimension(:) :: xa
932 <    real( kind = DP ), dimension(:) :: ya
933 <    real( kind = DP ), dimension(:) :: yppa
934 <    real( kind = DP ) :: x, y
935 <    real( kind = DP ) :: dy, d2y
936 <    real( kind = DP ) :: del, h, a, b, c, d
937 <    integer :: pp_arraySize
938 <
939 <
940 <    ! this spline code assumes that the x points are equally spaced
941 <    ! do not attempt to use this code if they are not.
942 <
943 <
944 <    ! find the closest point with a value below our own:
945 <    j = FLOOR(real((nx-1),kind=dp) * (x - xa(1)) / (xa(nx) - xa(1))) + 1
946 <
947 <    ! check to make sure we're inside the spline range:
948 <    if ((j.gt.nx).or.(j.lt.1)) then
949 <       write(errMSG,*) "EAM_splint: x is outside bounds of spline: ",x,j
950 <       call handleError(routineName,errMSG)
951 <    endif
952 <    ! check to make sure we haven't screwed up the calculation of j:
953 <    if ((x.lt.xa(j)).or.(x.gt.xa(j+1))) then
954 <       if (j.ne.nx) then
955 <          write(errMSG,*) "EAM_splint:",x," x is outside bounding range"
956 <          call handleError(routineName,errMSG)
957 <       endif
958 <    endif
959 <
960 <    del = xa(j+1) - x
961 <    h = xa(j+1) - xa(j)
962 <
963 <    a = del / h
964 <    b = 1.0E0_DP - a
965 <    c = a*(a*a - 1.0E0_DP)*h*h/6.0E0_DP
966 <    d = b*(b*b - 1.0E0_DP)*h*h/6.0E0_DP
967 <
968 <    y = a*ya(j) + b*ya(j+1) + c*yppa(j) + d*yppa(j+1)
969 <
970 <    dy = (ya(j+1)-ya(j))/h &
971 <         - (3.0E0_DP*a*a - 1.0E0_DP)*h*yppa(j)/6.0E0_DP &
972 <         + (3.0E0_DP*b*b - 1.0E0_DP)*h*yppa(j+1)/6.0E0_DP
973 <
974 <
975 <    d2y = a*yppa(j) + b*yppa(j+1)
976 <
977 <
978 <  end subroutine eam_splint
979 <
980 <
981 <  subroutine eam_spline(nx, xa, ya, yppa, yp1, ypn, boundary)
982 <
983 <
984 <    ! yp1 and ypn are the first derivatives of y at the two endpoints
985 <    ! if boundary is 'L' the lower derivative is used
986 <    ! if boundary is 'U' the upper derivative is used
987 <    ! if boundary is 'B' then both derivatives are used
988 <    ! if boundary is anything else, then both derivatives are assumed to be 0
989 <
990 <    integer :: nx, i, k, max_array_size
991 <
992 <    real( kind = DP ), dimension(:)        :: xa
993 <    real( kind = DP ), dimension(:)        :: ya
994 <    real( kind = DP ), dimension(:)        :: yppa
995 <    real( kind = DP ), dimension(size(xa)) :: u
996 <    real( kind = DP ) :: yp1,ypn,un,qn,sig,p
997 <    character(len=*) :: boundary
998 <
999 <    ! make sure the sizes match
1000 <    if ((nx /= size(xa)) .or. (nx /= size(ya))) then
1001 <       call handleWarning("EAM_SPLINE","Array size mismatch")
1002 <    end if
1003 <
1004 <    if ((boundary.eq.'l').or.(boundary.eq.'L').or. &
1005 <         (boundary.eq.'b').or.(boundary.eq.'B')) then
1006 <       yppa(1) = -0.5E0_DP
1007 <       u(1) = (3.0E0_DP/(xa(2)-xa(1)))*((ya(2)-&
1008 <            ya(1))/(xa(2)-xa(1))-yp1)
1009 <    else
1010 <       yppa(1) = 0.0E0_DP
1011 <       u(1)  = 0.0E0_DP
1012 <    endif
1013 <
1014 <    do i = 2, nx - 1
1015 <       sig = (xa(i) - xa(i-1)) / (xa(i+1) - xa(i-1))
1016 <       p = sig * yppa(i-1) + 2.0E0_DP
1017 <       yppa(i) = (sig - 1.0E0_DP) / p
1018 <       u(i) = (6.0E0_DP*((ya(i+1)-ya(i))/(xa(i+1)-xa(i)) - &
1019 <            (ya(i)-ya(i-1))/(xa(i)-xa(i-1)))/ &
1020 <            (xa(i+1)-xa(i-1)) - sig * u(i-1))/p
1021 <    enddo
1022 <
1023 <    if ((boundary.eq.'u').or.(boundary.eq.'U').or. &
1024 <         (boundary.eq.'b').or.(boundary.eq.'B')) then
1025 <       qn = 0.5E0_DP
1026 <       un = (3.0E0_DP/(xa(nx)-xa(nx-1)))* &
1027 <            (ypn-(ya(nx)-ya(nx-1))/(xa(nx)-xa(nx-1)))
1028 <    else
1029 <       qn = 0.0E0_DP
1030 <       un = 0.0E0_DP
1031 <    endif
1032 <
1033 <    yppa(nx)=(un-qn*u(nx-1))/(qn*yppa(nx-1)+1.0E0_DP)
1034 <
1035 <    do k = nx-1, 1, -1
1036 <       yppa(k)=yppa(k)*yppa(k+1)+u(k)
1037 <    enddo
1038 <
1039 <  end subroutine eam_spline
1040 <
1041 < end module eam
674 > end module suttonchen

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines