gasci_disconnected Module



Contents


Variables

Type Visibility Attributes Name Initial
integer, private, parameter :: idx_alpha = 1
integer, private, parameter :: idx_beta = 2
integer(kind=n_int), private, parameter :: oddBits = 6148914691236517205_n_int

Interfaces

private interface get_cumulative_list

  • private function get_cumulative_list_Excite_1_t(GAS_list, nI, incomplete_exc) result(cSum)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: GAS_list(:)
    integer, intent(in) :: nI(nel)
    type(Excite_1_t), intent(in) :: incomplete_exc

    Return Value real(kind=dp), (size(GAS_list))

  • private function get_cumulative_list_Excite_2_t(GAS_list, nI, incomplete_exc) result(cSum)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: GAS_list(:)
    integer, intent(in) :: nI(nel)
    type(Excite_2_t), intent(in) :: incomplete_exc

    Return Value real(kind=dp), (size(GAS_list))

private interface get_mat_element

  • private function get_mat_element_Excite_1_t(nI, exc) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nEl)
    type(Excite_1_t), intent(in) :: exc

    Return Value real(kind=dp)

  • private function get_mat_element_Excite_2_t(nI, exc) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nEl)
    type(Excite_2_t), intent(in) :: exc

    Return Value real(kind=dp)

public interface GAS_disc_ExcGenerator_t


Derived Types

type, public, extends(ExcitationGenerator_t) ::  GAS_disc_ExcGenerator_t

Components

Type Visibility Attributes Name Initial
class(GASSpec_t), private, allocatable :: GAS_spec
integer(kind=n_int), private, allocatable :: GAS_orbs(:,:)

Bitmasks containing the active spaces (stored in the same format as an ilut) also have spin-resolved bitmasks The index of GAS_orbs is [0:NIfD, 1:nGAS] Spin resolved version of GAS_orbs. The index is [0:NIfD, 1:nGAS, {idx_alpha, idx_beta}]

integer(kind=n_int), private, allocatable :: GAS_spin_orbs(:,:,:)

Bitmasks containing the active spaces (stored in the same format as an ilut) also have spin-resolved bitmasks The index of GAS_orbs is [0:NIfD, 1:nGAS] Spin resolved version of GAS_orbs. The index is [0:NIfD, 1:nGAS, {idx_alpha, idx_beta}]

integer, private, allocatable :: GAS_spin_orb_list(:,:,:)

Integer list of spin-orbitals for each GAS space, that contains in continous order the occupied orbitals. The index is [i-th occupied orbital in given GAS space, 1:nGAS, {idx_alpha, idx_beta}]. Note that a meaningful index is only [1:GAS_size(iGAS), iGAS, :] Number of orbitals in each GAS space. Lookup table containing the GAS space for each orbital.

integer, private, allocatable :: GAS_size(:)

Integer list of spin-orbitals for each GAS space, that contains in continous order the occupied orbitals. The index is [i-th occupied orbital in given GAS space, 1:nGAS, {idx_alpha, idx_beta}]. Note that a meaningful index is only [1:GAS_size(iGAS), iGAS, :] Number of orbitals in each GAS space. Lookup table containing the GAS space for each orbital.

integer, private, allocatable :: GAS_table(:)

Integer list of spin-orbitals for each GAS space, that contains in continous order the occupied orbitals. The index is [i-th occupied orbital in given GAS space, 1:nGAS, {idx_alpha, idx_beta}]. Note that a meaningful index is only [1:GAS_size(iGAS), iGAS, :] Number of orbitals in each GAS space. Lookup table containing the GAS space for each orbital.

Constructor

private pure function construct_GAS_disc_ExcGenerator_t (GAS_spec)

Type-Bound Procedures

procedure , public :: finalize => GAS_disc_finalize Subroutine
procedure , public :: gen_exc => GAS_disc_gen_exc Subroutine
procedure , public :: get_pgen => GAS_disc_get_pgen Function
procedure , public :: gen_all_excits => GAS_disc_gen_all_excits Subroutine
procedure , public :: generate_nGAS_single Subroutine
procedure , public :: generate_nGAS_double Subroutine
procedure , private , :: pick_hole_from_active_space Function
procedure , private , :: get_pgen_pick_weighted_hole Function
procedure , private , :: get_pgen_pick_hole_from_active_space Function
procedure , private , :: pick_weighted_hole_Excite_1_t Function
generic, private , :: pick_weighted_hole => pick_weighted_hole_Excite_1_t
procedure , private , :: calc_pgen_Excite_1_t Function
generic, private , :: calc_pgen => calc_pgen_Excite_1_t
procedure , private , :: pick_weighted_hole_Excite_2_t Function
generic, private , :: pick_weighted_hole => pick_weighted_hole_Excite_2_t
procedure , private , :: calc_pgen_Excite_2_t Function
generic, private , :: calc_pgen => calc_pgen_Excite_2_t

Functions

