(git:374b731)
Loading...
Searching...
No Matches
gle_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
10!> \par History
11!> \author MI 07.2009
12! **************************************************************************************************
14 USE bibliography, ONLY: ceriotti2009,&
16 cite_reference
22 USE kinds, ONLY: dp
23 USE parallel_rng_types, ONLY: gaussian,&
26 USE string_utilities, ONLY: compress
27#include "./base/base_uses.f90"
28
29 IMPLICIT NONE
30 PRIVATE
31
32 PUBLIC :: gle_dealloc, &
35
36!
37 TYPE gle_thermo_type
38 INTEGER :: degrees_of_freedom
39 REAL(KIND=dp) :: nkt, kin_energy, thermostat_energy
40 REAL(KIND=dp), DIMENSION(:), POINTER :: s
41 TYPE(rng_stream_type) :: gaussian_rng_stream
42 END TYPE gle_thermo_type
43
44! **************************************************************************************************
46 INTEGER :: ndim
47 INTEGER :: glob_num_gle, loc_num_gle, region
48 INTEGER, DIMENSION(:), POINTER :: mal
49 REAL(dp) :: temp, dt, dt_fact
50 REAL(dp), POINTER :: gle_s(:, :), gle_t(:, :)
51 REAL(dp), POINTER :: a_mat(:, :), c_mat(:, :)
52 TYPE(gle_thermo_type), POINTER :: nvt(:)
53 TYPE(map_info_type), POINTER :: map_info
54 END TYPE gle_type
55
56 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'gle_system_types'
57
58CONTAINS
59
60! **************************************************************************************************
61!> \brief ...
62!> \param gle ...
63!> \param dt ...
64!> \param temp ...
65!> \param section ...
66!> \param
67! **************************************************************************************************
68 SUBROUTINE gle_init(gle, dt, temp, section)
69 TYPE(gle_type), POINTER :: gle
70 REAL(dp), INTENT(IN) :: dt, temp
71 TYPE(section_vals_type), POINTER :: section
72
73 INTEGER :: i, ir, j, k, n_rep
74 REAL(dp), DIMENSION(:), POINTER :: list
75 REAL(kind=dp) :: a_scale
76
77 NULLIFY (gle%nvt)
78 NULLIFY (gle%gle_s)
79 NULLIFY (gle%gle_t)
80 NULLIFY (gle%map_info)
81 gle%loc_num_gle = 0
82 gle%glob_num_gle = 0
83 gle%temp = temp
84 gle%dt = dt*0.5_dp
85
86 CALL cite_reference(ceriotti2009)
87 CALL cite_reference(ceriotti2009b)
88 CALL section_vals_val_get(section, "NDIM", i_val=gle%ndim)
89 CALL section_vals_val_get(section, "A_SCALE", r_val=a_scale)
90
91 ALLOCATE (gle%a_mat(gle%ndim, gle%ndim))
92 ALLOCATE (gle%c_mat(gle%ndim, gle%ndim))
93 ALLOCATE (gle%gle_s(gle%ndim, gle%ndim))
94 ALLOCATE (gle%gle_t(gle%ndim, gle%ndim))
95
96 CALL section_vals_val_get(section, "A_LIST", n_rep_val=n_rep)
97
98 j = 1
99 k = 1
100 DO ir = 1, n_rep
101 NULLIFY (list)
102 CALL section_vals_val_get(section, "A_LIST", &
103 i_rep_val=ir, r_vals=list)
104
105 IF (ASSOCIATED(list)) THEN
106 DO i = 1, SIZE(list)
107 IF (j > gle%ndim) THEN
108 cpabort("GLE: Too many elements in A_LIST")
109 END IF
110 gle%a_mat(j, k) = list(i)
111 k = k + 1
112 IF (k > gle%ndim) THEN
113 k = 1
114 j = j + 1
115 END IF
116 END DO
117 END IF
118 END DO ! ir
119 IF (j < gle%ndim + 1) THEN
120 cpabort("GLE: Too few elements in A_LIST")
121 END IF
122 gle%a_mat = gle%a_mat*a_scale
123
124 CALL section_vals_val_get(section, "C_LIST", n_rep_val=n_rep)
125 IF (n_rep > 0) THEN
126 j = 1
127 k = 1
128 DO ir = 1, n_rep
129 NULLIFY (list)
130 CALL section_vals_val_get(section, "C_LIST", &
131 i_rep_val=ir, r_vals=list)
132
133 IF (ASSOCIATED(list)) THEN
134 DO i = 1, SIZE(list)
135 IF (j > gle%ndim) THEN
136 cpabort("GLE: Too many elements in C_LIST")
137 END IF
138 gle%c_mat(j, k) = list(i)
139 k = k + 1
140 IF (k > gle%ndim) THEN
141 k = 1
142 j = j + 1
143 END IF
144 END DO
145 END IF
146 END DO ! ir
147 IF (j < gle%ndim + 1) THEN
148 cpabort("GLE: Too few elements in C_LIST")
149 END IF
150 ELSE
151 gle%c_mat = 0.0_dp
152 DO i = 1, gle%ndim
153 gle%c_mat(i, i) = gle%temp
154 END DO
155 END IF
156 CALL create_map_info_type(gle%map_info)
157 END SUBROUTINE gle_init
158
159! **************************************************************************************************
160!> \brief ...
161!> \param gle ...
162!> \param mal_size ...
163!> \param
164! **************************************************************************************************
165 SUBROUTINE gle_thermo_create(gle, mal_size)
166 TYPE(gle_type), POINTER :: gle
167 INTEGER, INTENT(IN) :: mal_size
168
169 CHARACTER(LEN=40) :: name
170 INTEGER :: i, ithermo, my_index
171 REAL(kind=dp), ALLOCATABLE, DIMENSION(:, :, :) :: seed
172 REAL(kind=dp), DIMENSION(3, 2) :: initial_seed, my_seed
173
174 cpassert(ASSOCIATED(gle))
175 cpassert(.NOT. ASSOCIATED(gle%nvt))
176
177 ALLOCATE (gle%nvt(gle%loc_num_gle))
178 DO i = 1, gle%loc_num_gle
179 NULLIFY (gle%nvt(i)%s)
180 ALLOCATE (gle%nvt(i)%s(gle%ndim))
181 gle%nvt(i)%kin_energy = 0.0_dp
182 gle%nvt(i)%thermostat_energy = 0.0_dp
183 END DO
184
185 ALLOCATE (gle%mal(mal_size))
186 gle%mal(:) = 0
187
188 ! Initialize the gaussian stream random number
189 initial_seed = next_rng_seed()
190 ALLOCATE (seed(3, 2, gle%glob_num_gle))
191
192 seed(:, :, 1) = initial_seed
193 DO ithermo = 2, gle%glob_num_gle
194 seed(:, :, ithermo) = next_rng_seed(seed(:, :, ithermo - 1))
195 END DO
196
197 ! Update initial seed
198 initial_seed = next_rng_seed(seed(:, :, gle%glob_num_gle))
199 DO ithermo = 1, gle%loc_num_gle
200 my_index = gle%map_info%index(ithermo)
201 my_seed = seed(:, :, my_index)
202 WRITE (unit=name, fmt="(A,I8)") "Wiener process for Thermostat #", my_index
203 CALL compress(name)
204 gle%nvt(ithermo)%gaussian_rng_stream = rng_stream_type( &
205 name=name, distribution_type=gaussian, extended_precision=.true., seed=my_seed)
206 END DO
207
208 DEALLOCATE (seed)
209
210 END SUBROUTINE gle_thermo_create
211
212! **************************************************************************************************
213!> \brief Deallocate type for GLE thermostat
214!> \param gle ...
215! **************************************************************************************************
216 SUBROUTINE gle_dealloc(gle)
217 TYPE(gle_type), POINTER :: gle
218
219 INTEGER :: i
220
221 IF (ASSOCIATED(gle)) THEN
222 IF (ASSOCIATED(gle%a_mat)) THEN
223 DEALLOCATE (gle%a_mat)
224 END IF
225 IF (ASSOCIATED(gle%c_mat)) THEN
226 DEALLOCATE (gle%c_mat)
227 END IF
228 IF (ASSOCIATED(gle%gle_t)) THEN
229 DEALLOCATE (gle%gle_t)
230 END IF
231 IF (ASSOCIATED(gle%gle_s)) THEN
232 DEALLOCATE (gle%gle_s)
233 END IF
234 IF (ASSOCIATED(gle%nvt)) THEN
235 DO i = 1, SIZE(gle%nvt)
236 DEALLOCATE (gle%nvt(i)%s)
237 END DO
238 DEALLOCATE (gle%nvt)
239 END IF
240 IF (ASSOCIATED(gle%mal)) THEN
241 DEALLOCATE (gle%mal)
242 END IF
243
244 CALL release_map_info_type(gle%map_info)
245 DEALLOCATE (gle)
246 END IF
247
248 END SUBROUTINE gle_dealloc
249
250END MODULE gle_system_types
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public ceriotti2009
integer, save, public ceriotti2009b
Lumps all possible extended system variables into one type for easy access and passing.
subroutine, public release_map_info_type(map_info)
release the map_info type
subroutine, public create_map_info_type(map_info)
create the map_info type
subroutine, public gle_dealloc(gle)
Deallocate type for GLE thermostat.
subroutine, public gle_thermo_create(gle, mal_size)
...
subroutine, public gle_init(gle, dt, temp, section)
...
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
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
Definition list.F:24
Parallel (pseudo)random number generator (RNG) for multiple streams and substreams of random numbers.
real(kind=dp) function, dimension(3, 2), public next_rng_seed(seed)
Get the seed for the next RNG stream w.r.t. a given seed.
integer, parameter, public gaussian
Utilities for string manipulations.
subroutine, public compress(string, full)
Eliminate multiple space characters in a string. If full is .TRUE., then all spaces are eliminated.