setup_real_time_fciqmc Subroutine

public subroutine setup_real_time_fciqmc()

Arguments

None

Contents


Source Code

    subroutine setup_real_time_fciqmc()
        ! this is the last setup routine, which depending on compilation,
        ! number of copies etc. sets up the final needed quantities to run
        ! a simulation
        implicit none
        character(*), parameter :: this_routine = "setup_real_time_fciqmc"
        integer :: ierr, run

        ! the new total momentum has to be constructed before the
        ! time-evolved state is read in, as the latter deletes the
        ! pops_pert, because perturbation and read-in are done in one
        ! function (dependencies...)
        if (tHub) then
            if (allocated(pops_pert)) then

                if (pops_pert(1)%nannihilate == 1) kTotal = kTotal &
                                                            - G1(pops_pert(1)%ann_orbs(1))%k
                if (pops_pert(1)%ncreate == 1) kTotal = kTotal &
                                                        + G1(pops_pert(1)%crtn_orbs(1))%k
                call MomPbcSym(kTotal, nBasisMax)
                write(stdout, *) "New total momentum", kTotal
            end if
        end if

        ! allocate the according quantities!
        ! n_time_steps have to be set here!
        write(stdout, *) " Allocating greensfunction and wavefunction norm arrays!"
        ! allocate an additional slot for initial values
        if (numSnapshotOrbs > 0) then
            allocate(popSnapshot(numSnapshotOrbs), stat=ierr)
            allocate(allPopSnapshot(numSnapshotOrbs), stat=ierr)
            popSnapshot = 0.0_dp
            allPopSnapshot = 0.0_dp
        else
            allocate(popSnapshot(1), stat=ierr)
            allocate(allPopSnapshot(numSnapshotOrbs), stat=ierr)
            popSnapshot = 0.0_dp
            allPopSnapshot = 0.0_dp
        end if
        allocate(gs_energy(inum_runs), stat=ierr)
        allocate(temp_freeslot(MaxWalkersPart), stat=ierr)
        allocate(TotPartsPeak(inum_runs), stat=ierr)
        allocate(numCycShiftExcess(inum_runs), stat=ierr)
        ! allocate the buffer for storing previous values of alpha
        ! for now, take 50 values of alpha in the log
        alphaLogSize = 50
        alphaLogPos = 1
        allocate(alphaLog(alphaLogSize), stat=ierr)
        alphalog = 0.0_dp
        numCycShiftExcess = 0
        ! allocate spawn buffer for verlet scheme
        if (tVerletScheme) allocate(spawnBuf(0:niftot, 1:maxSpawned))

        TotPartsPeak = 0.0_dp
        gs_energy = benchmarkEnergy

        ! when projecting onto the perturbed reference, we obviously need to create
        ! a new state
        if (tHFOverlap) tNewOverlap = .true.

        call init_overlap_buffers()

        if (tRealTimePopsfile) call readTimeEvolvedState()

        ! check for set lms.. i think that does not quite work yet
        write(stdout, *) "mz spin projection: ", lms

        write(stdout, *) "tSinglePartPhase?:", tSinglePartPhase
        write(stdout, *) "tWalkContGrow?", tWalkContGrow
        write(stdout, *) "diagSft:", diagSft

        ! intialize the 2nd temporary determinant list needed in the
        ! real-time fciqmc

        ! also maybe use the spawn_ht hash table, so allocated it here!
        call setup_temp_det_list()

        write(stdout, *) "allocated(temp_det_list)?", allocated(temp_det_list)
        write(stdout, *) "associated(temp_det_pointer)?", associated(temp_det_pointer)
        write(stdout, *) "associated(temp_det_hash)?", associated(temp_det_hash)

        write(stdout, *) "associated(spawn_ht)?", associated(spawn_ht)

        write(stdout, *) "Allgrowrate: ", AllGrowRate
        ! print out the first infos on the calculation..
        ! although that definetly has to be changed for the real-time fciqm

        ! use new output format!
        tFCIMCStats2 = .true.

        if (tFCIMCStats2) then
            call write_fcimcstats2(iter_data_fciqmc, initial=.true.)
        else
            call WriteFciMCStatsHeader()
        end if

        ! set the iter variable to 0 probably
        iter = 0

        ! and also the PreviousCycles var. since its essentially regarded as
        ! a new calulcation
        PreviousCycles = 0

        ! for intermediate test_purposes turn off spawning to check if the
        ! diagonal step works as intented
!         pSingles = 0.0_dp
!         pDoubles = 0.0_dp

        ! also initialize the second_spawn_iter_data type
        call allocate_iter_data(second_spawn_iter_data)

        ! and also initialize the values:
        second_spawn_iter_data%ndied = 0.0_dp
        second_spawn_iter_data%nborn = 0.0_dp
        second_spawn_iter_data%nannihil = 0.0_dp
        second_spawn_iter_data%naborted = 0.0_dp
        second_spawn_iter_data%nremoved = 0.0_dp
        second_spawn_iter_data%update_growth = 0.0_dp
        second_spawn_iter_data%update_growth_tot = 0.0_dp
        second_spawn_iter_data%tot_parts_old = TotParts
        second_spawn_iter_data%update_iters = 0

        TotPartsStorage = TotParts
        TotPartsLastAlpha = TotParts

        ! also intitialize the 2nd spawning array to deal with the
        ! diagonal death step in the 2nd rt-fciqmc loop
        allocate(DiagVec(0:IlutBits%len_bcast, MaxWalkersPart), stat=ierr)
        call LogMemAlloc('DiagVec', MaxWalkersPart * (1 + IlutBits%len_bcast), size_n_int, &
                         this_routine, DiagVecTag, ierr)

        DiagVec = 0

        DiagParts => DiagVec

        ! and the initial_spawn_slots equivalent
        ! although i think i can reuse the initialSpawnedSlots..
!         allocate(initial_diag_spawn_list(0:nNodes-1), stat = ierr)

        valid_diag_spawns = 1

        do run = 1, inum_runs
            SumWalkersCyc(run) = SumWalkersCyc(run) + &
                                 sum(TotParts(min_part_type(run):max_part_type(run)))
        end do

        tVerletSweep = .false.
        if (tVerletScheme) then
            call setup_delta_psi()
            call backup_initial_state()
            call assign_value_to_tau(tau / iterInit, this_routine)
        end if

        if (tStaticShift) DiagSft = asymptoticShift

        if (tGenerateCoreSpace) call initialize_corespace_construction()

        if (tReadTrajectory) call read_in_trajectory()

        ! Set up the reference space for the adi-approach
        call setup_reference_space(tReadPops)

        call rotate_time()

    end subroutine setup_real_time_fciqmc