global_det_data Module



Contents


Variables

Type Visibility Attributes Name Initial
integer, private :: glob_tag = 0
integer, private :: glob_det_tag = 0
integer, private :: glob_tmp_tag = 0
integer, private, parameter :: pos_hel = 1
integer, private, parameter :: len_hel = 1
integer, private :: pos_hel_off
integer, private :: len_hel_off
integer, private :: pos_sg_idx
integer, private, parameter :: len_sg_idx = 1
integer, private :: pos_spawn_pop
integer, private :: len_spawn_pop
integer, private :: pos_tau_int
integer, private :: len_tau_int
integer, private :: pos_shift_int
integer, private :: len_shift_int
integer, private :: len_tot_spawns
integer, private :: len_acc_spawns
integer, public :: pos_tot_spawns
integer, public :: pos_acc_spawns
integer, public :: fvals_size
integer, private :: len_pops_sum
integer, private :: len_pops_iter
integer, private :: pos_pops_sum
integer, private :: pos_pops_iter
integer, public :: apvals_size
integer, private :: pos_av_sgn
integer, private :: len_av_sgn
integer, private :: pos_iter_occ
integer, private :: len_iter_occ
integer, private :: pos_av_sgn_transition
integer, private :: len_av_sgn_transition
integer, private :: pos_iter_occ_transition
integer, private :: len_iter_occ_transition
integer, public :: len_av_sgn_tot
integer, public :: len_iter_occ_tot
integer, private :: pos_spawn_rate
integer, private :: len_spawn_rate
integer, private :: len_pos_spawns
integer, private :: len_neg_spawns
integer, private :: pos_pos_spawns
integer, private :: pos_neg_spawns
integer, private :: len_det_orbs
integer, private :: pos_max_ratio
integer, private :: len_max_ratio
integer, public :: max_ratio_size
integer, public :: replica_est_len
real(kind=dp), public, pointer :: global_determinant_data(:,:) => null()
integer, private, pointer :: global_determinants(:,:) => null()
real(kind=dp), public, pointer :: global_determinant_data_tmp(:,:) => null()

Interfaces

public interface set_av_sgn_tot

  • private subroutine set_av_sgn_tot_sgl(j, part, av_sgn)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: j
    integer, intent(in) :: part
    real(kind=dp), intent(in) :: av_sgn
  • private subroutine set_av_sgn_tot_all(j, av_sgn)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: j
    real(kind=dp), intent(in) :: av_sgn(len_av_sgn_tot)

public interface set_iter_occ_tot

  • private subroutine set_iter_occ_tot_sgl(j, part, iter_occ)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: j
    integer, intent(in) :: part
    real(kind=dp), intent(in) :: iter_occ
  • private subroutine set_iter_occ_tot_all(j, iter_occ)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: j
    real(kind=dp), intent(in) :: iter_occ(len_iter_occ_tot)

public interface get_av_sgn_tot

  • private function get_av_sgn_tot_sgl(j, part) result(av_sgn)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: j
    integer, intent(in) :: part

    Return Value real(kind=dp)

  • private function get_av_sgn_tot_all(j) result(av_sgn)

    Arguments

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

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

public interface get_iter_occ_tot

  • private function get_iter_occ_tot_sgl(j, part) result(iter_occ)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: j
    integer, intent(in) :: part

    Return Value real(kind=dp)

  • private function get_iter_occ_tot_all(j) result(iter_occ)

    Arguments

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

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


Functions

public function det_diagH(j) result(hel_r)

Arguments

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

Return Value real(kind=dp)

public function det_offdiagH(j) result(hel)

Arguments

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

Return Value real(kind=dp)

public pure function get_supergroup_idx(j) result(sg_idx)

Arguments

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

Return Value integer

public function get_spawn_pop(j, part) result(t)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: part

Return Value real(kind=dp)

public function get_all_spawn_pops(j) result(t)

Arguments

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

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

public function get_tau_int(j, run) result(t)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: run

Return Value real(kind=dp)

public function get_shift_int(j, run) result(t)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: run

Return Value real(kind=dp)

public pure function get_tot_spawns(j, run) result(t)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: run

Return Value real(kind=dp)

public pure function get_acc_spawns(j, run) result(t)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: run

Return Value real(kind=dp)

private pure function get_pops_sum(j, part) result(AccSign)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: part

Return Value real(kind=dp)

public pure function get_pops_sum_full(j) result(AccSign)

Arguments

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

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

public pure function get_pops_iter(j) result(iter)

Arguments

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

Return Value real(kind=dp)

private function get_av_sgn_tot_sgl(j, part) result(av_sgn)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: part

Return Value real(kind=dp)

private function get_av_sgn_tot_all(j) result(av_sgn)

Arguments

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

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

private function get_iter_occ_tot_sgl(j, part) result(iter_occ)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: part

Return Value real(kind=dp)

private function get_iter_occ_tot_all(j) result(iter_occ)

Arguments

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

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

public function get_spawn_rate(j) result(rate)

