28#include "./base/base_uses.f90"
33 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
34 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'qs_wf_history_types'
63 TYPE(
dbcsr_p_type),
DIMENSION(:, :),
POINTER :: rho_ao_kp => null()
66 REAL(kind=
dp) :: dt = 0.0_dp
76 TYPE qs_wf_snapshot_p_type
78 END TYPE qs_wf_snapshot_p_type
99 INTEGER :: ref_count = -1, memory_depth = -1, last_state_index = -1, &
100 interpolation_method_nr = -1, snapshot_count = -1
101 LOGICAL :: store_wf = .false., store_rho_r = .false., store_rho_g = .false., &
102 store_rho_ao = .false., store_rho_ao_kp = .false., &
103 store_overlap = .false., store_frozen_density = .false.
104 TYPE(qs_wf_snapshot_p_type),
DIMENSION(:),
POINTER :: past_states => null()
132 IF (
ASSOCIATED(snapshot%rho_ao))
THEN
135 IF (
ASSOCIATED(snapshot%rho_ao_kp))
THEN
138 IF (
ASSOCIATED(snapshot%overlap))
THEN
141 IF (
ASSOCIATED(snapshot%rho_frozen))
THEN
143 DEALLOCATE (snapshot%rho_frozen)
158 cpassert(
ASSOCIATED(wf_history))
159 wf_history%ref_count = wf_history%ref_count + 1
176 IF (
ASSOCIATED(wf_history))
THEN
177 cpassert(wf_history%ref_count > 0)
178 wf_history%ref_count = wf_history%ref_count - 1
179 IF (wf_history%ref_count == 0)
THEN
180 IF (
ASSOCIATED(wf_history%past_states))
THEN
181 DO i = 1,
SIZE(wf_history%past_states)
182 IF (
ASSOCIATED(wf_history%past_states(i)%snapshot))
THEN
183 CALL wfs_release(wf_history%past_states(i)%snapshot)
184 DEALLOCATE (wf_history%past_states(i)%snapshot)
187 DEALLOCATE (wf_history%past_states)
189 DEALLOCATE (wf_history)
206 INTEGER,
INTENT(in) :: wf_index
211 cpassert(
ASSOCIATED(wf_history))
212 cpassert(
ASSOCIATED(wf_history%past_states))
213 IF (wf_index > wf_history%memory_depth .OR. wf_index > wf_history%snapshot_count)
THEN
216 res => wf_history%past_states( &
217 modulo(wf_history%snapshot_count + 1 - wf_index, &
218 wf_history%memory_depth) + 1)%snapshot
static GRID_HOST_DEVICE int modulo(int a, int m)
Equivalent of Fortran's MODULO, which always return a positive number. https://gcc....
subroutine, public dbcsr_deallocate_matrix(matrix)
...
DBCSR operations in CP2K.
represent a full matrix distributed on many processors
Defines the basic variable types.
integer, parameter, public dp
superstucture that hold various representations of the density and keeps track of which ones are vali...
subroutine, public qs_rho_release(rho_struct)
releases a rho_struct by decreasing the reference count by one and deallocating if it reaches 0 (to b...
interpolate the wavefunctions to speed up the convergence when doing MD
type(qs_wf_snapshot_type) function, pointer, public wfi_get_snapshot(wf_history, wf_index)
returns a snapshot, the first being the latest snapshot
subroutine, public wfi_retain(wf_history)
retains a wf history (see doc/ReferenceCounting.html)
subroutine wfs_release(snapshot)
releases a snapshot of a wavefunction (see doc/ReferenceCounting.html)
subroutine, public wfi_release(wf_history)
releases a wf_history of a wavefunction (see doc/ReferenceCounting.html)
keeps the density in various representations, keeping track of which ones are valid.
to create arrays of pointers to qs_wf_history_type
keeps track of the previous wavefunctions and can extrapolate them for the next step of md
represent a past snapshot of the wavefunction. some elements might not be associated (to spare memory...