15 USE iso_c_binding,
ONLY: c_null_ptr, &
27 USE sirius,
ONLY: sirius_free_handler, &
28 sirius_context_handler, &
29 sirius_ground_state_handler, &
30 sirius_kpoint_set_handler
33#include "./base/base_uses.f90"
38 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'pwdft_environment_types'
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
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.
78 CHARACTER(len=80),
DIMENSION(16) :: xc_func =
""
80 TYPE(sirius_context_handler) :: sctx
81 TYPE(sirius_ground_state_handler) :: gs_handler
82 TYPE(sirius_kpoint_set_handler) :: ks_handler
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
106 CALL sirius_free_handler(pwdft_env%gs_handler)
107 CALL sirius_free_handler(pwdft_env%ks_handler)
108 CALL sirius_free_handler(pwdft_env%sctx)
110 IF (
ASSOCIATED(pwdft_env%qs_subsys))
THEN
112 DEALLOCATE (pwdft_env%qs_subsys)
114 IF (
ASSOCIATED(pwdft_env%energy))
THEN
115 DEALLOCATE (pwdft_env%energy)
117 IF (
ASSOCIATED(pwdft_env%forces))
THEN
118 DEALLOCATE (pwdft_env%forces)
144 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)
149 TYPE(
section_vals_type),
OPTIONAL,
POINTER :: pwdft_input, force_env_input, xc_input
154 REAL(kind=
dp),
DIMENSION(:, :),
OPTIONAL,
POINTER :: forces
155 REAL(kind=
dp),
DIMENSION(3, 3),
OPTIONAL :: stress
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
162 TYPE(c_ptr),
OPTIONAL :: sctx
163 TYPE(c_ptr),
OPTIONAL :: gs_handler
164 TYPE(c_ptr),
OPTIONAL :: ks_handler
167 IF (
PRESENT(pwdft_input)) pwdft_input => pwdft_env%pwdft_input
168 IF (
PRESENT(force_env_input)) force_env_input => pwdft_env%force_env_input
169 IF (
PRESENT(xc_input)) xc_input => pwdft_env%xc_input
170 IF (
PRESENT(qs_subsys)) qs_subsys => pwdft_env%qs_subsys
171 IF (
PRESENT(cp_subsys))
THEN
174 IF (
PRESENT(para_env)) para_env => pwdft_env%para_env
175 IF (
PRESENT(energy)) energy => pwdft_env%energy
176 IF (
PRESENT(forces)) forces => pwdft_env%forces
177 IF (
PRESENT(stress)) stress(1:3, 1:3) = pwdft_env%stress(1:3, 1:3)
179 IF (
PRESENT(sctx)) sctx = pwdft_env%sctx
180 IF (
PRESENT(gs_handler)) gs_handler = pwdft_env%gs_handler
181 IF (
PRESENT(ks_handler)) ks_handler = pwdft_env%ks_handler
205 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)
210 TYPE(
section_vals_type),
OPTIONAL,
POINTER :: pwdft_input, force_env_input, xc_input
215 REAL(kind=
dp),
DIMENSION(:, :),
OPTIONAL,
POINTER :: forces
216 REAL(kind=
dp),
DIMENSION(3, 3),
OPTIONAL :: stress
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
223 TYPE(c_ptr),
OPTIONAL :: sctx
224 TYPE(c_ptr),
OPTIONAL :: gs_handler
225 TYPE(c_ptr),
OPTIONAL :: ks_handler
228 IF (
PRESENT(para_env)) pwdft_env%para_env => para_env
229 IF (
PRESENT(pwdft_input)) pwdft_env%pwdft_input => pwdft_input
230 IF (
PRESENT(force_env_input)) pwdft_env%force_env_input => force_env_input
231 IF (
PRESENT(xc_input)) pwdft_env%xc_input => xc_input
233 IF (
PRESENT(qs_subsys))
THEN
234 IF (
ASSOCIATED(pwdft_env%qs_subsys))
THEN
235 IF (.NOT.
ASSOCIATED(pwdft_env%qs_subsys, qs_subsys))
THEN
237 DEALLOCATE (pwdft_env%qs_subsys)
240 pwdft_env%qs_subsys => qs_subsys
242 IF (
PRESENT(cp_subsys))
THEN
246 IF (
PRESENT(energy)) pwdft_env%energy => energy
247 IF (
PRESENT(forces)) pwdft_env%forces => forces
248 IF (
PRESENT(stress)) pwdft_env%stress(1:3, 1:3) = stress(1:3, 1:3)
249 IF (
PRESENT(sctx)) pwdft_env%sctx = sctx
250 IF (
PRESENT(gs_handler)) pwdft_env%gs_handler = gs_handler
251 IF (
PRESENT(ks_handler)) pwdft_env%ks_handler = ks_handler
261 SUBROUTINE pwdft_env_clear(pwdft_env)
267 NULLIFY (pwdft_env%para_env)
268 NULLIFY (pwdft_env%pwdft_input)
269 NULLIFY (pwdft_env%force_env_input)
270 IF (
ASSOCIATED(pwdft_env%qs_subsys))
THEN
272 DEALLOCATE (pwdft_env%qs_subsys)
274 IF (
ASSOCIATED(pwdft_env%energy))
THEN
275 DEALLOCATE (pwdft_env%energy)
277 IF (
ASSOCIATED(pwdft_env%forces))
THEN
278 DEALLOCATE (pwdft_env%forces)
279 NULLIFY (pwdft_env%forces)
281 pwdft_env%stress = 0.0_dp
283 END SUBROUTINE pwdft_env_clear
296 CALL pwdft_env_clear(pwdft_env)
types that represent a subsys, i.e. a part of the system
Defines the basic variable types.
integer, parameter, public dp
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.
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
The PWDFT environment type.