guga_matrixElements Module



Contents


Abstract Interfaces

abstract interface

  • private function branch_weight_function(weight, bval, negSwitches, posSwitches) result(prob)

    Arguments

    Type IntentOptional Attributes Name
    type(WeightObj_t), intent(in) :: weight
    real(kind=dp), intent(in) :: bval
    real(kind=dp), intent(in) :: negSwitches
    real(kind=dp), intent(in) :: posSwitches

    Return Value real(kind=dp)


Derived Types

type, private ::  BranchWeightArr_t

Components

Type Visibility Attributes Name Initial
procedure(branch_weight_function), public, pointer, nopass :: ptr => null()

Functions

public pure function calcDiagMatEleGuga_nI(nI) result(hel_ret)

Arguments

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

Return Value real(kind=dp)

public pure function calcDiagMatEleGuga_ilut(ilut) result(hElement)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:niftot)

Return Value real(kind=dp)

public pure function calcDiagExchangeGUGA_nI(iOrb, jOrb, nI) result(exchange)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: iOrb
integer, intent(in) :: jOrb
integer, intent(in) :: nI(nEl)

Return Value real(kind=dp)

private elemental function functionA(bValue, x, y) result(r)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: bValue
real(kind=dp), intent(in) :: x
real(kind=dp), intent(in) :: y

Return Value real(kind=dp)

public function calcStartProb(prob1, prob2) result(ret)

Arguments

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

Return Value real(kind=dp)

public function calcStayingProb(prob1, prob2, bVal) result(ret)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: prob1
real(kind=dp), intent(in) :: prob2
real(kind=dp), intent(in) :: bVal

Return Value real(kind=dp)

public function init_fullStartWeight(csf_i, sOrb, pOrb, negSwitches, posSwitches, bVal) result(fullStart)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
integer, intent(in) :: sOrb
integer, intent(in) :: pOrb
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches
real(kind=dp), intent(in) :: bVal

Return Value type(WeightObj_t)

public elemental function endFx(csf_i, sOrb) result(fx)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
integer, intent(in) :: sOrb

Return Value real(kind=dp)

public elemental function endGx(csf_i, sOrb) result(gx)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
integer, intent(in) :: sOrb

Return Value real(kind=dp)

public elemental function init_singleWeight(csf_i, sOrb) result(singleWeight)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
integer, intent(in) :: sOrb

Return Value type(WeightObj_t)

