(git:374b731)
Loading...
Searching...
No Matches
md_environment_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!> \par History
10!> give the md_env its own para_env Joost VandeVondele 07.2003
11!> Teodoro Laino - 09.2007 - University of Zurich - generalizing thermostats
12!> and barostats
13!> \author CJM SEPT-12-02
14! **************************************************************************************************
20 USE barostat_types, ONLY: barostat_type,&
22 USE cell_types, ONLY: cell_type
29 USE input_constants, ONLY: do_thermo_al,&
33 USE kinds, ONLY: dp
34 USE md_ener_types, ONLY: md_ener_type,&
38 USE reftraj_types, ONLY: reftraj_type,&
40 USE simpar_types, ONLY: simpar_type
46#include "../base/base_uses.f90"
47
48 IMPLICIT NONE
49
50 PRIVATE
51
52! **************************************************************************************************
54 ! para_env is the parallel environment of the MD, i.e. the systems
55 ! that are dealt with by the integrator e.g in the PIMD this could
56 ! be parent of every bead.
57 PRIVATE
58 LOGICAL :: init = .false., first_time = .false., ehrenfest_md = .false.
59 INTEGER, POINTER :: itimes => null()
60 REAL(kind=dp), POINTER :: used_time => null(), t => null()
61 REAL(kind=dp), POINTER :: constant => null()
62 TYPE(mp_para_env_type), POINTER :: para_env => null()
63 TYPE(cell_type), POINTER :: cell => null()
64 TYPE(force_env_type), POINTER :: force_env => null()
65 TYPE(md_ener_type), POINTER :: md_ener => null()
66 TYPE(thermostats_type), POINTER :: thermostats => null()
67 TYPE(barostat_type), POINTER :: barostat => null()
68 TYPE(reftraj_type), POINTER :: reftraj => null()
69 TYPE(free_energy_type), POINTER :: fe_env => null()
70 TYPE(simpar_type), POINTER :: simpar => null()
71 TYPE(average_quantities_type), POINTER :: averages => null()
72 TYPE(thermal_regions_type), POINTER :: thermal_regions => null()
73 END TYPE md_environment_type
74
75 ! *** Public subroutines and data types ***
78
79 ! *** Global parameters ***
80 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'md_environment_types'
81
82CONTAINS
83
84! **************************************************************************************************
85!> \brief Creates MD environment
86!> Purpose: Initialise the integrator environment.
87!> retain the para_env for this environment (should be used for parallel
88!> communications)
89!> \param md_env the force environment to retain
90!> \param md_section ...
91!> \param para_env ...
92!> \param force_env ...
93! **************************************************************************************************
94 SUBROUTINE md_env_create(md_env, md_section, para_env, force_env)
95 TYPE(md_environment_type), INTENT(OUT) :: md_env
96 TYPE(section_vals_type), POINTER :: md_section
97 TYPE(mp_para_env_type), POINTER :: para_env
98 TYPE(force_env_type), POINTER :: force_env
99
100 TYPE(section_vals_type), POINTER :: averages_section
101
102 md_env%para_env => para_env
103 CALL md_env%para_env%retain()
104 ALLOCATE (md_env%itimes)
105 ALLOCATE (md_env%constant)
106 ALLOCATE (md_env%used_time)
107 ALLOCATE (md_env%t)
108 md_env%itimes = -1
109 md_env%constant = 0.0_dp
110 md_env%used_time = 0.0_dp
111 md_env%t = 0.0_dp
112 md_env%init = .true.
113 md_env%first_time = .true.
114 md_env%ehrenfest_md = .false.
115 averages_section => section_vals_get_subs_vals(md_section, "AVERAGES")
116 CALL create_averages(md_env%averages, averages_section, force_env=force_env)
117
118 END SUBROUTINE md_env_create
119
120! **************************************************************************************************
121!> \brief releases the given md env
122!> \param md_env the md environment to release
123!> \par History
124!> 04.2003 created [fawzi]
125!> \author fawzi
126! **************************************************************************************************
127 SUBROUTINE md_env_release(md_env)
128 TYPE(md_environment_type), INTENT(INOUT) :: md_env
129
130 CALL fe_env_release(md_env%fe_env)
131 CALL mp_para_env_release(md_env%para_env)
132 DEALLOCATE (md_env%itimes)
133 DEALLOCATE (md_env%constant)
134 DEALLOCATE (md_env%used_time)
135 DEALLOCATE (md_env%t)
136
137 NULLIFY (md_env%cell)
138 NULLIFY (md_env%simpar)
139 CALL release_barostat_type(md_env%barostat)
140 IF (ASSOCIATED(md_env%thermostats)) THEN
141 CALL release_thermostats(md_env%thermostats)
142 DEALLOCATE (md_env%thermostats)
143 END IF
144 IF (ASSOCIATED(md_env%reftraj)) THEN
145 CALL release_reftraj(md_env%reftraj)
146 DEALLOCATE (md_env%reftraj)
147 END IF
148 IF (ASSOCIATED(md_env%md_ener)) THEN
149 CALL release_md_ener(md_env%md_ener)
150 DEALLOCATE (md_env%md_ener)
151 END IF
152 CALL force_env_release(md_env%force_env)
153 CALL release_averages(md_env%averages)
154 IF (ASSOCIATED(md_env%thermal_regions)) THEN
155 CALL release_thermal_regions(md_env%thermal_regions)
156 DEALLOCATE (md_env%thermal_regions)
157 END IF
158
159 END SUBROUTINE md_env_release
160
161! **************************************************************************************************
162!> \brief get components of MD environment type
163!> \param md_env the force environment to retain
164!> \param itimes ...
165!> \param constant ...
166!> \param used_time ...
167!> \param cell ...
168!> \param simpar ...
169!> \param npt ...
170!> \param force_env ...
171!> \param para_env ...
172!> \param reftraj ...
173!> \param t ...
174!> \param init ...
175!> \param first_time ...
176!> \param fe_env ...
177!> \param thermostats ...
178!> \param barostat ...
179!> \param thermostat_coeff ...
180!> \param thermostat_part ...
181!> \param thermostat_shell ...
182!> \param thermostat_baro ...
183!> \param thermostat_fast ...
184!> \param thermostat_slow ...
185!> \param md_ener ...
186!> \param averages ...
187!> \param thermal_regions ...
188!> \param ehrenfest_md ...
189! **************************************************************************************************
190 SUBROUTINE get_md_env(md_env, itimes, constant, used_time, cell, simpar, npt, &
191 force_env, para_env, reftraj, t, init, first_time, fe_env, thermostats, barostat, &
192 thermostat_coeff, thermostat_part, thermostat_shell, thermostat_baro, &
193 thermostat_fast, thermostat_slow, md_ener, averages, &
194 thermal_regions, ehrenfest_md)
195
196 TYPE(md_environment_type), INTENT(IN) :: md_env
197 INTEGER, OPTIONAL, POINTER :: itimes
198 REAL(kind=dp), OPTIONAL, POINTER :: constant, used_time
199 TYPE(cell_type), OPTIONAL, POINTER :: cell
200 TYPE(simpar_type), OPTIONAL, POINTER :: simpar
201 TYPE(npt_info_type), OPTIONAL, POINTER :: npt(:, :)
202 TYPE(force_env_type), OPTIONAL, POINTER :: force_env
203 TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
204 TYPE(reftraj_type), OPTIONAL, POINTER :: reftraj
205 REAL(kind=dp), OPTIONAL, POINTER :: t
206 LOGICAL, OPTIONAL :: init, first_time
207 TYPE(free_energy_type), OPTIONAL, POINTER :: fe_env
208 TYPE(thermostats_type), OPTIONAL, POINTER :: thermostats
209 TYPE(barostat_type), OPTIONAL, POINTER :: barostat
210 TYPE(thermostat_type), OPTIONAL, POINTER :: thermostat_coeff, thermostat_part, &
211 thermostat_shell, thermostat_baro, &
212 thermostat_fast, thermostat_slow
213 TYPE(md_ener_type), OPTIONAL, POINTER :: md_ener
214 TYPE(average_quantities_type), OPTIONAL, POINTER :: averages
215 TYPE(thermal_regions_type), OPTIONAL, POINTER :: thermal_regions
216 LOGICAL, OPTIONAL :: ehrenfest_md
217
218 IF (PRESENT(itimes)) itimes => md_env%itimes
219 IF (PRESENT(fe_env)) fe_env => md_env%fe_env
220 IF (PRESENT(constant)) constant => md_env%constant
221 IF (PRESENT(used_time)) used_time => md_env%used_time
222 IF (PRESENT(t)) t => md_env%t
223 IF (PRESENT(cell)) cell => md_env%cell
224 IF (PRESENT(simpar)) simpar => md_env%simpar
225 IF (PRESENT(thermostats)) thermostats => md_env%thermostats
226 IF (PRESENT(barostat)) barostat => md_env%barostat
227 IF (PRESENT(thermostat_part) .OR. PRESENT(thermostat_coeff) .OR. &
228 PRESENT(thermostat_baro) .OR. PRESENT(thermostat_shell) .OR. &
229 PRESENT(thermostat_fast) .OR. PRESENT(thermostat_slow)) THEN
230 IF (ASSOCIATED(md_env%thermostats)) THEN
231 IF (PRESENT(thermostat_part)) THEN
232 thermostat_part => md_env%thermostats%thermostat_part
233 END IF
234 IF (PRESENT(thermostat_coeff)) THEN
235 thermostat_coeff => md_env%thermostats%thermostat_coef
236 END IF
237 IF (PRESENT(thermostat_shell)) THEN
238 thermostat_shell => md_env%thermostats%thermostat_shell
239 END IF
240 IF (PRESENT(thermostat_fast)) THEN
241 thermostat_fast => md_env%thermostats%thermostat_fast
242 END IF
243 IF (PRESENT(thermostat_slow)) THEN
244 thermostat_slow => md_env%thermostats%thermostat_slow
245 END IF
246 IF (PRESENT(thermostat_baro)) THEN
247 thermostat_baro => md_env%thermostats%thermostat_baro
248 END IF
249 END IF
250 END IF
251 IF (PRESENT(npt)) THEN
252 IF (ASSOCIATED(md_env%barostat)) THEN
253 npt => md_env%barostat%npt
254 END IF
255 END IF
256 IF (PRESENT(averages)) averages => md_env%averages
257 IF (PRESENT(force_env)) force_env => md_env%force_env
258 IF (PRESENT(para_env)) para_env => md_env%para_env
259 IF (PRESENT(reftraj)) reftraj => md_env%reftraj
260 IF (PRESENT(md_ener)) md_ener => md_env%md_ener
261 IF (PRESENT(init)) init = md_env%init
262 IF (PRESENT(first_time)) first_time = md_env%first_time
263 IF (PRESENT(ehrenfest_md)) ehrenfest_md = md_env%ehrenfest_md
264 IF (PRESENT(thermal_regions)) thermal_regions => md_env%thermal_regions
265
266 END SUBROUTINE get_md_env
267
268! **************************************************************************************************
269!> \brief Set the integrator environment to the correct program.
270!> \param md_env the force environment to retain
271!> \param itimes ...
272!> \param constant ...
273!> \param cell ...
274!> \param simpar ...
275!> \param fe_env ...
276!> \param force_env ...
277!> \param para_env ...
278!> \param init ...
279!> \param first_time ...
280!> \param thermostats ...
281!> \param barostat ...
282!> \param reftraj ...
283!> \param md_ener ...
284!> \param averages ...
285!> \param thermal_regions ...
286!> \param ehrenfest_md ...
287! **************************************************************************************************
288 SUBROUTINE set_md_env(md_env, itimes, constant, cell, simpar, fe_env, force_env, &
289 para_env, init, first_time, thermostats, barostat, reftraj, md_ener, averages, &
290 thermal_regions, ehrenfest_md)
291
292 TYPE(md_environment_type), INTENT(INOUT) :: md_env
293 INTEGER, OPTIONAL, POINTER :: itimes
294 REAL(kind=dp), OPTIONAL, POINTER :: constant
295 TYPE(cell_type), OPTIONAL, POINTER :: cell
296 TYPE(simpar_type), OPTIONAL, POINTER :: simpar
297 TYPE(free_energy_type), OPTIONAL, POINTER :: fe_env
298 TYPE(force_env_type), OPTIONAL, POINTER :: force_env
299 TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
300 LOGICAL, OPTIONAL :: init, first_time
301 TYPE(thermostats_type), OPTIONAL, POINTER :: thermostats
302 TYPE(barostat_type), OPTIONAL, POINTER :: barostat
303 TYPE(reftraj_type), OPTIONAL, POINTER :: reftraj
304 TYPE(md_ener_type), OPTIONAL, POINTER :: md_ener
305 TYPE(average_quantities_type), OPTIONAL, POINTER :: averages
306 TYPE(thermal_regions_type), OPTIONAL, POINTER :: thermal_regions
307 LOGICAL, OPTIONAL :: ehrenfest_md
308
309 IF (PRESENT(init)) md_env%init = init
310 IF (PRESENT(first_time)) md_env%first_time = first_time
311 IF (PRESENT(ehrenfest_md)) md_env%ehrenfest_md = ehrenfest_md
312 IF (PRESENT(cell)) md_env%cell => cell
313 IF (PRESENT(barostat)) THEN
314 IF (ASSOCIATED(md_env%barostat)) THEN
315 IF (.NOT. ASSOCIATED(md_env%barostat, barostat)) THEN
316 CALL release_barostat_type(md_env%barostat)
317 END IF
318 END IF
319 md_env%barostat => barostat
320 END IF
321 IF (PRESENT(thermostats)) THEN
322 IF (ASSOCIATED(md_env%thermostats)) THEN
323 IF (.NOT. ASSOCIATED(md_env%thermostats, thermostats)) THEN
324 CALL release_thermostats(md_env%thermostats)
325 DEALLOCATE (md_env%thermostats)
326 END IF
327 END IF
328 md_env%thermostats => thermostats
329 END IF
330 IF (PRESENT(simpar)) md_env%simpar => simpar
331 IF (PRESENT(itimes)) md_env%itimes => itimes
332 IF (PRESENT(fe_env)) md_env%fe_env => fe_env
333 IF (PRESENT(constant)) md_env%constant => constant
334 IF (PRESENT(para_env)) md_env%para_env => para_env
335 IF (PRESENT(force_env)) THEN
336 IF (ASSOCIATED(force_env)) THEN
337 CALL force_env_retain(force_env)
338 END IF
339 IF (ASSOCIATED(md_env%force_env)) THEN
340 CALL force_env_release(md_env%force_env)
341 END IF
342 md_env%force_env => force_env
343 END IF
344 IF (PRESENT(reftraj)) THEN
345 IF (ASSOCIATED(md_env%reftraj)) THEN
346 IF (.NOT. ASSOCIATED(md_env%reftraj, reftraj)) THEN
347 CALL release_reftraj(md_env%reftraj)
348 DEALLOCATE (md_env%reftraj)
349 END IF
350 END IF
351 md_env%reftraj => reftraj
352 END IF
353 IF (PRESENT(md_ener)) THEN
354 IF (ASSOCIATED(md_env%md_ener)) THEN
355 IF (.NOT. ASSOCIATED(md_env%md_ener, md_ener)) THEN
356 CALL release_md_ener(md_env%md_ener)
357 DEALLOCATE (md_env%md_ener)
358 END IF
359 END IF
360 md_env%md_ener => md_ener
361 END IF
362 IF (PRESENT(averages)) THEN
363 CALL release_averages(md_env%averages)
364 CALL retain_averages(averages)
365 md_env%averages => averages
366 END IF
367 IF (PRESENT(thermal_regions)) THEN
368 IF (ASSOCIATED(md_env%thermal_regions)) THEN
369 IF (.NOT. ASSOCIATED(md_env%thermal_regions, thermal_regions)) THEN
370 CALL release_thermal_regions(md_env%thermal_regions)
371 DEALLOCATE (md_env%thermal_regions)
372 END IF
373 END IF
374 md_env%thermal_regions => thermal_regions
375 END IF
376
377 END SUBROUTINE set_md_env
378
379! **************************************************************************************************
380!> \brief ...
381!> \param md_env ...
382!> \return ...
383!> \par History
384!> 02.2012 created [noamb]
385!> \author Noam Bernstein
386! **************************************************************************************************
387 PURE FUNCTION need_per_atom_wiener_process(md_env)
388 TYPE(md_environment_type), INTENT(IN) :: md_env
390
391! return value
392! check for Langevin ensemble
393
394 need_per_atom_wiener_process = (md_env%simpar%ensemble == langevin_ensemble)
396
397 ! check for adaptive-Langevin thermostat
398 IF (.NOT. ASSOCIATED(md_env%thermostats)) RETURN
399 IF (.NOT. ASSOCIATED(md_env%thermostats%thermostat_part)) RETURN
400 need_per_atom_wiener_process = (md_env%thermostats%thermostat_part%type_of_thermostat == do_thermo_al)
401
403
404END MODULE md_environment_types
Handles the type to compute averages during an MD.
subroutine, public create_averages(averages, averages_section, virial_avg, force_env)
Creates averages environment.
subroutine, public retain_averages(averages)
retains the given averages env
subroutine, public release_averages(averages)
releases the given averages env
Barostat structure: module containing barostat available for MD.
subroutine, public release_barostat_type(barostat)
...
Handles all functions related to the CELL.
Definition cell_types.F:15
Lumps all possible extended system variables into one type for easy access and passing.
Interface for the force calculations.
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
defines types for metadynamics calculation
subroutine, public fe_env_release(fe_env)
releases the fe_env
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public langevin_ensemble
integer, parameter, public do_thermo_al
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
Split md_ener module from md_environment_type.
subroutine, public release_md_ener(md_ener)
releases the given md_ener structure
subroutine, public set_md_env(md_env, itimes, constant, cell, simpar, fe_env, force_env, para_env, init, first_time, thermostats, barostat, reftraj, md_ener, averages, thermal_regions, ehrenfest_md)
Set the integrator environment to the correct program.
subroutine, public md_env_create(md_env, md_section, para_env, force_env)
Creates MD environment Purpose: Initialise the integrator environment. retain the para_env for this e...
subroutine, public md_env_release(md_env)
releases the given md env
pure logical function, public need_per_atom_wiener_process(md_env)
...
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
Interface to the message passing library MPI.
subroutine, public mp_para_env_release(para_env)
releases the para object (to be called when you don't want anymore the shared copy of this object)
initialization of the reftraj structure used to analyse previously generated trajectories
subroutine, public release_reftraj(reftraj)
...
Type for storing MD parameters.
Thermal regions type: to initialize and control the temperature of different regions.
subroutine, public release_thermal_regions(thermal_regions)
release thermal_regions
Thermostat structure: module containing thermostat available for MD.
subroutine, public release_thermostats(thermostats)
...
Type defining parameters related to the simulation cell.
Definition cell_types.F:55
wrapper to abstract the force evaluation of the various methods
stores all the informations relevant to an mpi environment
Simulation parameter type for molecular dynamics.