1!--------------------------------------------------------------------------------------------------!
2!   CP2K: A general program to perform molecular dynamics simulations                              !
3!   Copyright (C) 2000 - 2020  CP2K developers group                                               !
4!--------------------------------------------------------------------------------------------------!
5
6! **************************************************************************************************
7!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
8! **************************************************************************************************
9MODULE al_system_mapping
10
11   USE al_system_types,                 ONLY: al_system_type,&
12                                              al_thermo_create
13   USE cp_para_types,                   ONLY: cp_para_env_type
14   USE distribution_1d_types,           ONLY: distribution_1d_type
15   USE extended_system_types,           ONLY: map_info_type
16   USE input_constants,                 ONLY: &
17        do_thermo_communication, do_thermo_no_communication, isokin_ensemble, langevin_ensemble, &
18        npe_f_ensemble, npe_i_ensemble, nph_uniaxial_damped_ensemble, nph_uniaxial_ensemble, &
19        npt_f_ensemble, npt_i_ensemble, nve_ensemble, nvt_ensemble, reftraj_ensemble
20   USE kinds,                           ONLY: dp
21   USE message_passing,                 ONLY: mp_sum
22   USE molecule_kind_types,             ONLY: molecule_kind_type
23   USE molecule_types,                  ONLY: global_constraint_type,&
24                                              molecule_type
25   USE simpar_types,                    ONLY: simpar_type
26   USE thermostat_mapping,              ONLY: thermostat_mapping_region
27   USE thermostat_types,                ONLY: thermostat_info_type
28#include "../../base/base_uses.f90"
29
30   IMPLICIT NONE
31
32   PRIVATE
33
34   ! *** Global parameters ***
35
36   CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'al_system_mapping'
37
38   PUBLIC :: al_to_particle_mapping
39
40CONTAINS
41
42! **************************************************************************************************
43!> \brief Creates the thermostatting maps
44!> \param thermostat_info ...
45!> \param simpar ...
46!> \param local_molecules ...
47!> \param molecule_set ...
48!> \param molecule_kind_set ...
49!> \param al ...
50!> \param para_env ...
51!> \param gci ...
52!> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
53! **************************************************************************************************
54   SUBROUTINE al_to_particle_mapping(thermostat_info, simpar, local_molecules, &
55                                     molecule_set, molecule_kind_set, al, para_env, gci)
56
57      TYPE(thermostat_info_type), POINTER                :: thermostat_info
58      TYPE(simpar_type), POINTER                         :: simpar
59      TYPE(distribution_1d_type), POINTER                :: local_molecules
60      TYPE(molecule_type), POINTER                       :: molecule_set(:)
61      TYPE(molecule_kind_type), POINTER                  :: molecule_kind_set(:)
62      TYPE(al_system_type), POINTER                      :: al
63      TYPE(cp_para_env_type), POINTER                    :: para_env
64      TYPE(global_constraint_type), POINTER              :: gci
65
66      CHARACTER(LEN=*), PARAMETER :: routineN = 'al_to_particle_mapping', &
67         routineP = moduleN//':'//routineN
68
69      INTEGER                                            :: i, imap, j, natoms_local, &
70                                                            sum_of_thermostats
71      INTEGER, DIMENSION(:), POINTER                     :: deg_of_freedom, massive_atom_list
72      REAL(KIND=dp)                                      :: fac
73      TYPE(map_info_type), POINTER                       :: map_info
74
75      NULLIFY (massive_atom_list, deg_of_freedom)
76      SELECT CASE (simpar%ensemble)
77      CASE DEFAULT
78         CPABORT('Unknown ensemble!')
79      CASE (nve_ensemble, isokin_ensemble, npe_f_ensemble, npe_i_ensemble, nph_uniaxial_ensemble, &
80            nph_uniaxial_damped_ensemble, reftraj_ensemble, langevin_ensemble)
81         CPABORT('Never reach this point!')
82      CASE (nvt_ensemble, npt_i_ensemble, npt_f_ensemble)
83
84         CALL setup_al_thermostat(al, thermostat_info, deg_of_freedom, &
85                                  massive_atom_list, molecule_kind_set, local_molecules, molecule_set, &
86                                  para_env, natoms_local, simpar, sum_of_thermostats, gci)
87
88         ! Sum up the number of degrees of freedom on each thermostat.
89         ! first: initialize the target
90         map_info => al%map_info
91         map_info%s_kin = 0.0_dp
92         DO i = 1, 3
93            DO j = 1, natoms_local
94               map_info%p_kin(i, j)%point = map_info%p_kin(i, j)%point + 1
95            END DO
96         END DO
97
98         ! If thermostats are replicated but molecules distributed, we have to
99         ! sum s_kin over all processors
100         IF (map_info%dis_type == do_thermo_communication) CALL mp_sum(map_info%s_kin, para_env%group)
101
102         ! We know the total number of system thermostats.
103         IF ((sum_of_thermostats == 1) .AND. (map_info%dis_type /= do_thermo_no_communication)) THEN
104            fac = map_info%s_kin(1) - deg_of_freedom(1) - simpar%nfree_rot_transl
105            IF (fac == 0.0_dp) THEN
106               CPABORT('Zero degrees of freedom. Nothing to thermalize!')
107            END IF
108            al%nvt(1)%nkt = simpar%temp_ext*fac
109            al%nvt(1)%degrees_of_freedom = FLOOR(fac)
110         ELSE
111            DO i = 1, al%loc_num_al
112               imap = map_info%map_index(i)
113               fac = (map_info%s_kin(imap) - deg_of_freedom(i))
114               al%nvt(i)%nkt = simpar%temp_ext*fac
115               al%nvt(i)%degrees_of_freedom = FLOOR(fac)
116            END DO
117         END IF
118
119         DEALLOCATE (deg_of_freedom)
120         DEALLOCATE (massive_atom_list)
121      END SELECT
122
123   END SUBROUTINE al_to_particle_mapping
124
125! **************************************************************************************************
126!> \brief Main general setup for AD_LANGEVIN thermostats
127!> \param al ...
128!> \param thermostat_info ...
129!> \param deg_of_freedom ...
130!> \param massive_atom_list ...
131!> \param molecule_kind_set ...
132!> \param local_molecules ...
133!> \param molecule_set ...
134!> \param para_env ...
135!> \param natoms_local ...
136!> \param simpar ...
137!> \param sum_of_thermostats ...
138!> \param gci ...
139!> \param shell ...
140!> \author Teodoro Laino [tlaino] - University of Zurich - 10.2007
141! **************************************************************************************************
142   SUBROUTINE setup_al_thermostat(al, thermostat_info, deg_of_freedom, &
143                                  massive_atom_list, molecule_kind_set, local_molecules, molecule_set, &
144                                  para_env, natoms_local, simpar, sum_of_thermostats, gci, shell)
145
146      TYPE(al_system_type), POINTER                      :: al
147      TYPE(thermostat_info_type), POINTER                :: thermostat_info
148      INTEGER, DIMENSION(:), POINTER                     :: deg_of_freedom, massive_atom_list
149      TYPE(molecule_kind_type), POINTER                  :: molecule_kind_set(:)
150      TYPE(distribution_1d_type), POINTER                :: local_molecules
151      TYPE(molecule_type), POINTER                       :: molecule_set(:)
152      TYPE(cp_para_env_type), POINTER                    :: para_env
153      INTEGER, INTENT(OUT)                               :: natoms_local
154      TYPE(simpar_type), POINTER                         :: simpar
155      INTEGER, INTENT(OUT)                               :: sum_of_thermostats
156      TYPE(global_constraint_type), POINTER              :: gci
157      LOGICAL, INTENT(IN), OPTIONAL                      :: shell
158
159      CHARACTER(LEN=*), PARAMETER :: routineN = 'setup_al_thermostat', &
160         routineP = moduleN//':'//routineN
161
162      INTEGER                                            :: nkind, number, region
163      LOGICAL                                            :: do_shell
164      TYPE(map_info_type), POINTER                       :: map_info
165
166      do_shell = .FALSE.
167      IF (PRESENT(shell)) do_shell = shell
168      map_info => al%map_info
169
170      nkind = SIZE(molecule_kind_set)
171      sum_of_thermostats = thermostat_info%sum_of_thermostats
172      map_info%dis_type = thermostat_info%dis_type
173      number = thermostat_info%number_of_thermostats
174      region = al%region
175
176      CALL thermostat_mapping_region(map_info, deg_of_freedom, massive_atom_list, &
177                                     molecule_kind_set, local_molecules, molecule_set, para_env, natoms_local, &
178                                     simpar, number, region, gci, do_shell, thermostat_info%map_loc_thermo_gen, &
179                                     sum_of_thermostats)
180
181      ! This is the local number of available thermostats
182      al%loc_num_al = number
183      al%glob_num_al = sum_of_thermostats
184      CALL al_thermo_create(al)
185
186   END SUBROUTINE setup_al_thermostat
187
188END MODULE al_system_mapping
189