(git:34ef472)
csvr_system_mapping.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 
13  USE csvr_system_types, ONLY: csvr_system_type,&
15  USE distribution_1d_types, ONLY: distribution_1d_type
17  map_info_type
18  USE input_constants, ONLY: &
23  USE kinds, ONLY: dp
24  USE message_passing, ONLY: mp_para_env_type
25  USE molecule_kind_types, ONLY: molecule_kind_type
26  USE molecule_types, ONLY: global_constraint_type,&
27  molecule_type
28  USE simpar_types, ONLY: simpar_type
31  USE thermostat_types, ONLY: thermostat_info_type
32 #include "../../base/base_uses.f90"
33 
34  IMPLICIT NONE
35 
36  PRIVATE
37 
38  ! *** Global parameters ***
39 
40  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'csvr_system_mapping'
41 
44 
45 CONTAINS
46 
47 ! **************************************************************************************************
48 !> \brief Creates the thermostatting for the barostat
49 !> \param simpar ...
50 !> \param csvr ...
51 !> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
52 ! **************************************************************************************************
53  SUBROUTINE csvr_to_barostat_mapping(simpar, csvr)
54  TYPE(simpar_type), POINTER :: simpar
55  TYPE(csvr_system_type), POINTER :: csvr
56 
57  INTEGER :: i, ndeg
58  TYPE(map_info_type), POINTER :: map_info
59 
60  SELECT CASE (simpar%ensemble)
61  CASE DEFAULT
62  cpabort('Never reach this point!')
64  map_info => csvr%map_info
65  map_info%dis_type = do_thermo_only_master
66 
67  ! Counting the total number of thermostats ( 1 for NPT_I, NPT_IA, and NPT_F )
68  csvr%loc_num_csvr = 1
69  csvr%glob_num_csvr = 1
70  IF (simpar%ensemble == npt_f_ensemble) THEN
71  ndeg = 9
72  ELSE
73  ndeg = 1
74  END IF
75 
76  CALL init_baro_map_info(map_info, ndeg, csvr%loc_num_csvr)
77  CALL csvr_thermo_create(csvr)
78 
79  ! Now that we know how many there are stick this into csvr%nkt
80  ! (number of degrees of freedom times k_B T )
81  DO i = 1, csvr%loc_num_csvr
82  csvr%nvt(i)%nkt = simpar%temp_baro_ext*ndeg
83  csvr%nvt(i)%degrees_of_freedom = ndeg
84  IF (debug_isotropic_limit) THEN
85  csvr%nvt(i)%nkt = simpar%temp_baro_ext
86  csvr%nvt(i)%degrees_of_freedom = 1
87  END IF
88  END DO
89  END SELECT
90 
91  END SUBROUTINE csvr_to_barostat_mapping
92 
93 ! **************************************************************************************************
94 !> \brief Creates the thermostatting maps
95 !> \param thermostat_info ...
96 !> \param simpar ...
97 !> \param local_molecules ...
98 !> \param molecule_set ...
99 !> \param molecule_kind_set ...
100 !> \param csvr ...
101 !> \param para_env ...
102 !> \param gci ...
103 !> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
104 ! **************************************************************************************************
105  SUBROUTINE csvr_to_particle_mapping(thermostat_info, simpar, local_molecules, &
106  molecule_set, molecule_kind_set, csvr, para_env, gci)
107 
108  TYPE(thermostat_info_type), POINTER :: thermostat_info
109  TYPE(simpar_type), POINTER :: simpar
110  TYPE(distribution_1d_type), POINTER :: local_molecules
111  TYPE(molecule_type), POINTER :: molecule_set(:)
112  TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
113  TYPE(csvr_system_type), POINTER :: csvr
114  TYPE(mp_para_env_type), POINTER :: para_env
115  TYPE(global_constraint_type), POINTER :: gci
116 
117  INTEGER :: i, imap, j, natoms_local, &
118  sum_of_thermostats
119  INTEGER, DIMENSION(:), POINTER :: deg_of_freedom, massive_atom_list
120  REAL(kind=dp) :: fac
121  TYPE(map_info_type), POINTER :: map_info
122 
123  NULLIFY (massive_atom_list, deg_of_freedom)
124  SELECT CASE (simpar%ensemble)
125  CASE DEFAULT
126  cpabort('Unknown ensemble!')
129  cpabort('Never reach this point!')
131 
132  CALL setup_csvr_thermostat(csvr, thermostat_info, deg_of_freedom, &
133  massive_atom_list, molecule_kind_set, local_molecules, molecule_set, &
134  para_env, natoms_local, simpar, sum_of_thermostats, gci)
135 
136  ! Sum up the number of degrees of freedom on each thermostat.
137  ! first: initialize the target
138  map_info => csvr%map_info
139  map_info%s_kin = 0.0_dp
140  DO i = 1, 3
141  DO j = 1, natoms_local
142  map_info%p_kin(i, j)%point = map_info%p_kin(i, j)%point + 1
143  END DO
144  END DO
145 
146  ! If thermostats are replicated but molecules distributed, we have to
147  ! sum s_kin over all processors
148  IF (map_info%dis_type == do_thermo_communication) CALL para_env%sum(map_info%s_kin)
149 
150  ! We know the total number of system thermostats.
151  IF ((sum_of_thermostats == 1) .AND. (map_info%dis_type /= do_thermo_no_communication)) THEN
152  fac = map_info%s_kin(1) - deg_of_freedom(1) - simpar%nfree_rot_transl
153  IF (fac == 0.0_dp) THEN
154  cpabort('Zero degrees of freedom. Nothing to thermalize!')
155  END IF
156  csvr%nvt(1)%nkt = simpar%temp_ext*fac
157  csvr%nvt(1)%degrees_of_freedom = floor(fac)
158  ELSE
159  DO i = 1, csvr%loc_num_csvr
160  imap = map_info%map_index(i)
161  fac = (map_info%s_kin(imap) - deg_of_freedom(i))
162  csvr%nvt(i)%nkt = simpar%temp_ext*fac
163  csvr%nvt(i)%degrees_of_freedom = floor(fac)
164  END DO
165  END IF
166 
167  DEALLOCATE (deg_of_freedom)
168  DEALLOCATE (massive_atom_list)
169  END SELECT
170 
171  END SUBROUTINE csvr_to_particle_mapping
172 
173 ! **************************************************************************************************
174 !> \brief Main general setup for CSVR thermostats
175 !> \param csvr ...
176 !> \param thermostat_info ...
177 !> \param deg_of_freedom ...
178 !> \param massive_atom_list ...
179 !> \param molecule_kind_set ...
180 !> \param local_molecules ...
181 !> \param molecule_set ...
182 !> \param para_env ...
183 !> \param natoms_local ...
184 !> \param simpar ...
185 !> \param sum_of_thermostats ...
186 !> \param gci ...
187 !> \param shell ...
188 !> \author Teodoro Laino [tlaino] - University of Zurich - 10.2007
189 ! **************************************************************************************************
190  SUBROUTINE setup_csvr_thermostat(csvr, thermostat_info, deg_of_freedom, &
191  massive_atom_list, molecule_kind_set, local_molecules, molecule_set, &
192  para_env, natoms_local, simpar, sum_of_thermostats, gci, shell)
193 
194  TYPE(csvr_system_type), POINTER :: csvr
195  TYPE(thermostat_info_type), POINTER :: thermostat_info
196  INTEGER, DIMENSION(:), POINTER :: deg_of_freedom, massive_atom_list
197  TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
198  TYPE(distribution_1d_type), POINTER :: local_molecules
199  TYPE(molecule_type), POINTER :: molecule_set(:)
200  TYPE(mp_para_env_type), POINTER :: para_env
201  INTEGER, INTENT(OUT) :: natoms_local
202  TYPE(simpar_type), POINTER :: simpar
203  INTEGER, INTENT(OUT) :: sum_of_thermostats
204  TYPE(global_constraint_type), POINTER :: gci
205  LOGICAL, INTENT(IN), OPTIONAL :: shell
206 
207  INTEGER :: nkind, number, region
208  LOGICAL :: do_shell
209  TYPE(map_info_type), POINTER :: map_info
210 
211  do_shell = .false.
212  IF (PRESENT(shell)) do_shell = shell
213  map_info => csvr%map_info
214 
215  nkind = SIZE(molecule_kind_set)
216  sum_of_thermostats = thermostat_info%sum_of_thermostats
217  map_info%dis_type = thermostat_info%dis_type
218  number = thermostat_info%number_of_thermostats
219  region = csvr%region
220 
221  CALL thermostat_mapping_region(map_info, deg_of_freedom, massive_atom_list, &
222  molecule_kind_set, local_molecules, molecule_set, para_env, natoms_local, &
223  simpar, number, region, gci, do_shell, thermostat_info%map_loc_thermo_gen, &
224  sum_of_thermostats)
225 
226  ! This is the local number of available thermostats
227  csvr%loc_num_csvr = number
228  csvr%glob_num_csvr = sum_of_thermostats
229  CALL csvr_thermo_create(csvr)
230 
231  END SUBROUTINE setup_csvr_thermostat
232 
233 ! **************************************************************************************************
234 !> \brief ...
235 !> \param thermostat_info ...
236 !> \param simpar ...
237 !> \param local_molecules ...
238 !> \param molecule_set ...
239 !> \param molecule_kind_set ...
240 !> \param csvr ...
241 !> \param para_env ...
242 !> \param gci ...
243 !> \author Teodoro Laino [tlaino] - University of Zurich - 10.2007
244 ! **************************************************************************************************
245  SUBROUTINE csvr_to_shell_mapping(thermostat_info, simpar, local_molecules, &
246  molecule_set, molecule_kind_set, csvr, para_env, gci)
247 
248  TYPE(thermostat_info_type), POINTER :: thermostat_info
249  TYPE(simpar_type), POINTER :: simpar
250  TYPE(distribution_1d_type), POINTER :: local_molecules
251  TYPE(molecule_type), POINTER :: molecule_set(:)
252  TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
253  TYPE(csvr_system_type), POINTER :: csvr
254  TYPE(mp_para_env_type), POINTER :: para_env
255  TYPE(global_constraint_type), POINTER :: gci
256 
257  INTEGER :: i, imap, j, nshell_local, &
258  sum_of_thermostats
259  INTEGER, DIMENSION(:), POINTER :: deg_of_freedom, massive_shell_list
260  TYPE(map_info_type), POINTER :: map_info
261 
262  NULLIFY (massive_shell_list, deg_of_freedom)
263 
264  SELECT CASE (simpar%ensemble)
265  CASE DEFAULT
266  cpabort('Unknown ensemble!')
269  cpabort('Never reach this point!')
272 
273  CALL setup_csvr_thermostat(csvr, thermostat_info, deg_of_freedom, massive_shell_list, &
274  molecule_kind_set, local_molecules, molecule_set, para_env, nshell_local, &
275  simpar, sum_of_thermostats, gci, shell=.true.)
276 
277  map_info => csvr%map_info
278  ! Sum up the number of degrees of freedom on each thermostat.
279  ! first: initialize the target
280  map_info%s_kin = 0.0_dp
281  DO j = 1, nshell_local
282  DO i = 1, 3
283  map_info%p_kin(i, j)%point = map_info%p_kin(i, j)%point + 1
284  END DO
285  END DO
286 
287  ! If thermostats are replicated but molecules distributed, we have to
288  ! sum s_kin over all processors
289  IF (map_info%dis_type == do_thermo_communication) CALL para_env%sum(map_info%s_kin)
290 
291  ! Now that we know how many there are stick this into csvr%nkt
292  ! (number of degrees of freedom times k_B T )
293  DO i = 1, csvr%loc_num_csvr
294  imap = map_info%map_index(i)
295  csvr%nvt(i)%nkt = simpar%temp_sh_ext*map_info%s_kin(imap)
296  csvr%nvt(i)%degrees_of_freedom = floor(map_info%s_kin(imap))
297  END DO
298 
299  DEALLOCATE (deg_of_freedom)
300  DEALLOCATE (massive_shell_list)
301  END SELECT
302 
303  END SUBROUTINE csvr_to_shell_mapping
304 
305 END MODULE csvr_system_mapping
static GRID_HOST_DEVICE double fac(const int i)
Factorial function, e.g. fac(5) = 5! = 120.
Definition: grid_common.h:48
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.
subroutine, public csvr_thermo_create(csvr)
Initialize NVT type for CSVR thermostat.
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
Lumps all possible extended system variables into one type for easy access and passing.
logical, parameter, public debug_isotropic_limit
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_thermo_no_communication
integer, parameter, public do_thermo_only_master
integer, parameter, public nph_uniaxial_ensemble
integer, parameter, public npt_i_ensemble
integer, parameter, public isokin_ensemble
integer, parameter, public nph_uniaxial_damped_ensemble
integer, parameter, public npe_f_ensemble
integer, parameter, public langevin_ensemble
integer, parameter, public npe_i_ensemble
integer, parameter, public npt_ia_ensemble
integer, parameter, public nve_ensemble
integer, parameter, public npt_f_ensemble
integer, parameter, public reftraj_ensemble
integer, parameter, public nvt_ensemble
integer, parameter, public do_thermo_communication
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
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.
Type for storing MD parameters.
Definition: simpar_types.F:14
subroutine, public thermostat_mapping_region(map_info, deg_of_freedom, massive_atom_list, molecule_kind_set, local_molecules, molecule_set, para_env, natoms_local, simpar, number, region, gci, shell, map_loc_thermo_gen, sum_of_thermostats)
Main general setup thermostat regions (thermostat independent)
subroutine, public init_baro_map_info(map_info, ndeg, num_thermo)
Initialize the map_info for barostat thermostat.
Thermostat structure: module containing thermostat available for MD.