(git:b279b6b)
csvr_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 Type for the canonical sampling through velocity rescaling
10 !> \author Teodoro Laino - 09.2007 University of Zurich [tlaino]
11 ! **************************************************************************************************
13  USE bibliography, ONLY: bussi2007,&
14  cite_reference
16  map_info_type,&
18  USE input_section_types, ONLY: section_vals_type,&
20  USE kinds, ONLY: dp
21  USE parallel_rng_types, ONLY: gaussian,&
23  rng_stream_type
24  USE simpar_types, ONLY: simpar_type
25  USE string_utilities, ONLY: compress
26 #include "./base/base_uses.f90"
27 
28  IMPLICIT NONE
29 
30  PRIVATE
31  PUBLIC :: csvr_system_type, &
32  csvr_init, &
33  csvr_dealloc, &
35 
36 ! **************************************************************************************************
37  TYPE csvr_thermo_type
38  INTEGER :: degrees_of_freedom = 0
39  REAL(KIND=dp) :: nkt = 0.0_dp
40  REAL(KIND=dp) :: thermostat_energy = 0.0_dp
41  REAL(KIND=dp) :: region_kin_energy = 0.0_dp
42  TYPE(rng_stream_type) :: gaussian_rng_stream = rng_stream_type()
43  END TYPE csvr_thermo_type
44 
45 ! **************************************************************************************************
46  TYPE csvr_system_type
47  INTEGER :: region = 0, glob_num_csvr = 0, loc_num_csvr = 0
48  REAL(KIND=dp) :: tau_csvr = 0.0_dp, dt_fact = 0.0_dp
49  TYPE(csvr_thermo_type), POINTER :: nvt(:) => null()
50  TYPE(map_info_type), POINTER :: map_info => null()
51  END TYPE csvr_system_type
52 
53 ! *** Global parameters ***
54  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'csvr_system_types'
55 
56 CONTAINS
57 
58 ! **************************************************************************************************
59 !> \brief Initialize type for Canonical Sampling through Velocity Rescaling (CSVR)
60 !> \param csvr ...
61 !> \param simpar ...
62 !> \param section ...
63 !> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
64 ! **************************************************************************************************
65  SUBROUTINE csvr_init(csvr, simpar, section)
66  TYPE(csvr_system_type), POINTER :: csvr
67  TYPE(simpar_type), POINTER :: simpar
68  TYPE(section_vals_type), POINTER :: section
69 
70  NULLIFY (csvr%nvt)
71  NULLIFY (csvr%map_info)
72  csvr%loc_num_csvr = 0
73  csvr%glob_num_csvr = 0
74  csvr%dt_fact = 1.0_dp
75  CALL cite_reference(bussi2007)
76  CALL section_vals_val_get(section, "TIMECON", r_val=csvr%tau_csvr)
77  ! The CSVR library expects the tau_csv to be in unit of integration timestep
78  ! if applied once.. divided by two if the process is applied both to the first
79  ! and the second verlet step
80  csvr%tau_csvr = csvr%tau_csvr/(0.5_dp*simpar%dt)
81  CALL create_map_info_type(csvr%map_info)
82 
83  END SUBROUTINE csvr_init
84 
85 ! **************************************************************************************************
86 !> \brief Initialize NVT type for CSVR thermostat
87 !> \param csvr ...
88 !> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
89 ! **************************************************************************************************
90  SUBROUTINE csvr_thermo_create(csvr)
91  TYPE(csvr_system_type), POINTER :: csvr
92 
93  CHARACTER(LEN=40) :: name
94  INTEGER :: i, ithermo, my_index
95  REAL(kind=dp), ALLOCATABLE, DIMENSION(:, :, :) :: seed
96  REAL(kind=dp), DIMENSION(3, 2) :: initial_seed, my_seed
97 
98  cpassert(ASSOCIATED(csvr))
99  cpassert(.NOT. ASSOCIATED(csvr%nvt))
100 
101  ALLOCATE (csvr%nvt(csvr%loc_num_csvr))
102  DO i = 1, csvr%loc_num_csvr
103  csvr%nvt(i)%thermostat_energy = 0.0_dp
104  END DO
105  ! Initialize the gaussian stream random number
106  ALLOCATE (seed(3, 2, csvr%glob_num_csvr))
107  initial_seed = next_rng_seed()
108 
109  seed(:, :, 1) = initial_seed
110  DO ithermo = 2, csvr%glob_num_csvr
111  seed(:, :, ithermo) = next_rng_seed(seed(:, :, ithermo - 1))
112  END DO
113  ! Update initial seed
114  initial_seed = next_rng_seed(seed(:, :, csvr%glob_num_csvr))
115  DO ithermo = 1, csvr%loc_num_csvr
116  my_index = csvr%map_info%index(ithermo)
117  my_seed = seed(:, :, my_index)
118  WRITE (unit=name, fmt="(A,I8)") "Wiener process for Thermostat #", my_index
119  CALL compress(name)
120  csvr%nvt(ithermo)%gaussian_rng_stream = rng_stream_type( &
121  name=name, distribution_type=gaussian, extended_precision=.true., seed=my_seed)
122  END DO
123  DEALLOCATE (seed)
124 
125  END SUBROUTINE csvr_thermo_create
126 
127 ! **************************************************************************************************
128 !> \brief Deallocate type for CSVR thermostat
129 !> \param csvr ...
130 !> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
131 ! **************************************************************************************************
132  SUBROUTINE csvr_dealloc(csvr)
133  TYPE(csvr_system_type), POINTER :: csvr
134 
135  IF (ASSOCIATED(csvr)) THEN
136  CALL csvr_thermo_dealloc(csvr%nvt)
137  CALL release_map_info_type(csvr%map_info)
138  DEALLOCATE (csvr)
139  END IF
140 
141  END SUBROUTINE csvr_dealloc
142 
143 ! **************************************************************************************************
144 !> \brief Deallocate NVT type for CSVR thermostat
145 !> \param nvt ...
146 !> \author Teodoro Laino [tlaino] 10.2007- University of Zurich
147 ! **************************************************************************************************
148  SUBROUTINE csvr_thermo_dealloc(nvt)
149  TYPE(csvr_thermo_type), DIMENSION(:), POINTER :: nvt
150 
151  IF (ASSOCIATED(nvt)) &
152  DEALLOCATE (nvt)
153  END SUBROUTINE csvr_thermo_dealloc
154 
155 END MODULE csvr_system_types
156 
collects all references to literature in CP2K as new algorithms / method are included from literature...
Definition: bibliography.F:28
integer, save, public bussi2007
Definition: bibliography.F:43
Type for the canonical sampling through velocity rescaling.
subroutine, public csvr_thermo_create(csvr)
Initialize NVT type for CSVR thermostat.
subroutine, public csvr_dealloc(csvr)
Deallocate type for CSVR thermostat.
subroutine, public csvr_init(csvr, simpar, section)
Initialize type for Canonical Sampling through Velocity Rescaling (CSVR)
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
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
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
Type for storing MD parameters.
Definition: simpar_types.F:14
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.