From dd5d1ec5edda7c58d79c30b517ea5f8c4bf467bc Mon Sep 17 00:00:00 2001 From: Jeremie Vandenplas Date: Tue, 24 Nov 2020 20:25:52 +0100 Subject: [PATCH 1/4] bitset: update specs --- doc/specs/stdlib_bitsets.md | 78 +++++++++++++++++++------------------ 1 file changed, 41 insertions(+), 37 deletions(-) diff --git a/doc/specs/stdlib_bitsets.md b/doc/specs/stdlib_bitsets.md index ea8ddb2a7..30a14266a 100644 --- a/doc/specs/stdlib_bitsets.md +++ b/doc/specs/stdlib_bitsets.md @@ -54,7 +54,7 @@ bits. The other constants that are error codes are summarized below: |`char_string_too_large_error`|Character string was too large to be encoded in the bitset| |`char_string_too_small_error`|Character string was too small to hold the expected number of bits| |`index_invalid_error`|Index to a bitstring was less than zero or greater than the number of bits| -|`integer_overflow_error`|Attempt to define an integer value bigger than `huge(0_bits_kind`)| +|`integer_overflow_error`|Attempt to define an integer value bigger than `huge(0_bits_kind)`| |`read_failure`|Failure on a `read` statement| |`eof_failure`|An unexpected "End-of-File" on a `read` statement| |`write_failure`|Failure on a `write` statement| @@ -78,13 +78,13 @@ position, that, in turn, is indexed from 0 to `bits-1`. `bitset_type` is used only as a `class` to define entities that can be either a `bitset_64` or a `bitset_large`. The syntax for using the types are: -`class([[stdlib_bitset(module):bitset_type(class)]]) :: variable` +`class([[stdlib_bitsets(module):bitset_type(type)]]) :: variable` -`type([[stdlib_bitset(module):bitset_64(type)]]) :: variable` +`type([[stdlib_bitsets(module):bitset_64(type)]]) :: variable` and -`type([[stdlib_bitset(module):bitset_large(type)]]) :: variable` +`type([[stdlib_bitsets(module):bitset_large(type)]]) :: variable` ## The *bitset-literal* @@ -136,6 +136,7 @@ and all characters in the string must be either "0" or "1". ## Summary of the module's operations The `stdlib_bitsets` module defines a number of operations: + * "unary" methods of class `bitset_type`, * "binary" procedure overloads of type `bitset_64` or `bitset_large`, * assignments, and @@ -261,7 +262,7 @@ Determines whether all bits are set to 1 in `self`. #### Syntax -`result = self % [[bitset_type(class):all(bound)]]()` +`result = self % [[bitset_type(type):all(bound)]]()` #### Class @@ -311,7 +312,7 @@ number of bits, otherwise the result is undefined. #### Syntax -`call [[stdlib_bitsets(module):and(interface]] (set1, set2)` +`call [[stdlib_bitsets(module):and(interface)]](set1, set2)` #### Class @@ -417,7 +418,7 @@ Determines whether any bits are set in `self`. #### Syntax -`result = self % [[bitset_type(class):any(bound)]]()` +`result = self % [[bitset_type(type):any(bound)]]()` #### Class @@ -465,7 +466,7 @@ Returns the number of bits that are set to one in `self`. #### Syntax -`result = self % [[bitset_type(class):bit_count(bound)]] ()` +`result = self % [[bitset_type(type):bit_count(bound)]] ()` #### Class @@ -513,7 +514,7 @@ Reports the number of bits in `self`. #### Syntax -`result = self % [[bitset_type(class):bits(bound)]] ()` +`result = self % [[bitset_type(type):bits(bound)]] ()` #### Class @@ -566,11 +567,11 @@ Note: Positions outside the range 0 to `bits(set) -1` are ignored. #### Syntax -`call self % [[bitset_type(class):clear(bound)]](pos)' +`call self % [[bitset_type(type):clear(bound)]](pos)` or -`call self % [[bitset_type(class):clear(bound)]](start_pos, end_pos)` +`call self % [[bitset_type(type):clear(bound)]](start_pos, end_pos)` #### Class @@ -675,21 +676,24 @@ Experimental #### Description Flip the values of a sequence of one or more bits. + * If only `pos` is present flip the bit value with position `pos` in + `self`. * If `start_pos` and `end_pos` are present with `end_pos >= start_pos` flip the bit values with positions from `start_pos` to `end_pos` in `self`. + * If `end_pos < start_pos` then `self` is unmodified. #### Syntax -`call self % [[bitset_type(class):flip(bound)]] (pos)` +`call self % [[bitset_type(type):flip(bound)]] (pos)` or -`call self % [[bitset_type(class):flip(bound)]] (start_pos, end_pos)` +`call self % [[bitset_type(type):flip(bound)]] (start_pos, end_pos)` #### Class @@ -737,7 +741,7 @@ binary literal. #### Syntax -`call self % [[bitset_type(class):from_string(bound)]](string[, status])` +`call self % [[bitset_type(type):from_string(bound)]](string[, status])` #### Class @@ -790,7 +794,7 @@ codes: end program demo_from_string ``` -### `init` - `bitset_type` initialization routines. +### `init` - `bitset_type` initialization routines #### Status @@ -802,7 +806,7 @@ Experimental #### Syntax -`call [[stdlib_bitsets(module):init(interface)]] (self, bits [, status])` +`call self % [[bitset_type(type):init(bound)]] (bits [, status])` #### Class @@ -813,7 +817,7 @@ Subroutine. `self`: shall be a scalar `bitset_64` or `bitset_large` variable. It is an `intent(out)` argument. -`bits` (optional): shall be a scalar integer expression of kind +`bits`: shall be a scalar integer expression of kind `bits_kind`. It is an `intent(in)` argument that if present specifies the number of bits in `set`. A negative value, or a value greater than 64 if `self` is of type `bitset_64`, is an error. @@ -841,7 +845,7 @@ stop code. It can have any of the following error codes: type(bitset_large) :: set0 call set0 % init(166) if ( set0 % bits() == 166 ) & - write(*,*) `SET0 has the proper size.' + write(*,*) 'SET0 has the proper size.' if ( set0 % none() ) write(*,*) 'SET0 is properly initialized.' end program demo_init ``` @@ -859,7 +863,7 @@ file. #### Syntax -`call self % [[bitset_type(class):input(bound)]] (unit [, status])` +`call self % [[bitset_type(type):input(bound)]] (unit [, status])` #### Class @@ -940,7 +944,7 @@ Determines whether no bits are set in `self`. #### Syntax -`result = self % [[bitset_type(class):none(bound)]] ()` +`result = self % [[bitset_type(type):none(bound)]] ()` #### Class @@ -989,7 +993,7 @@ Performs the logical complement on the bits of `self`. #### Syntax -`call self % [[bitset_type(class):not(bound)]] ()` +`call self % [[bitset_type(type):not(bound)]] ()` #### Class @@ -1085,7 +1089,7 @@ Writes a binary representation of a bitset to an unformatted file. #### Syntax -`call self % [[bitset_type(class):output(bound)]] (unit[, status])` +`call self % [[bitset_type(type):output(bound)]] (unit[, status])` #### Class @@ -1159,11 +1163,11 @@ value. #### Syntax -`call self % [[bitset_type(class):read_bitset(bound)]](string[, status])` +`call self % [[bitset_type(type):read_bitset(bound)]](string[, status])` or -`call self % [[bitset_type(class):read_bitset(bound)]](unit[, advance, status])` +`call self % [[bitset_type(type):read_bitset(bound)]](unit[, advance, status])` #### Class @@ -1282,11 +1286,11 @@ set the bits at positions from `start_pos` to `end_pos` in `self` to 1. #### Syntax -`call self % [[bitset_type(class):set(bound)]] (POS)` +`call self % [[bitset_type(type):set(bound)]] (POS)` or -`call self % [[bitset_type(class):set(bound)]] (START_POS, END_POS)` +`call self % [[bitset_type(type):set(bound)]] (START_POS, END_POS)` #### Class @@ -1334,7 +1338,7 @@ Determine whether the bit at position `pos` is set to 1 in `self`. #### Syntax -`result = self % [[bitset_type(class):test(bound)]](pos)` +`result = self % [[bitset_type(type):test(bound)]](pos)` #### Class @@ -1383,7 +1387,7 @@ Represents the value of `self` as a binary literal in `string`. #### Syntax -`call self % [[bitset_type(class):to_string(bound)]](string[, status])` +`call self % [[bitset_type(type):to_string(bound)]](string[, status])` #### Class @@ -1440,7 +1444,7 @@ Determines the value of the bit at position, `pos`, in `self`. #### Syntax -`result = self % [[bitset_type(class):value(bound)]](pos)` +`result = self % [[bitset_type(type):value(bound)]](pos)` #### Class @@ -1491,11 +1495,11 @@ character string or formatted file. #### Syntax -`call self % [[bitset_type(class):write_bitset(bound)]](string[, status])` +`call self % [[bitset_type(type):write_bitset(bound)]](string[, status])` or -`call self % [[bitset_type(class):write_bitset(bound)]] (unit[, advance, status])` +`call self % [[bitset_type(type):write_bitset(bound)]] (unit[, advance, status])` #### Class @@ -1649,7 +1653,7 @@ Returns `.true.` if all bits in `set1` and `set2` have the same value, or -`result = set1 [[stdlib_bitsets(module):.EQ.(interface)]] set2` +`result = set1 .EQ. set2` #### Class @@ -1708,7 +1712,7 @@ Returns `.true.` if any bits in `self` and `set2` differ in value, or -`result = set1 [[stdlib_bitsets(module):.NE.(interface)]] set2` +`result = set1 .NE. set2` #### Class @@ -1769,7 +1773,7 @@ results are undefined. or -`result = set1 [[stdlib_bitsets(module):.GE.(interface)]] set2` +`result = set1 .GE. set2` #### Class @@ -1832,7 +1836,7 @@ results are undefined. or -`result = set1 [[stdlib_bitsets(module):.GT.(interface)]] set2` +`result = set1 .GT. set2` #### Class @@ -1894,7 +1898,7 @@ results are undefined. or -`result = set1 [[stdlib_bitsets(module):.LE.(interface)]] set2` +`result = set1 .LE. set2` #### Class @@ -1957,7 +1961,7 @@ results are undefined. or -`result = set1 [[stdlib_bitsets(module):.LT.(interface)]] set2 +`result = set1 .LT. set2 #### Class From efbcc71617a9fba3e603bd12c1dcc8f1dbaa77a3 Mon Sep 17 00:00:00 2001 From: Jeremie Vandenplas Date: Tue, 24 Nov 2020 21:37:49 +0100 Subject: [PATCH 2/4] bitset_specs: addition of links --- src/stdlib_bitsets.fypp | 126 ++++++++++++---------------------------- 1 file changed, 37 insertions(+), 89 deletions(-) diff --git a/src/stdlib_bitsets.fypp b/src/stdlib_bitsets.fypp index 881a7bd2c..ad52517ab 100644 --- a/src/stdlib_bitsets.fypp +++ b/src/stdlib_bitsets.fypp @@ -4,6 +4,7 @@ module stdlib_bitsets !! The current code uses 64 bit integers to store the bits and uses all 64 bits. !! The code assumes two's complement integers, and treats negative integers as !! having the sign bit set. +!!([Specification](../page/specs/stdlib_bitsets.html)) use :: stdlib_kinds, only: & bits_kind => int32, & ! If changed change also max_digits, and @@ -95,7 +96,8 @@ module stdlib_bitsets type, abstract :: bitset_type !! version: experimental !! -!! Parent type for bitset_64 and bitset_large +!! Parent type for bitset_64 and bitset_large ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types)) + private integer(bits_kind) :: num_bits @@ -817,7 +819,8 @@ module stdlib_bitsets type, extends(bitset_type) :: bitset_large !! Version: experimental !! -!! Type for bitsets with more than 64 bits. +!! Type for bitsets with more than 64 bits ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types)) + private integer(block_kind), private, allocatable :: blocks(:) @@ -1128,6 +1131,10 @@ module stdlib_bitsets interface assignment(=) +!! Version: experimental +!! +!! Used to define assignment for `bitset_large`. +!! ([Specification](../page/specs/stdlib_bitsets.html#-compare-two-bitsets-to-determine-whether-the-bits-have-the-same-value)) !! !!#### Example !! @@ -1192,7 +1199,7 @@ module stdlib_bitsets type, extends(bitset_type) :: bitset_64 !! Version: experimental !! -!! Type for bitsets with no more than 64 bits. +!! Type for bitsets with no more than 64 bits ([Specification](../page/specs/stdlib_bitsets.html#the-stdlib_bitsets-derived-types)) private integer(block_kind), private :: block = 0 @@ -1534,13 +1541,12 @@ module stdlib_bitsets interface and - - elemental module subroutine and_large(set1, set2) !! Version: experimental !! !! Sets the bits in `set1` to the bitwise `and` of the original bits in `set1` !! and `set2`. The sets must have the same number of bits !! otherwise the result is undefined. +!! ([Specification](../page/specs/stdlib_bitsets.html#and-bitwise-and-of-the-bits-of-two-bitsets)) !! !!#### Example !! @@ -1563,16 +1569,12 @@ module stdlib_bitsets !! if ( all(set0) ) write(*,*) 'Fourth test of AND worked.' !! end program demo_and !!``` + elemental module subroutine and_large(set1, set2) type(bitset_large), intent(inout) :: set1 type(bitset_large), intent(in) :: set2 end subroutine and_large elemental module subroutine and_64(set1, set2) -!! Version: experimental -!! -!! Sets the bits in `set1` to the bitwise `and` of the original bits in `set1` -!! and `set2`. The sets must have the same number of bits -!! otherwise the result is undefined. type(bitset_64), intent(inout) :: set1 type(bitset_64), intent(in) :: set2 end subroutine and_64 @@ -1581,14 +1583,14 @@ module stdlib_bitsets interface and_not - - elemental module subroutine and_not_large(set1, set2) !! Version: experimental !! !! Sets the bits in `set1` to the bitwise and of the original bits in `set1` !! with the bitwise negation of `set2`. The sets must have the same !! number of bits otherwise the result is undefined. !! +!! ([Specification](../page/specs/stdlib_bitsets.html#and_not-bitwise-and-of-one-bitset-with-the-negation-of-another)) +!! !!#### Example !! !!```fortran @@ -1611,16 +1613,13 @@ module stdlib_bitsets !! if ( none(set0) ) write(*,*) 'Fourth test of AND_NOT worked.' !! end program demo_and_not !!``` + + elemental module subroutine and_not_large(set1, set2) type(bitset_large), intent(inout) :: set1 type(bitset_large), intent(in) :: set2 end subroutine and_not_large elemental module subroutine and_not_64(set1, set2) -!! Version: experimental -!! -!! Sets the bits in `set1` to the bitwise and of the original bits in `set1` -!! with the bitwise negation of `set2`. The sets must have the same -!! number of bits otherwise the result is undefined. type(bitset_64), intent(inout) :: set1 type(bitset_64), intent(in) :: set2 end subroutine and_not_64 @@ -1628,8 +1627,6 @@ module stdlib_bitsets end interface and_not interface extract - - module subroutine extract_large(new, old, start_pos, stop_pos, status) !! Version: experimental !! !! Creates a new bitset, `new`, from a range, `start_pos` to `stop_pos`, in @@ -1638,6 +1635,7 @@ module stdlib_bitsets !! `bits(old)-1` then if `status` is present it has the value !! `index_invalid_error` and `new` is undefined, otherwise processing stops !! with an informative message. +!! ([Specification](../page/specs/stdlib_bitsets.html#extract-create-a-new-bitset-from-a-range-in-an-old-bitset)) !! !!#### Example !! @@ -1653,6 +1651,8 @@ module stdlib_bitsets !! if ( set1 % all() ) write(*,*) 'SET1 has the proper values.' !! end program demo_extract !!``` + + module subroutine extract_large(new, old, start_pos, stop_pos, status) type(bitset_large), intent(out) :: new type(bitset_large), intent(in) :: old integer(bits_kind), intent(in) :: start_pos, stop_pos @@ -1660,14 +1660,6 @@ module stdlib_bitsets end subroutine extract_large module subroutine extract_64(new, old, start_pos, stop_pos, status) -!! Version: experimental -!! -!! Creates a new bitset, `new`, from a range, `start_pos` to `stop_pos`, in -!! bitset `old`. If `start_pos` is greater than `stop_pos` the new bitset is -!! empty. If `start_pos` is less than zero or `stop_pos` is greater than -!! `bits(old)-1` then if `status` is present it has the value -!! `index_invalid_error`and `new` is undefined, otherwise processing stops -!! with an informative message. type(bitset_64), intent(out) :: new type(bitset_64), intent(in) :: old integer(bits_kind), intent(in) :: start_pos, stop_pos @@ -1678,13 +1670,12 @@ module stdlib_bitsets interface or - - elemental module subroutine or_large(set1, set2) !! Version: experimental !! !! Sets the bits in `set1` to the bitwise `or` of the original bits in `set1` !! and `set2`. The sets must have the same number of bits otherwise !! the result is undefined. +!! ([Specification](../page/specs/stdlib_bitsets.html#or-bitwise-or-of-the-bits-of-two-bitsets)) !! !!#### Example !! @@ -1708,16 +1699,12 @@ module stdlib_bitsets !! if ( all(set0) ) write(*,*) 'Fourth test of OR worked.' !! end program demo_or !!``` + elemental module subroutine or_large(set1, set2) type(bitset_large), intent(inout) :: set1 type(bitset_large), intent(in) :: set2 end subroutine or_large elemental module subroutine or_64(set1, set2) -!! Version: experimental -!! -!! Sets the bits in `set1` to the bitwise `or` of the original bits in `set1` -!! and `set2`. The sets must have the same number of bits otherwise -!! the result is undefined. type(bitset_64), intent(inout) :: set1 type(bitset_64), intent(in) :: set2 end subroutine or_64 @@ -1726,13 +1713,12 @@ module stdlib_bitsets interface xor - - elemental module subroutine xor_large(set1, set2) !! Version: experimental !! !! Sets the bits in `set1` to the bitwise `xor` of the original bits in `set1` -!! and `set2`. The sets must have the same number of bits otherwise -!! the result is undefined. +!! and `set2`. The sets must have the same number of bits +!! otherwise the result is undefined. +!!([Specification](../page/specs/stdlib_bitsets.html#xor-bitwise-exclusive-or)) !! !!#### Example !! @@ -1756,16 +1742,12 @@ module stdlib_bitsets !! if ( none(set0) ) write(*,*) 'Fourth test of XOR worked.' !! end program demo_xor !!``` + elemental module subroutine xor_large(set1, set2) type(bitset_large), intent(inout) :: set1 type(bitset_large), intent(in) :: set2 end subroutine xor_large elemental module subroutine xor_64(set1, set2) -!! Version: experimental -!! -!! Sets the bits in `set1` to the bitwise `xor` of the original bits in `set1` -!! and `set2`. The sets must have the same number of bits -!! otherwise the result is undefined. type(bitset_64), intent(inout) :: set1 type(bitset_64), intent(in) :: set2 end subroutine xor_64 @@ -1774,13 +1756,12 @@ module stdlib_bitsets interface operator(==) - - elemental module function eqv_large(set1, set2) result(eqv) !! Version: experimental !! !! Returns `.true.` if all bits in `set1` and `set2` have the same value, !! `.false.` otherwise. The sets must have the same number of bits !! otherwise the result is undefined. +!!([Specification](../page/specs/stdlib_bitsets.html#-compare-two-bitsets-to-determine-whether-the-bits-have-the-same-value)) !! !!#### Example !! @@ -1802,16 +1783,12 @@ module stdlib_bitsets !! end if !! end program demo_equality !!``` + elemental module function eqv_large(set1, set2) result(eqv) logical :: eqv type(bitset_large), intent(in) :: set1, set2 end function eqv_large elemental module function eqv_64(set1, set2) result(eqv) -!! Version: experimental -!! -!! Returns `.true.` if all bits in `set1` and `set2` have the same value, -!! `.false.` otherwise. The sets must have the same number of bits -!! otherwise the result is undefined. logical :: eqv type(bitset_64), intent(in) :: set1, set2 end function eqv_64 @@ -1820,13 +1797,12 @@ module stdlib_bitsets interface operator(/=) - - elemental module function neqv_large(set1, set2) result(neqv) !! Version: experimental !! !! Returns `.true.` if not all bits in `set1` and `set2` have the same value, !! `.false.` otherwise. The sets must have the same number of bits !! otherwise the result is undefined. +!!([Specification](../page/specs/stdlib_bitsets.html#-compare-two-bitsets-to-determine-whether-any-bits-differ-in-value)) !! !!#### Example !! @@ -1848,16 +1824,12 @@ module stdlib_bitsets !! end if !! end program demo_inequality !!``` + elemental module function neqv_large(set1, set2) result(neqv) logical :: neqv type(bitset_large), intent(in) :: set1, set2 end function neqv_large elemental module function neqv_64(set1, set2) result(neqv) -!! Version: experimental -!! -!! Returns `.true.` if not all bits in `set1` and `set2 have the same value, -!! `.false.` otherwise. The sets must have the same number of bits -!! otherwise the result is undefined. logical :: neqv type(bitset_64), intent(in) :: set1, set2 end function neqv_64 @@ -1866,14 +1838,13 @@ module stdlib_bitsets interface operator(>) - - elemental module function gt_large(set1, set2) result(gt) !! Version: experimental !! !! Returns `.true.` if the bits in `set1` and `set2` differ and the !! highest order different bit is set to 1 in `set1` and to 0 in `set2`, !! `.false.` otherwise. The sets must have the same number of bits !! otherwise the result is undefined. +!!([Specification](../page/specs/stdlib_bitsets.html#gt-compare-two-bitsets-to-determine-whether-the-first-is-greater-than-the-other)) !! !!#### Example !! @@ -1895,17 +1866,12 @@ module stdlib_bitsets !! end if !! end program demo_gt !!``` + elemental module function gt_large(set1, set2) result(gt) logical :: gt type(bitset_large), intent(in) :: set1, set2 end function gt_large elemental module function gt_64(set1, set2) result(gt) -!! Version: experimental -!! -!! Returns `.true.` if the bits in `set1` and `set2` differ and the -!! highest order different bit is set to 1 in `set1` and to 0 in `set2`, -!! `.false.` otherwise. The sets must have the same number of bits -!! otherwise the result is undefined. logical :: gt type(bitset_64), intent(in) :: set1, set2 end function gt_64 @@ -1914,14 +1880,13 @@ module stdlib_bitsets interface operator(>=) - - elemental module function ge_large(set1, set2) result(ge) !! Version: experimental !! !! Returns `.true.` if the bits in `set1` and `set2` are the same or the !! highest order different bit is set to 1 in `set1` and to 0 in `set2`, !! `.false.` otherwise. The sets must have the same number of bits !! otherwise the result is undefined. +!! ([Specification](../page/specs/stdlib_bitsets.html#gt-compare-two-bitsets-to-determine-whether-the-first-is-greater-than-or-equal-to-the-second)) !! !!#### Example !! @@ -1944,17 +1909,12 @@ module stdlib_bitsets !! end if !! end program demo_ge !!``` + elemental module function ge_large(set1, set2) result(ge) logical :: ge type(bitset_large), intent(in) :: set1, set2 end function ge_large elemental module function ge_64(set1, set2) result(ge) -!! Version: experimental -!! -!! Returns `.true.` if the bits in `set1` and `set2` are the same or the -!! highest order different bit is set to 1 in `set1` and to 0 in `set2`, -!! `.false.` otherwise. The sets must have the same number of bits -!! otherwise the result is undefined. logical :: ge type(bitset_64), intent(in) :: set1, set2 end function ge_64 @@ -1963,14 +1923,13 @@ module stdlib_bitsets interface operator(<) - - elemental module function lt_large(set1, set2) result(lt) !! Version: experimental !! !! Returns `.true.` if the bits in `set1` and `set2` differ and the !! highest order different bit is set to 0 in `set1` and to 1 in `set2`, !! `.false.` otherwise. The sets must have the same number of bits !! otherwise the result is undefined. +!!([Specification](../page/specs/stdlib_bitsets.html#lt-compare-two-bitsets-to-determine-whether-the-first-is-less-than-the-other)) !! !!#### Example !! @@ -1992,17 +1951,12 @@ module stdlib_bitsets !! end if !! end program demo_lt !!``` + elemental module function lt_large(set1, set2) result(lt) logical :: lt type(bitset_large), intent(in) :: set1, set2 end function lt_large elemental module function lt_64(set1, set2) result(lt) -!! Version: experimental -!! -!! Returns `.true.` if the bits in `set1` and `set2` differ and the -!! highest order different bit is set to 0 in `set1` and to 1 in `set2`, -!! `.false.` otherwise. The sets must have the same number of bits -!! otherwise the result is undefined. logical :: lt type(bitset_64), intent(in) :: set1, set2 end function lt_64 @@ -2011,14 +1965,13 @@ module stdlib_bitsets interface operator(<=) - - elemental module function le_large(set1, set2) result(le) !! Version: experimental !! !! Returns `.true.` if the bits in `set1` and `set2` are the same or the !! highest order different bit is set to 0 in `set1` and to 1 in `set2`, !! `.false.` otherwise. The sets must have the same number of bits !! otherwise the result is undefined. +!!([Specification](../page/specs/stdlib_bitsets.html#lt-compare-two-bitsets-to-determine-whether-the-first-is-less-than-or-equal-to-the-other)) !! !!#### Example !! @@ -2041,17 +1994,12 @@ module stdlib_bitsets !! end if !! end program demo_le !!``` + elemental module function le_large(set1, set2) result(le) logical :: le type(bitset_large), intent(in) :: set1, set2 end function le_large elemental module function le_64(set1, set2) result(le) -!! Version: experimental -!! -!! Returns `.true.` if the bits in `set1` and `set2` are the same or the -!! highest order different bit is set to 0 in `set1` and to 1 in `set2`, -!! `.false.` otherwise. The sets must have the same number of bits -!! otherwise the result is undefined. logical :: le type(bitset_64), intent(in) :: set1, set2 end function le_64 From d1bf5d08bef451ea1b63ab2658ae95cb37c2606f Mon Sep 17 00:00:00 2001 From: Jeremie Vandenplas Date: Tue, 24 Nov 2020 21:40:30 +0100 Subject: [PATCH 3/4] bitset_specs: correction subtitle --- doc/specs/stdlib_bitsets.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/specs/stdlib_bitsets.md b/doc/specs/stdlib_bitsets.md index 30a14266a..8a4d482c4 100644 --- a/doc/specs/stdlib_bitsets.md +++ b/doc/specs/stdlib_bitsets.md @@ -298,7 +298,7 @@ otherwise it is `.false.`. end program demo_all ``` -#### `and` - bitwise `and` of the bits of two bitsets. +### `and` - bitwise `and` of the bits of two bitsets. #### Status From 4615ed4749937b8d5912ec878ded049a4a7e8e75 Mon Sep 17 00:00:00 2001 From: Jeremie Vandenplas Date: Tue, 24 Nov 2020 21:46:08 +0100 Subject: [PATCH 4/4] bitset_specs: subtitles --- doc/specs/stdlib_bitsets.md | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/doc/specs/stdlib_bitsets.md b/doc/specs/stdlib_bitsets.md index 8a4d482c4..ca9d517d5 100644 --- a/doc/specs/stdlib_bitsets.md +++ b/doc/specs/stdlib_bitsets.md @@ -250,7 +250,7 @@ are summarized in the following table: ## Specification of the `stdlib_bitsets` methods and procedures -### `all` - determine whether all bits are set in `self`. +### `all` - determine whether all bits are set in `self` #### Status @@ -298,7 +298,7 @@ otherwise it is `.false.`. end program demo_all ``` -### `and` - bitwise `and` of the bits of two bitsets. +### `and` - bitwise `and` of the bits of two bitsets #### Status @@ -546,7 +546,7 @@ the number of defined bits in `self`. end program demo_bits ``` -### `clear` - clears a sequence of one or more bits. +### `clear` - clears a sequence of one or more bits #### Status @@ -1023,7 +1023,7 @@ complement of their values on input. end program demo_not ``` -### `or` - Bitwise OR of the bits of two bitsets. +### `or` - Bitwise OR of the bits of two bitsets #### Status @@ -1262,7 +1262,7 @@ as its error code. The possible error codes are: end program demo_read_bitset ``` -### `set` - sets a sequence of one or more bits to 1. +### `set` - sets a sequence of one or more bits to 1 #### Status