read_pops_splitpops Function

public function read_pops_splitpops(iunit, PopNel, det_tmp, binary_pops, det_list, max_dets, PopNIfSgn, gdata_read_handler, trimmed_parts) result(CurrWalkers)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: iunit
integer, intent(in) :: PopNel
integer, intent(out) :: det_tmp(PopNel)
logical, intent(in) :: binary_pops
integer(kind=n_int), intent(out) :: det_list(0:NifTot,max_dets)
integer, intent(in) :: max_dets
integer, intent(in) :: PopNIfSgn
type(gdata_io_t), intent(in) :: gdata_read_handler
logical, intent(inout) :: trimmed_parts

Return Value integer(kind=int64)


Contents

Source Code


Source Code

    function read_pops_splitpops(iunit, PopNel, det_tmp, binary_pops, &
                                 det_list, max_dets, PopNIfSgn, gdata_read_handler, &
                                 trimmed_parts) &
        result(CurrWalkers)

        ! A routine to read in split popsfiles to each of the nodes.
        !
        ! In: iunit       - The popsfile being read from
        !     binary_pops - Is this a binary popsfile?

        integer, intent(in) :: iunit, PopNel, max_dets, PopNIfSgn
        integer, intent(out) :: det_tmp(PopNel)
        integer(n_int), intent(out) :: det_list(0:NifTot, max_dets)
        logical, intent(in) :: binary_pops
        type(gdata_io_t), intent(in) :: gdata_read_handler
        integer(int64) :: CurrWalkers
        logical, intent(inout) :: trimmed_parts
        character(*), parameter :: this_routine = 'read_pops_splitpops'
        integer :: gdata_size
        integer(n_int), allocatable :: BatchRead(:, :)
        real(dp), allocatable :: gdata(:, :)
        real(dp), allocatable :: gdata_tmp(:)
        logical :: tEOF
        integer :: proc
        integer(int64) :: nread

        allocate (BatchRead(0:NifTot, 1:MaxWalkersPart))

        write (stdout, *) 'Reading a maximum of ', MaxWalkersPart, ' particles to &
                   &each node from split POPSFILES'

        ! Initialise the relevant counters
        CurrWalkers = 0
        pops_norm = 0.0_dp

        gdata_size = gdata_read_handler%entry_size()
        allocate (gdata(gdata_size, MaxWalkersPart))
        allocate (gdata_tmp(gdata_size))
        ! If we are using pre-split popsfiles, then we need to do the
        ! reading on all of the nodes.
        if (bNodeRoot) then

            ! Get ready for reading in the next batch of walkers
            do while (.true.)

                ! Read the next entry
                ! The decoded form is placed in det_tmp
                ! n.b. reading entry after CurrWalkers --> +1
                tEOF = read_popsfile_det(iunit, PopNel, binary_pops, &
                                         det_list(:, CurrWalkers + 1), &
                                         det_tmp, PopNIfSgn, &
                                         .true., nread, gdata_tmp, &
                                         trimmed_parts=trimmed_parts)

                ! When we have got to the end of the file, we are done.
                if (tEOF) exit

                CurrWalkers = CurrWalkers + 1
                gdata(:, CurrWalkers) = gdata_tmp(:)

                ! Add the contribution from this determinant to the
                ! norm of the popsfile wave function.
                call add_pops_norm_contrib(det_list(:, CurrWalkers))

                ! And a test that this split popsfile is somewhat valid...
                proc = DetermineDetNode(PopNel, det_tmp, 0)
                if (proc /= iProcIndex) &
                    call stop_all(this_routine, "Determinant in the &
                                   &wrong Split POPSFILE")

            enddo

        endif

        ! store the global det data (if available)
        call gdata_read_handler%read_gdata(gdata, int(CurrWalkers))
        deallocate (gdata)
        deallocate (gdata_tmp)
        deallocate (BatchRead)

    end function read_pops_splitpops