mirror of
https://github.com/QuantumPackage/qp2.git
synced 2024-11-07 05:53:37 +01:00
Fixed bug in get_d0
This commit is contained in:
parent
7237e885c3
commit
35f7b26ec5
@ -1,4 +1,14 @@
|
|||||||
%%% ARXIV TO BE UPDATED %%%
|
%%% ARXIV TO BE UPDATED %%%
|
||||||
|
@article{Loos2019Oct,
|
||||||
|
author = {Loos, Pierre-François and Pradines, Barthélémy and Scemama, Anthony and Giner, Emmanuel and Toulouse, Julien},
|
||||||
|
title = {{A Density-Based Basis-Set Incompleteness Correction for GW Methods}},
|
||||||
|
journal = {arXiv},
|
||||||
|
year = {2019},
|
||||||
|
month = {Oct},
|
||||||
|
eprint = {1910.12238},
|
||||||
|
url = {https://arxiv.org/abs/1910.12238}
|
||||||
|
}
|
||||||
|
|
||||||
@article{Hollett2019Aug,
|
@article{Hollett2019Aug,
|
||||||
author = {Hollett, Joshua W. and Loos, Pierre-Fran{\c{c}}ois},
|
author = {Hollett, Joshua W. and Loos, Pierre-Fran{\c{c}}ois},
|
||||||
title = {{Capturing static and dynamic correlation with $\Delta \text{NO}$-MP2 and $\Delta \text{NO}$-CCSD}},
|
title = {{Capturing static and dynamic correlation with $\Delta \text{NO}$-MP2 and $\Delta \text{NO}$-CCSD}},
|
||||||
|
@ -759,6 +759,21 @@ subroutine fill_buffer_double(i_generator, sp, h1, h2, bannedOrb, banned, fock_d
|
|||||||
variance(istate) = variance(istate) + alpha_h_psi * alpha_h_psi
|
variance(istate) = variance(istate) + alpha_h_psi * alpha_h_psi
|
||||||
norm(istate) = norm(istate) + coef * coef
|
norm(istate) = norm(istate) + coef * coef
|
||||||
|
|
||||||
|
!!!DEBUG
|
||||||
|
! integer :: k
|
||||||
|
! double precision :: alpha_h_psi_2,hij
|
||||||
|
! alpha_h_psi_2 = 0.d0
|
||||||
|
! do k = 1,N_det_selectors
|
||||||
|
! call i_H_j(det,psi_selectors(1,1,k),N_int,hij)
|
||||||
|
! alpha_h_psi_2 = alpha_h_psi_2 + psi_selectors_coef(k,istate) * hij
|
||||||
|
! enddo
|
||||||
|
! if(dabs(alpha_h_psi_2 - alpha_h_psi).gt.1.d-12)then
|
||||||
|
! call debug_det(psi_det_generators(1,1,i_generator),N_int)
|
||||||
|
! call debug_det(det,N_int)
|
||||||
|
! print*,'alpha_h_psi,alpha_h_psi_2 = ',alpha_h_psi,alpha_h_psi_2
|
||||||
|
! stop
|
||||||
|
! endif
|
||||||
|
!!!DEBUG
|
||||||
|
|
||||||
select case (weight_selection)
|
select case (weight_selection)
|
||||||
|
|
||||||
@ -870,10 +885,13 @@ subroutine splash_pq(mask, sp, det, i_gen, N_sel, bannedOrb, banned, mat, intere
|
|||||||
|
|
||||||
call get_mask_phase(psi_det_sorted(1,1,interesting(i)), phasemask,N_int)
|
call get_mask_phase(psi_det_sorted(1,1,interesting(i)), phasemask,N_int)
|
||||||
if(nt == 4) then
|
if(nt == 4) then
|
||||||
|
! call get_d2_reference(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
||||||
call get_d2(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
call get_d2(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
||||||
else if(nt == 3) then
|
else if(nt == 3) then
|
||||||
|
! call get_d1_reference(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
||||||
call get_d1(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
call get_d1(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
||||||
else
|
else
|
||||||
|
! call get_d0_reference(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
||||||
call get_d0(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
call get_d0(det(1,1,i), phasemask, bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, interesting(i)))
|
||||||
end if
|
end if
|
||||||
else if(nt == 4) then
|
else if(nt == 4) then
|
||||||
@ -1273,25 +1291,45 @@ subroutine get_d0(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
|||||||
if(sp == 3) then ! AB
|
if(sp == 3) then ! AB
|
||||||
h1 = p(1,1)
|
h1 = p(1,1)
|
||||||
h2 = p(1,2)
|
h2 = p(1,2)
|
||||||
do p2=1, mo_num
|
do p1=1, mo_num
|
||||||
if(bannedOrb(p2,2)) cycle
|
if(bannedOrb(p1, 1)) cycle
|
||||||
call get_mo_two_e_integrals(p2,h1,h2,mo_num,hij_cache1,mo_integrals_map)
|
call get_mo_two_e_integrals(p1,h2,h1,mo_num,hij_cache1,mo_integrals_map)
|
||||||
do p1=1, mo_num
|
do p2=1, mo_num
|
||||||
if(bannedOrb(p1, 1) .or. banned(p1, p2, bant)) cycle
|
if(bannedOrb(p2,2)) cycle
|
||||||
if(p1 /= h1 .and. p2 /= h2) then
|
if(banned(p1, p2, bant)) cycle ! rentable?
|
||||||
if (hij_cache1(p1) == 0.d0) cycle
|
if(p1 == h1 .or. p2 == h2) then
|
||||||
phase = get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2, N_int)
|
|
||||||
hij = hij_cache1(p1) * phase
|
|
||||||
else
|
|
||||||
call apply_particles(mask, 1,p1,2,p2, det, ok, N_int)
|
call apply_particles(mask, 1,p1,2,p2, det, ok, N_int)
|
||||||
call i_h_j(gen, det, N_int, hij)
|
call i_h_j(gen, det, N_int, hij)
|
||||||
if (hij == 0.d0) cycle
|
else
|
||||||
|
phase = get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2, N_int)
|
||||||
|
! hij = mo_two_e_integral(p2, p1, h2, h1) * phase
|
||||||
|
hij = hij_cache1(p2) * phase
|
||||||
end if
|
end if
|
||||||
|
if (hij == 0.d0) cycle
|
||||||
do k=1,N_states
|
do k=1,N_states
|
||||||
mat(k, p1, p2) = mat(k, p1, p2) + coefs(k) * hij ! HOTSPOT
|
mat(k, p1, p2) = mat(k, p1, p2) + coefs(k) * hij ! HOTSPOT
|
||||||
enddo
|
enddo
|
||||||
end do
|
end do
|
||||||
end do
|
end do
|
||||||
|
! do p2=1, mo_num
|
||||||
|
! if(bannedOrb(p2,2)) cycle
|
||||||
|
! call get_mo_two_e_integrals(p2,h1,h2,mo_num,hij_cache1,mo_integrals_map)
|
||||||
|
! do p1=1, mo_num
|
||||||
|
! if(bannedOrb(p1, 1) .or. banned(p1, p2, bant)) cycle
|
||||||
|
! if(p1 /= h1 .and. p2 /= h2) then
|
||||||
|
! if (hij_cache1(p1) == 0.d0) cycle
|
||||||
|
! phase = get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2, N_int)
|
||||||
|
! hij = hij_cache1(p1) * phase
|
||||||
|
! else
|
||||||
|
! call apply_particles(mask, 1,p1,2,p2, det, ok, N_int)
|
||||||
|
! call i_h_j(gen, det, N_int, hij)
|
||||||
|
! if (hij == 0.d0) cycle
|
||||||
|
! end if
|
||||||
|
! do k=1,N_states
|
||||||
|
! mat(k, p1, p2) = mat(k, p1, p2) + coefs(k) * hij ! HOTSPOT
|
||||||
|
! enddo
|
||||||
|
! end do
|
||||||
|
! end do
|
||||||
|
|
||||||
else ! AA BB
|
else ! AA BB
|
||||||
p1 = p(1,sp)
|
p1 = p(1,sp)
|
||||||
@ -1301,24 +1339,36 @@ subroutine get_d0(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
|||||||
call get_mo_two_e_integrals(puti,p2,p1,mo_num,hij_cache1,mo_integrals_map)
|
call get_mo_two_e_integrals(puti,p2,p1,mo_num,hij_cache1,mo_integrals_map)
|
||||||
call get_mo_two_e_integrals(puti,p1,p2,mo_num,hij_cache2,mo_integrals_map)
|
call get_mo_two_e_integrals(puti,p1,p2,mo_num,hij_cache2,mo_integrals_map)
|
||||||
do putj=puti+1, mo_num
|
do putj=puti+1, mo_num
|
||||||
if(bannedOrb(putj, sp) .or. banned(putj, sp, bant)) cycle
|
if(bannedOrb(putj, sp)) cycle
|
||||||
if(puti /= p1 .and. putj /= p2 .and. puti /= p2 .and. putj /= p1) then
|
if(banned(puti, putj, bant)) cycle ! rentable?
|
||||||
hij = hij_cache1(putj) - hij_cache2(putj)
|
if(puti == p1 .or. putj == p2 .or. puti == p2 .or. putj == p1) then
|
||||||
if (hij /= 0.d0) then
|
|
||||||
hij = hij * get_phase_bi(phasemask, sp, sp, puti, p1 , putj, p2, N_int)
|
|
||||||
do k=1,N_states
|
|
||||||
mat(k, puti, putj) = mat(k, puti, putj) + coefs(k) * hij
|
|
||||||
enddo
|
|
||||||
endif
|
|
||||||
else
|
|
||||||
call apply_particles(mask, sp,puti,sp,putj, det, ok, N_int)
|
call apply_particles(mask, sp,puti,sp,putj, det, ok, N_int)
|
||||||
call i_h_j(gen, det, N_int, hij)
|
call i_h_j(gen, det, N_int, hij)
|
||||||
if (hij /= 0.d0) then
|
else
|
||||||
do k=1,N_states
|
hij = (mo_two_e_integral(p1, p2, puti, putj) - mo_two_e_integral(p2, p1, puti, putj))* get_phase_bi(phasemask, sp, sp, puti, p1 , putj, p2, N_int)
|
||||||
mat(k, puti, putj) = mat(k, puti, putj) + coefs(k) * hij
|
|
||||||
enddo
|
|
||||||
endif
|
|
||||||
end if
|
end if
|
||||||
|
if (hij == 0.d0) cycle
|
||||||
|
do k=1,N_states
|
||||||
|
mat(k, puti, putj) = mat(k, puti, putj) + coefs(k) * hij
|
||||||
|
enddo
|
||||||
|
! if(bannedOrb(putj, sp) .or. banned(putj, sp, bant)) cycle
|
||||||
|
! if(puti /= p1 .and. putj /= p2 .and. puti /= p2 .and. putj /= p1) then
|
||||||
|
! hij = hij_cache1(putj) - hij_cache2(putj)
|
||||||
|
! if (hij /= 0.d0) then
|
||||||
|
! hij = hij * get_phase_bi(phasemask, sp, sp, puti, p1 , putj, p2, N_int)
|
||||||
|
! do k=1,N_states
|
||||||
|
! mat(k, puti, putj) = mat(k, puti, putj) + coefs(k) * hij
|
||||||
|
! enddo
|
||||||
|
! endif
|
||||||
|
! else
|
||||||
|
! call apply_particles(mask, sp,puti,sp,putj, det, ok, N_int)
|
||||||
|
! call i_h_j(gen, det, N_int, hij)
|
||||||
|
! if (hij /= 0.d0) then
|
||||||
|
! do k=1,N_states
|
||||||
|
! mat(k, puti, putj) = mat(k, puti, putj) + coefs(k) * hij
|
||||||
|
! enddo
|
||||||
|
! endif
|
||||||
|
! end if
|
||||||
end do
|
end do
|
||||||
end do
|
end do
|
||||||
end if
|
end if
|
||||||
@ -1448,3 +1498,356 @@ subroutine bitstring_to_list_in_selection( string, list, n_elements, Nint)
|
|||||||
|
|
||||||
end
|
end
|
||||||
!
|
!
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
! OLD unoptimized routines for debugging
|
||||||
|
! ======================================
|
||||||
|
|
||||||
|
subroutine get_d0_reference(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: gen(N_int, 2), mask(N_int, 2)
|
||||||
|
integer(bit_kind), intent(in) :: phasemask(N_int,2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_num, 2), banned(mo_num, mo_num,2)
|
||||||
|
integer(bit_kind) :: det(N_int, 2)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: mat(N_states, mo_num, mo_num)
|
||||||
|
integer, intent(in) :: h(0:2,2), p(0:4,2), sp
|
||||||
|
|
||||||
|
integer :: i, j, s, h1, h2, p1, p2, puti, putj
|
||||||
|
double precision :: hij, phase
|
||||||
|
double precision, external :: get_phase_bi, mo_two_e_integral
|
||||||
|
logical :: ok
|
||||||
|
|
||||||
|
integer :: bant
|
||||||
|
bant = 1
|
||||||
|
|
||||||
|
|
||||||
|
if(sp == 3) then ! AB
|
||||||
|
h1 = p(1,1)
|
||||||
|
h2 = p(1,2)
|
||||||
|
do p1=1, mo_num
|
||||||
|
if(bannedOrb(p1, 1)) cycle
|
||||||
|
do p2=1, mo_num
|
||||||
|
if(bannedOrb(p2,2)) cycle
|
||||||
|
if(banned(p1, p2, bant)) cycle ! rentable?
|
||||||
|
if(p1 == h1 .or. p2 == h2) then
|
||||||
|
call apply_particles(mask, 1,p1,2,p2, det, ok, N_int)
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
else
|
||||||
|
phase = get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2, N_int)
|
||||||
|
hij = mo_two_e_integral(p1, p2, h1, h2) * phase
|
||||||
|
end if
|
||||||
|
mat(:, p1, p2) += coefs(:) * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
else ! AA BB
|
||||||
|
p1 = p(1,sp)
|
||||||
|
p2 = p(2,sp)
|
||||||
|
do puti=1, mo_num
|
||||||
|
if(bannedOrb(puti, sp)) cycle
|
||||||
|
do putj=puti+1, mo_num
|
||||||
|
if(bannedOrb(putj, sp)) cycle
|
||||||
|
if(banned(puti, putj, bant)) cycle ! rentable?
|
||||||
|
if(puti == p1 .or. putj == p2 .or. puti == p2 .or. putj == p1) then
|
||||||
|
call apply_particles(mask, sp,puti,sp,putj, det, ok, N_int)
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
else
|
||||||
|
hij = (mo_two_e_integral(p1, p2, puti, putj) - mo_two_e_integral(p2, p1, puti, putj))* get_phase_bi(phasemask, sp, sp, puti, p1 , putj, p2, N_int)
|
||||||
|
end if
|
||||||
|
mat(:, puti, putj) += coefs(:) * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end if
|
||||||
|
end
|
||||||
|
|
||||||
|
subroutine get_d1_reference(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: mask(N_int, 2), gen(N_int, 2)
|
||||||
|
integer(bit_kind), intent(in) :: phasemask(N_int,2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_num, 2), banned(mo_num, mo_num,2)
|
||||||
|
integer(bit_kind) :: det(N_int, 2)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: mat(N_states, mo_num, mo_num)
|
||||||
|
integer, intent(in) :: h(0:2,2), p(0:4,2), sp
|
||||||
|
double precision :: hij, tmp_row(N_states, mo_num), tmp_row2(N_states, mo_num)
|
||||||
|
double precision, external :: get_phase_bi, mo_two_e_integral
|
||||||
|
logical :: ok
|
||||||
|
|
||||||
|
logical, allocatable :: lbanned(:,:)
|
||||||
|
integer :: puti, putj, ma, mi, s1, s2, i, i1, i2, j
|
||||||
|
integer :: hfix, pfix, h1, h2, p1, p2, ib
|
||||||
|
|
||||||
|
integer, parameter :: turn2(2) = (/2,1/)
|
||||||
|
integer, parameter :: turn3(2,3) = reshape((/2,3, 1,3, 1,2/), (/2,3/))
|
||||||
|
|
||||||
|
integer :: bant
|
||||||
|
|
||||||
|
|
||||||
|
allocate (lbanned(mo_num, 2))
|
||||||
|
lbanned = bannedOrb
|
||||||
|
|
||||||
|
do i=1, p(0,1)
|
||||||
|
lbanned(p(i,1), 1) = .true.
|
||||||
|
end do
|
||||||
|
do i=1, p(0,2)
|
||||||
|
lbanned(p(i,2), 2) = .true.
|
||||||
|
end do
|
||||||
|
|
||||||
|
ma = 1
|
||||||
|
if(p(0,2) >= 2) ma = 2
|
||||||
|
mi = turn2(ma)
|
||||||
|
|
||||||
|
bant = 1
|
||||||
|
|
||||||
|
if(sp == 3) then
|
||||||
|
!move MA
|
||||||
|
if(ma == 2) bant = 2
|
||||||
|
puti = p(1,mi)
|
||||||
|
hfix = h(1,ma)
|
||||||
|
p1 = p(1,ma)
|
||||||
|
p2 = p(2,ma)
|
||||||
|
if(.not. bannedOrb(puti, mi)) then
|
||||||
|
tmp_row = 0d0
|
||||||
|
do putj=1, hfix-1
|
||||||
|
if(lbanned(putj, ma) .or. banned(putj, puti,bant)) cycle
|
||||||
|
hij = (mo_two_e_integral(p1, p2, putj, hfix)-mo_two_e_integral(p2,p1,putj,hfix)) * get_phase_bi(phasemask, ma, ma, putj, p1, hfix, p2, N_int)
|
||||||
|
tmp_row(1:N_states,putj) += hij * coefs(1:N_states)
|
||||||
|
end do
|
||||||
|
do putj=hfix+1, mo_num
|
||||||
|
if(lbanned(putj, ma) .or. banned(putj, puti,bant)) cycle
|
||||||
|
hij = (mo_two_e_integral(p1, p2, hfix, putj)-mo_two_e_integral(p2,p1,hfix,putj)) * get_phase_bi(phasemask, ma, ma, hfix, p1, putj, p2, N_int)
|
||||||
|
tmp_row(1:N_states,putj) += hij * coefs(1:N_states)
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(ma == 1) then
|
||||||
|
mat(1:N_states,1:mo_num,puti) += tmp_row(1:N_states,1:mo_num)
|
||||||
|
else
|
||||||
|
mat(1:N_states,puti,1:mo_num) += tmp_row(1:N_states,1:mo_num)
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
|
||||||
|
!MOVE MI
|
||||||
|
pfix = p(1,mi)
|
||||||
|
tmp_row = 0d0
|
||||||
|
tmp_row2 = 0d0
|
||||||
|
do puti=1,mo_num
|
||||||
|
if(lbanned(puti,mi)) cycle
|
||||||
|
!p1 fixed
|
||||||
|
putj = p1
|
||||||
|
if(.not. banned(putj,puti,bant)) then
|
||||||
|
hij = mo_two_e_integral(p2,pfix,hfix,puti) * get_phase_bi(phasemask, ma, mi, hfix, p2, puti, pfix, N_int)
|
||||||
|
tmp_row(:,puti) += hij * coefs(:)
|
||||||
|
end if
|
||||||
|
|
||||||
|
putj = p2
|
||||||
|
if(.not. banned(putj,puti,bant)) then
|
||||||
|
hij = mo_two_e_integral(p1,pfix,hfix,puti) * get_phase_bi(phasemask, ma, mi, hfix, p1, puti, pfix, N_int)
|
||||||
|
tmp_row2(:,puti) += hij * coefs(:)
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(mi == 1) then
|
||||||
|
mat(:,:,p1) += tmp_row(:,:)
|
||||||
|
mat(:,:,p2) += tmp_row2(:,:)
|
||||||
|
else
|
||||||
|
mat(:,p1,:) += tmp_row(:,:)
|
||||||
|
mat(:,p2,:) += tmp_row2(:,:)
|
||||||
|
end if
|
||||||
|
else
|
||||||
|
if(p(0,ma) == 3) then
|
||||||
|
do i=1,3
|
||||||
|
hfix = h(1,ma)
|
||||||
|
puti = p(i, ma)
|
||||||
|
p1 = p(turn3(1,i), ma)
|
||||||
|
p2 = p(turn3(2,i), ma)
|
||||||
|
tmp_row = 0d0
|
||||||
|
do putj=1,hfix-1
|
||||||
|
if(lbanned(putj,ma) .or. banned(puti,putj,1)) cycle
|
||||||
|
hij = (mo_two_e_integral(p1, p2, putj, hfix)-mo_two_e_integral(p2,p1,putj,hfix)) * get_phase_bi(phasemask, ma, ma, putj, p1, hfix, p2, N_int)
|
||||||
|
tmp_row(:,putj) += hij * coefs(:)
|
||||||
|
end do
|
||||||
|
do putj=hfix+1,mo_num
|
||||||
|
if(lbanned(putj,ma) .or. banned(puti,putj,1)) cycle
|
||||||
|
hij = (mo_two_e_integral(p1, p2, hfix, putj)-mo_two_e_integral(p2,p1,hfix,putj)) * get_phase_bi(phasemask, ma, ma, hfix, p1, putj, p2, N_int)
|
||||||
|
tmp_row(:,putj) += hij * coefs(:)
|
||||||
|
end do
|
||||||
|
|
||||||
|
mat(:, :puti-1, puti) += tmp_row(:,:puti-1)
|
||||||
|
mat(:, puti, puti:) += tmp_row(:,puti:)
|
||||||
|
end do
|
||||||
|
else
|
||||||
|
hfix = h(1,mi)
|
||||||
|
pfix = p(1,mi)
|
||||||
|
p1 = p(1,ma)
|
||||||
|
p2 = p(2,ma)
|
||||||
|
tmp_row = 0d0
|
||||||
|
tmp_row2 = 0d0
|
||||||
|
do puti=1,mo_num
|
||||||
|
if(lbanned(puti,ma)) cycle
|
||||||
|
putj = p2
|
||||||
|
if(.not. banned(puti,putj,1)) then
|
||||||
|
hij = mo_two_e_integral(pfix, p1, hfix, puti) * get_phase_bi(phasemask, mi, ma, hfix, pfix, puti, p1, N_int)
|
||||||
|
tmp_row(:,puti) += hij * coefs(:)
|
||||||
|
end if
|
||||||
|
|
||||||
|
putj = p1
|
||||||
|
if(.not. banned(puti,putj,1)) then
|
||||||
|
hij = mo_two_e_integral(pfix, p2, hfix, puti) * get_phase_bi(phasemask, mi, ma, hfix, pfix, puti, p2, N_int)
|
||||||
|
tmp_row2(:,puti) += hij * coefs(:)
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
mat(:,:p2-1,p2) += tmp_row(:,:p2-1)
|
||||||
|
mat(:,p2,p2:) += tmp_row(:,p2:)
|
||||||
|
mat(:,:p1-1,p1) += tmp_row2(:,:p1-1)
|
||||||
|
mat(:,p1,p1:) += tmp_row2(:,p1:)
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
deallocate(lbanned)
|
||||||
|
|
||||||
|
!! MONO
|
||||||
|
if(sp == 3) then
|
||||||
|
s1 = 1
|
||||||
|
s2 = 2
|
||||||
|
else
|
||||||
|
s1 = sp
|
||||||
|
s2 = sp
|
||||||
|
end if
|
||||||
|
|
||||||
|
do i1=1,p(0,s1)
|
||||||
|
ib = 1
|
||||||
|
if(s1 == s2) ib = i1+1
|
||||||
|
do i2=ib,p(0,s2)
|
||||||
|
p1 = p(i1,s1)
|
||||||
|
p2 = p(i2,s2)
|
||||||
|
if(bannedOrb(p1, s1) .or. bannedOrb(p2, s2) .or. banned(p1, p2, 1)) cycle
|
||||||
|
call apply_particles(mask, s1, p1, s2, p2, det, ok, N_int)
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
mat(:, p1, p2) += coefs(:) * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end
|
||||||
|
|
||||||
|
subroutine get_d2_reference(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: mask(N_int, 2), gen(N_int, 2)
|
||||||
|
integer(bit_kind), intent(in) :: phasemask(2,N_int)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_num, 2), banned(mo_num, mo_num,2)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: mat(N_states, mo_num, mo_num)
|
||||||
|
integer, intent(in) :: h(0:2,2), p(0:4,2), sp
|
||||||
|
|
||||||
|
double precision, external :: get_phase_bi, mo_two_e_integral
|
||||||
|
|
||||||
|
integer :: i, j, tip, ma, mi, puti, putj
|
||||||
|
integer :: h1, h2, p1, p2, i1, i2
|
||||||
|
double precision :: hij, phase
|
||||||
|
|
||||||
|
integer, parameter:: turn2d(2,3,4) = reshape((/0,0, 0,0, 0,0, 3,4, 0,0, 0,0, 2,4, 1,4, 0,0, 2,3, 1,3, 1,2 /), (/2,3,4/))
|
||||||
|
integer, parameter :: turn2(2) = (/2, 1/)
|
||||||
|
integer, parameter :: turn3(2,3) = reshape((/2,3, 1,3, 1,2/), (/2,3/))
|
||||||
|
|
||||||
|
integer :: bant
|
||||||
|
bant = 1
|
||||||
|
|
||||||
|
tip = p(0,1) * p(0,2)
|
||||||
|
|
||||||
|
ma = sp
|
||||||
|
if(p(0,1) > p(0,2)) ma = 1
|
||||||
|
if(p(0,1) < p(0,2)) ma = 2
|
||||||
|
mi = mod(ma, 2) + 1
|
||||||
|
|
||||||
|
if(sp == 3) then
|
||||||
|
if(ma == 2) bant = 2
|
||||||
|
|
||||||
|
if(tip == 3) then
|
||||||
|
puti = p(1, mi)
|
||||||
|
do i = 1, 3
|
||||||
|
putj = p(i, ma)
|
||||||
|
if(banned(putj,puti,bant)) cycle
|
||||||
|
i1 = turn3(1,i)
|
||||||
|
i2 = turn3(2,i)
|
||||||
|
p1 = p(i1, ma)
|
||||||
|
p2 = p(i2, ma)
|
||||||
|
h1 = h(1, ma)
|
||||||
|
h2 = h(2, ma)
|
||||||
|
|
||||||
|
hij = (mo_two_e_integral(p1, p2, h1, h2) - mo_two_e_integral(p2,p1, h1, h2)) * get_phase_bi(phasemask, ma, ma, h1, p1, h2, p2, N_int)
|
||||||
|
if(ma == 1) then
|
||||||
|
mat(:, putj, puti) += coefs(:) * hij
|
||||||
|
else
|
||||||
|
mat(:, puti, putj) += coefs(:) * hij
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
else
|
||||||
|
h1 = h(1,1)
|
||||||
|
h2 = h(1,2)
|
||||||
|
do j = 1,2
|
||||||
|
putj = p(j, 2)
|
||||||
|
p2 = p(turn2(j), 2)
|
||||||
|
do i = 1,2
|
||||||
|
puti = p(i, 1)
|
||||||
|
|
||||||
|
if(banned(puti,putj,bant)) cycle
|
||||||
|
p1 = p(turn2(i), 1)
|
||||||
|
|
||||||
|
hij = mo_two_e_integral(p1, p2, h1, h2) * get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2,N_int)
|
||||||
|
mat(:, puti, putj) += coefs(:) * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end if
|
||||||
|
|
||||||
|
else
|
||||||
|
if(tip == 0) then
|
||||||
|
h1 = h(1, ma)
|
||||||
|
h2 = h(2, ma)
|
||||||
|
do i=1,3
|
||||||
|
puti = p(i, ma)
|
||||||
|
do j=i+1,4
|
||||||
|
putj = p(j, ma)
|
||||||
|
if(banned(puti,putj,1)) cycle
|
||||||
|
|
||||||
|
i1 = turn2d(1, i, j)
|
||||||
|
i2 = turn2d(2, i, j)
|
||||||
|
p1 = p(i1, ma)
|
||||||
|
p2 = p(i2, ma)
|
||||||
|
hij = (mo_two_e_integral(p1, p2, h1, h2) - mo_two_e_integral(p2,p1, h1, h2)) * get_phase_bi(phasemask, ma, ma, h1, p1, h2, p2,N_int)
|
||||||
|
mat(:, puti, putj) += coefs(:) * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
else if(tip == 3) then
|
||||||
|
h1 = h(1, mi)
|
||||||
|
h2 = h(1, ma)
|
||||||
|
p1 = p(1, mi)
|
||||||
|
do i=1,3
|
||||||
|
puti = p(turn3(1,i), ma)
|
||||||
|
putj = p(turn3(2,i), ma)
|
||||||
|
if(banned(puti,putj,1)) cycle
|
||||||
|
p2 = p(i, ma)
|
||||||
|
|
||||||
|
hij = mo_two_e_integral(p1, p2, h1, h2) * get_phase_bi(phasemask, mi, ma, h1, p1, h2, p2,N_int)
|
||||||
|
mat(:, min(puti, putj), max(puti, putj)) += coefs(:) * hij
|
||||||
|
end do
|
||||||
|
else ! tip == 4
|
||||||
|
puti = p(1, sp)
|
||||||
|
putj = p(2, sp)
|
||||||
|
if(.not. banned(puti,putj,1)) then
|
||||||
|
p1 = p(1, mi)
|
||||||
|
p2 = p(2, mi)
|
||||||
|
h1 = h(1, mi)
|
||||||
|
h2 = h(2, mi)
|
||||||
|
hij = (mo_two_e_integral(p1, p2, h1, h2) - mo_two_e_integral(p2,p1, h1, h2)) * get_phase_bi(phasemask, mi, mi, h1, p1, h2, p2,N_int)
|
||||||
|
mat(:, puti, putj) += coefs(:) * hij
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
end
|
||||||
|
|
||||||
|
|
||||||
|
@ -153,6 +153,13 @@ subroutine get_mo_two_e_integrals(j,k,l,sze,out_val,map)
|
|||||||
integer(key_kind) :: p,q,r,s,i2
|
integer(key_kind) :: p,q,r,s,i2
|
||||||
PROVIDE mo_two_e_integrals_in_map mo_integrals_cache
|
PROVIDE mo_two_e_integrals_in_map mo_integrals_cache
|
||||||
|
|
||||||
|
!DEBUG
|
||||||
|
! do i=1,sze
|
||||||
|
! out_val(i) = get_two_e_integral(i,j,k,l,map)
|
||||||
|
! enddo
|
||||||
|
! return
|
||||||
|
!DEBUG
|
||||||
|
|
||||||
ii0 = l-mo_integrals_cache_min
|
ii0 = l-mo_integrals_cache_min
|
||||||
ii0 = ior(ii0, k-mo_integrals_cache_min)
|
ii0 = ior(ii0, k-mo_integrals_cache_min)
|
||||||
ii0 = ior(ii0, j-mo_integrals_cache_min)
|
ii0 = ior(ii0, j-mo_integrals_cache_min)
|
||||||
|
Loading…
Reference in New Issue
Block a user