DeallocFCIMCMemPar Subroutine

public subroutine DeallocFCIMCMemPar()

Arguments

None

Contents

Source Code


Source Code

    subroutine DeallocFCIMCMemPar()

        CHARACTER(len=*), PARAMETER :: this_routine = 'DeallocFciMCMemPar'
        type(ll_node), pointer :: Curr, Prev
        integer :: i, ierr

        deallocate(RandomHash2, stat=ierr)
        if (ierr /= 0) call stop_all(this_routine, "Err deallocating")

        ! Deallocate the linked list
        do i = 1, nWalkerHashes
            Curr => HashIndex(i)%Next
            Prev => HashIndex(i)
            nullify (Prev%Next)
            do while (associated(Curr))
                Prev => Curr
                Curr => Curr%Next
                deallocate(Prev)
                if (ierr /= 0) call stop_all(this_routine, "Err deallocating")
            end do
        end do
        deallocate(HashIndex, stat=ierr)
        if (ierr /= 0) call stop_all(this_routine, "Err deallocating")
        nullify (Curr)
        nullify (Prev)

        deallocate(FreeSlot, stat=ierr)
        if (ierr /= 0) call stop_all(this_routine, "Err deallocating")

        IF (tHistSpawn .or. tCalcFCIMCPsi) THEN
            DEallocate(Histogram)
            DEallocate(AllHistogram)
            IF (tHistSpawn) THEN
                DEallocate(InstHist)
                DEallocate(InstAnnihil)
                DEallocate(AvAnnihil)
            end if
            IF (iProcIndex == 0) THEN
                IF (tHistSpawn) THEN
                    DEallocate(AllInstHist)
                    DEallocate(AllAvAnnihil)
                    DEallocate(AllInstAnnihil)
                end if
            end if
        else if (tHistEnergies) THEN
            DEallocate(HistogramEnergy)
            DEallocate(AttemptHist)
            DEallocate(SpawnHist)
            DEallocate(SinglesHist)
            DEallocate(DoublesHist)
            DEallocate(DoublesAttemptHist)
            DEallocate(SinglesAttemptHist)
            DEallocate(SinglesHistOccOcc)
            DEallocate(SinglesHistVirtOcc)
            DEallocate(SinglesHistOccVirt)
            DEallocate(SinglesHistVirtVirt)
            IF (iProcIndex == Root) THEN
                DEallocate(AllHistogramEnergy)
                DEallocate(AllAttemptHist)
                DEallocate(AllSpawnHist)
                DEallocate(AllSinglesAttemptHist)
                DEallocate(AllSinglesHist)
                DEallocate(AllDoublesAttemptHist)
                DEallocate(AllDoublesHist)
                DEallocate(AllSinglesHistOccOcc)
                DEallocate(AllSinglesHistVirtOcc)
                DEallocate(AllSinglesHistOccVirt)
                DEallocate(AllSinglesHistVirtVirt)
            end if
        end if
        if (tHistExcitToFrom) call clean_hist_excit_tofrom()
        DEallocate(WalkVecDets)
        CALL LogMemDealloc(this_routine, WalkVecDetsTag)
        DEallocate(SpawnVec)
        CALL LogMemDealloc(this_routine, SpawnVecTag)
        DEallocate(SpawnVec2)
        CALL LogMemDealloc(this_routine, SpawnVec2Tag)
        if (tAutoAdaptiveShift) then
            DEallocate(SpawnInfoVec)
            CALL LogMemDealloc(this_routine, SpawnInfoVecTag)
            DEallocate(SpawnInfoVec2)
            CALL LogMemDealloc(this_routine, SpawnInfoVec2Tag)
        end if

        if (allocated(TempSpawnedParts)) then
            deallocate(TempSpawnedParts)
            log_dealloc(TempSpawnedPartsTag)
        end if
        DEallocate(HFDet)
        CALL LogMemDealloc(this_routine, HFDetTag)
        DEallocate(iLutHF)
        DEallocate(iLutRef)
        DEallocate(ProjEDet)
        DEallocate(iLutHF_True)
        DEallocate(HFDet_True)
        IF (ALLOCATED(HighestPopDet)) DEallocate(HighestPopDet)
        IF (ALLOCATED(RandomOrbIndex)) DEallocate(RandomOrbIndex)

        IF (ALLOCATED(SpinInvBrr)) THEN
            CALL LogMemDealloc(this_routine, SpinInvBRRTag)
            DEallocate(SpinInvBRR)
        end if
        IF (ALLOCATED(CoreMask)) THEN
            DEallocate(CoreMask)
            DEallocate(CASMask)
        end if
        IF (tPrintOrbOcc) THEN
            DEallocate(OrbOccs)
            CALL LogMemDeAlloc(this_routine, OrbOccsTag)
        end if

        IF (tHistInitPops) THEN
            if (allocated(HistInitPops)) then
                deallocate(HistInitPops)
                call LogMemDeAlloc(this_routine, HistInitPopsTag)
            end if
            IF (iProcIndex == 0) THEN
                if (allocated(AllHistInitPops)) then
                    deallocate(AllHistInitPops)
                    call LogMemDeAlloc(this_routine, AllHistInitPopsTag)
                end if
            end if
        end if

        if (tHub) then
            if (allocated(momIndexTable)) deallocate(momIndexTable)
            deallocate(breathingCont)
        end if

        if (tRDMonFly) call dealloc_global_rdm_data()

        if (allocated(refdetflip)) deallocate(refdetflip)
        if (allocated(ilutrefflip)) deallocate(ilutrefflip)
        if (allocated(ValidSpawnedList)) deallocate(ValidSpawnedList)
        if (allocated(InitialSpawnedSlots)) deallocate(InitialSpawnedSlots)

        ! Cleanup global storage
        call clean_global_det_data()

        ! Cleanup excitation generation storage
        call clean_excit_gen_store(fcimc_excit_gen_store)

        ! Cleanup cont time
        call clean_cont_time()

        ! Cleanup the load balancing
        call clean_load_balance()

        ! Cleanup adi caches
        call clean_adi()


        ! Cleanup excitation generator
        if (t_guga_pchb) then
            call finalize_pchb_excitgen_guga()
        end if

        if (t_pcpp_excitgen) call finalize_pcpp_excitgen()

        if(t_impurity_excitgen) call clearImpurityExcitgen()

        if (tSemiStochastic) call end_semistoch()

        if (tTrialWavefunction) call end_trial_wf()

        call finalize_exz_gen_class()


    end subroutine DeallocFCIMCMemPar