unit_test_helpers Module



Contents


Interfaces

public interface run_excit_gen_tester

  • private subroutine run_excit_gen_tester_function(excit_gen, excit_gen_name, opt_nI, opt_n_dets, gen_all_excits, calc_pgen, problem_filter, i_unit, successful)

    @brief Test if an excitation generator generates all and only expected states with the correct pgen.

    @author Werner Dobrautz, Oskar Weser

    @details The pgen_diagnostic is given by \f[\sum_i \frac{1}{p_i N}\f] and should be roughly one. All problematic states with respect to that diagnostic are printed in the end with their pgen_diagnostic, excitation type (ic), matrix element, and pgen. @param[in] excit_gen, An excitation generator. @param[in] excit_gen_name, The name of the excitation generator. @param[in] opt_nI, An optional reference state. @param[in] opt_n_dets, An optional number of valid determinants to generate. Defaults to 100000. (Does not count determinants with nJ(1) == 0!) @param[in] gen_all_excits, An optional subroutine to generate all states that can be reached from the reference state. @param[in] calc_pgen, An optional function that calculates the pgen for a given reference an excitation. If a state is never generated, the pgen cannot be taken from the excitation generator. Adds an additional column to the output table. @param[in] problem_filter, An optional predicate function. Return true, if an excitation exc from determinant det_I and a given pgen_diagnostic (sum 1/pgen) is considered to be problematic. If it returns true, an entry in the final table is printed. If there is any problematic excitation, the out parameter successful will become .false.. By default all states with a pgen_diagnostic that deviate with more than 5\,\% from 100\,\% and have nonzereo matrix element are printed.

    Arguments

    Type IntentOptional Attributes Name
    procedure(generate_excitation_t) :: excit_gen
    character(len=*), intent(in) :: excit_gen_name
    integer, intent(in), optional :: opt_nI(nel)
    integer, intent(in), optional :: opt_n_dets
    procedure(generate_all_excits_t), optional :: gen_all_excits
    procedure(calc_pgen_t), optional :: calc_pgen
    procedure(problem_filter_t), optional :: problem_filter
    integer, intent(in), optional :: i_unit
    logical, intent(out), optional :: successful
  • private subroutine run_excit_gen_tester_class(exc_generator, excit_gen_name, opt_nI, opt_n_dets, problem_filter, i_unit, successful)

    Arguments

    Type IntentOptional Attributes Name
    class(ExcitationGenerator_t), intent(inout) :: exc_generator
    character(len=*), intent(in) :: excit_gen_name
    integer, intent(in), optional :: opt_nI(nel)
    integer, intent(in), optional :: opt_n_dets
    procedure(problem_filter_t), optional :: problem_filter
    integer, intent(in), optional :: i_unit
    logical, intent(out), optional :: successful

Abstract Interfaces

abstract interface

  • private function calc_pgen_t(nI, ilutI, ex, ic, ClassCount2, ClassCountUnocc2)

    Arguments

    Type IntentOptional Attributes Name
    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)

abstract interface

  • private function problem_filter_t(nI, exc, ic, pgen_diagnostic)

    Return true, if an excitation exc from determinant det_I and a given pgen_diagnostic (sum 1/pgen) is considered to be problematic.

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: nI(nEl)
    integer, intent(in) :: exc(2,maxExcit)
    integer, intent(in) :: ic
    real(kind=dp), intent(in) :: pgen_diagnostic

    Return Value logical


Functions

public function create_lattice_hamil_ilut(list_ilut) result(hamil)

Arguments

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

Return Value real(kind=dp), (size(list_ilut,2),size(list_ilut,2))

public function create_lattice_hamil_nI(list_nI) result(hamil)

Arguments

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

Return Value real(kind=dp), (size(list_nI,2),size(list_nI,2))

public function create_spin_dependent_hopping(list_nI, spin_opt) result(hamil)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: list_nI(:,:)
integer, intent(in), optional :: spin_opt

Return Value real(kind=dp), (size(list_nI,2),size(list_nI,2))

public function create_hamiltonian_old(list_nI) result(hamil)

Arguments

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

Return Value real(kind=dp), (size(list_nI,2),size(list_nI,2))

public function similarity_transform(H, t_mat_opt) result(trans_H)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: H(:,:)
real(kind=dp), intent(in), optional :: t_mat_opt(:,:)

Return Value real(kind=dp), (size(H,1),size(H,2))

public function get_tranformation_matrix(hamil, n_pairs) result(t_matrix)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: hamil(:,:)
integer, intent(in) :: n_pairs

Return Value real(kind=dp), (size(hamil,1),size(hamil,2))

public function create_all_spin_flips(nI_in) result(spin_flips)

Arguments

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

Return Value integer, allocatable, (:,:)

private function is_in_list_ilut(tgt_ilut, n_states, ilut_list_in, t_sorted_opt)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int), intent(in) :: tgt_ilut(0:niftot)
integer, intent(in) :: n_states
integer(kind=n_int), intent(in) :: ilut_list_in(0:niftot,n_states)
logical, intent(in), optional :: t_sorted_opt

Return Value logical

private function find_open_shell_indices(nI) result(open_shells)

Arguments

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

Return Value integer, allocatable, (:)


Subroutines

public subroutine setup_arr_brr(in_lat)

Arguments

Type IntentOptional Attributes Name
class(lattice), intent(in) :: in_lat

private subroutine run_excit_gen_tester_function(excit_gen, excit_gen_name, opt_nI, opt_n_dets, gen_all_excits, calc_pgen, problem_filter, i_unit, successful)

@brief Test if an excitation generator generates all and only expected states with the correct pgen.

Read more…

Arguments

Type IntentOptional Attributes Name
procedure(generate_excitation_t) :: excit_gen
character(len=*), intent(in) :: excit_gen_name
integer, intent(in), optional :: opt_nI(nel)
integer, intent(in), optional :: opt_n_dets
procedure(generate_all_excits_t), optional :: gen_all_excits
procedure(calc_pgen_t), optional :: calc_pgen
procedure(problem_filter_t), optional :: problem_filter
integer, intent(in), optional :: i_unit
logical, intent(out), optional :: successful

private subroutine run_excit_gen_tester_class(exc_generator, excit_gen_name, opt_nI, opt_n_dets, problem_filter, i_unit, successful)

Arguments

Type IntentOptional Attributes Name
class(ExcitationGenerator_t), intent(inout) :: exc_generator
character(len=*), intent(in) :: excit_gen_name
integer, intent(in), optional :: opt_nI(nel)
integer, intent(in), optional :: opt_n_dets
procedure(problem_filter_t), optional :: problem_filter
integer, intent(in), optional :: i_unit
logical, intent(out), optional :: successful

public subroutine batch_run_excit_gen_tester(pgen_unit_test_spec)

Arguments

Type IntentOptional Attributes Name
type(PgenUnitTestSpec_t), intent(in) :: pgen_unit_test_spec

public subroutine create_hilbert_space(nI, n_states, state_list_ni, state_list_ilut, gen_all_excits_opt)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nI(nel)
integer, intent(out) :: n_states
integer, intent(out), allocatable :: state_list_ni(:,:)
integer(kind=n_int), intent(out), allocatable :: state_list_ilut(:,:)
procedure(generate_all_excits_t), optional :: gen_all_excits_opt