~alirezagh76/bigdft/1.8

« back to all changes in this revision

Viewing changes to bigdft/src/modules/sw_potential.f90

  • Committer: Alireza Ghasemi
  • Date: 2019-08-12 10:16:31 UTC
  • mfrom: (1683.1.431 genovese)
  • Revision ID: alirezagh76@gmail.com-20190812101631-dp60bryufwstgydt
Merged with Luigi at ETSF

Show diffs side-by-side

added added

removed removed

Lines of Context:
143
143
         & deallocate_atomic_neighbours
144
144
    use dynamic_memory
145
145
    use f_utils
 
146
    use module_base, only: f_err_throw
 
147
    use at_domain, only: bc_periodic_dims,geocode_to_bc
146
148
 
147
149
    implicit none
148
150
 
157
159
    real(gp), dimension(3*astruct%nat), target :: pos_normalised
158
160
    real(gp), dimension(3*astruct%nat) :: box_vec
159
161
    real(gp), dimension(:), pointer :: pos
160
 
    real(gp), dimension(3) :: box
 
162
    real(gp), dimension(3) :: lbox
161
163
    integer :: NATOMS
162
164
    real(gp)  :: SIGMA 
163
165
    real(gp)  :: A 
172
174
    real(gp) :: A_EPS
173
175
 
174
176
    real(gp), dimension(:), pointer :: xa, ya, za
175
 
 
 
177
    logical, dimension(3) :: peri
176
178
    integer :: i, j, i_id, j_id, k, k_id
177
179
    integer :: my_counter_i
178
180
    real(gp) :: invsig
194
196
    pos(1:NATOMS) = rxyz(1, :) * Bohr_Ang
195
197
    pos(1 + NATOMS:2 * NATOMS) = rxyz(2, :) * Bohr_Ang
196
198
    pos(1 + 2 * NATOMS:3 * NATOMS) = rxyz(3, :) * Bohr_Ang
197
 
    box = astruct%cell_dim * Bohr_Ang
198
 
    if (astruct%geocode == "S") box(2) = 1._gp
199
 
 
200
 
    box_vec(1:natoms) = box(1)
201
 
    box_vec(1+natoms:2*natoms) = box(2)
202
 
    box_vec(1+natoms+natoms:3*natoms) = box(3)
203
 
 
204
 
    if ( astruct%geocode .eq. 'P') pos = modulo(pos, box_vec) !apply PBC implement surface later on
205
 
    if ( astruct%geocode .eq. 'S') pos(1:natoms) = modulo(pos(1:natoms), box_vec(1:natoms))
206
 
    if ( astruct%geocode .eq. 'S') pos(2*natoms+1:3*natoms) = modulo(pos(2*natoms+1:3*natoms), box_vec(2*natoms+1:3*natoms))
 
199
    lbox = astruct%cell_dim * Bohr_Ang
 
200
 
 
201
    peri=bc_periodic_dims(geocode_to_bc(astruct%geocode))
 
202
 
 
203
    where(.not. peri) lbox = 1._gp
 
204
 
 
205
    box_vec(1:natoms) = lbox(1)
 
206
    box_vec(1+natoms:2*natoms) = lbox(2)
 
207
    box_vec(1+natoms+natoms:3*natoms) = lbox(3)
 
208
 
 
209
    if (peri(1)) pos(1:natoms) = modulo(pos(1:natoms), box_vec(1:natoms))
 
210
    if (peri(2)) pos(natoms+1:2*natoms) = modulo(pos(natoms+1:2*natoms), box_vec(natoms+1:2*natoms))
 
211
    if (peri(3)) pos(2*natoms+1:3*natoms) = modulo(pos(2*natoms+1:3*natoms), box_vec(2*natoms+1:3*natoms))
 
212
       
 
213
!!$    if ( astruct%geocode .eq. 'P') pos = modulo(pos, box_vec) !apply PBC implement surface later on
 
214
!!$    if ( astruct%geocode .eq. 'S') pos(1:natoms) = modulo(pos(1:natoms), box_vec(1:natoms))
 
215
!!$    if ( astruct%geocode .eq. 'W') pos(natoms+1:2*natoms) = modulo(pos(natoms+1:2*natoms), box_vec(natoms+1:2*natoms))
 
216
!!$    if ( astruct%geocode .eq. 'S') pos(2*natoms+1:3*natoms) = modulo(pos(2*natoms+1:3*natoms), box_vec(2*natoms+1:3*natoms))
 
217
 
207
218
 
208
219
    ! Generate a neighbour list
209
220
    call astruct_neighbours(astruct, rxyz, nei)
246
257
          endif
247
258
 
248
259
          ! Rescale the lengths into Angstroems
249
 
          xij = xij * box(1)
250
 
          yij = yij * box(2)
251
 
          zij = zij * box(3)
 
260
          xij = xij * lbox(1)
 
261
          yij = yij * lbox(2)
 
262
          zij = zij * lbox(3)
252
263
 
253
264
          rij2 = xij*xij + yij*yij + zij*zij
254
265
 
321
332
                endif
322
333
 
323
334
                ! Rescale the lengths into Angstroems
324
 
                xik = xik * box(1)
325
 
                yik = yik * box(2)
326
 
                zik = zik * box(3)
 
335
                xik = xik * lbox(1)
 
336
                yik = yik * lbox(2)
 
337
                zik = zik * lbox(3)
327
338
 
328
339
                rik2 = xik*xik + yik*yik + zik*zik
329
340