UMatCache Module



Contents


Variables

Type Visibility Attributes Name Initial
real(kind=dp), public, Pointer :: UMatCacheData(:,:,:) => null()
integer, public, Pointer :: UMatLabels(:,:) => null()
integer, public :: nSlots
integer, public :: nPairs
integer, public :: nTypes
integer, public :: nStates
integer, private :: nBI_umat
logical, public :: tSmallUMat
integer, public :: iDumpCacheFlag
integer, public :: nStatesDump
logical, public :: tReadInCache
real(kind=dp), public, Pointer :: UMat2D(:,:) => null()
real(kind=dp), private, Pointer :: UMat3d(:,:,:) => null()
real(kind=dp), private, Pointer :: UMat3dExch(:,:,:) => null()
logical, public :: tUMat2D
logical, public :: tDeferred_Umat2d
integer, private, DIMENSION(:), POINTER :: INVBRR => null()
integer, private, DIMENSION(:), POINTER :: INVBRR2 => null()
integer, private :: NOCC
logical, public :: FREEZETRANSFER
integer, public :: nSlotsInit
integer, public :: nMemInit
integer, public :: UMatCacheFlag
logical, public :: gen2CPMDInts
integer, public :: nHits
integer, public :: nMisses
integer, private :: iCacheOvCount
logical, public :: tTransGTID
logical, public :: tTransFindx
integer, public, Pointer :: TransTable(:) => null()
integer, private, Pointer :: InvTransTable(:) => null()
integer, public :: nAuxBasis
integer, public :: nBasisPairs
logical, public :: tDFInts
real(kind=dp), public, Pointer :: DFCoeffs(:,:) => null()
real(kind=dp), public, Pointer :: DFInts(:,:) => null()
real(kind=dp), public, Pointer :: DFFitInts(:,:) => null()
real(kind=dp), public, Pointer :: DFInvFitInts(:,:) => null()
integer, public :: iDFMethod
integer(kind=TagIntType), private :: tagUMatCacheData = 0
integer(kind=TagIntType), private :: tagUMatLabels = 0
integer(kind=TagIntType), private :: tagOUMatCacheData = 0
integer(kind=TagIntType), private :: tagOUMatLabels = 0
integer(kind=TagIntType), public :: tagUMat2D = 0
integer(kind=TagIntType), private :: tagTransTable = 0
integer(kind=TagIntType), private :: tagInvTransTable = 0
integer(kind=TagIntType), public :: tagDFCoeffs = 0
integer(kind=TagIntType), public :: tagDFInts = 0
integer(kind=TagIntType), public :: tagDFFitInts = 0
integer(kind=TagIntType), public :: tagDFInvFitInts = 0
integer(kind=TagIntType), private :: tagInvBRR = 0
integer(kind=TagIntType), private :: tagInvBRR2 = 0

Functions

public elemental function UMat2Ind(i, j, k, l) result(ind)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
integer, intent(in) :: k
integer, intent(in) :: l

Return Value integer(kind=int64)

public elemental function UMatInd(i, j, k, l) result(ind)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
integer, intent(in) :: k
integer, intent(in) :: l

Return Value integer(kind=int64)

private elemental function UMatInd_base(I, J, K, L, nBI) result(UMatInd)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: I
integer, intent(in) :: J
integer, intent(in) :: K
integer, intent(in) :: L
integer, intent(in) :: nBI

Return Value integer(kind=int64)

public elemental function UMatConj(I, J, K, L, val)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: I
integer, intent(in) :: J
integer, intent(in) :: K
integer, intent(in) :: L
real(kind=dp), intent(in) :: val

Return Value real(kind=dp)

public function HasKPoints()

Arguments

None

Return Value logical

public elemental function GTID(gInd) result(id)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: gInd

Return Value integer

public elemental function spatial(spin_orb) result(spat_orb)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: spin_orb

Return Value integer

public function GETCACHEDUMATEL(IDI, IDJ, IDK, IDL, UMATEL, ICACHE, ICACHEI, A, B, ITYPE)

Arguments

Type IntentOptional Attributes Name
integer :: IDI
integer :: IDJ
integer :: IDK
integer :: IDL
real(kind=dp) :: UMATEL
integer :: ICACHE
integer :: ICACHEI
integer :: A
integer :: B
integer :: ITYPE

