22#include "./base/base_uses.f90" 
   27   LOGICAL, 
PRIVATE, 
PARAMETER :: debug_this_module = .true.
 
   28   CHARACTER(len=*), 
PARAMETER, 
PRIVATE :: moduleN = 
'qs_diis_types' 
   44      INTEGER                                          :: nbuffer = -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()
 
 
   58   TYPE qs_diis_buffer_p_type
 
   60   END TYPE qs_diis_buffer_p_type
 
   70      INTEGER                                          :: nbuffer = -1
 
   74      REAL(kind=
dp), 
DIMENSION(:, :), 
POINTER          :: b_matrix => null()
 
 
   77   TYPE qs_diis_buffer_p_type_sparse
 
   79   END TYPE qs_diis_buffer_p_type_sparse
 
   89      INTEGER                                          :: nbuffer = -1
 
   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()
 
 
   97   TYPE qs_diis_buffer_p_type_kp
 
   99   END TYPE qs_diis_buffer_p_type_kp
 
  113      IF (
ASSOCIATED(diis_buffer%b_matrix)) 
THEN 
  114         DEALLOCATE (diis_buffer%b_matrix)
 
 
  134      IF (
ASSOCIATED(diis_buffer%b_matrix)) 
THEN 
  135         DEALLOCATE (diis_buffer%b_matrix)
 
  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)
 
  141               DEALLOCATE (diis_buffer%error(i, j)%matrix)
 
  144         DEALLOCATE (diis_buffer%error)
 
  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)
 
  150               DEALLOCATE (diis_buffer%param(i, j)%matrix)
 
  153         DEALLOCATE (diis_buffer%param)
 
 
  166      IF (
ASSOCIATED(diis_buffer%b_matrix)) 
THEN 
  167         DEALLOCATE (diis_buffer%b_matrix)
 
  169      IF (
ASSOCIATED(diis_buffer%smat)) 
THEN 
  170         DO i = 1, 
SIZE(diis_buffer%smat)
 
  173         DEALLOCATE (diis_buffer%smat)
 
  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)
 
  183         DEALLOCATE (diis_buffer%error)
 
  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)
 
  193         DEALLOCATE (diis_buffer%param)
 
 
Represents a complex full matrix distributed on many processors.
 
subroutine, public cp_cfm_release(matrix)
Releases a full matrix.
 
subroutine, public dbcsr_release(matrix)
...
 
represent a full matrix distributed on many processors
 
Defines the basic variable types.
 
integer, parameter, public dp
 
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.
 
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