The Elk Code
gwspecf.f90
Go to the documentation of this file.
1 
2 ! Copyright (C) 2016 A. Davydov, A. Sanna, J. K. Dewhurst, S. Sharma and
3 ! E. K. U. Gross. This file is distributed under the terms of the GNU General
4 ! Public License. See the file COPYING for license details.
5 
6 subroutine gwspecf
7 use modmain
8 use modgw
9 use modmpi
10 use modomp
11 use modtest
12 implicit none
13 ! local variables
14 integer ik,iw,nthd
15 real(8) dw
16 ! allocatable arrays
17 real(8), allocatable :: wr(:),sft(:),sf(:)
18 complex(8), allocatable :: se(:,:,:)
19 ! initialise universal variables
20 call init0
21 call init1
22 call init2
23 call init3
24 ! read Fermi energy from file
25 call readefm
26 ! get the eigenvalues and occupation numbers from file
27 do ik=1,nkpt
28  call getevalsv(filext,ik,vkl(:,ik),evalsv(:,ik))
29  call getoccsv(filext,ik,vkl(:,ik),occsv(:,ik))
30 end do
31 ! real axis frequencies
32 allocate(wr(nwplot))
33 dw=(wplot(2)-wplot(1))/dble(nwplot)
34 do iw=1,nwplot
35  wr(iw)=dw*dble(iw-1)+wplot(1)
36 end do
37 ! allocate and zero the total spectral function
38 allocate(sft(nwplot))
39 sft(1:nwplot)=0.d0
40 if (mp_mpi) write(*,*)
41 ! synchronise MPI processes
42 call mpi_barrier(mpicom,ierror)
43 ! loop over reduced k-point set
44 call holdthd(nkpt/np_mpi,nthd)
45 !$OMP PARALLEL DEFAULT(SHARED) &
46 !$OMP PRIVATE(sf,se) &
47 !$OMP NUM_THREADS(nthd)
48 allocate(sf(nwplot),se(nstsv,nstsv,0:nwfm))
49 !$OMP DO SCHEDULE(DYNAMIC)
50 do ik=1,nkpt
51 ! distribute among MPI processes
52  if (mod(ik-1,np_mpi) /= lp_mpi) cycle
53 !$OMP CRITICAL(gwspecf_1)
54  write(*,'("Info(gwspecf): ",I6," of ",I6," k-points")') ik,nkpt
55 !$OMP END CRITICAL(gwspecf_1)
56 ! get the self-energy at the fermionic frequencies from file
57  call getgwsefm(ik,se)
58 ! solve the Dyson equation on the real axis
59  call dysonr(ik,wr,se,sf)
60 ! write the spectral function to file
61 !$OMP CRITICAL(gwspecf_2)
62  call writegwsf(ik,wr,sf)
63 !$OMP END CRITICAL(gwspecf_2)
64 ! add to the total spectral function
65 !$OMP CRITICAL(gwspecf_3)
66  sft(1:nwplot)=sft(1:nwplot)+wkpt(ik)*sf(1:nwplot)
67 !$OMP END CRITICAL(gwspecf_3)
68 end do
69 !$OMP END DO
70 deallocate(sf,se)
71 !$OMP END PARALLEL
72 call freethd(nthd)
73 ! add total spectral function from each process
74 if (np_mpi > 1) then
75  call mpi_allreduce(mpi_in_place,sft,nwplot,mpi_double_precision,mpi_sum, &
76  mpicom,ierror)
77 end if
78 ! write the total spectral function to file (MPI master process only)
79 if (mp_mpi) then
80  open(50,file='GWTSF.OUT',form='FORMATTED')
81  do iw=1,nwplot
82  write(50,'(2G18.10)') wr(iw),sft(iw)
83  end do
84  close(50)
85  write(*,*)
86  write(*,'("Info(gw):")')
87  write(*,'(" GW spectral functions and Kohn-Sham eigenvalues written to &
88  &GWSF_Kkkkkkk.OUT")')
89  write(*,'(" for all k-points")')
90  write(*,*)
91  write(*,'(" Total GW spectral function written to GWTSF.OUT")')
92  write(*,*)
93  write(*,'(" Fermi energy for the Kohn-Sham eigenvalues is at zero in plots")')
94  write(*,'(" Fermi energy for the GW spectral function is undetermined")')
95  write(*,*)
96  write(*,'(" Spectral function units are states/Hartree/unit cell")')
97 end if
98 ! write the total GW spectral function to test file
99 call writetest(610,'total GW spectral function',nv=nwplot,tol=5.d-2,rva=sft)
100 deallocate(wr,sft)
101 end subroutine
102 
subroutine writetest(id, descr, nv, iv, iva, tol, rv, rva, zv, zva)
Definition: modtest.f90:16
character(256) filext
Definition: modmain.f90:1301
real(8), dimension(:,:), allocatable evalsv
Definition: modmain.f90:921
subroutine getgwsefm(ik, se)
Definition: getgwsefm.f90:7
logical mp_mpi
Definition: modmpi.f90:17
integer nkpt
Definition: modmain.f90:461
subroutine getevalsv(fext, ikp, vpl, evalsv_)
Definition: getevalsv.f90:7
Definition: modomp.f90:6
integer np_mpi
Definition: modmpi.f90:13
integer nstsv
Definition: modmain.f90:889
real(8), dimension(2) wplot
Definition: modmain.f90:1079
real(8), dimension(:), allocatable wkpt
Definition: modmain.f90:475
subroutine readefm
Definition: readefm.f90:10
subroutine writegwsf(ik, wr, sf)
Definition: writegwsf.f90:7
subroutine init3
Definition: init3.f90:7
subroutine init2
Definition: init2.f90:7
real(8), dimension(:,:), allocatable occsv
Definition: modmain.f90:905
subroutine init1
Definition: init1.f90:10
real(8), dimension(:,:), allocatable vkl
Definition: modmain.f90:471
Definition: modgw.f90:6
Definition: modmpi.f90:6
subroutine getoccsv(fext, ikp, vpl, occsvp)
Definition: getoccsv.f90:7
integer lp_mpi
Definition: modmpi.f90:15
subroutine freethd(nthd)
Definition: modomp.f90:106
subroutine holdthd(nloop, nthd)
Definition: modomp.f90:78
integer nwfm
Definition: modgw.f90:19
subroutine dysonr(ik, wr, sem, sf)
Definition: dysonr.f90:7
subroutine init0
Definition: init0.f90:10
subroutine gwspecf
Definition: gwspecf.f90:7
integer nwplot
Definition: modmain.f90:1073
integer mpicom
Definition: modmpi.f90:11
integer ierror
Definition: modmpi.f90:19