(git:374b731)
Loading...
Searching...
No Matches
al_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
17 USE input_constants, ONLY: &
22 USE kinds, ONLY: dp
27 USE simpar_types, ONLY: simpar_type
30#include "../../base/base_uses.f90"
31
32 IMPLICIT NONE
33
34 PRIVATE
35
36 ! *** Global parameters ***
37
38 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'al_system_mapping'
39
41
42CONTAINS
43
44! **************************************************************************************************
45!> \brief Creates the thermostatting maps
46!> \param thermostat_info ...
47!> \param simpar ...
48!> \param local_molecules ...
49!> \param molecule_set ...
50!> \param molecule_kind_set ...
51!> \param al ...
52!> \param para_env ...
53!> \param gci ...
54!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
55! **************************************************************************************************
56 SUBROUTINE al_to_particle_mapping(thermostat_info, simpar, local_molecules, &
57 molecule_set, molecule_kind_set, al, para_env, gci)
58
59 TYPE(thermostat_info_type), POINTER :: thermostat_info
60 TYPE(simpar_type), POINTER :: simpar
61 TYPE(distribution_1d_type), POINTER :: local_molecules
62 TYPE(molecule_type), POINTER :: molecule_set(:)
63 TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
64 TYPE(al_system_type), POINTER :: al
65 TYPE(mp_para_env_type), POINTER :: para_env
66 TYPE(global_constraint_type), POINTER :: gci
67
68 INTEGER :: i, imap, j, natoms_local, &
69 sum_of_thermostats
70 INTEGER, DIMENSION(:), POINTER :: deg_of_freedom, massive_atom_list
71 REAL(kind=dp) :: fac
72 TYPE(map_info_type), POINTER :: map_info
73
74 NULLIFY (massive_atom_list, deg_of_freedom)
75 SELECT CASE (simpar%ensemble)
76 CASE DEFAULT
77 cpabort('Unknown ensemble!')
80 cpabort('Never reach this point!')
82
83 CALL setup_al_thermostat(al, thermostat_info, deg_of_freedom, &
84 massive_atom_list, molecule_kind_set, local_molecules, molecule_set, &
85 para_env, natoms_local, simpar, sum_of_thermostats, gci)
86
87 ! Sum up the number of degrees of freedom on each thermostat.
88 ! first: initialize the target
89 map_info => al%map_info
90 map_info%s_kin = 0.0_dp
91 DO i = 1, 3
92 DO j = 1, natoms_local
93 map_info%p_kin(i, j)%point = map_info%p_kin(i, j)%point + 1
94 END DO
95 END DO
96
97 ! If thermostats are replicated but molecules distributed, we have to
98 ! sum s_kin over all processors
99 IF (map_info%dis_type == do_thermo_communication) CALL para_env%sum(map_info%s_kin)
100
101 ! We know the total number of system thermostats.
102 IF ((sum_of_thermostats == 1) .AND. (map_info%dis_type /= do_thermo_no_communication)) THEN
103 fac = map_info%s_kin(1) - deg_of_freedom(1) - simpar%nfree_rot_transl
104 IF (fac == 0.0_dp) THEN
105 cpabort('Zero degrees of freedom. Nothing to thermalize!')
106 END IF
107 al%nvt(1)%nkt = simpar%temp_ext*fac
108 al%nvt(1)%degrees_of_freedom = floor(fac)
109 ELSE
110 DO i = 1, al%loc_num_al
111 imap = map_info%map_index(i)
112 fac = (map_info%s_kin(imap) - deg_of_freedom(i))
113 al%nvt(i)%nkt = simpar%temp_ext*fac
114 al%nvt(i)%degrees_of_freedom = floor(fac)
115 END DO
116 END IF
117
118 DEALLOCATE (deg_of_freedom)
119 DEALLOCATE (massive_atom_list)
120 END SELECT
121
122 END SUBROUTINE al_to_particle_mapping
123
124! **************************************************************************************************
125!> \brief Main general setup for AD_LANGEVIN thermostats
126!> \param al ...
127!> \param thermostat_info ...
128!> \param deg_of_freedom ...
129!> \param massive_atom_list ...
130!> \param molecule_kind_set ...
131!> \param local_molecules ...
132!> \param molecule_set ...
133!> \param para_env ...
134!> \param natoms_local ...
135!> \param simpar ...
136!> \param sum_of_thermostats ...
137!> \param gci ...
138!> \param shell ...
139!> \author Teodoro Laino [tlaino] - University of Zurich - 10.2007
140! **************************************************************************************************
141 SUBROUTINE setup_al_thermostat(al, thermostat_info, deg_of_freedom, &
142 massive_atom_list, molecule_kind_set, local_molecules, molecule_set, &
143 para_env, natoms_local, simpar, sum_of_thermostats, gci, shell)
144
145 TYPE(al_system_type), POINTER :: al
146 TYPE(thermostat_info_type), POINTER :: thermostat_info
147 INTEGER, DIMENSION(:), POINTER :: deg_of_freedom, massive_atom_list
148 TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
149 TYPE(distribution_1d_type), POINTER :: local_molecules
150 TYPE(molecule_type), POINTER :: molecule_set(:)
151 TYPE(mp_para_env_type), POINTER :: para_env
152 INTEGER, INTENT(OUT) :: natoms_local
153 TYPE(simpar_type), POINTER :: simpar
154 INTEGER, INTENT(OUT) :: sum_of_thermostats
155 TYPE(global_constraint_type), POINTER :: gci
156 LOGICAL, INTENT(IN), OPTIONAL :: shell
157
158 INTEGER :: nkind, number, region
159 LOGICAL :: do_shell
160 TYPE(map_info_type), POINTER :: map_info
161
162 do_shell = .false.
163 IF (PRESENT(shell)) do_shell = shell
164 map_info => al%map_info
165
166 nkind = SIZE(molecule_kind_set)
167 sum_of_thermostats = thermostat_info%sum_of_thermostats
168 map_info%dis_type = thermostat_info%dis_type
169 number = thermostat_info%number_of_thermostats
170 region = al%region
171
172 CALL thermostat_mapping_region(map_info, deg_of_freedom, massive_atom_list, &
173 molecule_kind_set, local_molecules, molecule_set, para_env, natoms_local, &
174 simpar, number, region, gci, do_shell, thermostat_info%map_loc_thermo_gen, &
175 sum_of_thermostats)
176
177 ! This is the local number of available thermostats
178 al%loc_num_al = number
179 al%glob_num_al = sum_of_thermostats
180 CALL al_thermo_create(al)
181
182 END SUBROUTINE setup_al_thermostat
183
184END MODULE al_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 al_to_particle_mapping(thermostat_info, simpar, local_molecules, molecule_set, molecule_kind_set, al, para_env, gci)
Creates the thermostatting maps.
Type for the canonical sampling through velocity rescaling.
subroutine, public al_thermo_create(al)
Initialize NVT type for AD_LANGEVIN 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.
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 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.
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)
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.