(git:e7e05ae)
thermostat_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 Thermostat structure: module containing thermostat available for MD
10 !> \author teo [tlaino] - University of Zurich - 09.2007
11 ! **************************************************************************************************
13  USE al_system_types, ONLY: al_dealloc,&
14  al_init,&
15  al_system_type
16  USE csvr_system_types, ONLY: csvr_dealloc,&
17  csvr_init,&
18  csvr_system_type
20  lnhc_init,&
21  lnhc_parameters_type
22  USE gle_system_types, ONLY: gle_dealloc,&
23  gle_init,&
24  gle_type
27  do_thermo_al,&
33  section_vals_type,&
35  USE kinds, ONLY: default_string_length,&
36  dp
37  USE simpar_types, ONLY: simpar_type
38 #include "../../base/base_uses.f90"
39 
40  IMPLICIT NONE
41 
42  PRIVATE
43  PUBLIC :: thermostats_type, &
44  thermostat_type, &
49  thermostat_info_type, &
52 
53 ! **************************************************************************************************
54 !> \brief Define thermostat types
55 !> \param error variable to control error logging, stopping,...
56 !> see module cp_error_handling
57 !> \par History
58 !> 10.2007 created [tlaino] - Teodoro Laino - University of Zurich
59 !> \author Teodoro Laino
60 ! **************************************************************************************************
61  TYPE thermostats_type
62  TYPE(thermostat_info_type), POINTER :: thermostat_info_part => null()
63  TYPE(thermostat_info_type), POINTER :: thermostat_info_shell => null()
64 ! cjm
65  TYPE(thermostat_info_type), POINTER :: thermostat_info_fast => null()
66  TYPE(thermostat_type), POINTER :: thermostat_fast => null()
67  TYPE(thermostat_info_type), POINTER :: thermostat_info_slow => null()
68  TYPE(thermostat_type), POINTER :: thermostat_slow => null()
69 ! cjm
70  TYPE(thermostat_type), POINTER :: thermostat_part => null()
71  TYPE(thermostat_type), POINTER :: thermostat_coef => null()
72  TYPE(thermostat_type), POINTER :: thermostat_shell => null()
73  TYPE(thermostat_type), POINTER :: thermostat_baro => null()
74  END TYPE thermostats_type
75 
76  ! Single thermostat_type
77 ! **************************************************************************************************
78  TYPE thermostat_type
79  INTEGER :: type_of_thermostat = do_thermo_nose
80  CHARACTER(LEN=default_string_length) :: label = ""
81  TYPE(lnhc_parameters_type), POINTER :: nhc => null()
82  TYPE(csvr_system_type), POINTER :: csvr => null()
83  TYPE(al_system_type), POINTER :: al => null()
84  TYPE(gle_type), POINTER :: gle => null()
85  TYPE(section_vals_type), POINTER :: section => null()
86  END TYPE thermostat_type
87 
88  ! Global info type
89 ! **************************************************************************************************
90  TYPE thermostat_info_type
91  INTEGER :: sum_of_thermostats = 0
92  INTEGER :: number_of_thermostats = 0
93  INTEGER :: dis_type = do_thermo_no_communication
94  INTEGER, POINTER, DIMENSION(:) :: map_loc_thermo_gen => null()
95  END TYPE thermostat_info_type
96 
97  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'thermostat_types'
98 
99 CONTAINS
100 
101 ! **************************************************************************************************
102 !> \brief ...
103 !> \param thermostats ...
104 !> \par History
105 !> 09.2007 created [tlaino]
106 !> \author Teodoro Laino
107 ! **************************************************************************************************
108  SUBROUTINE allocate_thermostats(thermostats)
109  TYPE(thermostats_type), INTENT(OUT) :: thermostats
110 
111  ! Thermostats Info
112  ALLOCATE (thermostats%thermostat_info_part)
113  ALLOCATE (thermostats%thermostat_info_shell)
114 !cjm
115  ALLOCATE (thermostats%thermostat_info_fast)
116  ALLOCATE (thermostats%thermostat_info_slow)
117 !cjm
118 
119  END SUBROUTINE allocate_thermostats
120 
121 ! **************************************************************************************************
122 !> \brief ...
123 !> \param thermostats ...
124 !> \par History
125 !> 09.2007 created [tlaino]
126 !> \author Teodoro Laino
127 ! **************************************************************************************************
128  SUBROUTINE release_thermostats(thermostats)
129  TYPE(thermostats_type), INTENT(INOUT) :: thermostats
130 
131  IF (ASSOCIATED(thermostats%thermostat_info_part)) THEN
132  CALL release_thermostat_info(thermostats%thermostat_info_part)
133  DEALLOCATE (thermostats%thermostat_info_part)
134  END IF
135  IF (ASSOCIATED(thermostats%thermostat_info_shell)) THEN
136  CALL release_thermostat_info(thermostats%thermostat_info_shell)
137  DEALLOCATE (thermostats%thermostat_info_shell)
138  END IF
139  IF (ASSOCIATED(thermostats%thermostat_info_fast)) THEN
140  CALL release_thermostat_info(thermostats%thermostat_info_fast)
141  DEALLOCATE (thermostats%thermostat_info_fast)
142  END IF
143  IF (ASSOCIATED(thermostats%thermostat_info_slow)) THEN
144  CALL release_thermostat_info(thermostats%thermostat_info_slow)
145  DEALLOCATE (thermostats%thermostat_info_slow)
146  END IF
147  IF (ASSOCIATED(thermostats%thermostat_fast)) THEN
148  CALL release_thermostat_type(thermostats%thermostat_fast)
149  DEALLOCATE (thermostats%thermostat_fast)
150  END IF
151  IF (ASSOCIATED(thermostats%thermostat_slow)) THEN
152  CALL release_thermostat_type(thermostats%thermostat_slow)
153  DEALLOCATE (thermostats%thermostat_slow)
154  END IF
155  IF (ASSOCIATED(thermostats%thermostat_part)) THEN
156  CALL release_thermostat_type(thermostats%thermostat_part)
157  DEALLOCATE (thermostats%thermostat_part)
158  END IF
159  IF (ASSOCIATED(thermostats%thermostat_shell)) THEN
160  CALL release_thermostat_type(thermostats%thermostat_shell)
161  DEALLOCATE (thermostats%thermostat_shell)
162  END IF
163  IF (ASSOCIATED(thermostats%thermostat_baro)) THEN
164  CALL release_thermostat_type(thermostats%thermostat_baro)
165  DEALLOCATE (thermostats%thermostat_baro)
166  END IF
167  IF (ASSOCIATED(thermostats%thermostat_coef)) THEN
168  CALL release_thermostat_type(thermostats%thermostat_coef)
169  DEALLOCATE (thermostats%thermostat_coef)
170  END IF
171 
172  END SUBROUTINE release_thermostats
173 
174 ! **************************************************************************************************
175 !> \brief Create a thermostat type
176 !> \param thermostat ...
177 !> \param simpar ...
178 !> \param section ...
179 !> \param skip_region ...
180 !> \param label ...
181 !> \par History
182 !> 09.2007 created [tlaino]
183 !> \author Teodoro Laino
184 ! **************************************************************************************************
185  SUBROUTINE create_thermostat_type(thermostat, simpar, section, skip_region, label)
186  TYPE(thermostat_type), INTENT(OUT) :: thermostat
187  TYPE(simpar_type), POINTER :: simpar
188  TYPE(section_vals_type), POINTER :: section
189  LOGICAL, INTENT(IN), OPTIONAL :: skip_region
190  CHARACTER(LEN=*), INTENT(IN) :: label
191 
192  INTEGER :: region
193  LOGICAL :: skip_region_loc
194  TYPE(section_vals_type), POINTER :: al_section, csvr_section, gle_section, &
195  nose_section
196 
197  skip_region_loc = .false.
198  IF (PRESENT(skip_region)) skip_region_loc = skip_region
199  thermostat%section => section
200  thermostat%label = label
201  region = do_region_global
202 
203  CALL section_vals_val_get(section, "TYPE", i_val=thermostat%type_of_thermostat)
204  IF (.NOT. skip_region_loc) CALL section_vals_val_get(section, "REGION", i_val=region)
205  IF (thermostat%type_of_thermostat == do_thermo_nose) THEN
206  nose_section => section_vals_get_subs_vals(section, "NOSE")
207  ALLOCATE (thermostat%nhc)
208  CALL lnhc_init(thermostat%nhc, nose_section)
209  thermostat%nhc%region = region
210  ELSE IF (thermostat%type_of_thermostat == do_thermo_csvr) THEN
211  csvr_section => section_vals_get_subs_vals(section, "CSVR")
212  ALLOCATE (thermostat%csvr)
213  CALL csvr_init(thermostat%csvr, simpar, csvr_section)
214  thermostat%csvr%region = region
215  ELSE IF (thermostat%type_of_thermostat == do_thermo_al) THEN
216  al_section => section_vals_get_subs_vals(section, "AD_LANGEVIN")
217  ALLOCATE (thermostat%al)
218  CALL al_init(thermostat%al, simpar, al_section)
219  thermostat%al%region = region
220  ELSE IF (thermostat%type_of_thermostat == do_thermo_gle) THEN
221  gle_section => section_vals_get_subs_vals(section, "GLE")
222  ALLOCATE (thermostat%gle)
223  CALL gle_init(thermostat%gle, dt=simpar%dt, temp=simpar%temp_ext, &
224  section=gle_section)
225  thermostat%gle%region = region
226  cpassert(region == do_region_massive)
227  END IF
228 
229  END SUBROUTINE create_thermostat_type
230 
231 ! **************************************************************************************************
232 !> \brief ...
233 !> \param thermostat_info ...
234 !> \par History
235 !> 10.2007 created [tlaino]
236 !> \author Teodoro Laino
237 ! **************************************************************************************************
238  SUBROUTINE release_thermostat_info(thermostat_info)
239  TYPE(thermostat_info_type), INTENT(INOUT) :: thermostat_info
240 
241  IF (ASSOCIATED(thermostat_info%map_loc_thermo_gen)) THEN
242  DEALLOCATE (thermostat_info%map_loc_thermo_gen)
243  END IF
244 
245  END SUBROUTINE release_thermostat_info
246 
247 ! **************************************************************************************************
248 !> \brief ...
249 !> \param thermostat ...
250 !> \par History
251 !> 09.2007 created [tlaino]
252 !> \author Teodoro Laino
253 ! **************************************************************************************************
254  SUBROUTINE release_thermostat_type(thermostat)
255  TYPE(thermostat_type), INTENT(INOUT) :: thermostat
256 
257  NULLIFY (thermostat%section)
258  IF (ASSOCIATED(thermostat%nhc)) THEN
259  CALL lnhc_dealloc(thermostat%nhc)
260  END IF
261  IF (ASSOCIATED(thermostat%csvr)) THEN
262  CALL csvr_dealloc(thermostat%csvr)
263  END IF
264  IF (ASSOCIATED(thermostat%al)) THEN
265  CALL al_dealloc(thermostat%al)
266  END IF
267  IF (ASSOCIATED(thermostat%gle)) THEN
268  CALL gle_dealloc(thermostat%gle)
269  END IF
270 
271  END SUBROUTINE release_thermostat_type
272 
273 ! **************************************************************************************************
274 !> \brief access internal structures of thermostats
275 !> \param thermostats ...
276 !> \param dt_fact ...
277 !> \par History
278 !> 10.2008 created [tlaino]
279 !> \author Teodoro Laino [tlaino] - University of Zurich
280 ! **************************************************************************************************
281  SUBROUTINE set_thermostats(thermostats, dt_fact)
282  TYPE(thermostats_type), POINTER :: thermostats
283  REAL(kind=dp), INTENT(IN), OPTIONAL :: dt_fact
284 
285  IF (ASSOCIATED(thermostats)) THEN
286  IF (PRESENT(dt_fact)) THEN
287  ! Particles
288 !cjm
289  IF (ASSOCIATED(thermostats%thermostat_fast)) THEN
290  SELECT CASE (thermostats%thermostat_fast%type_of_thermostat)
291  CASE (do_thermo_nose)
292  thermostats%thermostat_fast%nhc%dt_fact = dt_fact
293  END SELECT
294  END IF
295  IF (ASSOCIATED(thermostats%thermostat_slow)) THEN
296  SELECT CASE (thermostats%thermostat_slow%type_of_thermostat)
297  CASE (do_thermo_nose)
298  thermostats%thermostat_slow%nhc%dt_fact = dt_fact
299  END SELECT
300  END IF
301 !cjm
302  IF (ASSOCIATED(thermostats%thermostat_part)) THEN
303  SELECT CASE (thermostats%thermostat_part%type_of_thermostat)
304  CASE (do_thermo_nose)
305  thermostats%thermostat_part%nhc%dt_fact = dt_fact
306  CASE (do_thermo_csvr)
307  thermostats%thermostat_part%csvr%dt_fact = dt_fact
308  CASE (do_thermo_al)
309  thermostats%thermostat_part%al%dt_fact = dt_fact
310  CASE (do_thermo_gle)
311  thermostats%thermostat_part%gle%dt_fact = dt_fact
312  END SELECT
313  END IF
314  ! Coefficients
315  IF (ASSOCIATED(thermostats%thermostat_coef)) THEN
316  SELECT CASE (thermostats%thermostat_coef%type_of_thermostat)
317  CASE (do_thermo_nose)
318  thermostats%thermostat_coef%nhc%dt_fact = dt_fact
319  CASE (do_thermo_csvr)
320  thermostats%thermostat_coef%csvr%dt_fact = dt_fact
321  END SELECT
322  END IF
323  ! Shell
324  IF (ASSOCIATED(thermostats%thermostat_shell)) THEN
325  SELECT CASE (thermostats%thermostat_shell%type_of_thermostat)
326  CASE (do_thermo_nose)
327  thermostats%thermostat_shell%nhc%dt_fact = dt_fact
328  CASE (do_thermo_csvr)
329  thermostats%thermostat_shell%csvr%dt_fact = dt_fact
330  END SELECT
331  END IF
332  ! Baro
333  IF (ASSOCIATED(thermostats%thermostat_baro)) THEN
334  SELECT CASE (thermostats%thermostat_baro%type_of_thermostat)
335  CASE (do_thermo_nose)
336  thermostats%thermostat_baro%nhc%dt_fact = dt_fact
337  CASE (do_thermo_csvr)
338  thermostats%thermostat_baro%csvr%dt_fact = dt_fact
339  END SELECT
340  END IF
341  END IF
342  END IF
343  END SUBROUTINE set_thermostats
344 
345 END MODULE thermostat_types
Type for the canonical sampling through velocity rescaling.
subroutine, public al_dealloc(al)
Deallocate type for AD_LANGEVIN thermostat.
subroutine, public al_init(al, simpar, section)
Initialize type for Adaptive Langevin (AD_LANGEVIN)
Type for the canonical sampling through velocity rescaling.
subroutine, public csvr_dealloc(csvr)
Deallocate type for CSVR thermostat.
subroutine, public csvr_init(csvr, simpar, section)
Initialize type for Canonical Sampling through Velocity Rescaling (CSVR)
Lumps all possible extended system variables into one type for easy access and passing.
subroutine, public lnhc_dealloc(lnhc)
Deallocate type for Nose-Hoover thermostat.
subroutine, public lnhc_init(lnhc, section)
Initialize type for Nose-Hoover thermostat.
subroutine, public gle_dealloc(gle)
Deallocate type for GLE thermostat.
subroutine, public gle_init(gle, dt, temp, section)
...
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_thermo_nose
integer, parameter, public do_thermo_no_communication
integer, parameter, public do_thermo_al
integer, parameter, public do_thermo_csvr
integer, parameter, public do_thermo_gle
integer, parameter, public do_region_massive
integer, parameter, public do_region_global
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_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
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
Type for storing MD parameters.
Definition: simpar_types.F:14
Thermostat structure: module containing thermostat available for MD.
subroutine, public allocate_thermostats(thermostats)
...
subroutine, public release_thermostat_info(thermostat_info)
...
subroutine, public release_thermostat_type(thermostat)
...
subroutine, public create_thermostat_type(thermostat, simpar, section, skip_region, label)
Create a thermostat type.
subroutine, public set_thermostats(thermostats, dt_fact)
access internal structures of thermostats
subroutine, public release_thermostats(thermostats)
...