set_trial_states Subroutine

public subroutine set_trial_states(ndets_this_proc, init_vecs, trial_iluts, semistoch_started, paired_replicas)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ndets_this_proc
real(kind=dp), intent(in) :: init_vecs(:,:)
integer(kind=n_int), intent(in) :: trial_iluts(0:,:)
logical, intent(in) :: semistoch_started
logical, intent(in), optional :: paired_replicas

Contents

Source Code


Source Code

    subroutine set_trial_states(ndets_this_proc, init_vecs, trial_iluts, &
                                semistoch_started, paired_replicas)

        use bit_reps, only: encode_sign
        use CalcData, only: tSemiStochastic, tTrialWavefunction
        use FciMCData, only: CurrentDets, TotWalkers, HashIndex, nWalkerHashes
        use replica_data, only: set_initial_global_data
        use hash, only: clear_hash_table, fill_in_hash_table
        use semi_stoch_procs, only: fill_in_diag_helements, copy_core_dets_to_spawnedparts
        use semi_stoch_procs, only: add_core_states_currentdet_hash, reinit_current_trial_amps

        integer, intent(in) :: ndets_this_proc
        HElement_t(dp), intent(in) :: init_vecs(:, :)
        integer(n_int), intent(in) :: trial_iluts(0:, :)
        logical, intent(in) :: semistoch_started
        logical, intent(in), optional :: paired_replicas

        real(dp) :: real_sign(lenof_sign)
        integer :: i, j
        logical :: paired_reps_local

        if (present(paired_replicas)) then
            paired_reps_local = paired_replicas
        else
            paired_reps_local = .true.
        end if

        ! Now copy the amplitudes across to the CurrentDets array:
        ! First, get the correct states in CurrentDets.
        CurrentDets(0:NIfTot, 1:ndets_this_proc) = 0_n_int
        CurrentDets(0:nifd, 1:ndets_this_proc) = trial_iluts(0:nifd, 1:ndets_this_proc)

        ! Set signs.
        do i = 1, ndets_this_proc
            ! Construct the sign array to be encoded.
            if (paired_reps_local) then
                do j = 2, lenof_sign, 2
                    real_sign(j - 1:j) = init_vecs(j / 2, i)
                end do
            else
                do j = 1, inum_runs
                    real_sign(min_part_type(j):max_part_type(j)) = h_to_array(init_vecs(j, i))
                end do
            end if
            call encode_sign(CurrentDets(:, i), real_sign)
        end do

        TotWalkers = int(ndets_this_proc, int64)

        ! Reset and fill in the hash table.
        call clear_hash_table(HashIndex)
        call fill_in_hash_table(HashIndex, nWalkerHashes, CurrentDets, ndets_this_proc, .true.)

        if (tSemiStochastic .and. semistoch_started) then
            ! core_space stores all core determinants from all processors. Move those on this
            ! processor to trial_iluts, 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)
        end if

        if (tTrialWavefunction) call reinit_current_trial_amps()

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

        call set_initial_global_data(TotWalkers, CurrentDets)

    end subroutine set_trial_states