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 Types needed for a for a Energy Correction
10 : !> \par History
11 : !> 2019.09 created
12 : !> \author JGH
13 : ! **************************************************************************************************
14 : MODULE ec_env_types
15 : USE cp_dbcsr_api, ONLY: dbcsr_p_type
16 : USE cp_dbcsr_operations, ONLY: dbcsr_deallocate_matrix_set
17 : USE cp_fm_types, ONLY: cp_fm_release,&
18 : cp_fm_type
19 : USE dm_ls_scf_types, ONLY: ls_scf_env_type,&
20 : ls_scf_release
21 : USE hfx_types, ONLY: hfx_release,&
22 : hfx_type
23 : USE input_section_types, ONLY: section_vals_release,&
24 : section_vals_type
25 : USE kinds, ONLY: dp
26 : USE pw_types, ONLY: pw_r3d_rs_type
27 : USE qs_dispersion_types, ONLY: qs_dispersion_release,&
28 : qs_dispersion_type
29 : USE qs_force_types, ONLY: deallocate_qs_force,&
30 : qs_force_type
31 : USE qs_neighbor_list_types, ONLY: neighbor_list_set_p_type,&
32 : release_neighbor_list_sets
33 : USE qs_p_env_types, ONLY: p_env_release,&
34 : qs_p_env_type
35 : USE qs_period_efield_types, ONLY: efield_berry_release,&
36 : efield_berry_type
37 : USE task_list_types, ONLY: deallocate_task_list,&
38 : task_list_type
39 : #include "./base/base_uses.f90"
40 :
41 : IMPLICIT NONE
42 :
43 : PRIVATE
44 :
45 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'ec_env_types'
46 :
47 : PUBLIC :: energy_correction_type, ec_env_release
48 :
49 : ! *****************************************************************************
50 : !> \brief Contains information on the energy correction functional for KG
51 : !> \par History
52 : !> 03.2014 created
53 : !> \author JGH
54 : ! *****************************************************************************
55 : TYPE energy_correction_type
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.
68 : ! debug
69 : LOGICAL :: debug_forces = .FALSE.
70 : LOGICAL :: debug_stress = .FALSE.
71 : LOGICAL :: debug_external = .FALSE.
72 : ! basis set
73 : CHARACTER(len=20) :: basis = ""
74 : LOGICAL :: mao = .FALSE.
75 : ! Skip EC calculation if ground-state didnt converge
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
81 : ! energy components
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
87 : ! forces
88 : TYPE(qs_force_type), DIMENSION(:), POINTER :: force => Null()
89 : ! full neighbor lists and corresponding task list
90 : TYPE(neighbor_list_set_p_type), &
91 : DIMENSION(:), POINTER :: sab_orb => Null(), sac_ppl => Null(), sap_ppnl => Null()
92 : TYPE(task_list_type), POINTER :: task_list => Null()
93 : ! the XC function to be used for the correction, dispersion info
94 : TYPE(section_vals_type), POINTER :: xc_section => Null()
95 : TYPE(qs_dispersion_type), POINTER :: dispersion_env => Null()
96 : ! matrices in complete basis
97 : ! KS: Kohn-Sham; H: Core; S: overlap; T: kinetic energy;
98 : ! P: Harris density, W: Harris energy weighted density
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(), &
104 : matrix_w => Null()
105 : ! reduce basis
106 : TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: mao_coef => Null()
107 : ! external energy calclulation
108 : TYPE(cp_fm_type), DIMENSION(:), POINTER :: mo_occ => NULL()
109 : TYPE(cp_fm_type), DIMENSION(:), POINTER :: cpmos => NULL()
110 : ! CP equations
111 : TYPE(qs_p_env_type), POINTER :: p_env => Null()
112 : TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: matrix_hz => Null(), matrix_wz => Null(), &
113 : matrix_z => Null(), z_admm => Null()
114 : ! Harris (rhoout), and response density (rhoz) on grid
115 : TYPE(pw_r3d_rs_type), DIMENSION(:), POINTER :: rhoout_r => Null(), rhoz_r => Null()
116 : ! potentials from input density
117 : TYPE(pw_r3d_rs_type) :: vh_rspace = pw_r3d_rs_type()
118 : TYPE(pw_r3d_rs_type), DIMENSION(:), POINTER :: vxc_rspace => Null(), vtau_rspace => Null(), vadmm_rspace => Null()
119 : ! efield
120 : TYPE(efield_berry_type), POINTER :: efield => NULL()
121 : ! LS matrices and types
122 : TYPE(ls_scf_env_type), POINTER :: ls_env => Null()
123 : ! Environment for Hartree-Fock exchange
124 : TYPE(hfx_type), DIMENSION(:, :), POINTER :: x_data => Null()
125 : ! ADMM XC environments
126 : TYPE(section_vals_type), POINTER :: xc_section_primary => Null(), &
127 : xc_section_aux => Null()
128 : END TYPE energy_correction_type
129 :
130 : CONTAINS
131 :
132 : ! **************************************************************************************************
133 : !> \brief ...
134 : !> \param ec_env ...
135 : ! **************************************************************************************************
136 6686 : SUBROUTINE ec_env_release(ec_env)
137 : TYPE(energy_correction_type), POINTER :: ec_env
138 :
139 : CHARACTER(LEN=*), PARAMETER :: routineN = 'ec_env_release'
140 :
141 : INTEGER :: handle, iab
142 :
143 6686 : CALL timeset(routineN, handle)
144 :
145 6686 : IF (ASSOCIATED(ec_env)) THEN
146 : ! neighbor lists
147 6686 : CALL release_neighbor_list_sets(ec_env%sab_orb)
148 6686 : CALL release_neighbor_list_sets(ec_env%sac_ppl)
149 6686 : CALL release_neighbor_list_sets(ec_env%sap_ppnl)
150 : ! forces
151 6686 : IF (ASSOCIATED(ec_env%force)) CALL deallocate_qs_force(ec_env%force)
152 : ! operator matrices
153 6686 : IF (ASSOCIATED(ec_env%matrix_ks)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_ks)
154 6686 : IF (ASSOCIATED(ec_env%matrix_h)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_h)
155 6686 : IF (ASSOCIATED(ec_env%matrix_s)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_s)
156 6686 : IF (ASSOCIATED(ec_env%matrix_t)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_t)
157 6686 : IF (ASSOCIATED(ec_env%matrix_p)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_p)
158 6686 : IF (ASSOCIATED(ec_env%matrix_w)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_w)
159 6686 : IF (ASSOCIATED(ec_env%task_list)) THEN
160 236 : CALL deallocate_task_list(ec_env%task_list)
161 : END IF
162 : ! reduced basis
163 6686 : IF (ASSOCIATED(ec_env%mao_coef)) CALL dbcsr_deallocate_matrix_set(ec_env%mao_coef)
164 : ! dispersion environment
165 6686 : IF (ASSOCIATED(ec_env%dispersion_env)) THEN
166 236 : CALL qs_dispersion_release(ec_env%dispersion_env)
167 : END IF
168 :
169 6686 : IF (ASSOCIATED(ec_env%matrix_hz)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_hz)
170 6686 : IF (ASSOCIATED(ec_env%matrix_wz)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_wz)
171 6686 : IF (ASSOCIATED(ec_env%matrix_z)) CALL dbcsr_deallocate_matrix_set(ec_env%matrix_z)
172 6686 : IF (ASSOCIATED(ec_env%z_admm)) CALL dbcsr_deallocate_matrix_set(ec_env%z_admm)
173 6686 : NULLIFY (ec_env%matrix_z, ec_env%matrix_hz, ec_env%matrix_wz)
174 6686 : NULLIFY (ec_env%z_admm)
175 :
176 6686 : IF (ASSOCIATED(ec_env%p_env)) THEN
177 216 : CALL p_env_release(ec_env%p_env)
178 216 : DEALLOCATE (ec_env%p_env)
179 : END IF
180 : ! potential
181 6686 : IF (ASSOCIATED(ec_env%vh_rspace%pw_grid)) THEN
182 236 : CALL ec_env%vh_rspace%release()
183 : END IF
184 6686 : IF (ASSOCIATED(ec_env%vxc_rspace)) THEN
185 472 : DO iab = 1, SIZE(ec_env%vxc_rspace)
186 472 : CALL ec_env%vxc_rspace(iab)%release()
187 : END DO
188 236 : DEALLOCATE (ec_env%vxc_rspace)
189 : END IF
190 6686 : IF (ASSOCIATED(ec_env%vtau_rspace)) THEN
191 32 : DO iab = 1, SIZE(ec_env%vtau_rspace)
192 32 : CALL ec_env%vtau_rspace(iab)%release()
193 : END DO
194 16 : DEALLOCATE (ec_env%vtau_rspace)
195 : END IF
196 6686 : IF (ASSOCIATED(ec_env%vadmm_rspace)) THEN
197 48 : DO iab = 1, SIZE(ec_env%vadmm_rspace)
198 48 : CALL ec_env%vadmm_rspace(iab)%release()
199 : END DO
200 24 : DEALLOCATE (ec_env%vadmm_rspace)
201 : END IF
202 6686 : CALL efield_berry_release(ec_env%efield)
203 :
204 6686 : IF (ASSOCIATED(ec_env%ls_env)) THEN
205 22 : CALL ls_scf_release(ec_env%ls_env)
206 : END IF
207 :
208 6686 : IF (.NOT. ec_env%reuse_hfx) THEN
209 6676 : IF (ASSOCIATED(ec_env%x_data)) CALL hfx_release(ec_env%x_data)
210 : END IF
211 :
212 6686 : IF (ASSOCIATED(ec_env%xc_section_aux)) CALL section_vals_release(ec_env%xc_section_aux)
213 6686 : IF (ASSOCIATED(ec_env%xc_section_primary)) CALL section_vals_release(ec_env%xc_section_primary)
214 :
215 6686 : CALL cp_fm_release(ec_env%mo_occ)
216 6686 : CALL cp_fm_release(ec_env%cpmos)
217 :
218 6686 : DEALLOCATE (ec_env)
219 :
220 : END IF
221 :
222 6686 : NULLIFY (ec_env)
223 :
224 6686 : CALL timestop(handle)
225 :
226 6686 : END SUBROUTINE ec_env_release
227 :
228 0 : END MODULE ec_env_types
|