Arguments

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

Return Value real(kind=dp)

public pure function get_pos_spawns(j) result(avSpawn)

Arguments

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

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

public pure function get_neg_spawns(j) result(avSpawn)

Arguments

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

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

public function get_max_ratio(j) result(maxSpawn)

Arguments

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

Return Value real(kind=dp)

public function get_determinant(j) result(nI)

Arguments

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

Return Value integer, (nel)


Subroutines

public subroutine init_global_det_data(nrdms_standard, nrdms_transition)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nrdms_standard
integer, intent(in) :: nrdms_transition

public subroutine clean_global_det_data()

Arguments

None

public subroutine set_det_diagH(j, hel_r)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
real(kind=dp), intent(in) :: hel_r

public subroutine set_det_offdiagH(j, hel)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
real(kind=dp), intent(in) :: hel

public subroutine set_supergroup_idx(j, sg_idx)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: sg_idx

public subroutine set_spawn_pop(j, part, t)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: part
real(kind=dp), intent(in) :: t

public subroutine set_all_spawn_pops(j, t)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
real(kind=dp), intent(in), dimension(lenof_sign) :: t

public subroutine reset_all_tau_ints(j)

Arguments

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

public subroutine reset_tau_int(j, run)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: run

public subroutine update_tau_int(j, run, t)

Arguments

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

public subroutine reset_all_shift_ints(j)

Arguments

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

public subroutine reset_shift_int(j, run)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: run

public subroutine update_shift_int(j, run, t)

Arguments

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

public subroutine reset_all_tot_spawns(j)

Arguments

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

public subroutine update_tot_spawns(j, run, t)

Arguments

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

public subroutine readFVals(fvals, ndets, initial)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: fvals(2*inum_runs,ndets)
integer, intent(in) :: ndets
integer, intent(in), optional :: initial

public subroutine readFValsAsInt(fvals, j)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: fvals(:)
integer, intent(in) :: j

public subroutine writeFValsAsInt(fvals, j)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(inout) :: fvals(:)
integer, intent(in) :: j

public subroutine writeFVals(fvals, ndets, initial)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout) :: fvals(:,:)
integer, intent(in) :: ndets
integer, intent(in), optional :: initial

public subroutine reset_all_acc_spawns(j)

Arguments

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

public subroutine update_acc_spawns(j, run, t)

Arguments

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

public subroutine update_pops_sum_all(ndets, iter)

Arguments

Type IntentOptional Attributes Name
integer(kind=int64), intent(in) :: ndets
integer, intent(in) :: iter

public subroutine writeAPValsAsInt(apvals, j)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(inout) :: apvals(:)
integer, intent(in) :: j

public subroutine readAPValsAsInt(apvals, j)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: apvals(:)
integer, intent(in) :: j

public subroutine readAPVals(apvals, ndets, initial)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: apvals(lenof_sign+1,ndets)
integer, intent(in) :: ndets
integer, intent(in), optional :: initial

public subroutine writeAPVals(apvals, ndets, initial)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout) :: apvals(:,:)
integer, intent(in) :: ndets
integer, intent(in), optional :: initial

private subroutine set_av_sgn_tot_sgl(j, part, av_sgn)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: part
real(kind=dp), intent(in) :: av_sgn

private subroutine set_av_sgn_tot_all(j, av_sgn)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
real(kind=dp), intent(in) :: av_sgn(len_av_sgn_tot)

private subroutine set_iter_occ_tot_sgl(j, part, iter_occ)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
integer, intent(in) :: part
real(kind=dp), intent(in) :: iter_occ

private subroutine set_iter_occ_tot_all(j, iter_occ)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
real(kind=dp), intent(in) :: iter_occ(len_iter_occ_tot)

public subroutine set_spawn_rate(j, rate)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
real(kind=dp), intent(in) :: rate

public subroutine store_spawn(j, spawn_sgn)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: j
real(kind=dp), intent(in) :: spawn_sgn(lenof_sign)

public subroutine update_max_ratio(spawn, j)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: spawn
integer, intent(in) :: j

public subroutine set_max_ratio(val, j)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: val
integer, intent(in) :: j

public subroutine write_max_ratio(ms_vals, ndets, initial)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(out) :: ms_vals(:,:)
integer, intent(in) :: ndets
integer, intent(in), optional :: initial

public subroutine set_all_max_ratios(ms_vals, ndets, initial)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: ms_vals(:,:)
integer, intent(in) :: ndets
integer, intent(in), optional :: initial

public subroutine set_max_ratio_hdf5Int(val, j)

Arguments

Type IntentOptional Attributes Name
integer(kind=hsize_t), intent(in) :: val(:)
integer, intent(in) :: j

public subroutine write_max_ratio_as_int(ms_vals, pos)

Arguments

Type IntentOptional Attributes Name
integer(kind=hsize_t), intent(out) :: ms_vals(:)
integer, intent(in) :: pos

public subroutine store_decoding(j, nI)

Arguments

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