25#include "./base/base_uses.f90"
31 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'outer_scf_control_types'
32 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .false.
64 LOGICAL :: have_scf = .false.
65 INTEGER :: max_scf = -1
66 REAL(kind=
dp) :: eps_scf = -1.0_dp, step_size = -1.0_dp
68 INTEGER :: optimizer = -1
69 INTEGER :: diis_buffer_length = -1
70 INTEGER :: extrapolation_order = -1
71 INTEGER :: bisect_trust_count = -1
76 INTEGER :: iter_count = -1
77 LOGICAL :: deallocate_jacobian = .false.
83 REAL(kind=
dp),
DIMENSION(:),
POINTER :: energy => null()
84 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: variables => null()
85 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: gradient => null()
86 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: inv_jacobian => null()
87 INTEGER,
DIMENSION(:),
POINTER :: count => null()
108 l_val=outer_scf%have_scf)
109 IF (outer_scf%have_scf)
THEN
111 r_val=outer_scf%eps_scf)
113 r_val=outer_scf%step_size, explicit=exists)
115 i_val=outer_scf%diis_buffer_length)
117 i_val=outer_scf%bisect_trust_count)
119 i_val=outer_scf%type)
121 i_val=outer_scf%max_scf)
123 i_val=outer_scf%extrapolation_order)
125 i_val=outer_scf%optimizer)
127 SELECT CASE (outer_scf%optimizer)
137 outer_scf%cdft_opt_control%newton_step = abs(outer_scf%step_size)
139 outer_scf%cdft_opt_control%newton_step_save = &
140 outer_scf%cdft_opt_control%newton_step
Defines the basic variable types.
integer, parameter, public dp
parameters that control the outer loop of an SCF iteration
subroutine, public outer_scf_read_parameters(outer_scf, outer_scf_section)
reads the parameters of the outer_scf section into the given outer_scf
Control parameters for optimizers that work with CDFT constraints.
subroutine, public cdft_opt_type_create(cdft_opt_control)
allocates and initializes the CDFT optimizer control object with default values
subroutine, public cdft_opt_type_read(cdft_opt_control, inp_section)
reads the parameters of the CDFT optimizer type
contains the parameters needed by a scf run
contains the parameters needed by CDFT specific optimizers