(git:e7e05ae)
admm_dm_types.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 Types and set/get functions for auxiliary density matrix methods
10 !> \par History
11 !> 11.2014 created [Ole Schuett]
12 !> \author Ole Schuett
13 ! **************************************************************************************************
15  USE cp_control_types, ONLY: admm_control_type
16  USE dbcsr_api, ONLY: dbcsr_release,&
17  dbcsr_type
20  USE kinds, ONLY: dp
21 #include "./base/base_uses.f90"
22 
23  IMPLICIT NONE
24  PRIVATE
25 
26  PUBLIC :: admm_dm_type, mcweeny_history_type
28 
29  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'admm_dm_types'
30 
31  TYPE mcweeny_history_type
32  TYPE(dbcsr_type) :: m
33  INTEGER :: count = -1
34  TYPE(mcweeny_history_type), POINTER :: next => null()
35  END TYPE mcweeny_history_type
36 
37  TYPE mcweeny_history_p_type
38  TYPE(mcweeny_history_type), POINTER :: p => null()
39  END TYPE mcweeny_history_p_type
40 
41  TYPE admm_dm_type
42  LOGICAL :: purify = .false.
43  INTEGER :: method = -1
44  TYPE(dbcsr_type), POINTER :: matrix_a => null()
45  REAL(KIND=dp) :: eps_filter = 1e-20_dp
46  INTEGER :: mcweeny_max_steps = 100
47  INTEGER, DIMENSION(:, :), POINTER :: block_map => null()
48  TYPE(mcweeny_history_p_type), &
49  DIMENSION(:), POINTER :: mcweeny_history => null()
50  END TYPE
51 
52 CONTAINS
53 
54 ! **************************************************************************************************
55 !> \brief Create a new admm_dm type
56 !> \param admm_dm ...
57 !> \param admm_control ...
58 !> \param nspins ...
59 !> \param natoms ...
60 !> \author Ole Schuett
61 ! **************************************************************************************************
62  SUBROUTINE admm_dm_create(admm_dm, admm_control, nspins, natoms)
63  TYPE(admm_dm_type), POINTER :: admm_dm
64  TYPE(admm_control_type), POINTER :: admm_control
65  INTEGER, INTENT(IN) :: nspins, natoms
66 
67  INTEGER :: i, iatom, iblock, j, jatom
68 
69  ALLOCATE (admm_dm)
70  ! copy settings from admm_control
71  admm_dm%purify = (admm_control%purification_method == do_admm_purify_mcweeny)
72  admm_dm%method = admm_control%method
73  admm_dm%eps_filter = admm_control%eps_filter
74 
75  ALLOCATE (admm_dm%mcweeny_history(nspins))
76 
77  IF (admm_dm%method /= do_admm_basis_projection) THEN
78  ! create block map
79  ALLOCATE (admm_dm%block_map(natoms, natoms))
80  admm_dm%block_map(:, :) = 0
81  DO iblock = 1, SIZE(admm_control%blocks)
82  DO i = 1, SIZE(admm_control%blocks(iblock)%list)
83  iatom = admm_control%blocks(iblock)%list(i)
84  DO j = 1, SIZE(admm_control%blocks(iblock)%list)
85  jatom = admm_control%blocks(iblock)%list(j)
86  admm_dm%block_map(iatom, jatom) = 1
87  END DO
88  END DO
89  END DO
90  END IF
91  END SUBROUTINE admm_dm_create
92 
93 ! **************************************************************************************************
94 !> \brief Release a admm_dm type
95 !> \param admm_dm ...
96 !> \author Ole Schuett
97 ! **************************************************************************************************
98  SUBROUTINE admm_dm_release(admm_dm)
99  TYPE(admm_dm_type), POINTER :: admm_dm
100 
101  IF (.NOT. ASSOCIATED(admm_dm)) RETURN
102 
103  IF (ASSOCIATED(admm_dm%matrix_a)) THEN
104  CALL dbcsr_release(admm_dm%matrix_a)
105  DEALLOCATE (admm_dm%matrix_a)
106  END IF
107 
108  IF (ASSOCIATED(admm_dm%block_map)) &
109  DEALLOCATE (admm_dm%block_map)
110 
111  DEALLOCATE (admm_dm%mcweeny_history)
112  DEALLOCATE (admm_dm)
113 
114  END SUBROUTINE admm_dm_release
115 
116 END MODULE admm_dm_types
117 
Types and set/get functions for auxiliary density matrix methods.
Definition: admm_dm_types.F:14
subroutine, public admm_dm_create(admm_dm, admm_control, nspins, natoms)
Create a new admm_dm type.
Definition: admm_dm_types.F:63
subroutine, public admm_dm_release(admm_dm)
Release a admm_dm type.
Definition: admm_dm_types.F:99
Defines control structures, which contain the parameters and the settings for the DFT-based calculati...
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_admm_purify_mcweeny
integer, parameter, public do_admm_basis_projection
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34