Skip to content

Commit

Permalink
removed block structures
Browse files Browse the repository at this point in the history
  • Loading branch information
degawa committed Jul 2, 2023
1 parent 61029ee commit 7d6d979
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 27 deletions.
24 changes: 11 additions & 13 deletions example/sorting/example_sort_bitset.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ program example_sort_bitset
use stdlib_bitsets, only: bitset_large
implicit none
type(bitset_large), allocatable :: array(:)
integer(int32) :: i

array = [bitset_l("0101"), & ! 5
bitset_l("0100"), & ! 4
Expand All @@ -15,19 +16,16 @@ program example_sort_bitset

call sort(array)

block
integer(int32) :: i
do i = 1, size(array)
print *, to_string(array(i))
! 0001
! 0011
! 0100
! 0100
! 0101
! 1001
! 1010
end do
end block
do i = 1, size(array)
print *, to_string(array(i))
! 0001
! 0011
! 0100
! 0100
! 0101
! 1001
! 1010
end do

deallocate(array)
contains
Expand Down
24 changes: 10 additions & 14 deletions test/sorting/test_sorting.f90
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,8 @@ module test_sorting
type(bitset_large) :: bitsetl_temp
type(bitset_64) :: bitset64_temp
logical :: ltest, ldummy
character(32) :: bin32
character(64) :: bin64

contains

Expand Down Expand Up @@ -196,13 +198,10 @@ subroutine initialize_tests()
string_rand(index1) = string_temp
end do

block
character(32):: bin
do i = 0, bitset_size-1
write(bin,'(b32.32)') i
call bitsetl_increase(i)%from_string(bin)
end do
end block
do i = 0, bitset_size-1
write(bin32,'(b32.32)') i
call bitsetl_increase(i)%from_string(bin32)
end do
do i=0, bitset_size-1
bitsetl_decrease(bitset_size-1-i) = bitsetl_increase(i)
end do
Expand All @@ -216,13 +215,10 @@ subroutine initialize_tests()
bitsetl_rand(index1) = bitsetl_temp
end do

block
character(64):: bin
do i = 0, bitset_size-1
write(bin,'(b64.64)') i
call bitset64_increase(i)%from_string(bin)
end do
end block
do i = 0, bitset_size-1
write(bin64,'(b64.64)') i
call bitset64_increase(i)%from_string(bin64)
end do
do i=0, bitset_size-1
bitset64_decrease(bitset_size-1-i) = bitset64_increase(i)
end do
Expand Down

0 comments on commit 7d6d979

Please sign in to comment.