mirror of
https://github.com/LCPQ/quantum_package
synced 2025-01-03 10:05:57 +01:00
Remove dead code
This commit is contained in:
parent
20a857c446
commit
9cb9139537
@ -61,100 +61,3 @@ END_PROVIDER
|
||||
END_PROVIDER
|
||||
|
||||
|
||||
BEGIN_PROVIDER [ integer(bit_kind), psi_selectors_ab, (N_int,2,psi_selectors_size) ]
|
||||
&BEGIN_PROVIDER [ double precision, psi_selectors_coef_ab, (psi_selectors_size,N_states) ]
|
||||
&BEGIN_PROVIDER [ integer, psi_selectors_next_ab, (2,psi_selectors_size) ]
|
||||
implicit none
|
||||
BEGIN_DOC
|
||||
! Determinants on which we apply <i|H|j>.
|
||||
! They are sorted by the 3 highest electrons in the alpha part,
|
||||
! then by the 3 highest electrons in the beta part to accelerate
|
||||
! the research of connected determinants.
|
||||
END_DOC
|
||||
integer :: i,j,k
|
||||
integer, allocatable :: iorder(:)
|
||||
integer*8, allocatable :: bit_tmp(:)
|
||||
integer*8, external :: det_search_key
|
||||
|
||||
allocate ( iorder(N_det_selectors), bit_tmp(N_det_selectors) )
|
||||
|
||||
! Sort alpha dets
|
||||
! ---------------
|
||||
|
||||
integer(bit_kind) :: det_tmp(N_int)
|
||||
|
||||
do i=1,N_det_selectors
|
||||
iorder(i) = i
|
||||
call int_of_3_highest_electrons(psi_selectors(1,1,i),bit_tmp(i),N_int)
|
||||
enddo
|
||||
call i8sort(bit_tmp,iorder,N_det_selectors)
|
||||
!DIR$ IVDEP
|
||||
do i=1,N_det_selectors
|
||||
do j=1,N_int
|
||||
psi_selectors_ab(j,1,i) = psi_selectors(j,1,iorder(i))
|
||||
psi_selectors_ab(j,2,i) = psi_selectors(j,2,iorder(i))
|
||||
enddo
|
||||
do k=1,N_states
|
||||
psi_coef_sorted_ab(i,k) = psi_selectors_coef(iorder(i),k)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! Find next alpha
|
||||
! ---------------
|
||||
|
||||
integer :: next
|
||||
|
||||
next = N_det_selectors+1
|
||||
psi_selectors_next_ab(1,N_det_selectors) = next
|
||||
do i=N_det_selectors-1,1,-1
|
||||
if (bit_tmp(i) /= bit_tmp(i+1)) then
|
||||
next = i+1
|
||||
endif
|
||||
psi_selectors_next_ab(1,i) = next
|
||||
enddo
|
||||
|
||||
! Sort beta dets
|
||||
! --------------
|
||||
|
||||
integer :: istart, iend
|
||||
integer(bit_kind), allocatable :: psi_selectors_ab_temp (:,:)
|
||||
|
||||
allocate ( psi_selectors_ab_temp (N_int,N_det_selectors) )
|
||||
do i=1,N_det_selectors
|
||||
do j=1,N_int
|
||||
psi_selectors_ab_temp(j,i) = psi_selectors_ab(j,2,i)
|
||||
enddo
|
||||
iorder(i) = i
|
||||
call int_of_3_highest_electrons(psi_selectors_ab_temp(1,i),bit_tmp(i),N_int)
|
||||
enddo
|
||||
|
||||
istart=1
|
||||
do while ( istart<N_det_selectors )
|
||||
|
||||
iend = psi_selectors_next_ab(1,istart)
|
||||
call i8sort(bit_tmp(istart),iorder(istart),iend-istart)
|
||||
!DIR$ IVDEP
|
||||
do i=istart,iend-1
|
||||
do j=1,N_int
|
||||
psi_selectors_ab(j,2,i) = psi_selectors_ab_temp(j,iorder(i))
|
||||
enddo
|
||||
do k=1,N_states
|
||||
psi_coef_sorted_ab(i,k) = psi_coef(iorder(i),k)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
next = iend
|
||||
psi_selectors_next_ab(2,iend-1) = next
|
||||
do i=iend-2,1,-1
|
||||
if (bit_tmp(i) /= bit_tmp(i+1)) then
|
||||
next = i+1
|
||||
endif
|
||||
psi_selectors_next_ab(2,i) = next
|
||||
enddo
|
||||
|
||||
istart = iend
|
||||
enddo
|
||||
|
||||
deallocate(iorder, bit_tmp, psi_selectors_ab_temp)
|
||||
|
||||
END_PROVIDER
|
||||
|
@ -57,100 +57,3 @@ END_PROVIDER
|
||||
END_PROVIDER
|
||||
|
||||
|
||||
BEGIN_PROVIDER [ integer(bit_kind), psi_selectors_ab, (N_int,2,psi_selectors_size) ]
|
||||
&BEGIN_PROVIDER [ double precision, psi_selectors_coef_ab, (psi_selectors_size,N_states) ]
|
||||
&BEGIN_PROVIDER [ integer, psi_selectors_next_ab, (2,psi_selectors_size) ]
|
||||
implicit none
|
||||
BEGIN_DOC
|
||||
! Determinants on which we apply <i|H|j>.
|
||||
! They are sorted by the 3 highest electrons in the alpha part,
|
||||
! then by the 3 highest electrons in the beta part to accelerate
|
||||
! the research of connected determinants.
|
||||
END_DOC
|
||||
integer :: i,j,k
|
||||
integer, allocatable :: iorder(:)
|
||||
integer*8, allocatable :: bit_tmp(:)
|
||||
integer*8, external :: det_search_key
|
||||
|
||||
allocate ( iorder(N_det_selectors), bit_tmp(N_det_selectors) )
|
||||
|
||||
! Sort alpha dets
|
||||
! ---------------
|
||||
|
||||
integer(bit_kind) :: det_tmp(N_int)
|
||||
|
||||
do i=1,N_det_selectors
|
||||
iorder(i) = i
|
||||
call int_of_3_highest_electrons(psi_selectors(1,1,i),bit_tmp(i),N_int)
|
||||
enddo
|
||||
call i8sort(bit_tmp,iorder,N_det_selectors)
|
||||
!DIR$ IVDEP
|
||||
do i=1,N_det_selectors
|
||||
do j=1,N_int
|
||||
psi_selectors_ab(j,1,i) = psi_selectors(j,1,iorder(i))
|
||||
psi_selectors_ab(j,2,i) = psi_selectors(j,2,iorder(i))
|
||||
enddo
|
||||
do k=1,N_states
|
||||
psi_coef_sorted_ab(i,k) = psi_selectors_coef(iorder(i),k)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! Find next alpha
|
||||
! ---------------
|
||||
|
||||
integer :: next
|
||||
|
||||
next = N_det_selectors+1
|
||||
psi_selectors_next_ab(1,N_det_selectors) = next
|
||||
do i=N_det_selectors-1,1,-1
|
||||
if (bit_tmp(i) /= bit_tmp(i+1)) then
|
||||
next = i+1
|
||||
endif
|
||||
psi_selectors_next_ab(1,i) = next
|
||||
enddo
|
||||
|
||||
! Sort beta dets
|
||||
! --------------
|
||||
|
||||
integer :: istart, iend
|
||||
integer(bit_kind), allocatable :: psi_selectors_ab_temp (:,:)
|
||||
|
||||
allocate ( psi_selectors_ab_temp (N_int,N_det_selectors) )
|
||||
do i=1,N_det_selectors
|
||||
do j=1,N_int
|
||||
psi_selectors_ab_temp(j,i) = psi_selectors_ab(j,2,i)
|
||||
enddo
|
||||
iorder(i) = i
|
||||
call int_of_3_highest_electrons(psi_selectors_ab_temp(1,i),bit_tmp(i),N_int)
|
||||
enddo
|
||||
|
||||
istart=1
|
||||
do while ( istart<N_det_selectors )
|
||||
|
||||
iend = psi_selectors_next_ab(1,istart)
|
||||
call i8sort(bit_tmp(istart),iorder(istart),iend-istart)
|
||||
!DIR$ IVDEP
|
||||
do i=istart,iend-1
|
||||
do j=1,N_int
|
||||
psi_selectors_ab(j,2,i) = psi_selectors_ab_temp(j,iorder(i))
|
||||
enddo
|
||||
do k=1,N_states
|
||||
psi_coef_sorted_ab(i,k) = psi_coef(iorder(i),k)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
next = iend
|
||||
psi_selectors_next_ab(2,iend-1) = next
|
||||
do i=iend-2,1,-1
|
||||
if (bit_tmp(i) /= bit_tmp(i+1)) then
|
||||
next = i+1
|
||||
endif
|
||||
psi_selectors_next_ab(2,i) = next
|
||||
enddo
|
||||
|
||||
istart = iend
|
||||
enddo
|
||||
|
||||
deallocate(iorder, bit_tmp, psi_selectors_ab_temp)
|
||||
|
||||
END_PROVIDER
|
||||
|
@ -386,66 +386,6 @@ subroutine sort_dets_by_det_search_key(Ndet, det_in, coef_in, det_out, coef_out)
|
||||
end
|
||||
|
||||
|
||||
subroutine int_of_3_highest_electrons( det_in, res, Nint )
|
||||
implicit none
|
||||
use bitmasks
|
||||
integer,intent(in) :: Nint
|
||||
integer(bit_kind) :: det_in(Nint)
|
||||
integer*8 :: res
|
||||
BEGIN_DOC
|
||||
! Returns an integer*8 as :
|
||||
!
|
||||
! |_<--- 21 bits ---><--- 21 bits ---><--- 21 bits --->|
|
||||
!
|
||||
! |0<--- i1 ---><--- i2 ---><--- i3 --->|
|
||||
!
|
||||
! It encodes the value of the indices of the 3 highest MOs
|
||||
! in descending order
|
||||
!
|
||||
END_DOC
|
||||
integer :: i, k, icount
|
||||
integer(bit_kind) :: ix
|
||||
res = 0_8
|
||||
icount = 3
|
||||
do k=Nint,1,-1
|
||||
ix = det_in(k)
|
||||
do while (ix /= 0_bit_kind)
|
||||
i = bit_kind_size-1-leadz(ix)
|
||||
ix = ibclr(ix,i)
|
||||
res = ior(ishft(res, 21_8), i+ishft(k-1,bit_kind_shift))
|
||||
icount -= 1
|
||||
if (icount == 0) then
|
||||
return
|
||||
endif
|
||||
enddo
|
||||
enddo
|
||||
end
|
||||
|
||||
subroutine filter_3_highest_electrons( det_in, det_out, Nint )
|
||||
implicit none
|
||||
use bitmasks
|
||||
integer,intent(in) :: Nint
|
||||
integer(bit_kind) :: det_in(Nint), det_out(Nint)
|
||||
BEGIN_DOC
|
||||
! Returns a determinant with only the 3 highest electrons
|
||||
END_DOC
|
||||
integer :: i, k, icount
|
||||
integer(bit_kind) :: ix
|
||||
det_out = 0_8
|
||||
icount = 3
|
||||
do k=Nint,1,-1
|
||||
ix = det_in(k)
|
||||
do while (ix /= 0_bit_kind)
|
||||
i = bit_kind_size-1-leadz(ix)
|
||||
ix = ibclr(ix,i)
|
||||
det_out(k) = ibset(det_out(k),i)
|
||||
icount -= 1
|
||||
if (icount == 0) then
|
||||
return
|
||||
endif
|
||||
enddo
|
||||
enddo
|
||||
end
|
||||
|
||||
BEGIN_PROVIDER [ double precision, psi_coef_max, (N_states) ]
|
||||
&BEGIN_PROVIDER [ double precision, psi_coef_min, (N_states) ]
|
||||
@ -465,130 +405,6 @@ end
|
||||
|
||||
END_PROVIDER
|
||||
|
||||
BEGIN_PROVIDER [ integer(bit_kind), psi_det_sorted_ab, (N_int,2,psi_det_size) ]
|
||||
&BEGIN_PROVIDER [ double precision, psi_coef_sorted_ab, (N_det,N_states) ]
|
||||
&BEGIN_PROVIDER [ integer, psi_det_sorted_next_ab, (2,psi_det_size) ]
|
||||
implicit none
|
||||
BEGIN_DOC
|
||||
! Determinants on which we apply <i|H|j>.
|
||||
! They are sorted by the 3 highest electrons in the alpha part,
|
||||
! then by the 3 highest electrons in the beta part to accelerate
|
||||
! the research of connected determinants.
|
||||
END_DOC
|
||||
|
||||
call sort_dets_by_3_highest_electrons( &
|
||||
psi_det, &
|
||||
psi_coef, &
|
||||
psi_det_sorted_ab, &
|
||||
psi_coef_sorted_ab, &
|
||||
psi_det_sorted_next_ab, &
|
||||
N_det, N_states, N_int, &
|
||||
psi_det_size )
|
||||
|
||||
END_PROVIDER
|
||||
|
||||
subroutine sort_dets_by_3_highest_electrons(det_in,coef_in,det_out,coef_out, &
|
||||
det_next, Ndet, Nstates, Nint, LDA)
|
||||
implicit none
|
||||
integer, intent(in) :: Ndet, Nstates, Nint, LDA
|
||||
integer(bit_kind), intent(in) :: det_in (Nint,2,Ndet)
|
||||
integer(bit_kind), intent(out) :: det_out (Nint,2,Ndet)
|
||||
integer, intent(out) :: det_next (2,Ndet)
|
||||
double precision, intent(in) :: coef_in (LDA,Nstates)
|
||||
double precision, intent(out) :: coef_out (LDA,Nstates)
|
||||
BEGIN_DOC
|
||||
! Determinants on which we apply <i|H|j>.
|
||||
! They are sorted by the 3 highest electrons in the alpha part,
|
||||
! then by the 3 highest electrons in the beta part to accelerate
|
||||
! the research of connected determinants.
|
||||
END_DOC
|
||||
integer :: i,j,k
|
||||
integer, allocatable :: iorder(:)
|
||||
integer*8, allocatable :: bit_tmp(:)
|
||||
integer*8, external :: det_search_key
|
||||
|
||||
allocate ( iorder(Ndet), bit_tmp(Ndet) )
|
||||
|
||||
! Sort alpha dets
|
||||
! ---------------
|
||||
|
||||
integer(bit_kind) :: det_tmp(Nint)
|
||||
|
||||
do i=1,Ndet
|
||||
iorder(i) = i
|
||||
call int_of_3_highest_electrons(psi_det(1,1,i),bit_tmp(i),N_int)
|
||||
enddo
|
||||
call i8sort(bit_tmp,iorder,Ndet)
|
||||
!DIR$ IVDEP
|
||||
do i=1,Ndet
|
||||
do j=1,N_int
|
||||
det_out(j,1,i) = psi_det(j,1,iorder(i))
|
||||
det_out(j,2,i) = psi_det(j,2,iorder(i))
|
||||
enddo
|
||||
do k=1,Nstates
|
||||
coef_out(i,k) = psi_coef(iorder(i),k)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! Find next alpha
|
||||
! ---------------
|
||||
|
||||
integer :: next
|
||||
|
||||
next = Ndet+1
|
||||
det_next(1,Ndet) = next
|
||||
do i=Ndet-1,1,-1
|
||||
if (bit_tmp(i) /= bit_tmp(i+1)) then
|
||||
next = i+1
|
||||
endif
|
||||
det_next(1,i) = next
|
||||
enddo
|
||||
|
||||
! Sort beta dets
|
||||
! --------------
|
||||
|
||||
integer :: istart, iend
|
||||
integer(bit_kind), allocatable :: det_sorted_temp (:,:)
|
||||
|
||||
allocate ( det_sorted_temp (N_int,Ndet) )
|
||||
do i=1,Ndet
|
||||
do j=1,N_int
|
||||
det_sorted_temp(j,i) = det_out(j,2,i)
|
||||
enddo
|
||||
iorder(i) = i
|
||||
call int_of_3_highest_electrons(det_sorted_temp(1,i),bit_tmp(i),N_int)
|
||||
enddo
|
||||
|
||||
istart=1
|
||||
do while ( istart<Ndet )
|
||||
|
||||
iend = det_next(1,istart)
|
||||
call i8sort(bit_tmp(istart),iorder(istart),iend-istart)
|
||||
!DIR$ IVDEP
|
||||
do i=istart,iend-1
|
||||
do j=1,N_int
|
||||
det_out(j,2,i) = det_sorted_temp(j,iorder(i))
|
||||
enddo
|
||||
do k=1,Nstates
|
||||
coef_out(i,k) = psi_coef(iorder(i),k)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
next = iend
|
||||
det_next(2,iend-1) = next
|
||||
do i=iend-2,1,-1
|
||||
if (bit_tmp(i) /= bit_tmp(i+1)) then
|
||||
next = i+1
|
||||
endif
|
||||
det_next(2,i) = next
|
||||
enddo
|
||||
|
||||
istart = iend
|
||||
enddo
|
||||
|
||||
deallocate(iorder, bit_tmp, det_sorted_temp)
|
||||
|
||||
end
|
||||
|
||||
!==============================================================================!
|
||||
! !
|
||||
|
Loading…
Reference in New Issue
Block a user