10
0
mirror of https://github.com/LCPQ/quantum_package synced 2024-06-29 16:34:50 +02:00
quantum_package/src/Davidson/davidson_parallel.irp.f

398 lines
11 KiB
Fortran
Raw Normal View History

2016-09-30 15:29:06 +02:00
use bitmasks
2016-09-30 18:33:46 +02:00
use f77_zmq
2016-09-30 15:29:06 +02:00
subroutine davidson_slave_inproc(i)
implicit none
integer, intent(in) :: i
call davidson_run_slave(1,i)
end
subroutine davidson_slave_tcp(i)
implicit none
integer, intent(in) :: i
call davidson_run_slave(0,i)
end
subroutine davidson_run_slave(thread,iproc)
use f77_zmq
implicit none
integer, intent(in) :: thread, iproc
2016-10-11 22:45:40 +02:00
integer :: worker_id, task_id, blockb
2016-09-30 15:29:06 +02:00
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
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 end_zmq_to_qp_run_socket(zmq_to_qp_run_socket)
call end_zmq_push_socket(zmq_socket_push,thread)
return
end if
2017-04-19 12:24:09 +02:00
call davidson_slave_work(zmq_to_qp_run_socket, zmq_socket_push, N_states_diag, N_det, worker_id)
2016-09-30 15:29:06 +02:00
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
2017-04-19 12:24:09 +02:00
subroutine davidson_slave_work(zmq_to_qp_run_socket, zmq_socket_push, N_st, sze, worker_id)
2016-09-30 15:29:06 +02:00
use f77_zmq
implicit none
integer(ZMQ_PTR),intent(in) :: zmq_to_qp_run_socket
integer(ZMQ_PTR),intent(in) :: zmq_socket_push
2017-04-19 12:24:09 +02:00
integer,intent(in) :: worker_id, N_st, sze
2017-04-17 01:36:16 +02:00
integer :: task_id
character*(512) :: msg
integer :: imin, imax, ishift, istep
2016-09-30 15:29:06 +02:00
2017-04-17 01:36:16 +02:00
double precision, allocatable :: v_0(:,:), s_0(:,:), u_t(:,:)
!DIR$ ATTRIBUTES ALIGN : $IRP_ALIGN :: u_t, v_0, s_0
2016-09-30 15:29:06 +02:00
2017-04-17 01:36:16 +02:00
! Get wave function (u_t)
! -----------------------
integer :: rc
write(msg, *) 'get_psi ', worker_id
rc = f77_zmq_send(zmq_to_qp_run_socket,trim(msg),len(trim(msg)),0)
if (rc /= len(trim(msg))) then
print *, 'f77_zmq_send(zmq_to_qp_run_socket,trim(msg),len(trim(msg)),0)'
stop 'error'
endif
rc = f77_zmq_recv(zmq_to_qp_run_socket,msg,len(msg),0)
if (msg(1:13) /= 'get_psi_reply') then
print *, rc, trim(msg)
print *, 'Error in get_psi_reply'
stop 'error'
endif
integer :: N_states_read, N_det_read, psi_det_size_read
integer :: N_det_selectors_read, N_det_generators_read
2017-04-19 12:08:17 +02:00
double precision :: energy(N_st)
read(msg(14:rc),*) rc, N_states_read, N_det_read, psi_det_size_read, &
2017-04-17 01:36:16 +02:00
N_det_generators_read, N_det_selectors_read
2017-04-19 12:08:17 +02:00
2017-04-17 01:36:16 +02:00
if (rc /= worker_id) then
print *, 'Wrong worker ID'
stop 'error'
endif
2016-09-30 18:33:46 +02:00
2017-04-17 01:36:16 +02:00
if (N_states_read /= N_st) then
2017-04-19 12:08:17 +02:00
print *, N_st
2017-04-17 01:36:16 +02:00
stop 'error : N_st'
endif
if (N_det_read /= N_det) then
2017-04-18 18:55:51 +02:00
N_det = N_det_read
TOUCH N_det
2017-04-17 01:36:16 +02:00
endif
2017-04-19 16:44:34 +02:00
allocate(v_0(sze,N_st), s_0(sze,N_st),u_t(N_st,N_det))
2017-04-17 01:36:16 +02:00
rc = f77_zmq_recv(zmq_to_qp_run_socket,psi_det,N_int*2*N_det*bit_kind,0)
if (rc /= N_int*2*N_det*bit_kind) then
print *, 'f77_zmq_recv(zmq_to_qp_run_socket,psi_det,N_int*2*N_det*bit_kind,0)'
stop 'error'
endif
rc = f77_zmq_recv(zmq_to_qp_run_socket,u_t,size(u_t)*8,0)
if (rc /= size(u_t)*8) then
print *, rc, size(u_t)*8
print *, 'f77_zmq_recv(zmq_to_qp_run_socket,u_t,size(u_t)×8,0)'
stop 'error'
endif
2017-04-19 12:08:17 +02:00
rc = f77_zmq_recv(zmq_to_qp_run_socket,energy,N_st*8,0)
if (rc /= N_st*8) then
print *, '77_zmq_recv(zmq_to_qp_run_socket,energy,N_st*8,0)'
2017-04-17 01:36:16 +02:00
stop 'error'
endif
! Run tasks
! ---------
2016-10-10 14:45:58 +02:00
2016-09-30 15:29:06 +02:00
do
2017-04-17 01:36:16 +02:00
v_0 = 0.d0
s_0 = 0.d0
call get_task_from_taskserver(zmq_to_qp_run_socket,worker_id, task_id, msg)
2016-10-10 14:45:58 +02:00
if(task_id == 0) exit
2017-04-17 01:36:16 +02:00
read (msg,*) imin, imax, ishift, istep
2017-04-19 12:24:09 +02:00
call H_S2_u_0_nstates_openmp_work(v_0,s_0,u_t,N_st,N_det,imin,imax,ishift,istep)
2016-10-10 14:45:58 +02:00
call task_done_to_taskserver(zmq_to_qp_run_socket,worker_id,task_id)
2017-04-17 01:36:16 +02:00
call davidson_push_results(zmq_socket_push, v_0, s_0, task_id)
2016-09-30 15:29:06 +02:00
end do
2017-04-19 12:08:17 +02:00
deallocate(v_0, s_0, u_t)
2016-10-09 00:11:50 +02:00
2016-09-30 15:29:06 +02:00
end subroutine
2017-04-17 01:36:16 +02:00
subroutine davidson_push_results(zmq_socket_push, v_0, s_0, task_id)
2016-09-30 15:29:06 +02:00
use f77_zmq
implicit none
integer(ZMQ_PTR) ,intent(in) :: zmq_socket_push
2016-10-10 14:45:58 +02:00
integer ,intent(in) :: task_id
2017-04-17 01:36:16 +02:00
double precision ,intent(in) :: v_0(N_det,N_states_diag)
double precision ,intent(in) :: s_0(N_det,N_states_diag)
2016-09-30 15:29:06 +02:00
integer :: rc
2017-04-17 01:36:16 +02:00
rc = f77_zmq_send( zmq_socket_push, v_0, 8*N_states_diag*N_det, ZMQ_SNDMORE)
if(rc /= 8*N_states_diag* N_det) stop "davidson_push_results failed to push vt"
2016-09-30 15:29:06 +02:00
2017-04-17 01:36:16 +02:00
rc = f77_zmq_send( zmq_socket_push, s_0, 8*N_states_diag*N_det, ZMQ_SNDMORE)
if(rc /= 8*N_states_diag* N_det) stop "davidson_push_results failed to push st"
2016-09-30 15:29:06 +02:00
2016-10-10 14:45:58 +02:00
rc = f77_zmq_send( zmq_socket_push, task_id, 4, 0)
if(rc /= 4) stop "davidson_push_results failed to push task_id"
2017-02-08 20:54:15 +01:00
! Activate is zmq_socket_push is a REQ
integer :: idummy
rc = f77_zmq_recv( zmq_socket_push, idummy, 4, 0)
if (rc /= 4) then
print *, irp_here, ': f77_zmq_send( zmq_socket_push, idummy, 4, 0)'
stop 'error'
endif
2016-09-30 15:29:06 +02:00
end subroutine
2017-04-17 01:36:16 +02:00
subroutine davidson_pull_results(zmq_socket_pull, v_0, s_0, task_id)
2016-09-30 15:29:06 +02:00
use f77_zmq
implicit none
integer(ZMQ_PTR) ,intent(in) :: zmq_socket_pull
2016-10-10 14:45:58 +02:00
integer ,intent(out) :: task_id
2017-04-17 01:36:16 +02:00
double precision ,intent(out) :: v_0(N_det,N_states_diag)
double precision ,intent(out) :: s_0(N_det,N_states_diag)
2016-09-30 15:29:06 +02:00
integer :: rc
2017-04-19 12:08:17 +02:00
rc = f77_zmq_recv( zmq_socket_pull, v_0, 8*N_det*N_states_diag, 0)
if(rc /= 8*N_det*N_states_diag) stop "davidson_push_results failed to pull v_0"
2016-09-30 15:29:06 +02:00
2017-04-19 12:08:17 +02:00
rc = f77_zmq_recv( zmq_socket_pull, s_0, 8*N_det*N_states_diag, 0)
if(rc /= 8*N_det*N_states_diag) stop "davidson_push_results failed to pull s_0"
2016-09-30 15:29:06 +02:00
2016-10-10 14:45:58 +02:00
rc = f77_zmq_recv( zmq_socket_pull, task_id, 4, 0)
if(rc /= 4) stop "davidson_pull_results failed to pull task_id"
2017-02-08 20:54:15 +01:00
! Activate if zmq_socket_pull is a REP
rc = f77_zmq_send( zmq_socket_pull, 0, 4, 0)
if (rc /= 4) then
print *, irp_here, ' : f77_zmq_send (zmq_socket_pull,...'
stop 'error'
endif
2016-09-30 15:29:06 +02:00
end subroutine
2017-04-19 12:24:09 +02:00
subroutine davidson_collector(zmq_to_qp_run_socket, v0, s0, sze, N_st)
2016-09-30 15:29:06 +02:00
use f77_zmq
implicit none
2017-04-19 12:24:09 +02:00
integer, intent(in) :: sze, N_st
2016-10-07 12:22:43 +02:00
integer(ZMQ_PTR), intent(in) :: zmq_to_qp_run_socket
2016-09-30 15:29:06 +02:00
2017-04-19 12:24:09 +02:00
double precision ,intent(inout) :: v0(sze, N_st)
double precision ,intent(inout) :: s0(sze, N_st)
2016-10-07 12:22:43 +02:00
2017-04-17 01:36:16 +02:00
integer :: more, task_id
2016-09-30 15:29:06 +02:00
2017-04-17 01:36:16 +02:00
double precision, allocatable :: v_0(:,:), s_0(:,:)
integer :: i,j
2017-04-18 16:46:08 +02:00
integer(ZMQ_PTR), external :: new_zmq_pull_socket
integer(ZMQ_PTR) :: zmq_socket_pull
2016-10-07 09:46:59 +02:00
2017-04-19 12:08:17 +02:00
allocate(v_0(N_det,N_st), s_0(N_det,N_st))
2017-04-17 01:36:16 +02:00
v0 = 0.d0
s0 = 0.d0
2016-09-30 15:29:06 +02:00
more = 1
2017-04-18 16:46:08 +02:00
zmq_socket_pull = new_zmq_pull_socket()
2016-09-30 15:29:06 +02:00
do while (more == 1)
2017-04-17 01:36:16 +02:00
call davidson_pull_results(zmq_socket_pull, v_0, s_0, task_id)
2017-04-19 12:08:17 +02:00
do j=1,N_st
2017-04-17 01:36:16 +02:00
do i=1,N_det
v0(i,j) = v0(i,j) + v_0(i,j)
s0(i,j) = s0(i,j) + s_0(i,j)
enddo
enddo
2016-10-10 14:45:58 +02:00
call zmq_delete_task(zmq_to_qp_run_socket,zmq_socket_pull,task_id,more)
2016-09-30 15:29:06 +02:00
end do
2017-04-17 01:36:16 +02:00
deallocate(v_0,s_0)
2017-02-27 10:43:57 +01:00
call end_zmq_pull_socket(zmq_socket_pull)
2016-10-08 00:39:55 +02:00
2016-09-30 15:29:06 +02:00
end subroutine
2016-10-10 14:45:58 +02:00
2017-04-18 16:46:08 +02:00
2017-04-19 12:24:09 +02:00
subroutine H_S2_u_0_nstates_zmq(v_0,s_0,u_0,N_st,sze)
2017-04-17 01:36:16 +02:00
use omp_lib
use bitmasks
2016-09-30 18:33:46 +02:00
use f77_zmq
implicit none
2017-04-17 01:36:16 +02:00
BEGIN_DOC
! Computes v_0 = H|u_0> and s_0 = S^2 |u_0>
!
! n : number of determinants
!
! H_jj : array of <j|H|j>
!
! S2_jj : array of <j|S^2|j>
END_DOC
2017-04-19 12:24:09 +02:00
integer, intent(in) :: N_st, sze
double precision, intent(out) :: v_0(sze,N_st), s_0(sze,N_st)
double precision, intent(inout):: u_0(sze,N_st)
2017-04-17 01:36:16 +02:00
integer :: i,j,k
integer :: ithread
double precision, allocatable :: u_t(:,:)
!DIR$ ATTRIBUTES ALIGN : $IRP_ALIGN :: u_t
2017-04-19 19:45:18 +02:00
PROVIDE psi_det_beta_unique psi_bilinear_matrix_order_transp_reverse psi_det_alpha_unique
PROVIDE psi_bilinear_matrix_transp_values psi_bilinear_matrix_values psi_bilinear_matrix_columns_loc
PROVIDE ref_bitmask_energy nproc
2017-04-17 01:36:16 +02:00
allocate(u_t(N_st,N_det))
do k=1,N_st
call dset_order(u_0(1,k),psi_bilinear_matrix_order,N_det)
2016-09-30 18:33:46 +02:00
enddo
2017-04-17 01:36:16 +02:00
call dtranspose( &
u_0, &
size(u_0, 1), &
u_t, &
size(u_t, 1), &
N_det, N_st)
2016-09-30 18:33:46 +02:00
2017-04-17 01:36:16 +02:00
integer(ZMQ_PTR) :: zmq_to_qp_run_socket
2016-09-30 18:33:46 +02:00
2017-04-19 12:24:09 +02:00
if(N_st /= N_states_diag .or. sze < N_det) stop "assert fail in H_S2_u_0_nstates"
2016-09-30 18:33:46 +02:00
2017-04-17 01:36:16 +02:00
ASSERT (Nint > 0)
ASSERT (Nint == N_int)
ASSERT (n>0)
2016-09-30 15:29:06 +02:00
2017-04-17 01:36:16 +02:00
call new_parallel_job(zmq_to_qp_run_socket,'davidson')
2016-09-30 18:33:46 +02:00
2017-04-17 01:36:16 +02:00
character*(512) :: task
integer :: rc
double precision :: energy(N_st)
energy = 0.d0
task = ' '
write(task,*) 'put_psi ', 1, N_st, N_det, N_det
rc = f77_zmq_send(zmq_to_qp_run_socket,trim(task),len(trim(task)),ZMQ_SNDMORE)
if (rc /= len(trim(task))) then
print *, 'f77_zmq_send(zmq_to_qp_run_socket,trim(task),len(trim(task)),ZMQ_SNDMORE)'
stop 'error'
2017-03-25 11:57:06 +01:00
endif
2017-04-17 01:36:16 +02:00
rc = f77_zmq_send(zmq_to_qp_run_socket,psi_det,N_int*2*N_det*bit_kind,ZMQ_SNDMORE)
if (rc /= N_int*2*N_det*bit_kind) then
print *, 'f77_zmq_send(zmq_to_qp_run_socket,psi_det,N_int*2*N_det*bit_kind,ZMQ_SNDMORE)'
stop 'error'
2017-03-25 11:57:06 +01:00
endif
2017-04-17 01:36:16 +02:00
rc = f77_zmq_send(zmq_to_qp_run_socket,u_t,size(u_t)*8,ZMQ_SNDMORE)
if (rc /= size(u_t)*8) then
print *, 'f77_zmq_send(zmq_to_qp_run_socket,u_t,size(u_t)*8,ZMQ_SNDMORE)'
stop 'error'
2017-03-01 01:19:17 +01:00
endif
2017-04-17 01:36:16 +02:00
rc = f77_zmq_send(zmq_to_qp_run_socket,energy,N_st*8,0)
if (rc /= N_st*8) then
print *, 'f77_zmq_send(zmq_to_qp_run_socket,energy,size_energy*8,0)'
stop 'error'
2017-03-25 11:57:06 +01:00
endif
2017-04-17 01:36:16 +02:00
rc = f77_zmq_recv(zmq_to_qp_run_socket,task,len(task),0)
if (task(1:rc) /= 'put_psi_reply 1') then
print *, rc, trim(task)
print *, 'Error in put_psi_reply'
stop 'error'
2017-03-01 01:19:17 +01:00
endif
2016-10-03 14:02:26 +02:00
2017-04-17 01:36:16 +02:00
deallocate(u_t)
2016-09-30 18:33:46 +02:00
2017-04-19 19:45:18 +02:00
! Create tasks
! ============
2017-04-17 01:36:16 +02:00
integer :: istep, imin, imax, ishift
2017-04-19 19:45:18 +02:00
double precision :: w, max_workload, N_det_inv, di
2017-04-19 19:56:38 +02:00
max_workload = 200000.d0
2017-04-19 19:45:18 +02:00
w = 0.d0
istep=4
ishift=0
imin=1
N_det_inv = 1.d0/dble(N_det)
di = dble(N_det)
do imax=1,N_det
di = di-1.d0
2017-04-19 20:22:37 +02:00
w = w + di*N_det_inv
2017-04-19 19:45:18 +02:00
if (w > max_workload) then
do ishift=0,istep-1
write(task,'(4(I9,1X),1A)') imin, imax, ishift, istep, '|'
call add_task_to_taskserver(zmq_to_qp_run_socket,trim(task))
enddo
istep = max(istep-1,1)
imin = imax+1
w = 0.d0
endif
enddo
if (w > 0.d0) then
imax = N_det
2017-04-18 18:41:07 +02:00
do ishift=0,istep-1
write(task,'(4(I9,1X),1A)') imin, imax, ishift, istep, '|'
call add_task_to_taskserver(zmq_to_qp_run_socket,trim(task))
enddo
2017-04-19 19:45:18 +02:00
endif
2017-04-18 18:41:07 +02:00
2017-04-17 01:36:16 +02:00
v_0 = 0.d0
s_0 = 0.d0
call omp_set_nested(.True.)
2017-04-19 12:08:17 +02:00
call zmq_set_running(zmq_to_qp_run_socket)
2017-04-17 01:36:16 +02:00
!$OMP PARALLEL NUM_THREADS(2) PRIVATE(ithread)
ithread = omp_get_thread_num()
if (ithread == 0 ) then
2017-04-19 12:24:09 +02:00
call davidson_collector(zmq_to_qp_run_socket, v_0, s_0, N_det, N_st)
2017-04-17 01:36:16 +02:00
else
call davidson_slave_inproc(1)
endif
!$OMP END PARALLEL
call end_parallel_job(zmq_to_qp_run_socket, 'davidson')
2016-10-10 14:45:58 +02:00
2017-04-17 01:36:16 +02:00
do k=1,N_st
call dset_order(v_0(1,k),psi_bilinear_matrix_order_reverse,N_det)
call dset_order(s_0(1,k),psi_bilinear_matrix_order_reverse,N_det)
call dset_order(u_0(1,k),psi_bilinear_matrix_order_reverse,N_det)
enddo
end
2016-10-10 14:45:58 +02:00