(git:c9ed8e0)
Loading...
Searching...
No Matches
qs_wf_history_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief interpolate the wavefunctions to speed up the convergence when
10!> doing MD
11!> \par History
12!> 12.2002 created [fawzi]
13!> 02.2005 wf_mol added [MI]
14!> \author fawzi
15! **************************************************************************************************
21 USE cp_fm_types, ONLY: cp_fm_release,&
23 USE kinds, ONLY: dp
24 USE pw_types, ONLY: pw_c1d_gs_type,&
26 USE qs_rho_types, ONLY: qs_rho_release,&
28#include "./base/base_uses.f90"
29
30 IMPLICIT NONE
31 PRIVATE
32
33 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
34 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_wf_history_types'
35
36 PUBLIC :: qs_wf_snapshot_type, &
39
40! **************************************************************************************************
41!> \brief represent a past snapshot of the wavefunction.
42!> some elements might not be associated (to spare memory)
43!> depending on how the snapshot was taken
44!> \param wf the wavefunctions
45!> \param rho_r the density in r space
46!> \param rho_g the density in g space
47!> \param rho_ao the density in ao space
48!> \param overlap the overlap matrix
49!> \param rho_frozen the frozen density structure
50!> \param dt the time of the snapshot (wrf to te previous snapshot!)
51!> \note
52!> keep track also of occupation numbers and energies?
53!> \par History
54!> 02.2003 created [fawzi]
55!> 02.2005 wf_mol added [MI]
56!> \author fawzi
57! **************************************************************************************************
59 TYPE(cp_fm_type), DIMENSION(:), POINTER :: wf => null()
60 TYPE(pw_r3d_rs_type), DIMENSION(:), POINTER :: rho_r => null()
61 TYPE(pw_c1d_gs_type), DIMENSION(:), POINTER :: rho_g => null()
62 TYPE(dbcsr_p_type), DIMENSION(:), POINTER :: rho_ao => null()
63 TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER :: rho_ao_kp => null()
64 TYPE(dbcsr_type), POINTER :: overlap => null()
65 TYPE(qs_rho_type), POINTER :: rho_frozen => null()
66 REAL(kind=dp) :: dt = 0.0_dp
67 END TYPE qs_wf_snapshot_type
68
69! **************************************************************************************************
70!> \brief pointer to a snapshot
71!> \param snapshot the pointer to the snapshot
72!> \par History
73!> 02.2003 created [fawzi]
74!> \author fawzi
75! **************************************************************************************************
76 TYPE qs_wf_snapshot_p_type
77 TYPE(qs_wf_snapshot_type), POINTER :: snapshot => null()
78 END TYPE qs_wf_snapshot_p_type
79
80! **************************************************************************************************
81!> \brief keeps track of the previous wavefunctions and can extrapolate them
82!> for the next step of md
83!> \param ref_cont reference count (see doc/ReferenceCounting.html)
84!> \param memory_depth how many snapshots should be stored
85!> \param last_state_index index of the latest snapshot
86!> \param past_states array with the past states (index starts at
87!> last_state_index)
88!> \param interpolation_method_nr the tag of the method used to
89!> extrapolate the new start state for qs
90!> \param snapshot_count number of snapshot taken so far (cumulative,
91!> can be bigger than the history depth)
92!> \note
93!> use a linked list for the past states ?
94!> \par History
95!> 02.2003 created [fawzi]
96!> \author fawzi
97! **************************************************************************************************
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()
105 END TYPE qs_wf_history_type
106
107! **************************************************************************************************
108!> \brief to create arrays of pointers to qs_wf_history_type
109!> \param wf_hist the pointer to the wf history
110!> \author fawzi
111! **************************************************************************************************
113 TYPE(qs_wf_history_type), POINTER :: wf_history => null()
114 END TYPE qs_wf_history_p_type
115
116CONTAINS
117
118! **************************************************************************************************
119!> \brief releases a snapshot of a wavefunction (see doc/ReferenceCounting.html)
120!> \param snapshot the snapshot to release
121!> \par History
122!> 02.2003 created [fawzi]
123!> 02.2005 wf_mol added [MI]
124!> \author fawzi
125! **************************************************************************************************
126 SUBROUTINE wfs_release(snapshot)
127 TYPE(qs_wf_snapshot_type), INTENT(INOUT) :: snapshot
128
129 CALL cp_fm_release(snapshot%wf)
130 ! snapshot%rho_r & snapshot%rho_g is deallocated in wfs_update
131 ! of qs_wf_history_methods, in case you wonder about it.
132 IF (ASSOCIATED(snapshot%rho_ao)) THEN
133 CALL dbcsr_deallocate_matrix_set(snapshot%rho_ao)
134 END IF
135 IF (ASSOCIATED(snapshot%rho_ao_kp)) THEN
136 CALL dbcsr_deallocate_matrix_set(snapshot%rho_ao_kp)
137 END IF
138 IF (ASSOCIATED(snapshot%overlap)) THEN
139 CALL dbcsr_deallocate_matrix(snapshot%overlap)
140 END IF
141 IF (ASSOCIATED(snapshot%rho_frozen)) THEN
142 CALL qs_rho_release(snapshot%rho_frozen)
143 DEALLOCATE (snapshot%rho_frozen)
144 END IF
145
146 END SUBROUTINE wfs_release
147
148! **************************************************************************************************
149!> \brief retains a wf history (see doc/ReferenceCounting.html)
150!> \param wf_history the wf_history to retain
151!> \par History
152!> 02.2003 created [fawzi]
153!> \author fawzi
154! **************************************************************************************************
155 SUBROUTINE wfi_retain(wf_history)
156 TYPE(qs_wf_history_type), POINTER :: wf_history
157
158 cpassert(ASSOCIATED(wf_history))
159 wf_history%ref_count = wf_history%ref_count + 1
160
161 END SUBROUTINE wfi_retain
162
163! **************************************************************************************************
164!> \brief releases a wf_history of a wavefunction
165!> (see doc/ReferenceCounting.html)
166!> \param wf_history the wf_history to release
167!> \par History
168!> 02.2003 created [fawzi]
169!> \author fawzi
170! **************************************************************************************************
171 SUBROUTINE wfi_release(wf_history)
172 TYPE(qs_wf_history_type), POINTER :: wf_history
173
174 INTEGER :: i
175
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)
185 END IF
186 END DO
187 DEALLOCATE (wf_history%past_states)
188 END IF
189 DEALLOCATE (wf_history)
190 END IF
191 END IF
192 NULLIFY (wf_history)
193 END SUBROUTINE wfi_release
194
195! **************************************************************************************************
196!> \brief returns a snapshot, the first being the latest snapshot
197!> \param wf_history the plage where to get the snapshot
198!> \param wf_index the index of the snapshot you want
199!> \return ...
200!> \par History
201!> 12.2002 created [fawzi]
202!> \author fawzi
203! **************************************************************************************************
204 FUNCTION wfi_get_snapshot(wf_history, wf_index) RESULT(res)
205 TYPE(qs_wf_history_type), POINTER :: wf_history
206 INTEGER, INTENT(in) :: wf_index
207 TYPE(qs_wf_snapshot_type), POINTER :: res
208
209 NULLIFY (res)
210
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
214 cpabort("")
215 END IF
216 res => wf_history%past_states( &
217 modulo(wf_history%snapshot_count + 1 - wf_index, &
218 wf_history%memory_depth) + 1)%snapshot
219 END FUNCTION wfi_get_snapshot
220
221END MODULE qs_wf_history_types
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
Definition cp_fm_types.F:15
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
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)
represent a full matrix
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...