39#include "./base/base_uses.f90"
45 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'ec_env_types'
56 CHARACTER(len=20) :: ec_name =
""
57 INTEGER :: energy_functional = 0
58 INTEGER :: ks_solver = 0
59 INTEGER :: factorization = 0
60 INTEGER :: ec_initial_guess = 0
61 REAL(kind=
dp) :: eps_default = 0.0_dp
62 LOGICAL :: do_ec_admm = .false.
63 LOGICAL :: do_ec_hfx = .false.
64 LOGICAL :: should_update = .false.
65 LOGICAL :: use_ls_solver = .false.
66 LOGICAL :: reuse_hfx = .false.
67 LOGICAL :: basis_inconsistent = .false.
69 LOGICAL :: debug_forces = .false.
70 LOGICAL :: debug_stress = .false.
71 LOGICAL :: debug_external = .false.
73 CHARACTER(len=20) :: basis =
""
74 LOGICAL :: mao = .false.
76 LOGICAL :: do_skip = .false., skip_ec = .false.
77 INTEGER :: mao_max_iter = 0
78 REAL(kind=
dp) :: mao_eps_grad = 0.0_dp
79 REAL(kind=
dp) :: mao_eps1 = 0.0_dp
80 INTEGER :: mao_iolevel = 0
82 REAL(kind=
dp) :: etotal = 0.0_dp, old_etotal = 0.0_dp
83 REAL(kind=
dp) :: eband = 0.0_dp, ecore = 0.0_dp, exc = 0.0_dp, &
84 ehartree = 0.0_dp, vhxc = 0.0_dp
85 REAL(kind=
dp) :: edispersion = 0.0_dp, efield_elec = 0.0_dp, &
86 efield_nuclear = 0.0_dp, ex = 0.0_dp, exc_aux_fit = 0.0_dp
91 DIMENSION(:),
POINTER :: sab_orb => null(), sac_ppl => null(), sap_ppnl => null()
99 TYPE(
dbcsr_p_type),
DIMENSION(:, :),
POINTER :: matrix_ks => null(), &
100 matrix_h => null(), &
101 matrix_s => null(), &
102 matrix_t => null(), &
103 matrix_p => null(), &
112 TYPE(
dbcsr_p_type),
DIMENSION(:),
POINTER :: matrix_hz => null(), matrix_wz => null(), &
113 matrix_z => null(), z_admm => null()
120 vtau_rspace => null(), &
121 vadmm_rspace => null()
127 TYPE(
hfx_type),
DIMENSION(:, :),
POINTER :: x_data => null()
130 xc_section_aux => null()
132 CHARACTER(len=40) :: exresp_fn =
""
133 CHARACTER(len=40) :: exresult_fn =
""
134 LOGICAL :: do_error = .false.
135 REAL(kind=
dp),
DIMENSION(3, 3) :: rpv = 0.0_dp, rpverror = 0.0_dp
136 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: rf => null(), &
149 CHARACTER(LEN=*),
PARAMETER :: routinen =
'ec_env_release'
151 INTEGER :: handle, iab
153 CALL timeset(routinen, handle)
155 IF (
ASSOCIATED(ec_env))
THEN
169 IF (
ASSOCIATED(ec_env%task_list))
THEN
175 IF (
ASSOCIATED(ec_env%dispersion_env))
THEN
183 NULLIFY (ec_env%matrix_z, ec_env%matrix_hz, ec_env%matrix_wz)
184 NULLIFY (ec_env%z_admm)
186 IF (
ASSOCIATED(ec_env%p_env))
THEN
188 DEALLOCATE (ec_env%p_env)
191 IF (
ASSOCIATED(ec_env%vh_rspace%pw_grid))
THEN
192 CALL ec_env%vh_rspace%release()
194 IF (
ASSOCIATED(ec_env%vxc_rspace))
THEN
195 DO iab = 1,
SIZE(ec_env%vxc_rspace)
196 CALL ec_env%vxc_rspace(iab)%release()
198 DEALLOCATE (ec_env%vxc_rspace)
200 IF (
ASSOCIATED(ec_env%vtau_rspace))
THEN
201 DO iab = 1,
SIZE(ec_env%vtau_rspace)
202 CALL ec_env%vtau_rspace(iab)%release()
204 DEALLOCATE (ec_env%vtau_rspace)
206 IF (
ASSOCIATED(ec_env%vadmm_rspace))
THEN
207 DO iab = 1,
SIZE(ec_env%vadmm_rspace)
208 CALL ec_env%vadmm_rspace(iab)%release()
210 DEALLOCATE (ec_env%vadmm_rspace)
214 IF (
ASSOCIATED(ec_env%ls_env))
THEN
218 IF (.NOT. ec_env%reuse_hfx)
THEN
219 IF (
ASSOCIATED(ec_env%x_data))
CALL hfx_release(ec_env%x_data)
228 IF (
ASSOCIATED(ec_env%rf))
THEN
229 DEALLOCATE (ec_env%rf)
231 IF (
ASSOCIATED(ec_env%rferror))
THEN
232 DEALLOCATE (ec_env%rferror)
241 CALL timestop(handle)
DBCSR operations in CP2K.
represent a full matrix distributed on many processors
Types needed for a linear scaling quickstep SCF run based on the density matrix.
subroutine, public ls_scf_release(ls_scf_env)
release the LS type.
Types needed for a for a Energy Correction.
subroutine, public ec_env_release(ec_env)
...
Types and set/get functions for HFX.
subroutine, public hfx_release(x_data)
This routine deallocates all data structures
Defines the basic variable types.
integer, parameter, public dp
Definition of disperson types for DFT calculations.
subroutine, public qs_dispersion_release(dispersion_env)
...
subroutine, public deallocate_qs_force(qs_force)
Deallocate a Quickstep force data structure.
Define the neighbor list data types and the corresponding functionality.
subroutine, public release_neighbor_list_sets(nlists)
releases an array of neighbor_list_sets
basis types for the calculation of the perturbation of density theory.
subroutine, public p_env_release(p_env)
relases the given p_env (see doc/ReferenceCounting.html)
type for berry phase efield matrices. At the moment only used for cosmat and sinmat
subroutine, public efield_berry_release(efield)
...
subroutine, public deallocate_task_list(task_list)
deallocates the components and the object itself
Contains information on the energy correction functional for KG.
stores some data used in construction of Kohn-Sham matrix
Represent a qs system that is perturbed. Can calculate the linear operator and the rhs of the system ...