Used to define assignment for bitset_large
.
(Specification)
program example_assignment
use stdlib_bitsets
logical(int8) :: logical1(64) = .true.
logical(int32), allocatable :: logical2(:)
type(bitset_64) :: set0, set1
set0 = logical1
if ( set0 % bits() /= 64 ) then
error stop procedure // &
' initialization with logical(int8) failed to set' // &
' the right size.'
else if ( .not. set0 % all() ) then
error stop procedure // ' initialization with' // &
' logical(int8) failed to set the right values.'
else
write(*,*) 'Initialization with logical(int8) succeeded.'
end if
set1 = set0
if ( set1 == set0 ) &
write(*,*) 'Initialization by assignment succeeded'
logical2 = set1
if ( all( logical2 ) ) then
write(*,*) 'Initialization of logical(int32) succeeded.'
end if
end program example_assignment
Used to define assignment from an array of type logical(int16)
to a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int16), | intent(in) | :: | logical_vector(:) |
Used to define assignment from an array of type logical(int32)
to a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int32), | intent(in) | :: | logical_vector(:) |
Used to define assignment from an array of type logical(int64)
to a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int64), | intent(in) | :: | logical_vector(:) |
Used to define assignment from an array of type logical(int8)
to a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(bitset_large), | intent(out) | :: | self | |||
logical(kind=int8), | intent(in) | :: | logical_vector(:) |
Used to define assignment to an array of type logical(int16)
from a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
logical(kind=int16), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |
Used to define assignment to an array of type logical(int32)
from a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
logical(kind=int32), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |
Used to define assignment to an array of type logical(int64)
from a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
logical(kind=int64), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |
Used to define assignment to an array of type logical(int8)
from a
bitset_large
.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
logical(kind=int8), | intent(out), | allocatable | :: | logical_vector(:) | ||
type(bitset_large), | intent(in) | :: | set |