The Elk Code
epsinv.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2010 J. K. Dewhurst, S. Sharma and E. K. U. Gross.
3 ! This file is distributed under the terms of the GNU General Public License.
4 ! See the file COPYING for license details.
5 
6 subroutine epsinv
7 use modmain
8 use modmpi
9 use modomp
10 implicit none
11 ! local variables
12 integer iq,ik,ig,iw
13 integer n,nthd
14 ! automatic arrays
15 integer(omp_lock_kind) lock(nwrf)
16 real(8) vgqc(3,ngrf),gqc(ngrf),gclgq(ngrf)
17 ! allocatable arrays
18 real(8), allocatable :: jlgqr(:,:,:)
19 complex(8), allocatable :: ylmgq(:,:),sfacgq(:,:),epsi(:,:,:)
20 complex(4), allocatable :: vchi0(:,:,:)
21 ! allocate local arrays
22 allocate(jlgqr(njcmax,nspecies,ngrf))
23 allocate(ylmgq(lmmaxo,ngrf),sfacgq(ngrf,natmtot))
24 allocate(epsi(ngrf,ngrf,nwrf),vchi0(ngrf,ngrf,nwrf))
25 ! initialise the OpenMP locks
26 do iw=1,nwrf
27  call omp_init_lock(lock(iw))
28 end do
29 if (mp_mpi) write(*,*)
30 ! synchronise MPI processes
31 call mpi_barrier(mpicom,ierror)
32 ! loop over q-points
33 do iq=1,nqpt
34  if (mp_mpi) write(*,'("Info(epsinv): ",I6," of ",I6," q-points")') iq,nqpt
35 ! generate the G+q-vectors and related functions
36  call gengqf(ngrf,vqc(:,iq),vgqc,gqc,jlgqr,ylmgq,sfacgq)
37 ! generate the regularised Coulomb Green's function in G+q-space
38  call gengclgq(.true.,iq,ngrf,gqc,gclgq)
39 ! use the symmetric form
40  gclgq(1:ngrf)=sqrt(gclgq(1:ngrf))
41 ! zero the response function
42  vchi0(1:ngrf,1:ngrf,1:nwrf)=0.e0
43  call holdthd(nkptnr/np_mpi,nthd)
44 !$OMP PARALLEL DO DEFAULT(SHARED) &
45 !$OMP SCHEDULE(DYNAMIC) &
46 !$OMP NUM_THREADS(nthd)
47  do ik=1,nkptnr
48 ! distribute among MPI processes
49  if (mod(ik-1,np_mpi) /= lp_mpi) cycle
50 ! compute v¹⸍² χ₀ v¹⸍²
51  call genvchi0(.false.,ik,lock,vql(:,iq),gclgq,jlgqr,ylmgq,sfacgq,ngrf,vchi0)
52  end do
53 !$OMP END PARALLEL DO
54  call freethd(nthd)
55 ! add vchi0 from each process and redistribute
56  if (np_mpi > 1) then
57  n=ngrf*ngrf*nwrf
58  call mpi_allreduce(mpi_in_place,vchi0,n,mpi_complex,mpi_sum,mpicom,ierror)
59  end if
60 ! negate and add δ(G,G')
61  epsi(1:ngrf,1:ngrf,1:nwrf)=-vchi0(1:ngrf,1:ngrf,1:nwrf)
62  do ig=1,ngrf
63  epsi(ig,ig,1:nwrf)=epsi(ig,ig,1:nwrf)+1.d0
64  end do
65 !-------------------------------------!
66 ! invert epsilon over G-space !
67 !-------------------------------------!
68  call holdthd(nwrf,nthd)
69 !$OMP PARALLEL DO DEFAULT(SHARED) &
70 !$OMP SCHEDULE(DYNAMIC) &
71 !$OMP NUM_THREADS(nthd)
72  do iw=1,nwrf
73  call zminv(ngrf,epsi(:,:,iw))
74  end do
75 !$OMP END PARALLEL DO
76  call freethd(nthd)
77 ! write inverse RPA epsilon to EPSINV.OUT
78  if (mp_mpi) call putepsinv(iq,epsi)
79 ! end loop over q-points
80 end do
81 ! destroy the OpenMP locks
82 do iw=1,nwrf
83  call omp_destroy_lock(lock(iw))
84 end do
85 deallocate(jlgqr,ylmgq,sfacgq,epsi,vchi0)
86 ! synchronise MPI processes
87 call mpi_barrier(mpicom,ierror)
88 end subroutine
89 
logical mp_mpi
Definition: modmpi.f90:17
integer lmmaxo
Definition: modmain.f90:203
subroutine epsinv
Definition: epsinv.f90:7
integer nqpt
Definition: modmain.f90:525
subroutine gengqf(ng, vqpc, vgqc, gqc, jlgqr, ylmgq, sfacgq)
Definition: gengqf.f90:7
Definition: modomp.f90:6
subroutine putepsinv(iq, epsi)
Definition: putepsinv.f90:7
integer nkptnr
Definition: modmain.f90:463
integer np_mpi
Definition: modmpi.f90:13
pure subroutine gengclgq(treg, iq, ngq, gqc, gclgq)
Definition: gengclgq.f90:7
real(8), dimension(:,:), allocatable vqc
Definition: modmain.f90:547
subroutine genvchi0(t3hw, ik, lock, vqpl, gclgq, jlgqr, ylmgq, sfacgq, nm, vchi0)
Definition: genvchi0.f90:7
real(8), dimension(:,:), allocatable vql
Definition: modmain.f90:545
Definition: modmpi.f90:6
integer lp_mpi
Definition: modmpi.f90:15
integer nspecies
Definition: modmain.f90:34
subroutine freethd(nthd)
Definition: modomp.f90:106
subroutine holdthd(nloop, nthd)
Definition: modomp.f90:78
integer njcmax
Definition: modmain.f90:1173
subroutine zminv(n, a)
Definition: zminv.f90:7
integer natmtot
Definition: modmain.f90:40
integer mpicom
Definition: modmpi.f90:11
integer ierror
Definition: modmpi.f90:19