get_offdiag_helement_k_sp_hub Function

public function get_offdiag_helement_k_sp_hub(nI, ex, tpar) result(hel)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nI(nel)
integer, intent(in) :: ex(2,2)
logical, intent(in) :: tpar

Return Value real(kind=dp)


Contents


Source Code

    function get_offdiag_helement_k_sp_hub(nI, ex, tpar) result(hel)
        ! this routine is called for the double excitations in the
        ! k-space hubbard. in case of transcorrelation, this can also be
        ! spin-parallel excitations now. the triple excitation have a
        ! seperate routine!
        ! The result does not depend on nI!
        integer, intent(in) :: nI(nel), ex(2, 2)
        logical, intent(in) :: tpar
        HElement_t(dp) :: hel
        integer :: src(2), tgt(2), ij(2), ab(2), spin
        type(symmetry) :: k_sym_a, k_sym_b, k_sym_c, k_sym_d
        real(dp) :: sgn

        src = get_src(ex)
        tgt = get_tgt(ex)

        if (.not. t_trans_corr_2body) then
            if (same_spin(src(1), src(2)) .or. same_spin(tgt(1), tgt(2))) then
                hel = h_cast(0.0_dp)
                return
            end if
        else
            ! if src has same spin but tgt has opposite spin -> 0 mat ele
            if (same_spin(src(1), src(2)) .and. (.not. same_spin(tgt(1), tgt(2)) &
                                                 .or. .not. same_spin(src(1), tgt(1)))) then

                hel = h_cast(0.0_dp)
                return
            end if
        end if

        ij = get_spatial(src)
        ab = get_spatial(tgt)
        ! that about the spin?? must spin(a) be equal spin(i) and same for
        ! b and j? does this have an effect on the sign of the matrix element?

        ! in the case of 2-body transcorrelation, parallel spin double exciattions
        ! are possible todo: check if we get the coulomb and exchange contributions
        ! correct..

        ! the U part is still just the the spin-opposite part
        ! damn... i need a sign convention here too..
        if (same_spin(src(1), tgt(1)) .and. same_spin(src(2), tgt(2))) then
            hel = get_umat_kspace(ij(1), ij(2), ab(1), ab(2))
        else if (same_spin(src(1), tgt(2)) .and. same_spin(src(2), tgt(1))) then
            hel = -get_umat_kspace(ij(1), ij(2), ab(1), ab(2))
        end if

        ! if hel == 0, due to momentum conservation violation we can already
        ! exit here, since this means this excitation is just no possible!
        ! is hel only 0 due to momentum conservation?
        if (abs(hel) < EPS) return

        if (t_trans_corr) then
            ! do something
            ! here the one-body term with out (-t) is necessary

            ! optimized version:
            hel = hel * exp(trans_corr_param / 2.0_dp * &
                            (epsilon_kvec(G1(src(1))%Sym) + epsilon_kvec(G1(src(2))%Sym) &
                             - epsilon_kvec(G1(tgt(1))%Sym) - epsilon_kvec(G1(tgt(2))%Sym)))
        end if

        if (t_trans_corr_2body) then
            ! i need the k-vector of the transferred momentum..
            ! i am not sure if the orbitals involved in ex() are every
            ! re-shuffled.. if yes, it is not so easy in the spin-parallel
            ! case to reobtain the transferred momentum. although it must be
            ! possible. for now just assume (ex(2,2)) is the final orbital b
            ! with momentum k_i + k_j - k_a and we need the
            ! k_j - k_a momentum

            if (same_spin(src(1), src(2))) then
                spin = get_spin_pn(src(1))
                ! we need the spin of the excitation here if it is parallel

                ! in the same-spin case, this is the only contribution to the
                ! matrix element
                ! and maybe i have to take the sign additionally into
                ! account here?? or is this taken care of with tpar??

                ! thanks to Manu i have figured it out. we have to take
                ! the momentum between the to equally possible excitations:
                ! c^+_b c^+_a c_q c_p with W(q-a)
                ! and
                !-c^+_b c^+_a c_p c_q with W(p-a)
                ! with one of the orbital spins.
                ! i think it doesnt matter, which one.
                ! although for the sign it maybe does.. check thate
                ! TODO: i am not sure about the sign here...
                ! with a + i get nice symmetric results.. but i am really
                ! not sure damn.. ask ALI!
                ! i have to define an order of the input!
                ! maybe only look at i < j and a < b, as in the rest of the
                ! code! and then take the symmetrized matrix element

                src = [minval(src), maxval(src)]
                tgt = [minval(tgt), maxval(tgt)]

                k_sym_a = SymTable(G1(src(1))%sym%s, SymConjTab(G1(tgt(1))%sym%s))
                k_sym_b = SymTable(G1(src(1))%sym%s, SymConjTab(G1(tgt(2))%sym%s))

                ! yes this is it below! i just have to be sure that src and
                ! tgt are ordered.. we need a convention for these matrix
                ! elements!
                spin = get_spin_pn(src(1))

                hel = (same_spin_transcorr_factor(nI, k_sym_a, spin) &
                       - same_spin_transcorr_factor(nI, k_sym_b, spin))! &

            else
                ! else we need the opposite spin contribution

                ! the two-body contribution needs two k-vector inputs.
                ! figure out what momentum is necessary there!
                ! i need the transferred momentum
                ! and the momentum of other involved electron
                ! which by definition of k, is always ex(1,2) todo:
                ! check if this works as intented
                ! TODO no it is not!! I have to get the signed contribution
                ! here correct.. order in EX is not ensured!
                ! see above for same-spin excitations!
                ! what is k-vec now??
                ! this seems to have the correct symmetry..
                ! todo.. still the check if i need 1/2 factor or smth..
                ! and not sure about the sign between those two..
                ! here i am still not sure why i need two factors..
                ! i think i could get away with a convention, which momentum
                ! to take depending on the spin.. or i just symmetrize it..
                ! which hopefully is ok..
                ! because if i put it like that with k and -k it apparently
                ! cancels..
                ! maybe i also need a convention of an ordered input of ex..

                sgn = 1.0_dp
                ! also adapt this two body factor.. i hope this is correct now
                if (same_spin(src(1), tgt(1))) then
                    ! i need the right hole-momenta
                    k_sym_c = G1(tgt(1))%sym
                    k_sym_d = G1(tgt(2))%sym
                    sgn = 1.0_dp
                else
                    k_sym_c = G1(tgt(2))%sym
                    k_sym_d = G1(tgt(1))%sym
                    sgn = -1.0_dp
                end if

                hel = hel + sgn * (two_body_transcorr_factor(G1(src(1))%sym, k_sym_c) &
                                   + two_body_transcorr_factor(G1(src(2))%sym, k_sym_d))

                ! and now the 3-body contribution:
                ! which also needs the third involved mometum, which then
                ! again is ex(1,1)
                ! todo.. figure out spins!
                ! also check that! which electron momentum one has to take!
                ! maybe this cancels in the end.. who knows..

                ! what should i take as the spin here?? electron 1 or 2?
                ! i have to account for the sum of both possible spin
                ! influences!! damn.. todo!
                ! and this then determines which momentum i have to take.. or?

                hel = hel + sgn * (three_body_transcorr_fac(nI, G1(src(1))%sym, &
                                                            G1(src(2))%sym, k_sym_c, get_spin_pn(src(1))) &
                                   + three_body_transcorr_fac(nI, G1(src(2))%sym, &
                                                              G1(src(1))%sym, k_sym_d, get_spin_pn(src(2))))

            end if
        end if

        if (tpar) hel = -hel

    end function get_offdiag_helement_k_sp_hub