Skip to content

Commit 62f2d0b

Browse files
authored
Merge branch 'master' into master
2 parents e45b884 + 7be6485 commit 62f2d0b

18 files changed

+135
-861
lines changed

API-doc-FORD-file.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ project: Fortran-lang/stdlib
33
summary: A community driven standard library for (modern) Fortran
44
src_dir: src
55
include: src
6+
include
67
exclude_dir: src/tests
78
output_dir: API-doc
89
page_dir: doc

CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -65,6 +65,7 @@ list(
6565
"-DPROJECT_VERSION_MAJOR=${PROJECT_VERSION_MAJOR}"
6666
"-DPROJECT_VERSION_MINOR=${PROJECT_VERSION_MINOR}"
6767
"-DPROJECT_VERSION_PATCH=${PROJECT_VERSION_PATCH}"
68+
"-I${PROJECT_SOURCE_DIR}/include"
6869
)
6970

7071
add_subdirectory(src)

ci/fpm-deployment.sh

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ prune=(
3131
"$destdir/test/test_always_fail.f90"
3232
"$destdir/test/test_always_skip.f90"
3333
"$destdir/test/test_hash_functions.f90"
34-
"$destdir/src/common.f90"
3534
"$destdir/src/f18estop.f90"
3635
)
3736

@@ -42,7 +41,7 @@ fi
4241
major=$(cut -d. -f1 VERSION)
4342
minor=$(cut -d. -f2 VERSION)
4443
patch=$(cut -d. -f3 VERSION)
45-
fyflags="${fyflags} -DPROJECT_VERSION_MAJOR=${major} -DPROJECT_VERSION_MINOR=${minor} -DPROJECT_VERSION_PATCH=${patch}"
44+
fyflags="${fyflags} -DPROJECT_VERSION_MAJOR=${major} -DPROJECT_VERSION_MINOR=${minor} -DPROJECT_VERSION_PATCH=${patch} -I include"
4645

4746
mkdir -p "$destdir/src" "$destdir/test" "$destdir/example"
4847

example/bitsets/example_bitsets_bit_count.f90

Lines changed: 10 additions & 0 deletions
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
File renamed without changes.

src/f08estop.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
submodule (stdlib_error) estop
1+
submodule (stdlib_error) f08estop
22

33
implicit none
44

@@ -38,4 +38,4 @@
3838
endif
3939
end procedure
4040

41-
end submodule
41+
end submodule f08estop

src/f18estop.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
submodule (stdlib_error) estop
1+
submodule (stdlib_error) f18estop
22

33
implicit none
44

@@ -26,4 +26,4 @@
2626
endif
2727
end procedure
2828

29-
end submodule estop
29+
end submodule f18estop

src/stdlib_bitsets.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ module stdlib_bitsets
100100
!! Parent type for bitset_64 and bitset_large ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types))
101101

102102
private
103-
integer(bits_kind) :: num_bits
103+
integer(bits_kind) :: num_bits = 0_bits_kind
104104

105105
contains
106106

src/stdlib_bitsets_large.fypp

Lines changed: 6 additions & 12 deletions
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
@@ -1051,7 +1045,7 @@ contains
10511045
pure module subroutine set_range_large(self, start_pos, stop_pos)
10521046
!
10531047
! Sets all valid bits to 1 from the START_POS to the STOP_POS positions
1054-
! in SELF. If STOP_POA < START_POS no bits are changed. Positions outside
1048+
! in SELF. If STOP_POS < START_POS no bits are changed. Positions outside
10551049
! the range 0 to BITS(SELF)-1 are ignored.
10561050
!
10571051
class(bitset_large), intent(inout) :: self

test/CMakeLists.txt

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -10,11 +10,6 @@ macro(ADDTEST name)
1010
WORKING_DIRECTORY ${CMAKE_CURRENT_SOURCE_DIR})
1111
endmacro(ADDTEST)
1212

13-
list(
14-
APPEND fyppFlags
15-
"-I${PROJECT_SOURCE_DIR}/src"
16-
)
17-
1813
add_subdirectory(array)
1914
add_subdirectory(ascii)
2015
add_subdirectory(bitsets)

test/bitsets/test_stdlib_bitset_64.f90

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -231,6 +231,15 @@ subroutine test_initialization(error)
231231

232232
type(bitset_64) :: set4, set5
233233

234+
!The following block triggers an issue in gfortran 11 and 12
235+
block
236+
type(bitset_64) :: set6
237+
call check(error, set6 % bits(), 0, &
238+
'set6 % bits() returned non-zero value '//&
239+
'even though set6 was not initialized.')
240+
if (allocated(error)) return
241+
end block
242+
234243
set5 = log1
235244
call check(error, set5%bits(), 64, &
236245
'initialization with logical(int8) failed to set the right size.')

test/bitsets/test_stdlib_bitset_large.f90

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -345,6 +345,15 @@ subroutine test_initialization(error)
345345
logical(int64), allocatable :: log8(:)
346346
type(bitset_large) :: set4, set5
347347

348+
!The following triggers an issue in gfortran 11 and 12
349+
block
350+
type(bitset_large) :: set6
351+
call check(error, set6 % bits(), 0, &
352+
'set6 % bits() returned non-zero value '//&
353+
'even though set6 was not initialized.')
354+
if (allocated(error)) return
355+
end block
356+
348357
set5 = log1
349358
call check(error, set5 % bits(), 64, &
350359
' initialization with logical(int8) failed to set' // &

test/hash_functions/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ ADDTEST(hash_functions)
77
target_sources(
88
test_hash_functions
99
PRIVATE
10-
nmhash_scalar.c
10+
nmhash.c
1111
pengyhash.c
1212
SpookyV2.cpp
1313
SpookyV2Test.cpp

test/hash_functions/generate_hash_arrays.cpp

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33

44
extern "C" {
55
#include "nmhash.h"
6-
#include "nmhash_scalar.h"
76
#include "pengyhash.h"
87
#include "waterhash.h"
98
int generate_all_c_hash();

test/hash_functions/nmhash_scalar.c

Lines changed: 0 additions & 8 deletions
This file was deleted.

0 commit comments

Comments
 (0)