READFCIINTBIN Subroutine

public subroutine READFCIINTBIN(UMAT, ECORE)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(out) :: UMAT(*)
real(kind=dp), intent(out) :: ECORE

Contents

Source Code


Source Code

    SUBROUTINE READFCIINTBIN(UMAT, ECORE)
        real(dp), intent(out) :: ECORE
        HElement_t(dp), intent(out) :: UMAT(*)
        HElement_t(dp) Z
        integer(int64) MASK, IND
        INTEGER I, J, K, L, iunit
        LOGICAL LWRITE
        LWRITE = .FALSE.
        iunit = get_free_unit()
        open(iunit, FILE=FCIDUMP_name, STATUS='OLD', FORM='UNFORMATTED')

        MASK = (2**16) - 1
        !IND contains all the indices in an integer(int64) - use mask of 16bit to extract them
101     read(iunit, END=199) Z, IND
        L = int(iand(IND, MASK))
        IND = Ishft(IND, -16)
        K = int(iand(IND, MASK))
        IND = Ishft(IND, -16)
        J = int(iand(IND, MASK))
        IND = Ishft(IND, -16)
        I = int(iand(IND, MASK))

!.. Each orbital in the file corresponds to alpha and beta spinorbitalsa
        IF (I == 0) THEN
!.. Core energy
            ECORE = real(Z, dp)
        else if (J == 0) THEN
!C.. HF Eigenvalues
!            ARR(I*2-1,2)=real(Z,dp)
!            ARR(I*2,2)=real(Z,dp)
!            ARR(BRR(I*2-1),1)=real(Z,dp)
!            ARR(BRR(I*2),1)=real(Z,dp)
!            LWRITE=.TRUE.
        else if (K == 0) THEN
!.. 1-e integrals
!.. These are stored as spinorbitals (with elements between different spins being 0
            if (.not. t_non_hermitian_1_body) then
                TMAT2D(2 * I - 1, 2 * J - 1) = Z
                TMAT2D(2 * I, 2 * J) = Z
            end if

            TMAT2D(2 * J - 1, 2 * I - 1) = Z
            TMAT2D(2 * J, 2 * I) = Z
        ELSE
!.. 2-e integrals
!.. UMAT is stored as just spatial orbitals (not spinorbitals)
!..  we're reading in (IJ|KL), but we store <..|..> which is <IK|JL>
            UMAT(UMatInd(I, K, J, L)) = Z
        end if
!         write(14,'(1X,F20.12,4I3)') Z,I,J,K,L
        IF (I /= 0) GOTO 101
199     CONTINUE
        close(iunit)
! If we've changed the eigenvalues, we write out the basis again
!         IF(LWRITE) THEN
!            write(stdout,*) "1-electron energies have been read in."
!            CALL writebasis(stdout,G1,NBASIS,ARR,BRR)
!         end if
        RETURN
    END SUBROUTINE READFCIINTBIN