mirror of
https://github.com/QuantumPackage/qp2.git
synced 2024-12-21 11:03:29 +01:00
added Charge_Harmonizer for numerical integrals
This commit is contained in:
parent
cc334b34b7
commit
9e1b2f35d3
@ -99,6 +99,9 @@ BEGIN_PROVIDER [double precision, int2_grad1_u2e_ao, (ao_num, ao_num, n_points_f
|
||||
|
||||
implicit none
|
||||
integer :: ipoint, i, j, m, jpoint
|
||||
integer :: n_blocks, n_rest, n_pass
|
||||
integer :: i_blocks, i_rest, i_pass, ii
|
||||
double precision :: mem, n_double
|
||||
double precision :: time0, time1
|
||||
double precision :: x, y, z, r2
|
||||
double precision :: dx, dy, dz
|
||||
@ -106,6 +109,9 @@ BEGIN_PROVIDER [double precision, int2_grad1_u2e_ao, (ao_num, ao_num, n_points_f
|
||||
double precision :: tmp0, tmp1, tmp2
|
||||
double precision :: tmp0_x, tmp0_y, tmp0_z
|
||||
double precision :: tmp1_x, tmp1_y, tmp1_z
|
||||
double precision, allocatable :: tmp(:,:,:)
|
||||
double precision, allocatable :: tmp_grad1_u12(:,:,:)
|
||||
|
||||
|
||||
PROVIDE j2e_type
|
||||
PROVIDE Env_type
|
||||
@ -113,6 +119,101 @@ BEGIN_PROVIDER [double precision, int2_grad1_u2e_ao, (ao_num, ao_num, n_points_f
|
||||
call wall_time(time0)
|
||||
print*, ' providing int2_grad1_u2e_ao ...'
|
||||
|
||||
if(tc_integ_type .eq. "numeric") then
|
||||
|
||||
PROVIDE final_weight_at_r_vector_extra aos_in_r_array_extra
|
||||
|
||||
allocate(tmp(n_points_extra_final_grid,ao_num,ao_num))
|
||||
!$OMP PARALLEL &
|
||||
!$OMP DEFAULT (NONE) &
|
||||
!$OMP PRIVATE (j, i, jpoint) &
|
||||
!$OMP SHARED (tmp, ao_num, n_points_extra_final_grid, final_weight_at_r_vector_extra, aos_in_r_array_extra_transp)
|
||||
!$OMP DO SCHEDULE (static)
|
||||
do j = 1, ao_num
|
||||
do i = 1, ao_num
|
||||
do jpoint = 1, n_points_extra_final_grid
|
||||
tmp(jpoint,i,j) = final_weight_at_r_vector_extra(jpoint) * aos_in_r_array_extra_transp(jpoint,i) * aos_in_r_array_extra_transp(jpoint,j)
|
||||
enddo
|
||||
enddo
|
||||
enddo
|
||||
!$OMP END DO
|
||||
!$OMP END PARALLEL
|
||||
|
||||
! n_points_final_grid = n_blocks * n_pass + n_rest
|
||||
call total_memory(mem)
|
||||
mem = max(1.d0, qp_max_mem - mem)
|
||||
n_double = mem * 1.d8
|
||||
n_blocks = int(min(n_double / (n_points_extra_final_grid * 4.d0), 1.d0*n_points_final_grid))
|
||||
n_rest = int(mod(n_points_final_grid, n_blocks))
|
||||
n_pass = int((n_points_final_grid - n_rest) / n_blocks)
|
||||
|
||||
call write_int(6, n_pass, 'Number of passes')
|
||||
call write_int(6, n_blocks, 'Size of the blocks')
|
||||
call write_int(6, n_rest, 'Size of the last block')
|
||||
|
||||
allocate(tmp_grad1_u12(n_points_extra_final_grid,n_blocks,3))
|
||||
|
||||
do i_pass = 1, n_pass
|
||||
ii = (i_pass-1)*n_blocks + 1
|
||||
|
||||
!$OMP PARALLEL &
|
||||
!$OMP DEFAULT (NONE) &
|
||||
!$OMP PRIVATE (i_blocks, ipoint) &
|
||||
!$OMP SHARED (n_blocks, n_points_extra_final_grid, ii, &
|
||||
!$OMP final_grid_points, tmp_grad1_u12)
|
||||
!$OMP DO
|
||||
do i_blocks = 1, n_blocks
|
||||
ipoint = ii - 1 + i_blocks ! r1
|
||||
call get_grad1_u12_2e_r1_seq(ipoint, n_points_extra_final_grid, tmp_grad1_u12(1,i_blocks,1) &
|
||||
, tmp_grad1_u12(1,i_blocks,2) &
|
||||
, tmp_grad1_u12(1,i_blocks,3))
|
||||
enddo
|
||||
!$OMP END DO
|
||||
!$OMP END PARALLEL
|
||||
|
||||
do m = 1, 3
|
||||
call dgemm( "T", "N", ao_num*ao_num, n_blocks, n_points_extra_final_grid, 1.d0 &
|
||||
, tmp(1,1,1), n_points_extra_final_grid, tmp_grad1_u12(1,1,m), n_points_extra_final_grid &
|
||||
, 0.d0, int2_grad1_u2e_ao(1,1,ii,m), ao_num*ao_num)
|
||||
enddo
|
||||
enddo
|
||||
|
||||
deallocate(tmp_grad1_u12)
|
||||
|
||||
if(n_rest .gt. 0) then
|
||||
|
||||
allocate(tmp_grad1_u12(n_points_extra_final_grid,n_rest,3))
|
||||
|
||||
ii = n_pass*n_blocks + 1
|
||||
|
||||
!$OMP PARALLEL &
|
||||
!$OMP DEFAULT (NONE) &
|
||||
!$OMP PRIVATE (i_rest, ipoint) &
|
||||
!$OMP SHARED (n_rest, n_points_extra_final_grid, ii, &
|
||||
!$OMP final_grid_points, tmp_grad1_u12)
|
||||
!$OMP DO
|
||||
do i_rest = 1, n_rest
|
||||
ipoint = ii - 1 + i_rest ! r1
|
||||
call get_grad1_u12_2e_r1_seq(ipoint, n_points_extra_final_grid, tmp_grad1_u12(1,i_rest,1) &
|
||||
, tmp_grad1_u12(1,i_rest,2) &
|
||||
, tmp_grad1_u12(1,i_rest,3))
|
||||
enddo
|
||||
!$OMP END DO
|
||||
!$OMP END PARALLEL
|
||||
|
||||
do m = 1, 3
|
||||
call dgemm( "T", "N", ao_num*ao_num, n_rest, n_points_extra_final_grid, 1.d0 &
|
||||
, tmp(1,1,1), n_points_extra_final_grid, tmp_grad1_u12(1,1,m), n_points_extra_final_grid &
|
||||
, 0.d0, int2_grad1_u2e_ao(1,1,ii,m), ao_num*ao_num)
|
||||
enddo
|
||||
|
||||
deallocate(tmp_grad1_u12)
|
||||
endif
|
||||
|
||||
deallocate(tmp)
|
||||
|
||||
elseif(tc_integ_type .eq. "semi-analytic") then
|
||||
|
||||
if( (j2e_type .eq. "Mu") .and. &
|
||||
( (env_type .eq. "None") .or. (env_type .eq. "Prod_Gauss") .or. (env_type .eq. "Sum_Gauss") ) ) then
|
||||
|
||||
@ -178,6 +279,13 @@ BEGIN_PROVIDER [double precision, int2_grad1_u2e_ao, (ao_num, ao_num, n_points_f
|
||||
|
||||
endif ! j2e_type
|
||||
|
||||
else
|
||||
|
||||
print *, ' Error in int2_grad1_u2e_ao: Unknown tc_integ_type'
|
||||
stop
|
||||
|
||||
endif ! tc_integ_type
|
||||
|
||||
call wall_time(time1)
|
||||
print*, ' wall time for int2_grad1_u2e_ao (min) =', (time1-time0)/60.d0
|
||||
call print_memory_usage()
|
||||
|
@ -395,3 +395,81 @@ end
|
||||
|
||||
! ---
|
||||
|
||||
subroutine get_grad1_u12_2e_r1_seq(ipoint, n_grid2, resx, resy, resz)
|
||||
|
||||
BEGIN_DOC
|
||||
!
|
||||
! grad_1 u_2e(r1,r2)
|
||||
!
|
||||
! we use grid for r1 and extra_grid for r2
|
||||
!
|
||||
END_DOC
|
||||
|
||||
implicit none
|
||||
integer, intent(in) :: ipoint, n_grid2
|
||||
double precision, intent(out) :: resx(n_grid2), resy(n_grid2), resz(n_grid2)
|
||||
|
||||
integer :: jpoint
|
||||
double precision :: env_r1, tmp
|
||||
double precision :: grad1_env(3), r1(3)
|
||||
double precision, allocatable :: env_r2(:)
|
||||
double precision, allocatable :: u2b_r12(:)
|
||||
double precision, allocatable :: gradx1_u2b(:), grady1_u2b(:), gradz1_u2b(:)
|
||||
double precision, external :: env_nucl
|
||||
|
||||
PROVIDE j1e_type j2e_type env_type
|
||||
PROVIDE final_grid_points
|
||||
PROVIDE final_grid_points_extra
|
||||
|
||||
r1(1) = final_grid_points(1,ipoint)
|
||||
r1(2) = final_grid_points(2,ipoint)
|
||||
r1(3) = final_grid_points(3,ipoint)
|
||||
|
||||
if( (j2e_type .eq. "Mu") .or. &
|
||||
(j2e_type .eq. "Mur") .or. &
|
||||
(j2e_type .eq. "Boys") ) then
|
||||
|
||||
if(env_type .eq. "None") then
|
||||
|
||||
call grad1_j12_r1_seq(r1, n_grid2, resx, resy, resz)
|
||||
|
||||
else
|
||||
|
||||
! u(r1,r2) = j12_mu(r12) x v(r1) x v(r2)
|
||||
! grad1 u(r1, r2) = [(grad1 j12_mu) v(r1) + j12_mu grad1 v(r1)] v(r2)
|
||||
|
||||
allocate(env_r2(n_grid2))
|
||||
allocate(u2b_r12(n_grid2))
|
||||
allocate(gradx1_u2b(n_grid2))
|
||||
allocate(grady1_u2b(n_grid2))
|
||||
allocate(gradz1_u2b(n_grid2))
|
||||
|
||||
env_r1 = env_nucl(r1)
|
||||
call grad1_env_nucl(r1, grad1_env)
|
||||
|
||||
call env_nucl_r1_seq(n_grid2, env_r2)
|
||||
call j12_r1_seq(r1, n_grid2, u2b_r12)
|
||||
call grad1_j12_r1_seq(r1, n_grid2, gradx1_u2b, grady1_u2b, gradz1_u2b)
|
||||
|
||||
do jpoint = 1, n_points_extra_final_grid
|
||||
resx(jpoint) = (gradx1_u2b(jpoint) * env_r1 + u2b_r12(jpoint) * grad1_env(1)) * env_r2(jpoint)
|
||||
resy(jpoint) = (grady1_u2b(jpoint) * env_r1 + u2b_r12(jpoint) * grad1_env(2)) * env_r2(jpoint)
|
||||
resz(jpoint) = (gradz1_u2b(jpoint) * env_r1 + u2b_r12(jpoint) * grad1_env(3)) * env_r2(jpoint)
|
||||
enddo
|
||||
|
||||
deallocate(env_r2, u2b_r12, gradx1_u2b, grady1_u2b, gradz1_u2b)
|
||||
|
||||
endif ! env_type
|
||||
|
||||
else
|
||||
|
||||
print *, ' Error in get_grad1_u12_withsq_r1_seq: Unknown Jastrow'
|
||||
stop
|
||||
|
||||
endif ! j2e_type
|
||||
|
||||
return
|
||||
end
|
||||
|
||||
! ---
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user