(git:badb799)
Loading...
Searching...
No Matches
qs_charges_types.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief container for information about total charges on the grids
10!> \par History
11!> 10.2002 created [fawzi]
12!> \author Fawzi Mohamed
13! **************************************************************************************************
15
16 USE kinds, ONLY: dp
17#include "./base/base_uses.f90"
18
19 IMPLICIT NONE
20 PRIVATE
21
22 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
23 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_charges_types'
24
25 PUBLIC :: qs_charges_type
27!***
28
29! **************************************************************************************************
30!> \brief Container for information about total charges on the grids
31!> \param total_rho_core_rspace total charge on the rho_core grid
32!> \param total_rho_rspace total charge in the real space
33!> \param total_rho_gspace total charge in the g space
34!> \note
35!> this type is losing the reason to exist...
36!> \par History
37!> 10.2002 created [fawzi]
38!> 11.2002 moved total_rho_elec_rspace to qs_rho_type
39!> \author Fawzi Mohamed
40! **************************************************************************************************
42 REAL(kind=dp) :: total_rho_core_rspace = -1.0_dp, total_rho_gspace = -1.0_dp
43 REAL(kind=dp) :: total_rho0_soft_rspace = -1.0_dp, total_rho0_hard_lebedev = -1.0_dp
44 REAL(kind=dp) :: total_rho_soft_gspace = -1.0_dp
45 REAL(kind=dp), DIMENSION(:), POINTER :: total_rho1_hard => null(), &
46 total_rho1_soft => null()
47 REAL(kind=dp) :: total_rho1_hard_nuc = -1.0_dp
48 REAL(kind=dp) :: total_rho1_soft_nuc_rspace = -1.0_dp
49 REAL(kind=dp) :: total_rho1_soft_nuc_lebedev = -1.0_dp
50 REAL(kind=dp) :: background = -1.0_dp
51 END TYPE qs_charges_type
52
53CONTAINS
54
55! **************************************************************************************************
56!> \brief creates a charges object
57!> \param qs_charges the charges object to create
58!> \param nspins ...
59!> \param total_rho_core_rspace ...
60!> \param total_rho_gspace ...
61!> \par History
62!> 10.2002 created [fawzi]
63!> \author Fawzi Mohamed
64! **************************************************************************************************
65 SUBROUTINE qs_charges_create(qs_charges, nspins, total_rho_core_rspace, &
66 total_rho_gspace)
67 TYPE(qs_charges_type), INTENT(OUT) :: qs_charges
68 INTEGER, INTENT(in) :: nspins
69 REAL(kind=dp), INTENT(in), OPTIONAL :: total_rho_core_rspace, total_rho_gspace
70
71 qs_charges%total_rho_core_rspace = 0.0_dp
72 IF (PRESENT(total_rho_core_rspace)) &
73 qs_charges%total_rho_core_rspace = total_rho_core_rspace
74 qs_charges%total_rho_gspace = 0.0_dp
75 IF (PRESENT(total_rho_gspace)) &
76 qs_charges%total_rho_gspace = total_rho_gspace
77 qs_charges%total_rho_soft_gspace = 0.0_dp
78 qs_charges%total_rho0_hard_lebedev = 0.0_dp
79 qs_charges%total_rho_soft_gspace = 0.0_dp
80 qs_charges%background = 0.0_dp
81 ALLOCATE (qs_charges%total_rho1_hard(nspins))
82 qs_charges%total_rho1_hard(:) = 0.0_dp
83 ALLOCATE (qs_charges%total_rho1_soft(nspins))
84 qs_charges%total_rho1_soft(:) = 0.0_dp
85 qs_charges%total_rho1_hard_nuc = 0.0_dp
86 qs_charges%total_rho1_soft_nuc_rspace = 0.0_dp
87 qs_charges%total_rho1_soft_nuc_lebedev = 0.0_dp
88 END SUBROUTINE qs_charges_create
89
90! **************************************************************************************************
91!> \brief releases the charges object (see cp2k/doc/ReferenceCounting.html)
92!> \param qs_charges the object to be released
93!> \par History
94!> 10.2002 created [fawzi]
95!> \author Fawzi Mohamed
96! **************************************************************************************************
97 SUBROUTINE qs_charges_release(qs_charges)
98 TYPE(qs_charges_type), INTENT(INOUT) :: qs_charges
99
100 DEALLOCATE (qs_charges%total_rho1_hard)
101 DEALLOCATE (qs_charges%total_rho1_soft)
102
103 END SUBROUTINE qs_charges_release
104
105END MODULE qs_charges_types
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
container for information about total charges on the grids
subroutine, public qs_charges_release(qs_charges)
releases the charges object (see cp2k/doc/ReferenceCounting.html)
subroutine, public qs_charges_create(qs_charges, nspins, total_rho_core_rspace, total_rho_gspace)
creates a charges object
Container for information about total charges on the grids.