Skip to content

Commit

Permalink
Merge pull request #753 from jvdp1/fix_bits_bitset
Browse files Browse the repository at this point in the history
Fix `bits()` in `bitset_type` before initialization
  • Loading branch information
jvdp1 authored Jan 7, 2024
2 parents 42a547b + 091201d commit c086185
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 2 deletions.
2 changes: 1 addition & 1 deletion src/stdlib_bitsets.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ module stdlib_bitsets
!! Parent type for bitset_64 and bitset_large ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types))
private
integer(bits_kind) :: num_bits
integer(bits_kind) :: num_bits = 0_bits_kind
contains
Expand Down
2 changes: 1 addition & 1 deletion src/stdlib_bitsets_large.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -1051,7 +1051,7 @@ contains
pure module subroutine set_range_large(self, start_pos, stop_pos)
!
! Sets all valid bits to 1 from the START_POS to the STOP_POS positions
! in SELF. If STOP_POA < START_POS no bits are changed. Positions outside
! in SELF. If STOP_POS < START_POS no bits are changed. Positions outside
! the range 0 to BITS(SELF)-1 are ignored.
!
class(bitset_large), intent(inout) :: self
Expand Down
9 changes: 9 additions & 0 deletions test/bitsets/test_stdlib_bitset_64.f90
Original file line number Diff line number Diff line change
Expand Up @@ -231,6 +231,15 @@ subroutine test_initialization(error)

type(bitset_64) :: set4, set5

!The following block triggers an issue in gfortran 11 and 12
block
type(bitset_64) :: set6
call check(error, set6 % bits(), 0, &
'set6 % bits() returned non-zero value '//&
'even though set6 was not initialized.')
if (allocated(error)) return
end block

set5 = log1
call check(error, set5%bits(), 64, &
'initialization with logical(int8) failed to set the right size.')
Expand Down
9 changes: 9 additions & 0 deletions test/bitsets/test_stdlib_bitset_large.f90
Original file line number Diff line number Diff line change
Expand Up @@ -345,6 +345,15 @@ subroutine test_initialization(error)
logical(int64), allocatable :: log8(:)
type(bitset_large) :: set4, set5

!The following triggers an issue in gfortran 11 and 12
block
type(bitset_large) :: set6
call check(error, set6 % bits(), 0, &
'set6 % bits() returned non-zero value '//&
'even though set6 was not initialized.')
if (allocated(error)) return
end block

set5 = log1
call check(error, set5 % bits(), 64, &
' initialization with logical(int8) failed to set' // &
Expand Down

0 comments on commit c086185

Please sign in to comment.