Bit-level inquiry and manipulation#
bge#
Name#
bge(3) - [BIT:COMPARE] Bitwise greater than or equal to
Syntax#
result = bge(i, j)
Description#
Determines whether an integer is bitwise greater than or equal to another.
Arguments#
- i
Shall be of integer type.
- j
Shall be of integer type, and of the same kind as i.
Returns#
The return value is of type logical and of the default kind.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
bgt#
Name#
bgt(3) - [BIT:COMPARE] Bitwise greater than
Syntax#
result = bgt(i, j)
Description#
Determines whether an integer is bitwise greater than another.
Arguments#
- i
Shall be of integer type or a BOZ literal constant.
- j
Shall be of integer type, and of the same kind as i; or a BOZ literal constant.
Returns#
The return value is of type logical and of the default kind. The result is true if the sequence of bits represented by i is greater than the sequence of bits represented by j, otherwise the result is false.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
ble#
Name#
ble(3) - [BIT:COMPARE] Bitwise less than or equal to
Syntax#
result = ble(i, j)
Description#
Determines whether an integer is bitwise less than or equal to another.
Arguments#
- i
Shall be of integer type.
- j
Shall be of integer type, and of the same kind as i.
Returns#
The return value is of type logical and of the default kind.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
blt#
Name#
blt(3) - [BIT:COMPARE] Bitwise less than
Syntax#
result = blt(i, j)
Description#
Determines whether an integer is bitwise less than another.
Arguments#
- i
Shall be of integer type.
- j
Shall be of integer type, and of the same kind as i.
Returns#
The return value is of type logical and of the default kind.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
bit_size#
Name#
bit_size(3) - [BIT:INQUIRY] Bit size inquiry function
Syntax#
result = bit_size(i)
function(kind=KIND) :: bit_size
integer(kind=KIND),intent(in) :: ii
Description#
bit_size(i) returns the number of bits (integer precision plus sign bit) represented by the type of the integer i. i can be a scalar or an array.
Arguments#
- i
An integer value of any kind to determine the size of in bits. Because only the type of the argument is examined, the argument need not be defined.
Returns#
Returns the number of bits used to represent a value of the type
of __i__. The result is a _integer_ scalar of the same kind as __i__.
Examples#
Sample program:
program demo_bit_size
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer(kind=int64) :: answer
integer :: ilen
character(len=*),parameter :: fmt='(*(g0,1x))'
write(*,fmt)'default integer size is',bit_size(0),'bits'
write(*,fmt)bit_size(bit_size(0_int8)), 'which is kind=',kind(0_int8)
write(*,fmt)bit_size(bit_size(0_int16)),'which is kind=',kind(0_int16)
write(*,fmt)bit_size(bit_size(0_int32)),'which is kind=',kind(0_int32)
write(*,fmt)bit_size(bit_size(0_int64)),'which is kind=',kind(0_int64)
! Check size of value not explicitly defined.
write(*,fmt) int(bit_size(answer))
end program demo_bit_size
Typical Results:
default integer size is 32 bits
8 which is kind= 1
16 which is kind= 2
32 which is kind= 4
64 which is kind= 8
64
Standard#
Fortran 95 and later
####### fortran-lang intrinsic descriptions (license MIT) @urbanjost
btest#
Name#
btest(3) - [BIT:INQUIRY] Tests a bit of an integer value.
Syntax#
result = btest(i, pos)
integer(kind=KIND) elemental function btest(i,pos)
integer,intent(in) :: i
logical,intent(out) :: pos
where KIND is any integer kind supported by the programming environment.
Description#
btest(i,pos) returns logical .true. if the bit at pos in i is set.
Arguments#
- i
The type shall be integer.
- pos
The bit position to query. it must be a valid position for the value i; ie. 0 <= pos <= bit_size(i) .
A value of zero refers to the least significant bit.
Returns#
The result is a logical that has the value .true. if bit position pos of i has the value 1 and the value .false. if bit pos of i has the value 0.
Examples#
Sample program:
program demo_btest
implicit none
integer :: i, j, pos, a(2,2)
logical :: bool
character(len=*),parameter :: g='(*(g0))'
i = 32768 + 1024 + 64
write(*,'(a,i0,"=>",b32.32,/)')'Looking at the integer: ',i
! looking one bit at a time from LOW BIT TO HIGH BIT
write(*,g)'from bit 0 to bit ',bit_size(i),'==>'
do pos=0,bit_size(i)-1
bool = btest(i, pos)
write(*,'(l1)',advance='no')bool
enddo
write(*,*)
! a binary format the hard way.
! Note going from bit_size(i) to zero.
write(*,*)
write(*,g)'so for ',i,' with a bit size of ',bit_size(i)
write(*,'(b32.32)')i
write(*,g)merge('^','_',[(btest(i,j),j=bit_size(i)-1,0,-1)])
write(*,*)
write(*,g)'and for ',-i,' with a bit size of ',bit_size(i)
write(*,'(b32.32)')-i
write(*,g)merge('^','_',[(btest(-i,j),j=bit_size(i)-1,0,-1)])
! elemental:
!
a(1,:)=[ 1, 2 ]
a(2,:)=[ 3, 4 ]
write(*,*)
write(*,'(a,/,*(i2,1x,i2,/))')'given the array a ...',a
! the second bit of all the values in a
write(*,'(a,/,*(l2,1x,l2,/))')'the value of btest (a, 2)',btest(a,2)
! bits 1,2,3,4 of the value 2
write(*,'(a,/,*(l2,1x,l2,/))')'the value of btest (2, a)',btest(2,a)
end program demo_btest
Results:
Looking at the integer: 33856=>11111111111111110111101111000000
00000000000000001000010001000000
11111111111111110111101111000000
1000010001000000
11111111111111110111101111000000
from bit 0 to bit 32==>
FFFFFFTFFFTFFFFTFFFFFFFFFFFFFFFF
so for 33856 with a bit size of 32
00000000000000001000010001000000
________________^____^___^______
and for -33856 with a bit size of 32
11111111111111110111101111000000
^^^^^^^^^^^^^^^^_^^^^_^^^^______
given the array a ...
1 3
2 4
the value of btest (a, 2)
F F
F T
the value of btest (2, a)
T F
F F
Standard#
Fortran 95 and later
See Also#
ieor(3), ibclr(3), not(3), ibclr(3), ibits(3), ibset(3), iand(3), ior(3), ieor(3), mvbits(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
storage_size#
Name#
storage_size(3) - [BIT:INQUIRY] Storage size in bits
Syntax#
result = storage_size(a, kind)
Description#
Returns the storage size of argument a in bits.
Arguments#
- a
Shall be a scalar or array of any type.
- kind
(Optional) shall be a scalar integer constant expression.
Returns#
The result is a scalar integer with the kind type parameter specified by kind (or default integer type if kind is missing). The result value is the size expressed in bits for an element of an array that has the dynamic type and type parameters of a.
Examples#
Sample program
program demo_storage_size
implicit none
write(*,*)'size of integer ',storage_size(0)
write(*,*)'size of real ',storage_size(0.0)
write(*,*)'size of logical ',storage_size(.true.)
write(*,*)'size of complex ',storage_size((0.0,0.0))
write(*,*)'size of integer array ',storage_size([0,1,2,3,4,5,6,7,8,9])
end program demo_storage_size
Results:
size of integer 32
size of real 32
size of logical 32
size of complex 64
size of integer array 32
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
leadz#
Name#
leadz(3) - [BIT:COUNT] Number of leading zero bits of an integer
Syntax#
result = leadz(i)
Description#
leadz returns the number of leading zero bits of an integer.
Arguments#
- i
Shall be of type integer.
Returns#
The type of the return value is the same as a default integer. If all the bits of i are zero, the result value is bit_size(i).
Examples#
Sample program:
program demo_leadz
implicit none
integer :: value, i
character(len=80) :: f
write(*,'(*(g0))')'BIT_SIZE=',bit_size(value)
! make a format statement for writing a value as a bit string
write(f,'("(b",i0,".",i0,")")')bit_size(value),bit_size(value)
! show output for various integer values
value=0
do i=0,bit_size(value)-1
write (*,'("LEADING ZERO BITS=",i3,1x)') leadz(value)
write (*,'(" FOR VALUE ")',advance='no')
write(*,f,advance='no') value
write(*,'(*(1x,g0))') "OR",value
value=value+2**(i)
enddo
end program demo_leadz
Results:
BIT_SIZE=32
LEADING ZERO BITS= 32
FOR VALUE 00000000000000000000000000000000 OR 0
LEADING ZERO BITS= 31
FOR VALUE 00000000000000000000000000000001 OR 1
LEADING ZERO BITS= 30
FOR VALUE 00000000000000000000000000000011 OR 3
LEADING ZERO BITS= 29
FOR VALUE 00000000000000000000000000000111 OR 7
LEADING ZERO BITS= 28
FOR VALUE 00000000000000000000000000001111 OR 15
LEADING ZERO BITS= 27
FOR VALUE 00000000000000000000000000011111 OR 31
LEADING ZERO BITS= 26
FOR VALUE 00000000000000000000000000111111 OR 63
LEADING ZERO BITS= 25
FOR VALUE 00000000000000000000000001111111 OR 127
LEADING ZERO BITS= 24
FOR VALUE 00000000000000000000000011111111 OR 255
LEADING ZERO BITS= 23
FOR VALUE 00000000000000000000000111111111 OR 511
LEADING ZERO BITS= 22
FOR VALUE 00000000000000000000001111111111 OR 1023
LEADING ZERO BITS= 21
FOR VALUE 00000000000000000000011111111111 OR 2047
LEADING ZERO BITS= 20
FOR VALUE 00000000000000000000111111111111 OR 4095
LEADING ZERO BITS= 19
FOR VALUE 00000000000000000001111111111111 OR 8191
LEADING ZERO BITS= 18
FOR VALUE 00000000000000000011111111111111 OR 16383
LEADING ZERO BITS= 17
FOR VALUE 00000000000000000111111111111111 OR 32767
LEADING ZERO BITS= 16
FOR VALUE 00000000000000001111111111111111 OR 65535
LEADING ZERO BITS= 15
FOR VALUE 00000000000000011111111111111111 OR 131071
LEADING ZERO BITS= 14
FOR VALUE 00000000000000111111111111111111 OR 262143
LEADING ZERO BITS= 13
FOR VALUE 00000000000001111111111111111111 OR 524287
LEADING ZERO BITS= 12
FOR VALUE 00000000000011111111111111111111 OR 1048575
LEADING ZERO BITS= 11
FOR VALUE 00000000000111111111111111111111 OR 2097151
LEADING ZERO BITS= 10
FOR VALUE 00000000001111111111111111111111 OR 4194303
LEADING ZERO BITS= 9
FOR VALUE 00000000011111111111111111111111 OR 8388607
LEADING ZERO BITS= 8
FOR VALUE 00000000111111111111111111111111 OR 16777215
LEADING ZERO BITS= 7
FOR VALUE 00000001111111111111111111111111 OR 33554431
LEADING ZERO BITS= 6
FOR VALUE 00000011111111111111111111111111 OR 67108863
LEADING ZERO BITS= 5
FOR VALUE 00000111111111111111111111111111 OR 134217727
LEADING ZERO BITS= 4
FOR VALUE 00001111111111111111111111111111 OR 268435455
LEADING ZERO BITS= 3
FOR VALUE 00011111111111111111111111111111 OR 536870911
LEADING ZERO BITS= 2
FOR VALUE 00111111111111111111111111111111 OR 1073741823
LEADING ZERO BITS= 1
FOR VALUE 01111111111111111111111111111111 OR 2147483647
Standard#
Fortran 2008 and later
See Also#
bit_size(3), popcnt(3), poppar(3), trailz(3)
####### fortran-lang intrinsic descriptions
popcnt#
Name#
popcnt(3) - [BIT:COUNT] Number of bits set
Syntax#
result = popcnt(i)
Description#
Returns the number of bits set in the binary representation of an integer.
Arguments#
- i
Shall be of type integer.
Returns#
The return value is of type integer and of the default integer kind.
Examples#
Sample program:
program demo_popcnt
use, intrinsic :: iso_fortran_env, only : integer_kinds, &
& int8, int16, int32, int64
implicit none
print *, popcnt(127), poppar(127)
print *, popcnt(huge(0)), poppar(huge(0))
print *, popcnt(huge(0_int8)), poppar(huge(0_int8))
print *, popcnt(huge(0_int16)), poppar(huge(0_int16))
print *, popcnt(huge(0_int32)), poppar(huge(0_int32))
print *, popcnt(huge(0_int64)), poppar(huge(0_int64))
end program demo_popcnt
Results:
7 1
31 1
7 1
15 1
31 1
63 1
Standard#
Fortran 2008 and later
See Also#
poppar(3), leadz(3), trailz(3)
####### fortran-lang intrinsic descriptions
poppar#
Name#
poppar(3) - [BIT:COUNT] Parity of the number of bits set
Syntax#
result = poppar(i)
Description#
Returns the parity of an integer’s binary representation (i.e., the parity of the number of bits set).
Arguments#
- i
Shall be of type integer.
Returns#
The return value is equal to 0 if i has an even number of bits set and 1 if an odd number of bits are set.
It is of type integer and of the default integer kind.
Examples#
Sample program:
program demo_popcnt
use, intrinsic :: iso_fortran_env, only : integer_kinds, &
& int8, int16, int32, int64
implicit none
print *, popcnt(127), poppar(127)
print *, popcnt(huge(0_int8)), poppar(huge(0_int8))
print *, popcnt(huge(0_int16)), poppar(huge(0_int16))
print *, popcnt(huge(0_int32)), poppar(huge(0_int32))
print *, popcnt(huge(0_int64)), poppar(huge(0_int64))
end program demo_popcnt
Results:
7 1
7 1
15 1
31 1
63 1
Standard#
Fortran 2008 and later
See Also#
popcnt(3), leadz(3), trailz(3)
####### fortran-lang intrinsic descriptions
trailz#
Name#
trailz(3) - [BIT:COUNT] Number of trailing zero bits of an integer
Syntax#
result = trailz(i) integer :: result
integer(kind=NNN),intent(in) :: i
Description#
trailz(3) returns the number of trailing zero bits of an integer value
Arguments#
- i
Shall be of type integer.
Returns#
The type of the return value is the default integer. If all the bits of I are zero, the result value is bit_size(i).
Examples#
Sample program:
program demo_trailz
use, intrinsic :: iso_fortran_env, only : integer_kinds, &
& int8, int16, int32, int64
implicit none
integer(kind=int64) :: i, value
write(*,*)'Default integer:'
write(*,*)'bit_size=',bit_size(0)
write(*,'(1x,i3,1x,i3,1x,b0)')-1,trailz(1),-1
write(*,'(1x,i3,1x,i3,1x,b0)')0,trailz(0),0
write(*,'(1x,i3,1x,i3,1x,b0)')1,trailz(1),1
write(*,'(" huge(0)=",i0,1x,i0,1x,b0)') &
& huge(0),trailz(huge(0)),huge(0)
write(*,*)
write(*,*)'integer(kind=int64):'
do i=-1,62,5
value=2**i
write(*,'(1x,i19,1x,i3)')value,trailz(value)
enddo
value=huge(i)
write(*,'(1x,i19,1x,i3,"(huge(0_int64))")')value,trailz(value)
do i=-1,62,5
value=2**i
write(*,'(1x,i3,2x,b64.64)')i,value
enddo
value=huge(i)
write(*,'(1x,a,1x,b64.64)') "huge",value
end program demo_trailz
Results:
Default integer:
bit_size= 32
-1 0 11111111111111111111111111111111
0 32 0
1 0 1
huge(0)=2147483647 0 1111111111111111111111111111111
integer(kind=int64):
0 64
16 4
512 9
16384 14
524288 19
16777216 24
536870912 29
17179869184 34
549755813888 39
17592186044416 44
562949953421312 49
18014398509481984 54
576460752303423488 59
9223372036854775807 0(huge(0_int64))
-1 0000000000000000000000000000000000000000000000000000000000000000
4 0000000000000000000000000000000000000000000000000000000000010000
9 0000000000000000000000000000000000000000000000000000001000000000
14 0000000000000000000000000000000000000000000000000100000000000000
19 0000000000000000000000000000000000000000000010000000000000000000
24 0000000000000000000000000000000000000001000000000000000000000000
29 0000000000000000000000000000000000100000000000000000000000000000
34 0000000000000000000000000000010000000000000000000000000000000000
39 0000000000000000000000001000000000000000000000000000000000000000
44 0000000000000000000100000000000000000000000000000000000000000000
49 0000000000000010000000000000000000000000000000000000000000000000
54 0000000001000000000000000000000000000000000000000000000000000000
59 0000100000000000000000000000000000000000000000000000000000000000
huge 0111111111111111111111111111111111111111111111111111111111111111
Standard#
Fortran 2008 and later
See Also#
bit_size(3), popcnt(3), poppar(3), leadz(3)
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
dshiftl#
Name#
dshiftl(3) - [BIT:COPY] combines bits of arguments i and j
Syntax#
result = dshiftl(i, j, shift)
Description#
dshiftl(i, j, shift) combines bits of i and j. The rightmost shift bits of the result are the leftmost shift bits of j, and the remaining bits are the rightmost bits of i.
Arguments#
- i
Shall be of type integer.
- j
Shall be of type integer, and of the same kind as i.
- shift
Shall be of type integer.
Returns#
The return value has same type and kind as i.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
dshiftr#
Name#
dshiftr(3) - [BIT:COPY] combines bits of arguments i and j
Syntax#
result = dshiftr(i, j, shift)
Description#
dshiftr(i, j, shift) combines bits of i and j. The leftmost shift bits of the result are the rightmost shift bits of i, and the remaining bits are the leftmost bits of j.
Arguments#
- i
Shall be of type integer.
- j
Shall be of type integer, and of the same kind as i.
- shift
Shall be of type integer.
Returns#
The return value has same type and kind as i.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
merge_bits#
Name#
merge_bits(3) - [BIT:COPY] Merge bits using a mask
Syntax#
result = merge_bits(i, j, mask)
elemental function merge_bits(i,j,mask) result(r)
integer(kind=KIND) ,intent(in) :: i, j, mask
integer(kind=KIND) :: r
where the result and all input values have the same integer type and KIND with the exception that the mask and either i or j may be a BOZ constant.
Description#
A common graphics operation in Ternary Raster Operations is to combine bits from two different sources, generally referred to as bit-blending. merge_bits performs a masked bit-blend of i and j using the bits of the mask value to determine which of the input values to copy bits from.
Specifically, The k-th bit of the result is equal to the k-th bit of i if the k-th bit of mask is 1; it is equal to the k-th bit of j otherwise (so all three input values must have the same number of bits).
The resulting value is the same as would result from
__ior (iand (i, mask),iand (j, not (mask)))__
An exception to all values being of the same integer type is that i or j and/or the mask may be a BOZ constant (A BOZ constant means it is either a Binary, Octal, or Hexadecimal literal constant). The BOZ values are converted to the integer type of the non-BOZ value(s) as if called by the intrinsic function int() with the kind of the non-BOZ value(s), so the BOZ values must be in the range of the type of the result.
Arguments#
i : value to select bits from when the associated bit in the mask is 1.
j : value to select bits from when the associated bit in the mask is 0.
mask : a value whose bits are used as a mask to select bits from i and j
Returns#
The bits blended from i and j using the mask mask. It is the same type as i if i is of type integer, otherwise the same type as j.
Example#
program demo_merge_bits
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer(kind=int16) :: if_one,if_zero,msk
character(len=*),parameter :: fmt='(*(g0, 1X))'
! basic usage
print *,'MERGE_BITS( 5,10,41) should be 3.=>',merge_bits(5,10,41)
print *,'MERGE_BITS(13,18,22) should be 4.=>',merge_bits(13,18,22)
! use some values in base2 illustratively:
if_one =int(b'1010101010101010',kind=int16)
if_zero=int(b'0101010101010101',kind=int16)
msk=int(b'0101010101010101',kind=int16)
print '("should get all zero bits =>",b16.16)', &
& merge_bits(if_one,if_zero,msk)
msk=int(b'1010101010101010',kind=int16)
print '("should get all ones bits =>",b16.16)', &
& merge_bits(if_one,if_zero,msk)
! using BOZ values
print fmt, &
& merge_bits(32767_int16, o'12345', 32767_int16), &
& merge_bits(o'12345' , 32767_int16, b'0000000000010101'), &
& merge_bits(32767_int16, o'12345', z'1234')
! a do-it-yourself equivalent for comparison and validation
print fmt, &
& ior(iand(32767_int16, 32767_int16), &
& iand(o'12345', not(32767_int16))), &
& ior(iand(o'12345', int(o'12345', kind=int16)), &
& iand(32767_int16, not(int(o'12345', kind=int16)))), &
& ior(iand(32767_int16, z'1234'), &
& iand(o'12345', not(int( z'1234', kind=int16))))
end program demo_merge_bits
Results:
MERGE_BITS( 5,10,41) should be 3.=> 3
MERGE_BITS(13,18,22) should be 4.=> 4
should get all zero bits =>0000000000000000
should get all ones bits =>1111111111111111
32767 32751 5877
32767 32767 5877
Standard#
Fortran 2008 and later
####### fortran-lang intrinsic descriptions (license MIT) @urbanjost
mvbits#
Name#
mvbits(3) - [BIT:COPY] reproduce bit patterns found in one integer in another
Syntax#
call mvbits(from, frompos, len, to, topos)
Description#
mvbits(3f) copies a bit pattern found in a range of adjacent bits in the integer from to a specified position in another integer to (which is of the same kind as from). It otherwise leaves the bits in to as-is.
The bit positions copied must exist within the value of from. That is, the values of frompos+len-1 and topos+len-1 must be nonnegative and less than bit_size(from).
The bits are numbered 0 to bit_size(i)-1, from right to left.
Arguments#
- from
An integer to read bits from.
- frompos
frompos is the position of the first bit to copy. It is a nonnegative integer value < bit_size(from).
- len
A nonnegative integer value that indicates how many bits to copy from from. It must not specify copying bits past the end of from. That is, frompos + len must be less than or equal to bit_size(from).
- to
The integer variable to place the copied bits into. It must be of the same kind as from and may even be the same variable as from.
- to
is set by copying the sequence of bits of length len, starting at position frompos of from to position topos of to. No other bits of to are altered. On return, the len bits of to starting at topos are equal to the value that the len bits of from starting at frompos had on entry.
- topos
A nonnegative integer value indicating the starting location in to to place the specified copy of bits from from. topos + len must be less than or equal to bit_size(to).
Example#
Sample program that populates a new 32-bit integer with its bytes in reverse order (ie. changes the Endian of the integer).
program demo_mvbits
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer(kind=int32) :: intfrom, intto, abcd_int
character(len=*),parameter :: bits= '(g0,t30,b32.32)'
character(len=*),parameter :: fmt= '(g0,t30,a,t40,b32.32)'
intfrom=huge(0) ! all bits are 1 accept the sign bit
intto=0 ! all bits are 0
!! CHANGE BIT 0
! show the value and bit pattern
write(*,bits)intfrom,intfrom
write(*,bits)intto,intto
! copy bit 0 from intfrom to intto to show the rightmost bit changes
! (from, frompos, len, to, topos)
call mvbits(intfrom, 0, 1, intto, 0) ! change bit 0
write(*,bits)intto,intto
!! COPY PART OF A VALUE TO ITSELF
call mvbits(intfrom,0,1,intfrom,31) ! can copy bit from a value to itself
write(*,bits)intfrom,intfrom
!! MOVING BYTES AT A TIME
! make native integer value with bit patterns
! that happen to be the same as the beginning of the alphabet
! to make it easy to see the bytes are reversed
abcd_int=transfer('abcd',0)
! show the value and bit pattern
write(*,*)'native'
write(*,fmt)abcd_int,abcd_int,abcd_int
! change endian of the value
abcd_int=int_swap32(abcd_int)
! show the values and their bit pattern
write(*,*)'non-native'
write(*,fmt)abcd_int,abcd_int,abcd_int
contains
pure elemental function int_swap32(intin) result(intout)
! Convert a 32 bit integer from big Endian to little Endian,
! or conversely from little Endian to big Endian.
!
integer(kind=int32), intent(in) :: intin
integer(kind=int32) :: intout
! copy bytes from input value to new position in output value
! (from, frompos, len, to, topos)
call mvbits(intin, 0, 8, intout, 24) ! byte1 to byte4
call mvbits(intin, 8, 8, intout, 16) ! byte2 to byte3
call mvbits(intin, 16, 8, intout, 8) ! byte3 to byte2
call mvbits(intin, 24, 8, intout, 0) ! byte4 to byte1
end function int_swap32
end program demo_mvbits
Results:
```text
2147483647 01111111111111111111111111111111
0 00000000000000000000000000000000
1 00000000000000000000000000000001
-1 11111111111111111111111111111111
native
1684234849 abcd 01100100011000110110001001100001
non-native
1633837924 dcba 01100001011000100110001101100100
================================================================================
Standard#
Fortran 95 and later
See Also#
ieor(3), ibclr(3), not(3), btest(3), ibclr(3), ibits(3), ibset(3), iand(3), ior(3), ieor(3)
####### fortran-lang intrinsic descriptions (license MIT) @urbanjost
ibits#
Name#
ibits(3) - [BIT:COPY] Bit extraction
Syntax#
result = ibits(i, pos, len)
Description#
ibits extracts a field of length len from i, starting from bit position pos and extending left for len bits. The result is right-justified and the remaining bits are zeroed. The value of pos+len must be less than or equal to the value bit_size(i).
Arguments#
- i
The type shall be integer.
- pos
The type shall be integer. A value of zero refers to the least significant bit.
- len
The type shall be integer.
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 95 and later
See Also#
ieor(3), ibclr(3), not(3), btest(3), ibclr(3), ibset(3), iand(3), ior(3), ieor(3), mvbits(3)
####### fortran-lang intrinsic descriptions
ibclr#
Name#
ibclr(3) - [BIT:SET] Clear bit
Syntax#
result = ibclr(i, pos)
Description#
ibclr returns the value of i with the bit at position pos set to zero.
Arguments#
- i
The type shall be integer.
- pos
The type shall be integer. A value of zero refers to the least significant bit. pos is an intent(in) scalar or array of type integer. The value of pos must be within the range zero to (bit_size(i)-1).
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 95 and later
See Also#
ieor(3), not(3), btest(3), ibclr(3), ibits(3), ibset(3), iand(3), ior(3), ieor(3), mvbits(3)
####### fortran-lang intrinsic descriptions
ibset#
Name#
ibset(3) - [BIT:SET] Set bit
Syntax#
result = ibset(i, pos)
Description#
ibset returns the value of i with the bit at position pos set to one.
Arguments#
- i
The type shall be integer.
- pos
The type shall be integer. A value of zero refers to the least significant bit. pos is an intent(in) scalar or array of type integer. The value of pos must be within the range zero to (bit_size(i)-1).
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 95 and later
See Also#
ieor(3), ibclr(3), not(3), btest(3), ibclr(3), ibits(3), iand(3), ior(3), ieor(3), mvbits(3)
####### fortran-lang intrinsic descriptions
maskl#
Name#
maskl(3) - [BIT:SET] Generates a left justified mask
Syntax#
result = maskl(i, kind)
integer elemental function maskl(i,kind)
integer,intent(in),optional :: kind
Description#
maskl(i[, kind]) has its leftmost i bits set to 1, and the remaining bits set to 0.
Arguments#
- i
Shall be of type integer. Its value must be non-negative, and less than or equal to the number of bits for the kind of the result.
- kind
Shall be a scalar constant expression of type integer.
Returns#
The return value is of type integer. If kind is present, it specifies the kind value of the return type; otherwise, it is of the default integer kind.
The leftmost i bits are set to 1 and the other bits are set to 0.
Examples#
Sample program:
program demo_maskl
implicit none
integer :: i
i=maskl(1)
write(*,'(i0,1x,b0,/)') i,i
! elemental
write(*,'(*(i11,1x,b0,1x,/))') maskl([(i,i,i=1,bit_size(0))])
end program demo_maskl
Results:
-2147483648 10000000000000000000000000000000
0 0
-2147483648 10000000000000000000000000000000
-1073741824 11000000000000000000000000000000
-536870912 11100000000000000000000000000000
-268435456 11110000000000000000000000000000
-134217728 11111000000000000000000000000000
-67108864 11111100000000000000000000000000
-33554432 11111110000000000000000000000000
-16777216 11111111000000000000000000000000
-8388608 11111111100000000000000000000000
-4194304 11111111110000000000000000000000
-2097152 11111111111000000000000000000000
-1048576 11111111111100000000000000000000
-524288 11111111111110000000000000000000
-262144 11111111111111000000000000000000
-131072 11111111111111100000000000000000
-65536 11111111111111110000000000000000
-32768 11111111111111111000000000000000
-16384 11111111111111111100000000000000
-8192 11111111111111111110000000000000
-4096 11111111111111111111000000000000
-2048 11111111111111111111100000000000
-1024 11111111111111111111110000000000
-512 11111111111111111111111000000000
-256 11111111111111111111111100000000
-128 11111111111111111111111110000000
-64 11111111111111111111111111000000
-32 11111111111111111111111111100000
-16 11111111111111111111111111110000
-8 11111111111111111111111111111000
-4 11111111111111111111111111111100
-2 11111111111111111111111111111110
-1 11111111111111111111111111111111
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
maskr#
Name#
maskr(3) - [BIT:SET] Generates a right-justified mask
Syntax#
result = maskr(i, kind)
integer elemental function maskr(i,kind)
integer,intent(in),optional :: kind
Description#
maskr(i[, kind]) has its rightmost i bits set to 1, and the remaining bits set to 0.
Arguments#
- i
Shall be of type integer. Its value must be non-negative, and less than or equal to the number of bits for the kind of the result.
- kind
Shall be a scalar constant expression of type integer.
Returns#
The return value is of type integer. If kind is present, it specifies the kind value of the return type; otherwise, it is of the default integer kind.
It has its rightmost i bits set to 1, and the remaining bits set to 0.
Example#
Sample program:
program demo_maskr
implicit none
integer :: i
i=maskr(1)
write(*,'(i0,1x,b0,1x,b0/)') i,i, shiftl(7,bit_size(0)-1)
i=maskr(5)
write(*,'(i0,1x,b0,1x,b0/)') i,i, shiftl(7,bit_size(0)-5)
i=maskr(11)
write(*,'(i0,1x,b0,1x,b0/)') i,i, shiftl(7,bit_size(0)-11)
! elemental
write(*,'(*(i11,1x,b0,1x,/))') maskr([(i,i,i=0,bit_size(0))])
end program demo_maskr
Results:
1 1 10000000000000000000000000000000
31 11111 111000000000000000000000000000
2047 11111111111 111000000000000000000000
0 0
1 1
3 11
7 111
15 1111
31 11111
63 111111
127 1111111
255 11111111
511 111111111
1023 1111111111
2047 11111111111
4095 111111111111
8191 1111111111111
16383 11111111111111
32767 111111111111111
65535 1111111111111111
131071 11111111111111111
262143 111111111111111111
524287 1111111111111111111
1048575 11111111111111111111
2097151 111111111111111111111
4194303 1111111111111111111111
8388607 11111111111111111111111
16777215 111111111111111111111111
33554431 1111111111111111111111111
67108863 11111111111111111111111111
134217727 111111111111111111111111111
268435455 1111111111111111111111111111
536870911 11111111111111111111111111111
1073741823 111111111111111111111111111111
2147483647 1111111111111111111111111111111
-1 11111111111111111111111111111111
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
iparity#
Name#
iparity(3) - [BIT:LOGICAL] Bitwise exclusive or of array elements
Syntax#
result = iparity(array, mask)
or
result = iparity(array, dim, mask)
Description#
Reduces with bitwise xor (exclusive or) the elements of array along dimension dim if the corresponding element in mask is .true..
Arguments#
- array
Shall be an array of type integer
- dim
(Optional) shall be a scalar of type integer with a value in the range from „1“ to „n“, where „n“ equals the rank of array.
- mask
(Optional) shall be of type logical and either be a scalar or an array of the same shape as array.
Returns#
The result is of the same type as array.
If dim is absent, a scalar with the bitwise xor of all elements in array is returned. Otherwise, an array of rank n-1, where n equals the rank of array, and a shape similar to that of array with dimension dim dropped is returned.
Examples#
Sample program:
program demo_iparity
implicit none
integer, dimension(2) :: a
a(1) = int(b'00100100')
a(2) = int(b'01101010')
print '(b8.8)', iparity(a)
end program demo_iparity
Results:
01001110
Standard#
Fortran 2008 and later
See Also#
iany(3), iall(3), ieor(3), parity(3)
####### fortran-lang intrinsic descriptions
iall#
Name#
iall(3) - [BIT:LOGICAL] Bitwise and of array elements
Syntax#
result = iall(array, mask)
or
result = iall(array, dim, mask)
Description#
Reduces with bitwise and the elements of array along dimension dim if the corresponding element in mask is .true..
Arguments#
- array
Shall be an array of type integer
- dim
(Optional) shall be a scalar of type integer with a value in the range from 1 to n, where n equals the rank of array.
- mask
(Optional) shall be of type logical and either be a scalar or an array of the same shape as array.
Returns#
The result is of the same type as array.
If dim is absent, a scalar with the bitwise all of all elements in array is returned. Otherwise, an array of rank n-1, where n equals the rank of array, and a shape similar to that of array with dimension dim dropped is returned.
Examples#
Sample program:
program demo_iall
use, intrinsic :: iso_fortran_env, only : integer_kinds, &
& int8, int16, int32, int64
implicit none
integer(kind=int8) :: a(2)
a(1) = int(b'00100100')
a(2) = int(b'01101010')
print '(b8.8)', iall(a)
end program demo_iall
Results:
00100000
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
iand#
Name#
iand(3) - [BIT:LOGICAL] Bitwise logical and
Syntax#
result = iand(i, j)
Description#
Bitwise logical and.
Arguments#
- i
The type shall be integer.
- j
The type shall be integer, of the same kind as i.
Returns#
The return type is integer, of the same kind as the arguments. (If the argument kinds differ, it is of the same kind as the larger argument.)
Examples#
Sample program:
program demo_iand
implicit none
integer :: a, b
data a / z'f' /, b / z'3' /
write (*,*) iand(a, b)
end program demo_iand
Results:
3
Standard#
Fortran 95 and later
See Also#
ieor(3), ibclr(3), not(3), btest(3), ibclr(3), ibits(3), ibset(3), ior(3), ieor(3), mvbits(3)
####### fortran-lang intrinsic descriptions
iany#
Name#
iany(3) - [BIT:LOGICAL] Bitwise or of array elements
Syntax#
result = iany(array, mask)
or
result = iany(array, dim, mask)
Description#
Reduces with bitwise or (inclusive or) the elements of array along dimension dim if the corresponding element in mask is .true..
Arguments#
- array
Shall be an array of type integer
- dim
(Optional) shall be a scalar of type integer with a value in the range from 1 to n, where n equals the rank of array.
- mask
(Optional) shall be of type logical and either be a scalar or an array of the same shape as array.
Returns#
The result is of the same type as array.
If dim is absent, a scalar with the bitwise or of all elements in array is returned. Otherwise, an array of rank n-1, where n equals the rank of array, and a shape similar to that of array with dimension dim dropped is returned.
Examples#
Sample program:
program demo_iany
use, intrinsic :: iso_fortran_env, only : integer_kinds, &
& int8, int16, int32, int64
implicit none
integer(kind=int8) :: a(2)
a(1) = int(b'00100100')
a(2) = int(b'01101010')
print '(b8.8)', iany(a)
end program demo_iany
Results:
01101110
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
ieor#
Name#
ieor(3) - [BIT:LOGICAL] Bitwise logical exclusive or
Syntax#
result = ieor(i, j)
Description#
ieor returns the bitwise Boolean exclusive-or of i and j.
Arguments#
- i
The type shall be integer.
- j
The type shall be integer, of the same kind as i.
Returns#
The return type is integer, of the same kind as the arguments. (If the argument kinds differ, it is of the same kind as the larger argument.)
Standard#
Fortran 95 and later
See Also#
ieor(3), ibclr(3), not(3), btest(3), ibclr(3), ibits(3), ibset(3), iand(3), ior(3), mvbits(3)
####### fortran-lang intrinsic descriptions
ior#
Name#
ior(3) - [BIT:LOGICAL] Bitwise logical inclusive or
Syntax#
result = ior(i, j)
integer,intent(in) :: i
integer,intent(in) :: j
Description#
ior returns the bit-wise Boolean inclusive-or of i and j.
Arguments#
- i
an integer scalar or array.
- j
integer scalar or array, of the same kind as i.
Returns#
The return type is integer, of the same kind as the arguments. (If the argument kinds differ, it is of the same kind as the larger argument.)
Examples#
Sample program:
program demo_ior
implicit none
integer :: i, j, k
i=53 ! i=00110101 binary (lowest order byte)
j=45 ! j=00101101 binary (lowest order byte)
k=ior(i,j) ! k=00111101 binary (lowest order byte) , k=61 decimal
write(*,'(i8,1x,b8.8)')i,i,j,j,k,k
end program demo_ior
Results:
53 00110101
45 00101101
61 00111101
Standard#
Fortran 95 and later
See Also#
ieor(3), ibclr(3), not(3), btest(3), ibclr(3), ibits(3), ibset(3), iand(3), ieor(3), mvbits(3)
####### fortran-lang intrinsic descriptions
not#
Name#
not(3) - [BIT:LOGICAL] Logical negation
Syntax#
result = not(i)
Description#
NOT returns the bitwise Boolean inverse of I.
Arguments#
- i
The type shall be integer.
Returns#
The return type is integer, of the same kind as the argument.
Examples#
Sample program
program demo_not
implicit none
integer :: i
i=13741
write(*,'(b32.32,1x,i0)')i,i
write(*,'(b32.32,1x,i0)')not(i),not(i)
end program demo_not
Results:
00000000000000000011010110101101 13741
11111111111111111100101001010010 -13742
Standard#
Fortran 95 and later
See Also#
iand(3), ior(3), ieor(3), ibits(3), ibset(3),
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
ishftc#
Name#
ishftc(3) - [BIT:SHIFT] Shift bits circularly
Syntax#
result = ishftc(i, shift, size)
Description#
ishftc(3) returns a value corresponding to i with the rightmost size bits shifted circularly shift places; that is, bits shifted out one end are shifted into the opposite end. A value of shift greater than zero corresponds to a left shift, a value of zero corresponds to no shift, and a value less than zero corresponds to a right shift. The absolute value of shift must be less than size. If the size argument is omitted, it is taken to be equivalent to bit_size(i).
Arguments#
- i
The type shall be integer.
- shift
The type shall be integer.
- size
(Optional) The type shall be integer; the value must be greater than zero and less than or equal to bit_size(i).
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 95 and later
See Also#
####### fortran-lang intrinsic descriptions
ishft#
Name#
ishft(3) - [BIT:SHIFT] Shift bits
Syntax#
result = ishft(i, shift)
Description#
ishft(3) returns a value corresponding to i with all of the bits shifted shift places. A value of shift greater than zero corresponds to a left shift, a value of zero corresponds to no shift, and a value less than zero corresponds to a right shift. If the absolute value of shift is greater than bit_size(i), the value is undefined. Bits shifted out from the left end or right end are lost; zeros are shifted in from the opposite end.
Arguments#
- i
The type shall be integer.
- shift
The type shall be integer.
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 95 and later
See Also#
####### fortran-lang intrinsic descriptions
shifta#
Name#
shifta(3) - [BIT:SHIFT] shift bits right with fill
Syntax#
result = shifta(i, shift)
Description#
Returns a value corresponding to i with all of the bits shifted right by shift places. If the absolute value of shift is greater than bit_size(i), the value is undefined. Bits shifted out from the right end are lost. The fill is arithmetic: the bits shifted in from the left end are equal to the leftmost bit, which in two’s complement representation is the sign bit.
Arguments#
- i
The type shall be integer.
- shift
The type shall be integer.
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
shiftl#
Name#
shiftl(3) - [BIT:SHIFT] shift bits left
Syntax#
result = shiftl(i, shift)
Description#
Returns a value corresponding to i with all of the bits shifted left by shift places. If the absolute value of shift is greater than bit_size(i), the value is undefined. Bits shifted out from the left end are lost, and bits shifted in from the right end are set to 0.
Arguments#
- i
The type shall be integer.
- shift
The type shall be integer.
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions
shiftr#
Name#
shiftr(3) - [BIT:SHIFT] shift bits right
Syntax#
result = shiftr(i, shift)
Description#
Returns a value corresponding to i with all of the bits shifted right by shift places. If the absolute value of shift is greater than bit_size(i), the value is undefined. Bits shifted out from the right end are lost, and bits shifted in from the left end are set to 0.
Arguments#
- i
The type shall be integer.
- shift
The type shall be integer.
Returns#
The return value is of type integer and of the same kind as i.
Standard#
Fortran 2008 and later
See Also#
####### fortran-lang intrinsic descriptions