32#include "./base/base_uses.f90"
64 TYPE becke_vector_buffer
65 LOGICAL :: store_vectors = .false.
66 REAL(kind=
dp),
ALLOCATABLE, &
67 DIMENSION(:) :: distances
68 REAL(kind=
dp),
ALLOCATABLE, &
69 DIMENSION(:, :) :: distance_vecs, &
72 REAL(kind=
dp),
ALLOCATABLE, &
73 DIMENSION(:, :, :) :: pair_dist_vecs
74 END TYPE becke_vector_buffer
77 INTEGER :: cavity_shape = -1, cutoff_type = -1, &
78 confine_bounds(2) = -1
79 LOGICAL :: in_memory = .false., &
80 adjust = .false., cavity_confine = .false., &
81 should_skip = .false., print_cavity = .false., &
83 REAL(kind=
dp) :: rglobal = -1.0_dp, &
84 rcavity = -1.0_dp, eps_cavity = -1.0_dp
85 REAL(kind=
dp),
DIMENSION(:),
POINTER :: cutoffs => null(), cutoffs_tmp => null(), &
86 radii_tmp => null(), radii => null()
87 REAL(kind=
dp),
POINTER, &
88 DIMENSION(:, :) :: aij => null()
89 REAL(kind=
dp),
POINTER, &
90 DIMENSION(:, :, :) :: cavity_mat => null()
91 TYPE(becke_vector_buffer) :: vector_buffer = becke_vector_buffer()
111 INTEGER :: gaussian_shape = -1, shape_function = -1, atoms_memory = -1
112 LOGICAL :: use_bohr = .false., print_density = .false., use_atomic_cutoff = .false.
113 REAL(kind=
dp) :: radius = -1.0_dp, eps_cutoff = -1.0_dp, atomic_cutoff = -1.0_dp
114 REAL(kind=
dp),
DIMENSION(:),
POINTER :: radii => null()
188 INTEGER,
POINTER,
DIMENSION(:) :: atoms => null()
190 INTEGER :: constraint_type = -1
192 LOGICAL :: is_fragment_constraint = .false.
195 REAL(kind=
dp),
ALLOCATABLE, &
196 DIMENSION(:, :) :: d_sum_const_dr
198 REAL(kind=
dp),
POINTER,
DIMENSION(:) :: coeff => null()
200 REAL(kind=
dp),
POINTER, &
201 DIMENSION(:, :) :: integrated => null()
203 REAL(kind=
dp),
POINTER, &
204 DIMENSION(:, :, :, :) :: gradients => null()
205 REAL(kind=
dp),
POINTER, &
206 DIMENSION(:, :, :, :) :: gradients_x => null()
207 REAL(kind=
dp),
POINTER, &
208 DIMENSION(:, :, :, :) :: gradients_y => null()
209 REAL(kind=
dp),
POINTER, &
210 DIMENSION(:, :, :, :) :: gradients_z => null()
220 CHARACTER(LEN=default_path_length) :: fragment_a_fname =
"", &
221 fragment_b_fname =
"", &
222 fragment_a_spin_fname =
"", &
223 fragment_b_spin_fname =
""
224 INTEGER :: ref_count = -1, total_steps = -1,
TYPE = -1, &
225 precond_freq = -1, nreused = -1, max_reuse = -1, &
226 purge_freq = -1, nbad_conv = -1, purge_offset = -1, &
227 istep = -1, ienergy = -1, natoms = -1
228 INTEGER,
POINTER,
DIMENSION(:) :: atoms => null()
229 LOGICAL :: need_pot = .false., save_pot = .false., do_et = .false., &
230 reuse_precond = .false., purge_history = .false., &
231 should_purge = .false., calculate_metric = .false., &
233 fragments_integrated = .false., flip_fragment(2) = .false., &
234 transfer_pot = .false., external_control = .false., &
235 first_iteration = .false., print_weight = .false., in_memory = .false.
236 LOGICAL,
POINTER,
DIMENSION(:) :: is_constraint => null()
237 REAL(kind=
dp),
DIMENSION(:),
POINTER :: strength => null(),
TARGET => null(),
value => null()
238 REAL(kind=
dp),
POINTER, &
239 DIMENSION(:, :) :: charges_fragment => null()
242 DIMENSION(:) :: group => null()
244 DIMENSION(:) :: occupations
246 POINTER :: mo_coeff => null()
249 POINTER :: wmat => null(), matrix_p => null()
251 POINTER :: hirshfeld_control => null()
254 DIMENSION(:) :: charge => null()
256 DIMENSION(:, :) :: fragments => null()
261 CHARACTER(len=*),
PARAMETER,
PRIVATE :: modulen =
'qs_cdft_types'
283 SUBROUTINE becke_control_create(becke_control)
286 becke_control%adjust = .false.
288 becke_control%cavity_confine = .false.
289 becke_control%should_skip = .false.
290 becke_control%print_cavity = .false.
291 becke_control%in_memory = .false.
292 becke_control%use_bohr = .false.
293 becke_control%confine_bounds = 0
294 becke_control%rcavity = 3.0_dp
295 becke_control%rglobal = 6.0_dp
296 becke_control%eps_cavity = 1.0e-6_dp
298 becke_control%vector_buffer%store_vectors = .true.
299 NULLIFY (becke_control%aij)
300 NULLIFY (becke_control%cavity_mat)
301 NULLIFY (becke_control%cavity_env)
302 NULLIFY (becke_control%cutoffs)
303 NULLIFY (becke_control%cutoffs_tmp)
304 NULLIFY (becke_control%radii)
305 NULLIFY (becke_control%radii_tmp)
306 END SUBROUTINE becke_control_create
314 SUBROUTINE becke_control_release(becke_control)
317 IF (becke_control%vector_buffer%store_vectors)
THEN
318 IF (
ALLOCATED(becke_control%vector_buffer%distances)) &
319 DEALLOCATE (becke_control%vector_buffer%distances)
320 IF (
ALLOCATED(becke_control%vector_buffer%distance_vecs)) &
321 DEALLOCATE (becke_control%vector_buffer%distance_vecs)
322 IF (
ALLOCATED(becke_control%vector_buffer%position_vecs)) &
323 DEALLOCATE (becke_control%vector_buffer%position_vecs)
324 IF (
ALLOCATED(becke_control%vector_buffer%R12)) &
325 DEALLOCATE (becke_control%vector_buffer%R12)
326 IF (
ALLOCATED(becke_control%vector_buffer%pair_dist_vecs)) &
327 DEALLOCATE (becke_control%vector_buffer%pair_dist_vecs)
329 IF (
ASSOCIATED(becke_control%cutoffs)) &
330 DEALLOCATE (becke_control%cutoffs)
331 IF (
ASSOCIATED(becke_control%cutoffs_tmp)) &
332 DEALLOCATE (becke_control%cutoffs_tmp)
333 IF (
ASSOCIATED(becke_control%radii_tmp)) &
334 DEALLOCATE (becke_control%radii_tmp)
335 IF (
ASSOCIATED(becke_control%radii)) &
336 DEALLOCATE (becke_control%radii)
337 IF (
ASSOCIATED(becke_control%aij)) &
338 DEALLOCATE (becke_control%aij)
339 IF (
ASSOCIATED(becke_control%cavity_mat)) &
340 DEALLOCATE (becke_control%cavity_mat)
341 IF (becke_control%cavity_confine) &
344 END SUBROUTINE becke_control_release
355 cdft_control%total_steps = 0
356 NULLIFY (cdft_control%strength)
357 NULLIFY (cdft_control%target)
358 NULLIFY (cdft_control%value)
359 NULLIFY (cdft_control%atoms)
360 NULLIFY (cdft_control%is_constraint)
361 NULLIFY (cdft_control%charges_fragment)
362 NULLIFY (cdft_control%fragments)
363 NULLIFY (cdft_control%group)
364 NULLIFY (cdft_control%charge)
365 cdft_control%natoms = 0
367 cdft_control%need_pot = .true.
368 cdft_control%save_pot = .false.
369 cdft_control%transfer_pot = .false.
370 cdft_control%atomic_charges = .false.
371 cdft_control%first_iteration = .true.
372 cdft_control%fragment_density = .false.
373 cdft_control%fragments_integrated = .false.
374 cdft_control%flip_fragment = .false.
375 cdft_control%external_control = .false.
376 cdft_control%do_et = .false.
377 cdft_control%reuse_precond = .false.
378 cdft_control%nreused = 0
379 cdft_control%precond_freq = 0
380 cdft_control%max_reuse = 0
381 cdft_control%should_purge = .false.
382 cdft_control%purge_history = .false.
383 cdft_control%calculate_metric = .false.
384 cdft_control%in_memory = .false.
385 cdft_control%purge_freq = 0
386 cdft_control%nbad_conv = 0
387 cdft_control%purge_offset = 0
388 cdft_control%istep = 0
389 cdft_control%ienergy = 0
390 NULLIFY (cdft_control%becke_control)
391 ALLOCATE (cdft_control%becke_control)
392 CALL becke_control_create(cdft_control%becke_control)
393 NULLIFY (cdft_control%hirshfeld_control)
394 ALLOCATE (cdft_control%hirshfeld_control)
395 CALL hirshfeld_control_create(cdft_control%hirshfeld_control)
396 NULLIFY (cdft_control%wmat)
397 NULLIFY (cdft_control%matrix_s%matrix)
398 NULLIFY (cdft_control%mo_coeff)
399 NULLIFY (cdft_control%matrix_p)
401 cdft_control%ot_control%have_scf = .false.
402 cdft_control%ot_control%max_scf = 0
403 cdft_control%ot_control%eps_scf = 0.0_dp
404 cdft_control%ot_control%step_size = 0.0_dp
405 cdft_control%ot_control%type = -1
406 cdft_control%ot_control%optimizer = -1
407 cdft_control%ot_control%diis_buffer_length = -1
408 NULLIFY (cdft_control%ot_control%cdft_opt_control)
409 cdft_control%constraint_control%have_scf = .false.
410 cdft_control%constraint_control%max_scf = 0
411 cdft_control%constraint_control%eps_scf = 0.0_dp
412 cdft_control%constraint_control%step_size = 0.0_dp
413 cdft_control%constraint_control%type = -1
414 cdft_control%constraint_control%optimizer = -1
415 cdft_control%constraint_control%diis_buffer_length = -1
416 NULLIFY (cdft_control%constraint_control%cdft_opt_control)
417 cdft_control%constraint%iter_count = 0
418 NULLIFY (cdft_control%constraint%variables)
419 NULLIFY (cdft_control%constraint%gradient)
420 NULLIFY (cdft_control%constraint%energy)
421 NULLIFY (cdft_control%constraint%count)
422 NULLIFY (cdft_control%constraint%inv_jacobian)
423 cdft_control%constraint%deallocate_jacobian = .true.
438 IF (
ASSOCIATED(cdft_control%atoms)) &
439 DEALLOCATE (cdft_control%atoms)
440 IF (
ASSOCIATED(cdft_control%strength)) &
441 DEALLOCATE (cdft_control%strength)
442 IF (
ASSOCIATED(cdft_control%target)) &
443 DEALLOCATE (cdft_control%target)
444 IF (
ASSOCIATED(cdft_control%value)) &
445 DEALLOCATE (cdft_control%value)
446 IF (
ASSOCIATED(cdft_control%charges_fragment)) &
447 DEALLOCATE (cdft_control%charges_fragment)
448 IF (
ASSOCIATED(cdft_control%fragments)) &
449 DEALLOCATE (cdft_control%fragments)
450 IF (
ASSOCIATED(cdft_control%is_constraint)) &
451 DEALLOCATE (cdft_control%is_constraint)
452 IF (
ASSOCIATED(cdft_control%charge)) &
453 DEALLOCATE (cdft_control%charge)
455 IF (
ASSOCIATED(cdft_control%group))
THEN
456 DO i = 1,
SIZE(cdft_control%group)
457 IF (
ASSOCIATED(cdft_control%group(i)%atoms)) &
458 DEALLOCATE (cdft_control%group(i)%atoms)
459 IF (
ASSOCIATED(cdft_control%group(i)%coeff)) &
460 DEALLOCATE (cdft_control%group(i)%coeff)
461 IF (
ALLOCATED(cdft_control%group(i)%d_sum_const_dR)) &
462 DEALLOCATE (cdft_control%group(i)%d_sum_const_dR)
464 IF (
ASSOCIATED(cdft_control%group(i)%gradients)) &
465 DEALLOCATE (cdft_control%group(i)%gradients)
467 IF (
ASSOCIATED(cdft_control%group(i)%gradients_x)) &
468 DEALLOCATE (cdft_control%group(i)%gradients_x)
469 IF (
ASSOCIATED(cdft_control%group(i)%gradients_y)) &
470 DEALLOCATE (cdft_control%group(i)%gradients_y)
471 IF (
ASSOCIATED(cdft_control%group(i)%gradients_z)) &
472 DEALLOCATE (cdft_control%group(i)%gradients_z)
474 IF (
ASSOCIATED(cdft_control%group(i)%integrated)) &
475 DEALLOCATE (cdft_control%group(i)%integrated)
477 DEALLOCATE (cdft_control%group)
480 IF (
ASSOCIATED(cdft_control%becke_control))
THEN
481 CALL becke_control_release(cdft_control%becke_control)
482 DEALLOCATE (cdft_control%becke_control)
484 IF (
ASSOCIATED(cdft_control%hirshfeld_control))
THEN
485 CALL hirshfeld_control_release(cdft_control%hirshfeld_control)
486 DEALLOCATE (cdft_control%hirshfeld_control)
491 IF (
ASSOCIATED(cdft_control%constraint%variables)) &
492 DEALLOCATE (cdft_control%constraint%variables)
493 IF (
ASSOCIATED(cdft_control%constraint%count)) &
494 DEALLOCATE (cdft_control%constraint%count)
495 IF (
ASSOCIATED(cdft_control%constraint%gradient)) &
496 DEALLOCATE (cdft_control%constraint%gradient)
497 IF (
ASSOCIATED(cdft_control%constraint%energy)) &
498 DEALLOCATE (cdft_control%constraint%energy)
499 IF (
ASSOCIATED(cdft_control%constraint%inv_jacobian)) &
500 DEALLOCATE (cdft_control%constraint%inv_jacobian)
502 IF (
ALLOCATED(cdft_control%occupations))
THEN
503 DO i = 1,
SIZE(cdft_control%occupations)
504 IF (
ASSOCIATED(cdft_control%occupations(i)%array)) &
505 DEALLOCATE (cdft_control%occupations(i)%array)
507 DEALLOCATE (cdft_control%occupations)
520 SUBROUTINE hirshfeld_control_create(hirshfeld_control)
523 hirshfeld_control%use_bohr = .false.
524 hirshfeld_control%print_density = .false.
525 hirshfeld_control%use_atomic_cutoff = .true.
526 hirshfeld_control%radius = 3.0_dp
527 hirshfeld_control%eps_cutoff = 1.0e-12_dp
528 hirshfeld_control%atomic_cutoff = 1.0e-12_dp
530 hirshfeld_control%atoms_memory = 80
532 NULLIFY (hirshfeld_control%hirshfeld_env)
533 NULLIFY (hirshfeld_control%radii)
535 END SUBROUTINE hirshfeld_control_create
543 SUBROUTINE hirshfeld_control_release(hirshfeld_control)
546 IF (
ASSOCIATED(hirshfeld_control%radii)) &
547 DEALLOCATE (hirshfeld_control%radii)
550 END SUBROUTINE hirshfeld_control_release
simple routine to print charges for all atomic charge methods (currently mulliken,...
various utilities that regard array of different kinds: output, allocation,... maybe it is not a good...
represent a full matrix distributed on many processors
The types needed for the calculation of Hirshfeld charges and related functions.
subroutine, public release_hirshfeld_type(hirshfeld_env)
...
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_path_length
parameters that control the outer loop of an SCF iteration
Control parameters for optimizers that work with CDFT constraints.
subroutine, public cdft_opt_type_release(cdft_opt_control)
releases the CDFT optimizer control object
Defines CDFT control structures.
subroutine, public cdft_control_release(cdft_control)
release the cdft_control_type
subroutine, public cdft_control_create(cdft_control)
create the cdft_control_type
represent a pointer to a 1d array
quantities needed for a Hirshfeld based partitioning of real space
contains the parameters needed by a scf run
control parameters for CDFT simulations