33 use,
intrinsic :: iso_fortran_env
79 integer,
public,
parameter :: &
85 integer,
public,
parameter :: &
86 OEP_MIXING_SCHEME_CONST = 1, &
91 integer,
public,
parameter :: &
98 integer,
public :: level
99 real(real64) :: mixing
100 integer :: mixing_scheme
102 type(linear_solver_t) :: solver
103 type(scf_tol_t) :: scftol
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(:,:)
115 logical :: scdm_for_pzsic
117 integer,
public ::
type = -1
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
156 if (oep%level == oep_level_none)
then
165 if (st%d%nspin ==
spinors)
then
199 call parse_variable(namespace,
'OEPMixingScheme', oep_mixing_scheme_const, oep%mixing_scheme)
202 safe_allocate(oep%vxc_old(1:gr%np,st%d%ispin))
203 safe_allocate(oep%ss_old(1:gr%np,st%d%ispin))
216 safe_allocate(oep%vxc(1:gr%np,st%d%nspin))
218 safe_allocate(oep%vxc(1:gr%np,1:min(st%d%nspin, 2)))
224 call scf_tol_init(oep%scftol, namespace, st%qtot, def_maximumiter=10)
238 call parse_variable(namespace,
'SCDMforPZSIC', .false., oep%scdm_for_pzsic)
239 if (oep%scdm_for_pzsic)
call scdm_init(oep%scdm, namespace)
245 if (st%d%nspin ==
spinors)
then
253 if (st%d%kpt%parallel .and. oep%type ==
oep_type_sic)
then
263 class(
xc_oep_t),
intent(inout) :: oep
267 if (oep%level /= oep_level_none)
then
268 safe_deallocate_a(oep%vxc)
274 safe_deallocate_a(oep%vxc_old)
275 safe_deallocate_a(oep%ss_old)
286 integer,
optional,
intent(in) :: iunit
287 type(
namespace_t),
optional,
intent(in) :: namespace
289 if (oep%level == oep_level_none)
return
303 class(
xc_oep_t),
intent(inout) :: oep
304 integer,
intent(in) :: nspin
325 class(
xc_oep_t),
intent(inout) :: oep
327 integer,
intent(in) :: is
330 real(real64) :: max_eigen
344 if ((st%occ(ist, is) >
m_min_occ).and.(st%eigenval(ist, is) > max_eigen))
then
345 max_eigen = st%eigenval(ist, is)
351 if (abs(st%eigenval(ist, is)-max_eigen) <= 1e-3_real64)
then
352 oep%eigen_type(ist) = 2
355 oep%eigen_type(ist) = 1
356 oep%eigen_index(oep%eigen_n+1) = ist
357 oep%eigen_n = oep%eigen_n + 1
359 oep%eigen_type(ist) = 0
366 if (st%occ(ist, is) >
m_min_occ) oep%noccst = ist
370 assert(all(oep%eigen_type >= 0))
376#include "xc_kli_pauli_inc.F90"
377#include "xc_oep_sic_pauli_inc.F90"
381#include "xc_kli_inc.F90"
382#include "xc_oep_sic_inc.F90"
383#include "xc_oep_inc.F90"
386#include "complex.F90"
387#include "xc_kli_inc.F90"
388#include "xc_oep_sic_inc.F90"
389#include "xc_oep_inc.F90"
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
integer, parameter, public spinors
real(real64), parameter, public m_two
real(real64), parameter, public m_huge
real(real64), parameter, public m_zero
real(real64), parameter, public m_half
real(real64), parameter, public m_one
real(real64), parameter, public m_min_occ
Minimal occupation that is considered to be non-zero.
This module implements the underlying real-space grid.
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.
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
subroutine, public messages_not_implemented(feature, namespace)
subroutine, public messages_obsolete_variable(namespace, name, rep)
subroutine, public messages_input_error(namespace, var, details, row, column)
subroutine, public messages_experimental(name, namespace)
This module handles the communicators for the various parallelization strategies.
This module provides routines for perform the Selected Column of Density Matrix (SCDM) method This fo...
subroutine, public scdm_init(this, namespace)
subroutine, public scf_tol_init(this, namespace, qtot, def_maximumiter, tol_scheme)
pure logical function, public states_are_real(st)
This module handles spin dimensions of the states and the k-point distribution.
integer, parameter, public oep_type_mgga
subroutine, public xc_oep_spinfactor(oep, nspin)
A couple of auxiliary functions for oep.
subroutine, public xc_oep_end(oep)
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....
integer, parameter, public oep_type_photons
subroutine, public xc_oep_analyzeeigen(oep, st, is)
integer, parameter, public oep_mixing_scheme_dens
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....
integer, parameter, public oep_mixing_scheme_bb
subroutine, public xc_oep_write_info(oep, iunit, namespace)
subroutine, public dxc_oep_mix(oep, mesh, ss, rho, is)
A routine that takes care of mixing the potential.
integer, parameter, public oep_level_full
subroutine, public xc_oep_init(oep, namespace, gr, st, mc, space, oep_type)
subroutine, public zxc_oep_mix(oep, mesh, ss, rho, is)
A routine that takes care of mixing the potential.
integer, parameter, public oep_type_sic
integer, parameter, public oep_level_kli
The states_elec_t class contains all electronic wave functions.