core_space_t Derived Type

type, public :: core_space_t


Contents

Source Code


Components

Type Visibility Attributes Name Initial
integer(kind=MPIArg), public, allocatable, dimension(:) :: determ_sizes
integer(kind=MPIArg), public, allocatable, dimension(:) :: determ_displs
integer(kind=MPIArg), public, allocatable, dimension(:) :: determ_last
integer(kind=MPIArg), public :: determ_space_size
integer, public :: determ_space_size_int
integer, public, allocatable, dimension(:) :: indices_of_determ_states
integer(kind=n_int), public, pointer, dimension(:, :) :: core_space => null()
integer(kind=n_int), public, pointer, dimension(:, :) :: core_space_direct => null()
integer(kind=MPIArg), public :: core_space_win
type(shared_rhash_t), public :: core_ht
type(sparse_matrix_real), public, allocatable, dimension(:) :: sparse_core_ham
integer(kind=TagIntType), public, allocatable, dimension(:, :) :: SparseCoreHamilTags
real(kind=dp), public, allocatable, dimension(:, :) :: partial_determ_vecs
real(kind=dp), public, allocatable, dimension(:, :) :: full_determ_vecs
real(kind=dp), public, allocatable, dimension(:, :) :: full_determ_vecs_av
integer(kind=TagIntType), public :: FDetermTag
integer(kind=TagIntType), public :: FDetermAvTag
integer(kind=TagIntType), public :: PDetermTag
integer(kind=TagIntType), public :: IDetermTag
integer(kind=TagIntType), public :: CoreSpaceTag
type(sparse_matrix_int), public, allocatable, dimension(:) :: core_connections
real(kind=dp), public, allocatable, dimension(:) :: core_ham_diag
integer, public :: max_run
integer, public :: min_run
logical, public :: t_global

Type-Bound Procedures

procedure, public, :: alloc_wf

  • private subroutine alloc_wf(this)

    Arguments

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

procedure, public, :: associate_run

  • private subroutine associate_run(this, t_global, run)

    Arguments

    Type IntentOptional Attributes Name
    class(core_space_t), intent(inout) :: this
    logical, intent(in) :: t_global
    integer, intent(in) :: run

procedure, public, :: dealloc

  • private subroutine dealloc(this)

    Arguments

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

procedure, public, :: max_part

  • private pure function max_part(this) result(ir)

    Arguments

    Type IntentOptional Attributes Name
    class(core_space_t), intent(in) :: this

    Return Value integer

procedure, public, :: min_part

  • private pure function min_part(this) result(ir)

    Arguments

    Type IntentOptional Attributes Name
    class(core_space_t), intent(in) :: this

    Return Value integer

procedure, public, :: first_run

  • private pure function first_run(this) result(ir)

    Arguments

    Type IntentOptional Attributes Name
    class(core_space_t), intent(in) :: this

    Return Value integer

procedure, public, :: last_run

  • private pure function last_run(this) result(ir)

    Arguments

    Type IntentOptional Attributes Name
    class(core_space_t), intent(in) :: this

    Return Value integer

Source Code

    type :: core_space_t
        ! determ_sizes(i) holds the core space size on processor i.
        integer(MPIArg), allocatable, dimension(:) :: determ_sizes
        ! determ_displs(i) holds sum(determ_sizes(i-1)), that is, the
        ! total number of core states on all processors up to processor i.
        ! (determ_displs(1) == 0).
        integer(MPIArg), allocatable, dimension(:) :: determ_displs
        ! determ_last(i) holds the final index belonging process i.
        integer(MPIArg), allocatable, dimension(:) :: determ_last
        ! The total size of the core space on all processors.
        integer(MPIArg) :: determ_space_size
        ! determ_space_size_int is identical to determ_space_size, but converted
        ! to the default integer kind.
        integer :: determ_space_size_int
        ! This vector will store the indicies of the deterministic states in CurrentDets. This is worked out in the main loop.
        integer, allocatable, dimension(:) :: indices_of_determ_states

        ! This stores the entire core space from all processes, on each process.
        integer(n_int), pointer, dimension(:, :) :: core_space => null()
        integer(n_int), pointer, dimension(:, :) :: core_space_direct => null()
        integer(MPIArg) :: core_space_win

        type(shared_rhash_t) :: core_ht

        ! The core Hamiltonian for semi-stochastiic simulations.
        type(sparse_matrix_real), allocatable, dimension(:) :: sparse_core_ham
        integer(TagIntType), allocatable, dimension(:, :) :: SparseCoreHamilTags
        ! This stores all the amplitudes of the walkers in the deterministic space. This vector has the size of the part
        ! of the deterministic space stored on *this* processor only. It is therefore used to store the deterministic vector
        ! on this processor, before it is combined to give the whole vector, which is stored in full_determ_vecs.
        ! Later in the iteration, it is also used to store the result of the multiplication by the core Hamiltonian on
        ! full_determ_vecs.
        real(dp), allocatable, dimension(:, :) :: partial_determ_vecs
        real(dp), allocatable, dimension(:, :) :: full_determ_vecs
        real(dp), allocatable, dimension(:, :) :: full_determ_vecs_av
        integer(TagIntType) :: FDetermTag, FDetermAvTag, PDetermTag, IDetermTag, CoreSpaceTag
        ! Stores the parities for all connected pairs of states in the core space.
        type(sparse_matrix_int), allocatable, dimension(:) :: core_connections

        ! The diagonal elements of the core-space Hamiltonian (with Hii taken away).
        real(dp), allocatable, dimension(:) :: core_ham_diag

        ! ilut Sign range in which this core space operates
        integer :: max_run, min_run

        ! Is this a global core space?
        logical :: t_global
    contains
        procedure :: alloc_wf
        procedure :: associate_run
        procedure :: dealloc

        procedure :: max_part
        procedure :: min_part

        procedure :: first_run
        procedure :: last_run
    end type core_space_t