(git:419edc0)
Loading...
Searching...
No Matches
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-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief parameters that control an scf iteration
10!> \note
11!> not in cp_control_types, to separate operator related parameters from
12!> method related parameters (as suggested by Matthias)
13!> \par History
14!> 09.2002 created [fawzi]
15!> \author Fawzi Mohamed
16! **************************************************************************************************
18
24 USE input_constants, ONLY: &
44 USE kinds, ONLY: dp
51#include "./base/base_uses.f90"
52
53 IMPLICIT NONE
54
55 PRIVATE
56
57 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'scf_control_types'
58 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
59
60 ! Public data types
61
62 PUBLIC :: scf_control_type, &
64
65 ! Public subroutines
66
67 PUBLIC :: scf_c_create, &
71
72! **************************************************************************************************
73!> \brief contains the parameters needed by a scf run
74!> \param density_guess how to choose the initial density
75!> (CORE,RANDOM,RESTART,ATOMIC,FROZEN)
76!> \param eps_eigval wanted error on the eigenvalues
77!> \param eps_scf whanted error on the whole scf
78!> \param level_shift amount of level shift
79!> \param p_mix how to mix the new and old densities in non diss iterations
80!> \param eps_lumos error on the lumos calculated at the end of the scf
81!> \param max_iter_lumus maxumum number of iterations used to calculate
82!> the lumos at the end of the scf
83!> \param max_scf max scf iterations
84!> \param added_mos additional number of MOs that might be used in the SCF
85!> \param step_size the optimizer step size
86!> \param cdft_opt_control settings for optimizers that work only together with CDFT constraints
87!> \par History
88!> 09.2002 created [fawzi]
89!> \author Fawzi Mohamed
90! **************************************************************************************************
92 LOGICAL :: do_smear = .false.
93 LOGICAL :: common_mu = .false.
94 INTEGER :: method = -1
95 REAL(kind=dp) :: electronic_temperature = -1.0_dp, &
96 fixed_mag_mom = -1.0_dp, &
97 eps_fermi_dirac = -1.0_dp, &
98 window_size = -1.0_dp
99 REAL(kind=dp), DIMENSION(:), POINTER :: list => null()
100 END TYPE smear_type
101
102 TYPE diagonalization_type
103 INTEGER :: method = -1
104 REAL(kind=dp) :: eps_jacobi = -1.0_dp
105 REAL(kind=dp) :: jacobi_threshold = -1.0_dp
106 INTEGER :: max_iter = -1, nkrylov = -1, nblock_krylov = -1
107 ! Maximum Overlap Method
108 LOGICAL :: mom = .false., mom_didguess = .false.
109 INTEGER :: mom_proj_formula = -1
110 ! indices of de-occupied and newly occupied alpha / beta molecular orbitals
111 INTEGER, DIMENSION(:), POINTER :: mom_deocca => null(), mom_deoccb => null(), &
112 mom_occa => null(), mom_occb => null()
113 ! determines on SCF which iteration MOM will be switched on;
114 ! since MOs from the previous iteration should be available, it might be at least
115 ! 1 when wave-function has been read from restart file, or
116 ! 2 when the atomic guess method has been used
117 INTEGER :: mom_start = -1
118 INTEGER :: mom_type = -1
119 REAL(kind=dp) :: eps_iter = -1.0_dp
120 REAL(kind=dp) :: eps_adapt = -1.0_dp
121 TYPE(qs_ot_settings_type) :: ot_settings = qs_ot_settings_type()
122 END TYPE diagonalization_type
123
126 TYPE(smear_type), POINTER :: smear => null()
127 TYPE(diagonalization_type) :: diagonalization = diagonalization_type()
128 INTEGER :: density_guess = -1, mixing_method = -1
129 REAL(kind=dp) :: eps_eigval = -1.0_dp, eps_scf = -1.0_dp, eps_scf_hist = -1.0_dp, &
130 level_shift = -1.0_dp, &
131 eps_lumos = -1.0_dp, eps_diis = -1.0_dp
132 INTEGER :: max_iter_lumos = -1, max_diis = -1, nmixing = -1
133 INTEGER :: max_scf = -1, max_scf_hist = -1, &
134 maxl = -1, nkind = -1
135 LOGICAL :: do_diag_sub = .false., &
136 use_cholesky = .false., use_ot = .false., &
137 use_diag = .false., do_outer_scf_reortho = .false., &
138 ignore_convergence_failure = .false.
139 LOGICAL :: force_scf_calculation = .false.
140 LOGICAL :: non_selfconsistent = .false.
141 INTEGER, DIMENSION(2) :: added_mos = -1
142 INTEGER :: roks_scheme = -1
143 REAL(kind=dp) :: roks_f = -1.0_dp
144 REAL(kind=dp), DIMENSION(0:2, 0:2, 1:2) :: roks_parameter = -1.0_dp
145 END TYPE scf_control_type
146
147CONTAINS
148
149! **************************************************************************************************
150!> \brief allocates and initializes an scf control object with the default values
151!> \param scf_control the object to initialize
152!> \par History
153!> 09.2002 created [fawzi]
154!> - Default ROKS parameters added (05.04.06,MK)
155!> \author Fawzi Mohamed
156! **************************************************************************************************
157 SUBROUTINE scf_c_create(scf_control)
158
159 TYPE(scf_control_type), INTENT(INOUT) :: scf_control
160
161 CHARACTER(LEN=*), PARAMETER :: routinen = 'scf_c_create'
162
163 INTEGER :: handle
164
165 CALL timeset(routinen, handle)
166
167 ! Load the default values
168
169 IF (scf_control%non_selfconsistent) THEN
170 scf_control%density_guess = no_guess
171 ELSE
172 scf_control%density_guess = atomic_guess
173 END IF
174 scf_control%eps_eigval = 1.0e-5_dp
175 scf_control%eps_scf = 1.0e-5_dp
176 scf_control%eps_scf_hist = 0.0_dp
177 scf_control%eps_lumos = 1.0e-5_dp
178 scf_control%max_iter_lumos = 2999
179 scf_control%eps_diis = 0.1_dp
180 scf_control%level_shift = 0.0_dp
181 scf_control%max_diis = 4
182 scf_control%max_scf = 50
183 scf_control%nmixing = 2
184 scf_control%use_cholesky = .true.
185 scf_control%use_diag = .true.
186 scf_control%do_diag_sub = .false.
187 scf_control%use_ot = .false.
188 scf_control%ignore_convergence_failure = .false.
189 scf_control%force_scf_calculation = .false.
190 scf_control%do_outer_scf_reortho = .true.
191 scf_control%max_diis = 4
192 scf_control%eps_diis = 0.1_dp
193 scf_control%added_mos(:) = 0
194 scf_control%max_scf_hist = 0
195
196 !Mixing
197 IF (scf_control%non_selfconsistent) THEN
198 scf_control%mixing_method = no_mix
199 ELSE
200 scf_control%mixing_method = direct_p_mix
201 END IF
202
203 ! Diagonalization
204 scf_control%diagonalization%method = 0
205 scf_control%diagonalization%eps_jacobi = 0.0_dp
206 scf_control%diagonalization%jacobi_threshold = 1.0e-7_dp
207 scf_control%diagonalization%max_iter = 0
208 scf_control%diagonalization%eps_iter = 0.0_dp
209 scf_control%diagonalization%eps_adapt = 0.0_dp
210 scf_control%diagonalization%nkrylov = 0
211 scf_control%diagonalization%nblock_krylov = 0
212 CALL qs_ot_settings_init(scf_control%diagonalization%ot_settings)
213
214 scf_control%diagonalization%mom = .false.
215 scf_control%diagonalization%mom_didguess = .false.
216 scf_control%diagonalization%mom_proj_formula = 0
217 NULLIFY (scf_control%diagonalization%mom_deoccA)
218 NULLIFY (scf_control%diagonalization%mom_deoccB)
219 NULLIFY (scf_control%diagonalization%mom_occA)
220 NULLIFY (scf_control%diagonalization%mom_occB)
221 scf_control%diagonalization%mom_start = 0
222
223 ! ROKS
224
225 scf_control%roks_scheme = high_spin_roks
226 scf_control%roks_f = 0.5_dp
227
228 ! Initialize the diagonal blocks with the default ROKS parameters
229 ! 0 = v)irtual, 1 = o)pen shell, 2 = c)losed shell
230
231 scf_control%roks_parameter(0, 0, 1) = 1.5_dp ! avv
232 scf_control%roks_parameter(0, 0, 2) = -0.5_dp ! bvv
233 scf_control%roks_parameter(1, 1, 1) = 0.5_dp ! aoo
234 scf_control%roks_parameter(1, 1, 2) = 0.5_dp ! boo
235 scf_control%roks_parameter(2, 2, 1) = -0.5_dp ! acc
236 scf_control%roks_parameter(2, 2, 2) = 1.5_dp ! bcc
237
238 ! Initialize off-diagonal blocks (fixed)
239
240 scf_control%roks_parameter(0, 1, 1) = 1.0_dp ! avo
241 scf_control%roks_parameter(0, 1, 2) = 0.0_dp ! bvo
242 scf_control%roks_parameter(0, 2, 1) = 0.5_dp ! avc
243 scf_control%roks_parameter(0, 2, 2) = 0.5_dp ! bvc
244 scf_control%roks_parameter(1, 2, 1) = 0.0_dp ! aoc
245 scf_control%roks_parameter(1, 2, 2) = 1.0_dp ! boc
246
247 ! Symmetry enforces
248
249 scf_control%roks_parameter(1, 0, 1) = scf_control%roks_parameter(0, 1, 1) ! aov
250 scf_control%roks_parameter(1, 0, 2) = scf_control%roks_parameter(0, 1, 2) ! bov
251 scf_control%roks_parameter(2, 0, 1) = scf_control%roks_parameter(0, 2, 1) ! acv
252 scf_control%roks_parameter(2, 0, 2) = scf_control%roks_parameter(0, 2, 2) ! bcv
253 scf_control%roks_parameter(2, 1, 1) = scf_control%roks_parameter(1, 2, 1) ! aco
254 scf_control%roks_parameter(2, 1, 2) = scf_control%roks_parameter(1, 2, 2) ! bco
255
256 ! Outer SCF default settings
257
258 scf_control%outer_scf%have_scf = .false.
259 scf_control%outer_scf%max_scf = 0
260 scf_control%outer_scf%eps_scf = 0.0_dp
261 scf_control%outer_scf%step_size = 0.0_dp
262 scf_control%outer_scf%type = -1
263 scf_control%outer_scf%optimizer = -1
264 scf_control%outer_scf%diis_buffer_length = -1
265 NULLIFY (scf_control%outer_scf%cdft_opt_control)
266
267 ! Smearing of the MO occupations
268
269 NULLIFY (scf_control%smear)
270
271 CALL timestop(handle)
272
273 END SUBROUTINE scf_c_create
274
275! **************************************************************************************************
276!> \brief releases the given scf_control (see cp2k/doc/ReferenceCounting.html)
277!> \param scf_control the object to free
278!> \par History
279!> 09.2002 created [fawzi]
280!> \author Fawzi Mohamed
281!> \note
282!> at the moment does nothing
283! **************************************************************************************************
284 SUBROUTINE scf_c_release(scf_control)
285
286 TYPE(scf_control_type), INTENT(INOUT) :: scf_control
287
288 IF (ASSOCIATED(scf_control%smear%list)) THEN
289 DEALLOCATE (scf_control%smear%list)
290 END IF
291 DEALLOCATE (scf_control%smear)
292
293 IF (ASSOCIATED(scf_control%outer_scf%cdft_opt_control)) &
294 CALL cdft_opt_type_release(scf_control%outer_scf%cdft_opt_control)
295
296 ! Maximum overlap method orbital indices lists
297 ! mom_deoccA, mom_deoccB, mom_occA, mom_occB
298 ! points to memory allocated by input file parser,
299 ! so they do not have to be deallocated
300
301 END SUBROUTINE scf_c_release
302
303! **************************************************************************************************
304!> \brief reads the parameters of the scf section into the given scf_control
305!> \param scf_control the object that wil contain the values read
306!> \param inp_section ...
307!> \par History
308!> 05.2001 created [Matthias]
309!> 09.2002 creaded separated scf_control type [fawzi]
310!> \author Matthias Krack
311! **************************************************************************************************
312 SUBROUTINE scf_c_read_parameters(scf_control, inp_section)
313
314 TYPE(scf_control_type), INTENT(INOUT) :: scf_control
315 TYPE(section_vals_type), POINTER :: inp_section
316
317 CHARACTER(LEN=*), PARAMETER :: routinen = 'scf_c_read_parameters'
318
319 INTEGER :: cholesky_flag, handle, ialgo
320 INTEGER, DIMENSION(:), POINTER :: added_mos
321 LOGICAL :: do_mixing, explicit
322 REAL(kind=dp), DIMENSION(:), POINTER :: roks_parameter
323 TYPE(section_vals_type), POINTER :: mixing_section, outer_scf_section, &
324 scf_section, smear_section
325
326 CALL timeset(routinen, handle)
327
328 scf_section => section_vals_get_subs_vals(inp_section, "SCF")
329 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%_SECTION_PARAMETERS_", &
330 l_val=scf_control%use_diag)
331 IF (scf_control%use_diag) THEN
332 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DIAG_SUB_SCF%_SECTION_PARAMETERS_", &
333 l_val=scf_control%do_diag_sub)
334 END IF
335 CALL section_vals_val_get(scf_section, "OT%_SECTION_PARAMETERS_", l_val=scf_control%use_ot)
336 IF (scf_control%use_diag .AND. scf_control%use_ot) THEN
337 ! don't allow both options to be true
338 cpabort("Don't activate OT and Diagonaliztion together")
339 ELSEIF (.NOT. (scf_control%use_diag .OR. scf_control%use_ot)) THEN
340 ! set default to diagonalization
341 scf_control%use_diag = .true.
342 END IF
343 CALL section_vals_val_get(scf_section, "OT%ALGORITHM", i_val=ialgo)
344 scf_control%do_outer_scf_reortho = ialgo .EQ. ot_algo_taylor_or_diag
345 CALL section_vals_val_get(scf_section, "SCF_GUESS", i_val=scf_control%density_guess)
346 CALL section_vals_val_get(scf_section, "eps_eigval", r_val=scf_control%eps_eigval)
347 CALL section_vals_val_get(scf_section, "cholesky", i_val=cholesky_flag)
348 IF (scf_control%use_ot) THEN
349 ! eps_diis default is 0 for OT
350 scf_control%eps_diis = 0.0_dp
351 CALL section_vals_val_get(scf_section, "EPS_DIIS", explicit=explicit)
352 IF (explicit) THEN
353 CALL section_vals_val_get(scf_section, "EPS_DIIS", r_val=scf_control%eps_diis)
354 END IF
355 ELSE
356 CALL section_vals_val_get(scf_section, "EPS_DIIS", r_val=scf_control%eps_diis)
357 END IF
358 IF (cholesky_flag > 0) THEN
359 scf_control%use_cholesky = .true.
360 END IF
361 CALL section_vals_val_get(scf_section, "IGNORE_CONVERGENCE_FAILURE", l_val=scf_control%ignore_convergence_failure)
362 CALL section_vals_val_get(scf_section, "FORCE_SCF_CALCULATION", l_val=scf_control%force_scf_calculation)
363 CALL section_vals_val_get(scf_section, "eps_scf", r_val=scf_control%eps_scf)
364 CALL section_vals_val_get(scf_section, "level_shift", r_val=scf_control%level_shift)
365 CALL section_vals_val_get(scf_section, "max_diis", i_val=scf_control%max_diis)
366 CALL section_vals_val_get(scf_section, "max_scf", i_val=scf_control%max_scf)
367
368 ! Diagonaliztion section
369 IF (scf_control%use_diag) THEN
370 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%ALGORITHM", &
371 i_val=scf_control%diagonalization%method)
372 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%EPS_JACOBI", &
373 r_val=scf_control%diagonalization%eps_jacobi)
374 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%JACOBI_THRESHOLD", &
375 r_val=scf_control%diagonalization%jacobi_threshold)
376 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%MAX_ITER", &
377 i_val=scf_control%diagonalization%max_iter)
378 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%EPS_ITER", &
379 r_val=scf_control%diagonalization%eps_iter)
380 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%EPS_ADAPT", &
381 r_val=scf_control%diagonalization%eps_adapt)
382 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%KRYLOV%NKRYLOV", &
383 i_val=scf_control%diagonalization%nkrylov)
384 CALL section_vals_val_get(scf_section, "DIAGONALIZATION%KRYLOV%NBLOCK", &
385 i_val=scf_control%diagonalization%nblock_krylov)
386 IF (scf_control%diagonalization%method == diag_ot) THEN
387 ! read OT section
388 CALL ot_diag_read_input(scf_control%diagonalization%ot_settings, scf_section)
389 END IF
390 ! read maximum overlap method's parameters
391 CALL section_vals_val_get(scf_section, "MOM%_SECTION_PARAMETERS_", &
392 l_val=scf_control%diagonalization%MOM)
393 IF (scf_control%diagonalization%mom) THEN
394 CALL section_vals_val_get(scf_section, "MOM%MOM_TYPE", &
395 i_val=scf_control%diagonalization%mom_type)
396
397 CALL section_vals_val_get(scf_section, "MOM%START_ITER", &
398 i_val=scf_control%diagonalization%mom_start)
399
400 CALL section_vals_val_get(scf_section, "MOM%DEOCC_ALPHA", &
401 i_vals=scf_control%diagonalization%mom_deoccA)
402
403 CALL section_vals_val_get(scf_section, "MOM%DEOCC_BETA", &
404 i_vals=scf_control%diagonalization%mom_deoccB)
405
406 CALL section_vals_val_get(scf_section, "MOM%OCC_ALPHA", &
407 i_vals=scf_control%diagonalization%mom_occA)
408
409 CALL section_vals_val_get(scf_section, "MOM%OCC_BETA", &
410 i_vals=scf_control%diagonalization%mom_occB)
411
412 CALL section_vals_val_get(scf_section, "MOM%PROJ_FORMULA", &
413 i_val=scf_control%diagonalization%mom_proj_formula)
414 END IF
415 END IF
416
417 ! Read ROKS parameters
418 CALL section_vals_val_get(scf_section, "ROKS_SCHEME", i_val=scf_control%roks_scheme)
419
420 SELECT CASE (scf_control%roks_scheme)
421 CASE (general_roks)
422 ! Read parameters for the general ROKS scheme
423 CALL section_vals_val_get(scf_section, "ROKS_F", r_val=scf_control%roks_f)
424 CASE (high_spin_roks)
425 ! Read high-spin ROKS parameters for the diagonal block
426 ! 0 = v)irtual, 1 = o)pen shell, 2 = c)losed shell
427 NULLIFY (roks_parameter)
428 CALL section_vals_val_get(scf_section, "ROKS_PARAMETERS", r_vals=roks_parameter)
429 IF (ASSOCIATED(roks_parameter)) THEN
430 scf_control%roks_parameter(2, 2, 1) = roks_parameter(1) ! acc
431 scf_control%roks_parameter(2, 2, 2) = roks_parameter(2) ! bcc
432 scf_control%roks_parameter(1, 1, 1) = roks_parameter(3) ! aoo
433 scf_control%roks_parameter(1, 1, 2) = roks_parameter(4) ! boo
434 scf_control%roks_parameter(0, 0, 1) = roks_parameter(5) ! avv
435 scf_control%roks_parameter(0, 0, 2) = roks_parameter(6) ! bvv
436 END IF
437 END SELECT
438
439 ! should be moved to printkey
440 CALL section_vals_val_get(scf_section, "eps_lumo", r_val=scf_control%eps_lumos)
441 CALL section_vals_val_get(scf_section, "max_iter_lumo", i_val=scf_control%max_iter_lumos)
442
443 ! Extra MOs, e.g. for smearing
444 CALL section_vals_val_get(scf_section, "added_mos", i_vals=added_mos)
445 cpassert(ASSOCIATED(added_mos))
446 IF (SIZE(added_mos) > 0) THEN
447 scf_control%added_mos(1) = added_mos(1)
448 IF (SIZE(added_mos) > 1) THEN
449 scf_control%added_mos(2) = added_mos(2)
450 END IF
451 END IF
452
453 CALL section_vals_val_get(scf_section, "max_scf_history", i_val=scf_control%max_scf_hist)
454 CALL section_vals_val_get(scf_section, "eps_scf_history", r_val=scf_control%eps_scf_hist)
455
456 IF (scf_control%level_shift /= 0.0_dp) scf_control%use_cholesky = .false.
457
458 ! Outer SCF subsection
459 outer_scf_section => section_vals_get_subs_vals(scf_section, "OUTER_SCF")
460 CALL outer_scf_read_parameters(scf_control%outer_scf, outer_scf_section)
461
462 smear_section => section_vals_get_subs_vals(scf_section, "SMEAR")
463 CALL init_smear(scf_control%smear)
464 CALL read_smear_section(scf_control%smear, smear_section)
465
466 do_mixing = .false.
467 mixing_section => section_vals_get_subs_vals(scf_section, "MIXING")
468 CALL section_vals_val_get(mixing_section, "_SECTION_PARAMETERS_", &
469 l_val=do_mixing)
470 IF (do_mixing) THEN
471 CALL section_vals_val_get(mixing_section, "METHOD", &
472 i_val=scf_control%mixing_method)
473 CALL section_vals_val_get(mixing_section, "NMIXING", i_val=scf_control%nmixing)
474 END IF ! do mixing
475
476 CALL timestop(handle)
477
478 END SUBROUTINE scf_c_read_parameters
479
480! **************************************************************************************************
481!> \brief ...
482!> \param smear ...
483! **************************************************************************************************
484 SUBROUTINE init_smear(smear)
485 TYPE(smear_type), POINTER :: smear
486
487 cpassert(.NOT. ASSOCIATED(smear))
488 ALLOCATE (smear)
489 smear%do_smear = .false.
490 smear%method = smear_energy_window
491 smear%electronic_temperature = 0.0_dp
492 smear%eps_fermi_dirac = 1.0e-5_dp
493 smear%fixed_mag_mom = -100.0_dp
494 smear%window_size = 0.0_dp
495 NULLIFY (smear%list)
496 END SUBROUTINE init_smear
497
498! **************************************************************************************************
499!> \brief ...
500!> \param smear ...
501!> \param smear_section ...
502! **************************************************************************************************
503 SUBROUTINE read_smear_section(smear, smear_section)
504 TYPE(smear_type), POINTER :: smear
505 TYPE(section_vals_type), POINTER :: smear_section
506
507 REAL(kind=dp), DIMENSION(:), POINTER :: r_vals
508
509 NULLIFY (r_vals)
510
511 CALL section_vals_val_get(smear_section, "_SECTION_PARAMETERS_", &
512 l_val=smear%do_smear)
513 IF (smear%do_smear) THEN
514 CALL section_vals_val_get(smear_section, "METHOD", &
515 i_val=smear%method)
516 CALL section_vals_val_get(smear_section, "ELECTRONIC_TEMPERATURE", &
517 r_val=smear%electronic_temperature)
518 CALL section_vals_val_get(smear_section, "EPS_FERMI_DIRAC", &
519 r_val=smear%eps_fermi_dirac)
520 CALL section_vals_val_get(smear_section, "WINDOW_SIZE", &
521 r_val=smear%window_size)
522 IF (smear%method == smear_list) THEN
523 CALL section_vals_val_get(smear_section, "LIST", &
524 r_vals=r_vals)
525 cpassert(ASSOCIATED(r_vals))
526 ALLOCATE (smear%list(SIZE(r_vals)))
527 smear%list = r_vals
528 END IF
529 CALL section_vals_val_get(smear_section, "FIXED_MAGNETIC_MOMENT", &
530 r_val=smear%fixed_mag_mom)
531 END IF ! do smear
532 END SUBROUTINE read_smear_section
533
534! **************************************************************************************************
535!> \brief writes out the scf parameters
536!> \param scf_control the object you want to print
537!> \param dft_section ...
538!> \par History
539!> 05.2001 created [Matthias]
540!> 09.2002 created separated scf_control type [fawzi]
541!> \author Matthias Krack
542! **************************************************************************************************
543 SUBROUTINE scf_c_write_parameters(scf_control, dft_section)
544
545 TYPE(scf_control_type), INTENT(IN) :: scf_control
546 TYPE(section_vals_type), POINTER :: dft_section
547
548 CHARACTER(LEN=*), PARAMETER :: routinen = 'scf_c_write_parameters'
549
550 INTEGER :: handle, output_unit, roks_scheme
551 LOGICAL :: roks
552 REAL(kind=dp) :: elec_temp
553 TYPE(cp_logger_type), POINTER :: logger
554 TYPE(enumeration_type), POINTER :: enum
555 TYPE(keyword_type), POINTER :: keyword
556 TYPE(section_type), POINTER :: section
557 TYPE(section_vals_type), POINTER :: scf_section
558
559 CALL timeset(routinen, handle)
560
561 NULLIFY (logger)
562 logger => cp_get_default_logger()
563
564 NULLIFY (scf_section)
565 NULLIFY (section)
566
567 scf_section => section_vals_get_subs_vals(dft_section, "SCF")
568 output_unit = cp_print_key_unit_nr(logger, scf_section, "PRINT%PROGRAM_RUN_INFO", &
569 extension=".scfLog")
570
571 IF (output_unit > 0) THEN
572
573 IF (scf_control%max_scf > 0) THEN
574
575 CALL create_scf_section(section)
576
577 keyword => section_get_keyword(section, "SCF_GUESS")
578 CALL keyword_get(keyword, enum=enum)
579
580 IF (.NOT. scf_control%non_selfconsistent .OR. scf_control%force_scf_calculation) THEN
581 WRITE (unit=output_unit, &
582 fmt="(/,/,T2,A,T25,A,T51,A30,/,T25,56('-'),3(/,T25,A,T76,I5),/, "// &
583 "T25,56('-'),4(/,T25,A,T72,ES9.2),/,T25,56('-'), "// &
584 "1(/,T25,A,T71,F10.6))") &
585 "SCF PARAMETERS", &
586 "Density guess: ", adjustr(trim(enum_i2c(enum, scf_control%density_guess))), &
587 "max_scf: ", scf_control%max_scf, &
588 "max_scf_history: ", scf_control%max_scf_hist, &
589 "max_diis: ", scf_control%max_diis, &
590 "eps_scf: ", scf_control%eps_scf, &
591 "eps_scf_history: ", scf_control%eps_scf_hist, &
592 "eps_diis: ", scf_control%eps_diis, &
593 "eps_eigval: ", scf_control%eps_eigval, &
594 "level_shift [a.u.]:", scf_control%level_shift
595 END IF
596
597 IF (sum(abs(scf_control%added_mos)) > 0) THEN
598 WRITE (unit=output_unit, fmt="(T25,A,T71,2I5)") &
599 "added MOs ", scf_control%added_mos
600 END IF
601
602 IF (scf_control%diagonalization%mom) THEN
603 ! TODO extend the output with further parameters
604 WRITE (unit=output_unit, fmt="(T25,A)") "MOM enabled"
605 END IF
606
607 IF (scf_control%mixing_method > 0 .AND. .NOT. scf_control%use_ot .AND. &
608 .NOT. scf_control%non_selfconsistent) THEN
609 keyword => section_get_keyword(section, "MIXING%METHOD")
610 CALL keyword_get(keyword, enum=enum)
611 WRITE (unit=output_unit, fmt="(T25,A,/,T25,A,T51,A30)") &
612 repeat("-", 56), &
613 "Mixing method: ", adjustr(trim(enum_i2c(enum, scf_control%mixing_method)))
614 IF (scf_control%mixing_method > 1) THEN
615 WRITE (unit=output_unit, fmt="(T47,A34)") "charge density mixing in g-space"
616 END IF
617 END IF
618 IF (scf_control%smear%do_smear) THEN
619 keyword => section_get_keyword(section, "SMEAR%METHOD")
620 CALL keyword_get(keyword, enum=enum)
621 WRITE (unit=output_unit, fmt="(T25,A,/,T25,A,T51,A30)") &
622 repeat("-", 56), &
623 "Smear method: ", adjustr(trim(enum_i2c(enum, scf_control%smear%method)))
624 SELECT CASE (scf_control%smear%method)
625 CASE (smear_fermi_dirac)
626 elec_temp = cp_unit_from_cp2k(scf_control%smear%electronic_temperature, &
627 "K")
628 WRITE (unit=output_unit, fmt="(T25,A,T61,F20.1)") &
629 "Electronic temperature [K]:", elec_temp
630 WRITE (unit=output_unit, fmt="(T25,A,T71,ES10.2)") &
631 "Electronic temperature [a.u.]:", scf_control%smear%electronic_temperature, &
632 "Accuracy threshold:", scf_control%smear%eps_fermi_dirac
633 IF (scf_control%smear%fixed_mag_mom > 0.0_dp) WRITE (unit=output_unit, fmt="(T25,A,T61,F20.1)") &
634 "Fixed magnetic moment set to:", scf_control%smear%fixed_mag_mom
636 WRITE (unit=output_unit, fmt="(T25,A,T71,F10.6)") &
637 "Smear window [a.u.]: ", scf_control%smear%window_size
638 END SELECT
639 END IF
640
641 CALL section_vals_val_get(dft_section, "ROKS", l_val=roks)
642 IF (roks .AND. (.NOT. scf_control%use_ot)) THEN
643 CALL section_vals_val_get(scf_section, "ROKS_SCHEME", &
644 i_val=roks_scheme)
645 keyword => section_get_keyword(section, "ROKS_SCHEME")
646 CALL keyword_get(keyword, enum=enum)
647 WRITE (unit=output_unit, fmt="(T25,A,/,T25,A,T51,A30)") &
648 repeat("-", 56), &
649 "ROKS scheme:", adjustr(trim(enum_i2c(enum, roks_scheme)))
650 SELECT CASE (roks_scheme)
651 CASE (general_roks)
652 WRITE (unit=output_unit, fmt="(T25,A,T71,F10.6)") &
653 "ROKS parameter f:", scf_control%roks_f
654 CASE (high_spin_roks)
655 WRITE (unit=output_unit, &
656 fmt="(T25,A,6(/,T25,A,T71,F10.6))") &
657 "ROKS parameters: a)lpha, b)eta; c)losed, o)pen, v)irtual", &
658 "acc", scf_control%roks_parameter(2, 2, 1), &
659 "bcc", scf_control%roks_parameter(2, 2, 2), &
660 "aoo", scf_control%roks_parameter(1, 1, 1), &
661 "boo", scf_control%roks_parameter(1, 1, 2), &
662 "avv", scf_control%roks_parameter(0, 0, 1), &
663 "bvv", scf_control%roks_parameter(0, 0, 2)
664 END SELECT
665 END IF
666 CALL section_release(section)
667
668 IF (scf_control%outer_scf%have_scf) THEN
669 WRITE (output_unit, "(T25,56('-'),/,T25,A)") "Outer loop SCF in use "
670 SELECT CASE (scf_control%outer_scf%type)
671 CASE (outer_scf_none)
672 WRITE (output_unit, '(T25,A)') "No variables optimised in outer loop"
674 WRITE (output_unit, '(T25,A)') "DDAPC constraint enforced"
676 WRITE (output_unit, '(T25,A)') "S2 constraint enforced"
678 WRITE (output_unit, '(T25,A)') "Floating basis function optimization enforced"
680 cpabort("CDFT constraints must be defined in QS&CDFT")
681 CASE DEFAULT
682 cpabort("")
683 END SELECT
684 WRITE (output_unit, '(T25,A,T72,ES9.2)') "eps_scf", scf_control%outer_scf%eps_scf
685 WRITE (output_unit, '(T25,A,T72,I9)') "max_scf", scf_control%outer_scf%max_scf
686 SELECT CASE (scf_control%outer_scf%optimizer)
688 WRITE (output_unit, '(T25,A)') "No outer loop optimization"
690 WRITE (output_unit, '(T25,A)') "Steepest descent optimization"
692 WRITE (output_unit, '(T25,A)') "Gradient bisection"
693 WRITE (output_unit, '(T25,A,T72,I9)') "bisect_trust_count", scf_control%outer_scf%bisect_trust_count
695 WRITE (output_unit, '(T25,A)') "DIIS optimization"
696 WRITE (output_unit, '(T25,A,T72,I9)') "DIIS buffer length", &
697 scf_control%outer_scf%diis_buffer_length
700 cpabort("Selected optimizer only compatible with CDFT")
702 WRITE (output_unit, '(T25,A)') "Optimization with the secant method"
703 CASE DEFAULT
704 cpabort("")
705 END SELECT
706 WRITE (output_unit, '(T25,A,T72,ES9.2)') "step_size", scf_control%outer_scf%step_size
707 ELSE
708 WRITE (output_unit, "(T25,56('-'),/,T25,A)") "No outer SCF"
709 END IF
710
711 END IF ! max_scf > 0
712
713 END IF ! output_unit > 0
714
715 CALL cp_print_key_finished_output(output_unit, logger, scf_section, &
716 "PRINT%PROGRAM_RUN_INFO")
717
718 CALL timestop(handle)
719
720 END SUBROUTINE scf_c_write_parameters
721
722! **************************************************************************************************
723
724! **************************************************************************************************
725!> \brief ...
726!> \param settings ...
727!> \param scf_section ...
728! **************************************************************************************************
729 SUBROUTINE ot_diag_read_input(settings, scf_section)
730 TYPE(qs_ot_settings_type) :: settings
731 TYPE(section_vals_type), POINTER :: scf_section
732
733 CHARACTER(len=*), PARAMETER :: routinen = 'ot_diag_read_input'
734
735 INTEGER :: handle, output_unit
736 LOGICAL :: explicit
737 TYPE(cp_logger_type), POINTER :: logger
738 TYPE(section_vals_type), POINTER :: ot_section
739
740 CALL timeset(routinen, handle)
741
742 logger => cp_get_default_logger()
743 output_unit = cp_print_key_unit_nr(logger, scf_section, "PRINT%PROGRAM_RUN_INFO", &
744 extension=".log")
745
746 ! decide default settings
747 CALL qs_ot_settings_init(settings)
748
749 ! use ot input new style
750 ot_section => section_vals_get_subs_vals(scf_section, "DIAGONALIZATION%OT")
751 CALL section_vals_get(ot_section, explicit=explicit)
752
753 CALL ot_readwrite_input(settings, ot_section, output_unit)
754
755 CALL cp_print_key_finished_output(output_unit, logger, scf_section, &
756 "PRINT%PROGRAM_RUN_INFO")
757
758 CALL timestop(handle)
759
760 END SUBROUTINE ot_diag_read_input
761
762! **************************************************************************************************
763
764END MODULE scf_control_types
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
Definition cp_units.F:1179
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public smear_fermi_dirac
integer, parameter, public outer_scf_optimizer_sd
integer, parameter, public outer_scf_optimizer_bisect
integer, parameter, public outer_scf_optimizer_secant
integer, parameter, public smear_energy_window
integer, parameter, public outer_scf_cdft_constraint
integer, parameter, public no_guess
integer, parameter, public outer_scf_optimizer_broyden
integer, parameter, public atomic_guess
integer, parameter, public outer_scf_basis_center_opt
integer, parameter, public direct_p_mix
integer, parameter, public outer_scf_s2_constraint
integer, parameter, public ot_algo_taylor_or_diag
integer, parameter, public smear_list
integer, parameter, public no_mix
integer, parameter, public high_spin_roks
integer, parameter, public diag_ot
integer, parameter, public outer_scf_ddapc_constraint
integer, parameter, public outer_scf_optimizer_newton_ls
integer, parameter, public outer_scf_optimizer_none
integer, parameter, public outer_scf_optimizer_newton
integer, parameter, public general_roks
integer, parameter, public outer_scf_none
integer, parameter, public outer_scf_optimizer_diis
function that build the scf section of the input
subroutine, public create_scf_section(section)
creates the structure of the section with the DFT SCF parameters
represents an enumeration, i.e. a mapping between integers and strings
character(len=default_string_length) function, public enum_i2c(enum, i)
maps an integer to a string
represents keywords in an input
subroutine, public keyword_get(keyword, names, usage, description, type_of_var, n_var, default_value, lone_keyword_value, repeats, enum, citations)
...
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
recursive type(keyword_type) function, pointer, public section_get_keyword(section, keyword_name)
returns the requested keyword
subroutine, public section_vals_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
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
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
Definition list.F:24
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_release(cdft_opt_control)
releases the CDFT optimizer control object
orbital transformations
Definition qs_ot_types.F:15
subroutine, public qs_ot_settings_init(settings)
sets default values for the settings type
subroutine, public ot_readwrite_input(settings, ot_section, output_unit)
...
parameters that control an scf iteration
subroutine, public scf_c_read_parameters(scf_control, inp_section)
reads the parameters of the scf section into the given scf_control
subroutine, public scf_c_release(scf_control)
releases the given scf_control (see cp2k/doc/ReferenceCounting.html)
subroutine, public scf_c_write_parameters(scf_control, dft_section)
writes out the scf parameters
subroutine, public scf_c_create(scf_control)
allocates and initializes an scf control object with the default values
type of a logger, at the moment it contains just a print level starting at which level it should be l...
represent a keyword in the input
represent a section of the input file
contains the parameters needed by a scf run
notice, this variable needs to be copyable, needed for spins as e.g. in qs_ot_scf
Definition qs_ot_types.F:63
contains the parameters needed by a scf run