mirror of
https://github.com/LCPQ/quantum_package
synced 2024-11-03 20:54:00 +01:00
Merge branch 'develop' of github.com:scemama/quantum_package into develop
This commit is contained in:
commit
15157fa0c9
@ -18,7 +18,7 @@ IRPF90_FLAGS : --ninja --align=32
|
|||||||
# 0 : Deactivate
|
# 0 : Deactivate
|
||||||
#
|
#
|
||||||
[OPTION]
|
[OPTION]
|
||||||
MODE : OPT ; [ OPT | PROFILE | DEBUG ] : Chooses the section below
|
MODE : DEBUG ; [ OPT | PROFILE | DEBUG ] : Chooses the section below
|
||||||
CACHE : 1 ; Enable cache_compile.py
|
CACHE : 1 ; Enable cache_compile.py
|
||||||
OPENMP : 1 ; Append OpenMP flags
|
OPENMP : 1 ; Append OpenMP flags
|
||||||
|
|
||||||
@ -32,7 +32,7 @@ OPENMP : 1 ; Append OpenMP flags
|
|||||||
#
|
#
|
||||||
[OPT]
|
[OPT]
|
||||||
FC : -traceback
|
FC : -traceback
|
||||||
FCFLAGS : -xHost -O2 -ip -ftz -g
|
FCFLAGS : -xSSE4.2 -O2 -ip -ftz -g
|
||||||
|
|
||||||
# Profiling flags
|
# Profiling flags
|
||||||
#################
|
#################
|
||||||
|
@ -1 +1 @@
|
|||||||
Perturbation Selectors_full Generators_full ZMQ
|
Perturbation Selectors_full Generators_full ZMQ Full_CI
|
||||||
|
@ -1,11 +1,12 @@
|
|||||||
program fci_zmq
|
program fci_zmq
|
||||||
implicit none
|
implicit none
|
||||||
integer :: i,k
|
integer :: i,j,k
|
||||||
logical, external :: detEq
|
logical, external :: detEq
|
||||||
|
|
||||||
double precision, allocatable :: pt2(:), norm_pert(:), H_pert_diag(:)
|
double precision, allocatable :: pt2(:), norm_pert(:), H_pert_diag(:)
|
||||||
integer :: N_st, degree
|
integer :: N_st, degree
|
||||||
integer(bit_kind) :: chk
|
integer(bit_kind) :: chk
|
||||||
|
|
||||||
N_st = N_states
|
N_st = N_states
|
||||||
allocate (pt2(N_st), norm_pert(N_st),H_pert_diag(N_st))
|
allocate (pt2(N_st), norm_pert(N_st),H_pert_diag(N_st))
|
||||||
|
|
||||||
@ -52,14 +53,6 @@ program fci_zmq
|
|||||||
endif
|
endif
|
||||||
call diagonalize_CI
|
call diagonalize_CI
|
||||||
call save_wavefunction
|
call save_wavefunction
|
||||||
! chk = 0_8
|
|
||||||
! do i=1, N_det
|
|
||||||
! do k=1, N_int
|
|
||||||
! chk = xor(psi_det(k,1,i), chk)
|
|
||||||
! chk = xor(psi_det(k,2,i), chk)
|
|
||||||
! end do
|
|
||||||
! end do
|
|
||||||
! print *, "CHK ", chk
|
|
||||||
|
|
||||||
print *, 'N_det = ', N_det
|
print *, 'N_det = ', N_det
|
||||||
print *, 'N_states = ', N_states
|
print *, 'N_states = ', N_states
|
||||||
@ -162,6 +155,60 @@ subroutine selection_dressing_slave_inproc(i)
|
|||||||
implicit none
|
implicit none
|
||||||
integer, intent(in) :: i
|
integer, intent(in) :: i
|
||||||
|
|
||||||
call selection_slaved(1,i,ci_electronic_energy)
|
call run_selection_slave(1,i,ci_electronic_energy)
|
||||||
end
|
end
|
||||||
|
|
||||||
|
subroutine selection_collector(b, pt2)
|
||||||
|
use f77_zmq
|
||||||
|
use selection_types
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
|
||||||
|
type(selection_buffer), intent(inout) :: b
|
||||||
|
double precision, intent(out) :: pt2(N_states)
|
||||||
|
double precision :: pt2_mwen(N_states)
|
||||||
|
integer(ZMQ_PTR),external :: new_zmq_to_qp_run_socket
|
||||||
|
integer(ZMQ_PTR) :: zmq_to_qp_run_socket
|
||||||
|
|
||||||
|
integer(ZMQ_PTR), external :: new_zmq_pull_socket
|
||||||
|
integer(ZMQ_PTR) :: zmq_socket_pull
|
||||||
|
|
||||||
|
integer :: msg_size, rc, more
|
||||||
|
integer :: acc, i, j, robin, N, ntask
|
||||||
|
double precision, allocatable :: val(:)
|
||||||
|
integer(bit_kind), allocatable :: det(:,:,:)
|
||||||
|
integer, allocatable :: task_id(:)
|
||||||
|
integer :: done
|
||||||
|
real :: time, time0
|
||||||
|
zmq_to_qp_run_socket = new_zmq_to_qp_run_socket()
|
||||||
|
zmq_socket_pull = new_zmq_pull_socket()
|
||||||
|
allocate(val(b%N), det(N_int, 2, b%N), task_id(N_det))
|
||||||
|
done = 0
|
||||||
|
more = 1
|
||||||
|
pt2(:) = 0d0
|
||||||
|
call CPU_TIME(time0)
|
||||||
|
do while (more == 1)
|
||||||
|
call pull_selection_results(zmq_socket_pull, pt2_mwen, val(1), det(1,1,1), N, task_id, ntask)
|
||||||
|
pt2 += pt2_mwen
|
||||||
|
do i=1, N
|
||||||
|
call add_to_selection_buffer(b, det(1,1,i), val(i))
|
||||||
|
end do
|
||||||
|
|
||||||
|
do i=1, ntask
|
||||||
|
if(task_id(i) == 0) then
|
||||||
|
print *, "Error in collector"
|
||||||
|
endif
|
||||||
|
call zmq_delete_task(zmq_to_qp_run_socket,zmq_socket_pull,task_id(i),more)
|
||||||
|
end do
|
||||||
|
done += ntask
|
||||||
|
call CPU_TIME(time)
|
||||||
|
! print *, "DONE" , done, time - time0
|
||||||
|
end do
|
||||||
|
|
||||||
|
|
||||||
|
call end_zmq_to_qp_run_socket(zmq_to_qp_run_socket)
|
||||||
|
call end_zmq_pull_socket(zmq_socket_pull)
|
||||||
|
call sort_selection_buffer(b)
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
156
plugins/Full_CI_ZMQ/run_selection_slave.irp.f
Normal file
156
plugins/Full_CI_ZMQ/run_selection_slave.irp.f
Normal file
@ -0,0 +1,156 @@
|
|||||||
|
|
||||||
|
subroutine run_selection_slave(thread,iproc,energy)
|
||||||
|
use f77_zmq
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
double precision, intent(in) :: energy(N_states_diag)
|
||||||
|
integer, intent(in) :: thread, iproc
|
||||||
|
integer :: rc, i
|
||||||
|
|
||||||
|
integer :: worker_id, task_id(1), ctask, ltask
|
||||||
|
character*(512) :: task
|
||||||
|
|
||||||
|
integer(ZMQ_PTR),external :: new_zmq_to_qp_run_socket
|
||||||
|
integer(ZMQ_PTR) :: zmq_to_qp_run_socket
|
||||||
|
|
||||||
|
integer(ZMQ_PTR), external :: new_zmq_push_socket
|
||||||
|
integer(ZMQ_PTR) :: zmq_socket_push
|
||||||
|
|
||||||
|
type(selection_buffer) :: buf, buf2
|
||||||
|
logical :: done
|
||||||
|
double precision :: pt2(N_states)
|
||||||
|
|
||||||
|
zmq_to_qp_run_socket = new_zmq_to_qp_run_socket()
|
||||||
|
zmq_socket_push = new_zmq_push_socket(thread)
|
||||||
|
call connect_to_taskserver(zmq_to_qp_run_socket,worker_id,thread)
|
||||||
|
if(worker_id == -1) then
|
||||||
|
print *, "WORKER -1"
|
||||||
|
!call disconnect_from_taskserver(zmq_to_qp_run_socket,zmq_socket_push,worker_id)
|
||||||
|
call end_zmq_to_qp_run_socket(zmq_to_qp_run_socket)
|
||||||
|
call end_zmq_push_socket(zmq_socket_push,thread)
|
||||||
|
return
|
||||||
|
end if
|
||||||
|
buf%N = 0
|
||||||
|
ctask = 1
|
||||||
|
pt2 = 0d0
|
||||||
|
|
||||||
|
do
|
||||||
|
call get_task_from_taskserver(zmq_to_qp_run_socket,worker_id, task_id(ctask), task)
|
||||||
|
done = task_id(ctask) == 0
|
||||||
|
if (done) then
|
||||||
|
ctask = ctask - 1
|
||||||
|
else
|
||||||
|
integer :: i_generator, i_generator_start, i_generator_max, step, N
|
||||||
|
read (task,*) i_generator_start, i_generator_max, step, N
|
||||||
|
if(buf%N == 0) then
|
||||||
|
! Only first time
|
||||||
|
call create_selection_buffer(N, N*2, buf)
|
||||||
|
call create_selection_buffer(N, N*3, buf2)
|
||||||
|
else
|
||||||
|
if(N /= buf%N) stop "N changed... wtf man??"
|
||||||
|
end if
|
||||||
|
!print *, "psi_selectors_coef ", psi_selectors_coef(N_det_selectors-5:N_det_selectors, 1)
|
||||||
|
!call debug_det(psi_selectors(1,1,N_det_selectors), N_int)
|
||||||
|
do i_generator=i_generator_start,i_generator_max,step
|
||||||
|
call select_connected(i_generator,energy,pt2,buf)
|
||||||
|
enddo
|
||||||
|
endif
|
||||||
|
|
||||||
|
if(done .or. ctask == size(task_id)) then
|
||||||
|
if(buf%N == 0 .and. ctask > 0) stop "uninitialized selection_buffer"
|
||||||
|
do i=1, ctask
|
||||||
|
call task_done_to_taskserver(zmq_to_qp_run_socket,worker_id,task_id(i))
|
||||||
|
end do
|
||||||
|
if(ctask > 0) then
|
||||||
|
call push_selection_results(zmq_socket_push, pt2, buf, task_id(1), ctask)
|
||||||
|
do i=1,buf%cur
|
||||||
|
call add_to_selection_buffer(buf2, buf%det(1,1,i), buf%val(i))
|
||||||
|
enddo
|
||||||
|
call sort_selection_buffer(buf2)
|
||||||
|
buf%mini = buf2%mini
|
||||||
|
pt2 = 0d0
|
||||||
|
buf%cur = 0
|
||||||
|
end if
|
||||||
|
ctask = 0
|
||||||
|
end if
|
||||||
|
|
||||||
|
if(done) exit
|
||||||
|
ctask = ctask + 1
|
||||||
|
end do
|
||||||
|
call disconnect_from_taskserver(zmq_to_qp_run_socket,zmq_socket_push,worker_id)
|
||||||
|
call end_zmq_to_qp_run_socket(zmq_to_qp_run_socket)
|
||||||
|
call end_zmq_push_socket(zmq_socket_push,thread)
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine push_selection_results(zmq_socket_push, pt2, b, task_id, ntask)
|
||||||
|
use f77_zmq
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(ZMQ_PTR), intent(in) :: zmq_socket_push
|
||||||
|
double precision, intent(in) :: pt2(N_states)
|
||||||
|
type(selection_buffer), intent(inout) :: b
|
||||||
|
integer, intent(in) :: ntask, task_id(*)
|
||||||
|
integer :: rc
|
||||||
|
|
||||||
|
call sort_selection_buffer(b)
|
||||||
|
|
||||||
|
rc = f77_zmq_send( zmq_socket_push, b%cur, 4, ZMQ_SNDMORE)
|
||||||
|
if(rc /= 4) stop "push"
|
||||||
|
rc = f77_zmq_send( zmq_socket_push, pt2, 8*N_states, ZMQ_SNDMORE)
|
||||||
|
if(rc /= 8*N_states) stop "push"
|
||||||
|
|
||||||
|
rc = f77_zmq_send( zmq_socket_push, b%val(1), 8*b%cur, ZMQ_SNDMORE)
|
||||||
|
if(rc /= 8*b%cur) stop "push"
|
||||||
|
|
||||||
|
rc = f77_zmq_send( zmq_socket_push, b%det(1,1,1), bit_kind*N_int*2*b%cur, ZMQ_SNDMORE)
|
||||||
|
if(rc /= bit_kind*N_int*2*b%cur) stop "push"
|
||||||
|
|
||||||
|
rc = f77_zmq_send( zmq_socket_push, ntask, 4, ZMQ_SNDMORE)
|
||||||
|
if(rc /= 4) stop "push"
|
||||||
|
|
||||||
|
rc = f77_zmq_send( zmq_socket_push, task_id(1), ntask*4, 0)
|
||||||
|
if(rc /= 4*ntask) stop "push"
|
||||||
|
|
||||||
|
! Activate is zmq_socket_push is a REQ
|
||||||
|
! rc = f77_zmq_recv( zmq_socket_push, task_id(1), ntask*4, 0)
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine pull_selection_results(zmq_socket_pull, pt2, val, det, N, task_id, ntask)
|
||||||
|
use f77_zmq
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
integer(ZMQ_PTR), intent(in) :: zmq_socket_pull
|
||||||
|
double precision, intent(inout) :: pt2(N_states)
|
||||||
|
double precision, intent(out) :: val(*)
|
||||||
|
integer(bit_kind), intent(out) :: det(N_int, 2, *)
|
||||||
|
integer, intent(out) :: N, ntask, task_id(*)
|
||||||
|
integer :: rc, rn, i
|
||||||
|
|
||||||
|
rc = f77_zmq_recv( zmq_socket_pull, N, 4, 0)
|
||||||
|
if(rc /= 4) stop "pull"
|
||||||
|
|
||||||
|
rc = f77_zmq_recv( zmq_socket_pull, pt2, N_states*8, 0)
|
||||||
|
if(rc /= 8*N_states) stop "pull"
|
||||||
|
|
||||||
|
rc = f77_zmq_recv( zmq_socket_pull, val(1), 8*N, 0)
|
||||||
|
if(rc /= 8*N) stop "pull"
|
||||||
|
|
||||||
|
rc = f77_zmq_recv( zmq_socket_pull, det(1,1,1), bit_kind*N_int*2*N, 0)
|
||||||
|
if(rc /= bit_kind*N_int*2*N) stop "pull"
|
||||||
|
|
||||||
|
rc = f77_zmq_recv( zmq_socket_pull, ntask, 4, 0)
|
||||||
|
if(rc /= 4) stop "pull"
|
||||||
|
|
||||||
|
rc = f77_zmq_recv( zmq_socket_pull, task_id(1), ntask*4, 0)
|
||||||
|
if(rc /= 4*ntask) stop "pull"
|
||||||
|
|
||||||
|
! Activate is zmq_socket_pull is a REP
|
||||||
|
! rc = f77_zmq_send( zmq_socket_pull, task_id(1), ntask*4, 0)
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
|
File diff suppressed because it is too large
Load Diff
70
plugins/Full_CI_ZMQ/selection_buffer.irp.f
Normal file
70
plugins/Full_CI_ZMQ/selection_buffer.irp.f
Normal file
@ -0,0 +1,70 @@
|
|||||||
|
|
||||||
|
subroutine create_selection_buffer(N, siz, res)
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer, intent(in) :: N, siz
|
||||||
|
type(selection_buffer), intent(out) :: res
|
||||||
|
|
||||||
|
allocate(res%det(N_int, 2, siz), res%val(siz))
|
||||||
|
|
||||||
|
res%val = 0d0
|
||||||
|
res%det = 0_8
|
||||||
|
res%N = N
|
||||||
|
res%mini = 0d0
|
||||||
|
res%cur = 0
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine add_to_selection_buffer(b, det, val)
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
type(selection_buffer), intent(inout) :: b
|
||||||
|
integer(bit_kind), intent(in) :: det(N_int, 2)
|
||||||
|
double precision, intent(in) :: val
|
||||||
|
integer :: i
|
||||||
|
|
||||||
|
if(dabs(val) >= b%mini) then
|
||||||
|
b%cur += 1
|
||||||
|
b%det(:,:,b%cur) = det(:,:)
|
||||||
|
b%val(b%cur) = val
|
||||||
|
if(b%cur == size(b%val)) then
|
||||||
|
call sort_selection_buffer(b)
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine sort_selection_buffer(b)
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
type(selection_buffer), intent(inout) :: b
|
||||||
|
double precision, allocatable :: vals(:), absval(:)
|
||||||
|
integer, allocatable :: iorder(:)
|
||||||
|
integer(bit_kind), allocatable :: detmp(:,:,:)
|
||||||
|
integer :: i, nmwen
|
||||||
|
logical, external :: detEq
|
||||||
|
nmwen = min(b%N, b%cur)
|
||||||
|
|
||||||
|
|
||||||
|
allocate(iorder(b%cur), detmp(N_int, 2, nmwen), absval(b%cur), vals(nmwen))
|
||||||
|
absval = -dabs(b%val(:b%cur))
|
||||||
|
do i=1,b%cur
|
||||||
|
iorder(i) = i
|
||||||
|
end do
|
||||||
|
call dsort(absval, iorder, b%cur)
|
||||||
|
|
||||||
|
do i=1, nmwen
|
||||||
|
detmp(:,:,i) = b%det(:,:,iorder(i))
|
||||||
|
vals(i) = b%val(iorder(i))
|
||||||
|
end do
|
||||||
|
b%det(:,:,:nmwen) = detmp(:,:,:)
|
||||||
|
b%det(:,:,nmwen+1:) = 0_bit_kind
|
||||||
|
b%val(:nmwen) = vals(:)
|
||||||
|
b%val(nmwen+1:) = 0d0
|
||||||
|
b%mini = max(b%mini,dabs(b%val(b%N)))
|
||||||
|
b%cur = nmwen
|
||||||
|
end subroutine
|
||||||
|
|
697
plugins/Full_CI_ZMQ/selection_double.irp.f
Normal file
697
plugins/Full_CI_ZMQ/selection_double.irp.f
Normal file
@ -0,0 +1,697 @@
|
|||||||
|
|
||||||
|
subroutine select_doubles(i_generator,hole_mask,particle_mask,fock_diag_tmp,E0,pt2,buf)
|
||||||
|
use bitmasks
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer, intent(in) :: i_generator
|
||||||
|
integer(bit_kind), intent(in) :: hole_mask(N_int,2), particle_mask(N_int,2)
|
||||||
|
double precision, intent(in) :: fock_diag_tmp(mo_tot_num)
|
||||||
|
double precision, intent(in) :: E0(N_states)
|
||||||
|
double precision, intent(inout) :: pt2(N_states)
|
||||||
|
type(selection_buffer), intent(inout) :: buf
|
||||||
|
|
||||||
|
double precision :: mat(N_states, mo_tot_num, mo_tot_num)
|
||||||
|
integer :: h1,h2,s1,s2,i1,i2,ib,sp,k
|
||||||
|
integer(bit_kind) :: hole(N_int,2), particle(N_int,2), mask(N_int, 2)
|
||||||
|
logical :: fullMatch, ok
|
||||||
|
|
||||||
|
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
|
||||||
|
|
||||||
|
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)
|
||||||
|
|
||||||
|
call bitstring_to_list_ab(hole , hole_list , N_holes , N_int)
|
||||||
|
call bitstring_to_list_ab(particle, particle_list, N_particles, N_int)
|
||||||
|
|
||||||
|
!call assert(psi_det_generators(1,1,i_generator) == psi_det_sorted(1,1,i_generator), "sorted selex")
|
||||||
|
do s1=1,2
|
||||||
|
do s2=s1,2
|
||||||
|
sp = s1
|
||||||
|
if(s1 /= s2) sp = 3
|
||||||
|
do i1=N_holes(s1),1,-1 ! Generate low excitations first
|
||||||
|
ib = 1
|
||||||
|
if(s1 == s2) ib = i1+1
|
||||||
|
do i2=N_holes(s2),ib,-1 ! Generate low excitations first
|
||||||
|
h1 = hole_list(i1,s1)
|
||||||
|
h2 = hole_list(i2,s2)
|
||||||
|
call apply_holes(psi_det_generators(1,1,i_generator), s1,h1,s2,h2, mask, ok, N_int)
|
||||||
|
!call assert(ok, irp_here)
|
||||||
|
|
||||||
|
logical :: banned(mo_tot_num, mo_tot_num,2)
|
||||||
|
logical :: bannedOrb(mo_tot_num, 2)
|
||||||
|
|
||||||
|
banned = .false.
|
||||||
|
bannedOrb = .false.
|
||||||
|
bannedOrb(h1, s1) = .true.
|
||||||
|
bannedOrb(h2, s2) = .true.
|
||||||
|
|
||||||
|
call spot_isinwf(mask, psi_det_sorted, i_generator, N_det, banned, fullMatch)
|
||||||
|
if(fullMatch) cycle
|
||||||
|
if(sp /= 2) call spot_occupied(mask(1,1), bannedOrb(1,1))
|
||||||
|
if(sp /= 1) call spot_occupied(mask(1,2), bannedOrb(1,2))
|
||||||
|
|
||||||
|
mat = 0d0
|
||||||
|
call splash_pq(mask, sp, psi_det_sorted, i_generator, N_det_selectors, bannedOrb, banned, mat)
|
||||||
|
call fill_buffer_double(i_generator, sp, h1, h2, bannedOrb, banned, fock_diag_tmp, E0, pt2, mat, buf)
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine fill_buffer_double(i_generator, sp, h1, h2, bannedOrb, banned, fock_diag_tmp, E0, pt2, mat, buf)
|
||||||
|
use bitmasks
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer, intent(in) :: i_generator, sp, h1, h2
|
||||||
|
double precision, intent(in) :: mat(N_states, mo_tot_num, mo_tot_num)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num, 2), banned(mo_tot_num, mo_tot_num)
|
||||||
|
double precision, intent(in) :: fock_diag_tmp(mo_tot_num)
|
||||||
|
double precision, intent(in) :: E0(N_states)
|
||||||
|
double precision, intent(inout) :: pt2(N_states)
|
||||||
|
type(selection_buffer), intent(inout) :: buf
|
||||||
|
logical :: ok
|
||||||
|
integer :: s1, s2, p1, p2, ib, j
|
||||||
|
integer(bit_kind) :: mask(N_int, 2), det(N_int, 2)
|
||||||
|
double precision :: e_pert, delta_E, val, Hii
|
||||||
|
double precision, external :: diag_H_mat_elem_fock
|
||||||
|
|
||||||
|
logical, external :: detEq
|
||||||
|
|
||||||
|
if(N_states > 1) stop "fill_buffer_double N_states > 1"
|
||||||
|
|
||||||
|
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)
|
||||||
|
!call assert(ok, "sosoqs")
|
||||||
|
do p1=1,mo_tot_num
|
||||||
|
if(bannedOrb(p1, s1)) cycle
|
||||||
|
ib = 1
|
||||||
|
if(sp /= 3) ib = p1+1
|
||||||
|
do p2=ib,mo_tot_num
|
||||||
|
if(bannedOrb(p2, s2)) cycle
|
||||||
|
if(banned(p1,p2)) cycle
|
||||||
|
if(mat(1, p1, p2) == 0d0) cycle
|
||||||
|
call apply_particles(mask, s1, p1, s2, p2, det, ok, N_int)
|
||||||
|
!call assert(ok, "ododod")
|
||||||
|
val = mat(1, p1, p2)
|
||||||
|
|
||||||
|
Hii = diag_H_mat_elem_fock(psi_det_generators(1,1,i_generator),det,fock_diag_tmp,N_int)
|
||||||
|
|
||||||
|
delta_E = E0(1) - Hii
|
||||||
|
if (delta_E < 0.d0) then
|
||||||
|
e_pert = 0.5d0 * (-dsqrt(delta_E * delta_E + 4.d0 * val * val) - delta_E)
|
||||||
|
else
|
||||||
|
e_pert = 0.5d0 * ( dsqrt(delta_E * delta_E + 4.d0 * val * val) - delta_E)
|
||||||
|
endif
|
||||||
|
pt2(1) += e_pert
|
||||||
|
if(dabs(e_pert) > buf%mini) then
|
||||||
|
! do j=1,buf%cur-1
|
||||||
|
! if(detEq(buf%det(1,1,j), det, N_int)) then
|
||||||
|
! print *, "tops"
|
||||||
|
! print *, i_generator, s1, s2, h1, h2,p1,p2
|
||||||
|
! stop
|
||||||
|
! end if
|
||||||
|
! end do
|
||||||
|
call add_to_selection_buffer(buf, det, e_pert)
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine splash_pq(mask, sp, det, i_gen, N_sel, bannedOrb, banned, mat)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind),intent(in) :: mask(N_int, 2), det(N_int, 2, N_sel)
|
||||||
|
integer, intent(in) :: sp, i_gen, N_sel
|
||||||
|
logical, intent(inout) :: bannedOrb(mo_tot_num, 2), banned(mo_tot_num, mo_tot_num, 2)
|
||||||
|
double precision, intent(inout) :: mat(N_states, mo_tot_num, mo_tot_num)
|
||||||
|
|
||||||
|
integer :: i, j, k, l, h(0:2,2), p(0:4,2), nt
|
||||||
|
integer(bit_kind) :: perMask(N_int, 2), mobMask(N_int, 2), negMask(N_int, 2)
|
||||||
|
logical :: bandon
|
||||||
|
|
||||||
|
mat = 0d0
|
||||||
|
bandon = .false.
|
||||||
|
|
||||||
|
do i=1,N_int
|
||||||
|
negMask(i,1) = not(mask(i,1))
|
||||||
|
negMask(i,2) = not(mask(i,2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
do i=1, N_sel
|
||||||
|
nt = 0
|
||||||
|
do j=1,N_int
|
||||||
|
mobMask(j,1) = iand(negMask(j,1), det(j,1,i))
|
||||||
|
mobMask(j,2) = iand(negMask(j,2), det(j,2,i))
|
||||||
|
nt += popcnt(mobMask(j, 1)) + popcnt(mobMask(j, 2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(nt > 4) cycle
|
||||||
|
|
||||||
|
do j=1,N_int
|
||||||
|
perMask(j,1) = iand(mask(j,1), not(det(j,1,i)))
|
||||||
|
perMask(j,2) = iand(mask(j,2), not(det(j,2,i)))
|
||||||
|
end do
|
||||||
|
|
||||||
|
call bitstring_to_list(perMask(1,1), h(1,1), h(0,1), N_int)
|
||||||
|
call bitstring_to_list(perMask(1,2), h(1,2), h(0,2), N_int)
|
||||||
|
|
||||||
|
call bitstring_to_list(mobMask(1,1), p(1,1), p(0,1), N_int)
|
||||||
|
call bitstring_to_list(mobMask(1,2), p(1,2), p(0,2), N_int)
|
||||||
|
|
||||||
|
!call assert(nt >= 2, irp_here//"qsd")
|
||||||
|
if(i < i_gen) then
|
||||||
|
if(nt == 4) call past_d2(banned, p, sp)
|
||||||
|
if(nt == 3) call past_d1(bannedOrb, p)
|
||||||
|
!call assert(nt /= 2, "should have been discarded")
|
||||||
|
else
|
||||||
|
if(i == i_gen) then
|
||||||
|
bandon = .true.
|
||||||
|
if(sp == 3) then
|
||||||
|
banned(:,:,2) = transpose(banned(:,:,1))
|
||||||
|
else
|
||||||
|
do k=1,mo_tot_num
|
||||||
|
do l=k+1,mo_tot_num
|
||||||
|
banned(l,k,1) = banned(k,l,1)
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
if(nt == 4) then
|
||||||
|
call get_d2(det(1,1,i), psi_phasemask(1,1,i), bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, i))
|
||||||
|
else if(nt == 3) then
|
||||||
|
call get_d1(det(1,1,i), psi_phasemask(1,1,i), bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, i))
|
||||||
|
else
|
||||||
|
call get_d0(det(1,1,i), psi_phasemask(1,1,i), bannedOrb, banned, mat, mask, h, p, sp, psi_selectors_coef_transp(1, i))
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
call assert(bandon, "BANDON")
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine get_d2(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: mask(N_int, 2), gen(N_int, 2)
|
||||||
|
integer(1), intent(in) :: phasemask(N_int*bit_kind_size, 2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num, 2), banned(mo_tot_num, mo_tot_num,2)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: mat(N_states, mo_tot_num, mo_tot_num)
|
||||||
|
integer, intent(in) :: h(0:2,2), p(0:4,2), sp
|
||||||
|
|
||||||
|
double precision, external :: get_phase_bi, integral8
|
||||||
|
|
||||||
|
integer :: i, j, tip, ma, mi, puti, putj
|
||||||
|
integer :: h1, h2, p1, p2, i1, i2
|
||||||
|
double precision :: hij, phase
|
||||||
|
|
||||||
|
integer, parameter:: turn2d(2,3,4) = reshape((/0,0, 0,0, 0,0, 3,4, 0,0, 0,0, 2,4, 1,4, 0,0, 2,3, 1,3, 1,2 /), (/2,3,4/))
|
||||||
|
integer, parameter :: turn2(2) = (/2, 1/)
|
||||||
|
integer, parameter :: turn3(2,3) = reshape((/2,3, 1,3, 1,2/), (/2,3/))
|
||||||
|
|
||||||
|
integer :: bant
|
||||||
|
bant = 1
|
||||||
|
|
||||||
|
tip = p(0,1) * p(0,2)
|
||||||
|
!call assert(p(0,1) + p(0,2) == 4, irp_here//"df")
|
||||||
|
ma = sp
|
||||||
|
if(p(0,1) > p(0,2)) ma = 1
|
||||||
|
if(p(0,1) < p(0,2)) ma = 2
|
||||||
|
mi = mod(ma, 2) + 1
|
||||||
|
|
||||||
|
!print *, "d2 SPtip", SP, tip
|
||||||
|
if(sp == 3) then
|
||||||
|
if(ma == 2) bant = 2
|
||||||
|
|
||||||
|
if(tip == 3) then
|
||||||
|
puti = p(1, mi)
|
||||||
|
do i = 1, 3
|
||||||
|
putj = p(i, ma)
|
||||||
|
if(banned(putj,puti,bant)) cycle
|
||||||
|
i1 = turn3(1,i)
|
||||||
|
i2 = turn3(2,i)
|
||||||
|
p1 = p(i1, ma)
|
||||||
|
p2 = p(i2, ma)
|
||||||
|
h1 = h(1, ma)
|
||||||
|
h2 = h(2, ma)
|
||||||
|
|
||||||
|
hij = (integral8(p1, p2, h1, h2) - integral8(p2,p1, h1, h2)) * get_phase_bi(phasemask, ma, ma, h1, p1, h2, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, mi, ma, puti, putj)
|
||||||
|
if(ma == 1) then
|
||||||
|
mat(:, putj, puti) += coefs * hij
|
||||||
|
else
|
||||||
|
mat(:, puti, putj) += coefs * hij
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
else
|
||||||
|
!call assert(tip == 4, "df")
|
||||||
|
do i = 1,2
|
||||||
|
do j = 1,2
|
||||||
|
puti = p(i, 1)
|
||||||
|
putj = p(j, 2)
|
||||||
|
|
||||||
|
if(banned(puti,putj,bant)) cycle
|
||||||
|
p1 = p(turn2(i), 1)
|
||||||
|
p2 = p(turn2(j), 2)
|
||||||
|
h1 = h(1,1)
|
||||||
|
h2 = h(1,2)
|
||||||
|
|
||||||
|
hij = integral8(p1, p2, h1, h2) * get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, 1, 2, puti, putj)
|
||||||
|
mat(:, puti, putj) += coefs * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end if
|
||||||
|
|
||||||
|
else
|
||||||
|
if(tip == 0) then
|
||||||
|
h1 = h(1, ma)
|
||||||
|
h2 = h(2, ma)
|
||||||
|
do i=1,3
|
||||||
|
puti = p(i, ma)
|
||||||
|
do j=i+1,4
|
||||||
|
putj = p(j, ma)
|
||||||
|
if(banned(puti,putj,1)) cycle
|
||||||
|
|
||||||
|
i1 = turn2d(1, i, j)
|
||||||
|
i2 = turn2d(2, i, j)
|
||||||
|
p1 = p(i1, ma)
|
||||||
|
p2 = p(i2, ma)
|
||||||
|
hij = (integral8(p1, p2, h1, h2) - integral8(p2,p1, h1, h2)) * get_phase_bi(phasemask, ma, ma, h1, p1, h2, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, ma, ma, puti, putj)
|
||||||
|
mat(:, puti, putj) += coefs * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
else if(tip == 3) then
|
||||||
|
h1 = h(1, mi)
|
||||||
|
h2 = h(1, ma)
|
||||||
|
p1 = p(1, mi)
|
||||||
|
!call assert(ma == sp, "dldl")
|
||||||
|
do i=1,3
|
||||||
|
puti = p(turn3(1,i), ma)
|
||||||
|
putj = p(turn3(2,i), ma)
|
||||||
|
if(banned(puti,putj,1)) cycle
|
||||||
|
p2 = p(i, ma)
|
||||||
|
|
||||||
|
hij = integral8(p1, p2, h1, h2) * get_phase_bi(phasemask, mi, ma, h1, p1, h2, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, ma, ma, puti, putj)
|
||||||
|
mat(:, min(puti, putj), max(puti, putj)) += coefs * hij
|
||||||
|
end do
|
||||||
|
else ! tip == 4
|
||||||
|
!call assert(tip == 4, "qsdf")
|
||||||
|
puti = p(1, sp)
|
||||||
|
putj = p(2, sp)
|
||||||
|
if(.not. banned(puti,putj,1)) then
|
||||||
|
p1 = p(1, mi)
|
||||||
|
p2 = p(2, mi)
|
||||||
|
h1 = h(1, mi)
|
||||||
|
h2 = h(2, mi)
|
||||||
|
hij = (integral8(p1, p2, h1, h2) - integral8(p2,p1, h1, h2)) * get_phase_bi(phasemask, mi, mi, h1, p1, h2, p2)
|
||||||
|
!call debug_hij(hij, gen, mask,ma,ma, puti, putj)
|
||||||
|
mat(:, puti, putj) += coefs * hij
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine debug_hij(hij, gen, mask, s1, s2, p1, p2)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: gen(N_int,2), mask(N_int,2)
|
||||||
|
double precision, intent(in) :: hij
|
||||||
|
integer, intent(in) :: s1, s2, p1, p2
|
||||||
|
integer(bit_kind) :: det(N_int,2)
|
||||||
|
double precision :: hij_ref, phase_ref
|
||||||
|
logical :: ok
|
||||||
|
integer :: degree
|
||||||
|
integer :: exc(0:2,2,2)
|
||||||
|
|
||||||
|
call apply_particles(mask, s1, p1, s2, p2, det, ok, N_int)
|
||||||
|
!call assert(ok, "nokey")
|
||||||
|
call i_H_j_phase_out(gen,det,N_int,hij_ref,phase_ref,exc,degree)
|
||||||
|
if(hij /= hij_ref) then
|
||||||
|
print *, hij, hij_ref
|
||||||
|
print *, s1, s2, p1, p2
|
||||||
|
call debug_det(gen, N_int)
|
||||||
|
call debug_det(mask, N_int)
|
||||||
|
stop
|
||||||
|
end if
|
||||||
|
|
||||||
|
! print *, "fourar", hij, hij_ref,s1,s2
|
||||||
|
end function
|
||||||
|
|
||||||
|
|
||||||
|
subroutine get_d1(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: mask(N_int, 2), gen(N_int, 2)
|
||||||
|
integer(1),intent(in) :: phasemask(N_int*bit_kind_size, 2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num, 2), banned(mo_tot_num, mo_tot_num,2)
|
||||||
|
integer(bit_kind) :: det(N_int, 2)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: mat(N_states, mo_tot_num, mo_tot_num)
|
||||||
|
double precision :: hij, tmp_row(N_states, mo_tot_num), tmp_row2(N_states, mo_tot_num)
|
||||||
|
double precision, external :: get_phase_bi, integral8
|
||||||
|
|
||||||
|
logical :: lbanned(mo_tot_num, 2), ok
|
||||||
|
integer :: puti, putj, ma, mi, s1, s2, i, i1, i2, j, hfix, pfix, h1, h2, p1, p2, ib
|
||||||
|
|
||||||
|
integer, intent(in) :: h(0:2,2), p(0:4,2), sp
|
||||||
|
|
||||||
|
integer, parameter :: turn2(2) = (/2,1/)
|
||||||
|
integer, parameter :: turn3(2,3) = reshape((/2,3, 1,3, 1,2/), (/2,3/))
|
||||||
|
|
||||||
|
integer :: bant
|
||||||
|
|
||||||
|
|
||||||
|
lbanned = bannedOrb
|
||||||
|
|
||||||
|
do i=1, p(0,1)
|
||||||
|
lbanned(p(i,1), 1) = .true.
|
||||||
|
end do
|
||||||
|
do i=1, p(0,2)
|
||||||
|
lbanned(p(i,2), 2) = .true.
|
||||||
|
end do
|
||||||
|
|
||||||
|
ma = 1
|
||||||
|
if(p(0,2) >= 2) ma = 2
|
||||||
|
mi = turn2(ma)
|
||||||
|
|
||||||
|
bant = 1
|
||||||
|
!print *, "d1 SP", sp, p(0,1)*p(0,2)
|
||||||
|
|
||||||
|
if(sp == 3) then
|
||||||
|
!move MA
|
||||||
|
!call assert(p(0,1)*p(0,2) == 2, "ddmmm")
|
||||||
|
if(ma == 2) bant = 2
|
||||||
|
puti = p(1,mi)
|
||||||
|
hfix = h(1,ma)
|
||||||
|
p1 = p(1,ma)
|
||||||
|
p2 = p(2,ma)
|
||||||
|
if(.not. bannedOrb(puti, mi)) then
|
||||||
|
tmp_row = 0d0
|
||||||
|
do putj=1, hfix-1
|
||||||
|
if(lbanned(putj, ma) .or. banned(putj, puti,bant)) cycle
|
||||||
|
hij = (integral8(p1, p2, putj, hfix)-integral8(p2,p1,putj,hfix)) * get_phase_bi(phasemask, ma, ma, putj, p1, hfix, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, mi, ma, puti, putj)
|
||||||
|
tmp_row(:,putj) += hij * coefs
|
||||||
|
end do
|
||||||
|
do putj=hfix+1, mo_tot_num
|
||||||
|
if(lbanned(putj, ma) .or. banned(putj, puti,bant)) cycle
|
||||||
|
hij = (integral8(p1, p2, hfix, putj)-integral8(p2,p1,hfix,putj)) * get_phase_bi(phasemask, ma, ma, hfix, p1, putj, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, mi, ma, puti, putj)
|
||||||
|
tmp_row(:,putj) += hij * coefs
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(ma == 1) then
|
||||||
|
mat(:,:,puti) += tmp_row(:,:)
|
||||||
|
else
|
||||||
|
mat(:,puti,:) += tmp_row(:,:)
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
|
||||||
|
!MOVE MI
|
||||||
|
pfix = p(1,mi)
|
||||||
|
tmp_row = 0d0
|
||||||
|
tmp_row2 = 0d0
|
||||||
|
do puti=1,mo_tot_num
|
||||||
|
if(lbanned(puti,mi)) cycle
|
||||||
|
!p1 fixed
|
||||||
|
putj = p1
|
||||||
|
if(.not. banned(putj,puti,bant)) then
|
||||||
|
hij = integral8(p2,pfix,hfix,puti) * get_phase_bi(phasemask, ma, mi, hfix, p2, puti, pfix)
|
||||||
|
tmp_row(:,puti) += hij * coefs
|
||||||
|
end if
|
||||||
|
|
||||||
|
!call debug_hij(hij, gen, mask, mi, ma, puti, putj)
|
||||||
|
putj = p2
|
||||||
|
if(.not. banned(putj,puti,bant)) then
|
||||||
|
hij = integral8(p1,pfix,hfix,puti) * get_phase_bi(phasemask, ma, mi, hfix, p1, puti, pfix)
|
||||||
|
!call debug_hij(hij, gen, mask, mi, ma, puti, putj)
|
||||||
|
tmp_row2(:,puti) += hij * coefs
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(mi == 1) then
|
||||||
|
mat(:,:,p1) += tmp_row(:,:)
|
||||||
|
mat(:,:,p2) += tmp_row2(:,:)
|
||||||
|
else
|
||||||
|
mat(:,p1,:) += tmp_row(:,:)
|
||||||
|
mat(:,p2,:) += tmp_row2(:,:)
|
||||||
|
end if
|
||||||
|
else
|
||||||
|
if(p(0,ma) == 3) then
|
||||||
|
do i=1,3
|
||||||
|
hfix = h(1,ma)
|
||||||
|
puti = p(i, ma)
|
||||||
|
p1 = p(turn3(1,i), ma)
|
||||||
|
p2 = p(turn3(2,i), ma)
|
||||||
|
tmp_row = 0d0
|
||||||
|
do putj=1,hfix-1
|
||||||
|
if(lbanned(putj,ma) .or. banned(puti,putj,1)) cycle
|
||||||
|
hij = (integral8(p1, p2, putj, hfix)-integral8(p2,p1,putj,hfix)) * get_phase_bi(phasemask, ma, ma, putj, p1, hfix, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, ma, ma, puti, putj)
|
||||||
|
tmp_row(:,putj) += hij * coefs
|
||||||
|
end do
|
||||||
|
do putj=hfix+1,mo_tot_num
|
||||||
|
if(lbanned(putj,ma) .or. banned(puti,putj,1)) cycle
|
||||||
|
hij = (integral8(p1, p2, hfix, putj)-integral8(p2,p1,hfix,putj)) * get_phase_bi(phasemask, ma, ma, hfix, p1, putj, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, ma, ma, puti, putj)
|
||||||
|
tmp_row(:,putj) += hij * coefs
|
||||||
|
end do
|
||||||
|
|
||||||
|
mat(:, :puti-1, puti) += tmp_row(:,:puti-1)
|
||||||
|
mat(:, puti, puti:) += tmp_row(:,puti:)
|
||||||
|
end do
|
||||||
|
else
|
||||||
|
!call assert(sp == ma, "sp == ma")
|
||||||
|
hfix = h(1,mi)
|
||||||
|
pfix = p(1,mi)
|
||||||
|
p1 = p(1,ma)
|
||||||
|
p2 = p(2,ma)
|
||||||
|
tmp_row = 0d0
|
||||||
|
tmp_row2 = 0d0
|
||||||
|
do puti=1,mo_tot_num
|
||||||
|
if(lbanned(puti,ma)) cycle
|
||||||
|
putj = p2
|
||||||
|
if(.not. banned(puti,putj,1)) then
|
||||||
|
hij = integral8(pfix, p1, hfix, puti) * get_phase_bi(phasemask, mi, ma, hfix, pfix, puti, p1)
|
||||||
|
!call debug_hij(hij, gen, mask, ma, ma, putj, puti)
|
||||||
|
tmp_row(:,puti) += hij * coefs
|
||||||
|
end if
|
||||||
|
|
||||||
|
putj = p1
|
||||||
|
if(.not. banned(puti,putj,1)) then
|
||||||
|
hij = integral8(pfix, p2, hfix, puti) * get_phase_bi(phasemask, mi, ma, hfix, pfix, puti, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, ma, ma, putj, puti)
|
||||||
|
tmp_row2(:,puti) += hij * coefs
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
mat(:,:p2-1,p2) += tmp_row(:,:p2-1)
|
||||||
|
mat(:,p2,p2:) += tmp_row(:,p2:)
|
||||||
|
mat(:,:p1-1,p1) += tmp_row2(:,:p1-1)
|
||||||
|
mat(:,p1,p1:) += tmp_row2(:,p1:)
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
|
||||||
|
!! MONO
|
||||||
|
if(sp == 3) then
|
||||||
|
s1 = 1
|
||||||
|
s2 = 2
|
||||||
|
else
|
||||||
|
s1 = sp
|
||||||
|
s2 = sp
|
||||||
|
end if
|
||||||
|
|
||||||
|
do i1=1,p(0,s1)
|
||||||
|
ib = 1
|
||||||
|
if(s1 == s2) ib = i1+1
|
||||||
|
do i2=ib,p(0,s2)
|
||||||
|
p1 = p(i1,s1)
|
||||||
|
p2 = p(i2,s2)
|
||||||
|
if(bannedOrb(p1, s1) .or. bannedOrb(p2, s2) .or. banned(p1, p2, 1)) cycle
|
||||||
|
call apply_particles(mask, s1, p1, s2, p2, det, ok, N_int)
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
mat(:, p1, p2) += coefs * hij
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
subroutine get_d0(gen, phasemask, bannedOrb, banned, mat, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: gen(N_int, 2), mask(N_int, 2)
|
||||||
|
integer(1), intent(in) :: phasemask(N_int*bit_kind_size, 2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num, 2), banned(mo_tot_num, mo_tot_num,2)
|
||||||
|
integer(bit_kind) :: det(N_int, 2)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: mat(N_states, mo_tot_num, mo_tot_num)
|
||||||
|
integer, intent(in) :: h(0:2,2), p(0:4,2), sp
|
||||||
|
|
||||||
|
integer :: i, j, s, h1, h2, p1, p2, puti, putj
|
||||||
|
double precision :: hij, phase
|
||||||
|
double precision, external :: get_phase_bi, integral8
|
||||||
|
logical :: ok
|
||||||
|
|
||||||
|
integer :: bant
|
||||||
|
bant = 1
|
||||||
|
|
||||||
|
!print *, "d0 SP", sp
|
||||||
|
|
||||||
|
if(sp == 3) then ! AB
|
||||||
|
h1 = p(1,1)
|
||||||
|
h2 = p(1,2)
|
||||||
|
do p1=1, mo_tot_num
|
||||||
|
if(bannedOrb(p1, 1)) cycle
|
||||||
|
do p2=1, mo_tot_num
|
||||||
|
if(bannedOrb(p2,2)) cycle
|
||||||
|
if(banned(p1, p2, bant)) cycle ! rentable?
|
||||||
|
if(p1 == h1 .or. p2 == h2) then
|
||||||
|
call apply_particles(mask, 1,p1,2,p2, det, ok, N_int)
|
||||||
|
!call assert(ok, "zsdq")
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
mat(:, p1, p2) += coefs * hij
|
||||||
|
else
|
||||||
|
hij = integral8(p1, p2, h1, h2) * get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2)
|
||||||
|
phase = get_phase_bi(phasemask, 1, 2, h1, p1, h2, p2)
|
||||||
|
!call debug_hij(hij, gen, mask, 1, 2, p1, p2)
|
||||||
|
mat(:, p1, p2) += coefs * hij
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
else ! AA BB
|
||||||
|
p1 = p(1,sp)
|
||||||
|
p2 = p(2,sp)
|
||||||
|
do puti=1, mo_tot_num
|
||||||
|
if(bannedOrb(puti, sp)) cycle
|
||||||
|
do putj=puti+1, mo_tot_num
|
||||||
|
if(bannedOrb(putj, sp)) cycle
|
||||||
|
if(banned(puti, putj, bant)) cycle ! rentable?
|
||||||
|
if(puti == p1 .or. putj == p2 .or. puti == p2 .or. putj == p1) then
|
||||||
|
call apply_particles(mask, sp,puti,sp,putj, det, ok, N_int)
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
mat(:, puti, putj) += coefs * hij
|
||||||
|
else
|
||||||
|
hij = (integral8(p1, p2, puti, putj) - integral8(p2, p1, puti, putj))* get_phase_bi(phasemask, sp, sp, puti, p1 , putj, p2)
|
||||||
|
mat(:, puti, putj) += coefs * hij
|
||||||
|
!call debug_hij(hij, gen, mask, sp, sp, puti, putj)
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end if
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine past_d1(bannedOrb, p)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
logical, intent(inout) :: bannedOrb(mo_tot_num, 2)
|
||||||
|
integer, intent(in) :: p(0:4, 2)
|
||||||
|
integer :: i,s
|
||||||
|
|
||||||
|
do s = 1, 2
|
||||||
|
do i = 1, p(0, s)
|
||||||
|
bannedOrb(p(i, s), s) = .true.
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine past_d2(banned, p, sp)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
logical, intent(inout) :: banned(mo_tot_num, mo_tot_num)
|
||||||
|
integer, intent(in) :: p(0:4, 2), sp
|
||||||
|
integer :: i,j
|
||||||
|
|
||||||
|
if(sp == 3) then
|
||||||
|
do i=1,p(0,1)
|
||||||
|
do j=1,p(0,2)
|
||||||
|
banned(p(i,1), p(j,2)) = .true.
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
else
|
||||||
|
do i=1,p(0, sp)
|
||||||
|
do j=1,i-1
|
||||||
|
banned(p(j,sp), p(i,sp)) = .true.
|
||||||
|
banned(p(i,sp), p(j,sp)) = .true.
|
||||||
|
end do
|
||||||
|
end do
|
||||||
|
end if
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
subroutine spot_isinwf(mask, det, i_gen, N, banned, fullMatch)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind),intent(in) :: mask(N_int, 2), det(N_int, 2, N)
|
||||||
|
integer, intent(in) :: i_gen, N
|
||||||
|
logical, intent(inout) :: banned(mo_tot_num, mo_tot_num)
|
||||||
|
logical, intent(out) :: fullMatch
|
||||||
|
|
||||||
|
|
||||||
|
integer :: i, j, na, nb, list(3)
|
||||||
|
integer(bit_kind) :: myMask(N_int, 2), negMask(N_int, 2)
|
||||||
|
|
||||||
|
fullMatch = .false.
|
||||||
|
|
||||||
|
do i=1,N_int
|
||||||
|
negMask(i,1) = not(mask(i,1))
|
||||||
|
negMask(i,2) = not(mask(i,2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
genl : do i=1, N
|
||||||
|
do j=1, N_int
|
||||||
|
if(iand(det(j,1,i), mask(j,1)) /= mask(j, 1)) cycle genl
|
||||||
|
if(iand(det(j,2,i), mask(j,2)) /= mask(j, 2)) cycle genl
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(i < i_gen) then
|
||||||
|
fullMatch = .true.
|
||||||
|
return
|
||||||
|
end if
|
||||||
|
|
||||||
|
do j=1, N_int
|
||||||
|
myMask(j, 1) = iand(det(j, 1, i), negMask(j, 1))
|
||||||
|
myMask(j, 2) = iand(det(j, 2, i), negMask(j, 2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
call bitstring_to_list(myMask(1,1), list(1), na, N_int)
|
||||||
|
call bitstring_to_list(myMask(1,2), list(na+1), nb, N_int)
|
||||||
|
!call assert(na + nb == 2, "oyo")
|
||||||
|
!call assert(na == 1 .or. list(1) < list(2), "sqdsmmmm")
|
||||||
|
banned(list(1), list(2)) = .true.
|
||||||
|
end do genl
|
||||||
|
end subroutine
|
||||||
|
|
388
plugins/Full_CI_ZMQ/selection_single.irp.f
Normal file
388
plugins/Full_CI_ZMQ/selection_single.irp.f
Normal file
@ -0,0 +1,388 @@
|
|||||||
|
|
||||||
|
|
||||||
|
subroutine select_singles(i_gen,hole_mask,particle_mask,fock_diag_tmp,E0,pt2,buf)
|
||||||
|
use bitmasks
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
BEGIN_DOC
|
||||||
|
! Select determinants connected to i_det by H
|
||||||
|
END_DOC
|
||||||
|
integer, intent(in) :: i_gen
|
||||||
|
integer(bit_kind), intent(in) :: hole_mask(N_int,2), particle_mask(N_int,2)
|
||||||
|
double precision, intent(in) :: fock_diag_tmp(mo_tot_num)
|
||||||
|
double precision, intent(in) :: E0(N_states)
|
||||||
|
double precision, intent(inout) :: pt2(N_states)
|
||||||
|
type(selection_buffer), intent(inout) :: buf
|
||||||
|
|
||||||
|
double precision :: vect(N_states, mo_tot_num)
|
||||||
|
logical :: bannedOrb(mo_tot_num)
|
||||||
|
integer :: i, k
|
||||||
|
integer :: h1,h2,s1,s2,i1,i2,ib,sp
|
||||||
|
integer(bit_kind) :: hole(N_int,2), particle(N_int,2), mask(N_int, 2)
|
||||||
|
logical :: fullMatch, ok
|
||||||
|
|
||||||
|
|
||||||
|
do k=1,N_int
|
||||||
|
hole (k,1) = iand(psi_det_generators(k,1,i_gen), hole_mask(k,1))
|
||||||
|
hole (k,2) = iand(psi_det_generators(k,2,i_gen), hole_mask(k,2))
|
||||||
|
particle(k,1) = iand(not(psi_det_generators(k,1,i_gen)), particle_mask(k,1))
|
||||||
|
particle(k,2) = iand(not(psi_det_generators(k,2,i_gen)), particle_mask(k,2))
|
||||||
|
enddo
|
||||||
|
|
||||||
|
! Create lists of holes and particles
|
||||||
|
! -----------------------------------
|
||||||
|
|
||||||
|
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)
|
||||||
|
|
||||||
|
call bitstring_to_list_ab(hole , hole_list , N_holes , N_int)
|
||||||
|
call bitstring_to_list_ab(particle, particle_list, N_particles, N_int)
|
||||||
|
|
||||||
|
do sp=1,2
|
||||||
|
do i=1, N_holes(sp)
|
||||||
|
h1 = hole_list(i,sp)
|
||||||
|
call apply_hole(psi_det_generators(1,1,i_gen), sp, h1, mask, ok, N_int)
|
||||||
|
!call assert(ok, irp_here)
|
||||||
|
bannedOrb = .false.
|
||||||
|
bannedOrb(h1) = .true.
|
||||||
|
call spot_hasBeen(mask, sp, psi_det_sorted, i_gen, N_det, bannedOrb, fullMatch)
|
||||||
|
if(fullMatch) cycle
|
||||||
|
call spot_occupied(mask(1,sp), bannedOrb)
|
||||||
|
vect = 0d0
|
||||||
|
call splash_p(mask, sp, psi_selectors(1,1,i_gen), psi_phasemask(1,1,i_gen), psi_selectors_coef_transp(1,i_gen), N_det_selectors - i_gen + 1, bannedOrb, vect)
|
||||||
|
call fill_buffer_single(i_gen, sp, h1, bannedOrb, fock_diag_tmp, E0, pt2, vect, buf)
|
||||||
|
end do
|
||||||
|
enddo
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine fill_buffer_single(i_generator, sp, h1, bannedOrb, fock_diag_tmp, E0, pt2, vect, buf)
|
||||||
|
use bitmasks
|
||||||
|
use selection_types
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer, intent(in) :: i_generator, sp, h1
|
||||||
|
double precision, intent(in) :: vect(N_states, mo_tot_num)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num)
|
||||||
|
double precision, intent(in) :: fock_diag_tmp(mo_tot_num)
|
||||||
|
double precision, intent(in) :: E0(N_states)
|
||||||
|
double precision, intent(inout) :: pt2(N_states)
|
||||||
|
type(selection_buffer), intent(inout) :: buf
|
||||||
|
logical :: ok
|
||||||
|
integer :: s1, s2, p1, p2, ib
|
||||||
|
integer(bit_kind) :: mask(N_int, 2), det(N_int, 2)
|
||||||
|
double precision :: e_pert, delta_E, val, Hii
|
||||||
|
double precision, external :: diag_H_mat_elem_fock
|
||||||
|
|
||||||
|
if(N_states > 1) stop "fill_buffer_single N_states > 1"
|
||||||
|
|
||||||
|
call apply_hole(psi_det_generators(1,1,i_generator), sp, h1, mask, ok, N_int)
|
||||||
|
|
||||||
|
do p1=1,mo_tot_num
|
||||||
|
if(bannedOrb(p1)) cycle
|
||||||
|
if(vect(1, p1) == 0d0) cycle
|
||||||
|
call apply_particle(mask, sp, p1, det, ok, N_int)
|
||||||
|
val = vect(1, p1)
|
||||||
|
|
||||||
|
Hii = diag_H_mat_elem_fock(psi_det_generators(1,1,i_generator),det,fock_diag_tmp,N_int)
|
||||||
|
|
||||||
|
delta_E = E0(1) - Hii
|
||||||
|
if (delta_E < 0.d0) then
|
||||||
|
e_pert = 0.5d0 * (-dsqrt(delta_E * delta_E + 4.d0 * val * val) - delta_E)
|
||||||
|
else
|
||||||
|
e_pert = 0.5d0 * ( dsqrt(delta_E * delta_E + 4.d0 * val * val) - delta_E)
|
||||||
|
endif
|
||||||
|
pt2(1) += e_pert
|
||||||
|
if(dabs(e_pert) > buf%mini) call add_to_selection_buffer(buf, det, e_pert)
|
||||||
|
end do
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine splash_p(mask, sp, det, phasemask, coefs, N_sel, bannedOrb, vect)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind),intent(in) :: mask(N_int, 2), det(N_int,2,N_sel)
|
||||||
|
integer(1), intent(in) :: phasemask(N_int*bit_kind_size, 2, N_sel)
|
||||||
|
double precision, intent(in) :: coefs(N_states, N_sel)
|
||||||
|
integer, intent(in) :: sp, N_sel
|
||||||
|
logical, intent(inout) :: bannedOrb(mo_tot_num)
|
||||||
|
double precision, intent(inout) :: vect(N_states, mo_tot_num)
|
||||||
|
|
||||||
|
integer :: i, j, h(0:2,2), p(0:3,2), nt
|
||||||
|
integer(bit_kind) :: perMask(N_int, 2), mobMask(N_int, 2), negMask(N_int, 2)
|
||||||
|
|
||||||
|
do i=1,N_int
|
||||||
|
negMask(i,1) = not(mask(i,1))
|
||||||
|
negMask(i,2) = not(mask(i,2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
do i=1, N_sel
|
||||||
|
nt = 0
|
||||||
|
do j=1,N_int
|
||||||
|
mobMask(j,1) = iand(negMask(j,1), det(j,1,i))
|
||||||
|
mobMask(j,2) = iand(negMask(j,2), det(j,2,i))
|
||||||
|
nt += popcnt(mobMask(j, 1)) + popcnt(mobMask(j, 2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(nt > 3) cycle
|
||||||
|
|
||||||
|
do j=1,N_int
|
||||||
|
perMask(j,1) = iand(mask(j,1), not(det(j,1,i)))
|
||||||
|
perMask(j,2) = iand(mask(j,2), not(det(j,2,i)))
|
||||||
|
end do
|
||||||
|
|
||||||
|
call bitstring_to_list(perMask(1,1), h(1,1), h(0,1), N_int)
|
||||||
|
call bitstring_to_list(perMask(1,2), h(1,2), h(0,2), N_int)
|
||||||
|
|
||||||
|
call bitstring_to_list(mobMask(1,1), p(1,1), p(0,1), N_int)
|
||||||
|
call bitstring_to_list(mobMask(1,2), p(1,2), p(0,2), N_int)
|
||||||
|
|
||||||
|
if(nt == 3) then
|
||||||
|
call get_m2(det(1,1,i), phasemask(1,1,i), bannedOrb, vect, mask, h, p, sp, coefs(1, i))
|
||||||
|
else if(nt == 2) then
|
||||||
|
call get_m1(det(1,1,i), phasemask(1,1,i), bannedOrb, vect, mask, h, p, sp, coefs(1, i))
|
||||||
|
else
|
||||||
|
call get_m0(det(1,1,i), phasemask(1,1,i), bannedOrb, vect, mask, h, p, sp, coefs(1, i))
|
||||||
|
end if
|
||||||
|
end do
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine get_m2(gen, phasemask, bannedOrb, vect, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: gen(N_int, 2), mask(N_int, 2)
|
||||||
|
integer(1), intent(in) :: phasemask(N_int*bit_kind_size, 2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: vect(N_states, mo_tot_num)
|
||||||
|
integer, intent(in) :: sp, h(0:2, 2), p(0:3, 2)
|
||||||
|
integer :: i, j, h1, h2, p1, p2, sfix, hfix, pfix, hmob, pmob, puti
|
||||||
|
double precision :: hij
|
||||||
|
double precision, external :: get_phase_bi, integral8
|
||||||
|
|
||||||
|
integer, parameter :: turn3_2(2,3) = reshape((/2,3, 1,3, 1,2/), (/2,3/))
|
||||||
|
integer, parameter :: turn2(2) = (/2,1/)
|
||||||
|
|
||||||
|
if(h(0,sp) == 2) then
|
||||||
|
h1 = h(1, sp)
|
||||||
|
h2 = h(2, sp)
|
||||||
|
do i=1,3
|
||||||
|
puti = p(i, sp)
|
||||||
|
if(bannedOrb(puti)) cycle
|
||||||
|
p1 = p(turn3_2(1,i), sp)
|
||||||
|
p2 = p(turn3_2(2,i), sp)
|
||||||
|
hij = integral8(p1, p2, h1, h2) - integral8(p2, p1, h1, h2)
|
||||||
|
hij *= get_phase_bi(phasemask, sp, sp, h1, p1, h2, p2)
|
||||||
|
!call debug_hij_mo(hij, gen, mask, sp, puti)
|
||||||
|
vect(:, puti) += hij * coefs
|
||||||
|
end do
|
||||||
|
else if(h(0,sp) == 1) then
|
||||||
|
sfix = turn2(sp)
|
||||||
|
hfix = h(1,sfix)
|
||||||
|
pfix = p(1,sfix)
|
||||||
|
hmob = h(1,sp)
|
||||||
|
do j=1,2
|
||||||
|
puti = p(j, sp)
|
||||||
|
if(bannedOrb(puti)) cycle
|
||||||
|
pmob = p(turn2(j), sp)
|
||||||
|
hij = integral8(pfix, pmob, hfix, hmob)
|
||||||
|
hij *= get_phase_bi(phasemask, sp, sfix, hmob, pmob, hfix, pfix)
|
||||||
|
!call debug_hij_mo(hij, gen, mask, sp, puti)
|
||||||
|
vect(:, puti) += hij * coefs
|
||||||
|
end do
|
||||||
|
else
|
||||||
|
puti = p(1,sp)
|
||||||
|
if(.not. bannedOrb(puti)) then
|
||||||
|
sfix = turn2(sp)
|
||||||
|
p1 = p(1,sfix)
|
||||||
|
p2 = p(2,sfix)
|
||||||
|
h1 = h(1,sfix)
|
||||||
|
h2 = h(2,sfix)
|
||||||
|
hij = (integral8(p1,p2,h1,h2) - integral8(p2,p1,h1,h2))
|
||||||
|
hij *= get_phase_bi(phasemask, sfix, sfix, h1, p1, h2, p2)
|
||||||
|
!call debug_hij_mo(hij, gen, mask, sp, puti)
|
||||||
|
vect(:, puti) += hij * coefs
|
||||||
|
end if
|
||||||
|
end if
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
subroutine get_m1(gen, phasemask, bannedOrb, vect, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: gen(N_int, 2), mask(N_int, 2)
|
||||||
|
integer(1), intent(in) :: phasemask(N_int*bit_kind_size, 2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: vect(N_states, mo_tot_num)
|
||||||
|
integer, intent(in) :: sp, h(0:2, 2), p(0:3, 2)
|
||||||
|
integer :: i, hole, p1, p2, sh
|
||||||
|
logical :: ok, lbanned(mo_tot_num)
|
||||||
|
integer(bit_kind) :: det(N_int, 2)
|
||||||
|
double precision :: hij
|
||||||
|
double precision, external :: get_phase_bi, integral8
|
||||||
|
|
||||||
|
lbanned = bannedOrb
|
||||||
|
sh = 1
|
||||||
|
if(h(0,2) == 1) sh = 2
|
||||||
|
hole = h(1, sh)
|
||||||
|
lbanned(p(1,sp)) = .true.
|
||||||
|
if(p(0,sp) == 2) lbanned(p(2,sp)) = .true.
|
||||||
|
!print *, "SPm1", sp, sh
|
||||||
|
|
||||||
|
p1 = p(1, sp)
|
||||||
|
|
||||||
|
if(sp == sh) then
|
||||||
|
p2 = p(2, sp)
|
||||||
|
lbanned(p2) = .true.
|
||||||
|
|
||||||
|
do i=1,hole-1
|
||||||
|
if(lbanned(i)) cycle
|
||||||
|
hij = (integral8(p1, p2, i, hole) - integral8(p2, p1, i, hole))
|
||||||
|
hij *= get_phase_bi(phasemask, sp, sp, i, p1, hole, p2)
|
||||||
|
!call debug_hij_mo(hij, gen, mask, sp, i)
|
||||||
|
vect(:,i) += hij * coefs
|
||||||
|
end do
|
||||||
|
do i=hole+1,mo_tot_num
|
||||||
|
if(lbanned(i)) cycle
|
||||||
|
hij = (integral8(p1, p2, hole, i) - integral8(p2, p1, hole, i))
|
||||||
|
hij *= get_phase_bi(phasemask, sp, sp, hole, p1, i, p2)
|
||||||
|
!call debug_hij_mo(hij, gen, mask, sp, i)
|
||||||
|
vect(:,i) += hij * coefs
|
||||||
|
end do
|
||||||
|
|
||||||
|
call apply_particle(mask, sp, p2, det, ok, N_int)
|
||||||
|
!call assert(ok, "OKE223")
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
vect(:, p2) += hij * coefs
|
||||||
|
else
|
||||||
|
p2 = p(1, sh)
|
||||||
|
do i=1,mo_tot_num
|
||||||
|
if(lbanned(i)) cycle
|
||||||
|
hij = integral8(p1, p2, i, hole)
|
||||||
|
hij *= get_phase_bi(phasemask, sp, sh, i, p1, hole, p2)
|
||||||
|
!call debug_hij_mo(hij, gen, mask, sp, i)
|
||||||
|
vect(:,i) += hij * coefs
|
||||||
|
end do
|
||||||
|
end if
|
||||||
|
|
||||||
|
call apply_particle(mask, sp, p1, det, ok, N_int)
|
||||||
|
!call assert(ok, "OKQQE2")
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
vect(:, p1) += hij * coefs
|
||||||
|
|
||||||
|
!print *, "endouille"
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine get_m0(gen, phasemask, bannedOrb, vect, mask, h, p, sp, coefs)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: gen(N_int, 2), mask(N_int, 2)
|
||||||
|
integer(1), intent(in) :: phasemask(N_int*bit_kind_size, 2)
|
||||||
|
logical, intent(in) :: bannedOrb(mo_tot_num)
|
||||||
|
double precision, intent(in) :: coefs(N_states)
|
||||||
|
double precision, intent(inout) :: vect(N_states, mo_tot_num)
|
||||||
|
integer, intent(in) :: sp, h(0:2, 2), p(0:3, 2)
|
||||||
|
integer :: i
|
||||||
|
logical :: ok, lbanned(mo_tot_num)
|
||||||
|
integer(bit_kind) :: det(N_int, 2)
|
||||||
|
double precision :: hij
|
||||||
|
|
||||||
|
lbanned = bannedOrb
|
||||||
|
lbanned(p(1,sp)) = .true.
|
||||||
|
do i=1,mo_tot_num
|
||||||
|
if(lbanned(i)) cycle
|
||||||
|
call apply_particle(mask, sp, i, det, ok, N_int)
|
||||||
|
!call assert(ok, "qsdo")
|
||||||
|
call i_h_j(gen, det, N_int, hij)
|
||||||
|
vect(:, i) += hij * coefs
|
||||||
|
end do
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine spot_hasBeen(mask, sp, det, i_gen, N, banned, fullMatch)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind),intent(in) :: mask(N_int, 2), det(N_int, 2, N)
|
||||||
|
integer, intent(in) :: i_gen, N, sp
|
||||||
|
logical, intent(inout) :: banned(mo_tot_num)
|
||||||
|
logical, intent(out) :: fullMatch
|
||||||
|
|
||||||
|
|
||||||
|
integer :: i, j, na, nb, list(3), nt
|
||||||
|
integer(bit_kind) :: myMask(N_int, 2), negMask(N_int, 2)
|
||||||
|
|
||||||
|
fullMatch = .false.
|
||||||
|
|
||||||
|
do i=1,N_int
|
||||||
|
negMask(i,1) = not(mask(i,1))
|
||||||
|
negMask(i,2) = not(mask(i,2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
genl : do i=1, N
|
||||||
|
nt = 0
|
||||||
|
|
||||||
|
do j=1, N_int
|
||||||
|
myMask(j, 1) = iand(det(j, 1, i), negMask(j, 1))
|
||||||
|
myMask(j, 2) = iand(det(j, 2, i), negMask(j, 2))
|
||||||
|
nt += popcnt(myMask(j, 1)) + popcnt(myMask(j, 2))
|
||||||
|
end do
|
||||||
|
|
||||||
|
if(nt > 3) cycle
|
||||||
|
|
||||||
|
if(nt <= 2 .and. i < i_gen) then
|
||||||
|
fullMatch = .true.
|
||||||
|
return
|
||||||
|
end if
|
||||||
|
|
||||||
|
call bitstring_to_list(myMask(1,sp), list(1), na, N_int)
|
||||||
|
|
||||||
|
if(nt == 3 .and. i < i_gen) then
|
||||||
|
do j=1,na
|
||||||
|
banned(list(j)) = .true.
|
||||||
|
end do
|
||||||
|
else if(nt == 1 .and. na == 1) then
|
||||||
|
banned(list(1)) = .true.
|
||||||
|
end if
|
||||||
|
end do genl
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
subroutine debug_hij_mo(hij, gen, mask, s1, p1)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer(bit_kind), intent(in) :: gen(N_int,2), mask(N_int,2)
|
||||||
|
double precision, intent(in) :: hij
|
||||||
|
integer, intent(in) :: s1, p1
|
||||||
|
integer(bit_kind) :: det(N_int,2)
|
||||||
|
double precision :: hij_ref, phase_ref
|
||||||
|
logical :: ok
|
||||||
|
integer :: degree
|
||||||
|
integer :: exc(0:2,2,2)
|
||||||
|
logical, external :: detEq
|
||||||
|
|
||||||
|
call apply_particle(mask, s1, p1, det, ok, N_int)
|
||||||
|
!call assert(ok, "nokey_mo")
|
||||||
|
!call assert(.not. detEq(det, gen, N_int), "Hii ...")
|
||||||
|
call i_H_j_phase_out(gen,det,N_int,hij_ref,phase_ref,exc,degree)
|
||||||
|
if(hij /= hij_ref) then
|
||||||
|
print *, hij, hij_ref
|
||||||
|
print *, s1, p1
|
||||||
|
call debug_det(gen, N_int)
|
||||||
|
call debug_det(mask, N_int)
|
||||||
|
call debug_det(det, N_int)
|
||||||
|
stop
|
||||||
|
end if
|
||||||
|
end function
|
||||||
|
|
@ -9,7 +9,6 @@ program selection_slave
|
|||||||
call provide_everything
|
call provide_everything
|
||||||
call switch_qp_run_to_master
|
call switch_qp_run_to_master
|
||||||
call run_wf
|
call run_wf
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
subroutine provide_everything
|
subroutine provide_everything
|
||||||
@ -80,6 +79,6 @@ subroutine selection_dressing_slave_tcp(i,energy)
|
|||||||
double precision, intent(in) :: energy(N_states_diag)
|
double precision, intent(in) :: energy(N_states_diag)
|
||||||
integer, intent(in) :: i
|
integer, intent(in) :: i
|
||||||
|
|
||||||
call selection_slaved(0,i,energy)
|
call run_selection_slave(0,i,energy)
|
||||||
end
|
end
|
||||||
|
|
||||||
|
@ -723,3 +723,153 @@ integer function detCmp(a,b,Nint)
|
|||||||
end function
|
end function
|
||||||
|
|
||||||
|
|
||||||
|
subroutine apply_excitation(det, exc, res, ok, Nint)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
|
||||||
|
integer, intent(in) :: Nint
|
||||||
|
integer, intent(in) :: exc(0:2,2,2)
|
||||||
|
integer(bit_kind),intent(in) :: det(Nint, 2)
|
||||||
|
integer(bit_kind),intent(out) :: res(Nint, 2)
|
||||||
|
logical, intent(out) :: ok
|
||||||
|
integer :: h1,p1,h2,p2,s1,s2,degree
|
||||||
|
integer :: ii, pos
|
||||||
|
|
||||||
|
|
||||||
|
ok = .false.
|
||||||
|
degree = exc(0,1,1) + exc(0,1,2)
|
||||||
|
|
||||||
|
if(.not. (degree > 0 .and. degree <= 2)) then
|
||||||
|
print *, degree
|
||||||
|
print *, "apply ex"
|
||||||
|
STOP
|
||||||
|
endif
|
||||||
|
|
||||||
|
call decode_exc(exc,degree,h1,p1,h2,p2,s1,s2)
|
||||||
|
res = det
|
||||||
|
|
||||||
|
ii = (h1-1)/bit_kind_size + 1
|
||||||
|
pos = mod(h1-1, 64)!iand(h1-1,bit_kind_size-1) ! mod 64
|
||||||
|
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) == 0_8) return
|
||||||
|
res(ii, s1) = ibclr(res(ii, s1), pos)
|
||||||
|
|
||||||
|
ii = (p1-1)/bit_kind_size + 1
|
||||||
|
pos = mod(p1-1, 64)!iand(p1-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) /= 0_8) return
|
||||||
|
res(ii, s1) = ibset(res(ii, s1), pos)
|
||||||
|
|
||||||
|
if(degree == 2) then
|
||||||
|
ii = (h2-1)/bit_kind_size + 1
|
||||||
|
pos = mod(h2-1, 64)!iand(h2-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s2), ishft(1_bit_kind, pos)) == 0_8) return
|
||||||
|
res(ii, s2) = ibclr(res(ii, s2), pos)
|
||||||
|
|
||||||
|
ii = (p2-1)/bit_kind_size + 1
|
||||||
|
pos = mod(p2-1, 64)!iand(p2-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s2), ishft(1_bit_kind, pos)) /= 0_8) return
|
||||||
|
res(ii, s2) = ibset(res(ii, s2), pos)
|
||||||
|
endif
|
||||||
|
|
||||||
|
ok = .true.
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine apply_particles(det, s1, p1, s2, p2, res, ok, Nint)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
integer, intent(in) :: Nint
|
||||||
|
integer, intent(in) :: s1, p1, s2, p2
|
||||||
|
integer(bit_kind),intent(in) :: det(Nint, 2)
|
||||||
|
integer(bit_kind),intent(out) :: res(Nint, 2)
|
||||||
|
logical, intent(out) :: ok
|
||||||
|
integer :: ii, pos
|
||||||
|
|
||||||
|
ok = .false.
|
||||||
|
res = det
|
||||||
|
|
||||||
|
if(p1 /= 0) then
|
||||||
|
ii = (p1-1)/bit_kind_size + 1
|
||||||
|
pos = mod(p1-1, 64)!iand(p1-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) /= 0_8) return
|
||||||
|
res(ii, s1) = ibset(res(ii, s1), pos)
|
||||||
|
end if
|
||||||
|
|
||||||
|
ii = (p2-1)/bit_kind_size + 1
|
||||||
|
pos = mod(p2-1, 64)!iand(p2-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s2), ishft(1_bit_kind, pos)) /= 0_8) return
|
||||||
|
res(ii, s2) = ibset(res(ii, s2), pos)
|
||||||
|
|
||||||
|
ok = .true.
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine apply_holes(det, s1, h1, s2, h2, res, ok, Nint)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
integer, intent(in) :: Nint
|
||||||
|
integer, intent(in) :: s1, h1, s2, h2
|
||||||
|
integer(bit_kind),intent(in) :: det(Nint, 2)
|
||||||
|
integer(bit_kind),intent(out) :: res(Nint, 2)
|
||||||
|
logical, intent(out) :: ok
|
||||||
|
integer :: ii, pos
|
||||||
|
|
||||||
|
ok = .false.
|
||||||
|
res = det
|
||||||
|
|
||||||
|
if(h1 /= 0) then
|
||||||
|
ii = (h1-1)/bit_kind_size + 1
|
||||||
|
pos = mod(h1-1, 64)!iand(h1-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) == 0_8) return
|
||||||
|
res(ii, s1) = ibclr(res(ii, s1), pos)
|
||||||
|
end if
|
||||||
|
|
||||||
|
ii = (h2-1)/bit_kind_size + 1
|
||||||
|
pos = mod(h2-1, 64)!iand(h2-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s2), ishft(1_bit_kind, pos)) == 0_8) return
|
||||||
|
res(ii, s2) = ibclr(res(ii, s2), pos)
|
||||||
|
|
||||||
|
ok = .true.
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
subroutine apply_particle(det, s1, p1, res, ok, Nint)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
integer, intent(in) :: Nint
|
||||||
|
integer, intent(in) :: s1, p1
|
||||||
|
integer(bit_kind),intent(in) :: det(Nint, 2)
|
||||||
|
integer(bit_kind),intent(out) :: res(Nint, 2)
|
||||||
|
logical, intent(out) :: ok
|
||||||
|
integer :: ii, pos
|
||||||
|
|
||||||
|
ok = .false.
|
||||||
|
res = det
|
||||||
|
|
||||||
|
ii = (p1-1)/bit_kind_size + 1
|
||||||
|
pos = mod(p1-1, 64)!iand(p1-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) /= 0_8) return
|
||||||
|
res(ii, s1) = ibset(res(ii, s1), pos)
|
||||||
|
|
||||||
|
ok = .true.
|
||||||
|
end subroutine
|
||||||
|
|
||||||
|
|
||||||
|
subroutine apply_hole(det, s1, h1, res, ok, Nint)
|
||||||
|
use bitmasks
|
||||||
|
implicit none
|
||||||
|
integer, intent(in) :: Nint
|
||||||
|
integer, intent(in) :: s1, h1
|
||||||
|
integer(bit_kind),intent(in) :: det(Nint, 2)
|
||||||
|
integer(bit_kind),intent(out) :: res(Nint, 2)
|
||||||
|
logical, intent(out) :: ok
|
||||||
|
integer :: ii, pos
|
||||||
|
|
||||||
|
ok = .false.
|
||||||
|
res = det
|
||||||
|
|
||||||
|
ii = (h1-1)/bit_kind_size + 1
|
||||||
|
pos = mod(h1-1, 64)!iand(h1-1,bit_kind_size-1)
|
||||||
|
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) == 0_8) return
|
||||||
|
res(ii, s1) = ibclr(res(ii, s1), pos)
|
||||||
|
|
||||||
|
ok = .true.
|
||||||
|
end subroutine
|
@ -1781,55 +1781,102 @@ subroutine H_u_0(v_0,u_0,H_jj,n,keys_tmp,Nint)
|
|||||||
end
|
end
|
||||||
|
|
||||||
|
|
||||||
subroutine apply_excitation(det, exc, res, ok, Nint)
|
subroutine get_double_excitation_phase(det1,det2,exc,phase,Nint)
|
||||||
use bitmasks
|
use bitmasks
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer, intent(in) :: Nint
|
integer, intent(in) :: Nint
|
||||||
integer, intent(in) :: exc(0:2,2,2)
|
integer(bit_kind), intent(in) :: det1(Nint,2)
|
||||||
integer(bit_kind),intent(in) :: det(Nint, 2)
|
integer(bit_kind), intent(in) :: det2(Nint,2)
|
||||||
integer(bit_kind),intent(out) :: res(Nint, 2)
|
integer, intent(in) :: exc(0:2,2,2)
|
||||||
logical, intent(out) :: ok
|
double precision, intent(out) :: phase
|
||||||
integer :: h1,p1,h2,p2,s1,s2,degree
|
integer :: tz
|
||||||
integer :: ii, pos
|
integer :: l, ispin, idx_hole, idx_particle, ishift
|
||||||
|
integer :: nperm
|
||||||
|
integer :: i,j,k,m,n
|
||||||
|
integer :: high, low
|
||||||
|
integer :: a,b,c,d
|
||||||
|
integer(bit_kind) :: hole, particle, tmp
|
||||||
|
double precision, parameter :: phase_dble(0:1) = (/ 1.d0, -1.d0 /)
|
||||||
|
|
||||||
|
ASSERT (Nint > 0)
|
||||||
|
nperm = 0
|
||||||
|
do ispin = 1,2
|
||||||
|
select case (exc(0,1,ispin))
|
||||||
|
case(0)
|
||||||
|
cycle
|
||||||
|
|
||||||
|
case(1)
|
||||||
|
low = min(exc(1,1,ispin), exc(1,2,ispin))
|
||||||
|
high = max(exc(1,1,ispin), exc(1,2,ispin))
|
||||||
|
|
||||||
|
ASSERT (low > 0)
|
||||||
|
j = ishft(low-1,-bit_kind_shift)+1 ! Find integer in array(Nint)
|
||||||
|
n = iand(low-1,bit_kind_size-1)+1 ! mod(low,bit_kind_size)
|
||||||
|
ASSERT (high > 0)
|
||||||
|
k = ishft(high-1,-bit_kind_shift)+1
|
||||||
|
m = iand(high-1,bit_kind_size-1)+1
|
||||||
|
|
||||||
|
if (j==k) then
|
||||||
|
nperm = nperm + popcnt(iand(det1(j,ispin), &
|
||||||
|
iand( ibset(0_bit_kind,m-1)-1_bit_kind, &
|
||||||
|
ibclr(-1_bit_kind,n)+1_bit_kind ) ))
|
||||||
|
else
|
||||||
|
nperm = nperm + popcnt(iand(det1(k,ispin), &
|
||||||
|
ibset(0_bit_kind,m-1)-1_bit_kind))
|
||||||
|
if (n < bit_kind_size) then
|
||||||
|
nperm = nperm + popcnt(iand(det1(j,ispin), ibclr(-1_bit_kind,n) +1_bit_kind))
|
||||||
|
endif
|
||||||
|
do i=j+1,k-1
|
||||||
|
nperm = nperm + popcnt(det1(i,ispin))
|
||||||
|
end do
|
||||||
|
endif
|
||||||
|
|
||||||
|
case (2)
|
||||||
|
|
||||||
|
do i=1,2
|
||||||
|
low = min(exc(i,1,ispin), exc(i,2,ispin))
|
||||||
|
high = max(exc(i,1,ispin), exc(i,2,ispin))
|
||||||
|
|
||||||
|
ASSERT (low > 0)
|
||||||
|
j = ishft(low-1,-bit_kind_shift)+1 ! Find integer in array(Nint)
|
||||||
|
n = iand(low-1,bit_kind_size-1)+1 ! mod(low,bit_kind_size)
|
||||||
|
ASSERT (high > 0)
|
||||||
|
k = ishft(high-1,-bit_kind_shift)+1
|
||||||
|
m = iand(high-1,bit_kind_size-1)+1
|
||||||
|
|
||||||
|
if (j==k) then
|
||||||
|
nperm = nperm + popcnt(iand(det1(j,ispin), &
|
||||||
|
iand( ibset(0_bit_kind,m-1)-1_bit_kind, &
|
||||||
|
ibclr(-1_bit_kind,n)+1_bit_kind ) ))
|
||||||
|
else
|
||||||
|
nperm = nperm + popcnt(iand(det1(k,ispin), &
|
||||||
|
ibset(0_bit_kind,m-1)-1_bit_kind))
|
||||||
|
if (n < bit_kind_size) then
|
||||||
|
nperm = nperm + popcnt(iand(det1(j,ispin), ibclr(-1_bit_kind,n) +1_bit_kind))
|
||||||
|
endif
|
||||||
|
do l=j+1,k-1
|
||||||
|
nperm = nperm + popcnt(det1(l,ispin))
|
||||||
|
end do
|
||||||
|
endif
|
||||||
|
|
||||||
|
enddo
|
||||||
|
|
||||||
|
a = min(exc(1,1,ispin), exc(1,2,ispin))
|
||||||
|
b = max(exc(1,1,ispin), exc(1,2,ispin))
|
||||||
|
c = min(exc(2,1,ispin), exc(2,2,ispin))
|
||||||
|
d = max(exc(2,1,ispin), exc(2,2,ispin))
|
||||||
|
if (c>a .and. c<b .and. d>b) then
|
||||||
|
nperm = nperm + 1
|
||||||
|
endif
|
||||||
|
exit
|
||||||
|
end select
|
||||||
|
|
||||||
|
enddo
|
||||||
|
phase = phase_dble(iand(nperm,1))
|
||||||
|
end
|
||||||
|
|
||||||
|
|
||||||
ok = .false.
|
|
||||||
degree = exc(0,1,1) + exc(0,1,2)
|
|
||||||
|
|
||||||
if(.not. (degree > 0 .and. degree <= 2)) then
|
|
||||||
print *, degree
|
|
||||||
print *, "apply ex"
|
|
||||||
STOP
|
|
||||||
endif
|
|
||||||
|
|
||||||
call decode_exc(exc,degree,h1,p1,h2,p2,s1,s2)
|
|
||||||
res = det
|
|
||||||
|
|
||||||
ii = (h1-1)/bit_kind_size + 1
|
|
||||||
pos = mod(h1-1, 64)!iand(h1-1,bit_kind_size-1) ! mod 64
|
|
||||||
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) == 0_8) return
|
|
||||||
res(ii, s1) = ibclr(res(ii, s1), pos)
|
|
||||||
|
|
||||||
ii = (p1-1)/bit_kind_size + 1
|
|
||||||
pos = mod(p1-1, 64)!iand(p1-1,bit_kind_size-1)
|
|
||||||
if(iand(det(ii, s1), ishft(1_bit_kind, pos)) /= 0_8) return
|
|
||||||
res(ii, s1) = ibset(res(ii, s1), pos)
|
|
||||||
|
|
||||||
if(degree == 2) then
|
|
||||||
ii = (h2-1)/bit_kind_size + 1
|
|
||||||
pos = mod(h2-1, 64)!iand(h2-1,bit_kind_size-1)
|
|
||||||
if(iand(det(ii, s2), ishft(1_bit_kind, pos)) == 0_8) return
|
|
||||||
res(ii, s2) = ibclr(res(ii, s2), pos)
|
|
||||||
|
|
||||||
ii = (p2-1)/bit_kind_size + 1
|
|
||||||
pos = mod(p2-1, 64)!iand(p2-1,bit_kind_size-1)
|
|
||||||
if(iand(det(ii, s2), ishft(1_bit_kind, pos)) /= 0_8) return
|
|
||||||
res(ii, s2) = ibset(res(ii, s2), pos)
|
|
||||||
endif
|
|
||||||
|
|
||||||
ok = .true.
|
|
||||||
end subroutine
|
|
||||||
|
|
||||||
subroutine get_phase(key1,key2,phase,Nint)
|
subroutine get_phase(key1,key2,phase,Nint)
|
||||||
use bitmasks
|
use bitmasks
|
||||||
|
Loading…
Reference in New Issue
Block a user