27#include "./base/base_uses.f90"
38 INTEGER :: degrees_of_freedom = -1
39 REAL(KIND=
dp) :: nkt = 0.0_dp, kin_energy = 0.0_dp, thermostat_energy = 0.0_dp
40 REAL(KIND=
dp),
DIMENSION(:),
POINTER :: s => null()
42 END TYPE gle_thermo_type
47 INTEGER :: glob_num_gle = -1, loc_num_gle = -1, region = -1
48 INTEGER,
DIMENSION(:),
POINTER :: mal => null()
49 REAL(
dp) :: temp = 0.0_dp, dt = 0.0_dp, dt_fact = 0.0_dp
50 REAL(
dp),
POINTER :: gle_s(:, :) => null(), gle_t(:, :) => null()
51 REAL(
dp),
POINTER :: a_mat(:, :) => null(), c_mat(:, :) => null()
52 TYPE(gle_thermo_type),
POINTER :: nvt(:) => null()
56 CHARACTER(len=*),
PARAMETER,
PRIVATE :: modulen =
'gle_system_types'
70 REAL(
dp),
INTENT(IN) :: dt, temp
73 INTEGER :: i, ir, j, k, n_rep
74 REAL(
dp),
DIMENSION(:),
POINTER ::
list
75 REAL(kind=
dp) :: a_scale
80 NULLIFY (gle%map_info)
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))
103 i_rep_val=ir, r_vals=
list)
105 IF (
ASSOCIATED(
list))
THEN
107 IF (j > gle%ndim)
THEN
108 cpabort(
"GLE: Too many elements in A_LIST")
110 gle%a_mat(j, k) =
list(i)
112 IF (k > gle%ndim)
THEN
119 IF (j < gle%ndim + 1)
THEN
120 cpabort(
"GLE: Too few elements in A_LIST")
122 gle%a_mat = gle%a_mat*a_scale
131 i_rep_val=ir, r_vals=
list)
133 IF (
ASSOCIATED(
list))
THEN
135 IF (j > gle%ndim)
THEN
136 cpabort(
"GLE: Too many elements in C_LIST")
138 gle%c_mat(j, k) =
list(i)
140 IF (k > gle%ndim)
THEN
147 IF (j < gle%ndim + 1)
THEN
148 cpabort(
"GLE: Too few elements in C_LIST")
153 gle%c_mat(i, i) = gle%temp
167 INTEGER,
INTENT(IN) :: mal_size
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
174 cpassert(
ASSOCIATED(gle))
175 cpassert(.NOT.
ASSOCIATED(gle%nvt))
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
185 ALLOCATE (gle%mal(mal_size))
190 ALLOCATE (seed(3, 2, gle%glob_num_gle))
192 seed(:, :, 1) = initial_seed
193 DO ithermo = 2, 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
205 name=name, distribution_type=
gaussian, extended_precision=.true., seed=my_seed)
221 IF (
ASSOCIATED(gle))
THEN
222 IF (
ASSOCIATED(gle%a_mat))
THEN
223 DEALLOCATE (gle%a_mat)
225 IF (
ASSOCIATED(gle%c_mat))
THEN
226 DEALLOCATE (gle%c_mat)
228 IF (
ASSOCIATED(gle%gle_t))
THEN
229 DEALLOCATE (gle%gle_t)
231 IF (
ASSOCIATED(gle%gle_s))
THEN
232 DEALLOCATE (gle%gle_s)
234 IF (
ASSOCIATED(gle%nvt))
THEN
235 DO i = 1,
SIZE(gle%nvt)
236 DEALLOCATE (gle%nvt(i)%s)
240 IF (
ASSOCIATED(gle%mal))
THEN
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)
...
Defines the basic variable types.
integer, parameter, public dp
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
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.