Skip to content

Commit 96763e1

Browse files
committed
add test following issue #726
1 parent de2dbbb commit 96763e1

File tree

1 file changed

+31
-0
lines changed

1 file changed

+31
-0
lines changed

test/bitsets/test_stdlib_bitset_large.f90

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ subroutine collect_stdlib_bitset_large(testsuite)
2828
new_unittest("string-operations", test_string_operations), &
2929
new_unittest("io", test_io), &
3030
new_unittest("initialization", test_initialization), &
31+
new_unittest("bitset-assignment-array", test_assignment_array), &
3132
new_unittest("bitset-inquiry", test_bitset_inquiry), &
3233
new_unittest("bit-operations", test_bit_operations), &
3334
new_unittest("bitset-comparisons", test_bitset_comparisons), &
@@ -558,6 +559,36 @@ subroutine test_initialization(error)
558559

559560
end subroutine test_initialization
560561

562+
subroutine test_assignment_array(error)
563+
!> Error handling
564+
type(error_type), allocatable, intent(out) :: error
565+
566+
logical(int8) :: log1(64) = .true.
567+
568+
integer :: i
569+
type(bitset_large) :: set1(0:4)
570+
571+
do i = 0, size(set1) - 1
572+
set1(i) = log1
573+
enddo
574+
575+
do i = 0, size(set1) - 1
576+
call check(error, set1(i) % bits(), 64, &
577+
' initialization with logical(int8) failed to set' // &
578+
' the right size in a bitset array.')
579+
if (allocated(error)) return
580+
enddo
581+
582+
!Test added following issue https://github.com/fortran-lang/stdlib/issues/726
583+
set1(0) = set1(0)
584+
585+
call check(error, set1(0) % bits(), 64, &
586+
' initialization from bitset_large failed to set' // &
587+
' the right size in a bitset array.')
588+
if (allocated(error)) return
589+
590+
end subroutine test_assignment_array
591+
561592
subroutine test_bitset_inquiry(error)
562593
!> Error handling
563594
type(error_type), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)