(git:ccc2433)
al_system_init.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 Noam Bernstein [noamb] 02.2012
10 ! **************************************************************************************************
12 
14  USE al_system_types, ONLY: al_system_type
15  USE distribution_1d_types, ONLY: distribution_1d_type
18  section_vals_type,&
20  USE kinds, ONLY: dp
21  USE message_passing, ONLY: mp_para_env_type
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_types, ONLY: thermostat_info_type
27 #include "../../base/base_uses.f90"
28 
29  IMPLICIT NONE
30 
31  PRIVATE
32  PUBLIC :: initialize_al_part
33 
34  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'al_system_init'
35 
36 CONTAINS
37 
38 ! **************************************************************************************************
39 !> \brief ...
40 !> \param thermostat_info ...
41 !> \param simpar ...
42 !> \param local_molecules ...
43 !> \param molecule ...
44 !> \param molecule_kind_set ...
45 !> \param para_env ...
46 !> \param al ...
47 !> \param al_section ...
48 !> \param gci ...
49 !> \author Noam Bernstein [noamb] 02.2012
50 ! **************************************************************************************************
51  SUBROUTINE initialize_al_part(thermostat_info, simpar, local_molecules, &
52  molecule, molecule_kind_set, para_env, al, al_section, &
53  gci)
54 
55  TYPE(thermostat_info_type), POINTER :: thermostat_info
56  TYPE(simpar_type), POINTER :: simpar
57  TYPE(distribution_1d_type), POINTER :: local_molecules
58  TYPE(molecule_type), POINTER :: molecule(:)
59  TYPE(molecule_kind_type), POINTER :: molecule_kind_set(:)
60  TYPE(mp_para_env_type), POINTER :: para_env
61  TYPE(al_system_type), POINTER :: al
62  TYPE(section_vals_type), POINTER :: al_section
63  TYPE(global_constraint_type), POINTER :: gci
64 
65  LOGICAL :: restart
66 
67  restart = .false.
68  CALL al_to_particle_mapping(thermostat_info, simpar, local_molecules, &
69  molecule, molecule_kind_set, al, para_env, gci)
70 
71  CALL restart_al(al, al_section, restart)
72 
73  IF (.NOT. restart) THEN
74  CALL init_al_variables(al)
75  END IF
76 
77  END SUBROUTINE initialize_al_part
78 
79 ! **************************************************************************************************
80 !> \brief ...
81 !> \param al ...
82 ! **************************************************************************************************
83  SUBROUTINE init_al_variables(al)
84  TYPE(al_system_type), POINTER :: al
85 
86  al%nvt(:)%mass = al%nvt(:)%nkt*al%tau_nh**2
87  al%nvt(:)%chi = 0.0_dp
88  END SUBROUTINE init_al_variables
89 
90 ! **************************************************************************************************
91 !> \brief ...
92 !> \param al ...
93 !> \param al_section ...
94 !> \param restart ...
95 !> \author Noam Bernstein [noamb] 02.2012
96 ! **************************************************************************************************
97  SUBROUTINE restart_al(al, al_section, restart)
98  TYPE(al_system_type), POINTER :: al
99  TYPE(section_vals_type), POINTER :: al_section
100  LOGICAL, INTENT(inout) :: restart
101 
102  INTEGER :: i, my_index, n_rep
103  LOGICAL :: explicit
104  TYPE(section_vals_type), POINTER :: work_section
105 
106  restart = .false.
107 
108  ! Possibly restart the initial thermostat DOF value
109  work_section => section_vals_get_subs_vals(section_vals=al_section, &
110  subsection_name="CHI")
111  CALL section_vals_get(work_section, explicit=explicit)
112  restart = explicit
113  IF (explicit) THEN
114  CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
115  n_rep_val=n_rep)
116  IF (n_rep == al%glob_num_al) THEN
117  DO i = 1, al%loc_num_al
118  my_index = al%map_info%index(i)
119  CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
120  i_rep_val=my_index, r_val=al%nvt(i)%chi)
121  END DO
122  ELSE
123  CALL cp_abort(__location__, &
124  'Number pf restartable stream not equal to the number of'// &
125  ' total thermostats!')
126  END IF
127  END IF
128 
129  ! Possibly restart the initial thermostat mass
130  work_section => section_vals_get_subs_vals(section_vals=al_section, &
131  subsection_name="MASS")
132  CALL section_vals_get(work_section, explicit=explicit)
133  IF (restart .NEQV. explicit) &
134  CALL cp_abort(__location__, &
135  "You need to define both CHI and MASS sections (or none) in the AD_LANGEVIN section")
136  restart = restart .AND. explicit
137  IF (explicit) THEN
138  CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
139  n_rep_val=n_rep)
140  IF (n_rep == al%glob_num_al) THEN
141  DO i = 1, al%loc_num_al
142  my_index = al%map_info%index(i)
143  CALL section_vals_val_get(section_vals=work_section, keyword_name="_DEFAULT_KEYWORD_", &
144  i_rep_val=my_index, r_val=al%nvt(i)%mass)
145  END DO
146  ELSE
147  CALL cp_abort(__location__, &
148  'Number pf restartable stream not equal to the number of'// &
149  ' total thermostats!')
150  END IF
151  END IF
152 
153  END SUBROUTINE restart_al
154 
155 END MODULE al_system_init
subroutine, public initialize_al_part(thermostat_info, simpar, local_molecules, molecule, molecule_kind_set, para_env, al, al_section, gci)
...
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.
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
subroutine, public section_vals_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
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
Thermostat structure: module containing thermostat available for MD.