2020-09-15 10:40:51 +02:00
|
|
|
subroutine read_integrals(nBas,S,T,V,Hc,G)
|
2019-03-20 13:38:42 +01:00
|
|
|
|
|
|
|
! Read one- and two-electron integrals from files
|
|
|
|
|
|
|
|
implicit none
|
2019-04-18 23:22:23 +02:00
|
|
|
include 'parameters.h'
|
2019-03-20 13:38:42 +01:00
|
|
|
|
|
|
|
! Input variables
|
|
|
|
|
|
|
|
integer,intent(in) :: nBas
|
|
|
|
|
|
|
|
! Local variables
|
|
|
|
|
|
|
|
logical :: debug
|
|
|
|
integer :: mu,nu,la,si
|
|
|
|
double precision :: Ov,Kin,Nuc,ERI
|
2019-05-07 22:55:36 +02:00
|
|
|
double precision :: lambda
|
2019-03-20 13:38:42 +01:00
|
|
|
|
|
|
|
! Output variables
|
|
|
|
|
2020-04-16 17:02:01 +02:00
|
|
|
double precision,intent(out) :: S(nBas,nBas)
|
|
|
|
double precision,intent(out) :: T(nBas,nBas)
|
|
|
|
double precision,intent(out) :: V(nBas,nBas)
|
|
|
|
double precision,intent(out) :: Hc(nBas,nBas)
|
|
|
|
double precision,intent(out) :: G(nBas,nBas,nBas,nBas)
|
2019-03-20 13:38:42 +01:00
|
|
|
|
|
|
|
! Open file with integrals
|
|
|
|
|
|
|
|
debug = .false.
|
|
|
|
|
2019-05-07 22:55:36 +02:00
|
|
|
lambda = 1d0
|
2019-04-18 23:22:23 +02:00
|
|
|
|
2019-05-07 22:55:36 +02:00
|
|
|
print*, 'Scaling integrals by ',lambda
|
2019-03-20 13:38:42 +01:00
|
|
|
|
|
|
|
open(unit=8 ,file='int/Ov.dat')
|
|
|
|
open(unit=9 ,file='int/Kin.dat')
|
|
|
|
open(unit=10,file='int/Nuc.dat')
|
|
|
|
open(unit=11,file='int/ERI.dat')
|
|
|
|
|
2020-09-28 21:25:25 +02:00
|
|
|
open(unit=21,file='int/x.dat')
|
|
|
|
open(unit=22,file='int/y.dat')
|
|
|
|
open(unit=23,file='int/z.dat')
|
|
|
|
|
2019-03-20 13:38:42 +01:00
|
|
|
! Read overlap integrals
|
|
|
|
|
2019-05-08 08:59:26 +02:00
|
|
|
S(:,:) = 0d0
|
2019-03-20 13:38:42 +01:00
|
|
|
do
|
|
|
|
read(8,*,end=8) mu,nu,Ov
|
|
|
|
S(mu,nu) = Ov
|
2020-01-17 17:35:40 +01:00
|
|
|
S(nu,mu) = Ov
|
2019-03-20 13:38:42 +01:00
|
|
|
enddo
|
|
|
|
8 close(unit=8)
|
|
|
|
|
|
|
|
! Read kinetic integrals
|
|
|
|
|
2019-05-08 08:59:26 +02:00
|
|
|
T(:,:) = 0d0
|
2019-03-20 13:38:42 +01:00
|
|
|
do
|
|
|
|
read(9,*,end=9) mu,nu,Kin
|
2019-05-08 08:59:26 +02:00
|
|
|
T(mu,nu) = Kin
|
2020-01-17 17:35:40 +01:00
|
|
|
T(nu,mu) = Kin
|
2019-03-20 13:38:42 +01:00
|
|
|
enddo
|
|
|
|
9 close(unit=9)
|
|
|
|
|
|
|
|
! Read nuclear integrals
|
|
|
|
|
2019-05-08 08:59:26 +02:00
|
|
|
V(:,:) = 0d0
|
2019-03-20 13:38:42 +01:00
|
|
|
do
|
|
|
|
read(10,*,end=10) mu,nu,Nuc
|
|
|
|
V(mu,nu) = Nuc
|
2020-01-17 17:35:40 +01:00
|
|
|
V(nu,mu) = Nuc
|
2019-03-20 13:38:42 +01:00
|
|
|
enddo
|
|
|
|
10 close(unit=10)
|
|
|
|
|
|
|
|
! Define core Hamiltonian
|
|
|
|
|
2019-05-08 08:59:26 +02:00
|
|
|
Hc(:,:) = T(:,:) + V(:,:)
|
2019-03-20 13:38:42 +01:00
|
|
|
|
|
|
|
! Read nuclear integrals
|
|
|
|
|
2019-05-08 08:59:26 +02:00
|
|
|
G(:,:,:,:) = 0d0
|
2019-03-20 13:38:42 +01:00
|
|
|
do
|
|
|
|
read(11,*,end=11) mu,nu,la,si,ERI
|
|
|
|
|
2019-05-07 22:55:36 +02:00
|
|
|
ERI = lambda*ERI
|
2019-03-20 13:38:42 +01:00
|
|
|
! <12|34>
|
|
|
|
G(mu,nu,la,si) = ERI
|
|
|
|
! <32|14>
|
|
|
|
G(la,nu,mu,si) = ERI
|
|
|
|
! <14|32>
|
|
|
|
G(mu,si,la,nu) = ERI
|
|
|
|
! <34|12>
|
|
|
|
G(la,si,mu,nu) = ERI
|
|
|
|
! <41|23>
|
|
|
|
G(si,mu,nu,la) = ERI
|
|
|
|
! <23|41>
|
|
|
|
G(nu,la,si,mu) = ERI
|
|
|
|
! <21|43>
|
|
|
|
G(nu,mu,si,la) = ERI
|
|
|
|
! <43|21>
|
|
|
|
G(si,la,nu,mu) = ERI
|
|
|
|
enddo
|
|
|
|
11 close(unit=11)
|
|
|
|
|
|
|
|
|
|
|
|
! Print results
|
|
|
|
if(debug) then
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
write(*,'(A28)') 'Overlap integrals'
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
call matout(nBas,nBas,S)
|
|
|
|
write(*,*)
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
write(*,'(A28)') 'Kinetic integrals'
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
call matout(nBas,nBas,T)
|
|
|
|
write(*,*)
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
write(*,'(A28)') 'Nuclear integrals'
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
call matout(nBas,nBas,V)
|
|
|
|
write(*,*)
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
write(*,'(A28)') 'Electron repulsion integrals'
|
|
|
|
write(*,'(A28)') '----------------------'
|
|
|
|
do la=1,nBas
|
|
|
|
do si=1,nBas
|
|
|
|
call matout(nBas,nBas,G(1,1,la,si))
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
write(*,*)
|
|
|
|
endif
|
|
|
|
|
|
|
|
end subroutine read_integrals
|