1!
2! Copyright (C) 2004-2007 Quantum ESPRESSO group
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8!--------------------------------------------------------------------------
9!
10MODULE wannier_gw
11  !
12  ! ... The variables needed for gww-gwl code (head.x)
13  !
14  USE kinds, ONLY: DP
15  !
16  SAVE
17  !
18  !From HEAD
19  LOGICAL :: l_head=.false.!if true calculates the head of the symmetrized dielectric matrix -1
20  INTEGER :: n_gauss!number of frequency steps for head calculation
21  REAL(kind=DP) :: omega_gauss!period for frequency calculation
22  INTEGER :: grid_type!0 GL -T,T 2 GL 0 T 3 Equally spaced 0 Omega
23  INTEGER :: nsteps_lanczos!number of lanczos steps
24    !options for grid_freq=5
25  INTEGER :: second_grid_n!sub spacing for second grid
26  INTEGER :: second_grid_i!max regular step using the second grid
27  LOGICAL :: l_scissor!if true displaces occupied manifold of scissor(1) and unoccupied manifold of scissor(2)
28  REAL(kind=DP) :: scissor(2)!see above
29  !From pw4gww
30  TYPE real_matrix_pointer
31     REAL(kind=DP), DIMENSION(:,:), POINTER :: p
32  END TYPE real_matrix_pointer
33
34  TYPE complex_matrix_pointer
35     COMPLEX(kind=DP), DIMENSION(:,:), POINTER :: p
36  END TYPE complex_matrix_pointer
37
38
39  TYPE optimal_options!options for obtaining optimal basis sets
40     LOGICAL :: l_complete!if true just do a diagonalization
41     INTEGER :: idiago !kind of optimization: 0=Gram-Schmidt like
42     INTEGER :: ithres!kind of threshold: 0=on modulus square
43     REAL(kind=DP) :: thres!value of threshold
44  END TYPE optimal_options
45
46
47
48  REAL(kind=DP),  ALLOCATABLE :: wannier_centers(:,:,:)!wannier centers in a.u.
49  REAL(kind=DP),  ALLOCATABLE :: wannier_radii(:,:)!wannier centers in a.u.
50  INTEGER, ALLOCATABLE  :: w_centers(:,:,:)!wanier centers on the grid
51
52  INTEGER, ALLOCATABLE  :: w_radii(:,:)!wannier lengths in grid units
53  COMPLEX(kind=DP), ALLOCATABLE :: u_trans(:,:,:)!unitarian transformation from bloch wfcs to wannier'
54  INTEGER :: numw_prod!number of products w_i(r)*w_j(r) then of orthonormalized products
55  INTEGER :: num_nbndv(2) !number of valence bands
56  INTEGER :: num_nbnds !number of studied bands valence plus  a part of conduction's
57  REAL(kind=DP), ALLOCATABLE :: becp_gw(:,:,:)!to store projections of wfcs with us projectors
58  REAL(kind=DP), ALLOCATABLE :: becp_gw_c(:,:,:)!to store projections of wfcs with us projectors for {c'} subspace
59  COMPLEX(kind=DP), ALLOCATABLE :: expgsave(:,:,:,:) !to store exp_igx  on us augmentation functions
60  INTEGER :: nset!number of states to be read  written from/to file simultaneously
61  LOGICAL :: l_truncated_coulomb!if true the Coulomb potential is truncated
62  REAL(kind=DP) :: truncation_radius!truncation radius for Coulomb potential
63  INTEGER :: remainder!1-cutoff 2-distance 3-no remainder 4-postprocessing from W 5-postprocessing from dressed polarization P
64  INTEGER :: restart_gww!for restarting the calculation of gww stuff, 0 begins from beginning
65
66
67  LOGICAL :: l_gram!if true uses gram schmidt for orthonormalizing the products of wanniers
68  !LOGICAL :: l_head!if true calculates the head of the symmetrized dielectric matrix -1
69  !INTEGER :: n_gauss!number of frequency steps for head calculation
70  !REAL(kind=DP) :: omega_gauss!period for frequency calculation
71  LOGICAL :: l_exchange!if true calculate the exchange terms with k-points sampling
72
73
74  LOGICAL :: l_zero!if .true. calculate also the v e v^1/2 operators with G=0,G'=0 put to 0
75
76  LOGICAL :: l_wing!if .true. calculate also the wing terms, it requires the file .e_head
77
78
79  !INTEGER :: grid_type!0 GL -T,T 2 GL 0 T 3 Equally spaced 0 Omega
80
81
82  INTEGER :: nset_overlap!number of states to be read  written from/to file simultaneously, when
83                         !calculating overlaps
84  INTEGER :: nspace!space on grid for evalueation of exchange-type integrals
85
86
87  REAL(kind=DP) :: ecutoff_global!cut off in Rydbergs for G sum on (dense charge grid)
88
89
90  INTEGER :: maxiter2!max number of iteration for the genaralized maximally localized wannier
91                      !of the second conduction manifold
92  REAL(kind=DP) :: diago_thr2!thresold for electronic states used in c_bands for upper
93                              !conduction manifold if any, if ==0 used same cutoff as for valence
94  LOGICAL :: l_plot_mlwf!if true save the orthonormal wannier for plotting
95
96
97
98  INTEGER :: max_ngm!max number of g vector for charge grid effctively stored
99
100!variables for parallelization on matrices
101
102  LOGICAL :: l_pmatrix !if true parallelize on  matrices
103  INTEGER :: p_mpime!processor number
104  INTEGER :: p_nproc!number of processors
105  INTEGER :: npcol!number of processor columns
106  INTEGER :: nprow!number of processor rows
107  INTEGER :: icontxt!blacs descriptor
108  INTEGER :: myrow!actual processor row
109  INTEGER :: mycol!actual processor column
110
111
112
113  LOGICAL :: l_coulomb_analysis!if true after polarization analysis consider eigenvalues of coulomb potential
114  REAL(kind=DP) ::  cutoff_coulomb_analysis!cutoff for coulomb analysis
115
116
117  INTEGER :: n_pola_lanczos!number of orthonormal states for polarization lanczos-style
118  INTEGER :: n_self_lanczos!number of orthonormal states for self-energy lanczos-style
119  INTEGER :: nsteps_lanczos_pola!number of lanczos steps for the polarizability
120  INTEGER :: nsteps_lanczos_self!number of lanczos steps for the self_energy
121  REAL(kind=DP) :: s_pola_lanczos!cutoff for lanczos basis for polarization
122  REAL(kind=DP) :: s_self_lanczos!cutoff for lanczos basis for self-energy
123  INTEGER :: nump_lanczos!dimension of basis for lanczos calculation of the polarization
124  INTEGER :: nums_lanczos!dimension of basis for lanczos calculation of the self-energy
125  REAL(kind=DP) :: s_g_lanczos!cutoff for absolute value of trial green function
126
127  LOGICAL :: l_pmat_diago!if true find the basis for the polarization diagonalizing the O matrix
128  REAL(kind=DP) :: pmat_ethr!threshold for diagonalizing the O matrix
129
130  REAL(kind=DP) :: pmat_cutoff!cutoff (in Ryd) for polarization diagonalization
131  INTEGER :: pmat_type!type of approximation 1 usual, 2 with wanniers, 3 with optimal representation,5 just plane waves
132  INTEGER :: n_fast_pmat!number of states  for fast evaluation of conduction manifold if =0 disabled
133  INTEGER :: n_pmat!number of orthonormal states for optimal representation O matrix
134  REAL(kind=DP) :: s_pmat!cutoff for optimal basis for O matrix
135  INTEGER :: lanczos_restart!restart point for lanczos
136  INTEGER :: n_pola_lanczos_eff!effective number of pola states; if 0 equal to n_pola_lanczos
137  INTEGER :: n_self_lanczos_eff!effective number of self states; if 0 equal to n_self_lanczos
138  REAL(kind=DP) :: off_fast_pmat!offset in Ry for fast assessment of polarizability if =0 disabled
139  LOGICAL :: l_fast_pola!if true fast assessment of polarizability for basis construction
140  LOGICAL :: l_v_basis!if true valuate the polarizability basis vectors as eigenstates of v operator
141  REAL(kind=DP) :: v_cutoff!cutoff in Ryd for v operator
142  LOGICAL :: l_iter_algorithm!if true uses iterative algorithms
143  REAL(kind=DP) :: dual_pb!dual value till 4.d0 for defing the grid on which the polarizability basis is created
144
145  REAL(kind=DP), ALLOCATABLE :: vg_q(:) ! contains the elements V(G) of the Coulomb potential obtained upon integration over q
146  LOGICAL :: l_t_wannier!if true builds t verctors starting from KS valence wannier functions
147  REAL(kind=DP) :: dual_vt!dual value till 4.d0 for defing the grid on which the t vectors created
148  REAL(kind=DP) :: dual_vs!dual value till 4.d0 for defing the grid on which the s vectors created
149
150  LOGICAL  :: lwannier!if true take advantage of localization of wannier functions
151  REAL(kind=DP) :: wannier_thres!threshold for modulus of wannier function in a.u.
152
153
154  INTEGER :: s_first_state!if different from 0, first KS state for calculatin s vectors (if last 1)
155  INTEGER :: s_last_state!if different from 0, last KS state for calculatin s vectors (if last num_nbnds)
156
157  LOGICAL :: l_selfconsistent!if true do selfconsistent GW calculation, requires file band.dat
158  REAL(kind=DP), ALLOCATABLE :: ene_gw(:,:)!GW energies of previous iteration for selfconsistent calculation
159  INTEGER :: n_gw_states!number of GW states for selfconsistent calculation
160  REAL(kind=DP) :: delta_self!delta energy for selfconsistent calculation
161
162  LOGICAL :: l_whole_s!if true calculates also the off-diagonal elemenets of V_xc for then
163                      !calculating the off-diagonal elements of sigma
164  LOGICAL :: l_ts_eigen!if true the t and global vectors are calculated considering also the eigenvalues of the partial basis (recommanded)
165
166  LOGICAL :: l_frac_occ! if true consider fractional occupancies
167  INTEGER :: num_nbndv_min(2)!limits for fully occupied states
168
169  LOGICAL :: l_cond_pol_base!if true uses conduction states till num_nbnds for the construction of the polarizability bases
170
171
172  LOGICAL :: l_semicore!if true evaluate semicore terms
173  INTEGER :: n_semicore!number of semicore states staring from the bottom of valence states
174  LOGICAL :: l_semicore_read!if true reads semicore file for calculating products for Green's function
175
176  LOGICAL :: l_verbose!if true a lot of ouput for debug
177
178
179  LOGICAL :: l_contour! if true calculates the terms for contour integration
180  LOGICAL :: l_real!if true calculate the polarizability basis, s and t vectors avoiding ffts it requires more memory
181
182  LOGICAL :: l_big_system!if true uses startegy for large systems: just local s vectors are used
183
184  REAL(kind=DP) ::extra_pw_cutoff!cutoff to add to the optimal polarizability basis plane-waves (sin and cos functions)
185                                 !if 0 no plane waves is added
186
187  !REAL(kind=DP) :: exchange_fast_dual!for defining the fast exchnage routines
188
189  LOGICAL :: l_bse!if true computing quantities for bse calculation
190  REAL(kind=DP) :: s_bse!threshold for wannier function overlap
191  REAL(kind=DP) :: dual_bse!dual factor for bse calculations
192
193  LOGICAL :: l_simple!if true writes on disk polarizability basis on real space for further post-processing
194
195  LOGICAL :: l_list !if true uses startegy for large systems from list of states included in s_first_state, s_last_state
196  INTEGER :: n_list(2)!number of states in list for the 2 spin channels
197  INTEGER, ALLOCATABLE :: i_list(:,:) !list of KS states to be computed
198
199  LOGICAL :: l_full!if true prepare data for further post-processing for a full-relativistic calculation
200  INTEGER :: n_full(2)!numeber of proper relativistic states in G of GW for collinear spin channel
201
202!variables for splitting the head calculation in blocks in order to reduce memory usage
203!no effect on results
204
205  INTEGER :: len_head_block_freq!length of blocks on frequency
206  INTEGER :: len_head_block_wfc!length of blocks on unperturbed occupied wfcs
207
208
209
210  INTERFACE free_memory
211
212  MODULE PROCEDURE free_complex,free_real
213
214  END INTERFACE
215
216  CONTAINS
217
218    subroutine free_complex( c)
219      implicit none
220      type(complex_matrix_pointer) :: c
221      deallocate(c%p)
222      return
223    end subroutine
224
225
226   subroutine free_real( r)
227      implicit none
228      type(real_matrix_pointer) :: r
229      deallocate(r%p)
230      return
231    end subroutine
232
233
234
235    subroutine  max_ngm_set
236 !set the value of max_ngm
237      use io_global, only : stdout
238      use gvect, only :     ngm,gg
239      use cell_base, only : tpiba2
240
241      implicit none
242
243      integer :: ig
244
245      max_ngm=0
246      do ig=1,ngm
247         if(gg(ig)*tpiba2 >= ecutoff_global) exit
248         max_ngm=max_ngm+1
249      enddo
250
251      write(stdout,*) 'MAX_NGM:', max_ngm, ngm
252
253end subroutine max_ngm_set
254
255
256
257END MODULE wannier_gw
258