(git:374b731)
Loading...
Searching...
No Matches
gopt_f_types.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 contains a functional that calculates the energy and its derivatives
10!> for the geometry optimizer
11!> \par History
12!> 01.2008 - Luca Bellucci and Teodoro Laino - Generalizing for Dimer Method.
13!> 03.2008 - Teodoro Laino [tlaino] - University of Zurich - Cell Optimization
14! **************************************************************************************************
21 USE dimer_types, ONLY: dimer_env_create,&
40 USE kinds, ONLY: default_string_length,&
41 dp
45#include "../base/base_uses.f90"
46
47 IMPLICIT NONE
48 PRIVATE
49
50 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
51 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'gopt_f_types'
52
54
55! **************************************************************************************************
56!> \brief calculates the potential energy of a system, and its derivatives
57!> \par History
58!> none
59! **************************************************************************************************
61 INTEGER :: ref_count = 0
62 INTEGER :: nfree = 0
63 INTEGER :: type_id=default_cell_method_id, ts_method_id=0, cell_method_id=0, shellcore_method_id=0
64 LOGICAL :: dimer_rotation = .false., do_line_search = .false., eval_opt_geo = .false.
65 CHARACTER(LEN=default_string_length) :: label = "", tag = ""
66 TYPE(force_env_type), POINTER :: force_env => null()
67 TYPE(global_environment_type), POINTER :: globenv => null()
68 ! Motion section must be references only for IO of the MOTION%PRINT..
69 TYPE(section_vals_type), POINTER :: motion_section => null(), geo_section => null()
70 TYPE(dimer_env_type), POINTER :: dimer_env => null()
71 TYPE(gopt_f_type), POINTER :: gopt_dimer_env => null()
72 TYPE(gopt_param_type), POINTER :: gopt_dimer_param => null()
73 TYPE(cell_opt_env_type), POINTER :: cell_env => null()
74 TYPE(spgr_type), POINTER :: spgr => null()
75 REAL(kind=dp), DIMENSION(3, 3) :: h_ref = 0.0_dp
76 LOGICAL :: require_consistent_energy_force = .false.
77 END TYPE gopt_f_type
78
79CONTAINS
80
81! **************************************************************************************************
82!> \brief ...
83!> \param gopt_env the geometry optimization environment to be created
84!> force_env:
85!> \param gopt_param ...
86!> \param force_env ...
87!> \param globenv ...
88!> \param geo_opt_section ...
89!> \param eval_opt_geo ...
90!> \par History
91!> none
92! **************************************************************************************************
93 RECURSIVE SUBROUTINE gopt_f_create(gopt_env, gopt_param, force_env, globenv, geo_opt_section, &
94 eval_opt_geo)
95
96 TYPE(gopt_f_type), POINTER :: gopt_env
97 TYPE(gopt_param_type), POINTER :: gopt_param
98 TYPE(force_env_type), POINTER :: force_env
99 TYPE(global_environment_type), POINTER :: globenv
100 TYPE(section_vals_type), POINTER :: geo_opt_section
101 LOGICAL, INTENT(IN), OPTIONAL :: eval_opt_geo
102
103 INTEGER :: natom, nshell
104 TYPE(cp_subsys_type), POINTER :: subsys
105 TYPE(particle_list_type), POINTER :: particles, shell_particles
106 TYPE(section_vals_type), POINTER :: dimer_section, rot_opt_section
107
108 cpassert(.NOT. ASSOCIATED(gopt_env))
109 ALLOCATE (gopt_env)
110 nshell = 0
111
112 NULLIFY (gopt_env%dimer_env, gopt_env%gopt_dimer_env, gopt_env%gopt_dimer_param, gopt_env%cell_env, gopt_env%spgr)
113 gopt_env%ref_count = 1
114 gopt_env%dimer_rotation = .false.
115 gopt_env%do_line_search = .false.
116 ALLOCATE (gopt_env%spgr)
117 CALL force_env_retain(force_env)
118 gopt_env%force_env => force_env
119 gopt_env%motion_section => section_vals_get_subs_vals(force_env%root_section, "MOTION")
120 gopt_env%geo_section => geo_opt_section
121 gopt_env%globenv => globenv
122 gopt_env%eval_opt_geo = .true.
123 IF (PRESENT(eval_opt_geo)) gopt_env%eval_opt_geo = eval_opt_geo
124 gopt_env%require_consistent_energy_force = .true.
125
126 CALL force_env_get(force_env, subsys=subsys)
127 gopt_env%type_id = gopt_param%type_id
128 SELECT CASE (gopt_env%type_id)
130 CALL cp_subsys_get(subsys, &
131 particles=particles, &
132 shell_particles=shell_particles)
133 IF (ASSOCIATED(shell_particles)) nshell = shell_particles%n_els
134 ! The same number of shell and core particles is assumed
135 gopt_env%nfree = particles%n_els + nshell
136 gopt_env%label = "GEO_OPT"
137 gopt_env%tag = "GEOMETRY"
138 SELECT CASE (gopt_param%type_id)
140 gopt_env%ts_method_id = gopt_param%ts_method_id
141 SELECT CASE (gopt_param%ts_method_id)
143 ! For the Dimer method we use the same framework of geometry optimizers
144 ! already defined for cp2k..
145 natom = force_env_get_natom(force_env)
146 dimer_section => section_vals_get_subs_vals(geo_opt_section, "TRANSITION_STATE%DIMER")
147 CALL dimer_env_create(gopt_env%dimer_env, subsys, globenv, dimer_section)
148
149 ! Setup the GEO_OPT environment for the rotation of the Dimer
150 rot_opt_section => section_vals_get_subs_vals(dimer_section, "ROT_OPT")
151 ALLOCATE (gopt_env%gopt_dimer_param)
152 CALL gopt_param_read(gopt_env%gopt_dimer_param, rot_opt_section, &
154 gopt_env%gopt_dimer_param%type_id = default_ts_method_id
155
156 CALL gopt_f_create(gopt_env%gopt_dimer_env, gopt_env%gopt_dimer_param, force_env=force_env, &
157 globenv=globenv, geo_opt_section=rot_opt_section, eval_opt_geo=eval_opt_geo)
158 CALL dimer_env_retain(gopt_env%dimer_env)
159 gopt_env%gopt_dimer_env%dimer_env => gopt_env%dimer_env
160 gopt_env%gopt_dimer_env%label = "ROT_OPT"
161 gopt_env%gopt_dimer_env%dimer_rotation = .true.
162 END SELECT
163 END SELECT
165 gopt_env%nfree = 6
166 gopt_env%label = "CELL_OPT"
167 gopt_env%tag = " CELL "
168 gopt_env%cell_method_id = gopt_param%cell_method_id
169 ALLOCATE (gopt_env%cell_env)
170 CALL cell_opt_env_create(gopt_env%cell_env, force_env, gopt_env%geo_section)
172 gopt_env%nfree = subsys%shell_particles%n_els
173 gopt_env%label = "SHELL_OPT"
174 gopt_env%tag = " SHELL-CORE "
175 gopt_env%shellcore_method_id = gopt_param%shellcore_method_id
176 END SELECT
177 END SUBROUTINE gopt_f_create
178
179! **************************************************************************************************
180!> \brief ...
181!> \param gopt_env the geometry optimization environment to retain
182!> \par History
183!> none
184! **************************************************************************************************
185 SUBROUTINE gopt_f_retain(gopt_env)
186 TYPE(gopt_f_type), POINTER :: gopt_env
187
188 cpassert(ASSOCIATED(gopt_env))
189 cpassert(gopt_env%ref_count > 0)
190 gopt_env%ref_count = gopt_env%ref_count + 1
191 END SUBROUTINE gopt_f_retain
192
193! **************************************************************************************************
194!> \brief ...
195!> \param gopt_env the geometry optimization environment to release
196!> \par History
197!> none
198! **************************************************************************************************
199 RECURSIVE SUBROUTINE gopt_f_release(gopt_env)
200 TYPE(gopt_f_type), POINTER :: gopt_env
201
202 IF (ASSOCIATED(gopt_env)) THEN
203 cpassert(gopt_env%ref_count > 0)
204 gopt_env%ref_count = gopt_env%ref_count - 1
205 IF (gopt_env%ref_count == 0) THEN
206 CALL force_env_release(gopt_env%force_env)
207 NULLIFY (gopt_env%force_env, &
208 gopt_env%globenv, &
209 gopt_env%motion_section, &
210 gopt_env%geo_section)
211 IF (ASSOCIATED(gopt_env%cell_env)) THEN
212 CALL cell_opt_env_release(gopt_env%cell_env)
213 DEALLOCATE (gopt_env%cell_env)
214 END IF
215 CALL dimer_env_release(gopt_env%dimer_env)
216 CALL gopt_f_release(gopt_env%gopt_dimer_env)
217 IF (ASSOCIATED(gopt_env%gopt_dimer_param)) DEALLOCATE (gopt_env%gopt_dimer_param)
218 CALL release_spgr_type(gopt_env%spgr)
219 DEALLOCATE (gopt_env)
220 END IF
221 END IF
222 END SUBROUTINE gopt_f_release
223
224END MODULE gopt_f_types
Contains type used for a Simulation Cell Optimization.
subroutine, public cell_opt_env_release(cell_env)
...
subroutine, public cell_opt_env_create(cell_env, force_env, geo_section)
...
types that represent a subsys, i.e. a part of the system
subroutine, public cp_subsys_get(subsys, ref_count, atomic_kinds, atomic_kind_set, particles, particle_set, local_particles, molecules, molecule_set, molecule_kinds, molecule_kind_set, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, natom, nparticle, ncore, nshell, nkind, atprop, virial, results, cell)
returns information about various attributes of the given subsys
Contains types used for a Dimer Method calculations.
Definition dimer_types.F:14
subroutine, public dimer_env_retain(dimer_env)
...
subroutine, public dimer_env_release(dimer_env)
...
subroutine, public dimer_env_create(dimer_env, subsys, globenv, dimer_section)
...
Interface for the force calculations.
integer function, public force_env_get_natom(force_env)
returns the number of atoms
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
subroutine, public force_env_retain(force_env)
retains the given force env
recursive subroutine, public force_env_release(force_env)
releases the given force env
Define type storing the global information of a run. Keep the amount of stored data small....
contains a functional that calculates the energy and its derivatives for the geometry optimizer
recursive subroutine, public gopt_f_create(gopt_env, gopt_param, force_env, globenv, geo_opt_section, eval_opt_geo)
...
subroutine, public gopt_f_retain(gopt_env)
...
recursive subroutine, public gopt_f_release(gopt_env)
...
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_shellcore_method_id
integer, parameter, public default_cell_method_id
integer, parameter, public default_minimization_method_id
integer, parameter, public default_ts_method_id
integer, parameter, public default_dimer_method_id
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
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
represent a simple array based list of the given type
Space Group Symmetry Type Module (version 1.0, Ferbruary 12, 2021)
subroutine, public release_spgr_type(spgr)
Release the SPGR type.
Type containing all informations abour the simulation cell optimization.
represents a system: atoms, molecules, their pos,vel,...
Defines the environment for a Dimer Method calculation.
Definition dimer_types.F:94
wrapper to abstract the force evaluation of the various methods
contains the initially parsed file and the initial parallel environment
calculates the potential energy of a system, and its derivatives