LCOV - code coverage report
Current view: top level - src - mixed_cdft_types.F (source / functions) Hit Total Coverage
Test: CP2K Regtests (git:20da4d9) Lines: 156 206 75.7 %
Date: 2024-05-07 06:35:50 Functions: 7 19 36.8 %

          Line data    Source code
       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 Types for mixed CDFT calculations
      10             : !> \par   History
      11             : !>                 Separated CDFT routines from mixed_environment_types
      12             : !> \author Nico Holmberg [01.2017]
      13             : ! **************************************************************************************************
      14             : MODULE mixed_cdft_types
      15             :    USE cp_array_utils,                  ONLY: cp_1d_r_p_type
      16             :    USE cp_blacs_env,                    ONLY: cp_blacs_env_release,&
      17             :                                               cp_blacs_env_type
      18             :    USE cp_fm_types,                     ONLY: cp_fm_release,&
      19             :                                               cp_fm_type
      20             :    USE cp_log_handling,                 ONLY: cp_logger_p_type,&
      21             :                                               cp_logger_release
      22             :    USE dbcsr_api,                       ONLY: dbcsr_p_type,&
      23             :                                               dbcsr_release_p,&
      24             :                                               dbcsr_type
      25             :    USE kinds,                           ONLY: dp
      26             :    USE pw_env_types,                    ONLY: pw_env_release,&
      27             :                                               pw_env_type
      28             :    USE qs_cdft_types,                   ONLY: cdft_control_release,&
      29             :                                               cdft_control_type
      30             :    USE qs_kind_types,                   ONLY: deallocate_qs_kind_set,&
      31             :                                               qs_kind_type
      32             : #include "./base/base_uses.f90"
      33             : 
      34             :    IMPLICIT NONE
      35             :    PRIVATE
      36             : 
      37             : ! **************************************************************************************************
      38             : !> \brief Container for results related to a mixed CDFT calculation
      39             : ! **************************************************************************************************
      40             :    TYPE mixed_cdft_result_type
      41             :       ! CDFT electronic couplings calculated with different methods
      42             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:)         :: lowdin, nonortho, &
      43             :                                                           rotation, wfn
      44             :       ! Energies of the CDFT states
      45             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:)         :: energy
      46             :       ! Lagrangian multipliers of the CDFT constraints
      47             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :)      :: strength
      48             :       ! Reliability metric for CDFT electronic couplings
      49             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :)      :: metric
      50             :       ! The mixed CDFT Hamiltonian matrix
      51             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :)      :: H
      52             :       ! Overlaps between CDFT states
      53             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :)      :: S
      54             :       ! S^(-1/2)
      55             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :)      :: S_minushalf
      56             :       ! Off-diagonal elements of the weight function matrices <Psi_j | w_i(r) | Psi_i>
      57             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :)      :: Wad, Wda
      58             :       ! Diagonal elements of the weight function matrices, i.e., the constraint values
      59             :       REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :)      :: W_diagonal
      60             :    END TYPE mixed_cdft_result_type
      61             : 
      62             : ! **************************************************************************************************
      63             : !> \brief Container for mixed CDFT matrices
      64             : ! **************************************************************************************************
      65             :    TYPE mixed_cdft_work_type
      66             :       ! Matrix representations of the CDFT weight functions
      67             :       TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER       :: w_matrix
      68             :       ! AO overlap matrix
      69             :       TYPE(dbcsr_type), POINTER                          :: mixed_matrix_s
      70             :       ! MO coefficients of each CDFT state
      71             :       TYPE(cp_fm_type), DIMENSION(:, :), POINTER         :: mixed_mo_coeff
      72             :       ! Density matrices of the CDFT states
      73             :       TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER       :: density_matrix
      74             :    END TYPE mixed_cdft_work_type
      75             : 
      76             : ! **************************************************************************************************
      77             : !> \brief Buffers for load balancing
      78             : !> \param rank indices of the processors the data in this buffer should be sent to
      79             : !> \param tag mpi tags for the messages to send
      80             : !> \param cavity the cavity to send
      81             : !> \param weight the weight to send
      82             : !> \param gradients the gradients to send
      83             : ! **************************************************************************************************
      84             :    TYPE buffers
      85             :       INTEGER                                          :: rank(2), tag(2)
      86             :       REAL(KIND=dp), POINTER, &
      87             :          DIMENSION(:, :, :)                            :: cavity, weight
      88             :       REAL(KIND=dp), POINTER, &
      89             :          DIMENSION(:, :, :, :)                         :: gradients
      90             :    END TYPE buffers
      91             : ! **************************************************************************************************
      92             : !> \brief To build array of buffers
      93             : !> \param buffs the pointer to the buffers type
      94             : ! **************************************************************************************************
      95             :    TYPE p_buffers
      96             :       TYPE(buffers), DIMENSION(:), POINTER             :: buffs
      97             :    END TYPE p_buffers
      98             : ! **************************************************************************************************
      99             : !> \brief Information about load balancing
     100             : !> \param matrix_info size of the target_list array to receive and grid point bounds of the data
     101             : !> \param target_list the target_list array of the processor that sends me data
     102             : ! **************************************************************************************************
     103             :    TYPE repl_info
     104             :       INTEGER, DIMENSION(:), POINTER                   :: matrix_info
     105             :       INTEGER, DIMENSION(:, :), POINTER                :: target_list
     106             :    END TYPE repl_info
     107             : ! **************************************************************************************************
     108             : !> \brief Load balancing control for mixed CDFT calculation
     109             : !> \param my_source index of the processor which will send this processor data
     110             : !> \param distributed bounds that determine which grid points this processor will compute after
     111             : !>                    applying load balancing (is_special = .FALSE.)
     112             : !> \param my_dest_repl the dest_list arrays of all processors which send additional work to this
     113             : !>                     processor (indices of the processors where the redistributed slices should be
     114             : !>                     returned)
     115             : !> \param dest_tags_repl tags for the send messages (is_special = .FALSE.)
     116             : !> \param more_work allow heavily overloaded processors to redistribute more_work slices
     117             : !> \param bo bounds of the data that this processor will send to other processors which tells the
     118             : !>           receivers how to rearrange the data correctly
     119             : !> \param expected_work a list of the estimated work per processor
     120             : !> \param prediction_error the difference between the estimated and actual work per processor
     121             : !> \param target_list a list of processors to send data and the size of data to send
     122             : !> \param recv_work flag that determines if this processor will receive data from others
     123             : !> \param send_work flag that determines if this processor will send data to others
     124             : !> \param recv_work_repl list of processor indices where this processor will send data during load
     125             : !>                       balancing
     126             : !> \param load_scale allow underloaded processors to accept load_scale additional work
     127             : !> \param very_overloaded value to determine which processors are heavily overloaded
     128             : !> \param cavity the cavity that this processor builds in addition to its own cavity defined
     129             : !>               on the grid points which were redistributed to this processor
     130             : !> \param weight the weight that this processor builds in addition to its own weight
     131             : !> \param gradients the gradients that this processor builds in addition to its own gradients
     132             : !> \param sendbuffer buffer to hold the data this processor will send
     133             : !> \param sendbuffer buffer to hold the data this processor will receive
     134             : !> \param recv_info additional information on the data this processor will receive
     135             : ! **************************************************************************************************
     136             :    TYPE mixed_cdft_dlb_type
     137             :       INTEGER                                          :: my_source, distributed(2), &
     138             :                                                           my_dest_repl(2), dest_tags_repl(2), &
     139             :                                                           more_work
     140             :       INTEGER, DIMENSION(:), POINTER                   :: bo, expected_work, &
     141             :                                                           prediction_error
     142             :       INTEGER, DIMENSION(:, :), POINTER                :: target_list
     143             :       LOGICAL                                          :: recv_work, send_work
     144             :       LOGICAL, DIMENSION(:), POINTER                   :: recv_work_repl
     145             :       REAL(KIND=dp)                                    :: load_scale, very_overloaded
     146             :       REAL(KIND=dp), POINTER, &
     147             :          DIMENSION(:, :, :)                            :: cavity, weight
     148             :       REAL(KIND=dp), POINTER, &
     149             :          DIMENSION(:, :, :, :)                         :: gradients
     150             :       ! Should convert to TYPE(p_buffers), POINTER
     151             :       TYPE(buffers), DIMENSION(:), POINTER             :: sendbuff
     152             :       TYPE(p_buffers), DIMENSION(:), POINTER           :: recvbuff
     153             :       TYPE(repl_info), DIMENSION(:), POINTER           :: recv_info
     154             :    END TYPE mixed_cdft_dlb_type
     155             : ! **************************************************************************************************
     156             : !> \brief Main mixed CDFT control type
     157             : !> \param sim_step              counter to keep track of the simulation step for MD
     158             : !> \param multiplicity          spin multiplicity
     159             : !> \param nconstraint           the number of constraints
     160             : !> \param run_type              what type of mixed CDFT simulation to perform
     161             : !> \param source_list           a list of processors which will send this processor data
     162             : !> \param dest_list             a list of processors which this processor will send data to
     163             : !> \param recv_bo               bounds of the data which this processor will receive (is_special = .FALSE.)
     164             : !> \param source_list_save      permanent copy of source_list which might get reallocated during
     165             : !>                              load balancing
     166             : !> \param dest_list_save        permanent copy of dest_list which might get reallocated during
     167             : !>                              load balancing
     168             : !> \param source_list_bo        bounds of the data which this processor will receive (is_special = .TRUE.)
     169             : !> \param dest_list_bo          bounds of the data this processor will send (is_special = .TRUE.)
     170             : !> \param source_bo_save        permanent copy of source_list_bo
     171             : !> \param deset_bo_save         permanent copy of dest_list_bo
     172             : !> \param is_pencil             flag controlling which scheme to use for constraint replication
     173             : !> \param dlb                   flag to enable dynamic load balancing
     174             : !> \param is_special            another flag controlling which scheme to use for constraint replication
     175             : !> \param first_iteration       flag to mark the first iteration e.g. during MD to output information
     176             : !> \param calculate_metric      flag which determines if the coupling reliability metric should be computed
     177             : !> \param wnf_ovelap_method     flag to enable the wavefunction overlap method for computing the coupling
     178             : !> \param has_unit_metric       flag to determine if the basis set has unit metric
     179             : !> \param use_lowdin            flag which determines if Lowdin orthogonalization is used to compute the coupling
     180             : !> \param do_ci                 flag which determines if a CDFT-CI calculation was requested
     181             : !> \param nonortho_coupling     flag which determines if the nonorthogonal CDFT interaction energies
     182             : !>                              should be printed out
     183             : !> \param identical_constraints flag which determines if the constraint definitions are identical
     184             : !>                              across all CDFT states
     185             : !> \param block_diagonalize     flag which determines if the CDFT Hamiltonian should be block
     186             : !>                              diagonalized
     187             : !> \param constraint_type       list of integers which determine what type of constraint should be applied
     188             : !>                              to each constraint group
     189             : !> \param eps_rho_rspace        threshold to determine when the realspace density can be considered zero
     190             : !> \param sim_dt                timestep of the MD simulation
     191             : !> \param eps_svd               value that controls which matrix inversion method to use
     192             : !> \param weight                the constraint weight function
     193             : !> \param cavity                the confinement cavity: the weight function is nonzero only within the cavity
     194             : !> \param cdft_control          container for cdft_control_type
     195             : !> \param sendbuff              buffer that holds the data to be replicated
     196             : !> \param blacs_env             the blacs_env needed to redistribute arrays during a coupling calculation
     197             : !> \param results               container for mixed CDFT results
     198             : !> \param matrix                container for mixed CDFT work matrices
     199             : !> \param dlb_control           container for load balancing structures
     200             : !> \param qs_kind_set           the qs_kind_set needed to setup a confinement cavity
     201             : !> \param pw_env                the pw_env that holds the fully distributed realspace grid
     202             : !> \param occupations           occupation numbers in case non-uniform occupation
     203             : ! **************************************************************************************************
     204             :    TYPE mixed_cdft_type
     205             :       INTEGER                                          :: sim_step, multiplicity, &
     206             :                                                           nconstraint, &
     207             :                                                           run_type
     208             :       INTEGER, DIMENSION(:, :), ALLOCATABLE            :: constraint_type
     209             :       INTEGER, POINTER, DIMENSION(:)                   :: source_list, dest_list, &
     210             :                                                           recv_bo, source_list_save, &
     211             :                                                           dest_list_save
     212             :       INTEGER, POINTER, DIMENSION(:, :)                :: source_list_bo, dest_list_bo, &
     213             :                                                           source_bo_save, dest_bo_save
     214             :       LOGICAL                                          :: is_pencil, dlb, &
     215             :                                                           is_special, first_iteration, &
     216             :                                                           calculate_metric, &
     217             :                                                           wfn_overlap_method, &
     218             :                                                           has_unit_metric, &
     219             :                                                           use_lowdin, &
     220             :                                                           do_ci, nonortho_coupling, &
     221             :                                                           identical_constraints, &
     222             :                                                           block_diagonalize
     223             :       REAL(KIND=dp)                                    :: eps_rho_rspace, sim_dt, &
     224             :                                                           eps_svd
     225             :       REAL(KIND=dp), POINTER, DIMENSION(:, :, :)       :: weight, cavity
     226             :       TYPE(cdft_control_type), POINTER                 :: cdft_control
     227             :       TYPE(buffers), DIMENSION(:), POINTER             :: sendbuff
     228             :       TYPE(cp_1d_r_p_type), ALLOCATABLE, &
     229             :          DIMENSION(:, :)                               :: occupations
     230             :       TYPE(cp_blacs_env_type), POINTER                 :: blacs_env
     231             :       TYPE(cp_logger_p_type), DIMENSION(:), POINTER    :: sub_logger
     232             :       TYPE(mixed_cdft_result_type)                     :: results
     233             :       TYPE(mixed_cdft_work_type)                       :: matrix
     234             :       TYPE(mixed_cdft_dlb_type), POINTER               :: dlb_control
     235             :       TYPE(pw_env_type), POINTER                       :: pw_env
     236             :       TYPE(qs_kind_type), DIMENSION(:), &
     237             :          POINTER                                       :: qs_kind_set
     238             :    END TYPE mixed_cdft_type
     239             : 
     240             : ! **************************************************************************************************
     241             : !> \brief Container for constraint settings to check consistency of force_evals
     242             : ! **************************************************************************************************
     243             :    TYPE mixed_cdft_settings_type
     244             :       LOGICAL                                            :: is_spherical, &
     245             :                                                             is_odd
     246             :       LOGICAL, DIMENSION(:, :), POINTER                  :: sb
     247             :       INTEGER                                            :: ncdft, &
     248             :                                                             max_nkinds
     249             :       INTEGER, DIMENSION(2, 3)                           :: bo
     250             :       INTEGER, DIMENSION(:), POINTER                     :: grid_span, &
     251             :                                                             spherical, &
     252             :                                                             odd
     253             :       INTEGER, DIMENSION(:, :), POINTER                  :: si, &
     254             :                                                             rs_dims, &
     255             :                                                             atoms, &
     256             :                                                             npts
     257             :       REAL(KIND=dp)                                      :: radius
     258             :       REAL(KIND=dp), DIMENSION(:), POINTER               :: cutoff, &
     259             :                                                             rel_cutoff
     260             :       REAL(KIND=dp), DIMENSION(:, :), POINTER            :: sr, &
     261             :                                                             coeffs, &
     262             :                                                             cutoffs, &
     263             :                                                             radii
     264             :    END TYPE mixed_cdft_settings_type
     265             : 
     266             : ! *** Public data types ***
     267             : 
     268             :    PUBLIC :: mixed_cdft_type, &
     269             :              mixed_cdft_settings_type
     270             : 
     271             : ! *** Public subroutines ***
     272             : 
     273             :    PUBLIC :: mixed_cdft_type_create, &
     274             :              mixed_cdft_type_release, &
     275             :              mixed_cdft_result_type_set, &
     276             :              mixed_cdft_result_type_release, &
     277             :              mixed_cdft_work_type_init, &
     278             :              mixed_cdft_work_type_release
     279             : 
     280             :    CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'mixed_cdft_types'
     281             : 
     282             : CONTAINS
     283             : 
     284             : ! **************************************************************************************************
     285             : !> \brief inits the given mixed_cdft_type
     286             : !> \param cdft_control the object to init
     287             : !> \author Nico Holmberg [01.2017]
     288             : ! **************************************************************************************************
     289          72 :    SUBROUTINE mixed_cdft_type_create(cdft_control)
     290             :       TYPE(mixed_cdft_type), POINTER                     :: cdft_control
     291             : 
     292          72 :       NULLIFY (cdft_control%pw_env, cdft_control%blacs_env, cdft_control%qs_kind_set)
     293          72 :       NULLIFY (cdft_control%dlb_control, cdft_control%dest_list_bo, cdft_control%dest_list)
     294          72 :       NULLIFY (cdft_control%dest_bo_save, cdft_control%dest_list_save, cdft_control%source_list)
     295          72 :       NULLIFY (cdft_control%source_list_save, cdft_control%source_bo_save, cdft_control%source_list_bo)
     296          72 :       NULLIFY (cdft_control%cavity, cdft_control%weight, cdft_control%sendbuff)
     297          72 :       NULLIFY (cdft_control%cdft_control, cdft_control%recv_bo)
     298          72 :       NULLIFY (cdft_control%sub_logger)
     299             : 
     300          72 :    END SUBROUTINE mixed_cdft_type_create
     301             : 
     302             : ! **************************************************************************************************
     303             : !> \brief releases the given mixed_cdft_type
     304             : !> \param cdft_control the object to release
     305             : !> \author Nico Holmberg [01.2017]
     306             : ! **************************************************************************************************
     307          72 :    SUBROUTINE mixed_cdft_type_release(cdft_control)
     308             :       TYPE(mixed_cdft_type), POINTER                     :: cdft_control
     309             : 
     310             :       INTEGER                                            :: i, j
     311             : 
     312          72 :       CALL pw_env_release(cdft_control%pw_env)
     313          72 :       IF (ASSOCIATED(cdft_control%dest_list)) &
     314          22 :          DEALLOCATE (cdft_control%dest_list)
     315          72 :       IF (ASSOCIATED(cdft_control%dest_list_save)) &
     316           0 :          DEALLOCATE (cdft_control%dest_list_save)
     317          72 :       IF (ASSOCIATED(cdft_control%dest_list_bo)) &
     318           0 :          DEALLOCATE (cdft_control%dest_list_bo)
     319          72 :       IF (ASSOCIATED(cdft_control%dest_bo_save)) &
     320           0 :          DEALLOCATE (cdft_control%dest_bo_save)
     321          72 :       IF (ASSOCIATED(cdft_control%source_list)) &
     322          22 :          DEALLOCATE (cdft_control%source_list)
     323          72 :       IF (ASSOCIATED(cdft_control%source_list_save)) &
     324           0 :          DEALLOCATE (cdft_control%source_list_save)
     325          72 :       IF (ASSOCIATED(cdft_control%source_list_bo)) &
     326           0 :          DEALLOCATE (cdft_control%source_list_bo)
     327          72 :       IF (ASSOCIATED(cdft_control%source_bo_save)) &
     328           0 :          DEALLOCATE (cdft_control%source_bo_save)
     329          72 :       IF (ASSOCIATED(cdft_control%recv_bo)) &
     330          22 :          DEALLOCATE (cdft_control%recv_bo)
     331          72 :       IF (ASSOCIATED(cdft_control%weight)) &
     332           0 :          DEALLOCATE (cdft_control%weight)
     333          72 :       IF (ASSOCIATED(cdft_control%cavity)) &
     334           0 :          DEALLOCATE (cdft_control%cavity)
     335          72 :       IF (ALLOCATED(cdft_control%constraint_type)) &
     336          72 :          DEALLOCATE (cdft_control%constraint_type)
     337          72 :       IF (ALLOCATED(cdft_control%occupations)) THEN
     338           0 :          DO i = 1, SIZE(cdft_control%occupations, 1)
     339           0 :             DO j = 1, SIZE(cdft_control%occupations, 2)
     340           0 :                IF (ASSOCIATED(cdft_control%occupations(i, j)%array)) &
     341           0 :                   DEALLOCATE (cdft_control%occupations(i, j)%array)
     342             :             END DO
     343             :          END DO
     344           0 :          DEALLOCATE (cdft_control%occupations)
     345             :       END IF
     346          72 :       IF (ASSOCIATED(cdft_control%dlb_control)) &
     347           4 :          CALL mixed_cdft_dlb_release(cdft_control%dlb_control)
     348          72 :       IF (ASSOCIATED(cdft_control%sendbuff)) THEN
     349           0 :          DO i = 1, SIZE(cdft_control%sendbuff)
     350           0 :             CALL mixed_cdft_buffers_release(cdft_control%sendbuff(i))
     351             :          END DO
     352           0 :          DEALLOCATE (cdft_control%sendbuff)
     353             :       END IF
     354          72 :       IF (ASSOCIATED(cdft_control%cdft_control)) THEN
     355          22 :          CALL cdft_control_release(cdft_control%cdft_control)
     356          22 :          DEALLOCATE (cdft_control%cdft_control)
     357             :       END IF
     358          72 :       IF (ASSOCIATED(cdft_control%blacs_env)) &
     359          72 :          CALL cp_blacs_env_release(cdft_control%blacs_env)
     360          72 :       IF (ASSOCIATED(cdft_control%qs_kind_set)) &
     361          28 :          CALL deallocate_qs_kind_set(cdft_control%qs_kind_set)
     362          72 :       IF (ASSOCIATED(cdft_control%sub_logger)) THEN
     363         124 :          DO i = 1, SIZE(cdft_control%sub_logger)
     364         124 :             CALL cp_logger_release(cdft_control%sub_logger(i)%p)
     365             :          END DO
     366          50 :          DEALLOCATE (cdft_control%sub_logger)
     367             :       END IF
     368          72 :       CALL mixed_cdft_result_type_release(cdft_control%results)
     369          72 :       CALL mixed_cdft_work_type_release(cdft_control%matrix)
     370          72 :       DEALLOCATE (cdft_control)
     371             : 
     372          72 :    END SUBROUTINE mixed_cdft_type_release
     373             : 
     374             : ! **************************************************************************************************
     375             : !> \brief releases the given load balancing control
     376             : !> \param dlb_control the object to release
     377             : !> \author Nico Holmberg [01.2017]
     378             : ! **************************************************************************************************
     379           4 :    SUBROUTINE mixed_cdft_dlb_release(dlb_control)
     380             :       TYPE(mixed_cdft_dlb_type), POINTER                 :: dlb_control
     381             : 
     382             :       INTEGER                                            :: i
     383             : 
     384           4 :       IF (ASSOCIATED(dlb_control%recv_work_repl)) &
     385           0 :          DEALLOCATE (dlb_control%recv_work_repl)
     386           4 :       IF (ASSOCIATED(dlb_control%sendbuff)) THEN
     387           0 :          DO i = 1, SIZE(dlb_control%sendbuff)
     388           0 :             CALL mixed_cdft_buffers_release(dlb_control%sendbuff(i))
     389             :          END DO
     390           0 :          DEALLOCATE (dlb_control%sendbuff)
     391             :       END IF
     392           4 :       IF (ASSOCIATED(dlb_control%recvbuff)) THEN
     393           0 :          DO i = 1, SIZE(dlb_control%recvbuff)
     394           0 :             CALL mixed_cdft_p_buffers_release(dlb_control%recvbuff(i))
     395             :          END DO
     396           0 :          DEALLOCATE (dlb_control%recvbuff)
     397             :       END IF
     398           4 :       IF (ASSOCIATED(dlb_control%recv_info)) THEN
     399           0 :          DO i = 1, SIZE(dlb_control%recv_info)
     400           0 :             IF (ASSOCIATED(dlb_control%recv_info(i)%matrix_info)) &
     401           0 :                DEALLOCATE (dlb_control%recv_info(i)%matrix_info)
     402           0 :             IF (ASSOCIATED(dlb_control%recv_info(i)%target_list)) &
     403           0 :                DEALLOCATE (dlb_control%recv_info(i)%target_list)
     404             :          END DO
     405           0 :          DEALLOCATE (dlb_control%recv_info)
     406             :       END IF
     407           4 :       IF (ASSOCIATED(dlb_control%bo)) &
     408           0 :          DEALLOCATE (dlb_control%bo)
     409           4 :       IF (ASSOCIATED(dlb_control%expected_work)) &
     410           0 :          DEALLOCATE (dlb_control%expected_work)
     411           4 :       IF (ASSOCIATED(dlb_control%prediction_error)) &
     412           4 :          DEALLOCATE (dlb_control%prediction_error)
     413           4 :       IF (ASSOCIATED(dlb_control%target_list)) &
     414           0 :          DEALLOCATE (dlb_control%target_list)
     415           4 :       IF (ASSOCIATED(dlb_control%cavity)) &
     416           0 :          DEALLOCATE (dlb_control%cavity)
     417           4 :       IF (ASSOCIATED(dlb_control%weight)) &
     418           0 :          DEALLOCATE (dlb_control%weight)
     419           4 :       IF (ASSOCIATED(dlb_control%gradients)) &
     420           0 :          DEALLOCATE (dlb_control%gradients)
     421           4 :       DEALLOCATE (dlb_control)
     422             : 
     423           4 :    END SUBROUTINE mixed_cdft_dlb_release
     424             : 
     425             : ! **************************************************************************************************
     426             : !> \brief releases the given buffers
     427             : !> \param buffer the object to release
     428             : !> \author Nico Holmberg [01.2017]
     429             : ! **************************************************************************************************
     430           0 :    SUBROUTINE mixed_cdft_buffers_release(buffer)
     431             :       TYPE(buffers)                                      :: buffer
     432             : 
     433           0 :       IF (ASSOCIATED(buffer%cavity)) &
     434           0 :          DEALLOCATE (buffer%cavity)
     435           0 :       IF (ASSOCIATED(buffer%weight)) &
     436           0 :          DEALLOCATE (buffer%weight)
     437           0 :       IF (ASSOCIATED(buffer%gradients)) &
     438           0 :          DEALLOCATE (buffer%gradients)
     439             : 
     440           0 :    END SUBROUTINE mixed_cdft_buffers_release
     441             : 
     442             : ! **************************************************************************************************
     443             : !> \brief releases the given pointer of buffers
     444             : !> \param p_buffer the object to release
     445             : !> \author Nico Holmberg [01.2017]
     446             : ! **************************************************************************************************
     447           0 :    SUBROUTINE mixed_cdft_p_buffers_release(p_buffer)
     448             :       TYPE(p_buffers)                                    :: p_buffer
     449             : 
     450             :       INTEGER                                            :: i
     451             : 
     452           0 :       IF (ASSOCIATED(p_buffer%buffs)) THEN
     453           0 :          DO i = 1, SIZE(p_buffer%buffs)
     454           0 :             CALL mixed_cdft_buffers_release(p_buffer%buffs(i))
     455             :          END DO
     456           0 :          DEALLOCATE (p_buffer%buffs)
     457             :       END IF
     458             : 
     459           0 :    END SUBROUTINE mixed_cdft_p_buffers_release
     460             : 
     461             : ! **************************************************************************************************
     462             : !> \brief Updates arrays within the mixed CDFT result container
     463             : !> \param results      the array container
     464             : !> \param lowdin       CDFT electronic couplings from Lowdin orthogonalization
     465             : !> \param wfn          CDFT electronic couplings from wavefunction overlap method
     466             : !> \param nonortho     CDFT electronic couplings (interaction energies) before orthogonalization
     467             : !> \param metric       Reliability metric for CDFT electronic couplings
     468             : !> \param rotation     CDFT electronic couplings using the weight function matrix for orthogonalization
     469             : !> \param H            The mixed CDFT Hamiltonian
     470             : !> \param S            The overlap matrix between CDFT states
     471             : !> \param Wad          Integrals of type <Psi_a | w_d(r) | Psi_d>
     472             : !> \param Wda          Integrals of type <Psi_d | w_a(r) | Psi_a>
     473             : !> \param W_diagonal   Values of the CDFT constraints
     474             : !> \param energy       Energies of the CDFT states
     475             : !> \param strength     Lagrangian multipliers of the CDFT states
     476             : !> \param S_minushalf  S^(-1/2)
     477             : !> \author Nico Holmberg [11.2017]
     478             : ! **************************************************************************************************
     479        1076 :    SUBROUTINE mixed_cdft_result_type_set(results, lowdin, wfn, nonortho, metric, rotation, &
     480        1076 :                                          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
     488             : 
     489         538 :       IF (PRESENT(lowdin)) THEN
     490          20 :          IF (ALLOCATED(results%lowdin)) DEALLOCATE (results%lowdin)
     491          60 :          ALLOCATE (results%lowdin(SIZE(lowdin)))
     492          40 :          results%lowdin(:) = lowdin(:)
     493             :       END IF
     494         538 :       IF (PRESENT(wfn)) THEN
     495           8 :          IF (ALLOCATED(results%wfn)) DEALLOCATE (results%wfn)
     496          24 :          ALLOCATE (results%wfn(SIZE(wfn)))
     497          20 :          results%wfn(:) = wfn(:)
     498             :       END IF
     499         538 :       IF (PRESENT(nonortho)) THEN
     500          18 :          IF (ALLOCATED(results%nonortho)) DEALLOCATE (results%nonortho)
     501          54 :          ALLOCATE (results%nonortho(SIZE(nonortho)))
     502         118 :          results%nonortho(:) = nonortho(:)
     503             :       END IF
     504         538 :       IF (PRESENT(rotation)) THEN
     505          90 :          IF (ALLOCATED(results%rotation)) DEALLOCATE (results%rotation)
     506         270 :          ALLOCATE (results%rotation(SIZE(rotation)))
     507         262 :          results%rotation(:) = rotation(:)
     508             :       END IF
     509         538 :       IF (PRESENT(energy)) THEN
     510          94 :          IF (ALLOCATED(results%energy)) DEALLOCATE (results%energy)
     511         282 :          ALLOCATE (results%energy(SIZE(energy)))
     512         306 :          results%energy(:) = energy(:)
     513             :       END IF
     514         538 :       IF (PRESENT(strength)) THEN
     515          94 :          IF (ALLOCATED(results%strength)) DEALLOCATE (results%strength)
     516         376 :          ALLOCATE (results%strength(SIZE(strength, 1), SIZE(strength, 2)))
     517         522 :          results%strength(:, :) = strength(:, :)
     518             :       END IF
     519         538 :       IF (PRESENT(metric)) THEN
     520          14 :          IF (ALLOCATED(results%metric)) DEALLOCATE (results%metric)
     521          56 :          ALLOCATE (results%metric(SIZE(metric, 1), SIZE(metric, 2)))
     522          78 :          results%metric(:, :) = metric(:, :)
     523             :       END IF
     524         538 :       IF (PRESENT(H)) THEN
     525         104 :          IF (ALLOCATED(results%H)) DEALLOCATE (results%H)
     526         416 :          ALLOCATE (results%H(SIZE(H, 1), SIZE(H, 2)))
     527         996 :          results%H(:, :) = H(:, :)
     528             :       END IF
     529         538 :       IF (PRESENT(S)) THEN
     530         104 :          IF (ALLOCATED(results%S)) DEALLOCATE (results%S)
     531         416 :          ALLOCATE (results%S(SIZE(S, 1), SIZE(S, 2)))
     532         996 :          results%S(:, :) = S(:, :)
     533             :       END IF
     534         538 :       IF (PRESENT(S_minushalf)) THEN
     535          94 :          IF (ALLOCATED(results%S_minushalf)) DEALLOCATE (results%S_minushalf)
     536         376 :          ALLOCATE (results%S_minushalf(SIZE(S_minushalf, 1), SIZE(S_minushalf, 2)))
     537         870 :          results%S_minushalf(:, :) = S_minushalf(:, :)
     538             :       END IF
     539         538 :       IF (PRESENT(Wad)) THEN
     540           2 :          IF (ALLOCATED(results%Wad)) DEALLOCATE (results%Wad)
     541           8 :          ALLOCATE (results%Wad(SIZE(Wad, 1), SIZE(Wad, 2)))
     542           6 :          results%Wad(:, :) = Wad(:, :)
     543             :       END IF
     544         538 :       IF (PRESENT(Wda)) THEN
     545          94 :          IF (ALLOCATED(results%Wda)) DEALLOCATE (results%Wda)
     546         376 :          ALLOCATE (results%Wda(SIZE(Wda, 1), SIZE(Wda, 2)))
     547         448 :          results%Wda(:, :) = Wda(:, :)
     548             :       END IF
     549         538 :       IF (PRESENT(W_diagonal)) THEN
     550          94 :          IF (ALLOCATED(results%W_diagonal)) DEALLOCATE (results%W_diagonal)
     551         376 :          ALLOCATE (results%W_diagonal(SIZE(W_diagonal, 1), SIZE(W_diagonal, 2)))
     552         522 :          results%W_diagonal(:, :) = W_diagonal(:, :)
     553             :       END IF
     554             : 
     555         538 :    END SUBROUTINE mixed_cdft_result_type_set
     556             : 
     557             : ! **************************************************************************************************
     558             : !> \brief Releases all arrays within the mixed CDFT result container
     559             : !> \param results the container
     560             : !> \author Nico Holmberg [11.2017]
     561             : ! **************************************************************************************************
     562         166 :    SUBROUTINE mixed_cdft_result_type_release(results)
     563             :       TYPE(mixed_cdft_result_type)                       :: results
     564             : 
     565         166 :       IF (ALLOCATED(results%lowdin)) DEALLOCATE (results%lowdin)
     566         166 :       IF (ALLOCATED(results%wfn)) DEALLOCATE (results%wfn)
     567         166 :       IF (ALLOCATED(results%metric)) DEALLOCATE (results%metric)
     568         166 :       IF (ALLOCATED(results%nonortho)) DEALLOCATE (results%nonortho)
     569         166 :       IF (ALLOCATED(results%rotation)) DEALLOCATE (results%rotation)
     570         166 :       IF (ALLOCATED(results%H)) DEALLOCATE (results%H)
     571         166 :       IF (ALLOCATED(results%S)) DEALLOCATE (results%S)
     572         166 :       IF (ALLOCATED(results%S_minushalf)) DEALLOCATE (results%S_minushalf)
     573         166 :       IF (ALLOCATED(results%Wad)) DEALLOCATE (results%Wad)
     574         166 :       IF (ALLOCATED(results%Wda)) DEALLOCATE (results%Wda)
     575         166 :       IF (ALLOCATED(results%W_diagonal)) DEALLOCATE (results%W_diagonal)
     576         166 :       IF (ALLOCATED(results%energy)) DEALLOCATE (results%energy)
     577         166 :       IF (ALLOCATED(results%strength)) DEALLOCATE (results%strength)
     578             : 
     579         166 :    END SUBROUTINE mixed_cdft_result_type_release
     580             : 
     581             : ! **************************************************************************************************
     582             : !> \brief Initializes the mixed_cdft_work_type
     583             : !> \param matrix the type to initialize
     584             : !> \author Nico Holmberg [01.2017]
     585             : ! **************************************************************************************************
     586          94 :    SUBROUTINE mixed_cdft_work_type_init(matrix)
     587             :       TYPE(mixed_cdft_work_type)                         :: matrix
     588             : 
     589          94 :       NULLIFY (matrix%w_matrix)
     590          94 :       NULLIFY (matrix%mixed_matrix_s)
     591          94 :       NULLIFY (matrix%mixed_mo_coeff)
     592          94 :       NULLIFY (matrix%density_matrix)
     593             : 
     594          94 :    END SUBROUTINE mixed_cdft_work_type_init
     595             : 
     596             : ! **************************************************************************************************
     597             : !> \brief Releases arrays within the mixed CDFT work matrix container
     598             : !> \param matrix the container
     599             : !> \author Nico Holmberg [01.2017]
     600             : ! **************************************************************************************************
     601         166 :    SUBROUTINE mixed_cdft_work_type_release(matrix)
     602             :       TYPE(mixed_cdft_work_type)                         :: matrix
     603             : 
     604             :       INTEGER                                            :: i, j
     605             : 
     606         166 :       IF (ASSOCIATED(matrix%w_matrix)) THEN
     607         190 :          DO i = 1, SIZE(matrix%w_matrix, 2)
     608         406 :             DO j = 1, SIZE(matrix%w_matrix, 1)
     609         312 :                CALL dbcsr_release_p(matrix%w_matrix(j, i)%matrix)
     610             :             END DO
     611             :          END DO
     612          94 :          DEALLOCATE (matrix%w_matrix)
     613             :       END IF
     614         166 :       IF (ASSOCIATED(matrix%mixed_matrix_s)) THEN
     615          94 :          CALL dbcsr_release_p(matrix%mixed_matrix_s)
     616             :       END IF
     617         166 :       IF (ASSOCIATED(matrix%mixed_mo_coeff)) THEN
     618         282 :          DO i = 1, SIZE(matrix%mixed_mo_coeff, 2)
     619         706 :             DO j = 1, SIZE(matrix%mixed_mo_coeff, 1)
     620         612 :                CALL cp_fm_release(matrix%mixed_mo_coeff(j, i))
     621             :             END DO
     622             :          END DO
     623          94 :          DEALLOCATE (matrix%mixed_mo_coeff)
     624             :       END IF
     625         166 :       IF (ASSOCIATED(matrix%density_matrix)) THEN
     626          42 :          DO i = 1, SIZE(matrix%density_matrix, 2)
     627         102 :             DO j = 1, SIZE(matrix%density_matrix, 1)
     628          88 :                CALL dbcsr_release_p(matrix%density_matrix(j, i)%matrix)
     629             :             END DO
     630             :          END DO
     631          14 :          DEALLOCATE (matrix%density_matrix)
     632             :       END IF
     633             : 
     634         166 :    END SUBROUTINE mixed_cdft_work_type_release
     635             : 
     636           0 : END MODULE mixed_cdft_types

Generated by: LCOV version 1.15