LargestBitSet Subroutine

subroutine LargestBitSet(iLut, NIfD, LargestOrb)

Arguments

Type IntentOptional Attributes Name
integer(kind=n_int) :: iLut(0:NIfD)

Count down through the integers in the bit string. The largest set bit is equal to INT(log_2 (N))

integer :: NIfD
integer :: LargestOrb

Contents

Source Code


Source Code

SUBROUTINE LargestBitSet(iLut, NIfD, LargestOrb)
    use constants, only: bits_n_int, end_n_int, n_int
    use error_handling_neci, only: stop_all
    IMPLICIT NONE
    INTEGER :: LargestOrb, NIfD, i, j
    INTEGER(KIND=n_int) :: iLut(0:NIfD)

#ifdef DEBUG_
    character(*), parameter :: this_routine = 'LargestBitSet'
#endif

!        do i=NIfD,0,-1
!!Count down through the integers in the bit string.
!!The largest set bit is equal to INT(log_2 (N))
!            IF(iLut(i).ne.0) THEN
!                LargestOrb=NINT(LOG(REAL(iLut(i)+1))*1.4426950408889634)
!                EXIT
!            end if
!        end do
!        LargestOrb=LargestOrb+(i*32)

    ! Initialise with invalid value (in case being erroniously called on empty bit-string).
    ASSERT(.not. all(ilut == 0))
    LargestOrb = 99999

    do i = NIfD, 0, -1
        do j = end_n_int, 0, -1
            if (btest(iLut(i), j)) then
                LargestOrb = (i * bits_n_int) + j + 1
                return
            end if
        end do
    end do

END SUBROUTINE LargestBitSet