SymGenExcitIt2 Subroutine

subroutine SymGenExcitIt2(NI, NEL, EXCITTYPES, NEXCITTYPES, CLASSES, SYMPRODIND, ILUT, ORBPAIRS, IEXCIT, ISPN, IFROM, ITO, I, J, K, L, ICC, LS, NK, IC, iMinElec1, iMaxElec1)

Arguments

Type IntentOptional Attributes Name
integer :: NI(NEL)
integer :: NEL
integer :: EXCITTYPES(5,NEXCITTYPES)
integer :: NEXCITTYPES
type(SymClass) :: CLASSES(*)
integer :: SYMPRODIND(2,3,1:*)
integer :: ILUT(0:*)
integer :: ORBPAIRS(2,*)
integer :: IEXCIT
integer :: ISPN
integer :: IFROM
integer :: ITO
integer :: I
integer :: J
integer :: K
integer :: L
integer :: ICC(4)
logical :: LS(2,2)
integer :: NK(NEL)
integer :: IC
integer :: iMinElec1
integer :: iMaxElec1

Contents

Source Code


Source Code

Subroutine SymGenExcitIt2(nI, nEl, ExcitTypes, nExcitTypes, &
                          Classes, SymProdInd, iLUT, OrbPairs, iExcit, iSpn, &
                          iFrom, iTo, I, J, K, L, iCC, LS, nK, iC, iMinElec1, iMaxElec1)
    use SystemData, only: TSTOREASEXCITATIONS
    use SystemData, only: Symmetry, SymmetrySize, SymmetrySizeB
    use SystemData, only: BasisFN, BasisFNSize, BasisFNSizeB
    use SymData, only: SymLabelCounts, SymStatePairs, SymClass
    use SymData, only: SymLabelList, SymPairProds
    use constants, only: stdout
    IMPLICIT NONE
    INTEGER NEXCITTYPES
    INTEGER NEL, NI(NEL), EXCITTYPES(5, NEXCITTYPES)
    INTEGER I, J, K, L
    INTEGER NK(NEL)
    TYPE(SymClass) CLASSES(*)
    INTEGER IEXCIT
    INTEGER IFROM, ITO, ISPN
    TYPE(Symmetry) SPP
    INTEGER ICC(4)
!.. 1,1= 1B, 1,2=1A; 2,1=2B, 2,2=2A.
    LOGICAL LS(2, 2)

    INTEGER ORBPAIRS(2, *)
    INTEGER ILUT(0:*)
    INTEGER SYMPRODIND(2, 3, 1:*)
    INTEGER IC
    LOGICAL tDebugPrint
    INTEGER iMinElec1, iMaxElec1

    INTEGER iRet
    tDebugPrint = .false.
    if (tDebugPrint) write(stdout, *) "Entering SymGenExcitIt2"

    DO WHILE (.TRUE.)
! Indicate that we need to keep on cycling.  If it is changed
!  by the later routines we stop the loop
        iRet = 0
!.. see if we need a new EXCIT
        if (tDebugPrint) WRITE(stdout, *) "I,iExcit,nExcitTypes", I, iExcit, nExcitTypes
        IF (I < 0) THEN
!.. move to the next excitation
            IEXCIT = IEXCIT + 1
            IF (IEXCIT > NEXCITTYPES) THEN
!.. We're done
                NK(1) = 0
                RETURN
            END IF
            IF (EXCITTYPES(1, IEXCIT) == 1) THEN
                Call SymGenExcitIt_SetupSingle( &
                    iSpn, iFrom, iTo, iExcit, ExcitTypes, Classes, SymProdInd, &
                    I, J, K, L, nI, nEl, iMinElec1, tDebugPrint)
            ELSE
                Call SymGenExcitIt_SetupDouble( &
                    iSpn, iFrom, iTo, iExcit, ExcitTypes, SymProdInd, I, K, L, tDebugPrint)
            END IF
        END IF
        IF (EXCITTYPES(1, IEXCIT) == 1) THEN
            Call SymGenExcitIt_GenSingle(iRet, iSpn, iFrom, iTo, iCC, I, J, K, L, tDebugPrint, iMaxElec1, iC, nI, nK, nEl)
        ELSE
            Call SymGenExcitIt_GenDouble( &
                iRet, SPP, I, K, L, iTo, iSpn, iFrom, iCC, &
                iLUT, LS, OrbPairs, SymProdInd, nI, nK, nEl, iC, tDebugPrint)
        END IF
        if (iRet == 1) cycle
        if (iRet == 2) return
    END DO
End Subroutine SymGenExcitIt2