(git:e7e05ae)
cp_dbcsr_diag.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 Interface to (sca)lapack for the Cholesky based procedures
10 !> \author VW
11 !> \date 2009-11-09
12 !> \version 0.8
13 !>
14 !> <b>Modification history:</b>
15 !> - Created 2009-11-09
16 ! **************************************************************************************************
18 
19  USE cp_blacs_env, ONLY: cp_blacs_env_type
20  USE cp_cfm_diag, ONLY: cp_cfm_heevd
21  USE cp_cfm_types, ONLY: cp_cfm_create,&
23  cp_cfm_type
28  USE cp_fm_diag, ONLY: choose_eigv_solver,&
29  cp_fm_power,&
33  cp_fm_struct_type
34  USE cp_fm_types, ONLY: cp_fm_create,&
35  cp_fm_release,&
36  cp_fm_type
37  USE dbcsr_api, ONLY: dbcsr_get_info,&
38  dbcsr_type
39  USE kinds, ONLY: dp
40  USE message_passing, ONLY: mp_para_env_type
41 #include "base/base_uses.f90"
42 
43  IMPLICIT NONE
44 
45  PRIVATE
46 
47  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_dbcsr_diag'
48 
49  ! Public subroutines
50 
51  PUBLIC :: cp_dbcsr_syevd, &
55 
56 CONTAINS
57 
58 ! **************************************************************************************************
59 !> \brief ...
60 !> \param matrix ...
61 !> \param eigenvectors ...
62 !> \param eigenvalues ...
63 !> \param para_env ...
64 !> \param blacs_env ...
65 ! **************************************************************************************************
66  SUBROUTINE cp_dbcsr_syevd(matrix, eigenvectors, eigenvalues, para_env, blacs_env)
67 
68  ! Computes all eigenvalues and vectors of a real symmetric matrix
69  ! should be quite a bit faster than syevx for that case
70  ! especially in parallel with thightly clustered evals
71  ! needs more workspace in the worst case, but much better distributed
72 
73  TYPE(dbcsr_type) :: matrix, eigenvectors
74  REAL(kind=dp), DIMENSION(:), INTENT(OUT) :: eigenvalues
75  TYPE(mp_para_env_type), POINTER :: para_env
76  TYPE(cp_blacs_env_type), POINTER :: blacs_env
77 
78  CHARACTER(len=*), PARAMETER :: routinen = 'cp_dbcsr_syevd'
79 
80  INTEGER :: handle, nfullrows_total
81  TYPE(cp_fm_struct_type), POINTER :: fm_struct
82  TYPE(cp_fm_type) :: fm_eigenvectors, fm_matrix
83 
84  CALL timeset(routinen, handle)
85 
86  NULLIFY (fm_struct)
87  CALL dbcsr_get_info(matrix, nfullrows_total=nfullrows_total)
88 
89  CALL cp_fm_struct_create(fm_struct, context=blacs_env, nrow_global=nfullrows_total, &
90  ncol_global=nfullrows_total, para_env=para_env)
91  CALL cp_fm_create(fm_matrix, fm_struct, name="fm_matrix")
92  CALL cp_fm_create(fm_eigenvectors, fm_struct, name="fm_eigenvectors")
93  CALL cp_fm_struct_release(fm_struct)
94 
95  CALL copy_dbcsr_to_fm(matrix, fm_matrix)
96 
97  CALL choose_eigv_solver(fm_matrix, fm_eigenvectors, eigenvalues)
98 
99  CALL copy_fm_to_dbcsr(fm_eigenvectors, eigenvectors)
100 
101  CALL cp_fm_release(fm_matrix)
102  CALL cp_fm_release(fm_eigenvectors)
103 
104  CALL timestop(handle)
105 
106  END SUBROUTINE cp_dbcsr_syevd
107 
108 ! **************************************************************************************************
109 !> \brief compute eigenvalues and optionally eigenvectors of a real symmetric matrix using scalapack.
110 !> If eigenvectors are required this routine will replicate a full matrix on each CPU...
111 !> if more than a handful of vectors are needed, use cp_dbcsr_syevd instead
112 !> \param matrix ...
113 !> \param eigenvectors ...
114 !> \param eigenvalues ...
115 !> \param neig ...
116 !> \param work_syevx ...
117 !> \param para_env ...
118 !> \param blacs_env ...
119 !> \par matrix is supposed to be in upper triangular form, and overwritten by this routine
120 !> neig is the number of vectors needed (default all)
121 !> work_syevx evec calculation only, is the fraction of the working buffer allowed (1.0 use full buffer)
122 !> reducing this saves time, but might cause the routine to fail
123 ! **************************************************************************************************
124  SUBROUTINE cp_dbcsr_syevx(matrix, eigenvectors, eigenvalues, neig, work_syevx, &
125  para_env, blacs_env)
126 
127  ! Diagonalise the symmetric n by n matrix using the LAPACK library.
128 
129  TYPE(dbcsr_type), POINTER :: matrix
130  TYPE(dbcsr_type), OPTIONAL, POINTER :: eigenvectors
131  REAL(kind=dp), DIMENSION(:), INTENT(OUT) :: eigenvalues
132  INTEGER, INTENT(IN), OPTIONAL :: neig
133  REAL(kind=dp), INTENT(IN), OPTIONAL :: work_syevx
134  TYPE(mp_para_env_type), POINTER :: para_env
135  TYPE(cp_blacs_env_type), POINTER :: blacs_env
136 
137  CHARACTER(LEN=*), PARAMETER :: routinen = 'cp_dbcsr_syevx'
138 
139  INTEGER :: handle, n, neig_local
140  TYPE(cp_fm_struct_type), POINTER :: fm_struct
141  TYPE(cp_fm_type) :: fm_eigenvectors, fm_matrix
142 
143  CALL timeset(routinen, handle)
144 
145  ! by default all
146  CALL dbcsr_get_info(matrix, nfullrows_total=n)
147  neig_local = n
148  IF (PRESENT(neig)) neig_local = neig
149  IF (neig_local == 0) RETURN
150 
151  NULLIFY (fm_struct)
152  CALL cp_fm_struct_create(fm_struct, context=blacs_env, nrow_global=n, &
153  ncol_global=n, para_env=para_env)
154  CALL cp_fm_create(fm_matrix, fm_struct, name="fm_matrix")
155 
156  CALL copy_dbcsr_to_fm(matrix, fm_matrix)
157 
158  IF (PRESENT(eigenvectors)) THEN
159  CALL cp_fm_create(fm_eigenvectors, fm_struct, name="fm_eigenvectors")
160  CALL cp_fm_syevx(fm_matrix, fm_eigenvectors, eigenvalues, neig, work_syevx)
161  CALL copy_fm_to_dbcsr(fm_eigenvectors, eigenvectors)
162  CALL cp_fm_release(fm_eigenvectors)
163  ELSE
164  CALL cp_fm_syevx(fm_matrix, eigenvalues=eigenvalues, neig=neig, work_syevx=work_syevx)
165  END IF
166 
167  CALL cp_fm_struct_release(fm_struct)
168  CALL cp_fm_release(fm_matrix)
169 
170  CALL timestop(handle)
171 
172  END SUBROUTINE cp_dbcsr_syevx
173 
174 ! **************************************************************************************************
175 !> \brief ...
176 !> \param matrix ...
177 !> \param eigenvectors ...
178 !> \param eigenvalues ...
179 !> \param para_env ...
180 !> \param blacs_env ...
181 ! **************************************************************************************************
182  SUBROUTINE cp_dbcsr_heevd(matrix, eigenvectors, eigenvalues, para_env, blacs_env)
183 
184  TYPE(dbcsr_type) :: matrix
185  TYPE(dbcsr_type), OPTIONAL, POINTER :: eigenvectors
186  REAL(kind=dp), DIMENSION(:), INTENT(OUT) :: eigenvalues
187  TYPE(mp_para_env_type), POINTER :: para_env
188  TYPE(cp_blacs_env_type), POINTER :: blacs_env
189 
190  CHARACTER(len=*), PARAMETER :: routinen = 'cp_dbcsr_heevd'
191 
192  INTEGER :: handle, nfullrows_total
193  TYPE(cp_cfm_type) :: fm_eigenvectors, fm_matrix
194  TYPE(cp_fm_struct_type), POINTER :: fm_struct
195 
196  CALL timeset(routinen, handle)
197 
198  NULLIFY (fm_struct)
199  CALL dbcsr_get_info(matrix, nfullrows_total=nfullrows_total)
200 
201  CALL cp_fm_struct_create(fm_struct, context=blacs_env, nrow_global=nfullrows_total, &
202  ncol_global=nfullrows_total, para_env=para_env)
203  CALL cp_cfm_create(fm_matrix, fm_struct, name="fm_matrix")
204  CALL cp_cfm_create(fm_eigenvectors, fm_struct, name="fm_eigenvectors")
205  CALL cp_fm_struct_release(fm_struct)
206 
207  CALL copy_dbcsr_to_cfm(matrix, fm_matrix)
208 
209  CALL cp_cfm_heevd(fm_matrix, fm_eigenvectors, eigenvalues)
210 
211  CALL copy_cfm_to_dbcsr(fm_eigenvectors, eigenvectors)
212 
213  CALL cp_cfm_release(fm_matrix)
214  CALL cp_cfm_release(fm_eigenvectors)
215 
216  CALL timestop(handle)
217 
218  END SUBROUTINE cp_dbcsr_heevd
219 
220 ! **************************************************************************************************
221 !> \brief ...
222 !> \param matrix ...
223 !> \param exponent ...
224 !> \param threshold ...
225 !> \param n_dependent ...
226 !> \param para_env ...
227 !> \param blacs_env ...
228 !> \param verbose ...
229 !> \param eigenvectors ...
230 !> \param eigenvalues ...
231 ! **************************************************************************************************
232  SUBROUTINE cp_dbcsr_power(matrix, exponent, threshold, n_dependent, para_env, blacs_env, verbose, eigenvectors, eigenvalues)
233  TYPE(dbcsr_type), INTENT(INOUT) :: matrix
234  REAL(dp), INTENT(IN) :: exponent, threshold
235  INTEGER, INTENT(OUT) :: n_dependent
236  TYPE(mp_para_env_type), POINTER :: para_env
237  TYPE(cp_blacs_env_type), POINTER :: blacs_env
238  LOGICAL, INTENT(IN), OPTIONAL :: verbose
239  TYPE(dbcsr_type), INTENT(INOUT), OPTIONAL :: eigenvectors
240  REAL(kind=dp), DIMENSION(2), INTENT(OUT), OPTIONAL :: eigenvalues
241 
242  CHARACTER(len=*), PARAMETER :: routinen = 'cp_dbcsr_power'
243 
244  INTEGER :: handle, nfullrows_total
245  REAL(kind=dp), DIMENSION(2) :: eigenvalues_prv
246  TYPE(cp_fm_struct_type), POINTER :: fm_struct
247  TYPE(cp_fm_type) :: fm_eigenvectors, fm_matrix
248 
249  CALL timeset(routinen, handle)
250 
251  NULLIFY (fm_struct)
252  CALL dbcsr_get_info(matrix, nfullrows_total=nfullrows_total)
253 
254  CALL cp_fm_struct_create(fm_struct, context=blacs_env, nrow_global=nfullrows_total, &
255  ncol_global=nfullrows_total, para_env=para_env)
256  CALL cp_fm_create(fm_matrix, fm_struct, name="fm_matrix")
257  CALL cp_fm_create(fm_eigenvectors, fm_struct, name="fm_eigenvectors")
258  CALL cp_fm_struct_release(fm_struct)
259 
260  CALL copy_dbcsr_to_fm(matrix, fm_matrix)
261 
262  CALL cp_fm_power(fm_matrix, fm_eigenvectors, exponent, threshold, n_dependent, verbose, eigenvalues_prv)
263 
264  CALL copy_fm_to_dbcsr(fm_matrix, matrix)
265  CALL cp_fm_release(fm_matrix)
266 
267  IF (PRESENT(eigenvalues)) eigenvalues(:) = eigenvalues_prv
268  IF (PRESENT(eigenvectors)) CALL copy_fm_to_dbcsr(fm_eigenvectors, eigenvectors)
269 
270  CALL cp_fm_release(fm_eigenvectors)
271 
272  CALL timestop(handle)
273 
274  END SUBROUTINE
275 
276 END MODULE cp_dbcsr_diag
methods related to the blacs parallel environment
Definition: cp_blacs_env.F:15
used for collecting diagonalization schemes available for cp_cfm_type
Definition: cp_cfm_diag.F:14
subroutine, public cp_cfm_heevd(matrix, eigenvectors, eigenvalues)
Perform a diagonalisation of a complex matrix.
Definition: cp_cfm_diag.F:52
Represents a complex full matrix distributed on many processors.
Definition: cp_cfm_types.F:12
subroutine, public cp_cfm_create(matrix, matrix_struct, name)
Creates a new full matrix with the given structure.
Definition: cp_cfm_types.F:121
subroutine, public cp_cfm_release(matrix)
Releases a full matrix.
Definition: cp_cfm_types.F:159
Interface to (sca)lapack for the Cholesky based procedures.
Definition: cp_dbcsr_diag.F:17
subroutine, public cp_dbcsr_heevd(matrix, eigenvectors, eigenvalues, para_env, blacs_env)
...
subroutine, public cp_dbcsr_syevx(matrix, eigenvectors, eigenvalues, neig, work_syevx, para_env, blacs_env)
compute eigenvalues and optionally eigenvectors of a real symmetric matrix using scalapack....
subroutine, public cp_dbcsr_syevd(matrix, eigenvectors, eigenvalues, para_env, blacs_env)
...
Definition: cp_dbcsr_diag.F:67
subroutine, public cp_dbcsr_power(matrix, exponent, threshold, n_dependent, para_env, blacs_env, verbose, eigenvectors, eigenvalues)
...
DBCSR operations in CP2K.
subroutine, public copy_cfm_to_dbcsr(fm, matrix, keep_sparsity)
Copy a BLACS matrix to a dbcsr matrix.
subroutine, public copy_dbcsr_to_fm(matrix, fm)
Copy a DBCSR matrix to a BLACS matrix.
subroutine, public copy_dbcsr_to_cfm(matrix, fm)
Copy a DBCSR matrix to a BLACS matrix.
subroutine, public copy_fm_to_dbcsr(fm, matrix, keep_sparsity)
Copy a BLACS matrix to a dbcsr matrix.
used for collecting some of the diagonalization schemes available for cp_fm_type. cp_fm_power also mo...
Definition: cp_fm_diag.F:17
subroutine, public cp_fm_power(matrix, work, exponent, threshold, n_dependent, verbose, eigvals)
...
Definition: cp_fm_diag.F:896
subroutine, public choose_eigv_solver(matrix, eigenvectors, eigenvalues, info)
Choose the Eigensolver depending on which library is available ELPA seems to be unstable for small sy...
Definition: cp_fm_diag.F:208
subroutine, public cp_fm_syevx(matrix, eigenvectors, eigenvalues, neig, work_syevx)
compute eigenvalues and optionally eigenvectors of a real symmetric matrix using scalapack....
Definition: cp_fm_diag.F:657
represent the structure of a full matrix
Definition: cp_fm_struct.F:14
subroutine, public cp_fm_struct_create(fmstruct, para_env, context, nrow_global, ncol_global, nrow_block, ncol_block, descriptor, first_p_pos, local_leading_dimension, template_fmstruct, square_blocks, force_block)
allocates and initializes a full matrix structure
Definition: cp_fm_struct.F:125
subroutine, public cp_fm_struct_release(fmstruct)
releases a full matrix structure
Definition: cp_fm_struct.F:320
represent a full matrix distributed on many processors
Definition: cp_fm_types.F:15
subroutine, public cp_fm_create(matrix, matrix_struct, name, use_sp)
creates a new full matrix with the given structure
Definition: cp_fm_types.F:167
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Interface to the message passing library MPI.