Octopus
xc_oep.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!! Copyright (C) 2012-2013 M. Gruning, P. Melo, M. Oliveira
3!! Copyright (C) 2022 N. Tancogne-Dejean
4!!
5!! This program is free software; you can redistribute it and/or modify
6!! it under the terms of the GNU General Public License as published by
7!! the Free Software Foundation; either version 2, or (at your option)
8!! any later version.
9!!
10!! This program is distributed in the hope that it will be useful,
11!! but WITHOUT ANY WARRANTY; without even the implied warranty of
12!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13!! GNU General Public License for more details.
14!!
15!! You should have received a copy of the GNU General Public License
16!! along with this program; if not, write to the Free Software
17!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
18!! 02110-1301, USA.
19!!
20
21#include "global.h"
22
23module xc_oep_oct_m
24 use comm_oct_m
25 use debug_oct_m
29 use global_oct_m
30 use grid_oct_m
33 use, intrinsic :: iso_fortran_env
40 use math_oct_m
42 use mesh_oct_m
44 use mpi_oct_m
47 use parser_oct_m
50 use scdm_oct_m
51 use space_oct_m
56 use scdm_oct_m
59 use xc_oct_m
60 use xc_f03_lib_m
62
63 implicit none
64
65 private
66 public :: &
67 xc_oep_t, &
69 xc_oep_end, &
77
79 integer, public, parameter :: &
80 OEP_LEVEL_NONE = 1, &
81 oep_level_kli = 3, &
83
85 integer, public, parameter :: &
86 OEP_MIXING_SCHEME_CONST = 1, &
89
91 integer, public, parameter :: &
92 OEP_TYPE_EXX = 1, &
93 oep_type_mgga = 2, &
94 oep_type_sic = 3, &
95 oep_type_photons = 4 ! one-photon OEP
96
97 type xc_oep_t
98 integer, public :: level
99 real(real64) :: mixing
100 integer :: mixing_scheme
101 type(lr_t) :: lr
102 type(linear_solver_t) :: solver
103 type(scf_tol_t) :: scftol
104 integer :: eigen_n
105 integer, allocatable :: eigen_type(:), eigen_index(:)
106 real(real64) :: socc, sfact
107 real(real64), allocatable, public :: vxc(:,:), uxc_bar(:,:,:)
108 real(real64), allocatable :: dlxc(:, :, :, :)
109 complex(real64), allocatable :: zlxc(:, :, :, :)
110 real(real64), public :: norm2ss
111 real(real64), allocatable :: vxc_old(:,:), ss_old(:,:)
112 integer :: noccst
113
114 type(scdm_t) :: scdm
115 logical :: scdm_for_pzsic
117 integer, public :: type = -1
118 end type xc_oep_t
119
120contains
121
122 ! ---------------------------------------------------------
123 subroutine xc_oep_init(oep, namespace, gr, st, mc, space, oep_type)
124 type(xc_oep_t), intent(inout) :: oep
125 type(namespace_t), intent(in) :: namespace
126 type(grid_t), intent(inout) :: gr
127 type(states_elec_t), intent(in) :: st
128 type(multicomm_t), intent(in) :: mc
129 class(space_t), intent(in) :: space
130 integer, intent(in) :: oep_type
131
132 push_sub(xc_oep_init)
133
134 !%Variable OEPLevel
135 !%Type integer
136 !%Default oep_kli
137 !%Section Hamiltonian::XC
138 !%Description
139 !% At what level shall <tt>Octopus</tt> handle the optimized effective potential (OEP) equation.
140 !%Option oep_none 1
141 !% Do not solve OEP equation.
142 !%Option oep_kli 3
143 !% Krieger-Li-Iafrate (KLI) approximation.
144 !% Ref: JB Krieger, Y Li, GJ Iafrate, <i>Phys. Lett. A</i> <b>146</b>, 256 (1990).
145 !%Option oep_full 5
146 !% (Experimental) Full solution of OEP equation using the Sternheimer approach.
147 !% The linear solver will be controlled by the variables in section <tt>Linear Response::Solver</tt>,
148 !% and the iterations for OEP by <tt>Linear Response::SCF in LR calculations</tt> and variable
149 !% <tt>OEPMixing</tt>. Note that default for <tt>LRMaximumIter</tt> is set to 10.
150 !% Ref: S. Kuemmel and J. Perdew, <i>Phys. Rev. Lett.</i> <b>90</b>, 043004 (2003).
151 !%End
152 call messages_obsolete_variable(namespace, 'OEP_Level', 'OEPLevel')
153 call parse_variable(namespace, 'OEPLevel', oep_level_kli, oep%level)
154 if (.not. varinfo_valid_option('OEPLevel', oep%level)) call messages_input_error(namespace, 'OEPLevel')
155
156 if (oep%level == oep_level_none) then
157 pop_sub(xc_oep_init)
158 return
159 end if
160
161 oep%type = oep_type
162
163 if (oep%level == oep_level_full) then
164
165 if (st%d%nspin == spinors) then
166 call messages_not_implemented("Full OEP with spinors", namespace=namespace)
167 end if
168
169 call messages_experimental("Full OEP")
170
171 !%Variable OEPMixing
172 !%Type float
173 !%Default 1.0
174 !%Section Hamiltonian::XC
175 !%Description
176 !% The linear mixing factor used to solve the Sternheimer
177 !% equation in the full OEP procedure.
178 !%End
179 call messages_obsolete_variable(namespace, 'OEP_Mixing', 'OEPMixing')
180 call parse_variable(namespace, 'OEPMixing', m_one, oep%mixing)
181
182 !%Variable OEPMixingScheme
183 !%Type integer
184 !%Default oep_mixing_scheme_const
185 !%Section Hamiltonian::XC
186 !%Description
187 !% Different Mixing Schemes are possible
188 !%Option oep_mixing_scheme_const 1
189 !% Use a constant
190 !% Reference: S. Kuemmel and J. Perdew, <i>Phys. Rev. Lett.</i> <b>90</b>, 4, 043004 (2003)
191 !%Option oep_mixing_scheme_bb 2
192 !% Use the Barzilai-Borwein (BB) Method
193 !% Reference: T. W. Hollins, S. J. Clark, K. Refson, and N. I. Gidopoulos,
194 !% <i>Phys. Rev. B</i> <b>85</b>, 235126 (2012)
195 !%Option oep_mixing_scheme_dens 3
196 !% Use the inverse of the electron density
197 !% Reference: S. Kuemmel and J. Perdew, <i>Phys. Rev. B</i> <b>68</b>, 035103 (2003)
198 !%End
199 call parse_variable(namespace, 'OEPMixingScheme', oep_mixing_scheme_const, oep%mixing_scheme)
201 if (oep%mixing_scheme == oep_mixing_scheme_bb) then
202 safe_allocate(oep%vxc_old(1:gr%np,st%d%ispin))
203 safe_allocate(oep%ss_old(1:gr%np,st%d%ispin))
204 oep%vxc_old = m_zero
205 oep%ss_old = m_zero
206 end if
208 oep%norm2ss = m_zero
209 end if
211 ! obtain the spin factors
212 call xc_oep_spinfactor(oep, st%d%nspin)
213
214 ! This variable will keep vxc across iterations
215 if ((st%d%ispin == spinors) .or. oep%level == oep_level_full) then
216 safe_allocate(oep%vxc(1:gr%np,st%d%nspin))
217 else
218 safe_allocate(oep%vxc(1:gr%np,1:min(st%d%nspin, 2)))
219 end if
220 oep%vxc = m_zero
221
222 ! when performing full OEP, we need to solve a linear equation
223 if (oep%level == oep_level_full) then
224 call scf_tol_init(oep%scftol, namespace, st%qtot, def_maximumiter=10)
225 call linear_solver_init(oep%solver, namespace, gr, states_are_real(st), mc, space)
226 call lr_init(oep%lr)
227 end if
228
229 if (oep%type == oep_type_sic) then
230 !%Variable SCDMforPZSIC
231 !%Type logical
232 !%Default .false.
233 !%Section Hamiltonian::XC
234 !%Description
235 !% If set to .true., the code will use the SCDM method to Wannierize the orbitals before
236 !% computing the orbital-dependent SIC correction
237 !%End
238 call parse_variable(namespace, 'SCDMforPZSIC', .false., oep%scdm_for_pzsic)
239 if (oep%scdm_for_pzsic) call scdm_init(oep%scdm, namespace)
240 end if
241
242 ! the linear equation has to be more converged if we are to attain the required precision
243 !oep%lr%conv_abs_dens = oep%lr%conv_abs_dens / (oep%mixing)
244
245 if (st%d%nspin == spinors) then
246 call messages_experimental("OEP with spinors")
247 end if
248
249 if (st%d%kpt%parallel .and. oep%level == oep_level_full) then
250 call messages_experimental("OEP Full parallel in spin/k-points", namespace=namespace)
251 end if
252
253 if (st%d%kpt%parallel .and. oep%type == oep_type_sic) then
254 call messages_not_implemented("PZ-SIC with k-point parallelization")
255 end if
256
257 pop_sub(xc_oep_init)
258 end subroutine xc_oep_init
259
260
261 ! ---------------------------------------------------------
262 subroutine xc_oep_end(oep)
263 class(xc_oep_t), intent(inout) :: oep
264
265 push_sub(xc_oep_end)
266
267 if (oep%level /= oep_level_none) then
268 safe_deallocate_a(oep%vxc)
269 if (oep%level == oep_level_full .or. oep%type == oep_type_photons) then
270 call lr_dealloc(oep%lr)
271 call linear_solver_end(oep%solver)
272 end if
273 if (oep%level == oep_level_full .and. oep%mixing_scheme == oep_mixing_scheme_bb) then
274 safe_deallocate_a(oep%vxc_old)
275 safe_deallocate_a(oep%ss_old)
276 end if
277 end if
278
279 pop_sub(xc_oep_end)
280 end subroutine xc_oep_end
281
282
283 ! ---------------------------------------------------------
284 subroutine xc_oep_write_info(oep, iunit, namespace)
285 type(xc_oep_t), intent(in) :: oep
286 integer, optional, intent(in) :: iunit
287 type(namespace_t), optional, intent(in) :: namespace
288
289 if (oep%level == oep_level_none) return
290
291 push_sub(xc_oep_write_info)
292
293 call messages_print_var_option('OEPLevel', oep%level, iunit=iunit, namespace=namespace)
294
295 pop_sub(xc_oep_write_info)
296 end subroutine xc_oep_write_info
297
298
299 ! ---------------------------------------------------------
301 ! ---------------------------------------------------------
302 subroutine xc_oep_spinfactor(oep, nspin)
303 class(xc_oep_t), intent(inout) :: oep
304 integer, intent(in) :: nspin
305
306 push_sub(xc_oep_spinfactor)
307
308 select case (nspin)
309 case (1) ! we need to correct or the spin occupancies
310 oep%socc = m_half
311 oep%sfact = m_two
312 case (2, 4)
313 oep%socc = m_one
314 oep%sfact = m_one
315 case default ! cannot handle any other case
316 assert(.false.)
317 end select
318
319 pop_sub(xc_oep_spinfactor)
320 end subroutine xc_oep_spinfactor
321
322
323 ! ---------------------------------------------------------
324 subroutine xc_oep_analyzeeigen(oep, st, is)
325 class(xc_oep_t), intent(inout) :: oep
326 type(states_elec_t), intent(in) :: st
327 integer, intent(in) :: is
328
329 integer :: ist
330 real(real64) :: max_eigen
331
332 push_sub(xc_oep_analyzeeigen)
333
334 ! The arrays are reuse for different spins, we reset them
335 oep%eigen_type = -1
336 oep%eigen_index = -1
337 oep%noccst = 0
338 oep%eigen_n = 0
339
340 ! find out the top occupied state, to correct for the asymptotics
341 ! of the potential
342 max_eigen = -m_huge
343 do ist = 1, st%nst
344 if ((st%occ(ist, is) > m_min_occ).and.(st%eigenval(ist, is) > max_eigen)) then
345 max_eigen = st%eigenval(ist, is)
346 end if
347 end do
348
349 do ist = 1, st%nst
350 ! criterion for degeneracy
351 if (abs(st%eigenval(ist, is)-max_eigen) <= 1e-3_real64) then
352 oep%eigen_type(ist) = 2
353 else
354 if (st%occ(ist, is) > m_min_occ) then
355 oep%eigen_type(ist) = 1
356 oep%eigen_index(oep%eigen_n+1) = ist
357 oep%eigen_n = oep%eigen_n + 1
358 else
359 oep%eigen_type(ist) = 0
360 end if
361 end if
362 end do
363
364 ! find how many states are occupied.
365 do ist = 1, st%nst
366 if (st%occ(ist, is) > m_min_occ) oep%noccst = ist
367 end do
368
369 ! We check that all states have been assigned
370 assert(all(oep%eigen_type >= 0))
371
372 pop_sub(xc_oep_analyzeeigen)
373 end subroutine xc_oep_analyzeeigen
374
375
376#include "xc_kli_pauli_inc.F90"
377#include "xc_oep_sic_pauli_inc.F90"
378
379#include "undef.F90"
380#include "real.F90"
381#include "xc_kli_inc.F90"
382#include "xc_oep_sic_inc.F90"
383#include "xc_oep_inc.F90"
384
385#include "undef.F90"
386#include "complex.F90"
387#include "xc_kli_inc.F90"
388#include "xc_oep_sic_inc.F90"
389#include "xc_oep_inc.F90"
390
391end module xc_oep_oct_m
392
393!! Local Variables:
394!! mode: f90
395!! coding: utf-8
396!! End:
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
integer, parameter, public spinors
real(real64), parameter, public m_two
Definition: global.F90:189
real(real64), parameter, public m_huge
Definition: global.F90:205
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_half
Definition: global.F90:193
real(real64), parameter, public m_one
Definition: global.F90:188
real(real64), parameter, public m_min_occ
Minimal occupation that is considered to be non-zero.
Definition: global.F90:210
This module implements the underlying real-space grid.
Definition: grid.F90:117
subroutine, public lr_init(lr)
subroutine, public lr_dealloc(lr)
subroutine, public linear_solver_end(this)
subroutine, public linear_solver_init(this, namespace, gr, states_are_real, mc, space)
This module is intended to contain "only mathematical" functions and procedures.
Definition: math.F90:115
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
subroutine, public messages_not_implemented(feature, namespace)
Definition: messages.F90:1125
subroutine, public messages_obsolete_variable(namespace, name, rep)
Definition: messages.F90:1057
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:723
subroutine, public messages_experimental(name, namespace)
Definition: messages.F90:1097
This module handles the communicators for the various parallelization strategies.
Definition: multicomm.F90:145
This module provides routines for perform the Selected Column of Density Matrix (SCDM) method This fo...
Definition: scdm.F90:117
subroutine, public scdm_init(this, namespace)
Definition: scdm.F90:154
subroutine, public scf_tol_init(this, namespace, qtot, def_maximumiter, tol_scheme)
Definition: scf_tol.F90:160
pure logical function, public states_are_real(st)
This module handles spin dimensions of the states and the k-point distribution.
Definition: xc.F90:114
integer, parameter, public oep_type_mgga
Definition: xc_oep.F90:184
subroutine, public xc_oep_spinfactor(oep, nspin)
A couple of auxiliary functions for oep.
Definition: xc_oep.F90:396
subroutine, public xc_oep_end(oep)
Definition: xc_oep.F90:356
subroutine, public zxc_oep_calc(oep, namespace, xcs, gr, hm, st, space, rcell_volume, ex, ec, vxc)
This file handles the evaluation of the OEP potential, in the KLI or full OEP as described in S....
Definition: xc_oep.F90:2273
integer, parameter, public oep_type_photons
Definition: xc_oep.F90:184
subroutine, public xc_oep_analyzeeigen(oep, st, is)
Definition: xc_oep.F90:418
integer, parameter, public oep_mixing_scheme_dens
Definition: xc_oep.F90:178
subroutine, public dxc_oep_calc(oep, namespace, xcs, gr, hm, st, space, rcell_volume, ex, ec, vxc)
This file handles the evaluation of the OEP potential, in the KLI or full OEP as described in S....
Definition: xc_oep.F90:1436
integer, parameter, public oep_mixing_scheme_bb
Definition: xc_oep.F90:178
subroutine, public xc_oep_write_info(oep, iunit, namespace)
Definition: xc_oep.F90:378
subroutine, public dxc_oep_mix(oep, mesh, ss, rho, is)
A routine that takes care of mixing the potential.
Definition: xc_oep.F90:1766
integer, parameter, public oep_level_full
Definition: xc_oep.F90:172
subroutine, public xc_oep_init(oep, namespace, gr, st, mc, space, oep_type)
Definition: xc_oep.F90:217
subroutine, public zxc_oep_mix(oep, mesh, ss, rho, is)
A routine that takes care of mixing the potential.
Definition: xc_oep.F90:2603
integer, parameter, public oep_type_sic
Definition: xc_oep.F90:184
integer, parameter, public oep_level_kli
Definition: xc_oep.F90:172
The states_elec_t class contains all electronic wave functions.