Skip to content

Commit

Permalink
PR related to #726 and #723 (#727)
Browse files Browse the repository at this point in the history
* add explicity in test_stdlib_bitset_large

* add test following issue #726

* remove assign bitset_large

* Update src/stdlib_bitsets_large.fypp

* Update src/stdlib_bitsets.fypp

* remove assign bitset_64

* update specs
  • Loading branch information
jvdp1 committed Aug 8, 2023
1 parent 7ff6762 commit 0b00b7b
Show file tree
Hide file tree
Showing 5 changed files with 42 additions and 36 deletions.
4 changes: 2 additions & 2 deletions doc/specs/stdlib_bitsets.md
Original file line number Diff line number Diff line change
Expand Up @@ -194,8 +194,8 @@ undefined. These procedures are summarized in the following table:

### Assignments

The module defines an assignment operation, `=`, that creates a
duplicate of an original bitset. It also defines assignments to and
The module uses the intrinsic assignment operation, `=`, to create a
duplicate of an original bitset. It additionally defines assignments to and
from rank one arrays of logical type of kinds `int8`, `int16`,
`int32`, and `int64`. In the assignment to and from logical arrays
array index, `i`, is mapped to bit position, `pos=i-1`, and `.true.`
Expand Down
14 changes: 0 additions & 14 deletions src/stdlib_bitsets.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -1166,13 +1166,6 @@ module stdlib_bitsets
!! end program example_assignment
!!```
pure module subroutine assign_large( set1, set2 )
!! Version: experimental
!!
!! Used to define assignment for `bitset_large`.
type(bitset_large), intent(out) :: set1
type(bitset_large), intent(in) :: set2
end subroutine assign_large
#:for k1 in INT_KINDS
pure module subroutine assign_log${k1}$_large( self, logical_vector )
Expand Down Expand Up @@ -1510,13 +1503,6 @@ module stdlib_bitsets
interface assignment(=)
pure module subroutine assign_64( set1, set2 )
!! Version: experimental
!!
!! Used to define assignment for `bitset_64`.
type(bitset_64), intent(out) :: set1
type(bitset_64), intent(in) :: set2
end subroutine assign_64
#:for k1 in INT_KINDS
module subroutine assign_log${k1}$_64( self, logical_vector )
Expand Down
9 changes: 0 additions & 9 deletions src/stdlib_bitsets_64.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -72,15 +72,6 @@ contains
end function any_64
pure module subroutine assign_64( set1, set2 )
! Used to define assignment for bitset_64
type(bitset_64), intent(out) :: set1
type(bitset_64), intent(in) :: set2
set1 % num_bits = set2 % num_bits
set1 % block = set2 % block
end subroutine assign_64
#:for k1 in INT_KINDS
Expand Down
10 changes: 0 additions & 10 deletions src/stdlib_bitsets_large.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -89,16 +89,6 @@ contains
end function any_large


pure module subroutine assign_large( set1, set2 )
! Used to define assignment for bitset_large
type(bitset_large), intent(out) :: set1
type(bitset_large), intent(in) :: set2

set1 % num_bits = set2 % num_bits
allocate( set1 % blocks( size( set2 % blocks, kind=bits_kind ) ) )
set1 % blocks(:) = set2 % blocks(:)

end subroutine assign_large

#:for k1 in INT_KINDS
pure module subroutine assign_log${k1}$_large( self, logical_vector )
Expand Down
41 changes: 40 additions & 1 deletion test/bitsets/test_stdlib_bitset_large.f90
Original file line number Diff line number Diff line change
@@ -1,7 +1,15 @@
module test_stdlib_bitset_large
use testdrive, only : new_unittest, unittest_type, error_type, check
use :: stdlib_kinds, only : int8, int16, int32, int64
use stdlib_bitsets
use stdlib_bitsets, only: bitset_large, bits_kind&
, bits &
, success &
, and, and_not, or, xor&
, extract&
, assignment(=)&
, operator(<), operator(<=)&
, operator(>), operator(>=)&
, operator(/=), operator(==)
implicit none
character(*), parameter :: &
bitstring_0 = '000000000000000000000000000000000', &
Expand All @@ -20,6 +28,7 @@ subroutine collect_stdlib_bitset_large(testsuite)
new_unittest("string-operations", test_string_operations), &
new_unittest("io", test_io), &
new_unittest("initialization", test_initialization), &
new_unittest("bitset-assignment-array", test_assignment_array), &
new_unittest("bitset-inquiry", test_bitset_inquiry), &
new_unittest("bit-operations", test_bit_operations), &
new_unittest("bitset-comparisons", test_bitset_comparisons), &
Expand Down Expand Up @@ -550,6 +559,36 @@ subroutine test_initialization(error)

end subroutine test_initialization

subroutine test_assignment_array(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error

logical(int8) :: log1(64) = .true.

integer :: i
type(bitset_large) :: set1(0:4)

do i = 0, size(set1) - 1
set1(i) = log1
enddo

do i = 0, size(set1) - 1
call check(error, set1(i) % bits(), 64, &
' initialization with logical(int8) failed to set' // &
' the right size in a bitset array.')
if (allocated(error)) return
enddo

!Test added following issue https://github.com/fortran-lang/stdlib/issues/726
set1(0) = set1(0)

call check(error, set1(0) % bits(), 64, &
' initialization from bitset_large failed to set' // &
' the right size in a bitset array.')
if (allocated(error)) return

end subroutine test_assignment_array

subroutine test_bitset_inquiry(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
Expand Down

0 comments on commit 0b00b7b

Please sign in to comment.