(git:1f285aa)
cp_lbfgs_geo.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 Main driver for L-BFGS optimizer
10 !> \par History
11 !> 01.2020 Space Group Symmetry introduced by Pierre-AndrĂ© Cazade [pcazade]
12 ! **************************************************************************************************
14  USE cell_types, ONLY: cell_type
16  USE cp_lbfgs_optimizer_gopt, ONLY: cp_lbfgs_opt_gopt_type,&
22  cp_logger_type
23  USE cp_output_handling, ONLY: cp_iterate,&
26  USE cp_subsys_types, ONLY: cp_subsys_type
27  USE force_env_types, ONLY: force_env_get,&
28  force_env_type
29  USE global_types, ONLY: global_environment_type
30  USE gopt_f_methods, ONLY: gopt_f_ii,&
34  USE gopt_f_types, ONLY: gopt_f_type
35  USE gopt_param_types, ONLY: gopt_param_type
37  USE input_section_types, ONLY: section_vals_type,&
40  USE kinds, ONLY: dp
41  USE message_passing, ONLY: mp_para_env_type
43  print_spgr,&
45  USE space_groups_types, ONLY: spgr_type
46 #include "../base/base_uses.f90"
47 
48  IMPLICIT NONE
49  PRIVATE
50 
51  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_lbfgs_geo'
52 
53  PUBLIC :: geoopt_lbfgs
54 
55 CONTAINS
56 
57 ! **************************************************************************************************
58 !> \brief ...
59 !> \param force_env ...
60 !> \param gopt_param ...
61 !> \param globenv ...
62 !> \param geo_section ...
63 !> \param gopt_env ...
64 !> \param x0 ...
65 !> \par History
66 !> 08.2003 created [fawzi]
67 !> 01.2020 modified [pcazade]
68 !> \author Fawzi Mohamed
69 ! **************************************************************************************************
70  SUBROUTINE geoopt_lbfgs(force_env, gopt_param, globenv, geo_section, gopt_env, &
71  x0)
72  TYPE(force_env_type), POINTER :: force_env
73  TYPE(gopt_param_type), POINTER :: gopt_param
74  TYPE(global_environment_type), POINTER :: globenv
75  TYPE(section_vals_type), POINTER :: geo_section
76  TYPE(gopt_f_type), POINTER :: gopt_env
77  REAL(kind=dp), DIMENSION(:), POINTER :: x0
78 
79  CHARACTER(len=*), PARAMETER :: routinen = 'geoopt_lbfgs'
80 
81  INTEGER :: handle, iter_nr, its, output_unit
82  LOGICAL :: converged, should_stop
83  REAL(kind=dp) :: trust_radius
84  TYPE(cell_type), POINTER :: cell
85  TYPE(cp_lbfgs_opt_gopt_type), POINTER :: optimizer
86  TYPE(cp_logger_type), POINTER :: logger
87  TYPE(cp_subsys_type), POINTER :: subsys
88  TYPE(mp_para_env_type), POINTER :: para_env
89  TYPE(section_vals_type), POINTER :: root_section
90  TYPE(spgr_type), POINTER :: spgr
91 
92  CALL timeset(routinen, handle)
93 
94  NULLIFY (optimizer, para_env, spgr)
95  logger => cp_get_default_logger()
96  spgr => gopt_env%spgr
97  root_section => force_env%root_section
98  cpassert(ASSOCIATED(force_env))
99  cpassert(ASSOCIATED(gopt_param))
100 
101  ! collecting subsys
102  CALL force_env_get(force_env, para_env=para_env, cell=cell, subsys=subsys)
103 
104  ! Geometry optimization starts now
105  output_unit = cp_print_key_unit_nr(logger, geo_section, "PRINT%PROGRAM_RUN_INFO", &
106  extension=".geoLog")
107  CALL print_geo_opt_header(gopt_env, output_unit, "L-BFGS")
108 
109  ! finds space group
110  CALL section_vals_val_get(geo_section, "KEEP_SPACE_GROUP", l_val=spgr%keep_space_group)
111  IF (spgr%keep_space_group) THEN
112  CALL identify_space_group(subsys, geo_section, gopt_env, output_unit)
113  CALL spgr_apply_rotations_coord(spgr, x0)
114  CALL print_spgr(spgr)
115  END IF
116 
117  ! Stop if not implemented
118  IF (gopt_env%type_id == default_ts_method_id) &
119  cpabort("BFGS method not yet working with DIMER")
120 
121  CALL section_vals_val_get(geo_section, "LBFGS%TRUST_RADIUS", r_val=trust_radius)
122  ALLOCATE (optimizer)
123  CALL cp_opt_gopt_create(optimizer, para_env=para_env, obj_funct=gopt_env, &
124  x0=x0, wanted_relative_f_delta=gopt_param%wanted_rel_f_error, &
125  wanted_projected_gradient=gopt_param%wanted_proj_gradient, m=gopt_param%max_h_rank, &
126  max_f_per_iter=gopt_param%max_f_per_iter, trust_radius=trust_radius)
127  CALL cp_iterate(logger%iter_info, increment=0, iter_nr_out=iter_nr)
128  converged = .false.
129 
130  DO its = iter_nr + 1, gopt_param%max_iter
131  CALL cp_iterate(logger%iter_info, last=(its == gopt_param%max_iter))
132  CALL section_vals_val_set(geo_section, "STEP_START_VAL", i_val=its)
133  CALL gopt_f_ii(its, output_unit)
134 
135  ! Real optimization step..
136  IF (.NOT. cp_opt_gopt_next(optimizer, geo_section=geo_section, &
137  force_env=force_env, gopt_param=gopt_param, &
138  converged=converged, spgr=spgr)) EXIT
139 
140  ! Check for an external exit command
141  CALL external_control(should_stop, "GEO", globenv=globenv)
142  IF (should_stop) THEN
143  CALL cp_opt_gopt_stop(optimizer)
144  EXIT
145  END IF
146  IF (its == gopt_param%max_iter) EXIT
147  END DO
148 
149  IF ((its == gopt_param%max_iter) .AND. (.NOT. converged)) THEN
150  CALL print_geo_opt_nc(gopt_env, output_unit)
151  END IF
152 
153  ! Write final output information, if converged
154  CALL cp_iterate(logger%iter_info, last=.true., increment=0)
155  CALL gopt_f_io_finalize(gopt_env, force_env, optimizer%x, converged, its, root_section, &
156  optimizer%para_env, optimizer%master, output_unit)
157 
158  CALL cp_opt_gopt_release(optimizer)
159  DEALLOCATE (optimizer)
160  CALL cp_print_key_finished_output(output_unit, logger, geo_section, &
161  "PRINT%PROGRAM_RUN_INFO")
162 
163  CALL timestop(handle)
164 
165  END SUBROUTINE geoopt_lbfgs
166 
167 END MODULE cp_lbfgs_geo
Handles all functions related to the CELL.
Definition: cell_types.F:15
Routines to handle the external control of CP2K.
subroutine, public external_control(should_stop, flag, globenv, target_time, start_time, force_check)
External manipulations during a run : when the <PROJECT_NAME>.EXIT_$runtype command is sent the progr...
Main driver for L-BFGS optimizer.
Definition: cp_lbfgs_geo.F:13
subroutine, public geoopt_lbfgs(force_env, gopt_param, globenv, geo_section, gopt_env, x0)
...
Definition: cp_lbfgs_geo.F:72
routines that optimize a functional using the limited memory bfgs quasi-newton method....
subroutine, public cp_opt_gopt_create(optimizer, para_env, obj_funct, x0, m, print_every, wanted_relative_f_delta, wanted_projected_gradient, lower_bound, upper_bound, kind_of_bound, master, max_f_per_iter, trust_radius)
initializes the optimizer
logical function, public cp_opt_gopt_next(optimizer, n_iter, f, last_f, projected_gradient, converged, geo_section, force_env, gopt_param, spgr)
goes to the next optimal point (after an optimizer iteration) returns true if converged
subroutine, public cp_opt_gopt_stop(optimizer)
stops the optimization
subroutine, public cp_opt_gopt_release(optimizer)
releases the optimizer (see doc/ReferenceCounting.html)
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,...
subroutine, public cp_iterate(iteration_info, last, iter_nr, increment, iter_nr_out)
adds one to the actual iteration
types that represent a subsys, i.e. a part of the system
Interface for the force calculations.
recursive subroutine, public force_env_get(force_env, in_use, fist_env, qs_env, meta_env, fp_env, subsys, para_env, potential_energy, additional_potential, kinetic_energy, harmonic_shell, kinetic_shell, cell, sub_force_env, qmmm_env, qmmmx_env, eip_env, pwdft_env, globenv, input, force_env_section, method_name_id, root_section, mixed_env, nnp_env, embed_env)
returns various attributes about the force environment
Define type storing the global information of a run. Keep the amount of stored data small....
Definition: global_types.F:21
contains a functional that calculates the energy and its derivatives for the geometry optimizer
subroutine, public print_geo_opt_header(gopt_env, output_unit, label)
...
recursive subroutine, public gopt_f_io_finalize(gopt_env, force_env, x0, conv, its, root_section, para_env, master, output_unit)
Handles the Output at the end of an optimization run.
subroutine, public print_geo_opt_nc(gopt_env, output_unit)
...
subroutine, public gopt_f_ii(its, output_unit)
Prints iteration step of the optimization procedure on screen.
contains a functional that calculates the energy and its derivatives for the geometry optimizer
Definition: gopt_f_types.F:15
contains typo and related routines to handle parameters controlling the GEO_OPT module
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public default_ts_method_id
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_val_set(section_vals, keyword_name, i_rep_section, i_rep_val, val, l_val, i_val, r_val, c_val, l_vals_ptr, i_vals_ptr, r_vals_ptr, c_vals_ptr)
sets the requested value
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
Interface to the message passing library MPI.
Space Group Symmetry Type Module (version 1.0, Ferbruary 12, 2021)
Space Group Symmetry Module (version 1.0, January 16, 2020)
Definition: space_groups.F:14
subroutine, public print_spgr(spgr)
routine prints Space Group Information.
Definition: space_groups.F:830
subroutine, public spgr_apply_rotations_coord(spgr, coord)
routine applies the rotation matrices to the coordinates.
Definition: space_groups.F:618
subroutine, public identify_space_group(subsys, geo_section, gopt_env, iunit)
routine indentifies the space group and finds rotation matrices.
Definition: space_groups.F:286