TestInitiator_explicit Function

public function TestInitiator_explicit(ilut, nI, det_idx, is_init, sgn, exLvl, run) result(initiator)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(inout) :: ilut(0:NIfTot)
integer, intent(in) :: nI(nel)
integer, intent(in) :: det_idx
logical, intent(in) :: is_init
real(kind=dp), intent(in) :: sgn(lenof_sign)
integer, intent(in) :: exLvl
integer, intent(in) :: run

Return Value logical


Contents


Source Code

    function TestInitiator_explicit(ilut, nI, det_idx, is_init, sgn, exLvl, run) result(initiator)
        use adi_initiators, only: check_static_init
        ! For a given particle (with its given particle type), should it
        ! be considered as an initiator for the purposes of spawning.
        !
        ! Inputs: The ilut, the determinant, the particles sign, and if the particle
        !         is currently considered to be an initiator.

        ! N.B. This intentionally DOES NOT directly reference part_type.
        !      This means we can call it for individual, or aggregate,
        !      particles.

        integer(n_int), intent(inout) :: ilut(0:NIfTot)
        logical, intent(in) :: is_init
        integer, intent(in) :: run, nI(nel), exLvl, det_idx
        real(dp), intent(in) :: sgn(lenof_sign)

        logical :: initiator, staticInit, popInit, spawnInit
        integer :: i

        logical :: Senior
        real(dp) :: DetAge, HalfLife, AvgShift, diagH

        ! initiator flag according to population/spawn coherence
        popInit = initiator_criterium(sgn, det_diagH(det_idx), run) .or. &
                  spawn_criterium(det_idx)

        ! initiator flag according to SI or a static initiator space
        staticInit = check_static_init(ilut, nI, sgn, exLvl, run)

        if (tInitiatorSpace) then
            staticInit = test_flag(ilut, flag_static_init(run)) &
                         .or. check_determ_flag(ilut, run)
            if (.not. staticInit) then
                if (is_in_initiator_space(ilut, nI)) then
                    staticInit = .true.
                    call set_flag(CurrentDets(:, det_idx), flag_static_init(run))
                end if
            end if
        end if

        ! By default the particles status will stay the same
        initiator = is_init

        ! SI-caused initiators also have the initiator flag
        if (staticInit) then
            initiator = .true.
            ! thats it, we never remove static initiators
            return
        end if

        Senior = .false.
        if (tSeniorInitiators .and. .not. is_run_unnocc(sgn, run)) then
            DetAge = get_tau_int(det_idx, run)
            diagH = det_diagH(det_idx)
            AvgShift = get_shift_int(det_idx, run) / DetAge
            HalfLife = log(2.0_dp) / (diagH - AvgShift)
            !Usually the shift is negative, so the HalfLife is always positive.
            !In some cases, however, the shift is set to positive (to increase the birth at HF).
            !This will to a negative HalfLife for some determinants.
            if (HalfLife > 0.0) then
                Senior = DetAge > HalfLife * SeniorityAge
            end if
        end if
        if (Senior) initiator = .true.

        if (.not. initiator) then

            ! Determinant wasn't previously initiator
            ! - want to test if it has now got a large enough
            !   population to become an initiator.
            if (popInit) then
                initiator = .true.
                NoAddedInitiators = NoAddedInitiators + 1_int64
            end if

        else

            ! The determinants become
            ! non-initiators again if their population falls below
            ! n_add (this is on by default).

            ! All of the references stay initiators
            if (DetBitEQ(ilut, ilutRef(:, run), nifd)) staticInit = .true.
            ! If det. is the HF det, or it
            ! is in the deterministic space, then it must remain an initiator.
            if (.not. (staticInit) &
                .and. .not. (check_determ_flag(ilut, run) .and. t_core_inits) &
                .and. .not. Senior &
                .and. (.not. popInit)) then
                ! Population has fallen too low. Initiator status
                ! removed.
                initiator = .false.
                NoAddedInitiators = NoAddedInitiators - 1_int64
            end if

            if (.not. initiator .and. check_determ_flag(ilut, run)) &
                n_core_non_init = n_core_non_init + 1

        end if

    end function TestInitiator_explicit