private pure function construct_GAS_disc_ExcGenerator_t(GAS_spec) result(res)

Arguments

Type IntentOptional Attributes Name
class(GASSpec_t), intent(in) :: GAS_spec

Return Value type(GAS_disc_ExcGenerator_t)

private function GAS_disc_get_pgen(this, nI, ilutI, ex, ic, ClassCount2, ClassCountUnocc2) result(pgen)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(inout) :: this
integer, intent(in) :: nI(nEl)
integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
integer, intent(in) :: ex(2,maxExcit)
integer, intent(in) :: ic
integer, intent(in) :: ClassCount2(ScratchSize)
integer, intent(in) :: ClassCountUnocc2(ScratchSize)

Return Value real(kind=dp)

private function get_pgen_pick_weighted_hole(this, nI, exc) result(pgenVal)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
integer, intent(in) :: nI(nel)
type(Excite_2_t), intent(in) :: exc

Return Value real(kind=dp)

private function get_pgen_pick_hole_from_active_space(this, ilut, srcGASInd, spin_idx) result(pgenVal)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
integer(kind=n_int), intent(in) :: ilut(0:NIfD)
integer, intent(in) :: srcGASInd
integer, intent(in) :: spin_idx

Return Value real(kind=dp)

private function get_cumulative_list_Excite_1_t(GAS_list, nI, incomplete_exc) result(cSum)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: GAS_list(:)
integer, intent(in) :: nI(nel)
type(Excite_1_t), intent(in) :: incomplete_exc

Return Value real(kind=dp), (size(GAS_list))

private function get_cumulative_list_Excite_2_t(GAS_list, nI, incomplete_exc) result(cSum)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: GAS_list(:)
integer, intent(in) :: nI(nel)
type(Excite_2_t), intent(in) :: incomplete_exc

Return Value real(kind=dp), (size(GAS_list))

private function get_mat_element_Excite_1_t(nI, exc) result(res)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nI(nEl)
type(Excite_1_t), intent(in) :: exc

Return Value real(kind=dp)

private function get_mat_element_Excite_2_t(nI, exc) result(res)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nI(nEl)
type(Excite_2_t), intent(in) :: exc

Return Value real(kind=dp)

private function pick_weighted_hole_Excite_1_t(this, nI, exc, spin_idx, iGAS, pgen) result(tgt)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
integer, intent(in) :: nI(nel)
type(Excite_1_t), intent(in) :: exc
integer, intent(in) :: spin_idx
integer, intent(in) :: iGAS
real(kind=dp), intent(inout) :: pgen

Return Value integer

private function pick_weighted_hole_Excite_2_t(this, nI, exc, spin_idx, iGAS, pgen) result(tgt)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
integer, intent(in) :: nI(nel)
type(Excite_2_t), intent(in) :: exc
integer, intent(in) :: spin_idx
integer, intent(in) :: iGAS
real(kind=dp), intent(inout) :: pgen

Return Value integer

private function pick_hole_from_active_space(this, ilutI, nI, iGAS, ms, r, pgen) result(tgt)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
integer(kind=n_int), intent(in) :: ilutI(0:NIfD)
integer, intent(in) :: nI(nel)
integer, intent(in) :: iGAS
integer, intent(in) :: ms
real(kind=dp), intent(in) :: r
real(kind=dp), intent(out) :: pgen

Return Value integer

private function calc_pgen_Excite_1_t(this, det_I, ilutI, exc) result(pgen)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
type(SpinOrbIdx_t), intent(in) :: det_I
integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
type(Excite_1_t), intent(in) :: exc

Return Value real(kind=dp)

private function calc_pgen_Excite_2_t(this, det_I, ilutI, exc) result(pgen)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
type(SpinOrbIdx_t), intent(in) :: det_I
integer(kind=n_int), intent(in) :: ilutI(0:NIfTot)
type(Excite_2_t), intent(in) :: exc

Return Value real(kind=dp)


Subroutines

private subroutine GAS_disc_finalize(this)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(inout) :: this

private subroutine GAS_disc_gen_exc(this, nI, ilutI, nJ, ilutJ, exFlag, ic, ex, tParity, pGen, hel, store, part_type)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(inout) :: this
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

private subroutine GAS_disc_gen_all_excits(this, nI, n_excits, det_list)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
integer, intent(in) :: nI(nEl)
integer, intent(out) :: n_excits
integer(kind=n_int), intent(out), allocatable :: det_list(:,:)

private subroutine generate_nGAS_single(this, nI, ilutI, nJ, ilutJ, ex, par, pgen)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
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,2)
logical, intent(out) :: par
real(kind=dp), intent(out) :: pgen

private subroutine generate_nGAS_double(this, nI, ilutI, nJ, ilutJ, ex, par, pgen)

Arguments

Type IntentOptional Attributes Name
class(GAS_disc_ExcGenerator_t), intent(in) :: this
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,2)
logical, intent(out) :: par
real(kind=dp), intent(out) :: pgen