10
0
mirror of https://github.com/QuantumPackage/qp2.git synced 2024-08-31 08:13:43 +02:00

the alpha/beta single work

This commit is contained in:
Emmanuel Giner 2019-07-04 16:43:08 +02:00
parent 919662ee0b
commit 59aaf3806d
2 changed files with 163 additions and 120 deletions

View File

@ -353,7 +353,11 @@ subroutine orb_range_two_rdm_state_av_openmp_work_$N_int(big_array,dim1,norb,lis
enddo enddo
if(alpha_beta.or.spin_trace.or.alpha_alpha)then if(alpha_beta.or.spin_trace.or.alpha_alpha)then
! increment the alpha/beta part for single excitations ! increment the alpha/beta part for single excitations
!!!! call orb_range_off_diagonal_single_to_two_rdm_ab_dm(tmp_det, tmp_det2,c_average,big_array,dim1,orb_bitmask,list_orb_reverse,ispin) if (nkeys+norb .ge. size(values)) then
call update_keys_values(keys,values,size(values),nkeys,dim1,big_array)
nkeys = 0
endif
call orb_range_off_diag_single_to_two_rdm_ab_dm_buffer(tmp_det, tmp_det2,c_average,list_orb_reverse,ispin,sze_buff,nkeys,keys,values)
! increment the alpha/alpha part for single excitations ! increment the alpha/alpha part for single excitations
!!!! call orb_range_off_diagonal_single_to_two_rdm_aa_dm(tmp_det,tmp_det2,c_average,big_array,dim1,orb_bitmask,list_orb_reverse,ispin) !!!! call orb_range_off_diagonal_single_to_two_rdm_aa_dm(tmp_det,tmp_det2,c_average,big_array,dim1,orb_bitmask,list_orb_reverse,ispin)
endif endif
@ -445,7 +449,11 @@ subroutine orb_range_two_rdm_state_av_openmp_work_$N_int(big_array,dim1,norb,lis
enddo enddo
if(alpha_beta.or.spin_trace.or.beta_beta)then if(alpha_beta.or.spin_trace.or.beta_beta)then
! increment the alpha/beta part for single excitations ! increment the alpha/beta part for single excitations
!!!! call orb_range_off_diagonal_single_to_two_rdm_ab_dm(tmp_det, tmp_det2,c_average,big_array,dim1,orb_bitmask,list_orb_reverse,ispin) if (nkeys+norb .ge. size(values)) then
call update_keys_values(keys,values,size(values),nkeys,dim1,big_array)
nkeys = 0
endif
call orb_range_off_diag_single_to_two_rdm_ab_dm_buffer(tmp_det, tmp_det2,c_average,list_orb_reverse,ispin,sze_buff,nkeys,keys,values)
! increment the beta /beta part for single excitations ! increment the beta /beta part for single excitations
!!!! call orb_range_off_diagonal_single_to_two_rdm_bb_dm(tmp_det, tmp_det2,c_average,big_array,dim1,orb_bitmask,list_orb_reverse,ispin) !!!! call orb_range_off_diagonal_single_to_two_rdm_bb_dm(tmp_det, tmp_det2,c_average,big_array,dim1,orb_bitmask,list_orb_reverse,ispin)
endif endif

View File

@ -255,124 +255,159 @@
endif endif
end end
! subroutine orb_range_off_diagonal_single_to_two_rdm_ab_dm(det_1,det_2,c_1,gorb_bitmask,list_orb_reverse,ispin) subroutine orb_range_off_diag_single_to_two_rdm_ab_dm_buffer(det_1,det_2,c_1,list_orb_reverse,ispin,sze_buff,nkeys,keys,values)
! use bitmasks use bitmasks
! BEGIN_DOC BEGIN_DOC
!! routine that update the OFF DIAGONAL PART of the two body rdms in a specific range of orbitals for ! routine that update the OFF DIAGONAL PART of the two body rdms in a specific range of orbitals for
!!
!! a given couple of determinant det_1, det_2 being a SINGLE excitation with respect to one another
!!
!! c_1 is supposed to be a scalar quantity, such as state averaged coef of the determinant det_1
!!
!! big_array(dim1,dim1,dim1,dim1) is the two-body rdm to be updated in physicist notation
!!
!! orb_bitmask(N_int) is the bitmask for the orbital range, list_orb_reverse(mo_num) is the inverse range of orbitals
!!
!! ispin determines which spin-spin component of the two-rdm you will update
!!
!! ispin == 1 :: alpha/ alpha
!! ispin == 2 :: beta / beta
!! ispin == 3 :: alpha/ beta
!! ispin == 4 :: spin traced <=> total two-rdm
!!
!! here, only ispin == 3 or 4 will do something
! END_DOC
! implicit none
! integer, intent(in) :: dim1,ispin
! double precision, intent(inout) :: big_array(dim1,dim1,dim1,dim1)
! integer(bit_kind), intent(in) :: det_1(N_int,2),det_2(N_int,2)
! integer(bit_kind), intent(in) :: orb_bitmask(N_int)
! integer, intent(in) :: list_orb_reverse(mo_num)
! double precision, intent(in) :: c_1
! !
! integer :: occ(N_int*bit_kind_size,2) ! a given couple of determinant det_1, det_2 being a SINGLE excitation with respect to one another
! integer :: n_occ_ab(2)
! integer :: i,j,h1,h2,istate,p1
! integer :: exc(0:2,2,2)
! double precision :: phase
! !
! logical :: alpha_alpha,beta_beta,alpha_beta,spin_trace ! c_1 is supposed to be a scalar quantity, such as state averaged coef of the determinant det_1
! logical :: is_integer_in_string
! alpha_alpha = .False.
! beta_beta = .False.
! alpha_beta = .False.
! spin_trace = .False.
! if( ispin == 1)then
! alpha_alpha = .True.
! else if(ispin == 2)then
! beta_beta = .True.
! else if(ispin == 3)then
! alpha_beta = .True.
! else if(ispin == 4)then
! spin_trace = .True.
! endif
! !
! call bitstring_to_list_ab(det_1, occ, n_occ_ab, N_int) ! big_array(dim1,dim1,dim1,dim1) is the two-body rdm to be updated in physicist notation
! call get_single_excitation(det_1,det_2,exc,phase,N_int) !
! if(alpha_beta)then ! orb_bitmask(N_int) is the bitmask for the orbital range, list_orb_reverse(mo_num) is the inverse range of orbitals
! if (exc(0,1,1) == 1) then !
! ! Mono alpha ! ispin determines which spin-spin component of the two-rdm you will update
! h1 = exc(1,1,1) !
! if(.not.is_integer_in_string(h1,orb_bitmask,N_int))return ! ispin == 1 :: alpha/ alpha
! h1 = list_orb_reverse(h1) ! ispin == 2 :: beta / beta
! p1 = exc(1,2,1) ! ispin == 3 :: alpha/ beta
! if(.not.is_integer_in_string(p1,orb_bitmask,N_int))return ! ispin == 4 :: spin traced <=> total two-rdm
! p1 = list_orb_reverse(p1) !
! do i = 1, n_occ_ab(2) ! here, only ispin == 3 or 4 will do something
! h2 = occ(i,2) END_DOC
! if(.not.is_integer_in_string(h2,orb_bitmask,N_int))cycle implicit none
! h2 = list_orb_reverse(h2) integer, intent(in) :: ispin,sze_buff
! big_array(h1,h2,p1,h2) += c_1 * phase integer(bit_kind), intent(in) :: det_1(N_int,2),det_2(N_int,2)
! enddo integer, intent(in) :: list_orb_reverse(mo_num)
! else double precision, intent(in) :: c_1
! ! Mono beta double precision, intent(out) :: values(sze_buff)
! h1 = exc(1,1,2) integer , intent(out) :: keys(4,sze_buff)
! if(.not.is_integer_in_string(h1,orb_bitmask,N_int))return integer , intent(inout):: nkeys
! h1 = list_orb_reverse(h1)
! p1 = exc(1,2,2) integer :: occ(N_int*bit_kind_size,2)
! if(.not.is_integer_in_string(p1,orb_bitmask,N_int))return integer :: n_occ_ab(2)
! p1 = list_orb_reverse(p1) integer :: i,j,h1,h2,istate,p1
! do i = 1, n_occ_ab(1) integer :: exc(0:2,2,2)
! h2 = occ(i,1) double precision :: phase
! if(.not.is_integer_in_string(h2,orb_bitmask,N_int))cycle
! h2 = list_orb_reverse(h2) logical :: alpha_alpha,beta_beta,alpha_beta,spin_trace
! big_array(h2,h1,h2,p1) += c_1 * phase logical :: is_integer_in_string
! enddo alpha_alpha = .False.
! endif beta_beta = .False.
! else if(spin_trace)then alpha_beta = .False.
! if (exc(0,1,1) == 1) then spin_trace = .False.
! ! Mono alpha if( ispin == 1)then
! h1 = exc(1,1,1) alpha_alpha = .True.
! if(.not.is_integer_in_string(h1,orb_bitmask,N_int))return else if(ispin == 2)then
! h1 = list_orb_reverse(h1) beta_beta = .True.
! p1 = exc(1,2,1) else if(ispin == 3)then
! if(.not.is_integer_in_string(p1,orb_bitmask,N_int))return alpha_beta = .True.
! p1 = list_orb_reverse(p1) else if(ispin == 4)then
! do i = 1, n_occ_ab(2) spin_trace = .True.
! h2 = occ(i,2) endif
! if(.not.is_integer_in_string(h2,orb_bitmask,N_int))cycle
! h2 = list_orb_reverse(h2) call bitstring_to_list_ab(det_1, occ, n_occ_ab, N_int)
! big_array(h1,h2,p1,h2) += 0.5d0 * c_1 * phase call get_single_excitation(det_1,det_2,exc,phase,N_int)
! big_array(h2,h1,h2,p1) += 0.5d0 * c_1 * phase if(alpha_beta)then
! enddo if (exc(0,1,1) == 1) then
! else ! Mono alpha
! ! Mono beta h1 = exc(1,1,1)
! h1 = exc(1,1,2) if(list_orb_reverse(h1).lt.0)return
! if(.not.is_integer_in_string(h1,orb_bitmask,N_int))return h1 = list_orb_reverse(h1)
! h1 = list_orb_reverse(h1) p1 = exc(1,2,1)
! p1 = exc(1,2,2) if(list_orb_reverse(p1).lt.0)return
! if(.not.is_integer_in_string(p1,orb_bitmask,N_int))return p1 = list_orb_reverse(p1)
! p1 = list_orb_reverse(p1) do i = 1, n_occ_ab(2)
! do i = 1, n_occ_ab(1) h2 = occ(i,2)
! h2 = occ(i,1) if(list_orb_reverse(h2).lt.0)return
! if(.not.is_integer_in_string(h2,orb_bitmask,N_int))cycle h2 = list_orb_reverse(h2)
! h2 = list_orb_reverse(h2) nkeys += 1
! big_array(h1,h2,p1,h2) += 0.5d0 * c_1 * phase values(nkeys) = c_1 * phase
! big_array(h2,h1,h2,p1) += 0.5d0 * c_1 * phase keys(1,nkeys) = h1
! enddo keys(2,nkeys) = h2
! endif keys(3,nkeys) = p1
! endif keys(4,nkeys) = h2
! end enddo
else
! Mono beta
h1 = exc(1,1,2)
if(list_orb_reverse(h1).lt.0)return
h1 = list_orb_reverse(h1)
p1 = exc(1,2,2)
if(list_orb_reverse(p1).lt.0)return
p1 = list_orb_reverse(p1)
do i = 1, n_occ_ab(1)
h2 = occ(i,1)
if(list_orb_reverse(h2).lt.0)return
h2 = list_orb_reverse(h2)
nkeys += 1
values(nkeys) = c_1 * phase
keys(1,nkeys) = h1
keys(2,nkeys) = h2
keys(3,nkeys) = p1
keys(4,nkeys) = h2
enddo
endif
else if(spin_trace)then
if (exc(0,1,1) == 1) then
! Mono alpha
h1 = exc(1,1,1)
if(list_orb_reverse(h1).lt.0)return
h1 = list_orb_reverse(h1)
p1 = exc(1,2,1)
if(list_orb_reverse(p1).lt.0)return
p1 = list_orb_reverse(p1)
do i = 1, n_occ_ab(2)
h2 = occ(i,2)
if(list_orb_reverse(h2).lt.0)return
h2 = list_orb_reverse(h2)
nkeys += 1
values(nkeys) = 0.5d0 * c_1 * phase
keys(1,nkeys) = h1
keys(2,nkeys) = h2
keys(3,nkeys) = p1
keys(4,nkeys) = h2
nkeys += 1
values(nkeys) = 0.5d0 * c_1 * phase
keys(1,nkeys) = h2
keys(2,nkeys) = h1
keys(3,nkeys) = h2
keys(4,nkeys) = p1
enddo
else
! Mono beta
h1 = exc(1,1,2)
if(list_orb_reverse(h1).lt.0)return
h1 = list_orb_reverse(h1)
p1 = exc(1,2,2)
if(list_orb_reverse(p1).lt.0)return
p1 = list_orb_reverse(p1)
!print*,'****************'
!print*,'****************'
!print*,'h1,p1',h1,p1
do i = 1, n_occ_ab(1)
h2 = occ(i,1)
if(list_orb_reverse(h2).lt.0)return
h2 = list_orb_reverse(h2)
! print*,'h2 = ',h2
nkeys += 1
values(nkeys) = 0.5d0 * c_1 * phase
keys(1,nkeys) = h1
keys(2,nkeys) = h2
keys(3,nkeys) = p1
keys(4,nkeys) = h2
nkeys += 1
values(nkeys) = 0.5d0 * c_1 * phase
keys(1,nkeys) = h2
keys(2,nkeys) = h1
keys(3,nkeys) = h2
keys(4,nkeys) = p1
enddo
endif
endif
end
! subroutine orb_range_off_diagonal_single_to_two_rdm_aa_dm(det_1,det_2,c_1,gorb_bitmask,list_orb_reverse,ispin) ! subroutine orb_range_off_diagonal_single_to_two_rdm_aa_dm(det_1,det_2,c_1,gorb_bitmask,list_orb_reverse,ispin)
! BEGIN_DOC ! BEGIN_DOC