procedure_pointers Module


Contents


Variables

Type Visibility Attributes Name Initial
procedure(generate_excitation_t), public, pointer :: generate_excitation => null()
procedure(generate_excitation_t), public, pointer :: generate_two_body_excitation => null()
procedure(generate_single_excit_t), public, pointer :: generate_single_excit => null()
procedure(attempt_create_t), public, pointer :: attempt_create => null()
procedure(get_spawn_helement_t), public, pointer :: get_spawn_helement => null()
procedure(get_spawn_helement_t), public, pointer :: get_conn_helement => null()
procedure(encode_child_t), public, pointer :: encode_child => null()
procedure(attempt_die_t), public, pointer :: attempt_die => null()
procedure(extract_bit_rep_avsign_t), public, pointer :: extract_bit_rep_avsign => null()
procedure(fill_rdm_diag_currdet_t), public, pointer :: fill_rdm_diag_currdet => null()
procedure(get_umat_el_t), public, pointer :: get_umat_el => null()
procedure(get_umat_el_t), public, pointer :: get_umat_el_secondary => null()
procedure(scale_function_t), public, pointer :: scaleFunction => null()
procedure(shift_factor_function_t), public, pointer :: shiftFactorFunction => null()
procedure(generate_all_excits_t), public, pointer :: gen_all_excits => null()
procedure(scale_function_t), public, pointer :: shiftScaleFunction => null()

Abstract Interfaces

abstract interface

  • public function attempt_create_t(nI, ilutI, wSign, nJ, ilutJ, prob, HElGen, ic, ex, tPar, exLevel, part_type, AvSignCurr, AvExPerWalker, RDMBiasFacCurr, precond_fac) result(child)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nel)
    integer(kind=n_int), intent(in) :: ilutI(0:NifTot)
    real(kind=dp), intent(in) :: wSign(lenof_sign)
    integer, intent(in) :: nJ(nel)
    integer(kind=n_int), intent(inout) :: ilutJ(0:NifTot)
    real(kind=dp), intent(inout) :: prob
    real(kind=dp), intent(inout) :: HElGen
    integer, intent(in) :: ic
    integer, intent(in) :: ex(2,ic)
    logical, intent(in) :: tPar
    integer, intent(in) :: exLevel
    integer, intent(in) :: part_type
    real(kind=dp), intent(in), dimension(lenof_sign) :: AvSignCurr
    real(kind=dp), intent(in) :: AvExPerWalker
    real(kind=dp), intent(out) :: RDMBiasFacCurr
    real(kind=dp), intent(in) :: precond_fac

    Return Value real(kind=dp), (lenof_sign)

abstract interface

  • public function get_spawn_helement_t(nI, nJ, ilutI, ilutJ, ic, ex, tParity, HElGen) result(hel)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nel)
    integer, intent(in) :: nJ(nel)
    integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
    integer(kind=n_int), intent(in) :: ilutJ(0:NIfTot)
    integer, intent(in) :: ic
    integer, intent(in) :: ex(2,ic)
    logical, intent(in) :: tParity
    real(kind=dp), intent(in) :: HElGen

    Return Value real(kind=dp)

abstract interface

  • public function attempt_die_t(nI, Kii, wSign, exLevel, DetPosition) result(ndie)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nel)
    real(kind=dp), intent(in) :: Kii
    real(kind=dp), intent(in) :: wSign(lenof_sign)
    integer, intent(in) :: exLevel
    integer, intent(in), optional :: DetPosition

    Return Value real(kind=dp), dimension(lenof_sign)

abstract interface

  • public pure function get_umat_el_t(i, j, k, l) result(hel)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    integer, intent(in) :: k
    integer, intent(in) :: l

    Return Value real(kind=dp)

abstract interface

  • public function get_lmat_el_t(a, b, c, i, j, k) result(hel)

    Arguments

    Type IntentOptional Attributes Name
    integer, value :: a
    integer, value :: b
    integer, value :: c
    integer, value :: i
    integer, value :: j
    integer, value :: k

    Return Value real(kind=dp)

