(git:374b731)
Loading...
Searching...
No Matches
csvr_system_init.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!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
10! **************************************************************************************************
12
28 USE simpar_types, ONLY: simpar_type
30#include "../../base/base_uses.f90"
31
32 IMPLICIT NONE
33
34 PRIVATE
35
38
39 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'csvr_system_init'
40
41CONTAINS
42
43! **************************************************************************************************
44!> \brief fire up the thermostats, if NPT
45!> \param simpar ...
46!> \param csvr ...
47!> \param csvr_section ...
48!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
49! **************************************************************************************************
50 SUBROUTINE initialize_csvr_baro(simpar, csvr, csvr_section)
51
52 TYPE(simpar_type), POINTER :: simpar
53 TYPE(csvr_system_type), POINTER :: csvr
54 TYPE(section_vals_type), POINTER :: csvr_section
55
56 CALL csvr_to_barostat_mapping(simpar, csvr)
57 CALL restart_csvr(csvr, csvr_section)
58
59 END SUBROUTINE initialize_csvr_baro
60
61! **************************************************************************************************
62!> \brief ...
63!> \param thermostat_info ...
64!> \param simpar ...
65!> \param local_molecules ...
66!> \param molecule ...
67!> \param molecule_kind_set ...
68!> \param para_env ...
69!> \param csvr ...
70!> \param csvr_section ...
71!> \param gci ...
72!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
73! **************************************************************************************************
74 SUBROUTINE initialize_csvr_part(thermostat_info, simpar, local_molecules, &
75 molecule, molecule_kind_set, para_env, csvr, csvr_section, &
76 gci)
77
78 TYPE(thermostat_info_type), POINTER :: thermostat_info
79 TYPE(simpar_type), POINTER :: simpar
80 TYPE(distribution_1d_type), POINTER :: local_molecules
81 TYPE(molecule_type), POINTER :: molecule(:)
82 TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
83 TYPE(mp_para_env_type), POINTER :: para_env
84 TYPE(csvr_system_type), POINTER :: csvr
85 TYPE(section_vals_type), POINTER :: csvr_section
86 TYPE(global_constraint_type), POINTER :: gci
87
88 CALL csvr_to_particle_mapping(thermostat_info, simpar, local_molecules, &
89 molecule, molecule_kind_set, csvr, para_env, gci)
90 CALL restart_csvr(csvr, csvr_section)
91
92 END SUBROUTINE initialize_csvr_part
93
94! **************************************************************************************************
95!> \brief ...
96!> \param thermostat_info ...
97!> \param simpar ...
98!> \param local_molecules ...
99!> \param molecule ...
100!> \param molecule_kind_set ...
101!> \param para_env ...
102!> \param csvr ...
103!> \param csvr_section ...
104!> \param gci ...
105!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
106! **************************************************************************************************
107 SUBROUTINE initialize_csvr_shell(thermostat_info, simpar, local_molecules, &
108 molecule, molecule_kind_set, para_env, csvr, csvr_section, &
109 gci)
110
111 TYPE(thermostat_info_type), POINTER :: thermostat_info
112 TYPE(simpar_type), POINTER :: simpar
113 TYPE(distribution_1d_type), POINTER :: local_molecules
114 TYPE(molecule_type), POINTER :: molecule(:)
115 TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
116 TYPE(mp_para_env_type), POINTER :: para_env
117 TYPE(csvr_system_type), POINTER :: csvr
118 TYPE(section_vals_type), POINTER :: csvr_section
119 TYPE(global_constraint_type), POINTER :: gci
120
121 CALL csvr_to_shell_mapping(thermostat_info, simpar, local_molecules, &
122 molecule, molecule_kind_set, csvr, para_env, gci)
123 CALL restart_csvr(csvr, csvr_section)
124
125 END SUBROUTINE initialize_csvr_shell
126
127! **************************************************************************************************
128!> \brief ...
129!> \param csvr ...
130!> \param csvr_section ...
131!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
132! **************************************************************************************************
133 SUBROUTINE restart_csvr(csvr, csvr_section)
134 TYPE(csvr_system_type), POINTER :: csvr
135 TYPE(section_vals_type), POINTER :: csvr_section
136
137 CHARACTER(LEN=rng_record_length) :: rng_record
138 INTEGER :: i, my_index, n_rep
139 LOGICAL :: explicit
140 TYPE(section_vals_type), POINTER :: work_section
141
142! Possibly restart the initial thermostat energy
143
144 work_section => section_vals_get_subs_vals(section_vals=csvr_section, &
145 subsection_name="THERMOSTAT_ENERGY")
146 CALL section_vals_get(work_section, explicit=explicit)
147 IF (explicit) THEN
148 CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
149 n_rep_val=n_rep)
150 IF (n_rep == csvr%glob_num_csvr) THEN
151 DO i = 1, csvr%loc_num_csvr
152 my_index = csvr%map_info%index(i)
153 CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
154 i_rep_val=my_index, r_val=csvr%nvt(i)%thermostat_energy)
155 END DO
156 ELSE
157 CALL cp_abort(__location__, &
158 'Number pf restartable stream not equal to the number of'// &
159 ' total thermostats!')
160 END IF
161 END IF
162
163 ! Possibly restart the random number generators for the different thermostats
164 work_section => section_vals_get_subs_vals(section_vals=csvr_section, &
165 subsection_name="RNG_INIT")
166
167 CALL section_vals_get(work_section, explicit=explicit)
168 IF (explicit) THEN
169 CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
170 n_rep_val=n_rep)
171 IF (n_rep == csvr%glob_num_csvr) THEN
172 DO i = 1, csvr%loc_num_csvr
173 my_index = csvr%map_info%index(i)
174 CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
175 i_rep_val=my_index, c_val=rng_record)
176 csvr%nvt(i)%gaussian_rng_stream = rng_stream_type_from_record(rng_record)
177 END DO
178 ELSE
179 CALL cp_abort(__location__, &
180 'Number pf restartable stream not equal to the number of'// &
181 ' total thermostats!')
182 END IF
183 END IF
184 END SUBROUTINE restart_csvr
185
186END MODULE csvr_system_init
subroutine, public initialize_csvr_shell(thermostat_info, simpar, local_molecules, molecule, molecule_kind_set, para_env, csvr, csvr_section, gci)
...
subroutine, public initialize_csvr_baro(simpar, csvr, csvr_section)
fire up the thermostats, if NPT
subroutine, public initialize_csvr_part(thermostat_info, simpar, local_molecules, molecule, molecule_kind_set, para_env, csvr, csvr_section, gci)
...
subroutine, public csvr_to_particle_mapping(thermostat_info, simpar, local_molecules, molecule_set, molecule_kind_set, csvr, para_env, gci)
Creates the thermostatting maps.
subroutine, public csvr_to_barostat_mapping(simpar, csvr)
Creates the thermostatting for the barostat.
subroutine, public csvr_to_shell_mapping(thermostat_info, simpar, local_molecules, molecule_set, molecule_kind_set, csvr, para_env, gci)
...
Type for the canonical sampling through velocity rescaling.
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
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
subroutine, public section_vals_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
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
Interface to the message passing library MPI.
Define the molecule kind structure types and the corresponding functionality.
Define the data structure for the molecule information.
Parallel (pseudo)random number generator (RNG) for multiple streams and substreams of random numbers.
type(rng_stream_type) function, public rng_stream_type_from_record(rng_record)
Create a RNG stream from a record given as an internal file (string).
integer, parameter, public rng_record_length
Type for storing MD parameters.
Thermostat structure: module containing thermostat available for MD.
structure to store local (to a processor) ordered lists of integers.
stores all the informations relevant to an mpi environment
Simulation parameter type for molecular dynamics.