(git:374b731)
Loading...
Searching...
No Matches
glbopt_callback.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 Callback used by global geometry optimization schemes
10!> \author Ole Schuett
11! **************************************************************************************************
18 USE kinds, ONLY: dp
23#include "../base/base_uses.f90"
24
25 IMPLICIT NONE
26 PRIVATE
27
28 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'glbopt_callback'
29
30 PUBLIC :: glbopt_md_callback
31
32CONTAINS
33
34! **************************************************************************************************
35!> \brief Callback used to hook into the main MD-loop.
36!> It recognizes and counts bumps in the potential energy.
37!> When MD_BUMPS_MAX is reached, the MD simulations is stoped.
38!> \param mdctrl_data ...
39!> \param md_env ...
40!> \param should_stop ...
41!> \author Ole Schuett
42! **************************************************************************************************
43 SUBROUTINE glbopt_md_callback(mdctrl_data, md_env, should_stop)
44 TYPE(glbopt_mdctrl_data_type), POINTER :: mdctrl_data
45 TYPE(md_environment_type), POINTER :: md_env
46 LOGICAL, INTENT(inout) :: should_stop
47
48 INTEGER :: i, iw, n_atoms
49 INTEGER, POINTER :: itimes
50 LOGICAL :: passed_minimum
51 REAL(kind=dp), ALLOCATABLE, DIMENSION(:) :: positions
52 TYPE(cp_subsys_type), POINTER :: subsys
53 TYPE(force_env_type), POINTER :: force_env
54 TYPE(md_ener_type), POINTER :: md_ener
55
56 cpassert(ASSOCIATED(mdctrl_data))
57 cpassert(ASSOCIATED(md_env))
58
59 iw = mdctrl_data%output_unit
60
61 ! add new potential energy value to history
62 NULLIFY (md_ener, itimes)
63 CALL get_md_env(md_env=md_env, md_ener=md_ener, itimes=itimes, force_env=force_env)
64 mdctrl_data%itimes = itimes
65
66 mdctrl_data%epot_history(:) = eoshift(mdctrl_data%epot_history, shift=-1)
67 mdctrl_data%epot_history(1) = md_ener%epot
68
69 ! check if we passed a minimum
70 passed_minimum = .true.
71 DO i = 1, mdctrl_data%bump_steps_upwards
72 IF (mdctrl_data%epot_history(i) <= mdctrl_data%epot_history(i + 1)) &
73 passed_minimum = .false.
74 END DO
75
76 DO i = mdctrl_data%bump_steps_upwards + 1, mdctrl_data%bump_steps_upwards + mdctrl_data%bump_steps_downwards
77 IF (mdctrl_data%epot_history(i) >= mdctrl_data%epot_history(i + 1)) &
78 passed_minimum = .false.
79 END DO
80
81 ! count the passed bumps and stop md_run when md_bumps_max is reached.
82 IF (passed_minimum) &
83 mdctrl_data%md_bump_counter = mdctrl_data%md_bump_counter + 1
84
85 IF (mdctrl_data%md_bump_counter >= mdctrl_data%md_bumps_max) THEN
86 should_stop = .true.
87 IF (iw > 0) WRITE (iw, "(A)") " GLBOPT| Stopping MD because of MD_BUMPS_MAX."
88 END IF
89
90 CALL force_env_get(force_env, subsys=subsys)
91 CALL cp_subsys_get(subsys, natom=n_atoms)
92 ALLOCATE (positions(3*n_atoms))
93 CALL pack_subsys_particles(subsys, r=positions)
94
95 END SUBROUTINE glbopt_md_callback
96
97END MODULE glbopt_callback
98
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
subroutine, public pack_subsys_particles(subsys, f, r, s, v, fscale, cell)
Pack components of a subsystem particle sets into a single vector.
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
Callback used by global geometry optimization schemes.
subroutine, public glbopt_md_callback(mdctrl_data, md_env, should_stop)
Callback used to hook into the main MD-loop. It recognizes and counts bumps in the potential energy....
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Split md_ener module from md_environment_type.
subroutine, public get_md_env(md_env, itimes, constant, used_time, cell, simpar, npt, force_env, para_env, reftraj, t, init, first_time, fe_env, thermostats, barostat, thermostat_coeff, thermostat_part, thermostat_shell, thermostat_baro, thermostat_fast, thermostat_slow, md_ener, averages, thermal_regions, ehrenfest_md)
get components of MD environment type
A common interface for passing a callback into the md_run loop.
represents a system: atoms, molecules, their pos,vel,...
wrapper to abstract the force evaluation of the various methods