Skip to content

Commit

Permalink
Merge pull request #756 from PierUgit/popcnt2
Browse files Browse the repository at this point in the history
Replaced btest() by popcnt() in bit_count_large()
  • Loading branch information
jvdp1 authored Jan 9, 2024
2 parents d89a6e2 + 67981c3 commit 7be6485
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 11 deletions.
10 changes: 10 additions & 0 deletions example/bitsets/example_bitsets_bit_count.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,9 @@ program example_bit_count
character(*), parameter :: &
bits_0 = '0000000000000000000'
type(bitset_64) :: set0
type(bitset_large) :: set1
logical, allocatable :: logi(:)

call set0%from_string(bits_0)
if (set0%bit_count() == 0) then
write (*, *) "FROM_STRING interpreted "// &
Expand All @@ -12,4 +15,11 @@ program example_bit_count
if (set0%bit_count() == 1) then
write (*, *) "BIT_COUNT interpreted SET0's value properly."
end if

allocate( logi(1000), source=.false.)
logi(1::7) = .true.
set1 = logi
if (set1%bit_count() == count(logi)) then
write (*, *) "BIT_COUNT interpreted SET1's value properly."
end if
end program example_bit_count
16 changes: 5 additions & 11 deletions src/stdlib_bitsets_large.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -144,19 +144,13 @@ contains
integer(bits_kind) :: bit_count
class(bitset_large), intent(in) :: self

integer(bits_kind) :: block_, pos
integer(bits_kind) :: nblocks, pos

bit_count = 0
do block_ = 1_bits_kind, size(self % blocks, kind=bits_kind) - 1
do pos = 0, block_size-1
if ( btest( self % blocks(block_), pos ) ) &
bit_count = bit_count + 1
end do

end do
nblocks = size( self % blocks, kind=bits_kind )
bit_count = sum( popcnt( self % blocks(1:nblocks-1) ) )

do pos = 0_bits_kind, self % num_bits - (block_-1)*block_size - 1
if ( btest( self % blocks(block_), pos ) ) bit_count = bit_count + 1
do pos = 0_bits_kind, self % num_bits - (nblocks-1)*block_size - 1
if ( btest( self % blocks(nblocks), pos ) ) bit_count = bit_count + 1
end do

end function bit_count_large
Expand Down

0 comments on commit 7be6485

Please sign in to comment.