(git:374b731)
Loading...
Searching...
No Matches
pwdft_environment_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 The type definitions for the PWDFT environment
10!> \par History
11!> 07.2018 initial create
12!> \author JHU
13! **************************************************************************************************
15 USE iso_c_binding, ONLY: c_null_ptr, &
16 c_ptr
20 USE kinds, ONLY: dp
21 USE qs_subsys_types, ONLY: qs_subsys_get, &
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 ***
42
43 ! *** Public subroutines ***
44 PUBLIC :: pwdft_env_release, &
48
49! **************************************************************************************************
50!> \brief The PWDFT energy type
51!> \par History
52!> 07.2018 initial create
53!> \author JHU
54! **************************************************************************************************
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! **************************************************************************************************
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! 16 different functionals should be enough
77 CHARACTER(len=80), DIMENSION(16) :: xc_func = ""
78#if defined(__SIRIUS)
79 TYPE(sirius_context_handler) :: sctx
80 TYPE(sirius_ground_state_handler) :: gs_handler
81 TYPE(sirius_kpoint_set_handler) :: ks_handler
82#else
83 TYPE(c_ptr) :: sctx = c_null_ptr
84 TYPE(c_ptr) :: gs_handler = c_null_ptr
85 TYPE(c_ptr) :: ks_handler = c_null_ptr
86#endif
87
89
90CONTAINS
91
92! **************************************************************************************************
93!> \brief Releases the given pwdft environment (see doc/ReferenceCounting.html)
94!> \param pwdft_env The pwdft environment to release
95!> \par History
96!> 07.2018 initial create
97!> \author JHU
98! **************************************************************************************************
99 SUBROUTINE pwdft_env_release(pwdft_env)
100
101 TYPE(pwdft_environment_type), INTENT(INOUT) :: pwdft_env
102
103#if defined(__SIRIUS)
104
105 CALL sirius_free_handler(pwdft_env%gs_handler)
106 CALL sirius_free_handler(pwdft_env%ks_handler)
107 CALL sirius_free_handler(pwdft_env%sctx)
108
109 IF (ASSOCIATED(pwdft_env%qs_subsys)) THEN
110 CALL qs_subsys_release(pwdft_env%qs_subsys)
111 DEALLOCATE (pwdft_env%qs_subsys)
112 END IF
113 IF (ASSOCIATED(pwdft_env%energy)) THEN
114 DEALLOCATE (pwdft_env%energy)
115 END IF
116 IF (ASSOCIATED(pwdft_env%forces)) THEN
117 DEALLOCATE (pwdft_env%forces)
118 END IF
119#else
120 mark_used(pwdft_env)
121#endif
122 END SUBROUTINE pwdft_env_release
123
124! **************************************************************************************************
125!> \brief Returns various attributes of the pwdft environment
126!> \param pwdft_env The enquired pwdft environment
127!> \param pwdft_input ...
128!> \param force_env_input ...
129!> \param xc_input ...
130!> \param cp_subsys ...
131!> \param qs_subsys ...
132!> \param para_env ...
133!> \param energy ...
134!> \param forces ...
135!> \param stress ...
136!> \param sctx ...
137!> \param gs_handler ...
138!> \param ks_handler ...
139!> \par History
140!> 07.2018 initial create
141!> \author JHU
142! **************************************************************************************************
143 SUBROUTINE pwdft_env_get(pwdft_env, pwdft_input, force_env_input, xc_input, &
144 cp_subsys, qs_subsys, para_env, energy, forces, stress, &
145 sctx, gs_handler, ks_handler)
146
147 TYPE(pwdft_environment_type), INTENT(IN) :: pwdft_env
148 TYPE(section_vals_type), OPTIONAL, POINTER :: pwdft_input, force_env_input, xc_input
149 TYPE(cp_subsys_type), OPTIONAL, POINTER :: cp_subsys
150 TYPE(qs_subsys_type), OPTIONAL, POINTER :: qs_subsys
151 TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
152 TYPE(pwdft_energy_type), OPTIONAL, POINTER :: energy
153 REAL(kind=dp), DIMENSION(:, :), OPTIONAL, POINTER :: forces
154 REAL(kind=dp), DIMENSION(3, 3), OPTIONAL :: stress
155#if defined(__SIRIUS)
156 TYPE(sirius_context_handler), OPTIONAL :: sctx
157 TYPE(sirius_ground_state_handler), OPTIONAL :: gs_handler
158 TYPE(sirius_kpoint_set_handler), OPTIONAL :: ks_handler
159#else
160 !work around because the contexts are typed.
161 TYPE(c_ptr), OPTIONAL :: sctx
162 TYPE(c_ptr), OPTIONAL :: gs_handler
163 TYPE(c_ptr), OPTIONAL :: ks_handler
164#endif
165
166 IF (PRESENT(pwdft_input)) pwdft_input => pwdft_env%pwdft_input
167 IF (PRESENT(force_env_input)) force_env_input => pwdft_env%force_env_input
168 IF (PRESENT(xc_input)) xc_input => pwdft_env%xc_input
169 IF (PRESENT(qs_subsys)) qs_subsys => pwdft_env%qs_subsys
170 IF (PRESENT(cp_subsys)) THEN
171 CALL qs_subsys_get(pwdft_env%qs_subsys, cp_subsys=cp_subsys)
172 END IF
173 IF (PRESENT(para_env)) para_env => pwdft_env%para_env
174 IF (PRESENT(energy)) energy => pwdft_env%energy
175 IF (PRESENT(forces)) forces => pwdft_env%forces
176 IF (PRESENT(stress)) stress(1:3, 1:3) = pwdft_env%stress(1:3, 1:3)
177 ! it will never be allocated if SIRIUS is not included during compilation
178 IF (PRESENT(sctx)) sctx = pwdft_env%sctx
179 IF (PRESENT(gs_handler)) gs_handler = pwdft_env%gs_handler
180 IF (PRESENT(ks_handler)) ks_handler = pwdft_env%ks_handler
181 END SUBROUTINE pwdft_env_get
182
183! **************************************************************************************************
184!> \brief Sets various attributes of the pwdft environment
185!> \param pwdft_env The enquired pwdft environment
186!> \param pwdft_input ...
187!> \param force_env_input ...
188!> \param xc_input ...
189!> \param qs_subsys ...
190!> \param cp_subsys ...
191!> \param para_env ...
192!> \param energy ...
193!> \param forces ...
194!> \param stress ...
195!> \param sctx ...
196!> \param gs_handler ...
197!> \param ks_handler ...
198!> \par History
199!> 07.2018 initial create
200!> \author JHU
201!> \note
202!> For possible missing arguments see the attributes of pwdft_environment_type
203! **************************************************************************************************
204 SUBROUTINE pwdft_env_set(pwdft_env, pwdft_input, force_env_input, xc_input, &
205 qs_subsys, cp_subsys, para_env, energy, forces, stress, &
206 sctx, gs_handler, ks_handler)
207
208 TYPE(pwdft_environment_type), INTENT(INOUT) :: pwdft_env
209 TYPE(section_vals_type), OPTIONAL, POINTER :: pwdft_input, force_env_input, xc_input
210 TYPE(qs_subsys_type), OPTIONAL, POINTER :: qs_subsys
211 TYPE(cp_subsys_type), OPTIONAL, POINTER :: cp_subsys
212 TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
213 TYPE(pwdft_energy_type), OPTIONAL, POINTER :: energy
214 REAL(kind=dp), DIMENSION(:, :), OPTIONAL, POINTER :: forces
215 REAL(kind=dp), DIMENSION(3, 3), OPTIONAL :: stress
216#if defined(__SIRIUS)
217 TYPE(sirius_context_handler), OPTIONAL :: sctx
218 TYPE(sirius_ground_state_handler), OPTIONAL :: gs_handler
219 TYPE(sirius_kpoint_set_handler), OPTIONAL :: ks_handler
220#else
221!work around because the contexts are typed.
222 TYPE(c_ptr), OPTIONAL :: sctx
223 TYPE(c_ptr), OPTIONAL :: gs_handler
224 TYPE(c_ptr), OPTIONAL :: ks_handler
225#endif
226
227 IF (PRESENT(para_env)) pwdft_env%para_env => para_env
228 IF (PRESENT(pwdft_input)) pwdft_env%pwdft_input => pwdft_input
229 IF (PRESENT(force_env_input)) pwdft_env%force_env_input => force_env_input
230 IF (PRESENT(xc_input)) pwdft_env%xc_input => xc_input
231
232 IF (PRESENT(qs_subsys)) THEN
233 IF (ASSOCIATED(pwdft_env%qs_subsys)) THEN
234 IF (.NOT. ASSOCIATED(pwdft_env%qs_subsys, qs_subsys)) THEN
235 CALL qs_subsys_release(pwdft_env%qs_subsys)
236 DEALLOCATE (pwdft_env%qs_subsys)
237 END IF
238 END IF
239 pwdft_env%qs_subsys => qs_subsys
240 END IF
241 IF (PRESENT(cp_subsys)) THEN
242 CALL qs_subsys_set(pwdft_env%qs_subsys, cp_subsys=cp_subsys)
243 END IF
244
245 IF (PRESENT(energy)) pwdft_env%energy => energy
246 IF (PRESENT(forces)) pwdft_env%forces => forces
247 IF (PRESENT(stress)) pwdft_env%stress(1:3, 1:3) = stress(1:3, 1:3)
248 IF (PRESENT(sctx)) pwdft_env%sctx = sctx
249 IF (PRESENT(gs_handler)) pwdft_env%gs_handler = gs_handler
250 IF (PRESENT(ks_handler)) pwdft_env%ks_handler = ks_handler
251 END SUBROUTINE pwdft_env_set
252
253! **************************************************************************************************
254!> \brief Reinitializes the pwdft environment
255!> \param pwdft_env The pwdft environment to be reinitialized
256!> \par History
257!> 07.2018 initial create
258!> \author JHU
259! **************************************************************************************************
260 SUBROUTINE pwdft_env_clear(pwdft_env)
261
262 TYPE(pwdft_environment_type), INTENT(INOUT) :: pwdft_env
263
264! ------------------------------------------------------------------------
265
266 NULLIFY (pwdft_env%para_env)
267 NULLIFY (pwdft_env%pwdft_input)
268 NULLIFY (pwdft_env%force_env_input)
269 IF (ASSOCIATED(pwdft_env%qs_subsys)) THEN
270 CALL qs_subsys_release(pwdft_env%qs_subsys)
271 DEALLOCATE (pwdft_env%qs_subsys)
272 END IF
273 IF (ASSOCIATED(pwdft_env%energy)) THEN
274 DEALLOCATE (pwdft_env%energy)
275 END IF
276 IF (ASSOCIATED(pwdft_env%forces)) THEN
277 DEALLOCATE (pwdft_env%forces)
278 NULLIFY (pwdft_env%forces)
279 END IF
280 pwdft_env%stress = 0.0_dp
281
282 END SUBROUTINE pwdft_env_clear
283
284! **************************************************************************************************
285!> \brief Creates the pwdft environment
286!> \param pwdft_env The pwdft environment to be created
287!> \par History
288!> 07.2018 initial create
289!> \author JHU
290! **************************************************************************************************
291 SUBROUTINE pwdft_env_create(pwdft_env)
292
293 TYPE(pwdft_environment_type), INTENT(OUT) :: pwdft_env
294
295 CALL pwdft_env_clear(pwdft_env)
296
297 END SUBROUTINE pwdft_env_create
298
types that represent a subsys, i.e. a part of the system
objects that represent the structure of input sections and the data contained in an input section
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Interface to the message passing library MPI.
The type definitions for the PWDFT environment.
subroutine, public pwdft_env_get(pwdft_env, pwdft_input, force_env_input, xc_input, cp_subsys, qs_subsys, para_env, energy, forces, stress, sctx, gs_handler, ks_handler)
Returns various attributes of the pwdft environment.
subroutine, public pwdft_env_create(pwdft_env)
Creates the pwdft environment.
subroutine, public pwdft_env_set(pwdft_env, pwdft_input, force_env_input, xc_input, qs_subsys, cp_subsys, para_env, energy, forces, stress, sctx, gs_handler, ks_handler)
Sets various attributes of the pwdft environment.
subroutine, public pwdft_env_release(pwdft_env)
Releases the given pwdft environment (see doc/ReferenceCounting.html)
types that represent a quickstep subsys
subroutine, public qs_subsys_release(subsys)
releases a subsys (see doc/ReferenceCounting.html)
subroutine, public qs_subsys_get(subsys, atomic_kinds, atomic_kind_set, particles, particle_set, local_particles, molecules, molecule_set, molecule_kinds, molecule_kind_set, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, natom, nparticle, ncore, nshell, nkind, atprop, virial, results, cell, cell_ref, use_ref_cell, energy, force, qs_kind_set, cp_subsys, nelectron_total, nelectron_spin)
...
subroutine, public qs_subsys_set(subsys, cp_subsys, local_particles, local_molecules, cell, cell_ref, use_ref_cell, energy, force, qs_kind_set, nelectron_total, nelectron_spin)
...
represents a system: atoms, molecules, their pos,vel,...
stores all the informations relevant to an mpi environment