(git:b279b6b)
semi_empirical_int3_utils.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 !> \brief Utilities for evaluating the residual part (1/r^3) of Integrals for
10 !> semi-empiric methods
11 !> \author Teodoro Laino (11.2008) [tlaino]
12 ! **************************************************************************************************
14 
16  USE kinds, ONLY: dp
17  USE semi_empirical_int_arrays, ONLY: clm_d,&
18  indexb
19  USE semi_empirical_types, ONLY: semi_empirical_type
20 #include "./base/base_uses.f90"
21 
22  IMPLICIT NONE
23  PRIVATE
24  LOGICAL, PARAMETER, PRIVATE :: debug_this_module = .false.
25  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'semi_empirical_int3_utils'
26 
28 
29  abstract INTERFACE
30 ! **************************************************************************************************
31 !> \brief ...
32 !> \param r ...
33 !> \param l1 ...
34 !> \param l2 ...
35 !> \param add ...
36 !> \return ...
37 ! **************************************************************************************************
38  FUNCTION eval_func(r, l1, l2, add) RESULT(res)
39  USE kinds, ONLY: dp
40  REAL(KIND=dp), INTENT(IN) :: r
41  INTEGER, INTENT(IN) :: l1, l2
42  REAL(KIND=dp), INTENT(IN) :: add
43  REAL(KIND=dp) :: res
44 
45  END FUNCTION eval_func
46  END INTERFACE
47 CONTAINS
48 
49 ! **************************************************************************************************
50 !> \brief Low level general driver for computing residual part of semi-empirical
51 !> integrals <ij|kl> and their derivatives
52 !> The residual part is the leading 1/r^3 term
53 !>
54 !> \param sepi ...
55 !> \param sepj ...
56 !> \param ij ...
57 !> \param kl ...
58 !> \param li ...
59 !> \param lj ...
60 !> \param lk ...
61 !> \param ll ...
62 !> \param ic ...
63 !> \param r ...
64 !> \param itype ...
65 !> \param eval ...
66 !> \return ...
67 !> \date 11.2008 [tlaino]
68 !> \author Teodoro Laino [tlaino]
69 ! **************************************************************************************************
70  FUNCTION ijkl_low_3(sepi, sepj, ij, kl, li, lj, lk, ll, ic, r, itype, eval) RESULT(res)
71  TYPE(semi_empirical_type), POINTER :: sepi, sepj
72  INTEGER, INTENT(IN) :: ij, kl, li, lj, lk, ll, ic
73  REAL(kind=dp), INTENT(IN) :: r
74  INTEGER, INTENT(IN) :: itype
75 
76  PROCEDURE(eval_func) :: eval
77  REAL(kind=dp) :: res
78 
79  INTEGER :: l1, l2, lij, lkl
80  REAL(kind=dp) :: add, ccc, chrg, pij, pkl, sum
81 
82  sum = 0.0_dp
83  l1 = abs(li - lj)
84  lij = indexb(li + 1, lj + 1)
85  l2 = abs(lk - ll)
86  lkl = indexb(lk + 1, ll + 1)
87 
88  ! Standard value of the integral
89  IF (l1 == 0) THEN
90  IF (lij == 1) THEN
91  pij = sepi%ko(1)
92  IF (ic == 1) THEN
93  pij = sepi%ko(9)
94  END IF
95  ELSE IF (lij == 3) THEN
96  pij = sepi%ko(7)
97  ELSE IF (lij == 6) THEN
98  pij = sepi%ko(8)
99  END IF
100  END IF
101  !
102  IF (l2 == 0) THEN
103  IF (lkl == 1) THEN
104  pkl = sepj%ko(1)
105  IF (ic == 2) THEN
106  pkl = sepj%ko(9)
107  END IF
108  ELSE IF (lkl == 3) THEN
109  pkl = sepj%ko(7)
110  ELSE IF (lkl == 6) THEN
111  pkl = sepj%ko(8)
112  END IF
113  END IF
114  IF (l1 == 0 .AND. l2 == 0) THEN
115  IF (itype == do_method_pchg) THEN
116  add = 0.0_dp
117  ELSE
118  add = (pij + pkl)**2
119  END IF
120  ccc = clm_d(ij, l1, 0)*clm_d(kl, l2, 0)
121  IF (abs(ccc) > epsilon(0.0_dp)) THEN
122  chrg = eval(r, l1, l2, add)
123  sum = chrg
124  END IF
125  END IF
126  res = sum
127  END FUNCTION ijkl_low_3
128 
129 ! **************************************************************************************************
130 !> \brief Evaluates the residual Interaction function between two point-charges
131 !> The term evaluated is the 1/r^3 (for short range interactions)
132 !> r - Distance r12
133 !> l1 - Quantum numbers for multipole of configuration 1
134 !> l2 - Quantum numbers for multipole of configuration 2
135 !> add - additive term
136 !>
137 !> \param r ...
138 !> \param l1 ...
139 !> \param l2 ...
140 !> \param add ...
141 !> \return ...
142 !> \date 11.2008 [tlaino]
143 !> \author Teodoro Laino [tlaino]
144 ! **************************************************************************************************
145  FUNCTION charg_int_3(r, l1, l2, add) RESULT(charg)
146  REAL(kind=dp), INTENT(in) :: r
147  INTEGER, INTENT(in) :: l1, l2
148  REAL(kind=dp), INTENT(in) :: add
149  REAL(kind=dp) :: charg
150 
151 ! Computing only residual Integral Values
152 
153  charg = 0.0_dp
154  ! Q - Q.
155  IF (l1 == 0 .AND. l2 == 0) THEN
156  charg = -add/(2.0_dp*r**3)
157  RETURN
158  END IF
159  ! We should NEVER reach this point
160  cpabort("")
161  END FUNCTION charg_int_3
162 
163 ! **************************************************************************************************
164 !> \brief Evaluates the coefficient for the residual Interaction function
165 !> between two point-charges
166 !> l1 - Quantum numbers for multipole of configuration 1
167 !> l2 - Quantum numbers for multipole of configuration 2
168 !> add - additive term
169 !>
170 !> \param r ...
171 !> \param l1 ...
172 !> \param l2 ...
173 !> \param add ...
174 !> \return ...
175 !> \date 11.2008 [tlaino]
176 !> \author Teodoro Laino [tlaino]
177 ! **************************************************************************************************
178  FUNCTION coeff_int_3(r, l1, l2, add) RESULT(coeff)
179  REAL(kind=dp), INTENT(in) :: r
180  INTEGER, INTENT(in) :: l1, l2
181  REAL(kind=dp), INTENT(in) :: add
182  REAL(kind=dp) :: coeff
183 
184  mark_used(r) ! dummy arg to be compatible with the interface
185 
186 ! Computing only residual Integral Values
187 
188  coeff = 0.0_dp
189  ! Q - Q.
190  IF (l1 == 0 .AND. l2 == 0) THEN
191  coeff = -add/2.0_dp
192  RETURN
193  END IF
194  ! We should NEVER reach this point
195  cpabort("")
196  END FUNCTION coeff_int_3
197 
198 ! **************************************************************************************************
199 !> \brief Derivatives of residual interaction function between two point-charges
200 !>
201 !> r - Distance r12
202 !> l1 - Quantum numbers for multipole of configuration 1
203 !> l2 - Quantum numbers for multipole of configuration 2
204 !> add - additive term
205 !>
206 !> \param r ...
207 !> \param l1 ...
208 !> \param l2 ...
209 !> \param add ...
210 !> \return ...
211 !> \date 11.2008 [tlaino]
212 !> \author Teodoro Laino [tlaino]
213 ! **************************************************************************************************
214  FUNCTION dcharg_int_3(r, l1, l2, add) RESULT(charg)
215  REAL(kind=dp), INTENT(in) :: r
216  INTEGER, INTENT(in) :: l1, l2
217  REAL(kind=dp), INTENT(in) :: add
218  REAL(kind=dp) :: charg
219 
220 ! Computing only residual Integral Derivatives
221 
222  charg = 0.0_dp
223  ! Q - Q.
224  IF (l1 == 0 .AND. l2 == 0) THEN
225  charg = 3.0_dp*add/(2.0_dp*r**4)
226  RETURN
227  END IF
228  ! We should NEVER reach this point
229  cpabort("")
230  END FUNCTION dcharg_int_3
231 
232 END MODULE semi_empirical_int3_utils
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_method_pchg
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Utilities for evaluating the residual part (1/r^3) of Integrals for semi-empiric methods.
real(kind=dp) function, public charg_int_3(r, l1, l2, add)
Evaluates the residual Interaction function between two point-charges The term evaluated is the 1/r^3...
real(kind=dp) function, public coeff_int_3(r, l1, l2, add)
Evaluates the coefficient for the residual Interaction function between two point-charges l1 - Quantu...
real(kind=dp) function, public ijkl_low_3(sepi, sepj, ij, kl, li, lj, lk, ll, ic, r, itype, eval)
Low level general driver for computing residual part of semi-empirical integrals <ij|kl> and their de...
real(kind=dp) function, public dcharg_int_3(r, l1, l2, add)
Derivatives of residual interaction function between two point-charges.
Arrays of parameters used in the semi-empirical calculations \References Everywhere in this module TC...
integer, dimension(9, 9), public indexb
real(kind=dp), dimension(45, 0:2, -2:2), public clm_d
Definition of the semi empirical parameter types.