Line data Source code
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 : ! **************************************************************************************************
12 : MODULE thermostat_types
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
19 : USE extended_system_types, ONLY: lnhc_dealloc,&
20 : lnhc_init,&
21 : lnhc_parameters_type
22 : USE gle_system_types, ONLY: gle_dealloc,&
23 : gle_init,&
24 : gle_type
25 : USE input_constants, ONLY: do_region_global,&
26 : do_region_massive,&
27 : do_thermo_al,&
28 : do_thermo_csvr,&
29 : do_thermo_gle,&
30 : do_thermo_no_communication,&
31 : do_thermo_nose
32 : USE input_section_types, ONLY: section_vals_get_subs_vals,&
33 : section_vals_type,&
34 : section_vals_val_get
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, &
45 : allocate_thermostats, &
46 : release_thermostats, &
47 : create_thermostat_type, &
48 : release_thermostat_type, &
49 : thermostat_info_type, &
50 : release_thermostat_info, &
51 : set_thermostats
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 1786 : SUBROUTINE allocate_thermostats(thermostats)
109 : TYPE(thermostats_type), INTENT(OUT) :: thermostats
110 :
111 : ! Thermostats Info
112 1786 : ALLOCATE (thermostats%thermostat_info_part)
113 1786 : ALLOCATE (thermostats%thermostat_info_shell)
114 : !cjm
115 1786 : ALLOCATE (thermostats%thermostat_info_fast)
116 1786 : ALLOCATE (thermostats%thermostat_info_slow)
117 : !cjm
118 :
119 1786 : 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 1786 : SUBROUTINE release_thermostats(thermostats)
129 : TYPE(thermostats_type), INTENT(INOUT) :: thermostats
130 :
131 1786 : IF (ASSOCIATED(thermostats%thermostat_info_part)) THEN
132 0 : CALL release_thermostat_info(thermostats%thermostat_info_part)
133 0 : DEALLOCATE (thermostats%thermostat_info_part)
134 : END IF
135 1786 : IF (ASSOCIATED(thermostats%thermostat_info_shell)) THEN
136 0 : CALL release_thermostat_info(thermostats%thermostat_info_shell)
137 0 : DEALLOCATE (thermostats%thermostat_info_shell)
138 : END IF
139 1786 : IF (ASSOCIATED(thermostats%thermostat_info_fast)) THEN
140 1786 : CALL release_thermostat_info(thermostats%thermostat_info_fast)
141 1786 : DEALLOCATE (thermostats%thermostat_info_fast)
142 : END IF
143 1786 : IF (ASSOCIATED(thermostats%thermostat_info_slow)) THEN
144 1786 : CALL release_thermostat_info(thermostats%thermostat_info_slow)
145 1786 : DEALLOCATE (thermostats%thermostat_info_slow)
146 : END IF
147 1786 : IF (ASSOCIATED(thermostats%thermostat_fast)) THEN
148 0 : CALL release_thermostat_type(thermostats%thermostat_fast)
149 0 : DEALLOCATE (thermostats%thermostat_fast)
150 : END IF
151 1786 : IF (ASSOCIATED(thermostats%thermostat_slow)) THEN
152 0 : CALL release_thermostat_type(thermostats%thermostat_slow)
153 0 : DEALLOCATE (thermostats%thermostat_slow)
154 : END IF
155 1786 : IF (ASSOCIATED(thermostats%thermostat_part)) THEN
156 526 : CALL release_thermostat_type(thermostats%thermostat_part)
157 526 : DEALLOCATE (thermostats%thermostat_part)
158 : END IF
159 1786 : IF (ASSOCIATED(thermostats%thermostat_shell)) THEN
160 46 : CALL release_thermostat_type(thermostats%thermostat_shell)
161 46 : DEALLOCATE (thermostats%thermostat_shell)
162 : END IF
163 1786 : IF (ASSOCIATED(thermostats%thermostat_baro)) THEN
164 152 : CALL release_thermostat_type(thermostats%thermostat_baro)
165 152 : DEALLOCATE (thermostats%thermostat_baro)
166 : END IF
167 1786 : IF (ASSOCIATED(thermostats%thermostat_coef)) THEN
168 0 : CALL release_thermostat_type(thermostats%thermostat_coef)
169 0 : DEALLOCATE (thermostats%thermostat_coef)
170 : END IF
171 :
172 1786 : 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 724 : 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 724 : skip_region_loc = .FALSE.
198 152 : IF (PRESENT(skip_region)) skip_region_loc = skip_region
199 724 : thermostat%section => section
200 724 : thermostat%label = label
201 724 : region = do_region_global
202 :
203 724 : CALL section_vals_val_get(section, "TYPE", i_val=thermostat%type_of_thermostat)
204 724 : IF (.NOT. skip_region_loc) CALL section_vals_val_get(section, "REGION", i_val=region)
205 724 : IF (thermostat%type_of_thermostat == do_thermo_nose) THEN
206 556 : nose_section => section_vals_get_subs_vals(section, "NOSE")
207 556 : ALLOCATE (thermostat%nhc)
208 556 : CALL lnhc_init(thermostat%nhc, nose_section)
209 556 : thermostat%nhc%region = region
210 168 : ELSE IF (thermostat%type_of_thermostat == do_thermo_csvr) THEN
211 160 : csvr_section => section_vals_get_subs_vals(section, "CSVR")
212 160 : ALLOCATE (thermostat%csvr)
213 160 : CALL csvr_init(thermostat%csvr, simpar, csvr_section)
214 160 : thermostat%csvr%region = region
215 8 : ELSE IF (thermostat%type_of_thermostat == do_thermo_al) THEN
216 4 : al_section => section_vals_get_subs_vals(section, "AD_LANGEVIN")
217 4 : ALLOCATE (thermostat%al)
218 4 : CALL al_init(thermostat%al, simpar, al_section)
219 4 : thermostat%al%region = region
220 4 : ELSE IF (thermostat%type_of_thermostat == do_thermo_gle) THEN
221 4 : gle_section => section_vals_get_subs_vals(section, "GLE")
222 4 : ALLOCATE (thermostat%gle)
223 : CALL gle_init(thermostat%gle, dt=simpar%dt, temp=simpar%temp_ext, &
224 4 : section=gle_section)
225 4 : thermostat%gle%region = region
226 4 : CPASSERT(region == do_region_massive)
227 : END IF
228 :
229 724 : 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 7144 : SUBROUTINE release_thermostat_info(thermostat_info)
239 : TYPE(thermostat_info_type), INTENT(INOUT) :: thermostat_info
240 :
241 7144 : IF (ASSOCIATED(thermostat_info%map_loc_thermo_gen)) THEN
242 32 : DEALLOCATE (thermostat_info%map_loc_thermo_gen)
243 : END IF
244 :
245 7144 : 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 724 : SUBROUTINE release_thermostat_type(thermostat)
255 : TYPE(thermostat_type), INTENT(INOUT) :: thermostat
256 :
257 724 : NULLIFY (thermostat%section)
258 724 : IF (ASSOCIATED(thermostat%nhc)) THEN
259 556 : CALL lnhc_dealloc(thermostat%nhc)
260 : END IF
261 724 : IF (ASSOCIATED(thermostat%csvr)) THEN
262 160 : CALL csvr_dealloc(thermostat%csvr)
263 : END IF
264 724 : IF (ASSOCIATED(thermostat%al)) THEN
265 4 : CALL al_dealloc(thermostat%al)
266 : END IF
267 724 : IF (ASSOCIATED(thermostat%gle)) THEN
268 4 : CALL gle_dealloc(thermostat%gle)
269 : END IF
270 :
271 724 : 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 240 : SUBROUTINE set_thermostats(thermostats, dt_fact)
282 : TYPE(thermostats_type), POINTER :: thermostats
283 : REAL(KIND=dp), INTENT(IN), OPTIONAL :: dt_fact
284 :
285 240 : IF (ASSOCIATED(thermostats)) THEN
286 240 : IF (PRESENT(dt_fact)) THEN
287 : ! Particles
288 : !cjm
289 240 : IF (ASSOCIATED(thermostats%thermostat_fast)) THEN
290 0 : SELECT CASE (thermostats%thermostat_fast%type_of_thermostat)
291 : CASE (do_thermo_nose)
292 0 : thermostats%thermostat_fast%nhc%dt_fact = dt_fact
293 : END SELECT
294 : END IF
295 240 : IF (ASSOCIATED(thermostats%thermostat_slow)) THEN
296 0 : SELECT CASE (thermostats%thermostat_slow%type_of_thermostat)
297 : CASE (do_thermo_nose)
298 0 : thermostats%thermostat_slow%nhc%dt_fact = dt_fact
299 : END SELECT
300 : END IF
301 : !cjm
302 240 : IF (ASSOCIATED(thermostats%thermostat_part)) THEN
303 400 : SELECT CASE (thermostats%thermostat_part%type_of_thermostat)
304 : CASE (do_thermo_nose)
305 200 : thermostats%thermostat_part%nhc%dt_fact = dt_fact
306 : CASE (do_thermo_csvr)
307 0 : thermostats%thermostat_part%csvr%dt_fact = dt_fact
308 : CASE (do_thermo_al)
309 0 : thermostats%thermostat_part%al%dt_fact = dt_fact
310 : CASE (do_thermo_gle)
311 200 : thermostats%thermostat_part%gle%dt_fact = dt_fact
312 : END SELECT
313 : END IF
314 : ! Coefficients
315 240 : IF (ASSOCIATED(thermostats%thermostat_coef)) THEN
316 0 : SELECT CASE (thermostats%thermostat_coef%type_of_thermostat)
317 : CASE (do_thermo_nose)
318 0 : thermostats%thermostat_coef%nhc%dt_fact = dt_fact
319 : CASE (do_thermo_csvr)
320 0 : thermostats%thermostat_coef%csvr%dt_fact = dt_fact
321 : END SELECT
322 : END IF
323 : ! Shell
324 240 : IF (ASSOCIATED(thermostats%thermostat_shell)) THEN
325 40 : SELECT CASE (thermostats%thermostat_shell%type_of_thermostat)
326 : CASE (do_thermo_nose)
327 0 : thermostats%thermostat_shell%nhc%dt_fact = dt_fact
328 : CASE (do_thermo_csvr)
329 40 : thermostats%thermostat_shell%csvr%dt_fact = dt_fact
330 : END SELECT
331 : END IF
332 : ! Baro
333 240 : IF (ASSOCIATED(thermostats%thermostat_baro)) THEN
334 400 : SELECT CASE (thermostats%thermostat_baro%type_of_thermostat)
335 : CASE (do_thermo_nose)
336 200 : thermostats%thermostat_baro%nhc%dt_fact = dt_fact
337 : CASE (do_thermo_csvr)
338 200 : thermostats%thermostat_baro%csvr%dt_fact = dt_fact
339 : END SELECT
340 : END IF
341 : END IF
342 : END IF
343 240 : END SUBROUTINE set_thermostats
344 :
345 0 : END MODULE thermostat_types
|