Line data Source code
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 : ! **************************************************************************************************
12 : MODULE csvr_system_types
13 : USE bibliography, ONLY: Bussi2007,&
14 : cite_reference
15 : USE extended_system_types, ONLY: create_map_info_type,&
16 : map_info_type,&
17 : release_map_info_type
18 : USE input_section_types, ONLY: section_vals_type,&
19 : section_vals_val_get
20 : USE kinds, ONLY: dp
21 : USE parallel_rng_types, ONLY: GAUSSIAN,&
22 : next_rng_seed,&
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, &
34 : csvr_thermo_create
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 160 : 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 160 : NULLIFY (csvr%nvt)
71 160 : NULLIFY (csvr%map_info)
72 160 : csvr%loc_num_csvr = 0
73 160 : csvr%glob_num_csvr = 0
74 160 : csvr%dt_fact = 1.0_dp
75 160 : CALL cite_reference(Bussi2007)
76 160 : 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 160 : csvr%tau_csvr = csvr%tau_csvr/(0.5_dp*simpar%dt)
81 160 : CALL create_map_info_type(csvr%map_info)
82 :
83 160 : 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 160 : 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 160 : REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :, :) :: seed
96 : REAL(KIND=dp), DIMENSION(3, 2) :: initial_seed, my_seed
97 :
98 160 : CPASSERT(ASSOCIATED(csvr))
99 160 : CPASSERT(.NOT. ASSOCIATED(csvr%nvt))
100 :
101 6646 : ALLOCATE (csvr%nvt(csvr%loc_num_csvr))
102 2166 : DO i = 1, csvr%loc_num_csvr
103 2166 : csvr%nvt(i)%thermostat_energy = 0.0_dp
104 : END DO
105 : ! Initialize the gaussian stream random number
106 480 : ALLOCATE (seed(3, 2, csvr%glob_num_csvr))
107 160 : initial_seed = next_rng_seed()
108 :
109 1440 : seed(:, :, 1) = initial_seed
110 3878 : DO ithermo = 2, csvr%glob_num_csvr
111 3878 : seed(:, :, ithermo) = next_rng_seed(seed(:, :, ithermo - 1))
112 : END DO
113 : ! Update initial seed
114 160 : initial_seed = next_rng_seed(seed(:, :, csvr%glob_num_csvr))
115 2166 : DO ithermo = 1, csvr%loc_num_csvr
116 2006 : my_index = csvr%map_info%index(ithermo)
117 18054 : my_seed = seed(:, :, my_index)
118 2006 : WRITE (UNIT=name, FMT="(A,I8)") "Wiener process for Thermostat #", my_index
119 2006 : CALL compress(name)
120 : csvr%nvt(ithermo)%gaussian_rng_stream = rng_stream_type( &
121 2166 : name=name, distribution_type=GAUSSIAN, extended_precision=.TRUE., seed=my_seed)
122 : END DO
123 160 : DEALLOCATE (seed)
124 :
125 160 : 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 160 : SUBROUTINE csvr_dealloc(csvr)
133 : TYPE(csvr_system_type), POINTER :: csvr
134 :
135 160 : IF (ASSOCIATED(csvr)) THEN
136 160 : CALL csvr_thermo_dealloc(csvr%nvt)
137 160 : CALL release_map_info_type(csvr%map_info)
138 160 : DEALLOCATE (csvr)
139 : END IF
140 :
141 160 : 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 160 : SUBROUTINE csvr_thermo_dealloc(nvt)
149 : TYPE(csvr_thermo_type), DIMENSION(:), POINTER :: nvt
150 :
151 160 : IF (ASSOCIATED(nvt)) &
152 160 : DEALLOCATE (nvt)
153 160 : END SUBROUTINE csvr_thermo_dealloc
154 :
155 0 : END MODULE csvr_system_types
156 :
|