Skip to content

Commit ecd6c82

Browse files
committed
Typos and bits_kind fixes
Fixed various typos found in stdlib_bitsets.fypp by Jeremie. Modified stdlib_bitsets_large.fypp so it whould work for bits_kind==int64. [ticket: X]
1 parent 0554f5d commit ecd6c82

File tree

2 files changed

+133
-91
lines changed

2 files changed

+133
-91
lines changed

src/stdlib_bitsets.fypp

Lines changed: 29 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -5,29 +5,30 @@ module stdlib_bitsets
55
!! The code assumes two's complement integers, and treats negative integers as
66
!! having the sign bit set.
77

8-
use, intrinsic :: &
9-
iso_fortran_env, only: &
10-
bits_kind => int32, &
11-
block_kind => int64, &
12-
error_unit, &
13-
int8, &
14-
int16, &
15-
int32, &
16-
int64, &
17-
dp => real64
8+
use :: stdlib_kinds, only: &
9+
bits_kind => int32, &
10+
block_kind => int64, &
11+
int8, &
12+
int16, &
13+
int32, &
14+
int64
15+
16+
use, intrinsic :: &
17+
iso_fortran_env, only: &
18+
error_unit
1819

1920
implicit none
2021

2122
private
2223

23-
integer, parameter :: &
24+
integer(bits_kind), parameter :: &
2425
block_size = bit_size(0_block_kind)
2526

26-
integer(block_kind), private, parameter :: all_zeros = 0_block_kind
27-
integer(block_kind), private, parameter :: all_ones = not(all_zeros)
27+
integer(block_kind), parameter :: all_zeros = 0_block_kind
28+
integer(block_kind), parameter :: all_ones = not(all_zeros)
2829

29-
character(*), parameter, private :: module_name = "STDLIB_BITSETS"
30-
integer, parameter, private :: &
30+
character(*), parameter :: module_name = "STDLIB_BITSETS"
31+
integer, parameter :: &
3132
ia0 = iachar('0'), &
3233
ia9 = iachar('9')
3334