abstract interface

  • public pure function scale_function_t(hdiag) result(Si)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: hdiag

    Return Value real(kind=dp)

abstract interface

  • public pure function lMatInd_t(a, b, c, i, j, k) result(index)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in), value :: a
    integer(kind=int64), intent(in), value :: b
    integer(kind=int64), intent(in), value :: c
    integer(kind=int64), intent(in), value :: i
    integer(kind=int64), intent(in), value :: j
    integer(kind=int64), intent(in), value :: k

    Return Value integer(kind=int64)

abstract interface

  • public pure function shift_factor_function_t(pos, run, pop) result(f)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: pos
    integer, intent(in) :: run
    real(kind=dp), intent(in) :: pop

    Return Value real(kind=dp)

abstract interface

  • public subroutine generate_excitation_t(nI, ilutI, nJ, ilutJ, exFlag, ic, ex, tParity, pGen, hel, store, part_type)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nel)
    integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
    integer, intent(out) :: nJ(nel)
    integer(kind=n_int), intent(out) :: ilutJ(0:NifTot)
    integer, intent(in) :: exFlag
    integer, intent(out) :: ic
    integer, intent(out) :: ex(2,maxExcit)
    logical, intent(out) :: tParity
    real(kind=dp), intent(out) :: pGen
    real(kind=dp), intent(out) :: hel
    type(excit_gen_store_type), intent(inout), target :: store
    integer, intent(in), optional :: part_type

abstract interface

  • public subroutine generate_single_excit_t(nI, ilutI, nJ, ilutJ, ex, tpar, store, pGen)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nel)
    integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
    integer, intent(out) :: nJ(nel)
    integer(kind=n_int), intent(out) :: ilutJ(0:NIfTot)
    integer, intent(out) :: ex(2,maxExcit)
    logical, intent(out) :: tpar
    type(excit_gen_store_type), intent(inout), target :: store
    real(kind=dp), intent(out) :: pGen

abstract interface

  • public subroutine encode_child_t(ilutI, ilutJ, ic, ex)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=n_int), intent(in) :: ilutI(0:NifTot)
    integer(kind=n_int), intent(inout) :: ilutJ(0:NIfTot)
    integer, intent(in) :: ic
    integer, intent(in) :: ex(2,ic)

abstract interface

  • public subroutine extract_bit_rep_avsign_t(rdm_defs, ilutI, j, nI, SignI, FlagsI, IterRDMStartI, AvSignI, store)

    Arguments

    Type IntentOptional Attributes Name
    type(rdm_definitions_t), intent(in) :: rdm_defs
    integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
    integer, intent(in) :: j
    integer, intent(out) :: nI(nel)
    real(kind=dp), intent(out) :: SignI(lenof_sign)
    integer, intent(out) :: FlagsI
    real(kind=dp), intent(out) :: IterRDMStartI(len_iter_occ_tot)
    real(kind=dp), intent(out) :: AvSignI(len_av_sgn_tot)
    type(excit_gen_store_type), intent(inout), optional :: store

abstract interface

  • public subroutine fill_rdm_diag_currdet_t(spawn, one_rdms, ilutI, nI, ExcitLevelI, av_sign, iter_occ, tCoreSpaceDet, tLC)

    Arguments

    Type IntentOptional Attributes Name
    type(rdm_spawn_t), intent(inout) :: spawn
    type(one_rdm_t), intent(inout) :: one_rdms(:)
    integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
    integer, intent(in) :: nI(nel)
    integer, intent(in) :: ExcitLevelI
    real(kind=dp), intent(in) :: av_sign(:)
    real(kind=dp), intent(in) :: iter_occ(:)
    logical, intent(in), optional :: tCoreSpaceDet
    logical, intent(in), optional :: tLC

abstract interface

  • public subroutine generate_all_excits_t(nI, n_excits, det_list)

    Generate all excitations for a given determinant in the ilut Format

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nel)
    integer, intent(out) :: n_excits
    integer(kind=n_int), intent(out), allocatable :: det_list(:,:)