2019-07-05 15:39:27 +02:00
|
|
|
use bitmasks
|
2019-07-05 13:05:11 +02:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
subroutine get_mask_phase(det1, pm, Nint)
|
|
|
|
use bitmasks
|
|
|
|
implicit none
|
|
|
|
integer, intent(in) :: Nint
|
|
|
|
integer(bit_kind), intent(in) :: det1(Nint,2)
|
|
|
|
integer(bit_kind), intent(out) :: pm(Nint,2)
|
|
|
|
integer(bit_kind) :: tmp1, tmp2
|
|
|
|
integer :: i
|
|
|
|
tmp1 = 0_8
|
|
|
|
tmp2 = 0_8
|
2021-03-26 01:04:23 +01:00
|
|
|
select case (Nint)
|
|
|
|
|
|
|
|
BEGIN_TEMPLATE
|
|
|
|
case ($Nint)
|
|
|
|
do i=1,$Nint
|
|
|
|
pm(i,1) = ieor(det1(i,1), shiftl(det1(i,1), 1))
|
|
|
|
pm(i,2) = ieor(det1(i,2), shiftl(det1(i,2), 1))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 2))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 2))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 4))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 4))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 8))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 8))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 16))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 16))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 32))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 32))
|
|
|
|
pm(i,1) = ieor(pm(i,1), tmp1)
|
|
|
|
pm(i,2) = ieor(pm(i,2), tmp2)
|
|
|
|
if(iand(popcnt(det1(i,1)), 1) == 1) tmp1 = not(tmp1)
|
|
|
|
if(iand(popcnt(det1(i,2)), 1) == 1) tmp2 = not(tmp2)
|
|
|
|
end do
|
|
|
|
SUBST [ Nint ]
|
|
|
|
1;;
|
|
|
|
2;;
|
|
|
|
3;;
|
|
|
|
4;;
|
|
|
|
END_TEMPLATE
|
|
|
|
case default
|
|
|
|
do i=1,Nint
|
|
|
|
pm(i,1) = ieor(det1(i,1), shiftl(det1(i,1), 1))
|
|
|
|
pm(i,2) = ieor(det1(i,2), shiftl(det1(i,2), 1))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 2))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 2))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 4))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 4))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 8))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 8))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 16))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 16))
|
|
|
|
pm(i,1) = ieor(pm(i,1), shiftl(pm(i,1), 32))
|
|
|
|
pm(i,2) = ieor(pm(i,2), shiftl(pm(i,2), 32))
|
|
|
|
pm(i,1) = ieor(pm(i,1), tmp1)
|
|
|
|
pm(i,2) = ieor(pm(i,2), tmp2)
|
|
|
|
if(iand(popcnt(det1(i,1)), 1) == 1) tmp1 = not(tmp1)
|
|
|
|
if(iand(popcnt(det1(i,2)), 1) == 1) tmp2 = not(tmp2)
|
|
|
|
end do
|
|
|
|
end select
|
2019-01-25 11:39:31 +01:00
|
|
|
|
|
|
|
end subroutine
|
|
|
|
|
|
|
|
|
2020-08-29 01:15:48 +02:00
|
|
|
subroutine select_connected(i_generator,E0,pt2_data,b,subset,csubset)
|
2019-01-25 11:39:31 +01:00
|
|
|
use bitmasks
|
|
|
|
use selection_types
|
|
|
|
implicit none
|
|
|
|
integer, intent(in) :: i_generator, subset, csubset
|
|
|
|
type(selection_buffer), intent(inout) :: b
|
2020-08-29 01:15:48 +02:00
|
|
|
type(pt2_type), intent(inout) :: pt2_data
|
2019-01-25 11:39:31 +01:00
|
|
|
integer :: k,l
|
|
|
|
double precision, intent(in) :: E0(N_states)
|
|
|
|
|
|
|
|
integer(bit_kind) :: hole_mask(N_int,2), particle_mask(N_int,2)
|
|
|
|
|
|
|
|
double precision, allocatable :: fock_diag_tmp(:,:)
|
|
|
|
|
|
|
|
allocate(fock_diag_tmp(2,mo_num+1))
|
|
|
|
|
|
|
|
call build_fock_tmp(fock_diag_tmp,psi_det_generators(1,1,i_generator),N_int)
|
|
|
|
|
2019-10-24 18:53:02 +02:00
|
|
|
do k=1,N_int
|
|
|
|
hole_mask(k,1) = iand(generators_bitmask(k,1,s_hole), psi_det_generators(k,1,i_generator))
|
|
|
|
hole_mask(k,2) = iand(generators_bitmask(k,2,s_hole), psi_det_generators(k,2,i_generator))
|
|
|
|
particle_mask(k,1) = iand(generators_bitmask(k,1,s_part), not(psi_det_generators(k,1,i_generator)) )
|
|
|
|
particle_mask(k,2) = iand(generators_bitmask(k,2,s_part), not(psi_det_generators(k,2,i_generator)) )
|
2019-01-25 11:39:31 +01:00
|
|
|
enddo
|
2020-08-29 01:15:48 +02:00
|
|
|
call select_singles_and_doubles(i_generator,hole_mask,particle_mask,fock_diag_tmp,E0,pt2_data,b,subset,csubset)
|
2019-01-25 11:39:31 +01:00
|
|
|
deallocate(fock_diag_tmp)
|
|
|
|
end subroutine
|
|
|
|
|
|
|
|
|
|
|
|
double precision function get_phase_bi(phasemask, s1, s2, h1, p1, h2, p2, Nint)
|
|
|
|
use bitmasks
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
integer, intent(in) :: Nint
|
|
|
|
integer(bit_kind), intent(in) :: phasemask(Nint,2)
|
|
|
|
integer, intent(in) :: s1, s2, h1, h2, p1, p2
|
|
|
|
logical :: change
|
|
|
|
integer :: np
|
|
|
|
double precision, save :: res(0:1) = (/1d0, -1d0/)
|
|
|
|
|
|
|
|
integer :: h1_int, h2_int
|
|
|
|
integer :: p1_int, p2_int
|
|
|
|
integer :: h1_bit, h2_bit
|
|
|
|
integer :: p1_bit, p2_bit
|
|
|
|
h1_int = shiftr(h1-1,bit_kind_shift)+1
|
|
|
|
h1_bit = h1 - shiftl(h1_int-1,bit_kind_shift)-1
|
|
|
|
|
|
|
|
h2_int = shiftr(h2-1,bit_kind_shift)+1
|
|
|
|
h2_bit = h2 - shiftl(h2_int-1,bit_kind_shift)-1
|
|
|
|
|
|
|
|
p1_int = shiftr(p1-1,bit_kind_shift)+1
|
|
|
|
p1_bit = p1 - shiftl(p1_int-1,bit_kind_shift)-1
|
|
|
|
|
|
|
|
p2_int = shiftr(p2-1,bit_kind_shift)+1
|
|
|
|
p2_bit = p2 - shiftl(p2_int-1,bit_kind_shift)-1
|
|
|
|
|
|
|
|
|
|
|
|
! Put the phasemask bits at position 0, and add them all
|
|
|
|
h1_bit = int(shiftr(phasemask(h1_int,s1),h1_bit))
|
|
|
|
p1_bit = int(shiftr(phasemask(p1_int,s1),p1_bit))
|
|
|
|
h2_bit = int(shiftr(phasemask(h2_int,s2),h2_bit))
|
|
|
|
p2_bit = int(shiftr(phasemask(p2_int,s2),p2_bit))
|
|
|
|
|
|
|
|
np = h1_bit + p1_bit + h2_bit + p2_bit
|
|
|
|
|
|
|
|
if(p1 < h1) np = np + 1
|
|
|
|
if(p2 < h2) np = np + 1
|
|
|
|
|
|
|
|
if(s1 == s2 .and. max(h1, p1) > min(h2, p2)) np = np + 1
|
|
|
|
get_phase_bi = res(iand(np,1))
|
|
|
|
end
|
|
|
|
|
|
|
|
|
2020-08-29 01:15:48 +02:00
|
|
|
subroutine select_singles_and_doubles(i_generator,hole_mask,particle_mask,fock_diag_tmp,E0,pt2_data,buf,subset,csubset)
|
2019-01-25 11:39:31 +01:00
|
|
|
use bitmasks
|
|
|
|
use selection_types
|
|
|
|
implicit none
|
|
|
|
BEGIN_DOC
|
|
|
|
! WARNING /!\ : It is assumed that the generators and selectors are psi_det_sorted
|
|
|
|
END_DOC
|
|
|
|
|
|
|
|
integer, intent(in) :: i_generator, subset, csubset
|
|
|
|
integer(bit_kind), intent(in) :: hole_mask(N_int,2), particle_mask(N_int,2)
|
|
|
|
double precision, intent(in) :: fock_diag_tmp(mo_num)
|
|
|
|
double precision, intent(in) :: E0(N_states)
|
2020-08-29 01:15:48 +02:00
|
|
|
type(pt2_type), intent(inout) :: pt2_data
|
2019-01-25 11:39:31 +01:00
|
|
|
type(selection_buffer), intent(inout) :: buf
|
|
|
|
|
|
|
|
integer :: h1,h2,s1,s2,s3,i1,i2,ib,sp,k,i,j,nt,ii,sze
|
|
|
|
integer(bit_kind) :: hole(N_int,2), particle(N_int,2), mask(N_int, 2), pmask(N_int, 2)
|
|
|
|
logical :: fullMatch, ok
|
|
|
|
|
|
|
|
integer(bit_kind) :: mobMask(N_int, 2), negMask(N_int, 2)
|
|
|
|
integer,allocatable :: preinteresting(:), prefullinteresting(:)
|
|
|
|
integer,allocatable :: interesting(:), fullinteresting(:)
|
|
|
|
integer,allocatable :: tmp_array(:)
|
|
|
|
integer(bit_kind), allocatable :: minilist(:, :, :), fullminilist(:, :, :)
|
|
|
|
logical, allocatable :: banned(:,:,:), bannedOrb(:,:)
|
2019-07-08 13:13:48 +02:00
|
|
|
double precision, allocatable :: coef_fullminilist_rev(:,:)
|
2019-01-25 11:39:31 +01:00
|
|
|
|
|
|
|
|
|
|
|
double precision, allocatable :: mat(:,:,:)
|
|
|
|
|
|
|
|
logical :: monoAdo, monoBdo
|
|
|
|
integer :: maskInd
|
|
|
|
|
|
|
|
PROVIDE psi_bilinear_matrix_columns_loc psi_det_alpha_unique psi_det_beta_unique
|
|
|
|
PROVIDE psi_bilinear_matrix_rows psi_det_sorted_order psi_bilinear_matrix_order
|
|
|
|
PROVIDE psi_bilinear_matrix_transp_rows_loc psi_bilinear_matrix_transp_columns
|
|
|
|
PROVIDE psi_bilinear_matrix_transp_order psi_selectors_coef_transp
|
2020-09-23 18:58:07 +02:00
|
|
|
PROVIDE banned_excitation
|
2019-01-25 11:39:31 +01:00
|
|
|
|
|
|
|
monoAdo = .true.
|
|
|
|
monoBdo = .true.
|
2020-02-27 10:16:27 +01:00
|
|
|
|
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do k=1,N_int
|
|
|
|
hole (k,1) = iand(psi_det_generators(k,1,i_generator), hole_mask(k,1))
|
|
|
|
hole (k,2) = iand(psi_det_generators(k,2,i_generator), hole_mask(k,2))
|
|
|
|
particle(k,1) = iand(not(psi_det_generators(k,1,i_generator)), particle_mask(k,1))
|
|
|
|
particle(k,2) = iand(not(psi_det_generators(k,2,i_generator)), particle_mask(k,2))
|
|
|
|
enddo
|
2020-02-27 10:16:27 +01:00
|
|
|
|
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
integer :: N_holes(2), N_particles(2)
|
|
|
|
integer :: hole_list(N_int*bit_kind_size,2)
|
|
|
|
integer :: particle_list(N_int*bit_kind_size,2)
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
call bitstring_to_list_ab(hole , hole_list , N_holes , N_int)
|
|
|
|
call bitstring_to_list_ab(particle, particle_list, N_particles, N_int)
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
integer :: l_a, nmax, idx
|
|
|
|
integer, allocatable :: indices(:), exc_degree(:), iorder(:)
|
2022-04-08 17:21:03 +02:00
|
|
|
|
|
|
|
! Removed to avoid introducing determinants already presents in the wf
|
|
|
|
!double precision, parameter :: norm_thr = 1.d-16
|
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
allocate (indices(N_det), &
|
|
|
|
exc_degree(max(N_det_alpha_unique,N_det_beta_unique)))
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2020-12-12 01:33:40 +01:00
|
|
|
! Pre-compute excitation degrees wrt alpha determinants
|
2019-01-25 11:39:31 +01:00
|
|
|
k=1
|
|
|
|
do i=1,N_det_alpha_unique
|
|
|
|
call get_excitation_degree_spin(psi_det_alpha_unique(1,i), &
|
|
|
|
psi_det_generators(1,1,i_generator), exc_degree(i), N_int)
|
|
|
|
enddo
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2020-12-12 01:33:40 +01:00
|
|
|
! Iterate on 0SD beta, and find alphas 0SDTQ such that exc_degree <= 4
|
2019-01-25 11:39:31 +01:00
|
|
|
do j=1,N_det_beta_unique
|
|
|
|
call get_excitation_degree_spin(psi_det_beta_unique(1,j), &
|
|
|
|
psi_det_generators(1,2,i_generator), nt, N_int)
|
|
|
|
if (nt > 2) cycle
|
|
|
|
do l_a=psi_bilinear_matrix_columns_loc(j), psi_bilinear_matrix_columns_loc(j+1)-1
|
|
|
|
i = psi_bilinear_matrix_rows(l_a)
|
|
|
|
if (nt + exc_degree(i) <= 4) then
|
|
|
|
idx = psi_det_sorted_order(psi_bilinear_matrix_order(l_a))
|
2022-04-08 17:21:03 +02:00
|
|
|
! Removed to avoid introducing determinants already presents in the wf
|
|
|
|
!if (psi_average_norm_contrib_sorted(idx) > norm_thr) then
|
2019-11-18 20:06:05 +01:00
|
|
|
indices(k) = idx
|
|
|
|
k=k+1
|
2022-04-08 17:21:03 +02:00
|
|
|
!endif
|
2019-01-25 11:39:31 +01:00
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
enddo
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2020-12-12 01:33:40 +01:00
|
|
|
! Pre-compute excitation degrees wrt beta determinants
|
2019-01-25 11:39:31 +01:00
|
|
|
do i=1,N_det_beta_unique
|
|
|
|
call get_excitation_degree_spin(psi_det_beta_unique(1,i), &
|
|
|
|
psi_det_generators(1,2,i_generator), exc_degree(i), N_int)
|
|
|
|
enddo
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2020-12-12 01:33:40 +01:00
|
|
|
! Iterate on 0S alpha, and find betas TQ such that exc_degree <= 4
|
|
|
|
! Remove also contributions < 1.d-20)
|
2019-01-25 11:39:31 +01:00
|
|
|
do j=1,N_det_alpha_unique
|
|
|
|
call get_excitation_degree_spin(psi_det_alpha_unique(1,j), &
|
|
|
|
psi_det_generators(1,1,i_generator), nt, N_int)
|
|
|
|
if (nt > 1) cycle
|
|
|
|
do l_a=psi_bilinear_matrix_transp_rows_loc(j), psi_bilinear_matrix_transp_rows_loc(j+1)-1
|
|
|
|
i = psi_bilinear_matrix_transp_columns(l_a)
|
|
|
|
if (exc_degree(i) < 3) cycle
|
|
|
|
if (nt + exc_degree(i) <= 4) then
|
|
|
|
idx = psi_det_sorted_order( &
|
|
|
|
psi_bilinear_matrix_order( &
|
|
|
|
psi_bilinear_matrix_transp_order(l_a)))
|
2022-04-08 17:21:03 +02:00
|
|
|
! Removed to avoid introducing determinants already presents in the wf
|
|
|
|
!if (psi_average_norm_contrib_sorted(idx) > norm_thr) then
|
2019-11-18 20:06:05 +01:00
|
|
|
indices(k) = idx
|
|
|
|
k=k+1
|
2022-04-08 17:21:03 +02:00
|
|
|
!endif
|
2019-01-25 11:39:31 +01:00
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
enddo
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
deallocate(exc_degree)
|
|
|
|
nmax=k-1
|
2019-01-31 17:23:47 +01:00
|
|
|
|
2021-05-31 01:48:34 +02:00
|
|
|
call isort_noidx(indices,nmax)
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-10-30 15:28:46 +01:00
|
|
|
! Start with 32 elements. Size will double along with the filtering.
|
2019-01-25 11:39:31 +01:00
|
|
|
allocate(preinteresting(0:32), prefullinteresting(0:32), &
|
|
|
|
interesting(0:32), fullinteresting(0:32))
|
2019-01-31 17:23:47 +01:00
|
|
|
preinteresting(:) = 0
|
|
|
|
prefullinteresting(:) = 0
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do i=1,N_int
|
|
|
|
negMask(i,1) = not(psi_det_generators(i,1,i_generator))
|
|
|
|
negMask(i,2) = not(psi_det_generators(i,2,i_generator))
|
|
|
|
end do
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do k=1,nmax
|
|
|
|
i = indices(k)
|
|
|
|
mobMask(1,1) = iand(negMask(1,1), psi_det_sorted(1,1,i))
|
|
|
|
mobMask(1,2) = iand(negMask(1,2), psi_det_sorted(1,2,i))
|
|
|
|
nt = popcnt(mobMask(1, 1)) + popcnt(mobMask(1, 2))
|
|
|
|
do j=2,N_int
|
|
|
|
mobMask(j,1) = iand(negMask(j,1), psi_det_sorted(j,1,i))
|
|
|
|
mobMask(j,2) = iand(negMask(j,2), psi_det_sorted(j,2,i))
|
|
|
|
nt = nt + popcnt(mobMask(j, 1)) + popcnt(mobMask(j, 2))
|
|
|
|
end do
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
if(nt <= 4) then
|
|
|
|
if(i <= N_det_selectors) then
|
2020-02-27 10:16:27 +01:00
|
|
|
sze = preinteresting(0)
|
2019-01-25 11:39:31 +01:00
|
|
|
if (sze+1 == size(preinteresting)) then
|
|
|
|
allocate (tmp_array(0:sze))
|
|
|
|
tmp_array(0:sze) = preinteresting(0:sze)
|
|
|
|
deallocate(preinteresting)
|
|
|
|
allocate(preinteresting(0:2*sze))
|
|
|
|
preinteresting(0:sze) = tmp_array(0:sze)
|
|
|
|
deallocate(tmp_array)
|
|
|
|
endif
|
|
|
|
preinteresting(0) = sze+1
|
|
|
|
preinteresting(sze+1) = i
|
|
|
|
else if(nt <= 2) then
|
2020-02-27 10:16:27 +01:00
|
|
|
sze = prefullinteresting(0)
|
2019-01-25 11:39:31 +01:00
|
|
|
if (sze+1 == size(prefullinteresting)) then
|
|
|
|
allocate (tmp_array(0:sze))
|
|
|
|
tmp_array(0:sze) = prefullinteresting(0:sze)
|
|
|
|
deallocate(prefullinteresting)
|
|
|
|
allocate(prefullinteresting(0:2*sze))
|
|
|
|
prefullinteresting(0:sze) = tmp_array(0:sze)
|
|
|
|
deallocate(tmp_array)
|
|
|
|
endif
|
|
|
|
prefullinteresting(0) = sze+1
|
|
|
|
prefullinteresting(sze+1) = i
|
|
|
|
end if
|
|
|
|
end if
|
|
|
|
end do
|
|
|
|
deallocate(indices)
|
2019-02-22 19:19:58 +01:00
|
|
|
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
allocate(banned(mo_num, mo_num,2), bannedOrb(mo_num, 2))
|
|
|
|
allocate (mat(N_states, mo_num, mo_num))
|
|
|
|
maskInd = -1
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
integer :: nb_count, maskInd_save
|
|
|
|
logical :: monoBdo_save
|
|
|
|
logical :: found
|
|
|
|
do s1=1,2
|
|
|
|
do i1=N_holes(s1),1,-1 ! Generate low excitations first
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
found = .False.
|
|
|
|
monoBdo_save = monoBdo
|
|
|
|
maskInd_save = maskInd
|
|
|
|
do s2=s1,2
|
|
|
|
ib = 1
|
|
|
|
if(s1 == s2) ib = i1+1
|
|
|
|
do i2=N_holes(s2),ib,-1
|
|
|
|
maskInd = maskInd + 1
|
|
|
|
if(mod(maskInd, csubset) == (subset-1)) then
|
|
|
|
found = .True.
|
|
|
|
end if
|
|
|
|
enddo
|
|
|
|
if(s1 /= s2) monoBdo = .false.
|
|
|
|
enddo
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
if (.not.found) cycle
|
|
|
|
monoBdo = monoBdo_save
|
|
|
|
maskInd = maskInd_save
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
h1 = hole_list(i1,s1)
|
|
|
|
call apply_hole(psi_det_generators(1,1,i_generator), s1,h1, pmask, ok, N_int)
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
negMask = not(pmask)
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
interesting(0) = 0
|
|
|
|
fullinteresting(0) = 0
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do ii=1,preinteresting(0)
|
2020-02-27 10:16:27 +01:00
|
|
|
i = preinteresting(ii)
|
2019-01-25 11:39:31 +01:00
|
|
|
select case (N_int)
|
|
|
|
case (1)
|
2019-11-18 20:06:05 +01:00
|
|
|
mobMask(1,1) = iand(negMask(1,1), psi_det_sorted(1,1,i))
|
|
|
|
mobMask(1,2) = iand(negMask(1,2), psi_det_sorted(1,2,i))
|
2019-01-25 11:39:31 +01:00
|
|
|
nt = popcnt(mobMask(1, 1)) + popcnt(mobMask(1, 2))
|
|
|
|
case (2)
|
2019-11-18 20:06:05 +01:00
|
|
|
mobMask(1:2,1) = iand(negMask(1:2,1), psi_det_sorted(1:2,1,i))
|
|
|
|
mobMask(1:2,2) = iand(negMask(1:2,2), psi_det_sorted(1:2,2,i))
|
2019-01-25 11:39:31 +01:00
|
|
|
nt = popcnt(mobMask(1, 1)) + popcnt(mobMask(1, 2)) + &
|
|
|
|
popcnt(mobMask(2, 1)) + popcnt(mobMask(2, 2))
|
|
|
|
case (3)
|
2019-11-18 20:06:05 +01:00
|
|
|
mobMask(1:3,1) = iand(negMask(1:3,1), psi_det_sorted(1:3,1,i))
|
|
|
|
mobMask(1:3,2) = iand(negMask(1:3,2), psi_det_sorted(1:3,2,i))
|
2019-01-25 11:39:31 +01:00
|
|
|
nt = 0
|
|
|
|
do j=3,1,-1
|
|
|
|
if (mobMask(j,1) /= 0_bit_kind) then
|
|
|
|
nt = nt+ popcnt(mobMask(j, 1))
|
|
|
|
if (nt > 4) exit
|
|
|
|
endif
|
|
|
|
if (mobMask(j,2) /= 0_bit_kind) then
|
|
|
|
nt = nt+ popcnt(mobMask(j, 2))
|
|
|
|
if (nt > 4) exit
|
|
|
|
endif
|
|
|
|
end do
|
|
|
|
case (4)
|
2019-11-18 20:06:05 +01:00
|
|
|
mobMask(1:4,1) = iand(negMask(1:4,1), psi_det_sorted(1:4,1,i))
|
|
|
|
mobMask(1:4,2) = iand(negMask(1:4,2), psi_det_sorted(1:4,2,i))
|
2019-01-25 11:39:31 +01:00
|
|
|
nt = 0
|
|
|
|
do j=4,1,-1
|
|
|
|
if (mobMask(j,1) /= 0_bit_kind) then
|
|
|
|
nt = nt+ popcnt(mobMask(j, 1))
|
|
|
|
if (nt > 4) exit
|
|
|
|
endif
|
|
|
|
if (mobMask(j,2) /= 0_bit_kind) then
|
|
|
|
nt = nt+ popcnt(mobMask(j, 2))
|
|
|
|
if (nt > 4) exit
|
|
|
|
endif
|
|
|
|
end do
|
2019-10-30 15:28:46 +01:00
|
|
|
case default
|
2019-11-18 20:06:05 +01:00
|
|
|
mobMask(1:N_int,1) = iand(negMask(1:N_int,1), psi_det_sorted(1:N_int,1,i))
|
|
|
|
mobMask(1:N_int,2) = iand(negMask(1:N_int,2), psi_det_sorted(1:N_int,2,i))
|
2019-01-25 11:39:31 +01:00
|
|
|
nt = 0
|
|
|
|
do j=N_int,1,-1
|
|
|
|
if (mobMask(j,1) /= 0_bit_kind) then
|
|
|
|
nt = nt+ popcnt(mobMask(j, 1))
|
|
|
|
if (nt > 4) exit
|
|
|
|
endif
|
|
|
|
if (mobMask(j,2) /= 0_bit_kind) then
|
|
|
|
nt = nt+ popcnt(mobMask(j, 2))
|
|
|
|
if (nt > 4) exit
|
|
|
|
endif
|
|
|
|
end do
|
|
|
|
end select
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
if(nt <= 4) then
|
2020-02-27 10:16:27 +01:00
|
|
|
sze = interesting(0)
|
2019-01-25 11:39:31 +01:00
|
|
|
if (sze+1 == size(interesting)) then
|
|
|
|
allocate (tmp_array(0:sze))
|
|
|
|
tmp_array(0:sze) = interesting(0:sze)
|
|
|
|
deallocate(interesting)
|
|
|
|
allocate(interesting(0:2*sze))
|
|
|
|
interesting(0:sze) = tmp_array(0:sze)
|
|
|
|
deallocate(tmp_array)
|
|
|
|
endif
|
|
|
|
interesting(0) = sze+1
|
|
|
|
interesting(sze+1) = i
|
|
|
|
if(nt <= 2) then
|
2020-02-27 10:16:27 +01:00
|
|
|
sze = fullinteresting(0)
|
2019-01-25 11:39:31 +01:00
|
|
|
if (sze+1 == size(fullinteresting)) then
|
|
|
|
allocate (tmp_array(0:sze))
|
|
|
|
tmp_array(0:sze) = fullinteresting(0:sze)
|
|
|
|
deallocate(fullinteresting)
|
|
|
|
allocate(fullinteresting(0:2*sze))
|
|
|
|
fullinteresting(0:sze) = tmp_array(0:sze)
|
|
|
|
deallocate(tmp_array)
|
|
|
|
endif
|
|
|
|
fullinteresting(0) = sze+1
|
|
|
|
fullinteresting(sze+1) = i
|
|
|
|
end if
|
|
|
|
end if
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
end do
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do ii=1,prefullinteresting(0)
|
|
|
|
i = prefullinteresting(ii)
|
|
|
|
nt = 0
|
|
|
|
mobMask(1,1) = iand(negMask(1,1), psi_det_sorted(1,1,i))
|
|
|
|
mobMask(1,2) = iand(negMask(1,2), psi_det_sorted(1,2,i))
|
|
|
|
nt = popcnt(mobMask(1, 1)) + popcnt(mobMask(1, 2))
|
|
|
|
if (nt > 2) cycle
|
|
|
|
do j=N_int,2,-1
|
|
|
|
mobMask(j,1) = iand(negMask(j,1), psi_det_sorted(j,1,i))
|
|
|
|
mobMask(j,2) = iand(negMask(j,2), psi_det_sorted(j,2,i))
|
|
|
|
nt = nt+ popcnt(mobMask(j, 1)) + popcnt(mobMask(j, 2))
|
|
|
|
if (nt > 2) exit
|
|
|
|
end do
|
|
|
|
|
|
|
|
if(nt <= 2) then
|
2020-02-27 10:16:27 +01:00
|
|
|
sze = fullinteresting(0)
|
2019-01-25 11:39:31 +01:00
|
|
|
if (sze+1 == size(fullinteresting)) then
|
|
|
|
allocate (tmp_array(0:sze))
|
|
|
|
tmp_array(0:sze) = fullinteresting(0:sze)
|
|
|
|
deallocate(fullinteresting)
|
|
|
|
allocate(fullinteresting(0:2*sze))
|
|
|
|
fullinteresting(0:sze) = tmp_array(0:sze)
|
|
|
|
deallocate(tmp_array)
|
|
|
|
endif
|
|
|
|
fullinteresting(0) = sze+1
|
|
|
|
fullinteresting(sze+1) = i
|
|
|
|
end if
|
|
|
|
end do
|
|
|
|
allocate (fullminilist (N_int, 2, fullinteresting(0)), &
|
|
|
|
minilist (N_int, 2, interesting(0)) )
|
2019-11-18 20:06:05 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do i=1,fullinteresting(0)
|
2022-03-09 10:23:27 +01:00
|
|
|
fullminilist(:,:,i) = psi_det_sorted(:,:,fullinteresting(i))
|
2019-01-25 11:39:31 +01:00
|
|
|
enddo
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do i=1,interesting(0)
|
2022-03-09 10:23:27 +01:00
|
|
|
minilist(:,:,i) = psi_det_sorted(:,:,interesting(i))
|
2019-01-25 11:39:31 +01:00
|
|
|
enddo
|
|
|
|
|
|
|
|
do s2=s1,2
|
|
|
|
sp = s1
|
|
|
|
|
|
|
|
if(s1 /= s2) sp = 3
|
|
|
|
|
|
|
|
ib = 1
|
|
|
|
if(s1 == s2) ib = i1+1
|
|
|
|
monoAdo = .true.
|
|
|
|
do i2=N_holes(s2),ib,-1 ! Generate low excitations first
|
|
|
|
|
|
|
|
h2 = hole_list(i2,s2)
|
|
|
|
call apply_hole(pmask, s2,h2, mask, ok, N_int)
|
2020-09-23 18:58:07 +02:00
|
|
|
banned(:,:,1) = banned_excitation(:,:)
|
|
|
|
banned(:,:,2) = banned_excitation(:,:)
|
2019-01-25 11:39:31 +01:00
|
|
|
do j=1,mo_num
|
|
|
|
bannedOrb(j, 1) = .true.
|
|
|
|
bannedOrb(j, 2) = .true.
|
|
|
|
enddo
|
|
|
|
do s3=1,2
|
|
|
|
do i=1,N_particles(s3)
|
|
|
|
bannedOrb(particle_list(i,s3), s3) = .false.
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
if(s1 /= s2) then
|
|
|
|
if(monoBdo) then
|
|
|
|
bannedOrb(h1,s1) = .false.
|
|
|
|
end if
|
|
|
|
if(monoAdo) then
|
|
|
|
bannedOrb(h2,s2) = .false.
|
|
|
|
monoAdo = .false.
|
|
|
|
end if
|
|
|
|
end if
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
maskInd = maskInd + 1
|
|
|
|
if(mod(maskInd, csubset) == (subset-1)) then
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
call spot_isinwf(mask, fullminilist, i_generator, fullinteresting(0), banned, fullMatch, fullinteresting)
|
|
|
|
if(fullMatch) cycle
|
2020-02-27 10:16:27 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
call splash_pq(mask, sp, minilist, i_generator, interesting(0), bannedOrb, banned, mat, interesting)
|
2023-03-15 11:55:03 +01:00
|
|
|
call fill_buffer_double(i_generator, sp, h1, h2, bannedOrb, banned, fock_diag_tmp, E0, pt2_data, mat, buf)
|
2019-01-25 11:39:31 +01:00
|
|
|
end if
|
|
|
|
enddo
|
|
|
|
if(s1 /= s2) monoBdo = .false.
|
|
|
|
enddo
|
|
|
|
deallocate(fullminilist,minilist)
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
deallocate(preinteresting, prefullinteresting, interesting, fullinteresting)
|
|
|
|
deallocate(banned, bannedOrb,mat)
|
|
|
|
end subroutine
|
2020-08-29 01:15:48 +02:00
|
|
|
subroutine fill_buffer_double(i_generator, sp, h1, h2, bannedOrb, banned, fock_diag_tmp, E0, pt2_data, mat, buf)
|
2019-01-25 11:39:31 +01:00
|
|
|
use bitmasks
|
|
|
|
use selection_types
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
integer, intent(in) :: i_generator, sp, h1, h2
|
|
|
|
double precision, intent(in) :: mat(N_states, mo_num, mo_num)
|
|
|
|
logical, intent(in) :: bannedOrb(mo_num, 2), banned(mo_num, mo_num)
|
2020-08-29 01:15:48 +02:00
|
|
|
double precision, intent(in) :: fock_diag_tmp(mo_num)
|
2019-01-25 11:39:31 +01:00
|
|
|
double precision, intent(in) :: E0(N_states)
|
2020-08-29 01:15:48 +02:00
|
|
|
type(pt2_type), intent(inout) :: pt2_data
|
2019-01-25 11:39:31 +01:00
|
|
|
type(selection_buffer), intent(inout) :: buf
|
|
|
|
logical :: ok
|
2020-08-29 01:15:48 +02:00
|
|
|
integer :: s1, s2, p1, p2, ib, j, istate, jstate
|
2019-01-25 11:39:31 +01:00
|
|
|
integer(bit_kind) :: mask(N_int, 2), det(N_int, 2)
|
2020-09-23 18:58:07 +02:00
|
|
|
double precision :: e_pert(N_states), coef(N_states)
|
2020-09-03 11:09:25 +02:00
|
|
|
double precision :: delta_E, val, Hii, w, tmp, alpha_h_psi
|
2019-01-25 11:39:31 +01:00
|
|
|
double precision, external :: diag_H_mat_elem_fock
|
|
|
|
double precision :: E_shift
|
2020-09-03 16:16:16 +02:00
|
|
|
double precision :: s_weight(N_states,N_states)
|
2020-12-22 01:36:04 +01:00
|
|
|
PROVIDE dominant_dets_of_cfgs N_dominant_dets_of_cfgs
|
2020-09-03 16:16:16 +02:00
|
|
|
do jstate=1,N_states
|
|
|
|
do istate=1,N_states
|
|
|
|
s_weight(istate,jstate) = dsqrt(selection_weight(istate)*selection_weight(jstate))
|
|
|
|
enddo
|
|
|
|
enddo
|
2019-01-25 11:39:31 +01:00
|
|
|
|
|
|
|
if(sp == 3) then
|
|
|
|
s1 = 1
|
|
|
|
s2 = 2
|
|
|
|
else
|
|
|
|
s1 = sp
|
|
|
|
s2 = sp
|
|
|
|
end if
|
|
|
|
call apply_holes(psi_det_generators(1,1,i_generator), s1, h1, s2, h2, mask, ok, N_int)
|
|
|
|
E_shift = 0.d0
|
|
|
|
|
2020-12-08 18:44:53 +01:00
|
|
|
if (h0_type == 'CFG') then
|
|
|
|
j = det_to_configuration(i_generator)
|
|
|
|
E_shift = psi_det_Hii(i_generator) - psi_configuration_Hii(j)
|
2019-01-25 11:39:31 +01:00
|
|
|
endif
|
|
|
|
|
|
|
|
do p1=1,mo_num
|
|
|
|
if(bannedOrb(p1, s1)) cycle
|
|
|
|
ib = 1
|
|
|
|
if(sp /= 3) ib = p1+1
|
|
|
|
|
|
|
|
do p2=ib,mo_num
|
|
|
|
|
|
|
|
! -----
|
|
|
|
! /!\ Generating only single excited determinants doesn't work because a
|
|
|
|
! determinant generated by a single excitation may be doubly excited wrt
|
|
|
|
! to a determinant of the future. In that case, the determinant will be
|
|
|
|
! detected as already generated when generating in the future with a
|
|
|
|
! double excitation.
|
|
|
|
! -----
|
|
|
|
|
|
|
|
if(bannedOrb(p2, s2)) cycle
|
|
|
|
if(banned(p1,p2)) cycle
|
|
|
|
|
2020-12-15 23:46:19 +01:00
|
|
|
if(pseudo_sym)then
|
|
|
|
if(dabs(mat(1, p1, p2)).lt.thresh_sym)then
|
|
|
|
w = 0.d0
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
|
2019-11-18 20:06:05 +01:00
|
|
|
val = maxval(abs(mat(1:N_states, p1, p2)))
|
|
|
|
if( val == 0d0) cycle
|
2019-01-25 11:39:31 +01:00
|
|
|
call apply_particles(mask, s1, p1, s2, p2, det, ok, N_int)
|
|
|
|
|
2019-06-24 15:32:26 +02:00
|
|
|
if (do_only_cas) then
|
|
|
|
integer, external :: number_of_holes, number_of_particles
|
|
|
|
if (number_of_particles(det)>0) then
|
|
|
|
cycle
|
|
|
|
endif
|
|
|
|
if (number_of_holes(det)>0) then
|
|
|
|
cycle
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
if (do_ddci) then
|
|
|
|
logical, external :: is_a_two_holes_two_particles
|
|
|
|
if (is_a_two_holes_two_particles(det)) then
|
|
|
|
cycle
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
|
|
|
|
if (do_only_1h1p) then
|
|
|
|
logical, external :: is_a_1h1p
|
|
|
|
if (.not.is_a_1h1p(det)) cycle
|
|
|
|
endif
|
|
|
|
|
2020-12-10 18:22:16 +01:00
|
|
|
if (seniority_max >= 0) then
|
|
|
|
integer :: s
|
|
|
|
s = 0
|
|
|
|
do k=1,N_int
|
|
|
|
s = s + popcnt(ieor(det(k,1),det(k,2)))
|
|
|
|
enddo
|
|
|
|
|
|
|
|
if (s > seniority_max) cycle
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
2020-12-22 00:27:09 +01:00
|
|
|
integer :: degree
|
|
|
|
logical :: do_cycle
|
2020-12-10 18:22:16 +01:00
|
|
|
if (excitation_max >= 0) then
|
2020-12-22 00:27:09 +01:00
|
|
|
do_cycle = .True.
|
2021-04-29 14:43:02 +02:00
|
|
|
if (excitation_ref == 1) then
|
|
|
|
call get_excitation_degree(HF_bitmask,det(1,1),degree,N_int)
|
2020-12-22 01:36:04 +01:00
|
|
|
do_cycle = do_cycle .and. (degree > excitation_max)
|
2021-04-29 14:43:02 +02:00
|
|
|
else if (excitation_ref == 2) then
|
|
|
|
do k=1,N_dominant_dets_of_cfgs
|
|
|
|
call get_excitation_degree(dominant_dets_of_cfgs(1,1,k),det(1,1),degree,N_int)
|
|
|
|
do_cycle = do_cycle .and. (degree > excitation_max)
|
|
|
|
enddo
|
|
|
|
endif
|
2020-12-22 00:27:09 +01:00
|
|
|
if (do_cycle) cycle
|
2020-12-10 18:22:16 +01:00
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
|
|
if (excitation_alpha_max >= 0) then
|
2020-12-22 00:27:09 +01:00
|
|
|
do_cycle = .True.
|
2021-04-29 14:43:02 +02:00
|
|
|
if (excitation_ref == 1) then
|
|
|
|
call get_excitation_degree_spin(HF_bitmask,det(1,1),degree,N_int)
|
|
|
|
do_cycle = do_cycle .and. (degree > excitation_max)
|
|
|
|
else if (excitation_ref == 2) then
|
|
|
|
do k=1,N_dominant_dets_of_cfgs
|
|
|
|
call get_excitation_degree_spin(dominant_dets_of_cfgs(1,1,k),det(1,1),degree,N_int)
|
|
|
|
do_cycle = do_cycle .and. (degree > excitation_alpha_max)
|
|
|
|
enddo
|
|
|
|
endif
|
2020-12-22 00:27:09 +01:00
|
|
|
if (do_cycle) cycle
|
2020-12-10 18:22:16 +01:00
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
|
|
if (excitation_beta_max >= 0) then
|
2020-12-22 00:27:09 +01:00
|
|
|
do_cycle = .True.
|
2021-04-29 14:43:02 +02:00
|
|
|
if (excitation_ref == 1) then
|
|
|
|
call get_excitation_degree_spin(HF_bitmask,det(1,2),degree,N_int)
|
|
|
|
do_cycle = do_cycle .and. (degree > excitation_max)
|
|
|
|
else if (excitation_ref == 2) then
|
|
|
|
do k=1,N_dominant_dets_of_cfgs
|
|
|
|
call get_excitation_degree(dominant_dets_of_cfgs(1,2,k),det(1,2),degree,N_int)
|
|
|
|
do_cycle = do_cycle .and. (degree > excitation_beta_max)
|
|
|
|
enddo
|
|
|
|
endif
|
2020-12-22 00:27:09 +01:00
|
|
|
if (do_cycle) cycle
|
2020-12-10 18:22:16 +01:00
|
|
|
endif
|
|
|
|
|
2022-04-13 13:25:39 +02:00
|
|
|
if (twice_hierarchy_max >= 0) then
|
|
|
|
s = 0
|
|
|
|
do k=1,N_int
|
|
|
|
s = s + popcnt(ieor(det(k,1),det(k,2)))
|
|
|
|
enddo
|
|
|
|
if ( mod(s,2)>0 ) stop 'For now, hierarchy CI is defined only for an even number of electrons'
|
|
|
|
if (excitation_ref == 1) then
|
|
|
|
call get_excitation_degree(HF_bitmask,det(1,1),degree,N_int)
|
|
|
|
else if (excitation_ref == 2) then
|
|
|
|
stop 'For now, hierarchy CI is defined only for a single reference determinant'
|
|
|
|
! do k=1,N_dominant_dets_of_cfgs
|
|
|
|
! call get_excitation_degree(dominant_dets_of_cfgs(1,1,k),det(1,1),degree,N_int)
|
|
|
|
! enddo
|
|
|
|
endif
|
|
|
|
integer :: twice_hierarchy
|
|
|
|
twice_hierarchy = degree + s/2
|
2022-04-13 13:32:14 +02:00
|
|
|
if (twice_hierarchy > twice_hierarchy_max) cycle
|
2022-04-13 13:25:39 +02:00
|
|
|
endif
|
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
Hii = diag_H_mat_elem_fock(psi_det_generators(1,1,i_generator),det,fock_diag_tmp,N_int)
|
|
|
|
|
2019-10-24 13:55:38 +02:00
|
|
|
w = 0d0
|
|
|
|
|
2020-09-23 18:58:07 +02:00
|
|
|
e_pert = 0.d0
|
|
|
|
coef = 0.d0
|
|
|
|
logical :: do_diag
|
|
|
|
do_diag = .False.
|
2019-10-29 01:22:42 +01:00
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
do istate=1,N_states
|
|
|
|
delta_E = E0(istate) - Hii + E_shift
|
|
|
|
alpha_h_psi = mat(istate, p1, p2)
|
2020-09-23 18:58:07 +02:00
|
|
|
if (alpha_h_psi == 0.d0) cycle
|
|
|
|
|
2019-01-25 11:39:31 +01:00
|
|
|
val = alpha_h_psi + alpha_h_psi
|
|
|
|
tmp = dsqrt(delta_E * delta_E + val * val)
|
|
|
|
if (delta_E < 0.d0) then
|
|
|
|
tmp = -tmp
|
|
|
|
endif
|
2023-02-08 14:44:49 +01:00
|
|
|
|
|
|
|
!e_pert(istate) = alpha_h_psi * alpha_h_psi / (E0(istate) - Hii)
|
2020-09-03 11:09:25 +02:00
|
|
|
e_pert(istate) = 0.5d0 * (tmp - delta_E)
|
2023-02-08 14:44:49 +01:00
|
|
|
|
2019-10-24 13:55:38 +02:00
|
|
|
if (dabs(alpha_h_psi) > 1.d-4) then
|
2020-09-03 11:09:25 +02:00
|
|
|
coef(istate) = e_pert(istate) / alpha_h_psi
|
2019-10-24 13:55:38 +02:00
|
|
|
else
|
2020-08-29 01:15:48 +02:00
|
|
|
coef(istate) = alpha_h_psi / delta_E
|
2019-10-24 13:55:38 +02:00
|
|
|
endif
|
2020-08-29 01:15:48 +02:00
|
|
|
enddo
|
|
|
|
|
2021-02-17 00:46:58 +01:00
|
|
|
do_diag = sum(dabs(coef)) > 0.001d0 .and. N_states > 1
|
2020-09-23 18:58:07 +02:00
|
|
|
|
|
|
|
double precision :: eigvalues(N_states+1)
|
|
|
|
double precision :: work(1+6*(N_states+1)+2*(N_states+1)**2)
|
2021-05-17 15:08:44 +02:00
|
|
|
integer :: info, k , iwork(N_states+1)
|
2020-09-23 18:58:07 +02:00
|
|
|
|
|
|
|
if (do_diag) then
|
|
|
|
double precision :: pt2_matrix(N_states+1,N_states+1)
|
|
|
|
pt2_matrix(N_states+1,N_states+1) = Hii+E_shift
|
|
|
|
do istate=1,N_states
|
|
|
|
pt2_matrix(:,istate) = 0.d0
|
|
|
|
pt2_matrix(istate,istate) = E0(istate)
|
|
|
|
pt2_matrix(istate,N_states+1) = mat(istate,p1,p2)
|
|
|
|
pt2_matrix(N_states+1,istate) = mat(istate,p1,p2)
|
|
|
|
enddo
|
|
|
|
|
2021-05-17 15:08:44 +02:00
|
|
|
call DSYEV( 'V', 'U', N_states+1, pt2_matrix, N_states+1, eigvalues, &
|
|
|
|
work, size(work), info )
|
2020-09-23 18:58:07 +02:00
|
|
|
if (info /= 0) then
|
|
|
|
print *, 'error in '//irp_here
|
|
|
|
stop -1
|
|
|
|
endif
|
|
|
|
pt2_matrix = dabs(pt2_matrix)
|
2020-10-24 14:11:04 +02:00
|
|
|
iwork(1:N_states+1) = maxloc(pt2_matrix,DIM=1)
|
2020-09-23 18:58:07 +02:00
|
|
|
do k=1,N_states
|
2021-05-17 15:08:44 +02:00
|
|
|
e_pert(k) = eigvalues(iwork(k)) - E0(k)
|
2020-09-23 18:58:07 +02:00
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
|
|
|
|
|
|
|
|
|
2020-09-02 18:50:30 +02:00
|
|
|
! ! Gram-Schmidt using input overlap matrix
|
|
|
|
! do istate=1,N_states
|
|
|
|
! do jstate=1,istate-1
|
|
|
|
! if ( (pt2_overlap(jstate,istate) == 0.d0).or.(pt2_overlap(jstate,jstate) == 0.d0) ) cycle
|
|
|
|
! coef(istate) = coef(istate) - pt2_overlap(jstate,istate)/pt2_overlap(jstate,jstate) * coef(jstate)
|
|
|
|
! enddo
|
|
|
|
! enddo
|
2020-08-29 01:15:48 +02:00
|
|
|
|
2020-09-02 10:47:29 +02:00
|
|
|
do istate=1, N_states
|
2020-08-29 01:15:48 +02:00
|
|
|
|
|
|
|
alpha_h_psi = mat(istate, p1, p2)
|
|
|
|
|
2021-01-21 10:00:53 +01:00
|
|
|
pt2_data % overlap(:,istate) = pt2_data % overlap(:,istate) + coef(:) * coef(istate)
|
|
|
|
pt2_data % variance(istate) = pt2_data % variance(istate) + alpha_h_psi * alpha_h_psi
|
|
|
|
pt2_data % pt2(istate) = pt2_data % pt2(istate) + e_pert(istate)
|
2019-01-25 11:39:31 +01:00
|
|
|
|