GenSymPairs Subroutine

public subroutine GenSymPairs(nSymLabels, iPass)

Arguments

Type IntentOptional Attributes Name
integer :: nSymLabels
integer :: iPass

Contents

Source Code


Source Code

    SUBROUTINE GenSymPairs(nSymLabels, iPass)
        IMPLICIT NONE
        INTEGER iPass
        INTEGER I, J
        TYPE(Symmetry) PROD
        INTEGER nSymLabels, iProd
        INTEGER iSS, iOS
        DO I = 1, nSymLabels
            DO J = I, nSymLabels
!               write(stdout,*) I,J
                PROD = SYMPROD(SymLabels(I), SymLabels(J))
                CALL FindSymProd(Prod, SymPairProds, nSymPairProds, iProd)
                IF (iProd == nSymPairProds + 1) THEN
                    nSymPairProds = nSymPairProds + 1
                    SymPairProds(iProd)%Sym = Prod
                    SymPairProds(iProd)%nIndex = 0
                    SymPairProds(iProd)%nPairs = 0
                    SymPairProds(iProd)%nPairsStateSS = 0
                    SymPairProds(iProd)%nPairsStateOS = 0
                end if

!.. iOS counts the number of pairs of spin-orbitals with the opposite spin, which give rise to the
!.. given symmetry product. iSS is for same spin orbital pairs.
                iOS = SymLabelCounts(2, I) * SymLabelCounts(2, J)
                if (i /= j) iOS = iOS * 2
!.. Same spin has n(n-1)/2 if same state
                if (i /= J) then
                    iSS = SymLabelCounts(2, I) * SymLabelCounts(2, J)
                else
                    iSS = (SymLabelCounts(2, I) * (SymLabelCounts(2, J) - 1)) / 2
                end if
                if (iOS > 0 .or. iSS > 0) THEN
                    IF (iPass == 1) THEN
!   put the pair into the list of pairs.
                        SymStatePairs(1, SymPairProds(iProd)%nIndex + SymPairProds(iProd)%nPairs) = I
                        SymStatePairs(2, SymPairProds(iProd)%nIndex + SymPairProds(iProd)%nPairs) = J
!                     write(stdout,"(3I5,Z10,3I5)")
!     &                  iProd,I,J,PROD,SymPairProds(iProd)%nIndex
!     &                            +SymPairProds(iProd)%nPairs,
!     &                           SymPairProds(iProd)%nIndex,
!     &                            SymPairProds(iProd)%nPairs

                    end if
!   increment the counter in the pairlist
                    SymPairProds(iProd)%nPairs = SymPairProds(iProd)%nPairs + 1
                    SymPairProds(iProd)%nPairsStateOS = SymPairProds(iProd)%nPairsStateOS + iOS
                    SymPairProds(iProd)%nPairsStateSS = SymPairProds(iProd)%nPairsStateSS + iSS
!                write(stdout,*) "NN",SymLabelCounts(2,I),SymLabelCounts(2,J),
!     &           SymPairProds(iProd)%nPairsStateSS,
!     &           SymPairProds(iProd)%nPairsStateOS
                end if
            end do
        end do
    END SUBROUTINE GenSymPairs