read_popsfile_wrapper Subroutine

public subroutine read_popsfile_wrapper(perturbs)

Arguments

Type IntentOptional Attributes Name
type(perturbation), intent(in), optional, allocatable :: perturbs(:)

Contents

Source Code


Source Code

    subroutine read_popsfile_wrapper(perturbs)

        type(perturbation), intent(in), allocatable, optional :: perturbs(:)

        integer :: iunithead, PopsVersion
        ! Variables from popsfile header...
        integer :: iPopLenof_sign, PopNel, iPopIter, PopNIfD, WalkerListSize
        integer :: PopNIfSgn, PopNIfFlag, PopNIfTot, PopBlockingIter, read_nnodes
        integer :: Popinum_runs
        integer :: PopRandomHash(2056)
        logical :: formpops, binpops
        logical :: tPopHPHF, tPop64Bit, tPopLz
        integer(int64) :: iPopAllTotWalkers
        integer(int64) :: read_walkers_on_nodes(0:nProcessors - 1)
        real(dp) :: PopDiagSft(inum_runs), read_tau
        real(dp) :: read_psingles, read_pparallel, read_ptriples
        real(dp), dimension(lenof_sign) :: PopSumNoatHF
        HElement_t(dp) :: PopAllSumENum(inum_runs)
        integer :: perturb_ncreate, perturb_nannihilate, PopBalanceBlocks

        character(len=*), parameter :: this_routine = "read_popsfile_wrapper"

        read_psingles = 0.0_dp
        read_ptriples = 0.0_dp
        read_pparallel = 0.0_dp
        read_tau = 0.0_dp
        PopDiagSft = 0.0_dp

        ! Read the header.
        call open_pops_head(iunithead, formpops, binpops)

        PopsVersion = FindPopsfileVersion(iunithead)

        if (PopsVersion == 4) then
            call ReadPopsHeadv4(iunithead, tPop64Bit, tPopHPHF, tPopLz, iPopLenof_Sign, PopNel, &
                                iPopAllTotWalkers, PopDiagSft, PopSumNoatHF, PopAllSumENum, iPopIter, &
                                PopNIfD, PopNIfSgn, Popinum_runs, PopNIfFlag, PopNIfTot, &
                                read_tau, PopBlockingIter, PopRandomHash, read_psingles, &
                                read_pparallel, read_ptriples, read_nnodes, read_walkers_on_nodes, &
                                PopBalanceBlocks)
        else
            call stop_all(this_routine, "Only version 4 popsfile are supported with kp-fciqmc.")
        endif

        ! Check the number of electrons created and annihilated by the
        ! perturbation operators.
        if (present(perturbs)) then
            perturb_ncreate = perturbs(1)%ncreate
            perturb_nannihilate = perturbs(1)%nannihilate
        else
            perturb_ncreate = 0
            perturb_nannihilate = 0
        end if

        call CheckPopsParams(tPop64Bit, tPopHPHF, tPopLz, iPopLenof_Sign, PopNel, &
                             iPopAllTotWalkers, PopDiagSft, PopSumNoatHF, PopAllSumENum, iPopIter, &
                             PopNIfD, PopNIfSgn, PopNIfTot, &
                             WalkerListSize, read_tau, PopBlockingIter, read_psingles, read_pparallel, &
                             read_ptriples, perturb_ncreate, perturb_nannihilate)

        if (iProcIndex == root) close (iunithead)

        call InitFCIMC_pops(iPopAllTotWalkers, PopNIfSgn, PopNel, read_nnodes, &
                            read_walkers_on_nodes, perturbs, PopBalanceBlocks, &
                            PopDiagSft)

        ! If requested output the norm of the *unperturbed* walkers in the POPSFILE.
        if (tWritePopsNorm) call write_pops_norm()

    end subroutine read_popsfile_wrapper