Skip to content

Commit 7be6485

Browse files
authored
Merge pull request #756 from PierUgit/popcnt2
Replaced btest() by popcnt() in bit_count_large()
2 parents d89a6e2 + 67981c3 commit 7be6485

File tree

2 files changed

+15
-11
lines changed

2 files changed

+15
-11
lines changed

example/bitsets/example_bitsets_bit_count.f90

+10
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,9 @@ program example_bit_count
33
character(*), parameter :: &
44
bits_0 = '0000000000000000000'
55
type(bitset_64) :: set0
6+
type(bitset_large) :: set1
7+
logical, allocatable :: logi(:)
8+
69
call set0%from_string(bits_0)
710
if (set0%bit_count() == 0) then
811
write (*, *) "FROM_STRING interpreted "// &
@@ -12,4 +15,11 @@ program example_bit_count
1215
if (set0%bit_count() == 1) then
1316
write (*, *) "BIT_COUNT interpreted SET0's value properly."
1417
end if
18+
19+
allocate( logi(1000), source=.false.)
20+
logi(1::7) = .true.
21+
set1 = logi
22+
if (set1%bit_count() == count(logi)) then
23+
write (*, *) "BIT_COUNT interpreted SET1's value properly."
24+
end if
1525
end program example_bit_count

src/stdlib_bitsets_large.fypp

+5-11
Original file line numberDiff line numberDiff line change
@@ -144,19 +144,13 @@ contains
144144
integer(bits_kind) :: bit_count
145145
class(bitset_large), intent(in) :: self
146146

147-
integer(bits_kind) :: block_, pos
147+
integer(bits_kind) :: nblocks, pos
148148

149-
bit_count = 0
150-
do block_ = 1_bits_kind, size(self % blocks, kind=bits_kind) - 1
151-
do pos = 0, block_size-1
152-
if ( btest( self % blocks(block_), pos ) ) &
153-
bit_count = bit_count + 1
154-
end do
155-
156-
end do
149+
nblocks = size( self % blocks, kind=bits_kind )
150+
bit_count = sum( popcnt( self % blocks(1:nblocks-1) ) )
157151

158-
do pos = 0_bits_kind, self % num_bits - (block_-1)*block_size - 1
159-
if ( btest( self % blocks(block_), pos ) ) bit_count = bit_count + 1
152+
do pos = 0_bits_kind, self % num_bits - (nblocks-1)*block_size - 1
153+
if ( btest( self % blocks(nblocks), pos ) ) bit_count = bit_count + 1
160154
end do
161155

162156
end function bit_count_large

0 commit comments

Comments
 (0)