(git:374b731)
Loading...
Searching...
No Matches
ai_coulomb_test.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 Test of Electron Repulsion Routines (ERI)
10!> \par History
11!> none
12!> \author JGH (01.07.2009)
13! **************************************************************************************************
15
16 USE ai_coulomb, ONLY: coulomb2
17 USE kinds, ONLY: dp
18 USE machine, ONLY: m_walltime
21 nco,&
22 ncoset
23#include "../base/base_uses.f90"
24
25 IMPLICIT NONE
26
27 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'ai_coulomb_test'
28
29 REAL(kind=dp), PARAMETER :: threshold = 1.0e-6_dp
30
31 PRIVATE
32
33 PUBLIC :: eri_test
34! **************************************************************************************************
35
36CONTAINS
37
38! **************************************************************************************************
39!> \brief ...
40!> \param iw ...
41! **************************************************************************************************
42 SUBROUTINE eri_test(iw)
43
44 INTEGER, INTENT(IN) :: iw
45
46 INTEGER, PARAMETER :: lmax = 6
47
48 CHARACTER(LEN=11), DIMENSION(0:lmax) :: i2g
49 CHARACTER(LEN=5), DIMENSION(0:lmax) :: i2c
50 CHARACTER(LEN=7), DIMENSION(0:lmax) :: i2e
51 CHARACTER(LEN=9), DIMENSION(0:lmax) :: i2f
52 INTEGER :: i, ii, l, la_max, la_min, lc_max, &
53 lc_min, ll, n, npgfa, npgfb, npgfc, &
54 npgfd
55 REAL(kind=dp) :: perf, rac2, t, tend, tstart
56 REAL(kind=dp), ALLOCATABLE, DIMENSION(:) :: f
57 REAL(kind=dp), ALLOCATABLE, DIMENSION(:, :) :: vac
58 REAL(kind=dp), ALLOCATABLE, DIMENSION(:, :, :) :: v
59 REAL(kind=dp), DIMENSION(3) :: ra, rb, rc, rd
60 REAL(kind=dp), DIMENSION(:), POINTER :: rpgf, zeta, zetb, zetc, zetd
61
62 IF (iw > 0) WRITE (iw, '(/,A)') " Test of Electron Repulsion Integrals (ERI) "
63
64 CALL init_orbital_pointers(lmax)
65
66 i2c(0) = "(s|s)"
67 i2c(1) = "(p|p)"
68 i2c(2) = "(d|d)"
69 i2c(3) = "(f|f)"
70 i2c(4) = "(g|g)"
71 i2c(5) = "(h|h)"
72 i2c(6) = "(i|i)"
73
74 i2g(0) = "[(ss)|(ss)]"
75 i2g(1) = "[(pp)|(pp)]"
76 i2g(2) = "[(dd)|(dd)]"
77 i2g(3) = "[(ff)|(ff)]"
78 i2g(4) = "[(gg)|(gg)]"
79 i2g(5) = "[(hh)|(hh)]"
80 i2g(6) = "[(ii)|(ii)]"
81
82 i2f(0) = "[ss|(ss)]"
83 i2f(1) = "[pp|(pp)]"
84 i2f(2) = "[dd|(dd)]"
85 i2f(3) = "[ff|(ff)]"
86 i2f(4) = "[gg|(gg)]"
87 i2f(5) = "[hh|(hh)]"
88 i2f(6) = "[ii|(ii)]"
89
90 i2e(0) = "(ss|ss)"
91 i2e(1) = "(pp|pp)"
92 i2e(2) = "(dd|dd)"
93 i2e(3) = "(ff|ff)"
94 i2e(4) = "(gg|gg)"
95 i2e(5) = "(hh|hh)"
96 i2e(6) = "(ii|ii)"
97
98 npgfa = 4
99 npgfb = 2
100 npgfc = 4
101 npgfd = 1
102 n = max(npgfa, npgfb, npgfc, npgfd)
103
104 ALLOCATE (zeta(npgfa), zetb(npgfb), zetc(npgfc), zetd(npgfd), rpgf(n))
105
106 zeta(1:npgfa) = 0.5_dp
107 zetb(1:npgfb) = 0.4_dp
108 zetc(1:npgfc) = 0.3_dp
109 zetd(1:npgfd) = 0.2_dp
110
111 ra = (/0.0_dp, 0.0_dp, 0.0_dp/)
112 rb = (/1.0_dp, 0.0_dp, 0.0_dp/)
113 rc = (/0.0_dp, 0.3_dp, 0.3_dp/)
114 rd = (/0.7_dp, 0.2_dp, 0.1_dp/)
115
116 rac2 = sum((ra - rc)**2)
117 rpgf = 1.e10_dp
118
119 ! Performance test of coulomb2 routine
120 IF (iw > 0) THEN
121
122 WRITE (iw, '(//,A,/)') " Test of 2-Electron-2-Center Integrals (coulomb2) "
123 DO l = 0, lmax
124 la_max = l
125 la_min = l
126 lc_max = l
127 lc_min = l
128 ll = ncoset(l)
129 ALLOCATE (f(0:2*l + 2), v(npgfa*ll, npgfc*ll, 2*l + 1), vac(npgfa*ll, npgfc*ll))
130 vac = 0._dp
131 ii = max(100/(l + 1)**2, 1)
132 tstart = m_walltime()
133 DO i = 1, ii
134 CALL coulomb2(la_max, npgfa, zeta, rpgf, la_min, lc_max, npgfc, zetc, rpgf, lc_min, rc, rac2, vac, v, f)
135 END DO
136 tend = m_walltime()
137 t = tend - tstart + threshold
138 perf = real(ii*nco(l)**2, kind=dp)*1.e-6_dp*real(npgfa*npgfc, kind=dp)/t
139 WRITE (iw, '(A,T40,A,T66,F15.3)') " Performance [Mintegrals/s] ", i2c(l), perf
140 DEALLOCATE (f, v, vac)
141 END DO
142
143 END IF
144
145 DEALLOCATE (zeta, zetb, zetc, zetd, rpgf)
146
148
149 END SUBROUTINE eri_test
150
151! **************************************************************************************************
152
153END MODULE ai_coulomb_test
154
Test of Electron Repulsion Routines (ERI)
real(kind=dp), parameter threshold
subroutine, public eri_test(iw)
...
Calculation of Coulomb integrals over Cartesian Gaussian-type functions (electron repulsion integrals...
Definition ai_coulomb.F:41
subroutine, public coulomb2(la_max, npgfa, zeta, rpgfa, la_min, lc_max, npgfc, zetc, rpgfc, lc_min, rac, rac2, vac, v, f, maxder, vac_plus)
Calculation of the primitive two-center Coulomb integrals over Cartesian Gaussian-type functions.
Definition ai_coulomb.F:86
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Machine interface based on Fortran 2003 and POSIX.
Definition machine.F:17
real(kind=dp) function, public m_walltime()
returns time from a real-time clock, protected against rolling early/easily
Definition machine.F:123
Provides Cartesian and spherical orbital pointers and indices.
subroutine, public init_orbital_pointers(maxl)
Initialize or update the orbital pointers.
subroutine, public deallocate_orbital_pointers()
Deallocate the orbital pointers.
integer, dimension(:), allocatable, public nco
integer, dimension(:), allocatable, public ncoset