GENNEXTSYM Subroutine

public subroutine GENNEXTSYM(NEL, nBasisMax, TSPN, LMS, TPARITY, IPARITY, TSETUP, TDONE, IMax, ISYM)

Arguments

Type IntentOptional Attributes Name
integer :: NEL
integer :: nBasisMax(5,*)
logical :: TSPN
integer :: LMS
logical :: TPARITY
type(BasisFN) :: IPARITY
logical :: TSETUP
logical :: TDONE
type(BasisFN) :: IMax(2)
type(BasisFN) :: ISYM

Contents

Source Code


Source Code

    SUBROUTINE GENNEXTSYM(NEL, NBASISMAX, TSPN, LMS, TPARITY, IPARITY, TSETUP, TDONE, IMAX, ISYM)
        IMPLICIT NONE
        INTEGER NEL, nBasisMax(5, *)
        INTEGER LMS
        TYPE(BasisFN) IPARITY, ISYM, IMax(2)
        LOGICAL TSPN, TPARITY, TSETUP, TMORE, TDONE, TMORE2
        INTEGER ILEV
        IF (TSETUP) THEN
            IMAX(1) = NullBasisFn
            IMAX(2) = NullBasisFn
            DO ILEV = 1, 3
                IF (TPARITY) THEN
                    IMAX(1)%k(iLev) = IPARITY%k(ILEV)
                    IMAX(2)%k(ILEV) = IPARITY%k(ILEV)
                ELSE
                    IMAX(1)%k(iLev) = NBASISMAX(ILEV, 1)
                    IMAX(2)%k(iLev) = NBASISMAX(ILEV, 2)
!                  IF(NBASISMAX(1,3).EQ.2) THEN
!   hubbard non-pbc mom space
!                     IMAX(ILEV,1)=IMAX(ILEV,1)*NEL
!                     IMAX(ILEV,2)=IMAX(ILEV,2)*NEL
!                  end if
                end if
            end do
            IF (TSPN) THEN
                IMAX(1)%Ms = LMS
                IMAX(2)%Ms = LMS
            ELSE
                IMAX(1)%Ms = NBASISMAX(4, 1) * NEL
                IMAX(2)%Ms = NBASISMAX(4, 2) * NEL
            end if
!   If we're specifying a sym (TPARITY) in IPARITY(5), and
!   we have a system with all 1D reducible orbs, then we put
!   that into IMAX
            IF (NBASISMAX(5, 2) /= 0 .OR. TAbelian) THEN
                IF (TPARITY) THEN
                    IMAX(1)%Sym%s = IPARITY%Sym%s
                    IMAX(2)%Sym%s = IMAX(1)%Sym%s
                ELSE
                    IMAX(1)%Sym%s = MinSymRep()
                    IMAX(2)%Sym%s = MaxSymRep()
                end if
            ELSE
!   we've got a sym system with polydimensional irreps, which leads to
!   dets with combinations of irreps, so we cannot put sym into blocks

!  JSS: if only 1D symmetries, then a determinant can only interact with
!  other determinants of the same symmetry.  This applies to Abelian
!  groups.  If there are multi-dimensional irreps, then this is no
!  longer the case, so we set the symmetries to be 0 (i.e. ignore
!  symmetry when generating determinants which interact).  This is not
!  equivalent to setting %s=0 if the Abelian case (which corresponds to
!  the totally symmetric irrep).
                IMAX(1)%Sym%s = 0
                IMAX(2)%Sym%s = 0
            end if
            TDONE = .FALSE.
            CALL DOSYMLIMDEGEN(IMAX, NBASISMAX)
            ISym = IMax(1)
        end if
        IF (TSETUP .AND. KALLOWED(ISYM, NBASISMAX)) RETURN
!   Go to the next sym.
        TMORE2 = .TRUE.
        TMORE = .TRUE.
        ILEV = 5
        DO WHILE (TMORE2)
            DO WHILE (ILEV > 0)
                IF (ILEV == 5) THEN
                    IF (IMAX(1)%Sym%s /= 0) THEN
!   symmetry specifiers are incremented by multiplying*2 (unless there are no syms counted)
                        ISYM%Sym%s = ISYM%Sym%s * 2
                    ELSE
                        Call IncrSym(ISym%Sym)
                    end if
                    IF (ISYM%Sym%s == IMAX(1)%Sym%s) THEN
                        ILEV = ILEV - 1
                        IF (ILEV == 0) THEN
                            TMORE2 = .FALSE.
!   If we've run out of syms, we give up
                            TMORE = .FALSE.
                        end if
                    else if (KALLOWED(ISYM, NBASISMAX)) THEN
                        TMORE2 = .FALSE.
                        ILEV = 0
                    end if
                ELSE
                    ISYM%k(ILEV) = ISYM%k(ILEV) + 1
                    IF (ISYM%k(ILEV) > IMAX(2)%k(ILEV)) THEN
                        ISYM%k(ILEV) = IMAX(1)%k(ILEV)
                        ILEV = ILEV - 1
                        IF (ILEV == 0) THEN
                            TMORE2 = .FALSE.
!   If we've run out of syms, we give up
                            TMORE = .FALSE.
                        end if
                    else if (ILEV < 4) THEN
!   We've just incremented one of the higher columns, now go down to the
!   lower ones.
                        ILEV = ILEV + 1
                        ISYM%k(ILEV) = IMAX(1)%k(ILEV) - 1

                    else if (KALLOWED(ISYM, NBASISMAX)) THEN
                        TMORE2 = .FALSE.
                        ILEV = 0
                    end if
                end if
            end do
        end do
        TDONE = .NOT. TMORE
    END SUBROUTINE GENNEXTSYM