Return Value logical

public elemental function numBasisIndices(nBasis) result(nBI)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nBasis

Return Value integer

public function nullUMat(i, j, k, l) result(hel)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
integer, intent(in) :: k
integer, intent(in) :: l

Return Value real(kind=dp)


Subroutines

public subroutine CreateInvBRR2(BRR2, NBASIS)

Arguments

Type IntentOptional Attributes Name
integer :: BRR2(NBASIS)
integer :: NBASIS

public subroutine CreateInvBRR(BRR, NBASIS)

Arguments

Type IntentOptional Attributes Name
integer :: BRR(NBASIS)
integer :: NBASIS

public subroutine setup_UMatInd()

Arguments

None

public subroutine GetUMatSize(nBasis, iSize)

Arguments

Type IntentOptional Attributes Name
integer :: nBasis
integer(kind=int64), intent(out) :: iSize

public subroutine SETUPUMATCACHE(NSTATE, TSMALL)

Arguments

Type IntentOptional Attributes Name
integer :: NSTATE
logical :: TSMALL

public subroutine SETUPUMAT2D(G1, HarInt)

Arguments

Type IntentOptional Attributes Name
type(BasisFN) :: G1(*)
complex(kind=dp) :: HarInt(nStates,nStates)

public subroutine SETUPUMAT2D_DF()

Arguments

None

public subroutine SETUMATTRANS(TRANS)

Arguments

Type IntentOptional Attributes Name
integer :: TRANS(NSTATES)

public subroutine SetupUMatTransTable(OldNew, nOld, nNew)

Arguments

Type IntentOptional Attributes Name
integer :: OldNew(*)
integer :: nOld
integer :: nNew

public subroutine DESTROYUMATCACHE()

Arguments

None

public subroutine WriteUMatCacheStats()

Arguments

None

public subroutine SETUMATCACHEFLAG(NEWFLAG)

Arguments

Type IntentOptional Attributes Name
integer :: NEWFLAG

public subroutine FillUpCache()

Arguments

None

private subroutine BINARYSEARCH(VAL, TAB, A, B, LOC, LOC1, LOC2)

Arguments

Type IntentOptional Attributes Name
integer :: VAL
integer :: TAB(A:B)
integer :: A
integer :: B
integer :: LOC
integer :: LOC1
integer :: LOC2

private subroutine GETCACHEINDEX(I, J, RET)

Arguments

Type IntentOptional Attributes Name
integer :: I
integer :: J
integer :: RET

public subroutine GETCACHEINDEXSTATES(IND, I, J)

Arguments

Type IntentOptional Attributes Name
integer :: IND
integer :: I
integer :: J

public subroutine FreezeUMatCache(OrbTrans, nOld, nNew)

Arguments

Type IntentOptional Attributes Name
integer :: OrbTrans(nOld)
integer :: nOld
integer :: nNew

public subroutine FreezeUMAT2D(OldBasis, NewBasis, OrbTrans, iSS)

Arguments

Type IntentOptional Attributes Name
integer :: OldBasis
integer :: NewBasis
integer :: OrbTrans(OldBasis)
integer :: iSS

private subroutine FreezeUMatCacheInt(OrbTrans, nOld, nNew, onSlots, onPairs)

Arguments

Type IntentOptional Attributes Name
integer :: OrbTrans(nOld)
integer :: nOld
integer :: nNew
integer :: onSlots
integer :: onPairs

public subroutine CacheFCIDUMP(I, J, K, L, Z, CacheInd, ZeroedInt, NonZeroInt)

Arguments

Type IntentOptional Attributes Name
integer :: I
integer :: J
integer :: K
integer :: L
real(kind=dp) :: Z
integer :: CacheInd(nPairs)
integer(kind=int64) :: ZeroedInt
integer(kind=int64) :: NonZeroInt

private subroutine ReadInUMatCache()

Arguments

None

public subroutine DumpUMatCache()

Arguments

None

public subroutine SetupUMat2d_dense(nBasis)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nBasis

private subroutine CACHEUMATEL(B, UMATEL, ICACHE, ICACHEI, iType)

Arguments

Type IntentOptional Attributes Name
integer :: B
real(kind=dp) :: UMATEL(0:NTYPES-1)
integer :: ICACHE
integer :: ICACHEI
integer :: iType