(git:374b731)
Loading...
Searching...
No Matches
glbopt_master.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 Master's routines for global optimization
10!> \author Ole Schuett
11! **************************************************************************************************
32 USE input_constants, ONLY: dump_xmol,&
40 USE kinds, ONLY: default_string_length,&
41 dp,&
42 int_8
55 USE topology, ONLY: topology_control
56#include "../base/base_uses.f90"
57
58 IMPLICIT NONE
59 PRIVATE
60
61 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'glbopt_master'
62
63 PUBLIC :: glbopt_master_type
65 PUBLIC :: glbopt_master_steer
66
68 PRIVATE
69 REAL(KIND=dp) :: e_lowest = huge(1.0_dp)
70 REAL(kind=dp) :: e_target = tiny(1.0_dp)
71 INTEGER :: iw = 0
72 INTEGER :: progress_traj_unit = 0
73 INTEGER(int_8) :: total_md_steps = 0
74 INTEGER(int_8) :: total_gopt_steps = 0
75 INTEGER(int_8) :: count_reports = 0
76 INTEGER :: method = glbopt_do_minhop
77 TYPE(minhop_type), POINTER :: minhop => null()
78 TYPE(mincrawl_type), POINTER :: mincrawl => null()
79 INTEGER :: i_iteration = 0
80 TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set => null()
81 TYPE(particle_type), DIMENSION(:), POINTER :: particle_set => null()
82 TYPE(section_vals_type), POINTER :: glbopt_section => null()
83 END TYPE glbopt_master_type
84
85CONTAINS
86
87! **************************************************************************************************
88!> \brief Initializes the master of the global optimizer
89!> \param this ...
90!> \param para_env ...
91!> \param root_section ...
92!> \param n_walkers ...
93!> \param iw ...
94!> \author Ole Schuett
95! **************************************************************************************************
96 SUBROUTINE glbopt_master_init(this, para_env, root_section, n_walkers, iw)
97 TYPE(glbopt_master_type), INTENT(INOUT) :: this
98 TYPE(mp_para_env_type), POINTER :: para_env
99 TYPE(section_vals_type), POINTER :: root_section
100 INTEGER, INTENT(IN) :: n_walkers, iw
101
102 TYPE(cp_logger_type), POINTER :: logger
103
104 NULLIFY (logger)
105
106 this%iw = iw
107
108 this%glbopt_section => section_vals_get_subs_vals(root_section, "SWARM%GLOBAL_OPT")
109 CALL section_vals_retain(this%glbopt_section)
110
111 CALL section_vals_val_get(this%glbopt_section, "E_TARGET", r_val=this%E_target)
112 CALL section_vals_val_get(this%glbopt_section, "METHOD", i_val=this%method)
113
114 CALL glbopt_read_particle_set(this, para_env, root_section)
115
116 logger => cp_get_default_logger()
117 this%progress_traj_unit = cp_print_key_unit_nr(logger, &
118 this%glbopt_section, "PROGRESS_TRAJECTORY", &
119 middle_name="progress", extension=".xyz", &
120 file_action="WRITE", file_position="REWIND")
121
122 SELECT CASE (this%method)
123 CASE (glbopt_do_minhop)
124 ALLOCATE (this%minhop)
125 CALL minhop_init(this%minhop, this%glbopt_section, n_walkers, iw)
126 CASE (glbopt_do_mincrawl)
127 ALLOCATE (this%mincrawl)
128 CALL mincrawl_init(this%mincrawl, this%glbopt_section, n_walkers, iw, this%particle_set)
129 CASE DEFAULT
130 cpabort("Unknown glbopt_method")
131 END SELECT
132 END SUBROUTINE glbopt_master_init
133
134! **************************************************************************************************
135!> \brief Helper-routine for glbopt_master_init, reads part of SUBSYS-section
136!> \param this ...
137!> \param para_env ...
138!> \param root_section ...
139!> \author Ole Schuett
140! **************************************************************************************************
141 SUBROUTINE glbopt_read_particle_set(this, para_env, root_section)
142 TYPE(glbopt_master_type), INTENT(INOUT) :: this
143 TYPE(mp_para_env_type), POINTER :: para_env
144 TYPE(section_vals_type), POINTER :: root_section
145
146 TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
147 TYPE(colvar_p_type), DIMENSION(:), POINTER :: colvar_p
148 TYPE(exclusion_type), DIMENSION(:), POINTER :: exclusions
149 TYPE(global_constraint_type), POINTER :: gci
150 TYPE(molecule_kind_type), DIMENSION(:), POINTER :: molecule_kind_set
151 TYPE(molecule_type), DIMENSION(:), POINTER :: molecule_set
152 TYPE(particle_type), DIMENSION(:), POINTER :: particle_set
153 TYPE(section_vals_type), POINTER :: force_env_section, subsys_section
154
155 NULLIFY (atomic_kind_set, particle_set, molecule_kind_set, molecule_set)
156 NULLIFY (colvar_p, gci, exclusions, force_env_section, subsys_section)
157
158 force_env_section => section_vals_get_subs_vals(root_section, "FORCE_EVAL")
159 subsys_section => section_vals_get_subs_vals(root_section, "FORCE_EVAL%SUBSYS")
160
161 CALL topology_control(atomic_kind_set, &
162 particle_set, &
163 molecule_kind_set, &
164 molecule_set, &
165 colvar_p, &
166 gci, &
167 root_section=root_section, &
168 para_env=para_env, &
169 force_env_section=force_env_section, &
170 subsys_section=subsys_section, &
171 use_motion_section=.false., &
172 exclusions=exclusions)
173
174 !This is the only thing we need to write trajectories.
175 this%atomic_kind_set => atomic_kind_set
176 this%particle_set => particle_set
177 CALL exclusion_release(exclusions)
178 CALL deallocate_molecule_set(molecule_set)
179 CALL deallocate_molecule_kind_set(molecule_kind_set)
181 CALL colvar_p_release(colvar_p)
182
183 END SUBROUTINE glbopt_read_particle_set
184
185! **************************************************************************************************
186!> \brief Central steering routine of global optimizer
187!> \param this ...
188!> \param report ...
189!> \param cmd ...
190!> \param should_stop ...
191!> \author Ole Schuett
192! **************************************************************************************************
193 SUBROUTINE glbopt_master_steer(this, report, cmd, should_stop)
194 TYPE(glbopt_master_type), INTENT(INOUT) :: this
195 TYPE(swarm_message_type) :: report, cmd
196 LOGICAL, INTENT(INOUT) :: should_stop
197
198 CALL progress_report(this, report)
199
200 SELECT CASE (this%method)
201 CASE (glbopt_do_minhop)
202 CALL minhop_steer(this%minhop, report, cmd)
203 CASE (glbopt_do_mincrawl)
204 CALL mincrawl_steer(this%mincrawl, report, cmd)
205 CASE DEFAULT
206 cpabort("Unknown glbopt_method")
207 END SELECT
208
209 IF (this%E_lowest < this%E_target) THEN
210 IF (this%iw > 0) WRITE (this%iw, "(A,I8,A)") &
211 " GLBOPT| Reached E_pot < E_target after ", this%i_iteration, " iterations. Quitting."
212 should_stop = .true.
213 END IF
214 END SUBROUTINE glbopt_master_steer
215
216! **************************************************************************************************
217!> \brief Helper routine for glbopt_master_steer(), updates stats, etc.
218!> \param this ...
219!> \param report ...
220!> \author Ole Schuett
221! **************************************************************************************************
222 SUBROUTINE progress_report(this, report)
223 TYPE(glbopt_master_type), INTENT(INOUT) :: this
224 TYPE(swarm_message_type) :: report
225
226 CHARACTER(len=default_string_length) :: status
227 INTEGER :: gopt_steps, md_steps, report_worker_id
228 REAL(kind=dp) :: report_epot
229
230 this%i_iteration = this%i_iteration + 1
231
232 CALL swarm_message_get(report, "worker_id", report_worker_id)
233 CALL swarm_message_get(report, "status", status)
234
235 IF (trim(status) == "ok") THEN
236 CALL swarm_message_get(report, "Epot", report_epot)
237 CALL swarm_message_get(report, "md_steps", md_steps)
238 CALL swarm_message_get(report, "gopt_steps", gopt_steps)
239 this%total_md_steps = this%total_md_steps + md_steps
240 this%total_gopt_steps = this%total_gopt_steps + gopt_steps
241 this%count_reports = this%count_reports + 1
242
243 IF (report_epot < this%E_lowest) THEN
244 this%E_lowest = report_epot
245 CALL write_progress_traj(this, report)
246 END IF
247
248 IF (this%iw > 0) THEN
249 WRITE (this%iw, '(A,46X,I8)') &
250 " GLBOPT| Reporting worker ", report_worker_id
251 WRITE (this%iw, '(A,20X,E15.8)') &
252 " GLBOPT| Reported potential energy [Hartree] ", report_epot
253 WRITE (this%iw, '(A,13X,E15.8)') &
254 " GLBOPT| Lowest reported potential energy [Hartree] ", this%E_lowest
255 WRITE (this%iw, '(A,T71,F10.1)') &
256 " GLBOPT| Average number of MD steps", real(this%total_md_steps, kind=dp)/this%count_reports
257 WRITE (this%iw, '(A,T71,F10.1)') &
258 " GLBOPT| Average number of Geo-Opt steps", real(this%total_gopt_steps, kind=dp)/this%count_reports
259 END IF
260 END IF
261 END SUBROUTINE progress_report
262
263! **************************************************************************************************
264!> \brief Helper routine for progress_report(), write frames to trajectory.
265!> \param this ...
266!> \param report ...
267!> \author Ole Schuett
268! **************************************************************************************************
269 SUBROUTINE write_progress_traj(this, report)
270 TYPE(glbopt_master_type), INTENT(INOUT) :: this
271 TYPE(swarm_message_type), INTENT(IN) :: report
272
273 CHARACTER(len=default_string_length) :: title, unit_str
274 INTEGER :: report_worker_id
275 REAL(kind=dp) :: report_epot, unit_conv
276 REAL(kind=dp), DIMENSION(:), POINTER :: report_positions
277
278 NULLIFY (report_positions)
279
280 IF (this%progress_traj_unit <= 0) RETURN
281
282 CALL swarm_message_get(report, "worker_id", report_worker_id)
283 CALL swarm_message_get(report, "positions", report_positions)
284 CALL swarm_message_get(report, "Epot", report_epot)
285
286 WRITE (title, '(A,I8,A,I5,A,F20.10)') 'i = ', this%i_iteration, &
287 ' worker_id = ', report_worker_id, ' Epot = ', report_epot
288
289 !get the conversion factor for the length unit
290 CALL section_vals_val_get(this%glbopt_section, "PROGRESS_TRAJECTORY%UNIT", &
291 c_val=unit_str)
292 unit_conv = cp_unit_from_cp2k(1.0_dp, trim(unit_str))
293 CALL write_particle_coordinates(this%particle_set, &
294 iunit=this%progress_traj_unit, &
295 output_format=dump_xmol, &
296 content="POS", &
297 title=trim(title), &
298 array=report_positions, &
299 unit_conv=unit_conv)
300 DEALLOCATE (report_positions)
301 END SUBROUTINE write_progress_traj
302
303! **************************************************************************************************
304!> \brief Finalized the master of the global optimizer
305!> \param this ...
306!> \author Ole
307! **************************************************************************************************
308 SUBROUTINE glbopt_master_finalize(this)
309 TYPE(glbopt_master_type), INTENT(INOUT) :: this
310
311 TYPE(cp_logger_type), POINTER :: logger
312
313 NULLIFY (logger)
314
315 SELECT CASE (this%method)
316 CASE (glbopt_do_minhop)
317 CALL minhop_finalize(this%minhop)
318 DEALLOCATE (this%minhop)
319 CASE (glbopt_do_mincrawl)
320 CALL mincrawl_finalize(this%mincrawl)
321 DEALLOCATE (this%mincrawl)
322 CASE DEFAULT
323 cpabort("Unknown glbopt_method")
324 END SELECT
325
326 logger => cp_get_default_logger()
327 CALL cp_print_key_finished_output(this%progress_traj_unit, logger, &
328 this%glbopt_section, "PROGRESS_TRAJECTORY")
329
330 CALL section_vals_release(this%glbopt_section)
331 CALL deallocate_particle_set(this%particle_set)
332 CALL deallocate_atomic_kind_set(this%atomic_kind_set)
333
334 END SUBROUTINE glbopt_master_finalize
335
336END MODULE glbopt_master
337
Returns an entry from a swarm-message.
Define the atomic kind types and their sub types.
subroutine, public deallocate_atomic_kind_set(atomic_kind_set)
Destructor routine for a set of atomic kinds.
Initialize the collective variables types.
subroutine, public colvar_p_release(colvar_p)
Deallocate a set of colvar_p_type.
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,...
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
Definition cp_units.F:1179
an exclusion type
subroutine, public exclusion_release(exclusions)
Release exclusion type.
Master's routines for global optimization.
subroutine, public glbopt_master_steer(this, report, cmd, should_stop)
Central steering routine of global optimizer.
subroutine, public glbopt_master_init(this, para_env, root_section, n_walkers, iw)
Initializes the master of the global optimizer.
subroutine, public glbopt_master_finalize(this)
Finalized the master of the global optimizer.
Routines for the Minima Crawling global optimization scheme.
subroutine, public mincrawl_init(this, glbopt_section, n_workers, iw, particle_set)
Initializes master for Minima Crawling.
subroutine, public mincrawl_finalize(this)
Finalizes master for Minima Crawling.
subroutine, public mincrawl_steer(this, report, cmd)
Central steering routine of Minima Crawling.
Routines for the Minima Hopping global optimization scheme.
subroutine, public minhop_finalize(this)
Finalizes master for Minima Hopping.
subroutine, public minhop_init(this, glbopt_section, n_workers, iw)
Initializes master for Minima Hopping.
subroutine, public minhop_steer(this, report, cmd)
Central steering routine of Minima Hopping.
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public glbopt_do_minhop
integer, parameter, public dump_xmol
integer, parameter, public glbopt_do_mincrawl
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_retain(section_vals)
retains the given section values (see doc/ReferenceCounting.html)
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
recursive subroutine, public section_vals_release(section_vals)
releases the given object
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public int_8
Definition kinds.F:54
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
Interface to the message passing library MPI.
Define the molecule kind structure types and the corresponding functionality.
subroutine, public deallocate_molecule_kind_set(molecule_kind_set)
Deallocate a molecule kind set.
Define the data structure for the molecule information.
subroutine, public deallocate_molecule_set(molecule_set)
Deallocate a molecule set.
subroutine, public deallocate_global_constraint(gci)
Deallocate a global constraint.
Define methods related to particle_type.
subroutine, public write_particle_coordinates(particle_set, iunit, output_format, content, title, cell, array, unit_conv, charge_occup, charge_beta, charge_extended, print_kind)
Should be able to write a few formats e.g. xmol, and some binary format (dcd) some format can be used...
Define the data structure for the particle information.
subroutine, public deallocate_particle_set(particle_set)
Deallocate a particle set.
Swarm-message, a convenient data-container for with build-in serialization.
Control for reading in different topologies and coordinates.
Definition topology.F:13
subroutine, public topology_control(atomic_kind_set, particle_set, molecule_kind_set, molecule_set, colvar_p, gci, root_section, para_env, qmmm, qmmm_env, force_env_section, subsys_section, use_motion_section, exclusions, elkind)
...
Definition topology.F:125
Provides all information about an atomic kind.
type of a logger, at the moment it contains just a print level starting at which level it should be l...
A type used to store lists of exclusions and onfos.
stores all the informations relevant to an mpi environment