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 Methods for handling the 1/R^3 residual integral part
10 : !> \author Teodoro Laino (12.2008) [tlaino]
11 : ! **************************************************************************************************
12 : MODULE semi_empirical_expns3_methods
13 : USE cp_control_types, ONLY: semi_empirical_control_type
14 : USE input_constants, ONLY: do_method_undef
15 : USE kinds, ONLY: dp
16 : USE qs_kind_types, ONLY: get_qs_kind,&
17 : qs_kind_type
18 : USE semi_empirical_expns3_types, ONLY: semi_empirical_expns3_create
19 : USE semi_empirical_int3_utils, ONLY: coeff_int_3,&
20 : ijkl_low_3
21 : USE semi_empirical_int_arrays, ONLY: indexa,&
22 : l_index
23 : USE semi_empirical_types, ONLY: semi_empirical_type
24 : USE semi_empirical_utils, ONLY: get_se_type
25 : #include "./base/base_uses.f90"
26 :
27 : IMPLICIT NONE
28 : PRIVATE
29 : LOGICAL, PARAMETER, PRIVATE :: debug_this_module = .FALSE.
30 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'semi_empirical_expns3_methods'
31 :
32 : PUBLIC :: semi_empirical_expns3_setup
33 :
34 : CONTAINS
35 : ! **************************************************************************************************
36 : !> \brief Setup the quantity necessary to handle the slowly convergent
37 : !> residual integral term 1/R^3
38 : !>
39 : !> \param qs_kind_set ...
40 : !> \param se_control ...
41 : !> \param method_id ...
42 : !> \date 12.2008 [tlaino]
43 : !> \author Teodoro Laino [tlaino]
44 : ! **************************************************************************************************
45 32 : SUBROUTINE semi_empirical_expns3_setup(qs_kind_set, se_control, method_id)
46 : TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kind_set
47 : TYPE(semi_empirical_control_type), POINTER :: se_control
48 : INTEGER, INTENT(IN) :: method_id
49 :
50 : INTEGER :: i, itype, j, nkinds
51 : LOGICAL :: check
52 : TYPE(semi_empirical_type), POINTER :: sepi, sepj
53 :
54 32 : IF (se_control%do_ewald_r3) THEN
55 0 : NULLIFY (sepi, sepj)
56 0 : nkinds = SIZE(qs_kind_set)
57 0 : DO i = 1, nkinds
58 0 : CALL get_qs_kind(qs_kind_set(i), se_parameter=sepi)
59 0 : check = .NOT. ASSOCIATED(sepi%expns3_int)
60 0 : CPASSERT(check)
61 0 : ALLOCATE (sepi%expns3_int(nkinds))
62 0 : DO j = 1, nkinds
63 0 : NULLIFY (sepi%expns3_int(j)%expns3)
64 0 : CALL semi_empirical_expns3_create(sepi%expns3_int(j)%expns3)
65 : END DO
66 : END DO
67 :
68 0 : itype = get_se_type(method_id)
69 0 : DO i = 1, nkinds
70 0 : CALL get_qs_kind(qs_kind_set(i), se_parameter=sepi)
71 0 : DO j = 1, nkinds
72 0 : CALL get_qs_kind(qs_kind_set(j), se_parameter=sepj)
73 0 : CALL setup_c3_coeff(sepi, sepj, i, j, itype)
74 : END DO
75 : END DO
76 : END IF
77 32 : END SUBROUTINE semi_empirical_expns3_setup
78 :
79 : ! **************************************************************************************************
80 : !> \brief For any given semi-empirical pair i,j evaluates the coefficient of
81 : !> the integral residual part ( 1/r^3 term )
82 : !> The integral expression, unfortunately, does not allow any kind of
83 : !> separability. It is, therefore, mandatory to compute this coefficient
84 : !> as a pair term, instead of as an atomic quantity.
85 : !>
86 : !> \param sepi ...
87 : !> \param sepj ...
88 : !> \param ikind ...
89 : !> \param jkind ...
90 : !> \param itype ...
91 : !> \date 12.2008 [tlaino]
92 : !> \author Teodoro Laino [tlaino]
93 : ! **************************************************************************************************
94 0 : SUBROUTINE setup_c3_coeff(sepi, sepj, ikind, jkind, itype)
95 : TYPE(semi_empirical_type), POINTER :: sepi, sepj
96 : INTEGER, INTENT(IN) :: ikind, jkind, itype
97 :
98 : INTEGER :: i, ij, j, kl, kr, li, lk
99 : REAL(KIND=dp) :: core_core, e1b(9), e2a(9), r, zi, zj
100 :
101 : ! Set the distance to 0 (the coefficient is anyway independent of the atomic
102 : ! position)
103 :
104 0 : r = 0.0_dp
105 : ! Nuclei-Nuclei contribution
106 0 : ij = indexa(1, 1)
107 0 : zi = -sepi%zeff
108 0 : zj = -sepj%zeff
109 0 : core_core = ijkl_low_3(sepi, sepj, ij, ij, 0, 0, 0, 0, -1, r, itype, coeff_int_3)*zi*zj
110 :
111 : ! Electron(i)-Nuclei(j) contribution
112 0 : kl = indexa(1, 1)
113 0 : e1b(1) = ijkl_low_3(sepi, sepj, kl, ij, 0, 0, 0, 0, 2, r, itype, coeff_int_3)*zj
114 0 : IF (sepi%natorb > 1) THEN
115 0 : kl = indexa(2, 2)
116 0 : e1b(2) = ijkl_low_3(sepi, sepj, kl, ij, 1, 1, 0, 0, 2, r, itype, coeff_int_3)*zj
117 0 : kl = indexa(3, 3)
118 0 : e1b(3) = ijkl_low_3(sepi, sepj, kl, ij, 1, 1, 0, 0, 2, r, itype, coeff_int_3)*zj
119 0 : kl = indexa(4, 4)
120 0 : e1b(4) = ijkl_low_3(sepi, sepj, kl, ij, 1, 1, 0, 0, 2, r, itype, coeff_int_3)*zj
121 : ! Consistency check
122 0 : CPASSERT(e1b(2) == e1b(3))
123 0 : CPASSERT(e1b(3) == e1b(4))
124 0 : IF (sepi%dorb) THEN
125 0 : kl = indexa(5, 5)
126 0 : e1b(5) = ijkl_low_3(sepi, sepj, kl, ij, 2, 2, 0, 0, 2, r, itype, coeff_int_3)*zj
127 0 : kl = indexa(6, 6)
128 0 : e1b(6) = ijkl_low_3(sepi, sepj, kl, ij, 2, 2, 0, 0, 2, r, itype, coeff_int_3)*zj
129 0 : kl = indexa(7, 7)
130 0 : e1b(7) = ijkl_low_3(sepi, sepj, kl, ij, 2, 2, 0, 0, 2, r, itype, coeff_int_3)*zj
131 0 : kl = indexa(8, 8)
132 0 : e1b(8) = ijkl_low_3(sepi, sepj, kl, ij, 2, 2, 0, 0, 2, r, itype, coeff_int_3)*zj
133 0 : kl = indexa(9, 9)
134 0 : e1b(9) = ijkl_low_3(sepi, sepj, kl, ij, 2, 2, 0, 0, 2, r, itype, coeff_int_3)*zj
135 : ! Consistency check
136 0 : CPASSERT(e1b(5) == e1b(6))
137 0 : CPASSERT(e1b(6) == e1b(7))
138 0 : CPASSERT(e1b(7) == e1b(8))
139 0 : CPASSERT(e1b(8) == e1b(9))
140 : END IF
141 : END IF
142 :
143 : ! Electron(j)-Nuclei(i) contribution
144 0 : kl = indexa(1, 1)
145 0 : e2a(1) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 0, 0, 1, r, itype, coeff_int_3)*zi
146 0 : IF (sepj%natorb > 1) THEN
147 0 : kl = indexa(2, 2)
148 0 : e2a(2) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 1, 1, 1, r, itype, coeff_int_3)*zi
149 0 : kl = indexa(3, 3)
150 0 : e2a(3) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 1, 1, 1, r, itype, coeff_int_3)*zi
151 0 : kl = indexa(4, 4)
152 0 : e2a(4) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 1, 1, 1, r, itype, coeff_int_3)*zi
153 : ! Consistency check
154 0 : CPASSERT(e2a(2) == e2a(3))
155 0 : CPASSERT(e2a(3) == e2a(4))
156 0 : IF (sepj%dorb) THEN
157 0 : kl = indexa(5, 5)
158 0 : e2a(5) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 2, 2, 1, r, itype, coeff_int_3)*zi
159 0 : kl = indexa(6, 6)
160 0 : e2a(6) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 2, 2, 1, r, itype, coeff_int_3)*zi
161 0 : kl = indexa(7, 7)
162 0 : e2a(7) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 2, 2, 1, r, itype, coeff_int_3)*zi
163 0 : kl = indexa(8, 8)
164 0 : e2a(8) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 2, 2, 1, r, itype, coeff_int_3)*zi
165 0 : kl = indexa(9, 9)
166 0 : e2a(9) = ijkl_low_3(sepi, sepj, ij, kl, 0, 0, 2, 2, 1, r, itype, coeff_int_3)*zi
167 : ! Consistency check
168 0 : CPASSERT(e2a(5) == e2a(6))
169 0 : CPASSERT(e2a(6) == e2a(7))
170 0 : CPASSERT(e2a(7) == e2a(8))
171 0 : CPASSERT(e2a(8) == e2a(9))
172 : END IF
173 : END IF
174 :
175 : ! Copy info into the semi-empirical type (i)
176 0 : sepi%expns3_int(jkind)%expns3%core_core = core_core
177 0 : sepi%expns3_int(jkind)%expns3%e1b(1:sepi%natorb) = e1b(1:sepi%natorb)
178 0 : sepi%expns3_int(jkind)%expns3%e2a(1:sepj%natorb) = e2a(1:sepj%natorb)
179 : ! Copy info into the semi-empirical type (j)
180 0 : sepj%expns3_int(ikind)%expns3%core_core = core_core
181 0 : sepj%expns3_int(ikind)%expns3%e1b(1:sepj%natorb) = e2a(1:sepj%natorb)
182 0 : sepj%expns3_int(ikind)%expns3%e2a(1:sepi%natorb) = e1b(1:sepi%natorb)
183 :
184 : ! Electron-Electron contribution - sepi/sepj
185 0 : kr = 0
186 0 : DO i = 1, sepi%natorb
187 0 : li = l_index(i)
188 0 : ij = indexa(i, i)
189 0 : DO j = 1, sepj%natorb
190 0 : lk = l_index(j)
191 0 : kl = indexa(j, j)
192 0 : kr = kr + 1
193 : sepi%expns3_int(jkind)%expns3%w(kr) = &
194 0 : ijkl_low_3(sepi, sepj, ij, kl, li, li, lk, lk, 0, r, do_method_undef, coeff_int_3)
195 : END DO
196 : END DO
197 :
198 : ! Electron-Electron contribution - sepj/sepi
199 0 : kr = 0
200 0 : DO i = 1, sepj%natorb
201 0 : li = l_index(i)
202 0 : ij = indexa(i, i)
203 0 : DO j = 1, sepi%natorb
204 0 : lk = l_index(j)
205 0 : kl = indexa(j, j)
206 0 : kr = kr + 1
207 : sepj%expns3_int(ikind)%expns3%w(kr) = &
208 0 : ijkl_low_3(sepj, sepi, ij, kl, li, li, lk, lk, 0, r, do_method_undef, coeff_int_3)
209 : END DO
210 : END DO
211 :
212 0 : END SUBROUTINE setup_c3_coeff
213 :
214 : END MODULE semi_empirical_expns3_methods
|