calcDoubleR2L2R_stochastic Subroutine

public subroutine calcDoubleR2L2R_stochastic(ilut, csf_i, excitInfo, t, branch_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(in) :: excitInfo
integer(kind=n_int), intent(out) :: t(0:nifguga)
real(kind=dp), intent(out) :: branch_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 calcDoubleR2L2R_stochastic(ilut, csf_i, excitInfo, t, branch_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(in) :: excitInfo
        integer(n_int), intent(out) :: t(0:nifguga)
        real(dp), intent(out) :: branch_pgen
        real(dp), intent(in) :: posSwitches(nSpatOrbs), negSwitches(nSpatOrbs)
        type(WeightObj_t), intent(in), optional :: opt_weight
        character(*), parameter :: this_routine = "calcDoubleR2L2R_stochastic"

        integer :: iOrb, switch
        type(WeightObj_t) :: weights
        real(dp) :: temp_pgen
        HElement_t(dp) :: integral

        associate (i => excitInfo%i, j => excitInfo%j, k => excitInfo%k, &
                   l => excitInfo%l, start1 => excitInfo%fullstart, &
                   start2 => excitInfo%secondStart, ende1 => excitInfo%firstEnd, &
                   ende2 => excitInfo%fullEnd, typ => excitInfo%typ)

            ASSERT(.not. isThree(ilut, start1))
            ASSERT(.not. isZero(ilut, start2))
            ASSERT(.not. isThree(ilut, ende1))
            ASSERT(.not. isZero(ilut, ende2))

            if (present(opt_weight)) then
                weights = opt_weight
            else
                ! : create correct weights:
                weights = init_fullDoubleWeight(csf_i, start2, ende1, ende2, negSwitches(start2), &
                                                negSwitches(ende1), posSwitches(start2), posSwitches(ende1), &
                                                csf_i%B_real(start2), csf_i%B_real(ende1))
            end if

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

            ! check validity
            check_abort_excit(branch_pgen, t)

            do iOrb = start1 + 1, start2 - 1
                call singleStochasticUpdate(ilut, csf_i, iOrb, excitInfo, weights, posSwitches, &
                                            negSwitches, t, temp_pgen)
                ! check validity
                branch_pgen = branch_pgen * temp_pgen

                check_abort_excit(branch_pgen, t)

            end do

            ! change weights... maybe need both single and double type weights
            ! then do lowering semi start
            weights = weights%ptr

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

            ! check validity
            check_abort_excit(branch_pgen, t)

            do iOrb = start2 + 1, ende1 - 1
                call doubleUpdateStochastic(ilut, csf_i, iOrb, excitInfo, weights, negSwitches, &
                                            posSwitches, t, branch_pgen)
                ! check validity

                check_abort_excit(branch_pgen, t)

            end do

            ! then update weights and and to lowering semi-stop
            weights = weights%ptr

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

            ! check validity
            check_abort_excit(branch_pgen, t)

            do iOrb = ende1 + 1, ende2 - 1
                call singleStochasticUpdate(ilut, csf_i, iOrb, excitInfo, weights, posSwitches, &
                                            negSwitches, t, temp_pgen)

                branch_pgen = branch_pgen * temp_pgen
                ! check validity
                check_abort_excit(branch_pgen, t)

            end do

            ! and finally to end step
            call singleStochasticEnd(csf_i, excitInfo, t)

            ! if we do RDMs also store the x0 and x1 coupling coeffs
            if (tFillingStochRDMOnFly) then
                call encode_stochastic_rdm_info(GugaBits, t, rdm_ind= &
                        contract_2_rdm_ind(i, j, k, l, excit_lvl=2, excit_typ=typ), &
                                                x0=extract_matrix_element(t, 1), &
                                                x1=extract_matrix_element(t, 2))
            end if

            ! todo: think about the additional integral contributions and the
            ! relative sign of different order influences...
            ! and not sure yet if in this case i can use this function generally
            ! for L -> LL -> LL -> L
            ! and R -> RL -> RL -> R
            ! since the integral/order influences are different maybe... todo!

            ! update: on the matrix elements..
            ! i have to consider the non-overlap excitation, which can lead to
            ! the same excitation if there is no change in the stepvector
            ! in the overlap region
            ! the problem with the L2R2L and R2L2R funcitons is that the
            ! generator type changes for the non-overlap excitation so the
            ! matrix elements have to be changed more than in the R2L and L2R case

            switch = findFirstSwitch(ilut, t, start2 + 1, ende1)
            if (switch > 0) then
                integral = extract_matrix_element(t, 2) * (get_umat_el(start1, ende1, ende2, start2) + &
                                                           get_umat_el(ende1, start1, start2, ende2)) / 2.0_dp

                if (near_zero(integral)) then
                    branch_pgen = 0.0_dp
                    t = 0_n_int
                else
                    call encode_matrix_element(t, 0.0_dp, 2)
                    call encode_matrix_element(t, integral, 1)
                end if
            else
                integral = (-extract_matrix_element(t, 1) * (get_umat_el(start1, ende1, start2, ende2) + &
                                                     get_umat_el(ende1, start1, ende2, start2)) * 2.0_dp + (extract_matrix_element(t, 1) + &
                                                              extract_matrix_element(t, 2)) * (get_umat_el(start1, ende1, ende2, start2) + &
                                                                                        get_umat_el(ende1, start1, start2, ende2))) / 2.0_dp

                if (near_zero(integral)) then
                    branch_pgen = 0.0_dp
                    t = 0_n_int
                else
                    call encode_matrix_element(t, 0.0_dp, 2)
                    call encode_matrix_element(t, integral, 1)
                end if
            end if

        end associate

    end subroutine calcDoubleR2L2R_stochastic