89 INTEGER :: nspins = 0, natoms = 0
90 INTEGER :: nelectron_total = 0
91 INTEGER,
DIMENSION(2) :: nelectron_spin = 0
92 REAL(kind=
dp),
DIMENSION(2) :: mu_spin = 0.0_dp
93 REAL(kind=
dp),
DIMENSION(2) :: homo_spin = 0.0_dp
94 REAL(kind=
dp),
DIMENSION(2) :: lumo_spin = 0.0_dp
96#if defined(FTN_NO_DEFAULT_INIT)
97 TYPE(ls_mat_history_type) :: scf_history = ls_mat_history_type(matrix=null())
99 TYPE(ls_mat_history_type) :: scf_history = ls_mat_history_type()
101 INTEGER :: extrapolation_order = -1
103 LOGICAL :: has_unit_metric = .false.
105 LOGICAL :: curvy_steps = .false.
106 INTEGER :: s_preconditioner_type = 0
107 INTEGER :: s_inversion_type = 0
108 INTEGER :: purification_method = 0
109 INTEGER :: sign_method = 0
110 INTEGER :: sign_order = 0
111 LOGICAL :: sign_symmetric = .false.
112 INTEGER :: submatrix_sign_method = -1
113 INTEGER :: s_sqrt_method = 0
114 INTEGER :: s_sqrt_order = 0
116 LOGICAL :: needs_s_inv = .false., has_s_preconditioner = .false., fixed_mu = .false., &
117 dynamic_threshold = .false., check_s_inv = .false.
118 LOGICAL :: restart_read = .false., restart_write = .false., non_monotonic = .false.
119 REAL(kind=
dp) :: eps_filter = 0.0_dp, eps_scf = 0.0_dp
121 REAL(kind=
dp) :: eps_lanczos = 0.0_dp
122 INTEGER :: max_iter_lanczos = 0
124 REAL(kind=
dp) :: mixing_fraction = 0.0_dp
125 INTEGER :: max_scf = 0
126 LOGICAL :: ls_diis = .false.
127 INTEGER :: iter_ini_diis = 0
128 INTEGER :: nmixing = 0, max_diis = 0
129 REAL(kind=
dp) :: eps_diis = 0.0_dp
130 REAL(kind=
dp) :: energy_init = 0.0_dp
139 LOGICAL :: report_all_sparsities = .false., perform_mu_scan = .false., use_s_sqrt = .false.
141#if defined(FTN_NO_DEFAULT_INIT)
144 matrix_psave=null(), matrix_bch=null())
150 TYPE(chebyshev_type) :: chebyshev = chebyshev_type()
152 LOGICAL :: do_rho_mixing = .false.
153 INTEGER :: density_mixing_method = 0
156 LOGICAL :: do_transport = .false.
157 LOGICAL :: do_pexsi = .false.
159 LOGICAL :: calculate_forces = .false.
161#if defined(__LIBPEXSI)
168 LOGICAL :: do_pao = .false.
186 CHARACTER(len=*),
PARAMETER :: routinen =
'ls_scf_release'
188 INTEGER :: handle, ispin, istore
190 CALL timeset(routinen, handle)
194 DEALLOCATE (ls_scf_env%ls_mstruct%atom_to_molecule)
197 DO istore = 1, min(ls_scf_env%scf_history%istore, ls_scf_env%scf_history%nstore)
198 DO ispin = 1,
SIZE(ls_scf_env%scf_history%matrix, 1)
199 CALL dbcsr_release(ls_scf_env%scf_history%matrix(ispin, istore))
202 DEALLOCATE (ls_scf_env%scf_history%matrix)
204 IF (
ALLOCATED(ls_scf_env%matrix_p))
THEN
205 DO ispin = 1,
SIZE(ls_scf_env%matrix_p)
208 DEALLOCATE (ls_scf_env%matrix_p)
211 IF (
ASSOCIATED(ls_scf_env%chebyshev%print_key_dos)) &
213 IF (
ASSOCIATED(ls_scf_env%chebyshev%print_key_cube)) &
215 IF (
ASSOCIATED(ls_scf_env%chebyshev%min_energy))
THEN
216 DEALLOCATE (ls_scf_env%chebyshev%min_energy)
218 IF (
ASSOCIATED(ls_scf_env%chebyshev%max_energy))
THEN
219 DEALLOCATE (ls_scf_env%chebyshev%max_energy)
222 IF (
ASSOCIATED(ls_scf_env%mixing_store))
THEN
224 DEALLOCATE (ls_scf_env%mixing_store)
227 IF (ls_scf_env%do_pexsi)
THEN
231 IF (ls_scf_env%do_pao) &
234 DEALLOCATE (ls_scf_env)
236 CALL timestop(handle)