calcFullStartR2L_stochastic Subroutine

public subroutine calcFullStartR2L_stochastic(ilut, csf_i, excitInfo, t, pgen, posSwitches, negSwitches, opt_weight)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
type(ExcitationInformation_t), intent(inout) :: excitInfo
integer(kind=n_int), intent(out) :: t(0:nifguga)
real(kind=dp), intent(out) :: pgen
real(kind=dp), intent(in) :: posSwitches(nSpatOrbs)
real(kind=dp), intent(in) :: negSwitches(nSpatOrbs)
type(WeightObj_t), intent(in), optional :: opt_weight

Contents


Source Code

    subroutine calcFullStartR2L_stochastic(ilut, csf_i, excitInfo, t, pgen, &
                                           posSwitches, negSwitches, opt_weight)
        integer(n_int), intent(in) :: ilut(0:nifguga)
        type(CSF_Info_t), intent(in) :: csf_i
        type(ExcitationInformation_t), intent(inout) :: excitInfo
        integer(n_int), intent(out) :: t(0:nifguga)
        real(dp), intent(out) :: pgen
        real(dp), intent(in) :: posSwitches(nSpatOrbs), negSwitches(nSpatOrbs)
        type(WeightObj_t), intent(in), optional :: opt_weight
        character(*), parameter :: this_routine = "calcFullStartR2L_stochastic"

        integer :: i, st, en, se, gen, j, k, l, holeInd, elecInd
        type(WeightObj_t) :: weights
        real(dp) :: branch_pgen, temp_pgen, &
                    p_orig, rdm_mat, orb_pgen
        HElement_t(dp) :: integral
        procedure(calc_pgen_general), pointer :: calc_pgen_yix_start

        ASSERT(isProperCSF_ilut(ilut))
        ASSERT(.not. isZero(ilut, excitInfo%fullStart))
        ASSERT(.not. isThree(ilut, excitInfo%fullStart))

        ! create the fullStart
        st = excitInfo%fullStart
        en = excitInfo%fullEnd
        se = excitInfo%firstEnd
        gen = excitInfo%lastGen

        ! create correct weights:
        if (present(opt_weight)) then
            weights = opt_weight
        else
            weights = init_fullStartWeight(csf_i, se, en, negSwitches(se), &
                                           posSwitches(se), csf_i%B_real(se))
        end if

        if (t_approx_exchange .or. (t_approx_exchange_noninits .and. (.not. is_init_guga))) then
            ! todo the switch
            call forced_mixed_start(ilut, csf_i, excitInfo, t, branch_pgen)
        else
            call mixedFullStartStochastic(ilut, csf_i, excitInfo, weights, posSwitches, &
                                          negSwitches, t, branch_pgen)
        end if

        ! set pgen to 0 in case of early exit
        pgen = 0.0_dp

        ! check validity
        check_abort_excit(branch_pgen, t)

        ! then for the overlap region i need a double update routine, which
        ! somehow garuantees a switch happens at some point, to avoid
        ! single excitations

        do i = st + 1, se - 1
            call doubleUpdateStochastic(ilut, csf_i, i, excitInfo, &
                                        weights, negSwitches, posSwitches, t, branch_pgen)

            ! check validity
            if (near_zero(extract_matrix_element(t, 2)) .or. near_zero(branch_pgen)) then
                t = 0_n_int
                return
            end if
        end do

        ! then deal with specific semi-stop
        ! and update weights here
        ! i also could use the fact that the single weights are already
        ! initialized within the fullstart weights or?
        ! and then use smth like
        weights = weights%ptr

        call calcRaisingSemiStopStochastic(ilut, csf_i, excitInfo, weights, negSwitches, &
                                           posSwitches, t, branch_pgen)

        ! check validity
        check_abort_excit(branch_pgen, t)

        excitInfo%currentGen = excitInfo%lastGen

        do i = se + 1, en - 1
            call singleStochasticUpdate(ilut, csf_i, i, excitInfo, weights, posSwitches, &
                                        negSwitches, t, temp_pgen)
            branch_pgen = branch_pgen * temp_pgen

            if (t_trunc_guga_pgen .or. &
                (t_trunc_guga_pgen_noninits .and. .not. is_init_guga)) then
                if (branch_pgen < trunc_guga_pgen) then
                    t = 0_n_int
                    return
                end if
            end if

            ! check validity
            check_abort_excit(branch_pgen, t)

        end do

        call singleStochasticEnd(csf_i, excitInfo, t)

        ! if we do RDMs also store the x0 and x1 coupling coeffs
        ! and I need to do it before the routines below since excitInfo
        ! gets changed there
        if (tFillingStochRDMOnFly) then
            ! i need to unbias against the total pgen later on in the
            ! RDM sampling otherwise the rdm-bias factor is not correct!
            ! encode the necessary information in the rdm-matele!
            i = excitInfo%i
            j = excitInfo%j
            k = excitInfo%k
            l = excitInfo%l
            elecInd = se
            holeInd = en
            rdm_mat = extract_matrix_element(t, 2)
            call calc_orbital_pgen_contrib_start(&
                    csf_i, [2 * st, 2 * elecInd], holeInd, orb_pgen)
            p_orig = orb_pgen * branch_pgen / real(ElecPairs, dp)
            if (csf_i%stepvector(elecInd) == 3) p_orig = p_orig * 2.0_dp
        end if

        call encode_matrix_element(t, extract_matrix_element(t, 1) + &
                                   extract_matrix_element(t, 2), 1)
        call encode_matrix_element(t, 0.0_dp, 2)

        ! update: since i can formulate everything in terms of the already
        ! calculated matrix element i can abort here if it is zero
        if (near_zero(extract_matrix_element(t, 1))) then
            t = 0_n_int
            return
        end if

        global_excitInfo = excitInfo

        if (t_approx_exchange .or. (t_approx_exchange_noninits .and. (.not. is_init_guga))) then
            call calc_mixed_start_contr_approx(t, csf_i, excitInfo, integral)
            pgen = branch_pgen

        else
            call calc_mixed_start_contr_integral(ilut, csf_i, t, excitInfo, &
                integral)
            call calc_mixed_start_contr_pgen(ilut, csf_i, t, excitInfo, &
                branch_pgen, pgen)

!             call calc_mixed_start_contr_sym(ilut, csf_i, t, excitInfo, branch_pgen, pgen, &
!                                             integral)
        end if

        if (tFillingStochRDMOnFly) then
            if (.not. near_zero(p_orig)) then
                call encode_stochastic_rdm_info(GugaBits, t, rdm_ind= &
                                    contract_2_rdm_ind(i, j, k, l, excit_lvl=2, &
                                       excit_typ=excitInfo%typ), x0=0.0_dp, &
                                                x1=rdm_mat * pgen / p_orig)
            end if
        end if

        ! and finally update the matrix element with all contributions
        call update_matrix_element(t, (get_umat_el(st, en, se, st) + &
                                       get_umat_el(en, st, st, se)) / 2.0_dp + integral, 1)

    end subroutine calcFullStartR2L_stochastic