@@ -870,7 +871,7 @@ module stdlib_bitsets
870871
elemental module subroutine clear_bit_large(self, pos)
871872
!! Version: experimental
872873
!!
873-
!! Sets to zero the bit at `pos` position in `self`. If 'pos` is less than
874+
!! Sets to zero the bit at `pos` position in `self`. If `pos` is less than
874875
!! zero or greater than `bits(self)-1` it is ignored.
875876
class(bitset_large), intent(inout) :: self
876877
integer(bits_kind), intent(in) :: pos
@@ -1303,7 +1304,7 @@ module stdlib_bitsets
13031304
!! * `success` - if no problems were found,
13041305
!! * `alloc_fault` - if memory allocation failed
13051306
!! * `array_size_invalid_error` - if `bits` is either negative or larger
1306-
!! than 64 with `self` of class `bitset_64`, or
1307+
!! than 64 with `self` of class `bitset_64`.
13071308
class(bitset_64), intent(out) :: self
13081309
integer(bits_kind), intent(in) :: bits
13091310
integer, intent(out), optional :: status
@@ -1653,7 +1654,7 @@ module stdlib_bitsets
16531654
!! Version: experimental
16541655
!!
16551656
!! Creates a new bitset, `new`, from a range, `start_pos` to `stop_pos`, in
1656-
!! bitset `old`. If 'start_pos` is greater than `stop_pos` the new bitset is
1657+
!! bitset `old`. If `start_pos` is greater than `stop_pos` the new bitset is
16571658
!! empty. If `start_pos` is less than zero or `stop_pos` is greater than
16581659
!! `bits(old)-1` then if `status` is present it has the value
16591660
!! `index_invalid_error`and `new` is undefined, otherwise processing stops
@@ -1799,7 +1800,7 @@ module stdlib_bitsets
17991800
elemental module function eqv_64(set1, set2) result(eqv)
18001801
!! Version: experimental
18011802
!!
1802-
!! Returns `.true`. if all bits in `set1` and `set2` have the same value,
1803+
!! Returns `.true.` if all bits in `set1` and `set2` have the same value,
18031804
!! `.false.` otherwise. The sets must have the same number of bits
18041805
!! otherwise the result is undefined.
18051806
logical :: eqv
@@ -1893,7 +1894,7 @@ module stdlib_bitsets
18931894
!! Version: experimental
18941895
!!
18951896
!! Returns `.true.` if the bits in `set1` and `set2` differ and the
1896-
!! highest order different bit is set to 1 in `set1` and to 0 in `set2`.
1897+
!! highest order different bit is set to 1 in `set1` and to 0 in `set2`,
18971898
!! `.false.` otherwise. The sets must have the same number of bits
18981899
!! otherwise the result is undefined.
18991900
logical :: gt
@@ -1909,7 +1910,7 @@ module stdlib_bitsets
19091910
!! Version: experimental
19101911
!!
19111912
!! Returns `.true.` if the bits in `set1` and `set2` are the same or the
1912-
!! highest order different bit is set to 1 in `set1` and to 0 in `set2`.
1913+
!! highest order different bit is set to 1 in `set1` and to 0 in `set2`,
19131914
!! `.false.` otherwise. The sets must have the same number of bits
19141915
!! otherwise the result is undefined.
19151916
!!
@@ -1942,7 +1943,7 @@ module stdlib_bitsets
19421943
!! Version: experimental
19431944
!!
19441945
!! Returns `.true.` if the bits in `set1` and `set2` are the same or the
1945-
!! highest order different bit is set to 1 in `set1` and to 0 in `set2`.
1946+
!! highest order different bit is set to 1 in `set1` and to 0 in `set2`,
19461947
!! `.false.` otherwise. The sets must have the same number of bits
19471948
!! otherwise the result is undefined.
19481949
logical :: ge
@@ -1958,7 +1959,7 @@ module stdlib_bitsets
19581959
!! Version: experimental
19591960
!!
19601961
!! Returns `.true.` if the bits in `set1` and `set2` differ and the
1961-
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`.
1962+
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`,
19621963
!! `.false.` otherwise. The sets must have the same number of bits
19631964
!! otherwise the result is undefined.
19641965
!!
@@ -1990,7 +1991,7 @@ module stdlib_bitsets
19901991
!! Version: experimental
19911992
!!
19921993
!! Returns `.true.` if the bits in `set1` and `set2` differ and the
1993-
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`.
1994+
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`,
19941995
!! `.false.` otherwise. The sets must have the same number of bits
19951996
!! otherwise the result is undefined.
19961997
logical :: lt
@@ -2006,7 +2007,7 @@ module stdlib_bitsets
20062007
!! Version: experimental
20072008
!!
20082009
!! Returns `.true.` if the bits in `set1` and `set2` are the same or the
2009-
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`.
2010+
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`,
20102011
!! `.false.` otherwise. The sets must have the same number of bits
20112012
!! otherwise the result is undefined.
20122013
!!
@@ -2039,7 +2040,7 @@ module stdlib_bitsets
20392040
!! Version: experimental
20402041
!!
20412042
!! Returns `.true.` if the bits in `set1` and `set2` are the same or the
2042-
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`.
2043+
!! highest order different bit is set to 0 in `set1` and to 1 in `set2`,
20432044
!! `.false.` otherwise. The sets must have the same number of bits
20442045
!! otherwise the result is undefined.
20452046
logical :: le
@@ -2049,7 +2050,8 @@ module stdlib_bitsets
20492050
end interface operator(<=)
20502051

20512052
interface error_handler
2052-
module subroutine error_handler( message, error, status, module, procedure )
2053+
module subroutine error_handler( message, error, status, &
2054+
module, procedure )
20532055
character(*), intent(in) :: message
20542056
integer, intent(in) :: error
20552057
integer, intent(out), optional :: status

0 commit comments

Comments
 (0)