9
1
mirror of https://github.com/QuantumPackage/qp2.git synced 2024-07-04 18:25:50 +02:00

Accelerated PT2

This commit is contained in:
Anthony Scemama 2022-03-08 11:24:17 +01:00
parent 3d63d39df8
commit cef2ab8a91
3 changed files with 14 additions and 12 deletions

@ -1 +1 @@
Subproject commit 90ee61f5041c7c94a0c605625a264860292813a0 Subproject commit bc856147f6e626a6616b20344e5b8e3f30f44a92

View File

@ -31,11 +31,11 @@ subroutine run_pt2_slave(thread,iproc,energy)
double precision, intent(in) :: energy(N_states_diag) double precision, intent(in) :: energy(N_states_diag)
integer, intent(in) :: thread, iproc integer, intent(in) :: thread, iproc
if (N_det > 100000 ) then ! if (N_det > 100000 ) then
call run_pt2_slave_large(thread,iproc,energy) ! call run_pt2_slave_large(thread,iproc,energy)
else ! else
call run_pt2_slave_small(thread,iproc,energy) call run_pt2_slave_small(thread,iproc,energy)
endif ! endif
end end
subroutine run_pt2_slave_small(thread,iproc,energy) subroutine run_pt2_slave_small(thread,iproc,energy)

View File

@ -203,7 +203,7 @@ subroutine H_S2_u_0_nstates_openmp_work_$N_int(v_t,s_t,u_t,N_st,sze,istart,iend,
integer, allocatable :: doubles(:) integer, allocatable :: doubles(:)
integer, allocatable :: singles_a(:) integer, allocatable :: singles_a(:)
integer, allocatable :: singles_b(:) integer, allocatable :: singles_b(:)
integer, allocatable :: idx(:), idx0(:) integer, allocatable :: idx(:), buffer_lrow(:), idx0(:)
integer :: maxab, n_singles_a, n_singles_b, kcol_prev integer :: maxab, n_singles_a, n_singles_b, kcol_prev
integer*8 :: k8 integer*8 :: k8
logical :: compute_singles logical :: compute_singles
@ -253,7 +253,7 @@ compute_singles=.True.
!$OMP PRIVATE(krow, kcol, tmp_det, spindet, k_a, k_b, i, & !$OMP PRIVATE(krow, kcol, tmp_det, spindet, k_a, k_b, i, &
!$OMP lcol, lrow, l_a, l_b, utl, kk, u_is_sparse, & !$OMP lcol, lrow, l_a, l_b, utl, kk, u_is_sparse, &
!$OMP buffer, doubles, n_doubles, umax, & !$OMP buffer, doubles, n_doubles, umax, &
!$OMP tmp_det2, hij, sij, idx, l, kcol_prev, & !$OMP tmp_det2, hij, sij, idx, buffer_lrow, l, kcol_prev, &
!$OMP singles_a, n_singles_a, singles_b, ratio, & !$OMP singles_a, n_singles_a, singles_b, ratio, &
!$OMP n_singles_b, k8, last_found,left,right,right_max) !$OMP n_singles_b, k8, last_found,left,right,right_max)
@ -264,7 +264,7 @@ compute_singles=.True.
singles_a(maxab), & singles_a(maxab), &
singles_b(maxab), & singles_b(maxab), &
doubles(maxab), & doubles(maxab), &
idx(maxab), utl(N_st,block_size)) idx(maxab), buffer_lrow(maxab), utl(N_st,block_size))
kcol_prev=-1 kcol_prev=-1
@ -332,18 +332,20 @@ compute_singles=.True.
l_a = psi_bilinear_matrix_columns_loc(lcol) l_a = psi_bilinear_matrix_columns_loc(lcol)
ASSERT (l_a <= N_det) ASSERT (l_a <= N_det)
!DIR$ UNROLL(8)
!DIR$ LOOP COUNT avg(50000)
do j=1,psi_bilinear_matrix_columns_loc(lcol+1) - psi_bilinear_matrix_columns_loc(lcol) do j=1,psi_bilinear_matrix_columns_loc(lcol+1) - psi_bilinear_matrix_columns_loc(lcol)
lrow = psi_bilinear_matrix_rows(l_a) lrow = psi_bilinear_matrix_rows(l_a)
ASSERT (lrow <= N_det_alpha_unique) ASSERT (lrow <= N_det_alpha_unique)
buffer(1:$N_int,j) = psi_det_alpha_unique(1:$N_int, lrow) ! hot spot buffer_lrow(j) = lrow
ASSERT (l_a <= N_det) ASSERT (l_a <= N_det)
idx(j) = l_a idx(j) = l_a
l_a = l_a+1 l_a = l_a+1
enddo enddo
do j=1,psi_bilinear_matrix_columns_loc(lcol+1) - psi_bilinear_matrix_columns_loc(lcol)
buffer(1:$N_int,j) = psi_det_alpha_unique(1:$N_int, buffer_lrow(j)) ! hot spot
enddo
j = j-1 j = j-1
call get_all_spin_singles_$N_int( & call get_all_spin_singles_$N_int( &
@ -789,7 +791,7 @@ compute_singles=.True.
end do end do
!$OMP END DO !$OMP END DO
deallocate(buffer, singles_a, singles_b, doubles, idx, utl) deallocate(buffer, singles_a, singles_b, doubles, idx, buffer_lrow, utl)
!$OMP END PARALLEL !$OMP END PARALLEL
end end