function read_popsfile_det(iunit, nel_loc, BinPops, WalkerTemp, nI, &
PopNifSgn, decode_det, &
nread, gdata_tmp, read_max, trimmed_parts) result(tEOF)
integer, intent(in) :: iunit
integer, intent(in) :: nel_loc
integer(n_int), intent(out) :: WalkerTemp(0:NIfTot)
integer, intent(out) :: nI(nel_loc)
integer, intent(in) :: PopNifSgn
logical, intent(in) :: decode_det
logical, intent(in) :: BinPops
logical, intent(inout), optional :: trimmed_parts
integer(int64), intent(out) :: nread
integer(int64), intent(in), optional :: read_max
real(dp), intent(out) :: gdata_tmp(:)
integer(n_int) :: sgn_int(PopNifSgn)
integer :: flg, stat, k
real(dp) :: sgn(PopNifSgn)
real(dp) :: new_sgn(lenof_sign)
integer(n_int) :: flg_read
logical :: tStoreDet, tEOF
WalkerTemp = 0_n_int
flg_read = 0_n_int
tStoreDet = .false.
tEOF = .false.
nread = 0
r_loop: do while (.not. tStoreDet)
! If we have specified a maximum number of read attempts, then
! stick to that!
if (present(read_max)) then
if (nread == read_max) then
tEOF = .true.
exit
end if
end if
gdata_tmp = 0.0_dp
! All basis parameters match --> Read in directly.
if (tRealPOPSfile) then
if (BinPops) then
read (iunit, iostat=stat) WalkerTemp(0:nifd), sgn, &
flg_read, gdata_tmp
else
read (iunit, *, iostat=stat) WalkerTemp(0:nifd), &
sgn, flg_read, gdata_tmp
end if
else
if (BinPops) then
read (iunit, iostat=stat) WalkerTemp(0:nifd), &
sgn_int, flg_read, gdata_tmp
else
read (iunit, *, iostat=stat) WalkerTemp(0:nifd), &
sgn_int, flg_read, gdata_tmp
end if
sgn = sgn_int
end if
if (stat < 0) then
tEOF = .true. ! End of file reached.
exit r_loop
end if
nread = nread + 1
if ((inum_runs == 2) .and. (PopNifSgn == 1)) then
!Read in pops from a single run. Distribute an identical set of walkers to each walker set
!and then propagate the two independently
new_sgn(1) = sgn(1)
new_sgn(inum_runs) = sgn(1)
else
do k = 1, lenof_sign
new_sgn(k) = sgn(k)
enddo
endif
! Store the sign and flag information in the determinant.
flg = int(flg_read)
call encode_sign(WalkerTemp, new_sgn)
call encode_flags(WalkerTemp, flg)
if ((inum_runs == 2) .and. (PopNifSgn == 1)) then
if (test_flag(WalkerTemp, get_initiator_flag(1))) then
call set_flag(WalkerTemp, get_initiator_flag(2))
else
call clr_flag(WalkerTemp, get_initiator_flag(2))
endif
endif
! Test if we actually want to store this walker...
! SDS: If we have the odd empty site, don't worry about it.
if (any(abs(sgn) >= iWeightPopRead) .and. .not. IsUnoccDet(sgn)) then
tStoreDet = .true.
if (present(trimmed_parts)) trimmed_parts = .true.
exit
end if
enddo r_loop
! Decode the determinant as required
if (.not. tEOF .and. decode_det) then
call decode_bit_det(nI, WalkerTemp)
endif
end function read_popsfile_det