(git:b279b6b)
qs_kernel_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 
9  USE admm_types, ONLY: admm_env_release,&
10  admm_type
12  admm_control_type
13  USE hfx_types, ONLY: hfx_release,&
14  hfx_type
15  USE input_section_types, ONLY: section_vals_type
16  USE kinds, ONLY: dp
17  USE lri_environment_types, ONLY: lri_density_type,&
18  lri_environment_type
19  USE qs_tddfpt2_stda_types, ONLY: stda_env_type
20  USE xc_derivative_set_types, ONLY: xc_derivative_set_type,&
22  USE xc_rho_cflags_types, ONLY: xc_rho_cflags_type
24  xc_rho_set_type
25 #include "./base/base_uses.f90"
26 
27  IMPLICIT NONE
28 
29  PRIVATE
30 
31  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_kernel_types'
32 
33  LOGICAL, PARAMETER, PRIVATE :: debug_this_module = .false.
34  ! number of first derivative components (3: d/dx, d/dy, d/dz)
35  INTEGER, PARAMETER, PRIVATE :: nderivs = 3
36  INTEGER, PARAMETER, PRIVATE :: maxspins = 2
37 
38  PUBLIC :: full_kernel_env_type, kernel_env_type
39  PUBLIC :: release_kernel_env
40 
41 ! **************************************************************************************************
42 !> \brief Collection of variables required to evaluate adiabatic TDDFPT kernel.
43 !> \par History
44 !> * 12.2016 created [Sergey Chulkov]
45 ! **************************************************************************************************
46  TYPE full_kernel_env_type
47  ! ground state electron density
48  TYPE(xc_rho_set_type), POINTER :: xc_rho_set => null()
49  ! response density
50  TYPE(xc_rho_set_type), POINTER :: xc_rho1_set => null()
51  !> first and second derivatives of exchange-correlation functional
52  TYPE(xc_derivative_set_type) :: xc_deriv_set
53  !> XC input section
54  LOGICAL :: do_exck
55  TYPE(section_vals_type), POINTER :: xc_section => null()
56  !> flags which indicate required components of the exchange-correlation functional
57  !> (density, gradient, etc)
58  TYPE(xc_rho_cflags_type) :: xc_rho1_cflags
59  !> the method used to compute position derivatives of densities and potentials
60  INTEGER :: deriv_method_id
61  !> the density smoothing method
62  INTEGER :: rho_smooth_id
63  !> scaling coefficients in the linear combination:
64  !> K = alpha * K_{\alpha,\alpha} + beta * K_{\alpha,\beta}
65  REAL(kind=dp) :: alpha, beta
66  !> flags for finite differences/analytic XC kernels
67  LOGICAL :: deriv2_analytic
68  LOGICAL :: deriv3_analytic
69  ! Local resolution of the identity for Coulomb
70  TYPE(lri_environment_type), POINTER :: lri_env => null()
71  TYPE(lri_density_type), POINTER :: lri_density => null()
72  ! Short range HFX integral environment
73  TYPE(hfx_type), DIMENSION(:, :), POINTER :: x_data => null()
74  TYPE(section_vals_type), POINTER :: hfxsr_section => null()
75  TYPE(admm_type), POINTER :: admm_env => null()
76  TYPE(admm_control_type), POINTER :: admm_control => null()
77  END TYPE full_kernel_env_type
78 ! **************************************************************************************************
79 !> \brief Type to hold environments for the different kernels
80 !> \par History
81 !> * 04.2019 created [JHU]
82 ! **************************************************************************************************
83  TYPE kernel_env_type
84  TYPE(full_kernel_env_type), POINTER :: full_kernel => null()
85  TYPE(full_kernel_env_type), POINTER :: admm_kernel => null()
86  TYPE(stda_env_type), POINTER :: stda_kernel => null()
87  END TYPE kernel_env_type
88 
89 CONTAINS
90 
91 ! **************************************************************************************************
92 !> \brief Release kernel environment.
93 !> \param kernel_env kernel environment (destroyed on exit)
94 !> \par History
95 !> * 02.2017 created [Sergey Chulkov]
96 ! **************************************************************************************************
97  SUBROUTINE release_kernel_env(kernel_env)
98  TYPE(full_kernel_env_type), POINTER :: kernel_env
99 
100  IF (ASSOCIATED(kernel_env)) THEN
101  IF (ASSOCIATED(kernel_env%xc_rho1_set)) THEN
102  CALL xc_rho_set_release(kernel_env%xc_rho1_set)
103  DEALLOCATE (kernel_env%xc_rho1_set)
104  END IF
105  CALL xc_dset_release(kernel_env%xc_deriv_set)
106  IF (ASSOCIATED(kernel_env%xc_rho_set)) THEN
107  CALL xc_rho_set_release(kernel_env%xc_rho_set)
108  DEALLOCATE (kernel_env%xc_rho_set)
109  END IF
110  IF (ASSOCIATED(kernel_env%x_data)) THEN
111  CALL hfx_release(kernel_env%x_data)
112  END IF
113  IF (ASSOCIATED(kernel_env%admm_env)) THEN
114  CALL admm_env_release(kernel_env%admm_env)
115  END IF
116  IF (ASSOCIATED(kernel_env%admm_control)) THEN
117  CALL admm_control_release(kernel_env%admm_control)
118  END IF
119  END IF
120 
121  END SUBROUTINE release_kernel_env
122 
123 END MODULE qs_kernel_types
Types and set/get functions for auxiliary density matrix methods.
Definition: admm_types.F:15
subroutine, public admm_env_release(admm_env)
releases the ADMM environment, cleans up all types
Definition: admm_types.F:426
Defines control structures, which contain the parameters and the settings for the DFT-based calculati...
subroutine, public admm_control_release(admm_control)
...
Types and set/get functions for HFX.
Definition: hfx_types.F:15
subroutine, public hfx_release(x_data)
This routine deallocates all data structures
Definition: hfx_types.F:1905
objects that represent the structure of input sections and the data contained in an input section
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
contains the types and subroutines for dealing with the lri_env lri : local resolution of the identit...
subroutine, public release_kernel_env(kernel_env)
Release kernel environment.
Simplified Tamm Dancoff approach (sTDA).
represent a group ofunctional derivatives
subroutine, public xc_dset_release(derivative_set)
releases a derivative set
contains the structure
contains the structure
subroutine, public xc_rho_set_release(rho_set, pw_pool)
releases the given rho_set