(git:374b731)
Loading...
Searching...
No Matches
extended_system_types.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!> \brief Lumps all possible extended system variables into one
10!> type for easy access and passing
11!> \par History
12!> Teodoro Laino - 09.2007 - University of Zurich
13!> Cleaned the typo.. no need to have an extended
14!> type. Thermostat and Barostat type have been created
15!> \author CJM
16! **************************************************************************************************
18 USE bibliography, ONLY: nose1984a,&
19 nose1984b,&
20 cite_reference
24 USE kinds, ONLY: dp
25#include "./base/base_uses.f90"
26
27 IMPLICIT NONE
28 PRIVATE
29
30 PUBLIC :: lnhc_dealloc, &
31 lnhc_init, &
37
38 LOGICAL, PARAMETER, PUBLIC :: debug_isotropic_limit = .false.
39 LOGICAL, PARAMETER, PUBLIC :: debug_uniaxial_limit = .false.
40
41! **************************************************************************************************
43 REAL(kind=dp) :: eps
44 REAL(kind=dp) :: v
45 REAL(kind=dp) :: f
46 REAL(kind=dp) :: mass
47 END TYPE npt_info_type
48
49! **************************************************************************************************
50 TYPE nhc_info_type
51 INTEGER :: degrees_of_freedom
52 REAL(kind=dp) :: eta
53 REAL(kind=dp) :: v
54 REAL(kind=dp) :: f
55 REAL(kind=dp) :: nkt
56 REAL(kind=dp) :: mass
57 END TYPE nhc_info_type
58
59! **************************************************************************************************
60 TYPE point_info_type
61 REAL(kind=dp), POINTER :: point
62 END TYPE point_info_type
63
64! **************************************************************************************************
66 INTEGER :: dis_type
67 INTEGER, POINTER, DIMENSION(:) :: index, map_index
68 REAL(kind=dp), POINTER, DIMENSION(:) :: v_scale
69 REAL(kind=dp), POINTER, DIMENSION(:) :: s_kin
70 TYPE(point_info_type), POINTER, DIMENSION(:, :) :: p_scale
71 TYPE(point_info_type), POINTER, DIMENSION(:, :) :: p_kin
72 END TYPE map_info_type
73
74! **************************************************************************************************
76 INTEGER :: nyosh, nc, nhc_len
77 INTEGER :: glob_num_nhc, loc_num_nhc, region
78 REAL(kind=dp) :: tau_nhc, dt_fact
79 REAL(kind=dp), POINTER :: dt_yosh(:)
80 TYPE(nhc_info_type), POINTER :: nvt(:, :)
81 TYPE(map_info_type), POINTER :: map_info
83
84 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'extended_system_types'
85
86CONTAINS
87
88! **************************************************************************************************
89!> \brief Initialize type for Nose-Hoover thermostat
90!> \param lnhc ...
91!> \param section ...
92! **************************************************************************************************
93 SUBROUTINE lnhc_init(lnhc, section)
94 TYPE(lnhc_parameters_type), POINTER :: lnhc
95 TYPE(section_vals_type), POINTER :: section
96
97 NULLIFY (lnhc%dt_yosh)
98 NULLIFY (lnhc%nvt)
99 NULLIFY (lnhc%map_info)
100 lnhc%loc_num_nhc = 0
101 lnhc%glob_num_nhc = 0
102 lnhc%dt_fact = 1.0_dp
103 CALL cite_reference(nose1984a)
104 CALL cite_reference(nose1984b)
105 CALL section_vals_val_get(section, "LENGTH", i_val=lnhc%nhc_len)
106 CALL section_vals_val_get(section, "YOSHIDA", i_val=lnhc%nyosh)
107 CALL section_vals_val_get(section, "TIMECON", r_val=lnhc%tau_nhc)
108 CALL section_vals_val_get(section, "MTS", i_val=lnhc%nc)
109 CALL create_map_info_type(lnhc%map_info)
110
111 END SUBROUTINE lnhc_init
112
113! **************************************************************************************************
114!> \brief create the map_info type
115!> \param map_info ...
116! **************************************************************************************************
117 SUBROUTINE create_map_info_type(map_info)
118 TYPE(map_info_type), POINTER :: map_info
119
120 ALLOCATE (map_info)
121 NULLIFY (map_info%index, map_info%map_index)
122 NULLIFY (map_info%v_scale)
123 NULLIFY (map_info%p_scale)
124 NULLIFY (map_info%s_kin)
125 NULLIFY (map_info%p_kin)
126 map_info%dis_type = do_thermo_no_communication
127
128 END SUBROUTINE create_map_info_type
129
130! **************************************************************************************************
131!> \brief release the map_info type
132!> \param map_info ...
133! **************************************************************************************************
134 SUBROUTINE release_map_info_type(map_info)
135 TYPE(map_info_type), POINTER :: map_info
136
137 IF (ASSOCIATED(map_info)) THEN
138 IF (ASSOCIATED(map_info%p_kin)) THEN
139 DEALLOCATE (map_info%p_kin)
140 END IF
141 IF (ASSOCIATED(map_info%p_scale)) THEN
142 DEALLOCATE (map_info%p_scale)
143 END IF
144 IF (ASSOCIATED(map_info%v_scale)) THEN
145 DEALLOCATE (map_info%v_scale)
146 END IF
147 IF (ASSOCIATED(map_info%s_kin)) THEN
148 DEALLOCATE (map_info%s_kin)
149 END IF
150 IF (ASSOCIATED(map_info%index)) THEN
151 DEALLOCATE (map_info%index)
152 END IF
153 IF (ASSOCIATED(map_info%map_index)) THEN
154 DEALLOCATE (map_info%map_index)
155 END IF
156
157 DEALLOCATE (map_info)
158 END IF
159
160 END SUBROUTINE release_map_info_type
161
162! **************************************************************************************************
163!> \brief Deallocate type for Nose-Hoover thermostat
164!> \param lnhc ...
165! **************************************************************************************************
166 SUBROUTINE lnhc_dealloc(lnhc)
167 TYPE(lnhc_parameters_type), POINTER :: lnhc
168
169 IF (ASSOCIATED(lnhc)) THEN
170 IF (ASSOCIATED(lnhc%dt_yosh)) THEN
171 DEALLOCATE (lnhc%dt_yosh)
172 END IF
173 IF (ASSOCIATED(lnhc%nvt)) THEN
174 DEALLOCATE (lnhc%nvt)
175 END IF
176 CALL release_map_info_type(lnhc%map_info)
177 DEALLOCATE (lnhc)
178 END IF
179
180 END SUBROUTINE lnhc_dealloc
181
182END MODULE extended_system_types
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public nose1984a
integer, save, public nose1984b
Lumps all possible extended system variables into one type for easy access and passing.
subroutine, public lnhc_dealloc(lnhc)
Deallocate type for Nose-Hoover thermostat.
subroutine, public release_map_info_type(map_info)
release the map_info type
logical, parameter, public debug_uniaxial_limit
subroutine, public create_map_info_type(map_info)
create the map_info type
subroutine, public lnhc_init(lnhc, section)
Initialize type for Nose-Hoover thermostat.
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
objects that represent the structure of input sections and the data contained in an input section
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