private function getMinus_fullStart(nSwitches, bVal, fullStart) result(minusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: fullStart

Return Value real(kind=dp)

private function getPlus_fullStart(nSwitches, bVal, fullStart) result(plusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: fullStart

Return Value real(kind=dp)

private function getMinus_single(nSwitches, bVal, single) result(minusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: single

Return Value real(kind=dp)

private function getPlus_single(nSwitches, bVal, single) result(plusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: single

Return Value real(kind=dp)

private function plus_start_single(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function minus_start_single(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function minus_staying_single(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function plus_staying_single(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function plus_switching_single(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function minus_switching_single(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function minus_start_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function plus_start_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function zero_plus_start_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function zero_minus_start_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function zero_plus_staying_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function zero_minus_staying_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function zero_plus_switching_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function zero_minus_switching_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function minus_staying_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function plus_staying_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function minus_switching_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function plus_switching_double(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function probability_one(weights, bVal, negSwitches, posSwitches) result(prob)

Arguments

Type IntentOptional Attributes Name
type(WeightObj_t), intent(in) :: weights
real(kind=dp), intent(in) :: bVal
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches

Return Value real(kind=dp)

private function getZero_fullStart(negSwitches, posSwitches, bVal, fullStart) result(zeroWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: fullStart

Return Value real(kind=dp)

public function init_semiStartWeight(csf_i, sOrb, pOrb, negSwitches, posSwitches, bVal) result(semiStart)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
integer, intent(in) :: sOrb
integer, intent(in) :: pOrb
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches
real(kind=dp), intent(in) :: bVal

Return Value type(WeightObj_t)

public function init_doubleWeight(csf_i, sOrb) result(doubleWeight)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
integer, intent(in) :: sOrb

Return Value type(WeightObj_t)

public function getMinus_double(nSwitches, bVal, double) result(minusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: double

Return Value real(kind=dp)

public function getPlus_double(nSwitches, bVal, double) result(plusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: double

Return Value real(kind=dp)

public function get_forced_zero_double(negSwitches, posSwitches, bVal, double) result(zeroWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: double

Return Value real(kind=dp)

private function getZero_double(negSwitches, posSwitches, bVal, double) result(zeroWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: negSwitches
real(kind=dp), intent(in) :: posSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: double

Return Value real(kind=dp)

public function getMinus_semiStart(nSwitches, bVal, semiStart) result(minusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: semiStart

Return Value real(kind=dp)

public function getPlus_semiStart(nSwitches, bVal, semiStart) result(plusWeight)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: nSwitches
real(kind=dp), intent(in) :: bVal
type(WeightData_t), intent(in) :: semiStart

Return Value real(kind=dp)


Subroutines

public pure subroutine calc_guga_matrix_element(ilutI, csf_i, ilutJ, csf_j, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilutI(0:niftot)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: ilutJ(0:niftot)
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(out) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in) :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_single_excitation_ex(csf_i, csf_j, excitInfo, mat_ele, t_calc_full, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_calc_full
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_single_overlap_mixed_ex(csf_i, csf_j, excitInfo, mat_ele, t_calc_full, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_calc_full
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_normal_double_ex(csf_i, csf_j, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_fullstop_alike_ex(csf_i, csf_j, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_fullstart_alike_ex(csf_i, csf_j, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_fullstart_fullstop_alike_ex(csf_i, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_fullstop_mixed_ex(ilutI, csf_i, ilutJ, csf_j, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilutI(0:niftot)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: ilutJ(0:niftot)
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(inout) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_fullstart_mixed_ex(ilutI, csf_i, ilutJ, csf_j, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilutI(0:niftot)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: ilutJ(0:niftot)
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(inout) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

private pure subroutine calc_fullstart_fullstop_mixed_ex(ilutI, csf_i, ilutJ, csf_j, excitInfo, mat_ele, t_hamil, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilutI(0:niftot)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: ilutJ(0:niftot)
type(CSF_Info_t), intent(in) :: csf_j
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: mat_ele
logical, intent(in), optional :: t_hamil
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

public pure subroutine calc_integral_contribution_single(csf_i, csf_j, i, j, st, en, integral)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(CSF_Info_t), intent(in) :: csf_j
integer, intent(in) :: i
integer, intent(in) :: j
integer, intent(in) :: st
integer, intent(in) :: en
real(kind=dp), intent(inout) :: integral

public pure subroutine calc_mixed_start_contr_integral(ilut, csf_i, t, excitInfo, integral, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), intent(in), value :: excitInfo
real(kind=dp), intent(out) :: integral
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

public subroutine calc_mixed_start_contr_pgen(ilut, csf_i, t, excitInfo, branch_pgen, pgen)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), value :: excitInfo
real(kind=dp), value :: branch_pgen
real(kind=dp), intent(out) :: pgen

public subroutine calc_mixed_start_contr_sym(ilut, csf_i, t, excitInfo, branch_pgen, pgen, integral, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), intent(inout) :: excitInfo
real(kind=dp), intent(inout) :: branch_pgen
real(kind=dp), intent(out) :: pgen
real(kind=dp), intent(out) :: integral
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

public subroutine calc_mixed_end_contr_sym(ilut, csf_i, t, excitInfo, branch_pgen, pgen, integral, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), intent(inout) :: excitInfo
real(kind=dp), intent(inout) :: branch_pgen
real(kind=dp), intent(out) :: pgen
real(kind=dp), intent(out) :: integral
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

public subroutine calc_mixed_end_contr_pgen(ilut, csf_i, t, excitInfo, branch_pgen, pgen)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), value :: excitInfo
real(kind=dp), value :: branch_pgen
real(kind=dp), intent(out) :: pgen

public pure subroutine calc_mixed_end_contr_integral(ilut, csf_i, t, excitInfo, integral, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), intent(inout) :: excitInfo
real(kind=dp), intent(out) :: integral
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

public subroutine calc_mixed_contr_sym(ilut, csf_i, t, excitInfo, pgen, integral)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), intent(inout) :: excitInfo
real(kind=dp), intent(out) :: pgen
real(kind=dp), intent(out) :: integral

public pure subroutine calc_mixed_contr_integral(ilut, csf_i, t, start, ende, integral, rdm_ind, rdm_mat)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
integer, intent(in) :: start
integer, intent(in) :: ende
real(kind=dp), intent(out) :: integral
integer(kind=int_rdm), intent(out), optional, allocatable :: rdm_ind(:)
real(kind=dp), intent(out), optional, allocatable :: rdm_mat(:)

public subroutine calc_mixed_contr_pgen(ilut, csf_i, t, excitInfo, pgen)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: ilut(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(ExcitationInformation_t), value :: excitInfo
real(kind=dp), intent(out) :: pgen

public subroutine calcRemainingSwitches_excitInfo_double(csf_i, excitInfo, posSwitches, negSwitches)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: posSwitches(nSpatOrbs)
real(kind=dp), intent(out) :: negSwitches(nSpatOrbs)

public subroutine calcRemainingSwitches_excitInfo_single(csf_i, excitInfo, posSwitches, negSwitches)

Arguments

Type IntentOptional Attributes Name
type(CSF_Info_t), intent(in) :: csf_i
type(ExcitationInformation_t), intent(in) :: excitInfo
real(kind=dp), intent(out) :: posSwitches(nSpatOrbs)
real(kind=dp), intent(out) :: negSwitches(nSpatOrbs)

private subroutine setup_weight_funcs(t, csf_i, st, se, weight_funcs)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: t(0:nifguga)
type(CSF_Info_t), intent(in) :: csf_i
integer, intent(in) :: st
integer, intent(in) :: se
type(BranchWeightArr_t), intent(out) :: weight_funcs(nSpatOrbs)