CalcParentFlag_det Subroutine

public subroutine CalcParentFlag_det(j, nI, exLvl, parent_flags)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: nI(nel)
integer, intent(in) :: exLvl
integer, intent(out) :: parent_flags

Contents

Source Code


Source Code

    subroutine CalcParentFlag_det(j, nI, exLvl, parent_flags)

        ! In the CurrentDets array, the flag at NIfTot refers to whether that
        ! determinant *itself* is an initiator or not. We need to decide if
        ! this willchange due to the determinant acquiring a certain
        ! population, or its population dropping below the threshold.
        ! The CurrentDets(:,j) is the determinant we are currently spawning
        ! from, so this determines the ParentInitiator flag which is passed to
        ! the SpawnedDets array and refers to whether or not the walkers
        ! *parent* is an initiator or not.

        integer, intent(in) :: j, nI(nel), exLvl
        integer, intent(out) :: parent_flags
        real(dp) :: CurrentSign(lenof_sign)
        integer :: run, nopen
        logical :: tDetinCAS, parent_init
        real(dp) :: init_tm, expected_lifetime, hdiag
        character(*), parameter :: this_routine = 'CalcParentFlag'

        call extract_sign(CurrentDets(:, j), CurrentSign)

        if (tTruncInitiator) then

            ! Now loop over the particle types, and update the flags
            do run = 1, inum_runs

                ! By default, the parent_flags are the flags of the parent.
                parent_init = test_flag(CurrentDets(:, j), get_initiator_flag_by_run(run))

                ! Should this particle be considered to be an initiator
                ! for spawning purposes.
                if (tPureInitiatorSpace) then
                    parent_init = TestInitiator_pure_space(CurrentDets(:, j), nI, j, parent_init, run)
                else
                    parent_init = TestInitiator_explicit(CurrentDets(:, j), nI, j, parent_init, &
                                                         CurrentSign, exLvl, run)
                end if

                ! log the initiator
                if (parent_init) then
                    if (exLvl <= maxInitExLvlWrite .and. exLvl > 0) &
                        initsPerExLvl(exLvl) = initsPerExLvl(exLvl) + 1
                end if

                ! Update counters as required.
                if (parent_init) then
                    NoInitDets(run) = NoInitDets(run) + 1_int64
                    NoInitWalk(run) = NoInitWalk(run) + mag_of_run(CurrentSign, run)
                else
                    NoNonInitDets(run) = NoNonInitDets(run) + 1_int64
                    NoNonInitWalk(run) = NoNonInitWalk(run) + mag_of_run(CurrentSign, run)
                end if

                ! Update the parent flag as required.
                call set_flag(CurrentDets(:, j), get_initiator_flag_by_run(run), parent_init)

            end do

        end if

        ! Store this flag for use in the spawning routines...
        parent_flags = extract_flags(CurrentDets(:, j))

        ! We don't want the deterministic flag to be set in parent_flags, as
        ! that would set the same flag in the child in create_particle, which
        ! we don't want in general.
        do run = 1, inum_runs
            parent_flags = ibclr(parent_flags, flag_deterministic(run))
        end do

        ! We don't want the child to have trial or connected flags.
        parent_flags = ibclr(parent_flags, flag_trial)
        parent_flags = ibclr(parent_flags, flag_connected)

        if ((tHistInitPops .and. mod(iter, histInitPopsIter) == 0) &
            .or. tPrintHighPop) then
            call HistInitPopulations(CurrentSign(1), j)
            if (t_core_inits) then
                write(stdout, '(A)') 'Note that core-space determinants are also initiators because core-inits is ON.'
                write(stdout, '(A)') 'Nevertheless they are not counted in this histogramming.'
            end if
        end if

    end subroutine CalcParentFlag_det