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 : !> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
10 : ! **************************************************************************************************
11 : MODULE csvr_system_init
12 :
13 : USE csvr_system_mapping, ONLY: csvr_to_barostat_mapping,&
14 : csvr_to_particle_mapping,&
15 : csvr_to_shell_mapping
16 : USE csvr_system_types, ONLY: csvr_system_type
17 : USE distribution_1d_types, ONLY: distribution_1d_type
18 : USE input_section_types, ONLY: section_vals_get,&
19 : section_vals_get_subs_vals,&
20 : section_vals_type,&
21 : section_vals_val_get
22 : USE message_passing, ONLY: mp_para_env_type
23 : USE molecule_kind_types, ONLY: molecule_kind_type
24 : USE molecule_types, ONLY: global_constraint_type,&
25 : molecule_type
26 : USE parallel_rng_types, ONLY: rng_record_length,&
27 : rng_stream_type_from_record
28 : USE simpar_types, ONLY: simpar_type
29 : USE thermostat_types, ONLY: thermostat_info_type
30 : #include "../../base/base_uses.f90"
31 :
32 : IMPLICIT NONE
33 :
34 : PRIVATE
35 :
36 : PUBLIC :: initialize_csvr_part, initialize_csvr_baro, &
37 : initialize_csvr_shell
38 :
39 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'csvr_system_init'
40 :
41 : CONTAINS
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 32 : 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 32 : CALL csvr_to_barostat_mapping(simpar, csvr)
57 32 : CALL restart_csvr(csvr, csvr_section)
58 :
59 32 : 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 122 : 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 122 : molecule, molecule_kind_set, csvr, para_env, gci)
90 122 : CALL restart_csvr(csvr, csvr_section)
91 :
92 122 : 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 6 : 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 6 : molecule, molecule_kind_set, csvr, para_env, gci)
123 6 : CALL restart_csvr(csvr, csvr_section)
124 :
125 6 : 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 480 : 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 160 : subsection_name="THERMOSTAT_ENERGY")
146 160 : CALL section_vals_get(work_section, explicit=explicit)
147 160 : IF (explicit) THEN
148 : CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
149 22 : n_rep_val=n_rep)
150 22 : IF (n_rep == csvr%glob_num_csvr) THEN
151 614 : DO i = 1, csvr%loc_num_csvr
152 592 : my_index = csvr%map_info%index(i)
153 : CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
154 614 : 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 0 : ' 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 160 : subsection_name="RNG_INIT")
166 :
167 160 : CALL section_vals_get(work_section, explicit=explicit)
168 160 : IF (explicit) THEN
169 : CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
170 22 : n_rep_val=n_rep)
171 22 : IF (n_rep == csvr%glob_num_csvr) THEN
172 614 : DO i = 1, csvr%loc_num_csvr
173 592 : my_index = csvr%map_info%index(i)
174 : CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
175 592 : i_rep_val=my_index, c_val=rng_record)
176 614 : 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 0 : ' total thermostats!')
182 : END IF
183 : END IF
184 160 : END SUBROUTINE restart_csvr
185 :
186 : END MODULE csvr_system_init
|