create_initial_config Subroutine

private subroutine create_initial_config(iconfig, irepeat, nrepeats)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: iconfig
integer, intent(in) :: irepeat
integer, intent(in) :: nrepeats

Contents

Source Code


Source Code

    subroutine create_initial_config(iconfig, irepeat, nrepeats)

        use CalcData, only: tStartSinglePart, InitialPart, InitWalkers, tSemiStochastic, tReadPops
        use dSFMT_interface, only: dSFMT_init
        use fcimc_initialisation, only: InitFCIMC_HF
        use FciMCData, only: nWalkerHashes, HashIndex, pops_pert, SpawnedParts, TotWalkers, AllTotWalkers
        use FciMCData, only: TotParts, AllTotParts, TotPartsOld, AllTotPartsOld, kp_generate_time
        use FciMCData, only: tStartCoreGroundState, CurrentDets, HolesInList
        use hash, only: fill_in_hash_table, clear_hash_table
        use PopsfileMod, only: read_popsfile_wrapper
        use semi_stoch_procs, only: copy_core_dets_to_spawnedparts, fill_in_diag_helements
        use semi_stoch_procs, only: add_core_states_currentdet_hash, start_walkers_from_core_ground
        use semi_stoch_procs, only: check_determ_flag
        use timing_neci, only: get_total_time, set_timer, halt_timer

        integer, intent(in) :: iconfig, irepeat, nrepeats

        integer :: DetHash, nwalkers_int
        integer(int64) :: i
        integer(n_int) :: int_sign(lenof_sign_kp)
        real(dp) :: real_sign(lenof_sign_kp), TotPartsCheck(lenof_sign_kp)
        real(dp) :: nwalkers_target
        real(dp) :: norm, all_norm
        real(dp) :: total_time_before, total_time_after
        logical :: tCoreDet
        character(len=*), parameter :: t_r = "create_init_config"

        ! Clear everything from any previous repeats or starting configurations.
        call clear_hash_table(HashIndex)

        if (tStartSinglePart) then
            nwalkers_target = real(InitialPart, dp)
        else
            nwalkers_target = InitWalkers * nProcessors
        end if

        if (irepeat == 1) then
            if (.not. tFiniteTemp) then
                if (tReadPops) then
                    ! Call a wrapper function which will call the various functions
                    ! required to read in a popsfile.
                    if (allocated(pops_pert)) then
                        call read_popsfile_wrapper(pops_pert)
                    else
                        call read_popsfile_wrapper()
                    end if

                    if (tScalePopulation) then
                        call scale_population(CurrentDets, TotWalkers, nwalkers_target, TotPartsCheck, scaling_factor)
                        ! Update global data.
                        if (any(abs(TotPartsCheck - TotParts) > 1.0e-12_dp)) then
                            call stop_all(t_r, "Inconsistent values of TotParts calculated.")
                        end if
                        TotParts = TotParts * scaling_factor
                        TotPartsOld = TotParts
                        AllTotParts = AllTotParts * scaling_factor
                        AllTotPartsOld = AllTotParts
                    end if
                else
                    ! Put a walker on the Hartree-Fock, with the requested amplitude.
                    call InitFCIMC_HF()
                end if

                if (tSemiStochastic) then
                    ! core_space stores all core determinants from all processors. Move those on this
                    ! processor to SpawnedParts, which add_core_states_currentdet_hash uses.
                    call copy_core_dets_to_spawnedparts(cs_replicas(core_run))
                    ! Any core space determinants which are not already in CurrentDets will be added
                    ! by this routine.
                    call add_core_states_currentdet_hash(core_run)
                    if (tStartCoreGroundState .and. (.not. tReadPops)) &
                        call start_walkers_from_core_ground(tPrintInfo=.false., run=core_run)
                end if

            else if (tFiniteTemp) then
                ! Convert the initial number of walkers to an integer. Note that on multiple
                ! processors this may round up the requested number of walkers slightly.
                nwalkers_int = ceiling(nwalkers_target / real(nProcessors, dp))

                ! If requested, reset the random number generator with the requested seed
                ! before creating the random initial configuration.
                if (tUseInitConfigSeeds) call dSFMT_init((iProcIndex + 1) * init_config_seeds(iconfig))

                write(stdout, '(a44)', advance='no') "# Generating initial walker configuration..."
                call set_timer(kp_generate_time)
                total_time_before = get_total_time(kp_generate_time)

                ! Create the random initial configuration.
                if (tInitCorrectNWalkers) then
                    call generate_init_config_this_proc(nwalkers_int, nwalkers_per_site_init, tOccDetermInit)
                else
                    call generate_init_config_basic(nwalkers_int, nwalkers_per_site_init)
                end if

                call halt_timer(kp_generate_time)
                total_time_after = get_total_time(kp_generate_time)
                write(stdout, '(1x,a31,f9.3)') "Complete. Time taken (seconds):", total_time_after - total_time_before

            end if
        else if (irepeat > 1) then
            ! If repeating from a previsouly generated initial configuration, simpy reset the following
            ! data and copy the first Krylov vector (which is always the starting configuration) from
            ! the last run to CurrentDets.
            TotWalkers = TotWalkersInit
            AllTotWalkers = AllTotWalkersInit
            TotParts = TotPartsInit
            TotPartsOld = TotPartsInit
            AllTotParts = AllTotPartsInit
            AllTotPartsOld = AllTotPartsInit
            do i = 1, int(TotWalkers)
                ! Copy across the bitstring encoding of the determinant and also the walker signs.
                CurrentDets(0:IlutBits%ind_pop + lenof_sign_kp - 1, i) = krylov_vecs(0:IlutBits%ind_pop + lenof_sign_kp - 1, i)
                ! Copy across the flags.
                CurrentDets(NIfTot, i) = krylov_vecs(NIfTotKP, i)
            end do
            call fill_in_hash_table(HashIndex, nWalkerHashes, CurrentDets, int(TotWalkers), .true.)
        end if

        ! Calculate and store the diagonal element of the Hamiltonian for determinants in CurrentDets.
        call fill_in_diag_helements()

        ! If starting from this configuration more than once, store the relevant data for next time.
        if (nrepeats > 1 .and. irepeat == 1) then
            HolesInList = 0
            do i = 1, TotWalkers
                int_sign = CurrentDets(IlutBits%ind_pop:IlutBits%ind_pop + lenof_sign_kp - 1, i)
                call extract_sign(CurrentDets(:, i), real_sign)
                tCoreDet = check_determ_flag(CurrentDets(:, i))
                ! Don't add unoccpied determinants, unless they are core determinants.
                if (IsUnoccDet(real_sign) .and. (.not. tCoreDet)) HolesInList = HolesInList + 1
            end do
            TotWalkersInit = TotWalkers - HolesInList
            call MPISumAll(TotWalkersInit, AllTotWalkers)
            AllTotWalkersInit = AllTotWalkers
            TotPartsInit = TotParts
            AllTotPartsInit = AllTotParts
        end if

    end subroutine create_initial_config