(git:34ef472)
cell_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 CELL optimization
10 !> \par History
11 !> 03.2008 - Teodoro Laino [tlaino] - University of Zurich - Cell Optimization
12 ! **************************************************************************************************
13 MODULE cell_opt
14  USE bfgs_optimizer, ONLY: geoopt_bfgs
15  USE cg_optimizer, ONLY: geoopt_cg
16  USE cp_lbfgs_geo, ONLY: geoopt_lbfgs
18  cp_logger_type
20  cp_iterate,&
22  USE force_env_types, ONLY: force_env_type
23  USE global_types, ONLY: global_environment_type
25  USE gopt_f_types, ONLY: gopt_f_create,&
27  gopt_f_type
29  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  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cell_opt'
44 
45  PUBLIC :: cp_cell_opt
46 
47 CONTAINS
48 
49 ! **************************************************************************************************
50 !> \brief Main driver to perform geometry optimization
51 !> \param force_env ...
52 !> \param globenv ...
53 !> \author Teodoro Laino [tlaino] - University of Zurich - 03.2008
54 ! **************************************************************************************************
55  SUBROUTINE cp_cell_opt(force_env, globenv)
56  TYPE(force_env_type), POINTER :: force_env
57  TYPE(global_environment_type), POINTER :: globenv
58 
59  CHARACTER(len=*), PARAMETER :: routinen = 'cp_cell_opt'
60 
61  INTEGER :: handle, step_start_val
62  REAL(kind=dp), DIMENSION(:), POINTER :: x0
63  TYPE(cp_logger_type), POINTER :: logger
64  TYPE(gopt_f_type), POINTER :: gopt_env
65  TYPE(gopt_param_type), POINTER :: gopt_param
66  TYPE(section_vals_type), POINTER :: force_env_section, geo_section, &
67  root_section
68 
69  CALL timeset(routinen, handle)
70  logger => cp_get_default_logger()
71  cpassert(ASSOCIATED(force_env))
72  cpassert(ASSOCIATED(globenv))
73  NULLIFY (gopt_param, force_env_section, gopt_env, x0)
74  root_section => force_env%root_section
75  force_env_section => force_env%force_env_section
76  geo_section => section_vals_get_subs_vals(root_section, "MOTION%CELL_OPT")
77 
78  ALLOCATE (gopt_param)
79  CALL gopt_param_read(gopt_param, geo_section, type_id=default_cell_method_id)
80  CALL gopt_f_create(gopt_env, gopt_param, force_env=force_env, globenv=globenv, &
81  geo_opt_section=geo_section)
82  CALL gopt_f_create_x0(gopt_env, x0)
83 
84  CALL section_vals_val_get(geo_section, "STEP_START_VAL", i_val=step_start_val)
85  CALL cp_add_iter_level(logger%iter_info, "CELL_OPT")
86  CALL cp_iterate(logger%iter_info, iter_nr=step_start_val)
87  CALL cp_cell_opt_low(force_env, globenv, gopt_param, gopt_env, &
88  force_env_section, geo_section, x0)
89  CALL cp_rm_iter_level(logger%iter_info, "CELL_OPT")
90 
91  ! Reset counter for next iteration
92  CALL section_vals_val_set(geo_section, "STEP_START_VAL", i_val=0)
93  DEALLOCATE (x0)
94  CALL gopt_f_release(gopt_env)
95  DEALLOCATE (gopt_param)
96  CALL timestop(handle)
97 
98  END SUBROUTINE cp_cell_opt
99 
100 ! **************************************************************************************************
101 !> \brief call to low level geometry optimizers
102 !> \param force_env ...
103 !> \param globenv ...
104 !> \param gopt_param ...
105 !> \param gopt_env ...
106 !> \param force_env_section ...
107 !> \param geo_section ...
108 !> \param x0 ...
109 !> \author Teodoro Laino [tlaino] - University of Zurich - 03.2008
110 ! **************************************************************************************************
111  SUBROUTINE cp_cell_opt_low(force_env, globenv, gopt_param, gopt_env, force_env_section, &
112  geo_section, x0)
113  TYPE(force_env_type), POINTER :: force_env
114  TYPE(global_environment_type), POINTER :: globenv
115  TYPE(gopt_param_type), POINTER :: gopt_param
116  TYPE(gopt_f_type), POINTER :: gopt_env
117  TYPE(section_vals_type), POINTER :: force_env_section, geo_section
118  REAL(kind=dp), DIMENSION(:), POINTER :: x0
119 
120  cpassert(ASSOCIATED(force_env))
121  cpassert(ASSOCIATED(globenv))
122  cpassert(ASSOCIATED(gopt_param))
123  cpassert(ASSOCIATED(gopt_env))
124  cpassert(ASSOCIATED(x0))
125  cpassert(ASSOCIATED(force_env_section))
126  cpassert(ASSOCIATED(geo_section))
127  mark_used(force_env_section)
128 
129  SELECT CASE (gopt_param%method_id)
131  CALL geoopt_bfgs(force_env, gopt_param, globenv, &
132  geo_section, gopt_env, x0)
134  CALL geoopt_lbfgs(force_env, gopt_param, globenv, &
135  geo_section, gopt_env, x0)
136  CASE (default_cg_method_id)
137  CALL geoopt_cg(force_env, gopt_param, globenv, &
138  geo_section, gopt_env, x0)
139  CASE DEFAULT
140  cpabort("")
141  END SELECT
142 
143  END SUBROUTINE cp_cell_opt_low
144 
145 END MODULE cell_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.
performs CELL optimization
Definition: cell_opt.F:13
subroutine, public cp_cell_opt(force_env, globenv)
Main driver to perform geometry optimization.
Definition: cell_opt.F:56
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.
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_cell_method_id
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