(git:ccc2433)
outer_scf_control_types.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
9 !> \brief parameters that control the outer loop of an SCF iteration
10 !> \par History
11 !> 09.2018 created by moving outer SCF types to separate module [Nico Holmberg]
12 !> \author Nico Holmberg
13 ! **************************************************************************************************
15 
19  USE input_section_types, ONLY: section_vals_type,&
21  USE kinds, ONLY: dp
22  USE qs_cdft_opt_types, ONLY: cdft_opt_type,&
25 #include "./base/base_uses.f90"
26 
27  IMPLICIT NONE
28 
29  PRIVATE
30 
31  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'outer_scf_control_types'
32  LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .false.
33 
34  ! Public data types
35 
36  PUBLIC :: outer_scf_control_type, &
37  qs_outer_scf_type
38 
39  ! Public subroutines
40 
42 
43 ! **************************************************************************************************
44 !> \brief contains the parameters needed by a scf run
45 !> \param density_guess how to choose the initial density
46 !> (CORE,RANDOM,RESTART,ATOMIC,FROZEN)
47 !> \param eps_eigval wanted error on the eigenvalues
48 !> \param eps_scf whanted error on the whole scf
49 !> \param level_shift amount of level shift
50 !> \param p_mix how to mix the new and old densities in non diss iterations
51 !> \param eps_lumos error on the lumos calculated at the end of the scf
52 !> \param max_iter_lumus maxumum number of iterations used to calculate
53 !> the lumos at the end of the scf
54 !> \param max_scf max scf iterations
55 !> \param added_mos additional number of MOs that might be used in the SCF
56 !> \param step_size the optimizer step size
57 !> \param cdft_opt_control settings for optimizers that work only together with CDFT constraints
58 !> \par History
59 !> 09.2002 created [fawzi]
60 !> \author Fawzi Mohamed
61 ! **************************************************************************************************
62 
63  TYPE outer_scf_control_type
64  LOGICAL :: have_scf
65  INTEGER :: max_scf
66  REAL(KIND=dp) :: eps_scf, step_size
67  INTEGER :: TYPE
68  INTEGER :: optimizer
69  INTEGER :: diis_buffer_length
70  INTEGER :: extrapolation_order
71  INTEGER :: bisect_trust_count
72  TYPE(cdft_opt_type), POINTER :: cdft_opt_control
73  END TYPE outer_scf_control_type
74 
75  TYPE qs_outer_scf_type
76  INTEGER :: iter_count
77  LOGICAL :: deallocate_jacobian
78  ! these are the variable of outer loop.
79  ! right now, we assume that they can be easily written as
80  ! small arrays, but we might want to go the cp_fm_types
81  ! at a later stage
82  ! also, we just store the full iteration history
83  REAL(KIND=dp), DIMENSION(:), POINTER :: energy
84  REAL(KIND=dp), DIMENSION(:, :), POINTER :: variables
85  REAL(KIND=dp), DIMENSION(:, :), POINTER :: gradient
86  REAL(KIND=dp), DIMENSION(:, :), POINTER :: inv_jacobian
87  INTEGER, DIMENSION(:), POINTER :: count
88  END TYPE qs_outer_scf_type
89 
90 CONTAINS
91 
92 ! **************************************************************************************************
93 !> \brief reads the parameters of the outer_scf section into the given outer_scf
94 !> \param outer_scf the object that wil contain the values read
95 !> \param outer_scf_section the input section
96 !> \par History
97 !> 09.2018 created by separating from scf_c_read_parameters [Nico Holmberg]
98 !> \author Nico Holmberg
99 ! **************************************************************************************************
100  SUBROUTINE outer_scf_read_parameters(outer_scf, outer_scf_section)
101 
102  TYPE(outer_scf_control_type) :: outer_scf
103  TYPE(section_vals_type), POINTER :: outer_scf_section
104 
105  LOGICAL :: exists
106 
107  CALL section_vals_val_get(outer_scf_section, "_SECTION_PARAMETERS_", &
108  l_val=outer_scf%have_scf)
109  IF (outer_scf%have_scf) THEN
110  CALL section_vals_val_get(outer_scf_section, "EPS_SCF", &
111  r_val=outer_scf%eps_scf)
112  CALL section_vals_val_get(outer_scf_section, "STEP_SIZE", &
113  r_val=outer_scf%step_size, explicit=exists)
114  CALL section_vals_val_get(outer_scf_section, "DIIS_BUFFER_LENGTH", &
115  i_val=outer_scf%diis_buffer_length)
116  CALL section_vals_val_get(outer_scf_section, "BISECT_TRUST_COUNT", &
117  i_val=outer_scf%bisect_trust_count)
118  CALL section_vals_val_get(outer_scf_section, "TYPE", &
119  i_val=outer_scf%type)
120  CALL section_vals_val_get(outer_scf_section, "MAX_SCF", &
121  i_val=outer_scf%max_scf)
122  CALL section_vals_val_get(outer_scf_section, "EXTRAPOLATION_ORDER", &
123  i_val=outer_scf%extrapolation_order)
124  CALL section_vals_val_get(outer_scf_section, "OPTIMIZER", &
125  i_val=outer_scf%optimizer)
126  ! Optimizer specific initializations
127  SELECT CASE (outer_scf%optimizer)
128  CASE DEFAULT
129  ! Do nothing
132  ! CDFT optimizer -> read CDFT_OPT section
133  CALL cdft_opt_type_create(outer_scf%cdft_opt_control)
134  CALL cdft_opt_type_read(outer_scf%cdft_opt_control, &
135  outer_scf_section)
136  IF (exists) THEN
137  outer_scf%cdft_opt_control%newton_step = abs(outer_scf%step_size)
138  ! Permanent copy needed in case line search is performed
139  outer_scf%cdft_opt_control%newton_step_save = &
140  outer_scf%cdft_opt_control%newton_step
141  END IF
142  END SELECT
143  END IF
144 
145  END SUBROUTINE outer_scf_read_parameters
146 
147 END MODULE outer_scf_control_types
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public outer_scf_optimizer_broyden
integer, parameter, public outer_scf_optimizer_newton_ls
integer, parameter, public outer_scf_optimizer_newton
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
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