generate_connected_space_normal Subroutine

public subroutine generate_connected_space_normal(original_space_size, original_space, connected_space_size, connected_space, tSinglesOnlyOpt)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: original_space_size
integer(kind=n_int), intent(in) :: original_space(0:,:)
integer, intent(inout) :: connected_space_size
integer(kind=n_int), intent(out), optional :: connected_space(0:,:)
logical, intent(in), optional :: tSinglesOnlyOpt

Contents


Source Code

    subroutine generate_connected_space_normal(original_space_size, original_space, &
                                               connected_space_size, connected_space, tSinglesOnlyOpt)

        use Symexcit4, only: NewParentDet
        ! This routine either counts or generates all the determinants connected to those in
        ! original_space. If connected_space is not present then they will only be counted,
        ! else they will be stored in connected_space. If tSinglesOnlyOpt is present and
        ! also .true. then actually this routine will only generate all single excitations
        ! (regardless of the system being studied), otherwise it will generate all connected
        ! determinants.

        use guga_bitRepOps, only: convert_ilut_toGUGA, convert_ilut_toNECI
        use guga_excitations, only: actHamiltonian
        use SystemData, only: tGUGA
        integer :: nexcit, j
        integer(n_int), allocatable :: excitations(:, :)
        integer(n_int) :: ilutG(0:nifguga)

        integer, intent(in) :: original_space_size
        integer(n_int), intent(in) :: original_space(0:, :)
        integer, intent(inout) :: connected_space_size
        integer(n_int), optional, intent(out) :: connected_space(0:, :)
        logical, intent(in), optional :: tSinglesOnlyOpt
        character(*), parameter :: this_routine = "generate_connection_normal"

        integer(n_int) :: ilutJ(0:NIfTot)
        integer :: nI(nel), nJ(nel)
        integer :: i, excit(2, 2), ex_flag
        integer, allocatable :: excit_gen(:)
        integer :: nStore(6)
        logical :: tAllExcitFound, tStoreConnSpace, tSinglesOnly, tTempUseBrill
        integer :: n_excits
        integer(n_int), allocatable :: temp_dets(:, :)

        if (present(connected_space)) then
            tStoreConnSpace = .true.
        else
            tStoreConnSpace = .false.
        end if

        tSinglesOnly = .false.
        if (present(tSinglesOnlyOpt)) then
            if (tSinglesOnlyOpt) tSinglesOnly = .true.
        end if

        connected_space_size = 0

        ! Over all the states in the original list:
        do i = 1, original_space_size

            call decode_bit_det(nI, original_space(0:NIfTot, i))

            ! do the GUGA changes here, I want to do all the excitations from
            ! the currently looped over original_space(:,i)
            ! i think i still want to do this this way, since the dets
            ! implementation is really akward..
            if (tGUGA) then
                ! in GUGA don't do the tSinglesOnly option
                ASSERT(.not. tSinglesOnly)

                ! only STORE the excitations if the proper flag is set,
                ! otherwise only, increase the counter for the connected space
                ! why is this done??
                call convert_ilut_toGUGA(original_space(:, i), ilutG)

                call actHamiltonian(ilutG, CSF_Info_t(ilutG), excitations, nexcit)

                ! and if store flag is present:
                if (tStoreConnSpace) then
                    do j = 1, nexcit
                        call convert_ilut_toNECI(excitations(:, j), &
                                                 connected_space(:, connected_space_size + j))
                    end do
                end if

                ! update connected_space_size afterwards
                connected_space_size = connected_space_size + nexcit

                deallocate(excitations)
                call LogMemDealloc(this_routine, tag_excitations)

            else
                if (t_new_real_space_hubbard) then

#ifdef CMPLX_
                    call stop_all(this_routine, "not implemented for complex")
#else
                    call gen_all_excits_r_space_hubbard(nI, n_excits, temp_dets)
#endif

                    if (tStoreConnSpace) then
                        connected_space(0:nifd, connected_space_size + 1:connected_space_size + n_excits) &
                            = temp_dets(0:nifd, :)
                    end if

                    connected_space_size = connected_space_size + n_excits

                else

                    call NewParentDet(session)

                    call init_generate_connected_space(nI, ex_flag, tAllExcitFound, excit, excit_gen, nstore, tTempUseBrill)

                    if (tSinglesOnly) ex_flag = 1

                    do while (.true.)

                        call generate_connection_normal(nI, original_space(:, i), nJ, ilutJ, ex_flag, excit, &
                                                        tAllExcitFound, ncon=connected_space_size)
                        if (tAllExcitFound) exit

                        if (tStoreConnSpace) connected_space(0:NIfD, connected_space_size) = ilutJ(0:NIfD)

                    end do
                end if

            end if ! tGUGA
        end do

    end subroutine generate_connected_space_normal