(git:d18deda)
Loading...
Searching...
No Matches
qs_matrix_pools.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 wrapper for the pools of matrixes
10!> \par History
11!> 05.2003 created [fawzi]
12!> \author fawzi
13! **************************************************************************************************
28 USE qs_mo_types, ONLY: get_mo_set,&
30#include "./base/base_uses.f90"
31
32 IMPLICIT NONE
33 PRIVATE
34
35 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
36 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_matrix_pools'
37
38 PUBLIC :: qs_matrix_pools_type
41
42! **************************************************************************************************
43!> \brief container for the pools of matrixes used by qs
44!> \param ref_count reference count (see doc/ReferenceCounting.html)
45!> \param ao_mo_fm_pools pools with (ao x mo) full matrixes (same order as
46!> c).
47!> \param ao_ao_fm_pools pools with (ao x ao) full matrixes (same order as
48!> c).
49!> \param mo_mo_fm_pools pools with (mo x mo) full matrixes (same
50!> order as c).
51!> \param ao_mosub_fm_pools pools with (ao x mosub) full matrixes, where mosub
52!> are a subset of the mos
53!> \param mosub_mosub_fm_pools pools with (mosub x mosub) full matrixes, where mosub
54!> are a subset of the mos
55!>
56!> \param maxao_maxao_fm_pools pool of matrixes big enough to accommodate any
57!> aoxao matrix (useful for temp matrixes)
58!> \param maxao_maxmo_fm_pools pool of matrixes big enough to accommodate any
59!> aoxmo matrix (useful for temp matrixes)
60!> \param maxmo_maxmo_fm_pools pool of matrixes big enough to accommodate any
61!> moxmo matrix (useful for temp matrixes)
62!> \par History
63!> 04.2003 created [fawzi]
64!> \author fawzi
65! **************************************************************************************************
67 INTEGER :: ref_count = -1
68 TYPE(cp_fm_pool_p_type), DIMENSION(:), POINTER :: ao_mo_fm_pools => null(), &
69 ao_ao_fm_pools => null(), mo_mo_fm_pools => null()
70 TYPE(cp_fm_pool_p_type), DIMENSION(:), POINTER :: ao_mosub_fm_pools => null(), &
71 mosub_mosub_fm_pools => null()
73
74CONTAINS
75
76! **************************************************************************************************
77!> \brief retains the given qs_matrix_pools_type
78!> \param mpools the matrix pools type to retain
79!> \par History
80!> 04.2003 created [fawzi]
81!> \author fawzi
82! **************************************************************************************************
83 SUBROUTINE mpools_retain(mpools)
84 TYPE(qs_matrix_pools_type), POINTER :: mpools
85
86 cpassert(ASSOCIATED(mpools))
87 cpassert(mpools%ref_count > 0)
88 mpools%ref_count = mpools%ref_count + 1
89 END SUBROUTINE mpools_retain
90
91! **************************************************************************************************
92!> \brief releases the given mpools
93!> \param mpools the matrix pools type to retain
94!> \par History
95!> 04.2003 created [fawzi]
96!> \author fawzi
97! **************************************************************************************************
98 SUBROUTINE mpools_release(mpools)
99 TYPE(qs_matrix_pools_type), POINTER :: mpools
100
101 IF (ASSOCIATED(mpools)) THEN
102 cpassert(mpools%ref_count > 0)
103 mpools%ref_count = mpools%ref_count - 1
104 IF (mpools%ref_count == 0) THEN
105 CALL fm_pools_dealloc(mpools%ao_mo_fm_pools)
106 CALL fm_pools_dealloc(mpools%ao_ao_fm_pools)
107 CALL fm_pools_dealloc(mpools%mo_mo_fm_pools)
108 IF (ASSOCIATED(mpools%ao_mosub_fm_pools)) THEN
109 CALL fm_pools_dealloc(mpools%ao_mosub_fm_pools)
110 END IF
111 IF (ASSOCIATED(mpools%mosub_mosub_fm_pools)) THEN
112 CALL fm_pools_dealloc(mpools%mosub_mosub_fm_pools)
113 END IF
114 DEALLOCATE (mpools)
115 END IF
116 END IF
117 NULLIFY (mpools)
118 END SUBROUTINE mpools_release
119
120! **************************************************************************************************
121!> \brief returns various attributes of the mpools (notably the pools
122!> contained in it)
123!> \param mpools the matrix pools object you want info about
124!> \param ao_mo_fm_pools ...
125!> \param ao_ao_fm_pools ...
126!> \param mo_mo_fm_pools ...
127!> \param ao_mosub_fm_pools ...
128!> \param mosub_mosub_fm_pools ...
129!> \param maxao_maxmo_fm_pool ...
130!> \param maxao_maxao_fm_pool ...
131!> \param maxmo_maxmo_fm_pool ...
132!> \par History
133!> 04.2003 created [fawzi]
134!> \author fawzi
135! **************************************************************************************************
136 SUBROUTINE mpools_get(mpools, ao_mo_fm_pools, ao_ao_fm_pools, &
137 mo_mo_fm_pools, ao_mosub_fm_pools, mosub_mosub_fm_pools, &
138 maxao_maxmo_fm_pool, maxao_maxao_fm_pool, maxmo_maxmo_fm_pool)
139 TYPE(qs_matrix_pools_type), INTENT(IN) :: mpools
140 TYPE(cp_fm_pool_p_type), DIMENSION(:), OPTIONAL, &
141 POINTER :: ao_mo_fm_pools, ao_ao_fm_pools, &
142 mo_mo_fm_pools, ao_mosub_fm_pools, &
143 mosub_mosub_fm_pools
144 TYPE(cp_fm_pool_type), OPTIONAL, POINTER :: maxao_maxmo_fm_pool, &
145 maxao_maxao_fm_pool, &
146 maxmo_maxmo_fm_pool
147
148 IF (PRESENT(ao_mo_fm_pools)) ao_mo_fm_pools => mpools%ao_mo_fm_pools
149 IF (PRESENT(maxao_maxmo_fm_pool)) THEN
150 IF (ASSOCIATED(mpools%ao_mo_fm_pools)) THEN
151 maxao_maxmo_fm_pool => mpools%ao_mo_fm_pools(1)%pool
152 ELSE
153 NULLIFY (maxao_maxmo_fm_pool) ! raise an error?
154 END IF
155 END IF
156 IF (PRESENT(ao_ao_fm_pools)) ao_ao_fm_pools => mpools%ao_ao_fm_pools
157 IF (PRESENT(maxao_maxao_fm_pool)) THEN
158 IF (ASSOCIATED(mpools%ao_ao_fm_pools)) THEN
159 maxao_maxao_fm_pool => mpools%ao_ao_fm_pools(1)%pool
160 ELSE
161 NULLIFY (maxao_maxao_fm_pool) ! raise an error?
162 END IF
163 END IF
164 IF (PRESENT(mo_mo_fm_pools)) mo_mo_fm_pools => mpools%mo_mo_fm_pools
165 IF (PRESENT(maxmo_maxmo_fm_pool)) THEN
166 IF (ASSOCIATED(mpools%mo_mo_fm_pools)) THEN
167 maxmo_maxmo_fm_pool => mpools%mo_mo_fm_pools(1)%pool
168 ELSE
169 NULLIFY (maxmo_maxmo_fm_pool) ! raise an error?
170 END IF
171 END IF
172 IF (PRESENT(ao_mosub_fm_pools)) ao_mosub_fm_pools => mpools%ao_mosub_fm_pools
173 IF (PRESENT(mosub_mosub_fm_pools)) mosub_mosub_fm_pools => mpools%mosub_mosub_fm_pools
174 END SUBROUTINE mpools_get
175
176! **************************************************************************************************
177!> \brief creates a mpools
178!> \param mpools the mpools to create
179!> \par History
180!> 04.2003 created [fawzi]
181!> \author fawzi
182! **************************************************************************************************
183 SUBROUTINE mpools_create(mpools)
184 TYPE(qs_matrix_pools_type), POINTER :: mpools
185
186 ALLOCATE (mpools)
187 NULLIFY (mpools%ao_ao_fm_pools, mpools%ao_mo_fm_pools, &
188 mpools%mo_mo_fm_pools, mpools%ao_mosub_fm_pools, &
189 mpools%mosub_mosub_fm_pools)
190 mpools%ref_count = 1
191 END SUBROUTINE mpools_create
192
193! **************************************************************************************************
194!> \brief rebuilds the pools of the (ao x mo, ao x ao , mo x mo) full matrixes
195!> \param mpools the environment where the pools should be rebuilt
196!> \param mos the molecular orbitals (qs_env%c), must contain up to
197!> date nmo and nao
198!> \param blacs_env the blacs environment of the full matrixes
199!> \param para_env the parallel environment of the matrixes
200!> \param nmosub number of the orbitals for the creation
201!> of the pools containing only a subset of mos (OPTIONAL)
202!> \par History
203!> 08.2002 created [fawzi]
204!> 04.2005 added pools for a subset of mos [MI]
205!> \author Fawzi Mohamed
206! **************************************************************************************************
207 SUBROUTINE mpools_rebuild_fm_pools(mpools, mos, blacs_env, para_env, &
208 nmosub)
209 TYPE(qs_matrix_pools_type), POINTER :: mpools
210 TYPE(mo_set_type), DIMENSION(:), INTENT(IN) :: mos
211 TYPE(cp_blacs_env_type), POINTER :: blacs_env
212 TYPE(mp_para_env_type), POINTER :: para_env
213 INTEGER, DIMENSION(2), INTENT(IN), OPTIONAL :: nmosub
214
215 CHARACTER(len=*), PARAMETER :: routinen = 'mpools_rebuild_fm_pools'
216
217 INTEGER :: handle, ispin, max_nmo, min_nmo, nao, &
218 ncg, nmo, nrg, nspins
219 LOGICAL :: prepare_subset, should_rebuild
220 TYPE(cp_fm_pool_type), POINTER :: p_att
221 TYPE(cp_fm_struct_type), POINTER :: fmstruct
222
223 CALL timeset(routinen, handle)
224
225 NULLIFY (fmstruct, p_att)
226 prepare_subset = .false.
227 IF (PRESENT(nmosub)) THEN
228 IF (nmosub(1) > 0) prepare_subset = .true.
229 END IF
230
231 IF (.NOT. ASSOCIATED(mpools)) THEN
232 CALL mpools_create(mpools)
233 END IF
234 nspins = SIZE(mos)
235
236 IF (ASSOCIATED(mpools%ao_mo_fm_pools)) THEN
237 IF (nspins /= SIZE(mpools%ao_mo_fm_pools)) THEN
238 CALL fm_pools_dealloc(mpools%ao_mo_fm_pools)
239 END IF
240 END IF
241 IF (.NOT. ASSOCIATED(mpools%ao_mo_fm_pools)) THEN
242 ALLOCATE (mpools%ao_mo_fm_pools(nspins))
243 DO ispin = 1, nspins
244 NULLIFY (mpools%ao_mo_fm_pools(ispin)%pool)
245 END DO
246 END IF
247
248 IF (ASSOCIATED(mpools%ao_ao_fm_pools)) THEN
249 IF (nspins /= SIZE(mpools%ao_ao_fm_pools)) THEN
250 CALL fm_pools_dealloc(mpools%ao_ao_fm_pools)
251 END IF
252 END IF
253 IF (.NOT. ASSOCIATED(mpools%ao_ao_fm_pools)) THEN
254 ALLOCATE (mpools%ao_ao_fm_pools(nspins))
255 DO ispin = 1, nspins
256 NULLIFY (mpools%ao_ao_fm_pools(ispin)%pool)
257 END DO
258 END IF
259
260 IF (ASSOCIATED(mpools%mo_mo_fm_pools)) THEN
261 IF (nspins /= SIZE(mpools%mo_mo_fm_pools)) THEN
262 CALL fm_pools_dealloc(mpools%mo_mo_fm_pools)
263 END IF
264 END IF
265 IF (.NOT. ASSOCIATED(mpools%mo_mo_fm_pools)) THEN
266 ALLOCATE (mpools%mo_mo_fm_pools(nspins))
267 DO ispin = 1, nspins
268 NULLIFY (mpools%mo_mo_fm_pools(ispin)%pool)
269 END DO
270 END IF
271
272 IF (prepare_subset) THEN
273
274 IF (ASSOCIATED(mpools%ao_mosub_fm_pools)) THEN
275 IF (nspins /= SIZE(mpools%ao_mosub_fm_pools)) THEN
276 CALL fm_pools_dealloc(mpools%ao_mosub_fm_pools)
277 END IF
278 END IF
279 IF (.NOT. ASSOCIATED(mpools%ao_mosub_fm_pools)) THEN
280 ALLOCATE (mpools%ao_mosub_fm_pools(nspins))
281 DO ispin = 1, nspins
282 NULLIFY (mpools%ao_mosub_fm_pools(ispin)%pool)
283 END DO
284 END IF
285
286 IF (ASSOCIATED(mpools%mosub_mosub_fm_pools)) THEN
287 IF (nspins /= SIZE(mpools%mosub_mosub_fm_pools)) THEN
288 CALL fm_pools_dealloc(mpools%mosub_mosub_fm_pools)
289 END IF
290 END IF
291 IF (.NOT. ASSOCIATED(mpools%mosub_mosub_fm_pools)) THEN
292 ALLOCATE (mpools%mosub_mosub_fm_pools(nspins))
293 DO ispin = 1, nspins
294 NULLIFY (mpools%mosub_mosub_fm_pools(ispin)%pool)
295 END DO
296 END IF
297
298 END IF ! prepare_subset
299
300 CALL get_mo_set(mos(1), nao=nao, nmo=min_nmo)
301 max_nmo = min_nmo
302 DO ispin = 2, SIZE(mos)
303 CALL get_mo_set(mos(ispin), nmo=nmo)
304 IF (max_nmo < nmo) THEN
305 cpabort("the mo with the most orbitals must be the first ")
306 END IF
307 min_nmo = min(min_nmo, nmo)
308 END DO
309
310 ! aoao pools
311 should_rebuild = .false.
312 DO ispin = 1, nspins
313 p_att => mpools%ao_ao_fm_pools(ispin)%pool
314 should_rebuild = (should_rebuild .OR. (.NOT. ASSOCIATED(p_att)))
315 IF (.NOT. should_rebuild) THEN
316 fmstruct => fm_pool_get_el_struct(mpools%ao_ao_fm_pools(ispin)%pool)
317 CALL cp_fm_struct_get(fmstruct, nrow_global=nrg, ncol_global=ncg)
318 CALL get_mo_set(mos(1), nao=nao, nmo=nmo)
319 should_rebuild = nao /= nrg .OR. nao /= ncg
320 END IF
321 END DO
322 IF (should_rebuild) THEN
323 DO ispin = 1, nspins
324 CALL fm_pool_release(mpools%ao_ao_fm_pools(ispin)%pool)
325 END DO
326
327 CALL cp_fm_struct_create(fmstruct, nrow_global=nao, &
328 ncol_global=nao, para_env=para_env, &
329 context=blacs_env)
330 CALL fm_pool_create(mpools%ao_ao_fm_pools(1)%pool, fmstruct)
331 CALL cp_fm_struct_release(fmstruct)
332 DO ispin = 2, SIZE(mos)
333 mpools%ao_ao_fm_pools(ispin)%pool => mpools%ao_ao_fm_pools(1)%pool
334 CALL fm_pool_retain(mpools%ao_ao_fm_pools(1)%pool)
335 END DO
336 END IF
337
338 ! aomo pools
339 should_rebuild = .false.
340 DO ispin = 1, nspins
341 p_att => mpools%ao_mo_fm_pools(ispin)%pool
342 should_rebuild = (should_rebuild .OR. (.NOT. ASSOCIATED(p_att)))
343 IF (.NOT. should_rebuild) THEN
344 fmstruct => fm_pool_get_el_struct(mpools%ao_mo_fm_pools(ispin) &
345 %pool)
346 CALL cp_fm_struct_get(fmstruct, nrow_global=nrg, ncol_global=ncg)
347 CALL get_mo_set(mos(1), nao=nao, nmo=nmo)
348 should_rebuild = nao /= nrg .OR. nmo /= ncg
349 END IF
350 END DO
351 IF (should_rebuild) THEN
352 DO ispin = 1, nspins
353 CALL fm_pool_release(mpools%ao_mo_fm_pools(ispin)%pool)
354 END DO
355
356 IF (max_nmo == min_nmo) THEN
357 CALL cp_fm_struct_create(fmstruct, nrow_global=nao, &
358 ncol_global=max_nmo, para_env=para_env, &
359 context=blacs_env)
360 CALL fm_pool_create(mpools%ao_mo_fm_pools(1)%pool, fmstruct)
361 CALL cp_fm_struct_release(fmstruct)
362 DO ispin = 2, SIZE(mos)
363 mpools%ao_mo_fm_pools(ispin)%pool => mpools%ao_mo_fm_pools(1)%pool
364 CALL fm_pool_retain(mpools%ao_mo_fm_pools(1)%pool)
365 END DO
366 ELSE
367 DO ispin = 1, SIZE(mos)
368 CALL get_mo_set(mos(ispin), nmo=nmo, nao=nao)
369 CALL cp_fm_struct_create(fmstruct, nrow_global=nao, &
370 ncol_global=nmo, para_env=para_env, &
371 context=blacs_env)
372 CALL fm_pool_create(mpools%ao_mo_fm_pools(ispin)%pool, &
373 fmstruct)
374 CALL cp_fm_struct_release(fmstruct)
375 END DO
376 END IF
377 END IF
378
379 ! momo pools
380 should_rebuild = .false.
381 DO ispin = 1, nspins
382 p_att => mpools%mo_mo_fm_pools(ispin)%pool
383 should_rebuild = (should_rebuild .OR. (.NOT. ASSOCIATED(p_att)))
384 IF (.NOT. should_rebuild) THEN
385 fmstruct => fm_pool_get_el_struct(p_att)
386 CALL cp_fm_struct_get(fmstruct, nrow_global=nrg, &
387 ncol_global=ncg)
388 CALL get_mo_set(mos(1), nao=nao, nmo=nmo)
389 should_rebuild = nmo /= nrg .OR. nmo /= ncg
390 END IF
391 END DO
392 IF (should_rebuild) THEN
393 DO ispin = 1, nspins
394 CALL fm_pool_release(mpools%mo_mo_fm_pools(ispin)%pool)
395 END DO
396
397 IF (max_nmo == min_nmo) THEN
398 CALL cp_fm_struct_create(fmstruct, nrow_global=max_nmo, &
399 ncol_global=max_nmo, para_env=para_env, &
400 context=blacs_env)
401 CALL fm_pool_create(mpools%mo_mo_fm_pools(1)%pool, &
402 fmstruct)
403 CALL cp_fm_struct_release(fmstruct)
404 DO ispin = 2, SIZE(mos)
405 mpools%mo_mo_fm_pools(ispin)%pool => mpools%mo_mo_fm_pools(1)%pool
406 CALL fm_pool_retain(mpools%mo_mo_fm_pools(1)%pool)
407 END DO
408 ELSE
409 DO ispin = 1, SIZE(mos)
410 NULLIFY (mpools%mo_mo_fm_pools(ispin)%pool)
411 CALL get_mo_set(mos(ispin), nmo=nmo, nao=nao)
412 CALL cp_fm_struct_create(fmstruct, nrow_global=nmo, &
413 ncol_global=nmo, para_env=para_env, &
414 context=blacs_env)
415 CALL fm_pool_create(mpools%mo_mo_fm_pools(ispin)%pool, &
416 fmstruct)
417 CALL cp_fm_struct_release(fmstruct)
418 END DO
419 END IF
420 END IF
421
422 IF (prepare_subset) THEN
423 ! aomosub pools
424 should_rebuild = .false.
425 DO ispin = 1, nspins
426 p_att => mpools%ao_mosub_fm_pools(ispin)%pool
427 should_rebuild = (should_rebuild .OR. (.NOT. ASSOCIATED(p_att)))
428 IF (.NOT. should_rebuild) THEN
429 fmstruct => fm_pool_get_el_struct(mpools%ao_mosub_fm_pools(ispin) &
430 %pool)
431 CALL cp_fm_struct_get(fmstruct, nrow_global=nrg, &
432 ncol_global=ncg)
433 CALL get_mo_set(mos(1), nao=nao)
434 should_rebuild = nao /= nrg .OR. nmosub(ispin) /= ncg
435 END IF
436 END DO
437 IF (should_rebuild) THEN
438 DO ispin = 1, nspins
439 CALL fm_pool_release(mpools%ao_mosub_fm_pools(ispin)%pool)
440 END DO
441
442 IF (nspins == 1 .OR. nmosub(1) == nmosub(2)) THEN
443 CALL cp_fm_struct_create(fmstruct, nrow_global=nao, &
444 ncol_global=nmosub(1), para_env=para_env, &
445 context=blacs_env)
446 CALL fm_pool_create(mpools%ao_mosub_fm_pools(1)%pool, fmstruct)
447 CALL cp_fm_struct_release(fmstruct)
448 DO ispin = 2, SIZE(mos)
449 mpools%ao_mosub_fm_pools(ispin)%pool => mpools%ao_mosub_fm_pools(1)%pool
450 CALL fm_pool_retain(mpools%ao_mosub_fm_pools(1)%pool)
451 END DO
452 ELSE
453 DO ispin = 1, SIZE(mos)
454 CALL get_mo_set(mos(ispin), nao=nao)
455 CALL cp_fm_struct_create(fmstruct, nrow_global=nao, &
456 ncol_global=nmosub(1), para_env=para_env, &
457 context=blacs_env)
458 CALL fm_pool_create(mpools%ao_mosub_fm_pools(ispin)%pool, &
459 fmstruct)
460 CALL cp_fm_struct_release(fmstruct)
461 END DO
462 END IF
463 END IF ! should_rebuild
464
465 ! mosubmosub pools
466 should_rebuild = .false.
467 DO ispin = 1, nspins
468 p_att => mpools%mosub_mosub_fm_pools(ispin)%pool
469 should_rebuild = (should_rebuild .OR. (.NOT. ASSOCIATED(p_att)))
470 IF (.NOT. should_rebuild) THEN
471 fmstruct => fm_pool_get_el_struct(p_att)
472 CALL cp_fm_struct_get(fmstruct, nrow_global=nrg, &
473 ncol_global=ncg)
474 should_rebuild = nmosub(ispin) /= nrg .OR. nmosub(ispin) /= ncg
475 END IF
476 END DO
477 IF (should_rebuild) THEN
478 DO ispin = 1, nspins
479 CALL fm_pool_release(mpools%mosub_mosub_fm_pools(ispin)%pool)
480 END DO
481
482 IF (nspins == 1 .OR. nmosub(1) == nmosub(2)) THEN
483 CALL cp_fm_struct_create(fmstruct, nrow_global=nmosub(1), &
484 ncol_global=nmosub(1), para_env=para_env, &
485 context=blacs_env)
486 CALL fm_pool_create(mpools%mosub_mosub_fm_pools(1)%pool, &
487 fmstruct)
488 CALL cp_fm_struct_release(fmstruct)
489 DO ispin = 2, SIZE(mos)
490 mpools%mosub_mosub_fm_pools(ispin)%pool => mpools%mosub_mosub_fm_pools(1)%pool
491 CALL fm_pool_retain(mpools%mosub_mosub_fm_pools(1)%pool)
492 END DO
493 ELSE
494 DO ispin = 1, SIZE(mos)
495 NULLIFY (mpools%mosub_mosub_fm_pools(ispin)%pool)
496 CALL cp_fm_struct_create(fmstruct, nrow_global=nmosub(ispin), &
497 ncol_global=nmosub(ispin), para_env=para_env, &
498 context=blacs_env)
499 CALL fm_pool_create(mpools%mosub_mosub_fm_pools(ispin)%pool, &
500 fmstruct)
501 CALL cp_fm_struct_release(fmstruct)
502 END DO
503 END IF
504 END IF ! should_rebuild
505 END IF ! prepare_subset
506
507 CALL timestop(handle)
508 END SUBROUTINE mpools_rebuild_fm_pools
509
510! **************************************************************************************************
511
512END MODULE qs_matrix_pools
methods related to the blacs parallel environment
pool for for elements that are retained and released
subroutine, public fm_pool_create(pool, el_struct)
creates a pool of elements
subroutine, public fm_pool_release(pool)
releases the given pool (see cp2k/doc/ReferenceCounting.html)
subroutine, public fm_pool_retain(pool)
retains the pool (see cp2k/doc/ReferenceCounting.html)
subroutine, public fm_pools_dealloc(pools)
deallocate an array of pools (releasing each pool)
type(cp_fm_struct_type) function, pointer, public fm_pool_get_el_struct(pool)
returns the structure of the elements in this pool
represent the structure of a full matrix
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
subroutine, public cp_fm_struct_get(fmstruct, para_env, context, descriptor, ncol_block, nrow_block, nrow_global, ncol_global, first_p_pos, row_indices, col_indices, nrow_local, ncol_local, nrow_locals, ncol_locals, local_leading_dimension)
returns the values of various attributes of the matrix structure
subroutine, public cp_fm_struct_release(fmstruct)
releases a full matrix structure
Interface to the message passing library MPI.
wrapper for the pools of matrixes
subroutine, public mpools_create(mpools)
creates a mpools
subroutine, public mpools_release(mpools)
releases the given mpools
subroutine, public mpools_retain(mpools)
retains the given qs_matrix_pools_type
subroutine, public mpools_rebuild_fm_pools(mpools, mos, blacs_env, para_env, nmosub)
rebuilds the pools of the (ao x mo, ao x ao , mo x mo) full matrixes
subroutine, public mpools_get(mpools, ao_mo_fm_pools, ao_ao_fm_pools, mo_mo_fm_pools, ao_mosub_fm_pools, mosub_mosub_fm_pools, maxao_maxmo_fm_pool, maxao_maxao_fm_pool, maxmo_maxmo_fm_pool)
returns various attributes of the mpools (notably the pools contained in it)
Definition and initialisation of the mo data type.
Definition qs_mo_types.F:22
subroutine, public get_mo_set(mo_set, maxocc, homo, lfomo, nao, nelectron, n_el_f, nmo, eigenvalues, occupation_numbers, mo_coeff, mo_coeff_b, uniform_occupation, kts, mu, flexible_electron_count)
Get the components of a MO set data structure.
represent a blacs multidimensional parallel environment (for the mpi corrispective see cp_paratypes/m...
represent a pool of elements with the same structure
keeps the information about the structure of a full matrix
stores all the informations relevant to an mpi environment
container for the pools of matrixes used by qs