IsAOrbSymAllowed Function

public function IsAOrbSymAllowed(iSpn, OrbA, SpinOrbA, SymProduct, SumMl, SymA, SymB, MlA, MlB, ClassCountUnocc2)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: iSpn
integer, intent(in) :: OrbA
integer, intent(in) :: SpinOrbA
integer, intent(in) :: SymProduct
integer, intent(in) :: SumMl
integer, intent(out) :: SymA
integer, intent(out) :: SymB
integer, intent(out) :: MlA
integer, intent(out) :: MlB
integer, intent(in) :: ClassCountUnocc2(ScratchSize)

Return Value logical


Contents

Source Code


Source Code

    LOGICAL FUNCTION IsAOrbSymAllowed(iSpn, OrbA, SpinOrbA, SymProduct, SumMl, SymA, SymB, MlA, MlB, ClassCountUnocc2)
        INTEGER, INTENT(IN) :: iSpn, OrbA, SpinOrbA, SymProduct, SumMl, ClassCountUnocc2(ScratchSize)
        INTEGER, INTENT(OUT) :: SymA, SymB, MlA, MlB

        IsAOrbSymAllowed = .false.
        IF (tNoSymGenRandExcits) THEN
            SymA = 0
            SymB = 0
            MlA = 0
            MlB = 0
        else if (tKPntSym) THEN
            SymA = SpinOrbSymLabel(OrbA)
            SymB = RandExcitSymLabelProd(SymInvLabel(SymA), SymProduct)
            MlB = 0
            MlA = 0
        ELSE
            SymA = INT(G1(OrbA)%Sym%S, 4)
            SymB = IEOR(SymA, SymProduct)
            MlB = 0
            MlA = 0
            IF (tFixLz) THEN
                MlA = G1(OrbA)%Ml
                MlB = SumMl - MlA
            end if
        end if

        IF (abs(MlB) <= iMaxLz) THEN
!Make sure that the B orbital that we would need to pick to conserve momentum is actually in the available range of Ml values.
            IF (iSpn == 2) THEN
!We want an alpha/beta unocc pair.
                IF (SpinOrbA == 1) THEN
!We have picked an alpha orbital - check to see if there are allowed beta unoccupied orbitals from the SymB Class.
                    IF (ClassCountUnocc2(ClassCountInd(2, SymB, MlB)) /= 0) THEN
!Success! We have found an allowed A orbital!
                        IsAOrbSymAllowed = .true.
                    end if
                ELSE
!We have picked a beta orbital - check to see if there are allowed alpha unoccupied orbitals from the SymB Class.
                    IF (ClassCountUnocc2(ClassCountInd(1, SymB, MlB)) /= 0) THEN
!Success! We have found an allowed A orbital!
                        IsAOrbSymAllowed = .true.
                    end if
                end if
            else if (iSpn == 1) THEN
!We want a beta/beta pair.
                IF ((SymB /= SymA) .or. (MlA /= MlB)) THEN
!Check to see if there are any unoccupied beta orbitals in the SymB Class.
                    IF (ClassCountUnocc2(ClassCountInd(2, SymB, MlB)) /= 0) THEN
!Success! We have found an allowed A orbital!
                        IsAOrbSymAllowed = .true.
                    end if
                ELSE
!We want an orbital from the same class. Check that this isn't the only unoccupied beta orbital in the class.
                    IF (ClassCountUnocc2(ClassCountInd(2, SymB, MlB)) /= 1) THEN
!Success! We have found an allowed A orbital!
                        IsAOrbSymAllowed = .true.
                    end if
                end if
            ELSE
!We want an alpha/alpha pair.
                IF ((SymA /= SymB) .or. (MlA /= MlB)) THEN
!Check to see if there are any unoccupied alpha orbitals in the SymB Class.
                    IF (ClassCountUnocc2(ClassCountInd(1, SymB, MlB)) /= 0) THEN
!Success! We have found an allowed A orbital!
                        IsAOrbSymAllowed = .true.
                    end if
                ELSE
!We want an orbital from the same class. Check that this isn't the only unoccupied alpha orbital in the class.
                    IF (ClassCountUnocc2(ClassCountInd(1, SymB, MlB)) /= 1) THEN
!Success! We have found an allowed A orbital!
                        IsAOrbSymAllowed = .true.
                    end if
                end if
            end if
        end if

    END FUNCTION IsAOrbSymAllowed