(git:34ef472)
qs_block_davidson_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 module that contains the algorithms to perform an itrative
10 !> diagonalization by the block-Davidson approach
11 !> P. Blaha, et al J. Comp. Physics, 229, (2010), 453-460
12 !> \Iterative diagonalization in augmented plane wave based
13 !> methods in electronic structure calculations\
14 !> \par History
15 !> 05.2011 created [MI]
16 !> \author MI
17 ! **************************************************************************************************
19 
22  cp_fm_struct_type
23  USE cp_fm_types, ONLY: cp_fm_create,&
24  cp_fm_release,&
25  cp_fm_type
26  USE input_section_types, ONLY: section_vals_type,&
28  USE kinds, ONLY: dp
29 #include "./base/base_uses.f90"
30 
31  IMPLICIT NONE
32  PRIVATE
33  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_block_davidson_types'
34 
36  block_davidson_env_create, davidson_type
37 
38  TYPE davidson_type
39  INTEGER :: max_iter, prec_type, solver_type, niter_new_prec, first_prec
40  LOGICAL :: use_sparse_mos
41  REAL(KIND=dp) :: conv_percent, energy_gap, eps_iter
42  TYPE(cp_fm_type), POINTER :: H_block_mat, H_block_vec, &
43  matrix_z, matrix_pz, S_block_mat, W_block_mat
44  END TYPE davidson_type
45 
46 CONTAINS
47 
48 ! **************************************************************************************************
49 
50 ! **************************************************************************************************
51 !> \brief ...
52 !> \param bdav_env ...
53 !> \param nspins ...
54 !> \param scf_section ...
55 ! **************************************************************************************************
56  SUBROUTINE block_davidson_env_create(bdav_env, nspins, scf_section)
57 
58  TYPE(davidson_type), DIMENSION(:), POINTER :: bdav_env
59  INTEGER, INTENT(IN) :: nspins
60  TYPE(section_vals_type), POINTER :: scf_section
61 
62  INTEGER :: ispin
63 
64  cpassert(.NOT. ASSOCIATED(bdav_env))
65  ALLOCATE (bdav_env(nspins))
66  DO ispin = 1, nspins
67  NULLIFY (bdav_env(ispin)%H_block_mat)
68  NULLIFY (bdav_env(ispin)%H_block_vec)
69  NULLIFY (bdav_env(ispin)%S_block_mat)
70  NULLIFY (bdav_env(ispin)%W_block_mat)
71  NULLIFY (bdav_env(ispin)%matrix_z)
72  NULLIFY (bdav_env(ispin)%matrix_pz)
73 
74  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DAVIDSON%PRECONDITIONER", &
75  i_val=bdav_env(ispin)%prec_type)
76  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DAVIDSON%PRECOND_SOLVER", &
77  i_val=bdav_env(ispin)%solver_type)
78  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DAVIDSON%ENERGY_GAP", &
79  r_val=bdav_env(ispin)%energy_gap)
80  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DAVIDSON%NEW_PREC_EACH", &
81  i_val=bdav_env(ispin)%niter_new_prec)
82  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%MAX_ITER", &
83  i_val=bdav_env(ispin)%max_iter)
84  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%EPS_ITER", &
85  r_val=bdav_env(ispin)%eps_iter)
86  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DAVIDSON%FIRST_PREC", &
87  i_val=bdav_env(ispin)%first_prec)
88  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DAVIDSON%CONV_MOS_PERCENT", &
89  r_val=bdav_env(ispin)%conv_percent)
90  CALL section_vals_val_get(scf_section, "DIAGONALIZATION%DAVIDSON%SPARSE_MOS", &
91  l_val=bdav_env(ispin)%use_sparse_mos)
92 
93  END DO
94 
95  END SUBROUTINE block_davidson_env_create
96 
97 ! **************************************************************************************************
98 !> \brief ...
99 !> \param bdav_env ...
100 !> \param mo_coeff ...
101 !> \param nao ...
102 !> \param nmo ...
103 ! **************************************************************************************************
104  SUBROUTINE block_davidson_allocate(bdav_env, mo_coeff, nao, nmo)
105 
106  TYPE(davidson_type) :: bdav_env
107  TYPE(cp_fm_type), INTENT(IN) :: mo_coeff
108  INTEGER, INTENT(IN) :: nao, nmo
109 
110  CHARACTER(len=*), PARAMETER :: routinen = 'block_davidson_allocate'
111 
112  INTEGER :: handle, nmox2
113  TYPE(cp_fm_struct_type), POINTER :: fm_struct_tmp
114 
115  CALL timeset(routinen, handle)
116  NULLIFY (fm_struct_tmp)
117 
118  nmox2 = 2*nmo
119 
120  CALL cp_fm_struct_create(fm_struct_tmp, nrow_global=nao, ncol_global=nmo, &
121  para_env=mo_coeff%matrix_struct%para_env, &
122  context=mo_coeff%matrix_struct%context)
123  NULLIFY (bdav_env%matrix_z, bdav_env%matrix_pz)
124  ALLOCATE (bdav_env%matrix_z, bdav_env%matrix_pz)
125  CALL cp_fm_create(bdav_env%matrix_z, fm_struct_tmp, name="Z_mat")
126  CALL cp_fm_create(bdav_env%matrix_pz, fm_struct_tmp, name="Z_mat")
127  CALL cp_fm_struct_release(fm_struct_tmp)
128 
129  CALL timestop(handle)
130 
131  END SUBROUTINE block_davidson_allocate
132 
133 ! **************************************************************************************************
134 !> \brief ...
135 !> \param bdav_env ...
136 ! **************************************************************************************************
137  SUBROUTINE block_davidson_deallocate(bdav_env)
138 
139  TYPE(davidson_type), DIMENSION(:), POINTER :: bdav_env
140 
141  INTEGER :: ispin, nspins
142 
143  IF (ASSOCIATED(bdav_env)) THEN
144 
145  nspins = SIZE(bdav_env)
146  DO ispin = 1, nspins
147 
148  CALL cp_fm_release(bdav_env(ispin)%matrix_z)
149  CALL cp_fm_release(bdav_env(ispin)%matrix_pz)
150  DEALLOCATE (bdav_env(ispin)%matrix_z, bdav_env(ispin)%matrix_pz)
151  NULLIFY (bdav_env(ispin)%matrix_z, bdav_env(ispin)%matrix_pz)
152 
153  END DO
154 
155  END IF
156 
157  END SUBROUTINE block_davidson_deallocate
158 
159 ! **************************************************************************************************
160 !> \brief ...
161 !> \param bdav_env ...
162 ! **************************************************************************************************
163  SUBROUTINE block_davidson_release(bdav_env)
164 
165  TYPE(davidson_type), DIMENSION(:), POINTER :: bdav_env
166 
167  INTEGER :: ispin, nspins
168 
169  IF (ASSOCIATED(bdav_env)) THEN
170 
171  nspins = SIZE(bdav_env)
172  DO ispin = 1, nspins
173 
174  IF (ASSOCIATED(bdav_env(ispin)%matrix_z)) THEN
175  CALL cp_fm_release(bdav_env(ispin)%matrix_z)
176  CALL cp_fm_release(bdav_env(ispin)%matrix_pz)
177  DEALLOCATE (bdav_env(ispin)%matrix_z, bdav_env(ispin)%matrix_pz)
178  NULLIFY (bdav_env(ispin)%matrix_z, bdav_env(ispin)%matrix_pz)
179  END IF
180 
181  END DO
182  DEALLOCATE (bdav_env)
183 
184  END IF
185 
186  END SUBROUTINE block_davidson_release
187 
188 END MODULE qs_block_davidson_types
represent the structure of a full matrix
Definition: cp_fm_struct.F:14
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
Definition: cp_fm_struct.F:125
subroutine, public cp_fm_struct_release(fmstruct)
releases a full matrix structure
Definition: cp_fm_struct.F:320
represent a full matrix distributed on many processors
Definition: cp_fm_types.F:15
subroutine, public cp_fm_create(matrix, matrix_struct, name, use_sp)
creates a new full matrix with the given structure
Definition: cp_fm_types.F:167
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
module that contains the algorithms to perform an itrative diagonalization by the block-Davidson appr...
subroutine, public block_davidson_allocate(bdav_env, mo_coeff, nao, nmo)
...
subroutine, public block_davidson_release(bdav_env)
...
subroutine, public block_davidson_deallocate(bdav_env)
...
subroutine, public block_davidson_env_create(bdav_env, nspins, scf_section)
...