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