32#include "./base/base_uses.f90"
40 TYPE mixed_cdft_result_type
42 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:) :: lowdin, nonortho, &
45 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:) :: energy
47 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: strength
49 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: metric
51 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: h
53 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: s
55 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: s_minushalf
57 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: wad, wda
59 REAL(KIND=
dp),
ALLOCATABLE,
DIMENSION(:, :) :: w_diagonal
60 END TYPE mixed_cdft_result_type
65 TYPE mixed_cdft_work_type
67 TYPE(dbcsr_p_type),
DIMENSION(:, :),
POINTER :: w_matrix => null()
69 TYPE(dbcsr_type),
POINTER :: mixed_matrix_s => null()
71 TYPE(cp_fm_type),
DIMENSION(:, :),
POINTER :: mixed_mo_coeff => null()
73 TYPE(dbcsr_p_type),
DIMENSION(:, :),
POINTER :: density_matrix => null()
74 END TYPE mixed_cdft_work_type
85 INTEGER :: rank(2) = -1, tag(2) = -1
86 REAL(KIND=
dp),
POINTER, &
87 DIMENSION(:, :, :) :: cavity => null(), weight => null()
88 REAL(KIND=
dp),
POINTER, &
89 DIMENSION(:, :, :, :) :: gradients => null()
96 TYPE(buffers),
DIMENSION(:),
POINTER :: buffs => null()
104 INTEGER,
DIMENSION(:),
POINTER :: matrix_info => null()
105 INTEGER,
DIMENSION(:, :),
POINTER :: target_list => null()
136 TYPE mixed_cdft_dlb_type
137 INTEGER :: my_source = -1, distributed(2) = -1, &
138 my_dest_repl(2) = -1, dest_tags_repl(2) = -1, &
140 INTEGER,
DIMENSION(:),
POINTER :: bo => null(), expected_work => null(), &
141 prediction_error => null()
142 INTEGER,
DIMENSION(:, :),
POINTER :: target_list => null()
143 LOGICAL :: recv_work = .false., send_work = .false.
144 LOGICAL,
DIMENSION(:),
POINTER :: recv_work_repl => null()
145 REAL(KIND=
dp) :: load_scale = 0.0_dp, very_overloaded = 0.0_dp
146 REAL(KIND=
dp),
POINTER, &
147 DIMENSION(:, :, :) :: cavity => null(), weight => null()
148 REAL(KIND=
dp),
POINTER, &
149 DIMENSION(:, :, :, :) :: gradients => null()
151 TYPE(buffers),
DIMENSION(:),
POINTER :: sendbuff => null()
152 TYPE(p_buffers),
DIMENSION(:),
POINTER :: recvbuff => null()
153 TYPE(repl_info),
DIMENSION(:),
POINTER :: recv_info => null()
154 END TYPE mixed_cdft_dlb_type
205 INTEGER :: sim_step = -1, multiplicity = -1, &
208 INTEGER,
DIMENSION(:, :),
ALLOCATABLE :: constraint_type
209 INTEGER,
POINTER,
DIMENSION(:) :: source_list => null(), dest_list => null(), &
210 recv_bo => null(), source_list_save => null(), &
211 dest_list_save => null()
212 INTEGER,
POINTER,
DIMENSION(:, :) :: source_list_bo => null(), dest_list_bo => null(), &
213 source_bo_save => null(), dest_bo_save => null()
214 LOGICAL :: is_pencil = .false., dlb = .false., &
215 is_special = .false., first_iteration = .false., &
216 calculate_metric = .false., &
217 wfn_overlap_method = .false., &
218 has_unit_metric = .false., &
219 use_lowdin = .false., &
220 do_ci = .false., nonortho_coupling = .false., &
221 identical_constraints = .false., &
222 block_diagonalize = .false.
223 REAL(kind=
dp) :: eps_rho_rspace = 0.0_dp, sim_dt = 0.0_dp, &
225 REAL(kind=
dp),
POINTER,
DIMENSION(:, :, :) :: weight => null(), cavity => null()
227 TYPE(buffers),
DIMENSION(:),
POINTER :: sendbuff => null()
229 DIMENSION(:, :) :: occupations
232 TYPE(mixed_cdft_result_type) :: results = mixed_cdft_result_type()
233 TYPE(mixed_cdft_work_type) :: matrix = mixed_cdft_work_type()
234 TYPE(mixed_cdft_dlb_type),
POINTER :: dlb_control => null()
237 POINTER :: qs_kind_set => null()
244 LOGICAL :: is_spherical = .false., &
246 LOGICAL,
DIMENSION(:, :),
POINTER :: sb => null()
247 INTEGER :: ncdft = -1, &
249 INTEGER,
DIMENSION(2, 3) :: bo = -1
250 INTEGER,
DIMENSION(:),
POINTER :: grid_span => null(), &
251 spherical => null(), &
253 INTEGER,
DIMENSION(:, :),
POINTER :: si => null(), &
257 REAL(kind=
dp) :: radius = 0.0_dp
258 REAL(kind=
dp),
DIMENSION(:),
POINTER :: cutoff => null(), &
260 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: sr => null(), &
280 CHARACTER(len=*),
PARAMETER,
PRIVATE :: modulen =
'mixed_cdft_types'
292 NULLIFY (cdft_control%pw_env, cdft_control%blacs_env, cdft_control%qs_kind_set)
293 NULLIFY (cdft_control%dlb_control, cdft_control%dest_list_bo, cdft_control%dest_list)
294 NULLIFY (cdft_control%dest_bo_save, cdft_control%dest_list_save, cdft_control%source_list)
295 NULLIFY (cdft_control%source_list_save, cdft_control%source_bo_save, cdft_control%source_list_bo)
296 NULLIFY (cdft_control%cavity, cdft_control%weight, cdft_control%sendbuff)
297 NULLIFY (cdft_control%cdft_control, cdft_control%recv_bo)
298 NULLIFY (cdft_control%sub_logger)
313 IF (
ASSOCIATED(cdft_control%dest_list)) &
314 DEALLOCATE (cdft_control%dest_list)
315 IF (
ASSOCIATED(cdft_control%dest_list_save)) &
316 DEALLOCATE (cdft_control%dest_list_save)
317 IF (
ASSOCIATED(cdft_control%dest_list_bo)) &
318 DEALLOCATE (cdft_control%dest_list_bo)
319 IF (
ASSOCIATED(cdft_control%dest_bo_save)) &
320 DEALLOCATE (cdft_control%dest_bo_save)
321 IF (
ASSOCIATED(cdft_control%source_list)) &
322 DEALLOCATE (cdft_control%source_list)
323 IF (
ASSOCIATED(cdft_control%source_list_save)) &
324 DEALLOCATE (cdft_control%source_list_save)
325 IF (
ASSOCIATED(cdft_control%source_list_bo)) &
326 DEALLOCATE (cdft_control%source_list_bo)
327 IF (
ASSOCIATED(cdft_control%source_bo_save)) &
328 DEALLOCATE (cdft_control%source_bo_save)
329 IF (
ASSOCIATED(cdft_control%recv_bo)) &
330 DEALLOCATE (cdft_control%recv_bo)
331 IF (
ASSOCIATED(cdft_control%weight)) &
332 DEALLOCATE (cdft_control%weight)
333 IF (
ASSOCIATED(cdft_control%cavity)) &
334 DEALLOCATE (cdft_control%cavity)
335 IF (
ALLOCATED(cdft_control%constraint_type)) &
336 DEALLOCATE (cdft_control%constraint_type)
337 IF (
ALLOCATED(cdft_control%occupations))
THEN
338 DO i = 1,
SIZE(cdft_control%occupations, 1)
339 DO j = 1,
SIZE(cdft_control%occupations, 2)
340 IF (
ASSOCIATED(cdft_control%occupations(i, j)%array)) &
341 DEALLOCATE (cdft_control%occupations(i, j)%array)
344 DEALLOCATE (cdft_control%occupations)
346 IF (
ASSOCIATED(cdft_control%dlb_control)) &
347 CALL mixed_cdft_dlb_release(cdft_control%dlb_control)
348 IF (
ASSOCIATED(cdft_control%sendbuff))
THEN
349 DO i = 1,
SIZE(cdft_control%sendbuff)
350 CALL mixed_cdft_buffers_release(cdft_control%sendbuff(i))
352 DEALLOCATE (cdft_control%sendbuff)
354 IF (
ASSOCIATED(cdft_control%cdft_control))
THEN
356 DEALLOCATE (cdft_control%cdft_control)
358 IF (
ASSOCIATED(cdft_control%blacs_env)) &
360 IF (
ASSOCIATED(cdft_control%qs_kind_set)) &
362 IF (
ASSOCIATED(cdft_control%sub_logger))
THEN
363 DO i = 1,
SIZE(cdft_control%sub_logger)
366 DEALLOCATE (cdft_control%sub_logger)
370 DEALLOCATE (cdft_control)
379 SUBROUTINE mixed_cdft_dlb_release(dlb_control)
380 TYPE(mixed_cdft_dlb_type),
POINTER :: dlb_control
384 IF (
ASSOCIATED(dlb_control%recv_work_repl)) &
385 DEALLOCATE (dlb_control%recv_work_repl)
386 IF (
ASSOCIATED(dlb_control%sendbuff))
THEN
387 DO i = 1,
SIZE(dlb_control%sendbuff)
388 CALL mixed_cdft_buffers_release(dlb_control%sendbuff(i))
390 DEALLOCATE (dlb_control%sendbuff)
392 IF (
ASSOCIATED(dlb_control%recvbuff))
THEN
393 DO i = 1,
SIZE(dlb_control%recvbuff)
394 CALL mixed_cdft_p_buffers_release(dlb_control%recvbuff(i))
396 DEALLOCATE (dlb_control%recvbuff)
398 IF (
ASSOCIATED(dlb_control%recv_info))
THEN
399 DO i = 1,
SIZE(dlb_control%recv_info)
400 IF (
ASSOCIATED(dlb_control%recv_info(i)%matrix_info)) &
401 DEALLOCATE (dlb_control%recv_info(i)%matrix_info)
402 IF (
ASSOCIATED(dlb_control%recv_info(i)%target_list)) &
403 DEALLOCATE (dlb_control%recv_info(i)%target_list)
405 DEALLOCATE (dlb_control%recv_info)
407 IF (
ASSOCIATED(dlb_control%bo)) &
408 DEALLOCATE (dlb_control%bo)
409 IF (
ASSOCIATED(dlb_control%expected_work)) &
410 DEALLOCATE (dlb_control%expected_work)
411 IF (
ASSOCIATED(dlb_control%prediction_error)) &
412 DEALLOCATE (dlb_control%prediction_error)
413 IF (
ASSOCIATED(dlb_control%target_list)) &
414 DEALLOCATE (dlb_control%target_list)
415 IF (
ASSOCIATED(dlb_control%cavity)) &
416 DEALLOCATE (dlb_control%cavity)
417 IF (
ASSOCIATED(dlb_control%weight)) &
418 DEALLOCATE (dlb_control%weight)
419 IF (
ASSOCIATED(dlb_control%gradients)) &
420 DEALLOCATE (dlb_control%gradients)
421 DEALLOCATE (dlb_control)
423 END SUBROUTINE mixed_cdft_dlb_release
430 SUBROUTINE mixed_cdft_buffers_release(buffer)
431 TYPE(buffers) :: buffer
433 IF (
ASSOCIATED(buffer%cavity)) &
434 DEALLOCATE (buffer%cavity)
435 IF (
ASSOCIATED(buffer%weight)) &
436 DEALLOCATE (buffer%weight)
437 IF (
ASSOCIATED(buffer%gradients)) &
438 DEALLOCATE (buffer%gradients)
440 END SUBROUTINE mixed_cdft_buffers_release
447 SUBROUTINE mixed_cdft_p_buffers_release(p_buffer)
448 TYPE(p_buffers) :: p_buffer
452 IF (
ASSOCIATED(p_buffer%buffs))
THEN
453 DO i = 1,
SIZE(p_buffer%buffs)
454 CALL mixed_cdft_buffers_release(p_buffer%buffs(i))
456 DEALLOCATE (p_buffer%buffs)
459 END SUBROUTINE mixed_cdft_p_buffers_release
480 H, S, Wad, Wda, W_diagonal, energy, strength, S_minushalf)
481 TYPE(mixed_cdft_result_type) :: results
482 REAL(kind=
dp),
DIMENSION(:),
OPTIONAL :: lowdin, wfn, nonortho
483 REAL(kind=
dp),
DIMENSION(:, :),
OPTIONAL :: metric
484 REAL(kind=
dp),
DIMENSION(:),
OPTIONAL :: rotation
485 REAL(kind=
dp),
DIMENSION(:, :),
OPTIONAL :: h, s, wad, wda, w_diagonal
486 REAL(kind=
dp),
DIMENSION(:),
OPTIONAL :: energy
487 REAL(kind=
dp),
DIMENSION(:, :),
OPTIONAL :: strength, s_minushalf
489 IF (
PRESENT(lowdin))
THEN
490 IF (
ALLOCATED(results%lowdin))
DEALLOCATE (results%lowdin)
491 ALLOCATE (results%lowdin(
SIZE(lowdin)))
492 results%lowdin(:) = lowdin(:)
494 IF (
PRESENT(wfn))
THEN
495 IF (
ALLOCATED(results%wfn))
DEALLOCATE (results%wfn)
496 ALLOCATE (results%wfn(
SIZE(wfn)))
497 results%wfn(:) = wfn(:)
499 IF (
PRESENT(nonortho))
THEN
500 IF (
ALLOCATED(results%nonortho))
DEALLOCATE (results%nonortho)
501 ALLOCATE (results%nonortho(
SIZE(nonortho)))
502 results%nonortho(:) = nonortho(:)
504 IF (
PRESENT(rotation))
THEN
505 IF (
ALLOCATED(results%rotation))
DEALLOCATE (results%rotation)
506 ALLOCATE (results%rotation(
SIZE(rotation)))
507 results%rotation(:) = rotation(:)
509 IF (
PRESENT(energy))
THEN
510 IF (
ALLOCATED(results%energy))
DEALLOCATE (results%energy)
511 ALLOCATE (results%energy(
SIZE(energy)))
512 results%energy(:) = energy(:)
514 IF (
PRESENT(strength))
THEN
515 IF (
ALLOCATED(results%strength))
DEALLOCATE (results%strength)
516 ALLOCATE (results%strength(
SIZE(strength, 1),
SIZE(strength, 2)))
517 results%strength(:, :) = strength(:, :)
519 IF (
PRESENT(metric))
THEN
520 IF (
ALLOCATED(results%metric))
DEALLOCATE (results%metric)
521 ALLOCATE (results%metric(
SIZE(metric, 1),
SIZE(metric, 2)))
522 results%metric(:, :) = metric(:, :)
525 IF (
ALLOCATED(results%H))
DEALLOCATE (results%H)
526 ALLOCATE (results%H(
SIZE(h, 1),
SIZE(h, 2)))
527 results%H(:, :) = h(:, :)
530 IF (
ALLOCATED(results%S))
DEALLOCATE (results%S)
531 ALLOCATE (results%S(
SIZE(s, 1),
SIZE(s, 2)))
532 results%S(:, :) = s(:, :)
534 IF (
PRESENT(s_minushalf))
THEN
535 IF (
ALLOCATED(results%S_minushalf))
DEALLOCATE (results%S_minushalf)
536 ALLOCATE (results%S_minushalf(
SIZE(s_minushalf, 1),
SIZE(s_minushalf, 2)))
537 results%S_minushalf(:, :) = s_minushalf(:, :)
539 IF (
PRESENT(wad))
THEN
540 IF (
ALLOCATED(results%Wad))
DEALLOCATE (results%Wad)
541 ALLOCATE (results%Wad(
SIZE(wad, 1),
SIZE(wad, 2)))
542 results%Wad(:, :) = wad(:, :)
544 IF (
PRESENT(wda))
THEN
545 IF (
ALLOCATED(results%Wda))
DEALLOCATE (results%Wda)
546 ALLOCATE (results%Wda(
SIZE(wda, 1),
SIZE(wda, 2)))
547 results%Wda(:, :) = wda(:, :)
549 IF (
PRESENT(w_diagonal))
THEN
550 IF (
ALLOCATED(results%W_diagonal))
DEALLOCATE (results%W_diagonal)
551 ALLOCATE (results%W_diagonal(
SIZE(w_diagonal, 1),
SIZE(w_diagonal, 2)))
552 results%W_diagonal(:, :) = w_diagonal(:, :)
563 TYPE(mixed_cdft_result_type) :: results
565 IF (
ALLOCATED(results%lowdin))
DEALLOCATE (results%lowdin)
566 IF (
ALLOCATED(results%wfn))
DEALLOCATE (results%wfn)
567 IF (
ALLOCATED(results%metric))
DEALLOCATE (results%metric)
568 IF (
ALLOCATED(results%nonortho))
DEALLOCATE (results%nonortho)
569 IF (
ALLOCATED(results%rotation))
DEALLOCATE (results%rotation)
570 IF (
ALLOCATED(results%H))
DEALLOCATE (results%H)
571 IF (
ALLOCATED(results%S))
DEALLOCATE (results%S)
572 IF (
ALLOCATED(results%S_minushalf))
DEALLOCATE (results%S_minushalf)
573 IF (
ALLOCATED(results%Wad))
DEALLOCATE (results%Wad)
574 IF (
ALLOCATED(results%Wda))
DEALLOCATE (results%Wda)
575 IF (
ALLOCATED(results%W_diagonal))
DEALLOCATE (results%W_diagonal)
576 IF (
ALLOCATED(results%energy))
DEALLOCATE (results%energy)
577 IF (
ALLOCATED(results%strength))
DEALLOCATE (results%strength)
587 TYPE(mixed_cdft_work_type) :: matrix
589 NULLIFY (matrix%w_matrix)
590 NULLIFY (matrix%mixed_matrix_s)
591 NULLIFY (matrix%mixed_mo_coeff)
592 NULLIFY (matrix%density_matrix)
602 TYPE(mixed_cdft_work_type) :: matrix
606 IF (
ASSOCIATED(matrix%w_matrix))
THEN
607 DO i = 1,
SIZE(matrix%w_matrix, 2)
608 DO j = 1,
SIZE(matrix%w_matrix, 1)
612 DEALLOCATE (matrix%w_matrix)
614 IF (
ASSOCIATED(matrix%mixed_matrix_s))
THEN
617 IF (
ASSOCIATED(matrix%mixed_mo_coeff))
THEN
618 DO i = 1,
SIZE(matrix%mixed_mo_coeff, 2)
619 DO j = 1,
SIZE(matrix%mixed_mo_coeff, 1)
623 DEALLOCATE (matrix%mixed_mo_coeff)
625 IF (
ASSOCIATED(matrix%density_matrix))
THEN
626 DO i = 1,
SIZE(matrix%density_matrix, 2)
627 DO j = 1,
SIZE(matrix%density_matrix, 1)
631 DEALLOCATE (matrix%density_matrix)
various utilities that regard array of different kinds: output, allocation,... maybe it is not a good...
methods related to the blacs parallel environment
subroutine, public cp_blacs_env_release(blacs_env)
releases the given blacs_env
subroutine, public dbcsr_release_p(matrix)
...
represent a full matrix distributed on many processors
various routines to log and control the output. The idea is that decisions about where to log should ...
subroutine, public cp_logger_release(logger)
releases this logger
Defines the basic variable types.
integer, parameter, public dp
Types for mixed CDFT calculations.
subroutine, public mixed_cdft_type_release(cdft_control)
releases the given mixed_cdft_type
subroutine, public mixed_cdft_result_type_set(results, lowdin, wfn, nonortho, metric, rotation, h, s, wad, wda, w_diagonal, energy, strength, s_minushalf)
Updates arrays within the mixed CDFT result container.
subroutine, public mixed_cdft_result_type_release(results)
Releases all arrays within the mixed CDFT result container.
subroutine, public mixed_cdft_work_type_init(matrix)
Initializes the mixed_cdft_work_type.
subroutine, public mixed_cdft_type_create(cdft_control)
inits the given mixed_cdft_type
subroutine, public mixed_cdft_work_type_release(matrix)
Releases arrays within the mixed CDFT work matrix container.
container for various plainwaves related things
subroutine, public pw_env_release(pw_env, para_env)
releases the given pw_env (see doc/ReferenceCounting.html)
Defines CDFT control structures.
subroutine, public cdft_control_release(cdft_control)
release the cdft_control_type
Define the quickstep kind type and their sub types.
subroutine, public deallocate_qs_kind_set(qs_kind_set)
Destructor routine for a set of qs kinds.
represent a pointer to a 1d array
represent a blacs multidimensional parallel environment (for the mpi corrispective see cp_paratypes/m...
Container for constraint settings to check consistency of force_evals.
Main mixed CDFT control type.
contained for different pw related things
Provides all information about a quickstep kind.