(git:374b731)
Loading...
Searching...
No Matches
qs_diis_types.F
Go to the documentation of this file.
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 buffer for the diis of the scf
10!> \par History
11!> 02.2003 rewamped [fawzi]
12!> \author Matthias Krack
13! **************************************************************************************************
15 USE cp_cfm_types, ONLY: cp_cfm_release,&
17 USE cp_fm_types, ONLY: cp_fm_release,&
19 USE dbcsr_api, ONLY: dbcsr_p_type,&
20 dbcsr_release
21 USE kinds, ONLY: dp
22#include "./base/base_uses.f90"
23
24 IMPLICIT NONE
25 PRIVATE
26
27 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
28 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_diis_types'
29
30 PUBLIC :: qs_diis_buffer_type
31 PUBLIC :: qs_diis_b_release
36
37! **************************************************************************************************
38!> \brief keeps a buffer with the previous values of s,p,k
39!> \par History
40!> 02.2003 rewamped [fawzi]
41!> \author Matthias Krack
42! **************************************************************************************************
44 INTEGER :: nbuffer = -1
45 INTEGER :: ncall = -1
46 TYPE(cp_fm_type), DIMENSION(:, :), POINTER :: error => null()
47 TYPE(cp_fm_type), DIMENSION(:, :), POINTER :: param => null()
48 REAL(kind=dp), DIMENSION(:, :), POINTER :: b_matrix => null()
49 END TYPE qs_diis_buffer_type
50
51! **************************************************************************************************
52!> \brief build array of pointers to diis buffers
53!> \param diis_buffer the diis buffer pointer
54!> \par History
55!> 02.2003 created [fawzi]
56!> \author fawzi
57! **************************************************************************************************
58 TYPE qs_diis_buffer_p_type
59 TYPE(qs_diis_buffer_type), POINTER :: diis_buffer => null()
60 END TYPE qs_diis_buffer_p_type
61
62! **************************************************************************************************
63!> \brief build array of pointers to diis buffers for sparse matrix case
64!> \param diis_buffer the diis buffer pointer
65!> \par History
66!> 10.2014 Modified from non-sparse case by Fredy W. Aquino
67!> \author fwaq
68! **************************************************************************************************
70 INTEGER :: nbuffer = -1
71 INTEGER :: ncall = -1
72 TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER :: error => null()
73 TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER :: param => null()
74 REAL(kind=dp), DIMENSION(:, :), POINTER :: b_matrix => null()
76
77 TYPE qs_diis_buffer_p_type_sparse
78 TYPE(qs_diis_buffer_type_sparse), POINTER :: diis_buffer => null()
79 END TYPE qs_diis_buffer_p_type_sparse
80
81! **************************************************************************************************
82!> \brief build arrau of pointers to diis buffers in the k-point (complex full matrices) case
83!> \note we keep the overlap matrix and 1 parameter matrix per k-point, in the corresponding kp subgroup
84!> \par History
85!> 04.2023 created
86!> \author Augustin Bussy
87! **************************************************************************************************
89 INTEGER :: nbuffer = -1
90 INTEGER :: ncall = -1
91 TYPE(cp_cfm_type), DIMENSION(:), POINTER :: smat => null()
92 TYPE(cp_cfm_type), DIMENSION(:, :, :), POINTER :: param => null()
93 TYPE(cp_cfm_type), DIMENSION(:, :, :), POINTER :: error => null()
94 COMPLEX(KIND=dp), DIMENSION(:, :), POINTER :: b_matrix => null()
96
97 TYPE qs_diis_buffer_p_type_kp
98 TYPE(qs_diis_buffer_type_kp), POINTER :: diis_buffer => null()
99 END TYPE qs_diis_buffer_p_type_kp
100
101CONTAINS
102
103! **************************************************************************************************
104!> \brief releases the given diis buffer (see doc/ReferenceCounting.html)
105!> \param diis_buffer the buffer to release
106!> \par History
107!> 02.2003 created [fawzi]
108!> \author fawzi
109! **************************************************************************************************
110 SUBROUTINE qs_diis_b_release(diis_buffer)
111 TYPE(qs_diis_buffer_type), INTENT(INOUT) :: diis_buffer
112
113 IF (ASSOCIATED(diis_buffer%b_matrix)) THEN
114 DEALLOCATE (diis_buffer%b_matrix)
115 END IF
116 CALL cp_fm_release(diis_buffer%error)
117 CALL cp_fm_release(diis_buffer%param)
118
119 END SUBROUTINE qs_diis_b_release
120
121! **************************************************************************************************
122!> \brief releases the given diis buffer (see doc/ReferenceCounting.html)
123!> \param diis_buffer the buffer to release
124!> \par History
125!> 10-11-14 created [FA] modified from qs_diis_b_release
126!> \author Fredy W. Aquino
127! **************************************************************************************************
128 SUBROUTINE qs_diis_b_release_sparse(diis_buffer)
129
130 TYPE(qs_diis_buffer_type_sparse), INTENT(INOUT) :: diis_buffer
131
132 INTEGER :: i, j
133
134 IF (ASSOCIATED(diis_buffer%b_matrix)) THEN
135 DEALLOCATE (diis_buffer%b_matrix)
136 END IF
137 IF (ASSOCIATED(diis_buffer%error)) THEN
138 DO j = 1, SIZE(diis_buffer%error, 2)
139 DO i = 1, SIZE(diis_buffer%error, 1)
140 CALL dbcsr_release(diis_buffer%error(i, j)%matrix)
141 DEALLOCATE (diis_buffer%error(i, j)%matrix)
142 END DO
143 END DO
144 DEALLOCATE (diis_buffer%error)
145 END IF
146 IF (ASSOCIATED(diis_buffer%param)) THEN
147 DO j = 1, SIZE(diis_buffer%param, 2)
148 DO i = 1, SIZE(diis_buffer%param, 1)
149 CALL dbcsr_release(diis_buffer%param(i, j)%matrix)
150 DEALLOCATE (diis_buffer%param(i, j)%matrix)
151 END DO
152 END DO
153 DEALLOCATE (diis_buffer%param)
154 END IF
155 END SUBROUTINE qs_diis_b_release_sparse
156
157! **************************************************************************************************
158!> \brief releases the given diis KP buffer
159!> \param diis_buffer the buffer to release
160! **************************************************************************************************
161 SUBROUTINE qs_diis_b_release_kp(diis_buffer)
162 TYPE(qs_diis_buffer_type_kp), INTENT(INOUT) :: diis_buffer
163
164 INTEGER :: i, j, k
165
166 IF (ASSOCIATED(diis_buffer%b_matrix)) THEN
167 DEALLOCATE (diis_buffer%b_matrix)
168 END IF
169 IF (ASSOCIATED(diis_buffer%smat)) THEN
170 DO i = 1, SIZE(diis_buffer%smat)
171 CALL cp_cfm_release(diis_buffer%smat(i))
172 END DO
173 DEALLOCATE (diis_buffer%smat)
174 END IF
175 IF (ASSOCIATED(diis_buffer%error)) THEN
176 DO k = 1, SIZE(diis_buffer%error, 3)
177 DO j = 1, SIZE(diis_buffer%error, 2)
178 DO i = 1, SIZE(diis_buffer%error, 1)
179 CALL cp_cfm_release(diis_buffer%error(i, j, k))
180 END DO
181 END DO
182 END DO
183 DEALLOCATE (diis_buffer%error)
184 END IF
185 IF (ASSOCIATED(diis_buffer%param)) THEN
186 DO k = 1, SIZE(diis_buffer%param, 3)
187 DO j = 1, SIZE(diis_buffer%param, 2)
188 DO i = 1, SIZE(diis_buffer%param, 1)
189 CALL cp_cfm_release(diis_buffer%param(i, j, k))
190 END DO
191 END DO
192 END DO
193 DEALLOCATE (diis_buffer%param)
194 END IF
195 END SUBROUTINE qs_diis_b_release_kp
196END MODULE qs_diis_types
Represents a complex full matrix distributed on many processors.
subroutine, public cp_cfm_release(matrix)
Releases a full matrix.
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
buffer for the diis of the scf
subroutine, public qs_diis_b_release_kp(diis_buffer)
releases the given diis KP buffer
subroutine, public qs_diis_b_release(diis_buffer)
releases the given diis buffer (see doc/ReferenceCounting.html)
subroutine, public qs_diis_b_release_sparse(diis_buffer)
releases the given diis buffer (see doc/ReferenceCounting.html)
Represent a complex full matrix.
represent a full matrix
build arrau of pointers to diis buffers in the k-point (complex full matrices) case
build array of pointers to diis buffers for sparse matrix case
keeps a buffer with the previous values of s,p,k