subroutine init_kp_fciqmc_repeat(iconfig, irepeat, nrepeats, nvecs, iter_data)
use CalcData, only: tStartSinglePart, InitialPart, InitWalkers, DiagSft, iPopsFileNoRead
use CalcData, only: tPairedReplicas
use FciMCData, only: iter, InputDiagSft, PreviousCycles, OldAllAvWalkersCyc, proje_iter
use FciMCData, only: proje_iter_tot, AllGrowRate, SpawnedParts, fcimc_iter_data
use hash, only: clear_hash_table
use initial_trial_states
use LoggingData, only: tFCIMCStats2, tPrintDataTables
use util_mod, only: int_fmt
integer, intent(in) :: iconfig, irepeat, nrepeats, nvecs
integer :: ndets_this_proc, nexcit
real(dp), allocatable :: evals(:)
HElement_t(dp), allocatable :: evecs_this_proc(:, :), init_vecs(:, :)
integer(MPIArg) :: space_sizes(0:nProcessors - 1), space_displs(0:nProcessors - 1)
type(fcimc_iter_data), intent(in) :: iter_data
write(stdout, '(1x,a22,'//int_fmt(irepeat, 1)//')') "Starting repeat number", irepeat
if (tExcitedStateKP) then
nexcit = nvecs
allocate(evals(nexcit))
! Create the trial excited states.
call calc_trial_states_lanczos(kp_trial_space_in, nexcit, ndets_this_proc, SpawnedParts, &
evecs_this_proc, evals, space_sizes, space_displs)
! Set the populations of these states to the requested value.
call set_trial_populations(nexcit, ndets_this_proc, evecs_this_proc)
! Set the trial excited states as the FCIQMC wave functions.
call set_trial_states(ndets_this_proc, evecs_this_proc, SpawnedParts, .true., tPairedReplicas)
deallocate(evecs_this_proc, evals)
else if (tExcitedInitState) then
nexcit = maxval(kpfciqmc_ex_labels)
allocate(evals(nexcit))
! Create the trial excited states.
call calc_trial_states_lanczos(kp_trial_space_in, nexcit, ndets_this_proc, SpawnedParts, &
evecs_this_proc, evals, space_sizes, space_displs)
! Extract the desried initial excited states and average them.
call create_init_excited_state(ndets_this_proc, evecs_this_proc, kpfciqmc_ex_labels, kpfciqmc_ex_weights, init_vecs)
! Set the populations of these states to the requested value.
call set_trial_populations(1, ndets_this_proc, init_vecs)
! Set the trial excited states as the FCIQMC wave functions.
call set_trial_states(ndets_this_proc, init_vecs, SpawnedParts, .true., tPairedReplicas)
deallocate(evecs_this_proc, init_vecs, evals)
else
! If starting from multiple POPSFILEs then set this counter so that the
! correct POPSFILE is read in this time. To read in POPSFILE.x,
! iPopsFileNoRead needs to be set to -x-1. We want to read in POPSFILE
! numbers 0 to kp%nconfigs-1
if (tMultiplePopStart) iPopsFileNoRead = -(iconfig - 1) - 1
if (tOverlapPert .and. irepeat == 1) then
pert_overlaps = 0.0_dp
call create_overlap_pert_vec()
end if
call create_initial_config(iconfig, irepeat, nrepeats)
call clear_hash_table(krylov_vecs_ht)
krylov_vecs = 0_n_int
end if
! Rezero all the necessary data.
TotWalkersKP = 0
nkrylov_amp_elems_used = 0
iter = 0
PreviousCycles = 0
DiagSft = InputDiagSft
if (tStartSinglePart) then
OldAllAvWalkersCyc = InitialPart
else
OldAllAvWalkersCyc = InitWalkers * nProcessors
end if
proje_iter = 0.0_dp
proje_iter_tot = 0.0_dp
AllGrowRate = 0.0_dp
! Setting this variable to true stops the shift from varying instantly.
tSinglePartPhase = tSinglePartPhaseKPInit
! Print out initial stats.
if (tPrintDataTables) then
if (tFCIMCStats2) then
call write_fcimcstats2(iter_data)
else
call WriteFCIMCStats()
end if
end if
end subroutine init_kp_fciqmc_repeat