34#include "./base/base_uses.f90"
40 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'kg_environment_types'
45 TYPE(neighbor_list_set_p_type),
DIMENSION(:),
POINTER :: sab_orb => null()
46 TYPE(task_list_type),
POINTER :: task_list => null()
56 CHARACTER(len=20) :: ec_name =
""
57 INTEGER :: energy_functional = -1
58 INTEGER :: ks_solver = -1
59 INTEGER :: factorization = -1
60 REAL(kind=
dp) :: eps_default = 0.0_dp
62 CHARACTER(len=20) :: basis =
""
63 LOGICAL :: mao = .false.
64 INTEGER :: mao_max_iter = -1
65 REAL(kind=
dp) :: mao_eps_grad = 0.0_dp
67 REAL(kind=
dp) :: etotal = 0.0_dp
68 REAL(kind=
dp) :: eband = 0.0_dp, exc = 0.0_dp, ehartree = 0.0_dp, vhxc = 0.0_dp
69 REAL(kind=
dp) :: edispersion = 0.0_dp
72 DIMENSION(:),
POINTER :: sab_orb => null(), sac_ppl => null(), sap_ppnl => null()
79 TYPE(
dbcsr_p_type),
DIMENSION(:, :),
POINTER :: matrix_ks => null()
103 INTEGER :: nspins = -1
104 INTEGER :: natom = -1
106 INTEGER,
ALLOCATABLE,
DIMENSION(:) :: atom_to_molecule
108 INTEGER :: tnadd_method = -1
110 DIMENSION(:),
POINTER :: sab_orb_full => null(), sac_kin => null()
112 INTEGER,
DIMENSION(:),
POINTER :: subset_of_mol => null()
113 TYPE(subset_type),
DIMENSION(:),
POINTER :: subset => null()
114 INTEGER :: nsubsets = -1
115 INTEGER :: maxdegree = -1
116 INTEGER :: coloring_method = -1
137 CHARACTER(LEN=*),
PARAMETER :: routinen =
'kg_env_release'
139 INTEGER :: handle, isub
141 CALL timeset(routinen, handle)
143 cpassert(
ASSOCIATED(kg_env))
148 IF (
ASSOCIATED(kg_env%tnadd_mat))
THEN
152 DO isub = 1, kg_env%nsubsets
157 IF (
ASSOCIATED(kg_env%subset_of_mol))
DEALLOCATE (kg_env%subset_of_mol)
158 IF (
ASSOCIATED(kg_env%subset))
DEALLOCATE (kg_env%subset)
160 IF (
ALLOCATED(kg_env%atom_to_molecule))
DEALLOCATE (kg_env%atom_to_molecule)
163 IF (
ASSOCIATED(kg_env%lri_env))
THEN
165 DEALLOCATE (kg_env%lri_env)
167 IF (
ASSOCIATED(kg_env%lri_density))
THEN
169 DEALLOCATE (kg_env%lri_density)
171 IF (
ASSOCIATED(kg_env%lri_env1))
THEN
173 DEALLOCATE (kg_env%lri_env1)
175 IF (
ASSOCIATED(kg_env%lri_rho1))
THEN
177 DEALLOCATE (kg_env%lri_rho1)
180 IF (
ASSOCIATED(kg_env%int_grid_atom))
THEN
183 IF (
ASSOCIATED(kg_env%int_grid_molecules))
THEN
186 IF (
ASSOCIATED(kg_env%int_grid_full))
THEN
192 CALL timestop(handle)
DBCSR operations in CP2K.
subroutine, public deallocate_intgrid(int_grid)
Deallocate integration_grid_type.
Types needed for a Kim-Gordon-like partitioning into molecular subunits.
subroutine, public kg_env_release(kg_env)
...
Defines the basic variable types.
integer, parameter, public dp
contains the types and subroutines for dealing with the lri_env lri : local resolution of the identit...
subroutine, public lri_density_release(lri_density)
releases the given lri_density
subroutine, public lri_env_release(lri_env)
releases the given lri_env
Define the data structure for the molecule information.
Definition of disperson types for DFT calculations.
subroutine, public deallocate_atom_int_grid(int_grid)
...
Define the neighbor list data types and the corresponding functionality.
subroutine, public release_neighbor_list_sets(nlists)
releases an array of neighbor_list_sets
subroutine, public deallocate_task_list(task_list)
deallocates the components and the object itself
Contains information on the energy correction functional for KG.
Contains all the info needed for KG runs...