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 Types needed for a for a Harris model calculation
10 : !> \par History
11 : !> 2024.07 created
12 : !> \author JGH
13 : ! **************************************************************************************************
14 : MODULE qs_harris_types
15 : USE atomic_kind_types, ONLY: atomic_kind_type,&
16 : get_atomic_kind_set
17 : USE basis_set_types, ONLY: get_gto_basis_set,&
18 : gto_basis_set_type
19 : USE distribution_1d_types, ONLY: distribution_1d_type
20 : USE kinds, ONLY: default_string_length,&
21 : dp
22 : USE pw_types, ONLY: pw_r3d_rs_type
23 : USE qs_kind_types, ONLY: get_qs_kind,&
24 : qs_kind_type
25 : #include "./base/base_uses.f90"
26 :
27 : IMPLICIT NONE
28 :
29 : PRIVATE
30 :
31 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_harris_types'
32 :
33 : ! *****************************************************************************
34 : TYPE rho_vec_type
35 : REAL(KIND=dp), ALLOCATABLE, DIMENSION(:, :) :: rvecs
36 : END TYPE rho_vec_type
37 :
38 : TYPE harris_rhoin_type
39 : CHARACTER(LEN=default_string_length) :: basis_type = "NDef"
40 : TYPE(rho_vec_type), ALLOCATABLE, DIMENSION(:, :) :: rhovec
41 : TYPE(rho_vec_type), ALLOCATABLE, DIMENSION(:, :) :: intvec
42 : INTEGER :: nspin = 0
43 : INTEGER :: nbas = 0
44 : INTEGER, ALLOCATABLE, DIMENSION(:, :) :: basptr
45 : LOGICAL :: frozen = .FALSE.
46 : END TYPE harris_rhoin_type
47 :
48 : TYPE harris_energy_type
49 : REAL(KIND=dp) :: eharris = 0.0_dp
50 : REAL(KIND=dp) :: eband = 0.0_dp
51 : REAL(KIND=dp) :: exc_correction = 0.0_dp
52 : REAL(KIND=dp) :: eh_correction = 0.0_dp
53 : REAL(KIND=dp) :: ewald_correction = 0.0_dp
54 : REAL(KIND=dp) :: dispersion = 0.0_dp
55 : END TYPE harris_energy_type
56 :
57 : ! *****************************************************************************
58 : !> \brief Contains information on the Harris method
59 : !> \par History
60 : !> 07.2024 created
61 : !> \author JGH
62 : ! *****************************************************************************
63 : TYPE harris_type
64 : INTEGER :: energy_functional = 0
65 : INTEGER :: density_source = 0
66 : INTEGER :: orbital_basis = 0
67 : !
68 : TYPE(harris_energy_type) :: energy
69 : !
70 : TYPE(harris_rhoin_type) :: rhoin
71 : !
72 : TYPE(pw_r3d_rs_type) :: vh_rspace = pw_r3d_rs_type()
73 : TYPE(pw_r3d_rs_type), DIMENSION(:), POINTER :: vxc_rspace => Null()
74 :
75 : !
76 : LOGICAL :: debug_forces = .FALSE.
77 : LOGICAL :: debug_stress = .FALSE.
78 : END TYPE harris_type
79 : ! **************************************************************************************************
80 :
81 : PUBLIC :: harris_type, harris_energy_type, harris_env_release, &
82 : harris_print_energy, harris_rhoin_type, harris_rhoin_init
83 :
84 : ! **************************************************************************************************
85 :
86 : CONTAINS
87 :
88 : ! **************************************************************************************************
89 :
90 : ! **************************************************************************************************
91 : !> \brief ...
92 : !> \param iounit ...
93 : !> \param energy ...
94 : ! **************************************************************************************************
95 30 : SUBROUTINE harris_print_energy(iounit, energy)
96 : INTEGER, INTENT(IN) :: iounit
97 : TYPE(harris_energy_type) :: energy
98 :
99 30 : IF (iounit > 0) THEN
100 15 : WRITE (UNIT=iounit, FMT="(/,(T2,A))") "HARRIS MODEL ENERGY INFORMATION"
101 : WRITE (UNIT=iounit, FMT="((T3,A,T56,F25.14))") &
102 15 : "Harris model energy: ", energy%eharris, &
103 15 : "Band energy: ", energy%eband, &
104 15 : "Hartree correction energy: ", energy%eh_correction, &
105 15 : "XC correction energy: ", energy%exc_correction, &
106 15 : "Ewald sum correction energy: ", energy%ewald_correction, &
107 30 : "Dispersion energy (pair potential): ", energy%dispersion
108 : END IF
109 :
110 30 : END SUBROUTINE harris_print_energy
111 :
112 : ! **************************************************************************************************
113 : !> \brief ...
114 : !> \param rhoin ...
115 : !> \param basis_type ...
116 : !> \param qs_kind_set ...
117 : !> \param atomic_kind_set ...
118 : !> \param local_particles ...
119 : !> \param nspin ...
120 : ! **************************************************************************************************
121 6 : SUBROUTINE harris_rhoin_init(rhoin, basis_type, qs_kind_set, atomic_kind_set, &
122 : local_particles, nspin)
123 : TYPE(harris_rhoin_type) :: rhoin
124 : CHARACTER(LEN=*) :: basis_type
125 : TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kind_set
126 : TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
127 : TYPE(distribution_1d_type), POINTER :: local_particles
128 : INTEGER, INTENT(IN) :: nspin
129 :
130 : INTEGER :: iatom, ikind, iptr, ispin, natom, nkind, &
131 : nparticle_local, nsgf
132 6 : INTEGER, ALLOCATABLE, DIMENSION(:) :: atom_of_kind, kind_of, nbasf
133 : TYPE(gto_basis_set_type), POINTER :: basis_set
134 : TYPE(qs_kind_type), POINTER :: qs_kind
135 :
136 6 : CALL harris_rhoin_release(rhoin)
137 :
138 6 : rhoin%basis_type = basis_type
139 6 : rhoin%nspin = nspin
140 :
141 : CALL get_atomic_kind_set(atomic_kind_set=atomic_kind_set, &
142 6 : atom_of_kind=atom_of_kind, kind_of=kind_of)
143 6 : natom = SIZE(atom_of_kind)
144 6 : nkind = SIZE(qs_kind_set)
145 :
146 18 : ALLOCATE (nbasf(nkind))
147 22 : DO ikind = 1, nkind
148 16 : qs_kind => qs_kind_set(ikind)
149 16 : CALL get_qs_kind(qs_kind, basis_set=basis_set, basis_type=basis_type)
150 16 : CALL get_gto_basis_set(basis_set, nsgf=nsgf)
151 22 : nbasf(ikind) = nsgf
152 : END DO
153 :
154 18 : ALLOCATE (rhoin%basptr(natom, 2))
155 6 : iptr = 1
156 34 : DO iatom = 1, natom
157 28 : ikind = kind_of(iatom)
158 28 : rhoin%basptr(iatom, 1) = iptr
159 28 : iptr = iptr + nbasf(ikind)
160 34 : rhoin%basptr(iatom, 2) = iptr - 1
161 : END DO
162 6 : rhoin%nbas = iptr - 1
163 :
164 46 : ALLOCATE (rhoin%rhovec(nkind, nspin))
165 12 : DO ispin = 1, nspin
166 28 : DO ikind = 1, nkind
167 16 : nsgf = nbasf(ikind)
168 16 : nparticle_local = local_particles%n_el(ikind)
169 66 : ALLOCATE (rhoin%rhovec(ikind, ispin)%rvecs(nsgf, nparticle_local))
170 : END DO
171 : END DO
172 :
173 40 : ALLOCATE (rhoin%intvec(nkind, nspin))
174 12 : DO ispin = 1, nspin
175 28 : DO ikind = 1, nkind
176 16 : nsgf = nbasf(ikind)
177 16 : nparticle_local = local_particles%n_el(ikind)
178 66 : ALLOCATE (rhoin%intvec(ikind, ispin)%rvecs(nsgf, nparticle_local))
179 : END DO
180 : END DO
181 :
182 6 : DEALLOCATE (nbasf)
183 :
184 12 : END SUBROUTINE harris_rhoin_init
185 :
186 : ! **************************************************************************************************
187 : !> \brief ...
188 : !> \param harris_env ...
189 : ! **************************************************************************************************
190 6686 : SUBROUTINE harris_env_release(harris_env)
191 : TYPE(harris_type), POINTER :: harris_env
192 :
193 : INTEGER :: iab
194 :
195 6686 : IF (ASSOCIATED(harris_env)) THEN
196 : !
197 6686 : CALL harris_rhoin_release(harris_env%rhoin)
198 : !
199 6686 : IF (ASSOCIATED(harris_env%vh_rspace%pw_grid)) THEN
200 6 : CALL harris_env%vh_rspace%release()
201 : END IF
202 6686 : IF (ASSOCIATED(harris_env%vxc_rspace)) THEN
203 12 : DO iab = 1, SIZE(harris_env%vxc_rspace)
204 12 : CALL harris_env%vxc_rspace(iab)%release()
205 : END DO
206 6 : DEALLOCATE (harris_env%vxc_rspace)
207 : END IF
208 : !
209 6686 : DEALLOCATE (harris_env)
210 : END IF
211 :
212 6686 : NULLIFY (harris_env)
213 :
214 6686 : END SUBROUTINE harris_env_release
215 :
216 : ! **************************************************************************************************
217 : !> \brief ...
218 : !> \param rhoin ...
219 : ! **************************************************************************************************
220 6692 : SUBROUTINE harris_rhoin_release(rhoin)
221 : TYPE(harris_rhoin_type) :: rhoin
222 :
223 : INTEGER :: i, j
224 :
225 6692 : IF (ALLOCATED(rhoin%rhovec)) THEN
226 12 : DO i = 1, SIZE(rhoin%rhovec, 2)
227 28 : DO j = 1, SIZE(rhoin%rhovec, 1)
228 22 : IF (ALLOCATED(rhoin%rhovec(j, i)%rvecs)) THEN
229 16 : DEALLOCATE (rhoin%rhovec(j, i)%rvecs)
230 : END IF
231 : END DO
232 : END DO
233 22 : DEALLOCATE (rhoin%rhovec)
234 : END IF
235 6692 : IF (ALLOCATED(rhoin%intvec)) THEN
236 12 : DO i = 1, SIZE(rhoin%intvec, 2)
237 28 : DO j = 1, SIZE(rhoin%intvec, 1)
238 22 : IF (ALLOCATED(rhoin%intvec(j, i)%rvecs)) THEN
239 16 : DEALLOCATE (rhoin%intvec(j, i)%rvecs)
240 : END IF
241 : END DO
242 : END DO
243 22 : DEALLOCATE (rhoin%intvec)
244 : END IF
245 6692 : IF (ALLOCATED(rhoin%basptr)) THEN
246 6 : DEALLOCATE (rhoin%basptr)
247 : END IF
248 6692 : rhoin%basis_type = "NDef"
249 6692 : rhoin%nspin = 0
250 6692 : rhoin%nbas = 0
251 6692 : rhoin%frozen = .FALSE.
252 :
253 6692 : END SUBROUTINE harris_rhoin_release
254 :
255 0 : END MODULE qs_harris_types
|