(git:ccc2433)
geo_opt.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 performs geometry optimization
10 !> \par History
11 !> none
12 ! **************************************************************************************************
13 MODULE geo_opt
14 
15  USE bfgs_optimizer, ONLY: geoopt_bfgs
16  USE cg_optimizer, ONLY: geoopt_cg
17  USE cp_lbfgs_geo, ONLY: geoopt_lbfgs
19  cp_logger_type
21  cp_iterate,&
23  USE force_env_types, ONLY: force_env_type
24  USE global_types, ONLY: global_environment_type
26  USE gopt_f_types, ONLY: gopt_f_create,&
28  gopt_f_type
30  gopt_param_type
35  section_vals_type,&
38  USE kinds, ONLY: dp
39 #include "../base/base_uses.f90"
40 
41  IMPLICIT NONE
42  PRIVATE
43 
44  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'geo_opt'
45 
46  PUBLIC :: cp_geo_opt, cp_rot_opt
47 
48 CONTAINS
49 
50 ! **************************************************************************************************
51 !> \brief Main driver to perform geometry optimization
52 !> \param force_env ...
53 !> \param globenv ...
54 !> \param eval_opt_geo ...
55 !> \param rm_restart_info ...
56 ! **************************************************************************************************
57  SUBROUTINE cp_geo_opt(force_env, globenv, eval_opt_geo, rm_restart_info)
58 
59  TYPE(force_env_type), POINTER :: force_env
60  TYPE(global_environment_type), POINTER :: globenv
61  LOGICAL, INTENT(IN), OPTIONAL :: eval_opt_geo, rm_restart_info
62 
63  CHARACTER(len=*), PARAMETER :: routinen = 'cp_geo_opt'
64 
65  INTEGER :: handle, step_start_val
66  LOGICAL :: my_rm_restart_info
67  REAL(kind=dp), DIMENSION(:), POINTER :: x0
68  TYPE(cp_logger_type), POINTER :: logger
69  TYPE(gopt_f_type), POINTER :: gopt_env
70  TYPE(gopt_param_type), POINTER :: gopt_param
71  TYPE(section_vals_type), POINTER :: geo_section, root_section
72 
73  CALL timeset(routinen, handle)
74  logger => cp_get_default_logger()
75  cpassert(ASSOCIATED(force_env))
76  cpassert(ASSOCIATED(globenv))
77  NULLIFY (gopt_param, gopt_env, x0)
78  root_section => force_env%root_section
79  geo_section => section_vals_get_subs_vals(root_section, "MOTION%GEO_OPT")
80 
81  ALLOCATE (gopt_param)
82  CALL gopt_param_read(gopt_param, geo_section)
83  CALL gopt_f_create(gopt_env, gopt_param, force_env=force_env, globenv=globenv, &
84  geo_opt_section=geo_section, eval_opt_geo=eval_opt_geo)
85  CALL gopt_f_create_x0(gopt_env, x0)
86 
87  CALL section_vals_val_get(geo_section, "STEP_START_VAL", i_val=step_start_val)
88  CALL cp_add_iter_level(logger%iter_info, "GEO_OPT")
89  CALL cp_iterate(logger%iter_info, iter_nr=step_start_val)
90  CALL cp_geo_opt_low(force_env, globenv, gopt_param, gopt_env, &
91  geo_section, x0)
92  CALL cp_rm_iter_level(logger%iter_info, "GEO_OPT")
93 
94  ! Reset counter for next iteration, unless rm_restart_info==.FALSE.
95  my_rm_restart_info = .true.
96  IF (PRESENT(rm_restart_info)) my_rm_restart_info = rm_restart_info
97  IF (my_rm_restart_info) &
98  CALL section_vals_val_set(geo_section, "STEP_START_VAL", i_val=0)
99 
100  DEALLOCATE (x0)
101  CALL gopt_f_release(gopt_env)
102  DEALLOCATE (gopt_param)
103  CALL timestop(handle)
104 
105  END SUBROUTINE cp_geo_opt
106 
107 ! **************************************************************************************************
108 !> \brief Main driver to perform rotation optimization for Dimer
109 !> \param gopt_env ...
110 !> \param x0 ...
111 !> \param gopt_param ...
112 !> \param geo_section ...
113 ! **************************************************************************************************
114  SUBROUTINE cp_rot_opt(gopt_env, x0, gopt_param, geo_section)
115  TYPE(gopt_f_type), POINTER :: gopt_env
116  REAL(kind=dp), DIMENSION(:), POINTER :: x0
117  TYPE(gopt_param_type), POINTER :: gopt_param
118  TYPE(section_vals_type), POINTER :: geo_section
119 
120  CHARACTER(len=*), PARAMETER :: routinen = 'cp_rot_opt'
121 
122  INTEGER :: handle, step_start_val
123  TYPE(cp_logger_type), POINTER :: logger
124 
125  CALL timeset(routinen, handle)
126  logger => cp_get_default_logger()
127  cpassert(ASSOCIATED(gopt_env))
128  cpassert(ASSOCIATED(gopt_env%force_env))
129  cpassert(ASSOCIATED(gopt_env%globenv))
130 
131  CALL section_vals_val_get(geo_section, "STEP_START_VAL", i_val=step_start_val)
132  CALL cp_add_iter_level(logger%iter_info, "ROT_OPT")
133  CALL cp_iterate(logger%iter_info, iter_nr=step_start_val)
134  CALL cp_geo_opt_low(gopt_env%force_env, gopt_env%globenv, gopt_param, gopt_env, &
135  geo_section, x0)
136  CALL cp_rm_iter_level(logger%iter_info, "ROT_OPT")
137 
138  ! Reset counter for next iteration
139  CALL section_vals_val_set(geo_section, "STEP_START_VAL", i_val=0)
140  CALL timestop(handle)
141 
142  END SUBROUTINE cp_rot_opt
143 
144 ! **************************************************************************************************
145 !> \brief call to low level geometry optimizers
146 !> \param force_env ...
147 !> \param globenv ...
148 !> \param gopt_param ...
149 !> \param gopt_env ...
150 !> \param geo_section ...
151 !> \param x0 ...
152 ! **************************************************************************************************
153  SUBROUTINE cp_geo_opt_low(force_env, globenv, gopt_param, gopt_env, &
154  geo_section, x0)
155  TYPE(force_env_type), POINTER :: force_env
156  TYPE(global_environment_type), POINTER :: globenv
157  TYPE(gopt_param_type), POINTER :: gopt_param
158  TYPE(gopt_f_type), POINTER :: gopt_env
159  TYPE(section_vals_type), POINTER :: geo_section
160  REAL(kind=dp), DIMENSION(:), POINTER :: x0
161 
162  cpassert(ASSOCIATED(force_env))
163  cpassert(ASSOCIATED(globenv))
164  cpassert(ASSOCIATED(gopt_param))
165  cpassert(ASSOCIATED(gopt_env))
166  cpassert(ASSOCIATED(x0))
167  cpassert(ASSOCIATED(geo_section))
168 
169  SELECT CASE (gopt_param%method_id)
171  CALL geoopt_bfgs(force_env, gopt_param, globenv, &
172  geo_section, gopt_env, x0)
174  CALL geoopt_lbfgs(force_env, gopt_param, globenv, &
175  geo_section, gopt_env, x0)
176  CASE (default_cg_method_id)
177  CALL geoopt_cg(force_env, gopt_param, globenv, &
178  geo_section, gopt_env, x0)
179  CASE DEFAULT
180  cpabort("")
181  END SELECT
182 
183  END SUBROUTINE cp_geo_opt_low
184 
185 END MODULE geo_opt
Routines for Geometry optimization using BFGS algorithm.
recursive subroutine, public geoopt_bfgs(force_env, gopt_param, globenv, geo_section, gopt_env, x0)
Main driver for BFGS geometry optimizations.
Routines for Geometry optimization using Conjugate Gradients.
Definition: cg_optimizer.F:13
recursive subroutine, public geoopt_cg(force_env, gopt_param, globenv, geo_section, gopt_env, x0, do_update)
Driver for conjugate gradient optimization technique.
Definition: cg_optimizer.F:113
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
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...
subroutine, public cp_iterate(iteration_info, last, iter_nr, increment, iter_nr_out)
adds one to the actual iteration
subroutine, public cp_rm_iter_level(iteration_info, level_name, n_rlevel_att)
Removes an iteration level.
subroutine, public cp_add_iter_level(iteration_info, level_name, n_rlevel_new)
Adds an iteration level.
Interface for the force calculations.
performs geometry optimization
Definition: geo_opt.F:13
subroutine, public cp_geo_opt(force_env, globenv, eval_opt_geo, rm_restart_info)
Main driver to perform geometry optimization.
Definition: geo_opt.F:58
subroutine, public cp_rot_opt(gopt_env, x0, gopt_param, geo_section)
Main driver to perform rotation optimization for Dimer.
Definition: geo_opt.F:115
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 gopt_f_create_x0(gopt_env, x0)
returns the value of the parameters for the actual configuration
contains a functional that calculates the energy and its derivatives for the geometry optimizer
Definition: gopt_f_types.F:15
recursive subroutine, public gopt_f_create(gopt_env, gopt_param, force_env, globenv, geo_opt_section, eval_opt_geo)
...
Definition: gopt_f_types.F:95
recursive subroutine, public gopt_f_release(gopt_env)
...
Definition: gopt_f_types.F:200
contains typo and related routines to handle parameters controlling the GEO_OPT module
subroutine, public gopt_param_read(gopt_param, gopt_section, type_id)
reads the parameters of the geopmetry optimizer
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public default_lbfgs_method_id
integer, parameter, public default_bfgs_method_id
integer, parameter, public default_cg_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
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
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