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 The type definitions for the PWDFT environment
10 : !> \par History
11 : !> 07.2018 initial create
12 : !> \author JHU
13 : ! **************************************************************************************************
14 : MODULE pwdft_environment_types
15 : USE ISO_C_BINDING, ONLY: C_NULL_PTR, &
16 : C_PTR
17 : USE message_passing, ONLY: mp_para_env_type
18 : USE cp_subsys_types, ONLY: cp_subsys_type
19 : USE input_section_types, ONLY: section_vals_type
20 : USE kinds, ONLY: dp
21 : USE qs_subsys_types, ONLY: qs_subsys_get, &
22 : qs_subsys_release, &
23 : qs_subsys_set, &
24 : qs_subsys_type
25 :
26 : #if defined(__SIRIUS)
27 : USE sirius, ONLY: sirius_free_handler, &
28 : sirius_context_handler, &
29 : sirius_ground_state_handler, &
30 : sirius_kpoint_set_handler
31 : #endif
32 :
33 : #include "./base/base_uses.f90"
34 :
35 : IMPLICIT NONE
36 : PRIVATE
37 :
38 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'pwdft_environment_types'
39 :
40 : ! *** Public data types ***
41 : PUBLIC :: pwdft_environment_type, pwdft_energy_type
42 :
43 : ! *** Public subroutines ***
44 : PUBLIC :: pwdft_env_release, &
45 : pwdft_env_set, &
46 : pwdft_env_get, &
47 : pwdft_env_create
48 :
49 : ! **************************************************************************************************
50 : !> \brief The PWDFT energy type
51 : !> \par History
52 : !> 07.2018 initial create
53 : !> \author JHU
54 : ! **************************************************************************************************
55 : TYPE pwdft_energy_type
56 : REAL(KIND=dp) :: etotal = 0.0_dp
57 : REAL(KIND=dp) :: entropy = 0.0_dp
58 : REAL(KIND=dp) :: band_gap = -1.0_dp
59 : END TYPE pwdft_energy_type
60 :
61 : ! **************************************************************************************************
62 : !> \brief The PWDFT environment type
63 : !> \par History
64 : !> 07.2018 initial create
65 : !> \author JHU
66 : ! **************************************************************************************************
67 : TYPE pwdft_environment_type
68 : TYPE(mp_para_env_type), POINTER :: para_env => NULL()
69 : TYPE(qs_subsys_type), POINTER :: qs_subsys => NULL()
70 : TYPE(section_vals_type), POINTER :: pwdft_input => NULL()
71 : TYPE(section_vals_type), POINTER :: force_env_input => NULL()
72 : TYPE(section_vals_type), POINTER :: xc_input => NULL()
73 : TYPE(pwdft_energy_type), POINTER :: energy => NULL()
74 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: forces => NULL()
75 : REAL(KIND=dp), DIMENSION(3, 3) :: stress = 0.0_dp
76 : LOGICAL :: ignore_convergence_failure = .FALSE.
77 : ! 16 different functionals should be enough
78 : CHARACTER(len=80), DIMENSION(16) :: xc_func = ""
79 : #if defined(__SIRIUS)
80 : TYPE(sirius_context_handler) :: sctx
81 : TYPE(sirius_ground_state_handler) :: gs_handler
82 : TYPE(sirius_kpoint_set_handler) :: ks_handler
83 : #else
84 : TYPE(C_PTR) :: sctx = C_NULL_PTR
85 : TYPE(C_PTR) :: gs_handler = C_NULL_PTR
86 : TYPE(C_PTR) :: ks_handler = C_NULL_PTR
87 : #endif
88 :
89 : END TYPE pwdft_environment_type
90 :
91 : CONTAINS
92 :
93 : ! **************************************************************************************************
94 : !> \brief Releases the given pwdft environment
95 : !> \param pwdft_env The pwdft environment to release
96 : !> \par History
97 : !> 07.2018 initial create
98 : !> \author JHU
99 : ! **************************************************************************************************
100 16 : SUBROUTINE pwdft_env_release(pwdft_env)
101 :
102 : TYPE(pwdft_environment_type), INTENT(INOUT) :: pwdft_env
103 :
104 : #if defined(__SIRIUS)
105 :
106 16 : CALL sirius_free_handler(pwdft_env%gs_handler)
107 16 : CALL sirius_free_handler(pwdft_env%ks_handler)
108 16 : CALL sirius_free_handler(pwdft_env%sctx)
109 :
110 16 : IF (ASSOCIATED(pwdft_env%qs_subsys)) THEN
111 16 : CALL qs_subsys_release(pwdft_env%qs_subsys)
112 16 : DEALLOCATE (pwdft_env%qs_subsys)
113 : END IF
114 16 : IF (ASSOCIATED(pwdft_env%energy)) THEN
115 16 : DEALLOCATE (pwdft_env%energy)
116 : END IF
117 16 : IF (ASSOCIATED(pwdft_env%forces)) THEN
118 16 : DEALLOCATE (pwdft_env%forces)
119 : END IF
120 : #else
121 : MARK_USED(pwdft_env)
122 : #endif
123 16 : END SUBROUTINE pwdft_env_release
124 :
125 : ! **************************************************************************************************
126 : !> \brief Returns various attributes of the pwdft environment
127 : !> \param pwdft_env The enquired pwdft environment
128 : !> \param pwdft_input ...
129 : !> \param force_env_input ...
130 : !> \param xc_input ...
131 : !> \param cp_subsys ...
132 : !> \param qs_subsys ...
133 : !> \param para_env ...
134 : !> \param energy ...
135 : !> \param forces ...
136 : !> \param stress ...
137 : !> \param sctx ...
138 : !> \param gs_handler ...
139 : !> \param ks_handler ...
140 : !> \par History
141 : !> 07.2018 initial create
142 : !> \author JHU
143 : ! **************************************************************************************************
144 522 : SUBROUTINE pwdft_env_get(pwdft_env, pwdft_input, force_env_input, xc_input, &
145 : cp_subsys, qs_subsys, para_env, energy, forces, stress, &
146 : sctx, gs_handler, ks_handler)
147 :
148 : TYPE(pwdft_environment_type), INTENT(IN) :: pwdft_env
149 : TYPE(section_vals_type), OPTIONAL, POINTER :: pwdft_input, force_env_input, xc_input
150 : TYPE(cp_subsys_type), OPTIONAL, POINTER :: cp_subsys
151 : TYPE(qs_subsys_type), OPTIONAL, POINTER :: qs_subsys
152 : TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
153 : TYPE(pwdft_energy_type), OPTIONAL, POINTER :: energy
154 : REAL(KIND=dp), DIMENSION(:, :), OPTIONAL, POINTER :: forces
155 : REAL(KIND=dp), DIMENSION(3, 3), OPTIONAL :: stress
156 : #if defined(__SIRIUS)
157 : TYPE(sirius_context_handler), OPTIONAL :: sctx
158 : TYPE(sirius_ground_state_handler), OPTIONAL :: gs_handler
159 : TYPE(sirius_kpoint_set_handler), OPTIONAL :: ks_handler
160 : #else
161 : !work around because the contexts are typed.
162 : TYPE(C_PTR), OPTIONAL :: sctx
163 : TYPE(C_PTR), OPTIONAL :: gs_handler
164 : TYPE(C_PTR), OPTIONAL :: ks_handler
165 : #endif
166 :
167 522 : IF (PRESENT(pwdft_input)) pwdft_input => pwdft_env%pwdft_input
168 522 : IF (PRESENT(force_env_input)) force_env_input => pwdft_env%force_env_input
169 522 : IF (PRESENT(xc_input)) xc_input => pwdft_env%xc_input
170 522 : IF (PRESENT(qs_subsys)) qs_subsys => pwdft_env%qs_subsys
171 522 : IF (PRESENT(cp_subsys)) THEN
172 96 : CALL qs_subsys_get(pwdft_env%qs_subsys, cp_subsys=cp_subsys)
173 : END IF
174 522 : IF (PRESENT(para_env)) para_env => pwdft_env%para_env
175 522 : IF (PRESENT(energy)) energy => pwdft_env%energy
176 522 : IF (PRESENT(forces)) forces => pwdft_env%forces
177 522 : IF (PRESENT(stress)) stress(1:3, 1:3) = pwdft_env%stress(1:3, 1:3)
178 : ! it will never be allocated if SIRIUS is not included during compilation
179 522 : IF (PRESENT(sctx)) sctx = pwdft_env%sctx
180 522 : IF (PRESENT(gs_handler)) gs_handler = pwdft_env%gs_handler
181 522 : IF (PRESENT(ks_handler)) ks_handler = pwdft_env%ks_handler
182 522 : END SUBROUTINE pwdft_env_get
183 :
184 : ! **************************************************************************************************
185 : !> \brief Sets various attributes of the pwdft environment
186 : !> \param pwdft_env The enquired pwdft environment
187 : !> \param pwdft_input ...
188 : !> \param force_env_input ...
189 : !> \param xc_input ...
190 : !> \param qs_subsys ...
191 : !> \param cp_subsys ...
192 : !> \param para_env ...
193 : !> \param energy ...
194 : !> \param forces ...
195 : !> \param stress ...
196 : !> \param sctx ...
197 : !> \param gs_handler ...
198 : !> \param ks_handler ...
199 : !> \par History
200 : !> 07.2018 initial create
201 : !> \author JHU
202 : !> \note
203 : !> For possible missing arguments see the attributes of pwdft_environment_type
204 : ! **************************************************************************************************
205 80 : SUBROUTINE pwdft_env_set(pwdft_env, pwdft_input, force_env_input, xc_input, &
206 : qs_subsys, cp_subsys, para_env, energy, forces, stress, &
207 : sctx, gs_handler, ks_handler)
208 :
209 : TYPE(pwdft_environment_type), INTENT(INOUT) :: pwdft_env
210 : TYPE(section_vals_type), OPTIONAL, POINTER :: pwdft_input, force_env_input, xc_input
211 : TYPE(qs_subsys_type), OPTIONAL, POINTER :: qs_subsys
212 : TYPE(cp_subsys_type), OPTIONAL, POINTER :: cp_subsys
213 : TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
214 : TYPE(pwdft_energy_type), OPTIONAL, POINTER :: energy
215 : REAL(KIND=dp), DIMENSION(:, :), OPTIONAL, POINTER :: forces
216 : REAL(KIND=dp), DIMENSION(3, 3), OPTIONAL :: stress
217 : #if defined(__SIRIUS)
218 : TYPE(sirius_context_handler), OPTIONAL :: sctx
219 : TYPE(sirius_ground_state_handler), OPTIONAL :: gs_handler
220 : TYPE(sirius_kpoint_set_handler), OPTIONAL :: ks_handler
221 : #else
222 : !work around because the contexts are typed.
223 : TYPE(C_PTR), OPTIONAL :: sctx
224 : TYPE(C_PTR), OPTIONAL :: gs_handler
225 : TYPE(C_PTR), OPTIONAL :: ks_handler
226 : #endif
227 :
228 80 : IF (PRESENT(para_env)) pwdft_env%para_env => para_env
229 80 : IF (PRESENT(pwdft_input)) pwdft_env%pwdft_input => pwdft_input
230 80 : IF (PRESENT(force_env_input)) pwdft_env%force_env_input => force_env_input
231 80 : IF (PRESENT(xc_input)) pwdft_env%xc_input => xc_input
232 :
233 80 : IF (PRESENT(qs_subsys)) THEN
234 16 : IF (ASSOCIATED(pwdft_env%qs_subsys)) THEN
235 0 : IF (.NOT. ASSOCIATED(pwdft_env%qs_subsys, qs_subsys)) THEN
236 0 : CALL qs_subsys_release(pwdft_env%qs_subsys)
237 0 : DEALLOCATE (pwdft_env%qs_subsys)
238 : END IF
239 : END IF
240 16 : pwdft_env%qs_subsys => qs_subsys
241 : END IF
242 80 : IF (PRESENT(cp_subsys)) THEN
243 0 : CALL qs_subsys_set(pwdft_env%qs_subsys, cp_subsys=cp_subsys)
244 : END IF
245 :
246 80 : IF (PRESENT(energy)) pwdft_env%energy => energy
247 80 : IF (PRESENT(forces)) pwdft_env%forces => forces
248 80 : IF (PRESENT(stress)) pwdft_env%stress(1:3, 1:3) = stress(1:3, 1:3)
249 80 : IF (PRESENT(sctx)) pwdft_env%sctx = sctx
250 80 : IF (PRESENT(gs_handler)) pwdft_env%gs_handler = gs_handler
251 80 : IF (PRESENT(ks_handler)) pwdft_env%ks_handler = ks_handler
252 80 : END SUBROUTINE pwdft_env_set
253 :
254 : ! **************************************************************************************************
255 : !> \brief Reinitializes the pwdft environment
256 : !> \param pwdft_env The pwdft environment to be reinitialized
257 : !> \par History
258 : !> 07.2018 initial create
259 : !> \author JHU
260 : ! **************************************************************************************************
261 16 : SUBROUTINE pwdft_env_clear(pwdft_env)
262 :
263 : TYPE(pwdft_environment_type), INTENT(INOUT) :: pwdft_env
264 :
265 : ! ------------------------------------------------------------------------
266 :
267 16 : NULLIFY (pwdft_env%para_env)
268 16 : NULLIFY (pwdft_env%pwdft_input)
269 16 : NULLIFY (pwdft_env%force_env_input)
270 16 : IF (ASSOCIATED(pwdft_env%qs_subsys)) THEN
271 0 : CALL qs_subsys_release(pwdft_env%qs_subsys)
272 0 : DEALLOCATE (pwdft_env%qs_subsys)
273 : END IF
274 16 : IF (ASSOCIATED(pwdft_env%energy)) THEN
275 0 : DEALLOCATE (pwdft_env%energy)
276 : END IF
277 16 : IF (ASSOCIATED(pwdft_env%forces)) THEN
278 0 : DEALLOCATE (pwdft_env%forces)
279 : NULLIFY (pwdft_env%forces)
280 : END IF
281 208 : pwdft_env%stress = 0.0_dp
282 :
283 16 : END SUBROUTINE pwdft_env_clear
284 :
285 : ! **************************************************************************************************
286 : !> \brief Creates the pwdft environment
287 : !> \param pwdft_env The pwdft environment to be created
288 : !> \par History
289 : !> 07.2018 initial create
290 : !> \author JHU
291 : ! **************************************************************************************************
292 464 : SUBROUTINE pwdft_env_create(pwdft_env)
293 :
294 : TYPE(pwdft_environment_type), INTENT(OUT) :: pwdft_env
295 :
296 16 : CALL pwdft_env_clear(pwdft_env)
297 :
298 16 : END SUBROUTINE pwdft_env_create
299 :
300 0 : END MODULE pwdft_environment_types
|