SETUPUMATCACHE Subroutine

public subroutine SETUPUMATCACHE(NSTATE, TSMALL)

Arguments

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

Contents

Source Code


Source Code

    SUBROUTINE SETUPUMATCACHE(NSTATE, TSMALL)
        ! nState: # states.
        ! TSMALL is used if we create a pre-freezing cache to hold just the <ij|kj> integrals.
        INTEGER NSTATE
        real(dp) Memory
        LOGICAL TSMALL
        INTEGER ierr
        character(len=*), parameter :: thisroutine = 'SETUPUMATCACHE'
        NTYPES = HElement_t_size
        NHITS = 0
        NMISSES = 0
        iCacheOvCount = 0
        NSTATES = NSTATE
        IF (NSLOTSINIT <= 0) THEN
            NSLOTS = 0
            write(stdout, *) "Not using UMATCACHE."
        ELSE
            NPAIRS = NSTATES * (NSTATES + 1) / 2
            write(stdout, *) "NPairs: ", NSTATES, NPAIRS
            IF (TSMALL) THEN
                NSLOTS = NSTATES
                tSmallUMat = .TRUE.
                write(stdout, *) "Using small pre-freezing UMat Cache."
            ELSE
                IF (nMemInit /= 0) THEN
                    write(stdout, *) "Allocating ", nMemInit, "Mb for UMatCache+Labels."
                    nSlotsInit = nint((nMemInit * 1048576 / 8) / (nPairs * (nTypes * HElement_t_size + 1.0_dp / irat)))
                end if
                NSLOTS = MIN(NPAIRS, NSLOTSINIT)
                tSmallUMat = .FALSE.
            end if
            UMATCACHEFLAG = 0
            write(stdout, "(A,I3,2I7,I10)") "UMAT NTYPES,NSLOTS,NPAIRS,TOT", NTYPES, NSLOTS, NPAIRS, NSLOTS * NPAIRS * NTYPES
            TUMAT2D = .FALSE.
            ! Each cache element stores <ij|ab> and <ib|aj>.  If real orbitals
            ! then these are identical and we can use this to halve the storage
            ! space (setting nTypes=1).  If not, we must store both explicitly
            ! (nTypes=2).
            allocate(UMatCacheData(0:nTypes - 1, nSlots, nPairs), STAT=ierr)
            call LogMemAlloc('UMatCache', nTypes * nSlots * nPairs, 8 * HElement_t_size, thisroutine, tagUMatCacheData)
            allocate(UMatLabels(nSlots, nPairs), STAT=ierr)
            CALL LogMemAlloc('UMATLABELS', nSlots * nPairs, 4, thisroutine, tagUMatLabels)
            Memory = (REAL(nTypes * nSlots, dp) * nPairs * 8.0_dp * HElement_t_size + nSlots * nPairs * 4.0_dp) * 9.536743316e-7_dp
            write(stdout, "(A,G20.10,A)") "Total memory allocated for storage of integrals in cache is: ", Memory, "Mb/Processor"

            UMatCacheData = (0.0_dp)
            UMATLABELS(1:nSlots, 1:nPairs) = 0
            if (.not. tSmallUMat .and. tReadInCache) then
                write(stdout, *) 'reading in cache'
                call ReadInUMatCache
            end if
        end if
    END SUBROUTINE SetupUMatCache