24#include "./base/base_uses.f90"
30 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'qs_cdft_opt_types'
66 LOGICAL :: build_jacobian = .false.
67 LOGICAL :: broyden_update = .false.
68 LOGICAL :: continue_ls = .false.
69 LOGICAL :: jacobian_restart = .false.
70 REAL(kind=
dp) :: newton_step = 0.0_dp
71 REAL(kind=
dp) :: newton_step_save = 0.0_dp
72 REAL(kind=
dp) :: factor_ls = 0.0_dp
73 REAL(kind=
dp),
DIMENSION(:), &
74 ALLOCATABLE :: jacobian_step
75 REAL(kind=
dp),
DIMENSION(:), &
76 POINTER :: jacobian_vector => null()
77 INTEGER :: jacobian_type = -1
78 INTEGER :: broyden_type = -1
79 INTEGER :: jacobian_freq(2) = -1
80 INTEGER :: ijacobian(2) = -1
81 INTEGER :: max_ls = -1
97 CHARACTER(LEN=*),
PARAMETER :: routinen =
'cdft_opt_type_create'
101 CALL timeset(routinen, handle)
103 cpassert(.NOT.
ASSOCIATED(cdft_opt_control))
104 ALLOCATE (cdft_opt_control)
108 cdft_opt_control%jacobian_type = -1
109 cdft_opt_control%broyden_type = -1
110 cdft_opt_control%jacobian_freq(:) = 1
111 cdft_opt_control%newton_step = 1.0_dp
112 cdft_opt_control%newton_step_save = 1.0_dp
113 cdft_opt_control%factor_ls = 0.5_dp
114 cdft_opt_control%ijacobian(:) = 0
115 cdft_opt_control%max_ls = 0
116 cdft_opt_control%build_jacobian = .false.
117 cdft_opt_control%broyden_update = .false.
118 cdft_opt_control%continue_ls = .false.
119 cdft_opt_control%jacobian_restart = .false.
120 NULLIFY (cdft_opt_control%jacobian_vector)
122 CALL timestop(handle)
137 IF (
ASSOCIATED(cdft_opt_control))
THEN
138 IF (
ASSOCIATED(cdft_opt_control%jacobian_vector)) &
139 DEALLOCATE (cdft_opt_control%jacobian_vector)
140 IF (
ALLOCATED(cdft_opt_control%jacobian_step)) &
141 DEALLOCATE (cdft_opt_control%jacobian_step)
143 DEALLOCATE (cdft_opt_control)
146 NULLIFY (cdft_opt_control)
163 CHARACTER(LEN=*),
PARAMETER :: routinen =
'cdft_opt_type_read'
166 INTEGER,
DIMENSION(:),
POINTER :: tmplist
168 REAL(kind=
dp),
DIMENSION(:),
POINTER :: rtmplist
171 CALL timeset(routinen, handle)
173 cpassert(
ASSOCIATED(cdft_opt_control))
177 i_val=cdft_opt_control%max_ls)
179 i_val=cdft_opt_control%jacobian_type)
182 ALLOCATE (cdft_opt_control%jacobian_step(
SIZE(rtmplist)))
183 cdft_opt_control%jacobian_step(:) = rtmplist
185 i_val=cdft_opt_control%broyden_type)
187 l_val=cdft_opt_control%continue_ls)
189 r_val=cdft_opt_control%factor_ls)
190 IF (cdft_opt_control%factor_ls .LE. 0.0_dp .OR. &
191 cdft_opt_control%factor_ls .GE. 1.0_dp) &
192 CALL cp_abort(__location__, &
193 "Keyword FACTOR_LS must be between 0.0 and 1.0.")
198 IF (
SIZE(tmplist) /= 2) &
199 CALL cp_abort(__location__, &
200 "Keyword JACOBIAN_FREQ takes exactly two input values.")
201 IF (any(tmplist .LT. 0)) &
202 CALL cp_abort(__location__, &
203 "Keyword JACOBIAN_FREQ takes only positive values.")
204 IF (all(tmplist .EQ. 0)) &
205 CALL cp_abort(__location__, &
206 "Both values to keyword JACOBIAN_FREQ cannot be zero.")
207 cdft_opt_control%jacobian_freq(:) = tmplist(1:2)
210 l_val=cdft_opt_control%jacobian_restart)
211 IF (cdft_opt_control%jacobian_restart)
THEN
214 ALLOCATE (cdft_opt_control%jacobian_vector(
SIZE(rtmplist)))
215 cdft_opt_control%jacobian_vector = rtmplist
218 CALL timestop(handle)
233 INTEGER :: optimizer, output_unit
235 cpassert(
ASSOCIATED(cdft_opt_control))
237 SELECT CASE (optimizer)
241 WRITE (output_unit,
'(T3,A)')
"Optimization with Broyden's method"
242 SELECT CASE (cdft_opt_control%broyden_type)
244 WRITE (output_unit,
'(A)')
" variant : 1st method"
246 WRITE (output_unit,
'(A)')
" variant : 1st method with explicit initial Jacobian"
248 WRITE (output_unit,
'(A)')
" variant : 1st method with backtracking line search"
250 WRITE (output_unit,
'(A)') &
251 " variant : 1st method with explicit initial Jacobian"
252 WRITE (output_unit,
'(A)') &
253 " and backtracking line search"
255 WRITE (output_unit,
'(A)')
" variant : 2nd method"
257 WRITE (output_unit,
'(A)')
" variant : 2nd method with explicit initial Jacobian"
259 WRITE (output_unit,
'(A)')
" variant : 2nd method with backtracking line search"
261 WRITE (output_unit,
'(A)') &
262 " variant : 2nd method with explicit initial Jacobian"
263 WRITE (output_unit,
'(A)') &
264 " and backtracking line search"
267 WRITE (output_unit,
'(T3,A)')
"Optimization with Newton's method"
269 WRITE (output_unit,
'(T3,A)')
"Optimization with Newton's method using backtracking line search"
271 SELECT CASE (optimizer)
275 IF (cdft_opt_control%jacobian_freq(2) > 0)
THEN
276 WRITE (output_unit,
'(T6,A,I4,A)') &
277 "The Jacobian is restarted every ", cdft_opt_control%jacobian_freq(2),
" energy evaluation"
278 IF (cdft_opt_control%jacobian_freq(1) > 0) &
279 WRITE (output_unit,
'(T29,A,I4,A)') &
280 "or every ", cdft_opt_control%jacobian_freq(1),
" CDFT SCF iteration"
282 WRITE (output_unit,
'(T6,A,I4,A)') &
283 "The Jacobian is restarted every ", cdft_opt_control%jacobian_freq(1),
" CDFT SCF iteration"
285 WRITE (output_unit,
'(T3,A,F8.4)') &
286 "Optimizer step size: ", cdft_opt_control%newton_step_save
303 CHARACTER(LEN=*),
PARAMETER :: routinen =
'cdft_opt_type_copy'
309 IF (.NOT.
ASSOCIATED(old))
RETURN
311 CALL timeset(routinen, handle)
314 new%max_ls = old%max_ls
315 new%continue_ls = old%continue_ls
316 new%factor_ls = old%factor_ls
317 new%jacobian_type = old%jacobian_type
318 new%jacobian_freq(:) = old%jacobian_freq(:)
319 new%newton_step = old%newton_step
320 new%newton_step_save = old%newton_step_save
321 new%ijacobian(:) = old%ijacobian(:)
322 new%build_jacobian = old%build_jacobian
323 new%broyden_type = old%broyden_type
324 new%broyden_update = old%broyden_update
325 IF (
ALLOCATED(new%jacobian_step))
DEALLOCATE (new%jacobian_step)
326 ALLOCATE (new%jacobian_step(
SIZE(old%jacobian_step)))
327 new%jacobian_step(:) = old%jacobian_step
328 IF (old%jacobian_restart)
THEN
331 new%jacobian_restart = .true.
332 ALLOCATE (new%jacobian_vector(
SIZE(old%jacobian_vector)))
333 new%jacobian_vector = old%jacobian_vector
334 DEALLOCATE (old%jacobian_vector)
335 old%jacobian_restart = .false.
338 CALL timestop(handle)
Defines the basic variable types.
integer, parameter, public dp
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_release(cdft_opt_control)
releases the CDFT optimizer control object
subroutine, public cdft_opt_type_copy(new, old)
copies settings between two CDFT optimizer control objects retaining both
subroutine, public cdft_opt_type_read(cdft_opt_control, inp_section)
reads the parameters of the CDFT optimizer type
subroutine, public cdft_opt_type_write(cdft_opt_control, optimizer, output_unit)
writes information about the CDFT optimizer object
contains the parameters needed by CDFT specific optimizers