(git:b279b6b)
qs_ks_qmmm_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 !> \par History
10 !> 05.2004 [tlaino]
11 !> \author Teodoro Laino
12 ! **************************************************************************************************
15  USE cube_utils, ONLY: cube_info_type,&
17  USE dbcsr_api, ONLY: dbcsr_p_type
18  USE kinds, ONLY: dp
19  USE pw_env_types, ONLY: pw_env_get,&
21  pw_env_type
22  USE pw_pool_types, ONLY: pw_pool_type
23  USE pw_types, ONLY: pw_r3d_rs_type
24 #include "./base/base_uses.f90"
25 
26  IMPLICIT NONE
27  PRIVATE
28 
29  LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
30  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_ks_qmmm_types'
31 
32  PUBLIC :: qs_ks_qmmm_env_type
33  PUBLIC :: qs_ks_qmmm_release
34 
35 ! **************************************************************************************************
36 !> \brief calculation environment to calculate the ks_qmmm matrix,
37 !> holds the QM/MM potential and all the needed variables to
38 !> compute the QM/MM electrostatic 1-electron ks matrix
39 !> assumes that the core hamiltonian and energy are up to date.
40 !> v_metal_rspace is the potential at the metal sites within the image
41 !> charge approach
42 !> \par History
43 !> 05.2004 created [tlaino]
44 !> 01.2012 added v_metal_rspace [dgolze]
45 !> \author Teodoro Laino
46 ! **************************************************************************************************
47  TYPE qs_ks_qmmm_env_type
48  INTEGER :: n_evals
49  REAL(KIND=dp) :: pc_ener
50  TYPE(pw_env_type), POINTER :: pw_env
51  TYPE(pw_r3d_rs_type) :: v_qmmm_rspace
52  TYPE(pw_r3d_rs_type), POINTER :: v_metal_rspace
53  TYPE(cube_info_type), DIMENSION(:), POINTER :: cube_info
54  TYPE(dbcsr_p_type), DIMENSION(:), &
55  POINTER :: matrix_h
56  END TYPE qs_ks_qmmm_env_type
57 
58 CONTAINS
59 
60 ! **************************************************************************************************
61 !> \brief releases the ks_qmmm_env (see doc/ReferenceCounting.html)
62 !> \param ks_qmmm_env the ks_qmmm_env to be released
63 !> \par History
64 !> 05.2004 created [tlaino]
65 !> \author Teodoro Laino
66 ! **************************************************************************************************
67  SUBROUTINE qs_ks_qmmm_release(ks_qmmm_env)
68  TYPE(qs_ks_qmmm_env_type), INTENT(INOUT) :: ks_qmmm_env
69 
70  INTEGER :: i
71  TYPE(pw_pool_type), POINTER :: pool
72 
73  CALL pw_env_get(ks_qmmm_env%pw_env, auxbas_pw_pool=pool)
74  CALL pool%give_back_pw(ks_qmmm_env%v_qmmm_rspace)
75  CALL pw_env_release(ks_qmmm_env%pw_env)
76  IF (ASSOCIATED(ks_qmmm_env%cube_info)) THEN
77  DO i = 1, SIZE(ks_qmmm_env%cube_info)
78  CALL destroy_cube_info(ks_qmmm_env%cube_info(i))
79  END DO
80  DEALLOCATE (ks_qmmm_env%cube_info)
81  END IF
82  IF (ASSOCIATED(ks_qmmm_env%matrix_h)) THEN
83  CALL dbcsr_deallocate_matrix_set(ks_qmmm_env%matrix_h)
84  END IF
85 
86  END SUBROUTINE qs_ks_qmmm_release
87 
88 END MODULE qs_ks_qmmm_types
DBCSR operations in CP2K.
for a given dr()/dh(r) this will provide the bounds to be used if one wants to go over a sphere-subre...
Definition: cube_utils.F:18
subroutine, public destroy_cube_info(info)
...
Definition: cube_utils.F:185
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
container for various plainwaves related things
Definition: pw_env_types.F:14
subroutine, public pw_env_release(pw_env, para_env)
releases the given pw_env (see doc/ReferenceCounting.html)
Definition: pw_env_types.F:176
subroutine, public pw_env_get(pw_env, pw_pools, cube_info, gridlevel_info, auxbas_pw_pool, auxbas_grid, auxbas_rs_desc, auxbas_rs_grid, rs_descs, rs_grids, xc_pw_pool, vdw_pw_pool, poisson_env, interp_section)
returns the various attributes of the pw env
Definition: pw_env_types.F:113
Manages a pool of grids (to be used for example as tmp objects), but can also be used to instantiate ...
Definition: pw_pool_types.F:24
subroutine, public qs_ks_qmmm_release(ks_qmmm_env)
releases the ks_qmmm_env (see doc/ReferenceCounting.html)