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 New version of the module for the localization of the molecular orbitals
10 : !> This should be able to use different definition of the spread functional
11 : !> It should also calculate the integrals analytically so that it can be
12 : !> used irrespective of the pw_env and the collocation of wfn on the grids
13 : !> It should also work with a selected set of states, instead than all of them,
14 : !> in this case one should check that the selected states have the same occupation number
15 : !> The spread functional can be only estimated, or also optimized by minimization
16 : !> and in principle also maximization should be available.
17 : !> This operations can be required irrespective of the printing requirements
18 : !> It would be highly desirable to do all this along a MD run every N steps,
19 : !> and have a trajectory of the centeroids of the localized wfn
20 : !> In addition these functions can be used for properties calculations
21 : !> like NMR and XAS. Therefore it is necessary that the rotated wfn are then copied
22 : !> in the mos fm matrix to be available for next use.
23 : !> \author MI (05-2005)
24 : ! **************************************************************************************************
25 : MODULE qs_loc_types
26 :
27 : USE cell_types, ONLY: cell_release,&
28 : cell_retain,&
29 : cell_type
30 : USE cp_array_utils, ONLY: cp_2d_r_p_type
31 : USE cp_dbcsr_api, ONLY: dbcsr_deallocate_matrix,&
32 : dbcsr_p_type
33 : USE cp_fm_types, ONLY: cp_fm_release,&
34 : cp_fm_type
35 : USE distribution_1d_types, ONLY: distribution_1d_release,&
36 : distribution_1d_retain,&
37 : distribution_1d_type
38 : USE kinds, ONLY: default_string_length,&
39 : dp
40 : USE message_passing, ONLY: mp_para_env_release,&
41 : mp_para_env_type
42 : USE particle_types, ONLY: particle_type
43 : #include "./base/base_uses.f90"
44 :
45 : IMPLICIT NONE
46 :
47 : PRIVATE
48 :
49 : ! *** Global parameters ***
50 :
51 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_loc_types'
52 :
53 : ! **************************************************************************************************
54 : !> \brief contains all the info needed by quickstep to calculate
55 : !> the spread of a selected set of orbitals and if required
56 : !> to minimize or maximize the spread by rotation of the orbitals
57 : !> \param para_env info for the distribution of the calculations
58 : !> \param mo_coeff full matrix containing only the selected subset of orbitals
59 : !> \param local_molecules molecules distributed
60 : !> \param cell box that contains the system
61 : !> \param localized_wfn_control variables and parameter that define the spread
62 : !> functional and the optimization algorithm
63 : !> \param particle_set position, type, ao_indexes etc for each atom
64 : !> \param op_sm_set set of sparse matrices used to define the spread operator
65 : !> when the functional is defined by the use operator acting on the
66 : !> basis functions, e.g. the Berry phase definition
67 : !> The matrix element of the type <a|O|b> are computed in initialization
68 : !> of qs_loc_env
69 : !> \param op_fm_set set of full matrices used to define the spread operator
70 : !> when the functional has to be defined directly using the products of MOS
71 : !> as in the case of the Pipek-Mezek definition.
72 : !> \param weights for a spread defined as extension of the orbitral in the box, these
73 : !> factors renormalize with respect to the box size
74 : !> \note
75 : !> this type should replace the previous set up for the localization of the wfn
76 : !> \par History
77 : !> 04-05 created
78 : !> \author MI
79 : ! **************************************************************************************************
80 : TYPE qs_loc_env_type
81 : LOGICAL :: do_localize = .FALSE., first_time = .FALSE.
82 : LOGICAL :: molecular_states = .FALSE.
83 : LOGICAL :: wannier_states = .FALSE.
84 : CHARACTER(LEN=default_string_length) :: tag_mo = ""
85 : TYPE(mp_para_env_type), POINTER :: para_env => NULL()
86 : TYPE(cp_fm_type), DIMENSION(:), &
87 : POINTER :: moloc_coeff => NULL()
88 : TYPE(cp_fm_type), DIMENSION(:, :), &
89 : POINTER :: op_fm_set => NULL()
90 : TYPE(distribution_1d_type), POINTER :: local_molecules => NULL()
91 : TYPE(cell_type), POINTER :: cell => NULL()
92 : TYPE(localized_wfn_control_type), &
93 : POINTER :: localized_wfn_control => NULL()
94 : TYPE(particle_type), DIMENSION(:), &
95 : POINTER :: particle_set => NULL()
96 : TYPE(dbcsr_p_type), DIMENSION(:, :), &
97 : POINTER :: op_sm_set => NULL()
98 : REAL(KIND=dp) :: start_time = -1.0_dp, target_time = -1.0_dp
99 : REAL(KIND=dp) :: weights(6) = -1.0_dp
100 : INTEGER :: dim_op = -1
101 : END TYPE qs_loc_env_type
102 :
103 : ! **************************************************************************************************
104 : !> \brief A type that holds controlling information for the
105 : !> calculation of the spread of wfn and the optimization of
106 : !> the spread functional
107 : !> \param ref_count ...
108 : !> \param localization_method which algorithm is used for the optimization
109 : !> \param operator_type how the spread is defined
110 : !> \param nloc_states number of states on which the spread is computed
111 : !> \param set_of_states how to choose the states
112 : !> \param lu_bound_states lower and upper bounds of the set of states
113 : !> print_cubes:
114 : !> print_centers:
115 : !> print_spreads:
116 : !> \param loc_states list of states on which the spread is computed
117 : !> \param centers_set arrais containing centers and spreads of the selected wfn
118 : !> \param centers_file_name output file names
119 : !> \param spreads_file_name output file names
120 : ! **************************************************************************************************
121 : TYPE localized_wfn_control_type
122 : INTEGER :: ref_count = -1
123 : INTEGER :: min_or_max = -1
124 : INTEGER :: localization_method = -1
125 : INTEGER :: operator_type = -1
126 : INTEGER, DIMENSION(2) :: nloc_states = -1, nguess = -1
127 : INTEGER :: set_of_states = -1
128 : INTEGER, DIMENSION(2, 2) :: lu_bound_states = -1
129 : INTEGER :: max_iter = -1
130 : INTEGER :: out_each = -1
131 : INTEGER :: nextra = -1
132 : INTEGER :: coeff_po_guess = -1, coeff_po_guess_mo_space = -1
133 : REAL(KIND=dp) :: eps_localization = -1.0_dp
134 : REAL(KIND=dp) :: max_crazy_angle = -1.0_dp
135 : REAL(KIND=dp) :: crazy_scale = -1.0_dp
136 : REAL(KIND=dp) :: eps_occ = -1.0_dp
137 : REAL(KIND=dp), DIMENSION(2) :: lu_ene_bound = -1.0_dp
138 : LOGICAL :: crazy_use_diag = .FALSE.
139 : LOGICAL :: print_cubes = .FALSE., jacobi_fallback = .FALSE., jacobi_refinement = .FALSE.
140 : LOGICAL :: print_centers = .FALSE.
141 : LOGICAL :: print_spreads = .FALSE.
142 : LOGICAL :: do_homo = .FALSE.
143 : LOGICAL :: do_mixed = .FALSE., do_cg_po = .FALSE.
144 : LOGICAL :: loc_restart = .FALSE.
145 : LOGICAL :: use_history = .FALSE.
146 : INTEGER, POINTER, DIMENSION(:, :) :: loc_states => NULL()
147 : TYPE(cp_2d_r_p_type), DIMENSION(2) :: centers_set = cp_2d_r_p_type()
148 : END TYPE localized_wfn_control_type
149 :
150 : ! *** Public ***
151 : PUBLIC :: qs_loc_env_create, qs_loc_env_release, &
152 : get_qs_loc_env, set_qs_loc_env, &
153 : localized_wfn_control_create, localized_wfn_control_release
154 : PUBLIC :: qs_loc_env_type, localized_wfn_control_type
155 :
156 : CONTAINS
157 :
158 : ! **************************************************************************************************
159 : !> \brief ...
160 : !> \param qs_loc_env ...
161 : !> \par History
162 : !> 04-05 created
163 : !> \author MI
164 : ! **************************************************************************************************
165 3248 : SUBROUTINE qs_loc_env_create(qs_loc_env)
166 :
167 : TYPE(qs_loc_env_type), INTENT(OUT) :: qs_loc_env
168 :
169 464 : qs_loc_env%tag_mo = ""
170 : NULLIFY (qs_loc_env%para_env)
171 : NULLIFY (qs_loc_env%cell)
172 : NULLIFY (qs_loc_env%op_sm_set)
173 : NULLIFY (qs_loc_env%op_fm_set)
174 : NULLIFY (qs_loc_env%local_molecules)
175 : NULLIFY (qs_loc_env%moloc_coeff)
176 : NULLIFY (qs_loc_env%particle_set)
177 : NULLIFY (qs_loc_env%localized_wfn_control)
178 3248 : qs_loc_env%weights = 0.0_dp
179 :
180 464 : END SUBROUTINE qs_loc_env_create
181 :
182 : !****f* qs_loc_types/qs_loc_env_release [1.0] *
183 :
184 : ! **************************************************************************************************
185 : !> \brief ...
186 : !> \param qs_loc_env ...
187 : !> \par History
188 : !> 04-05 created
189 : !> \author MI
190 : ! **************************************************************************************************
191 464 : SUBROUTINE qs_loc_env_release(qs_loc_env)
192 :
193 : TYPE(qs_loc_env_type), INTENT(INOUT) :: qs_loc_env
194 :
195 : INTEGER :: i, ii, j
196 :
197 464 : IF (ASSOCIATED(qs_loc_env%cell)) CALL cell_release(qs_loc_env%cell)
198 464 : IF (ASSOCIATED(qs_loc_env%local_molecules)) &
199 432 : CALL distribution_1d_release(qs_loc_env%local_molecules)
200 464 : IF (ASSOCIATED(qs_loc_env%localized_wfn_control)) THEN
201 464 : CALL localized_wfn_control_release(qs_loc_env%localized_wfn_control)
202 : END IF
203 464 : IF (ASSOCIATED(qs_loc_env%para_env)) CALL mp_para_env_release(qs_loc_env%para_env)
204 464 : IF (ASSOCIATED(qs_loc_env%particle_set)) NULLIFY (qs_loc_env%particle_set)
205 :
206 464 : IF (ASSOCIATED(qs_loc_env%moloc_coeff)) THEN
207 976 : DO i = 1, SIZE(qs_loc_env%moloc_coeff, 1)
208 544 : ii = LBOUND(qs_loc_env%moloc_coeff, 1) + i - 1
209 976 : CALL cp_fm_release(qs_loc_env%moloc_coeff(ii))
210 : END DO
211 432 : DEALLOCATE (qs_loc_env%moloc_coeff)
212 : END IF
213 :
214 464 : CALL cp_fm_release(qs_loc_env%op_fm_set)
215 :
216 464 : IF (ASSOCIATED(qs_loc_env%op_sm_set)) THEN
217 1764 : DO i = 1, SIZE(qs_loc_env%op_sm_set, 2)
218 4428 : DO j = 1, SIZE(qs_loc_env%op_sm_set, 1)
219 3996 : CALL dbcsr_deallocate_matrix(qs_loc_env%op_sm_set(j, i)%matrix)
220 : END DO
221 : END DO
222 432 : DEALLOCATE (qs_loc_env%op_sm_set)
223 : END IF
224 :
225 464 : END SUBROUTINE qs_loc_env_release
226 :
227 : ! **************************************************************************************************
228 : !> \brief create the localized_wfn_control_type
229 : !> \param localized_wfn_control ...
230 : !> \par History
231 : !> 04.2005 created [MI]
232 : ! **************************************************************************************************
233 464 : SUBROUTINE localized_wfn_control_create(localized_wfn_control)
234 : TYPE(localized_wfn_control_type), POINTER :: localized_wfn_control
235 :
236 464 : CPASSERT(.NOT. ASSOCIATED(localized_wfn_control))
237 9280 : ALLOCATE (localized_wfn_control)
238 :
239 464 : localized_wfn_control%ref_count = 1
240 1392 : localized_wfn_control%nloc_states = 0
241 464 : localized_wfn_control%nextra = 0
242 1392 : localized_wfn_control%nguess = 0
243 3248 : localized_wfn_control%lu_bound_states = 0
244 1392 : localized_wfn_control%lu_ene_bound = 0.0_dp
245 464 : localized_wfn_control%print_cubes = .FALSE.
246 464 : localized_wfn_control%print_centers = .FALSE.
247 464 : localized_wfn_control%print_spreads = .FALSE.
248 464 : localized_wfn_control%do_homo = .TRUE.
249 464 : localized_wfn_control%use_history = .FALSE.
250 464 : NULLIFY (localized_wfn_control%loc_states)
251 464 : NULLIFY (localized_wfn_control%centers_set(1)%array)
252 464 : NULLIFY (localized_wfn_control%centers_set(2)%array)
253 464 : END SUBROUTINE localized_wfn_control_create
254 :
255 : ! **************************************************************************************************
256 : !> \brief release the localized_wfn_control_type
257 : !> \param localized_wfn_control ...
258 : !> \par History
259 : !> 04.2005 created [MI]
260 : ! **************************************************************************************************
261 1664 : SUBROUTINE localized_wfn_control_release(localized_wfn_control)
262 :
263 : TYPE(localized_wfn_control_type), POINTER :: localized_wfn_control
264 :
265 1664 : IF (ASSOCIATED(localized_wfn_control)) THEN
266 1280 : CPASSERT(localized_wfn_control%ref_count > 0)
267 1280 : localized_wfn_control%ref_count = localized_wfn_control%ref_count - 1
268 1280 : IF (localized_wfn_control%ref_count == 0) THEN
269 464 : IF (ASSOCIATED(localized_wfn_control%loc_states)) THEN
270 400 : DEALLOCATE (localized_wfn_control%loc_states)
271 : END IF
272 464 : IF (ASSOCIATED(localized_wfn_control%centers_set(1)%array)) THEN
273 432 : DEALLOCATE (localized_wfn_control%centers_set(1)%array)
274 : END IF
275 464 : IF (ASSOCIATED(localized_wfn_control%centers_set(2)%array)) THEN
276 154 : DEALLOCATE (localized_wfn_control%centers_set(2)%array)
277 : END IF
278 464 : localized_wfn_control%ref_count = 0
279 464 : DEALLOCATE (localized_wfn_control)
280 : END IF
281 : END IF
282 1664 : END SUBROUTINE localized_wfn_control_release
283 :
284 : ! **************************************************************************************************
285 : !> \brief retain the localized_wfn_control_type
286 : !> \param localized_wfn_control ...
287 : !> \par History
288 : !> 04.2005 created [MI]
289 : ! **************************************************************************************************
290 816 : SUBROUTINE localized_wfn_control_retain(localized_wfn_control)
291 : TYPE(localized_wfn_control_type), POINTER :: localized_wfn_control
292 :
293 816 : CPASSERT(ASSOCIATED(localized_wfn_control))
294 :
295 816 : localized_wfn_control%ref_count = localized_wfn_control%ref_count + 1
296 816 : END SUBROUTINE localized_wfn_control_retain
297 :
298 : ! **************************************************************************************************
299 : !> \brief ...
300 : !> \param qs_loc_env ...
301 : !> \param cell ...
302 : !> \param local_molecules ...
303 : !> \param localized_wfn_control ...
304 : !> \param moloc_coeff ...
305 : !> \param op_sm_set ...
306 : !> \param op_fm_set ...
307 : !> \param para_env ...
308 : !> \param particle_set ...
309 : !> \param weights ...
310 : !> \param dim_op ...
311 : !> \par History
312 : !> 04-05 created
313 : !> \author MI
314 : ! **************************************************************************************************
315 2006 : SUBROUTINE get_qs_loc_env(qs_loc_env, cell, local_molecules, localized_wfn_control, &
316 : moloc_coeff, op_sm_set, op_fm_set, para_env, particle_set, weights, dim_op)
317 :
318 : TYPE(qs_loc_env_type), INTENT(IN) :: qs_loc_env
319 : TYPE(cell_type), OPTIONAL, POINTER :: cell
320 : TYPE(distribution_1d_type), OPTIONAL, POINTER :: local_molecules
321 : TYPE(localized_wfn_control_type), OPTIONAL, &
322 : POINTER :: localized_wfn_control
323 : TYPE(cp_fm_type), DIMENSION(:), OPTIONAL, POINTER :: moloc_coeff
324 : TYPE(dbcsr_p_type), DIMENSION(:, :), OPTIONAL, &
325 : POINTER :: op_sm_set
326 : TYPE(cp_fm_type), DIMENSION(:, :), OPTIONAL, &
327 : POINTER :: op_fm_set
328 : TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
329 : TYPE(particle_type), DIMENSION(:), OPTIONAL, &
330 : POINTER :: particle_set
331 : REAL(dp), DIMENSION(6), OPTIONAL :: weights
332 : INTEGER, OPTIONAL :: dim_op
333 :
334 2006 : IF (PRESENT(cell)) cell => qs_loc_env%cell
335 2006 : IF (PRESENT(moloc_coeff)) moloc_coeff => qs_loc_env%moloc_coeff
336 2006 : IF (PRESENT(local_molecules)) local_molecules => qs_loc_env%local_molecules
337 2006 : IF (PRESENT(localized_wfn_control)) &
338 1494 : localized_wfn_control => qs_loc_env%localized_wfn_control
339 2006 : IF (PRESENT(op_sm_set)) op_sm_set => qs_loc_env%op_sm_set
340 2006 : IF (PRESENT(op_fm_set)) op_fm_set => qs_loc_env%op_fm_set
341 2006 : IF (PRESENT(para_env)) para_env => qs_loc_env%para_env
342 2006 : IF (PRESENT(particle_set)) particle_set => qs_loc_env%particle_set
343 5772 : IF (PRESENT(weights)) weights(1:6) = qs_loc_env%weights(1:6)
344 2006 : IF (PRESENT(dim_op)) dim_op = qs_loc_env%dim_op
345 :
346 2006 : END SUBROUTINE get_qs_loc_env
347 :
348 : ! **************************************************************************************************
349 : !> \brief ...
350 : !> \param qs_loc_env ...
351 : !> \param cell ...
352 : !> \param local_molecules ...
353 : !> \param localized_wfn_control ...
354 : !> \param moloc_coeff ...
355 : !> \param op_sm_set ...
356 : !> \param op_fm_set ...
357 : !> \param para_env ...
358 : !> \param particle_set ...
359 : !> \param weights ...
360 : !> \param dim_op ...
361 : !> \par History
362 : !> 04-05 created
363 : !> \author MI
364 : ! **************************************************************************************************
365 1248 : SUBROUTINE set_qs_loc_env(qs_loc_env, cell, local_molecules, localized_wfn_control, &
366 : moloc_coeff, op_sm_set, op_fm_set, para_env, particle_set, weights, dim_op)
367 :
368 : TYPE(qs_loc_env_type), INTENT(INOUT) :: qs_loc_env
369 : TYPE(cell_type), OPTIONAL, POINTER :: cell
370 : TYPE(distribution_1d_type), OPTIONAL, POINTER :: local_molecules
371 : TYPE(localized_wfn_control_type), OPTIONAL, &
372 : POINTER :: localized_wfn_control
373 : TYPE(cp_fm_type), DIMENSION(:), OPTIONAL, POINTER :: moloc_coeff
374 : TYPE(dbcsr_p_type), DIMENSION(:, :), OPTIONAL, &
375 : POINTER :: op_sm_set
376 : TYPE(cp_fm_type), DIMENSION(:, :), OPTIONAL, &
377 : POINTER :: op_fm_set
378 : TYPE(mp_para_env_type), OPTIONAL, POINTER :: para_env
379 : TYPE(particle_type), DIMENSION(:), OPTIONAL, &
380 : POINTER :: particle_set
381 : REAL(dp), DIMENSION(6), OPTIONAL :: weights
382 : INTEGER, OPTIONAL :: dim_op
383 :
384 1248 : IF (PRESENT(cell)) THEN
385 432 : CALL cell_retain(cell)
386 432 : CALL cell_release(qs_loc_env%cell)
387 432 : qs_loc_env%cell => cell
388 : END IF
389 :
390 1248 : IF (PRESENT(local_molecules)) THEN
391 432 : CALL distribution_1d_retain(local_molecules)
392 432 : IF (ASSOCIATED(qs_loc_env%local_molecules)) &
393 0 : CALL distribution_1d_release(qs_loc_env%local_molecules)
394 432 : qs_loc_env%local_molecules => local_molecules
395 : END IF
396 :
397 1248 : IF (PRESENT(localized_wfn_control)) THEN
398 816 : CALL localized_wfn_control_retain(localized_wfn_control)
399 816 : CALL localized_wfn_control_release(qs_loc_env%localized_wfn_control)
400 816 : qs_loc_env%localized_wfn_control => localized_wfn_control
401 : END IF
402 1248 : IF (PRESENT(para_env)) THEN
403 432 : CALL para_env%retain()
404 432 : CALL mp_para_env_release(qs_loc_env%para_env)
405 432 : qs_loc_env%para_env => para_env
406 : END IF
407 1248 : IF (PRESENT(particle_set)) qs_loc_env%particle_set => particle_set
408 1248 : IF (PRESENT(moloc_coeff)) THEN
409 432 : CALL cp_fm_release(qs_loc_env%moloc_coeff)
410 432 : qs_loc_env%moloc_coeff => moloc_coeff
411 : END IF
412 1248 : IF (PRESENT(op_sm_set)) THEN
413 0 : qs_loc_env%op_sm_set => op_sm_set
414 : END IF
415 1248 : IF (PRESENT(op_fm_set)) THEN
416 0 : qs_loc_env%op_fm_set => op_fm_set
417 : END IF
418 1248 : IF (PRESENT(weights)) THEN
419 0 : qs_loc_env%weights = weights
420 : END IF
421 1248 : IF (PRESENT(dim_op)) THEN
422 432 : qs_loc_env%dim_op = dim_op
423 : END IF
424 :
425 1248 : END SUBROUTINE set_qs_loc_env
426 :
427 0 : END MODULE qs_loc_types
428 :
|