Bit-level inquiry and manipulation#

bge#

Name#

bge(3) - [BIT:COMPARE] Bitwise greater than or equal to

Synopsis#

    result = bge(i,j)
      elemental logical function bge(i, j)

       integer(kind=**),intent(in) :: i
       integer(kind=**),intent(in) :: j

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • the integer kind of i and j may not necessarily be the same. In addition, values may be a BOZ constant with a value valid for the integer kind available with the most bits on the current platform.

  • The return value is of type default logical.

Description#

bge(3) Determines whether one integer is bitwise greater than or equal to another.

The bit-level representation of a value is platform dependent. The endian-ness of a system and whether the system uses a “two’s complement” representation of signs can affect the results, for example.

A BOZ constant (Binary, Octal, Hexadecimal) does not have a kind or type of its own, so be aware it is subject to truncation when transferred to an integer type. The most bits the constant may contain is limited by the most bits representable by any integer kind supported by the compilation.

Bit Sequence Comparison#

When bit sequences of unequal length are compared, the shorter sequence is padded with zero bits on the left to the same length as the longer sequence (up to the largest number of bits any available integer kind supports).

Bit sequences are compared from left to right, one bit at a time, until unequal bits are found or until all bits have been compared and found to be equal.

The bits are always evaluated in this order, not necessarily from MSB to LSB (most significant bit to least significant bit).

If unequal bits are found the sequence with zero in the unequal position is considered to be less than the sequence with one in the unequal position.

Options#

  • i

    The value to test if >= j based on the bit representation of the values.

  • j

    The value to test i against.

Result#

Returns .true. if i is bit-wise greater than j and .false. otherwise.

Examples#

Sample program:

program demo_bge
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer            :: i
integer(kind=int8) :: byte
integer(kind=int8),allocatable :: arr1(:), arr2(:)

  ! BASIC USAGE
   write(*,*)'bge(-127,127)=',bge( -127, 127 )
   ! on (very common) "two's complement" machines that are
   ! little-endian -127 will be greater than 127

   ! BOZ constants
   ! BOZ constants are subject to truncation, so make sure
   ! your values are valid for the integer kind being compared to
   write(*,*)'bge(b"0001",2)=',bge( b"1", 2)

  ! ELEMENTAL
   ! an array and scalar
   write(*, *)'compare array of values [-128, -0, +0, 127] to 127'
   write(*, *)bge(int([-128, -0, +0, 127], kind=int8), 127_int8)

   ! two arrays
   write(*, *)'compare two arrays'
   arr1=int( [ -127, -0, +0,  127], kind=int8 )
   arr2=int( [  127,  0,  0, -127], kind=int8 )
   write(*,*)'arr1=',arr1
   write(*,*)'arr2=',arr2
   write(*, *)'bge(arr1,arr2)=',bge( arr1, arr2 )

  ! SHOW TESTS AND BITS
   ! actually looking at the bit patterns should clarify what affect
   ! signs have ...
   write(*,*)'Compare some one-byte values to 64.'
   write(*,*)'Notice that the values are tested as bits not as integers'
   write(*,*)'so the results are as if values are unsigned integers.'
   do i=-128,127,32
      byte=i
      write(*,'(sp,i0.4,*(1x,1l,1x,b0.8))')i,bge(byte,64_int8),byte
   enddo

  ! SIGNED ZERO
   ! are +0 and -0 the same on your platform? When comparing at the
   ! bit level this is important
   write(*,'("plus zero=",b0)')  +0
   write(*,'("minus zero=",b0)') -0

end program demo_bge

Results:

How an integer value is represented at the bit level can vary. These are just the values expected on Today’s most common platforms …

    > bge(-127,127)= T
    > bge(b"0001",2)= F
    > compare array of values [-128, -0, +0, 127] to 127
    > T F F T
    > compare two arrays
    > arr1= -127    0    0  127
    > arr2=  127    0    0 -127
    > bge(arr1,arr2)= T T T F
    > Compare some one-byte values to 64.
    > Notice that the values are tested as bits not as integers
    > so the results are as if values are unsigned integers.
    > -0128  T 10000000
    > -0096  T 10100000
    > -0064  T 11000000
    > -0032  T 11100000
    > +0000  F 00000000
    > +0032  F 00100000
    > +0064  T 01000000
    > +0096  T 01100000
    > plus zero=0
    > minus zero=0

Standard#

Fortran 2008

See Also#

bgt(3), ble(3), blt(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

bgt#

Name#

bgt(3) - [BIT:COMPARE] Bitwise greater than

Synopsis#

    result = bgt(i, j)
      elemental logical function bgt(i, j)

       integer(kind=**),intent(in) :: i
       integer(kind=**),intent(in) :: j

Characteristics#

  • i is an integer or a boz-literal-constant.

  • j is an integer or a boz-literal-constant.

  • a kind designated as ** may be any supported kind for the type The integer kind of i and **j** may not necessarily be the same. kind. In addition, values may be a BOZ constant with a value valid for the integer kind available with the most bits on the current platform.

  • The return value is of type logical and of the default kind.

Description#

bgt determines whether an integer is bitwise greater than another. Bit-level representations of values are platform-dependent.

Options#

  • i

    reference value to compare against

  • j

    value to compare to i

Result#

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.

Bits are compared from right to left.

Examples#

Sample program:

program demo_bgt
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer            :: i
integer(kind=int8) :: byte
  ! Compare some one-byte values to 64.
   ! Notice that the values are tested as bits not as integers
   ! so sign bits in the integer are treated just like any other
   write(*,'(a)') 'we will compare other values to 64'
   i=64
   byte=i
   write(*,'(sp,i0.4,*(1x,1l,1x,b0.8))')i,bgt(byte,64_int8),byte

   write(*,'(a)') "comparing at the bit level, not as whole numbers."
   write(*,'(a)') "so pay particular attention to the negative"
   write(*,'(a)') "values on this two's complement platform ..."
   do i=-128,127,32
      byte=i
      write(*,'(sp,i0.4,*(1x,1l,1x,b0.8))')i,bgt(byte,64_int8),byte
   enddo

   ! see the BGE() description for an extended description
   ! of related information

end program demo_bgt

Results:

 > we will compare other values to 64
 > +0064  F 01000000
 > comparing at the bit level, not as whole numbers.
 > so pay particular attention to the negative
 > values on this two's complement platform ...
 > -0128  T 10000000
 > -0096  T 10100000
 > -0064  T 11000000
 > -0032  T 11100000
 > +0000  F 00000000
 > +0032  F 00100000
 > +0064  F 01000000
 > +0096  T 01100000

Standard#

Fortran 2008

See Also#

bge(3), ble(3), blt(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

ble#

Name#

ble(3) - [BIT:COMPARE] Bitwise less than or equal to

Synopsis#

    result = ble(i,j)
     elemental logical function ble(i, j)

      integer(kind=**),intent(in) :: i
      integer(kind=**),intent(in) :: j

Characteristics#

  • i and j may be of any supported integer kind, not necessarily the same. An exception is that values may be a BOZ constant with a value valid for the integer kind available with the most bits on the current platform.

  • the returned value is a logical scalar of default kind

Description#

ble(3) determines whether an integer is bitwise less than or equal to another, assuming any shorter value is padded on the left with zeros to the length of the longer value.

Options#

  • i

    the value to compare j to

  • j

    the value to be tested for being less than or equal to i

Result#

The return value is .true. if any bit in j is less than any bit in i starting with the rightmost bit and continuing tests leftward.

Examples#

Sample program:

program demo_ble
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer            :: i
integer(kind=int8) :: byte
  ! Compare some one-byte values to 64.
   ! Notice that the values are tested as bits not as integers
   ! so sign bits in the integer are treated just like any other
   do i=-128,127,32
      byte=i
      write(*,'(sp,i0.4,*(1x,1l,1x,b0.8))')i,ble(byte,64_int8),byte
      write(*,'(sp,i0.4,*(4x,b0.8))')64_int8,64_int8
   enddo

   ! see the BGE() description for an extended description
   ! of related information

end program demo_ble

Results:

   -0128  F 10000000
   +0064    01000000
   -0096  F 10100000
   +0064    01000000
   -0064  F 11000000
   +0064    01000000
   -0032  F 11100000
   +0064    01000000
   +0000  T 00000000
   +0064    01000000
   +0032  T 00100000
   +0064    01000000
   +0064  T 01000000
   +0064    01000000
   +0096  F 01100000
   +0064    01000000

Standard#

Fortran 2008

See Also#

bge(3), bgt(3), blt(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

blt#

Name#

blt(3) - [BIT:COMPARE] Bitwise less than

Synopsis#

    result = blt(i,j)
     elemental logical function blt(i, j)

      integer(kind=**),intent(in) :: i
      integer(kind=**),intent(in) :: j

Characteristics#

  • i is an integer of any kind or a BOZ-literal-constant

  • j is an integer of any kind or a BOZ-literal-constant, not necessarily the same as i.

  • the result is of default logical kind

BOZ constants must have a value valid for the integer kind available with the most bits on the current platform.

Description#

blt(3) determines whether an integer is bitwise less than another.

Options#

  • i

    Shall be of integer type or a BOZ literal constant.

  • j

    Shall be of integer type or a BOZ constant.

Result#

The return value is of type logical and of the default kind.

Examples#

Sample program:

program demo_blt
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer            :: i
integer(kind=int8) :: byte
  ! Compare some one-byte values to 64.
   ! Notice that the values are tested as bits not as integers
   ! so sign bits in the integer are treated just like any other
   do i=-128,127,32
      byte=i
      write(*,'(sp,i0.4,*(1x,1l,1x,b0.8))')i,blt(byte,64_int8),byte
   enddo
  ! BOZ literals
   write(*,*)blt(z'1000', z'101011010')
   ! see the BGE() description for an extended description
   ! of related information

end program demo_blt

Results:

   > -0128  F 10000000
   > -0096  F 10100000
   > -0064  F 11000000
   > -0032  F 11100000
   > +0000  T 00000000
   > +0032  T 00100000
   > +0064  F 01000000
   > +0096  F 01100000
   > T

Standard#

Fortran 2008

See Also#

bge(3), bgt(3), ble(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

bit_size#

Name#

bit_size(3) - [BIT:INQUIRY] Bit size inquiry function

Synopsis#

    result = bit_size(i)
     integer(kind=KIND) function bit_size(i)

      integer(kind=KIND),intent(in) :: i(..)

Characteristics#

  • i shall be of type integer. It may be a scalar or an array.

  • the value of KIND is any valid value for an integer kind parameter on the processor.

  • the return value is a scalar of the same kind as the input value.

Description#

bit_size(3) returns the number of bits (integer precision plus sign bit) represented by the type of the integer i.

Options#

  • i

    An integer value of any kind whose size in bits is to be determined. Because only the type of the argument is examined, the argument need not be defined; i can be a scalar or an array, but a scalar representing just a single element is always returned.

Result#

The number of bits used to represent a value of the type and kind 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
use,intrinsic :: iso_fortran_env, only : integer_kinds
implicit none
character(len=*),parameter   :: fmt=&
& '(a,": bit size is ",i3," which is kind=",i3," on this platform")'

    ! default integer bit size on this platform
    write(*,fmt) "default", bit_size(0), kind(0)

    write(*,fmt) "int8   ", bit_size(0_int8),   kind(0_int8)
    write(*,fmt) "int16  ", bit_size(0_int16),  kind(0_int16)
    write(*,fmt) "int32  ", bit_size(0_int32),  kind(0_int32)
    write(*,fmt) "int64  ", bit_size(0_int64),  kind(0_int64)

    write(*,'(a,*(i0:,", "))') "The available kinds are ",integer_kinds

end program demo_bit_size

Typical Results:

    default: bit size is  32 which is kind=  4 on this platform
    int8   : bit size is   8 which is kind=  1 on this platform
    int16  : bit size is  16 which is kind=  2 on this platform
    int32  : bit size is  32 which is kind=  4 on this platform
    int64  : bit size is  64 which is kind=  8 on this platform
    The available kinds are 1, 2, 4, 8, 16

Standard#

Fortran 95

See Also#

****(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

btest#

Name#

btest(3) - [BIT:INQUIRY] Tests a bit of an integer value.

Synopsis#

    result = btest(i,pos)
     elemental logical function btest(i,pos)

      integer(kind=**),intent(in)  :: i
      integer(kind=**),intent(in)  :: pos

Characteristics#

  • i is an integer of any kind

  • pos is a integer of any kind

  • the result is a default logical

Description#

btest(3) returns logical .true. if the bit at pos in i is set to 1. Position zero is the right-most bit. Bit position increases from right to left up to bitsize(i)-1.

Options#

  • i

    The integer containing the bit to be tested

  • pos

    The position of the bit to query. it must be a valid position for the value i; ie. 0 <= pos <= bit_size(i).

Result#

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.

Positions of bits in the sequence are numbered from right to left, with the position of the rightmost bit being zero.

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

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

Synopsis#

    result = storage_size(a [,KIND] )
     integer(kind=KIND) storage_size(a,KIND)

      type(TYPE(kind=**)) :: a
      integer,intent(in),optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • a may be of any type and kind. If it is polymorphic it shall not be an undefined pointer. If it is unlimited polymorphic or has any deferred type parameters, it shall not be an unallocated allocatable variable or a disassociated or undefined pointer.

  • The kind type parameter of the returned value is that specified by the value of kind; otherwise, the kind type parameter is that of default integer type.

  • The result is an integer scalar of default kind unless kind is specified, in which case it has the kind specified by kind.

Description#

storage_size(3) returns the storage size of argument a in bits.

Options#

  • a

    The entity to determine the storage size of

  • kind

    a scalar integer constant expression that defines the kind of the output value.

Result#

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.

If the type and type parameters are such that storage association applies, the result is consistent with the named constants defined in the intrinsic module ISO_FORTRAN_ENV.

NOTE1

An array element might take “type” more bits to store than an isolated scalar, since any hardware-imposed alignment requirements for array elements might not apply to a simple scalar variable.

NOTE2

This is intended to be the size in memory that an object takes when it is stored; this might differ from the size it takes during expression handling (which might be the native register size) or when stored in a file. If an object is never stored in memory but only in a register, this function nonetheless returns the size it would take if it were stored in memory.

Examples#

Sample program

program demo_storage_size
implicit none

   ! a default real, integer, and logical are the same storage size
   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))

   ! note the size of an element of the array, not the storage size of
   ! the entire array is returned for array arguments
   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

See Also#

c_sizeof(3)

fortran-lang intrinsic descriptions

leadz#

Name#

leadz(3) - [BIT:COUNT] Number of leading zero bits of an integer

Synopsis#

    result = leadz(i)
     elemental integer function leadz(i)

      integer(kind=**),intent(in) :: i

Characteristics#

  • i may be an integer of any kind.

  • the return value is a default integer type.

Description#

leadz(3) returns the number of leading zero bits of an integer.

Options#

  • i

    integer to count the leading zero bits of.

Result#

The number of leading zero bits, taking into account the kind of the input value. If all the bits of i are zero, the result value is bit_size(i).

The result may also be thought of as bit_size(i)-1-k where k is the position of the leftmost 1 bit in the input i. Positions are from 0 to bit-size(), with 0 at the right-most bit.

Examples#

Sample program:

program demo_leadz
implicit none
integer :: value, i
character(len=80) :: f

  ! 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=-150, 150, 50
     value=i
     write (*,'("LEADING ZERO BITS=",i3)',advance='no') leadz(value)
     write (*,'(" OF VALUE ")',advance='no')
     write(*,f,advance='no') value
     write(*,'(*(1x,g0))') "AKA",value
  enddo
  ! Notes:
  ! for two's-complements programming environments a negative non-zero
  ! integer value will always start with a 1 and a positive value with 0
  ! as the first bit is the sign bit. Such platforms are very common.
end program demo_leadz

Results:

  LEADING ZERO BITS=  0 OF VALUE 11111111111111111111111101101010 AKA -150
  LEADING ZERO BITS=  0 OF VALUE 11111111111111111111111110011100 AKA -100
  LEADING ZERO BITS=  0 OF VALUE 11111111111111111111111111001110 AKA -50
  LEADING ZERO BITS= 32 OF VALUE 00000000000000000000000000000000 AKA 0
  LEADING ZERO BITS= 26 OF VALUE 00000000000000000000000000110010 AKA 50
  LEADING ZERO BITS= 25 OF VALUE 00000000000000000000000001100100 AKA 100
  LEADING ZERO BITS= 24 OF VALUE 00000000000000000000000010010110 AKA 150

Standard#

Fortran 2008

See Also#

bit_size(3), popcnt(3), poppar(3), trailz(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

popcnt#

Name#

popcnt(3) - [BIT:COUNT] Number of bits set

Synopsis#

    result = popcnt(i)
     elemental integer function popcnt(i)

      integer(kind=KIND), intent(in) :: i

Characteristics#

  • i may be an integer of any kind.

  • The return value is an integer of the default integer kind.

Description#

popcnt(3) returns the number of bits set to one in the binary representation of an integer.

Options#

  • i

    value to count set bits in

Result#

The number of bits set to one in i.

Examples#

Sample program:

program demo_popcnt
use, intrinsic :: iso_fortran_env, only : integer_kinds, &
   & int8, int16, int32, int64
implicit none
character(len=*),parameter :: pretty='(b64,1x,i0)'
  ! basic usage
   print pretty, 127,     popcnt(127)
   print pretty, int(b"01010"), popcnt(int(b"01010"))

  ! any kind of an integer can be used
   print pretty, huge(0_int8),  popcnt(huge(0_int8))
   print pretty, huge(0_int16), popcnt(huge(0_int16))
   print pretty, huge(0_int32), popcnt(huge(0_int32))
   print pretty, huge(0_int64), popcnt(huge(0_int64))
end program demo_popcnt

Results:

Note that on most machines the first bit is the sign bit, and a zero is used for positive values; but that this is system-dependent. These are typical values, where the huge(3f) function has set all but the first bit to 1.

 >                                                         1111111 7
 >                                                            1010 2
 >                                                         1111111 7
 >                                                 111111111111111 15
 >                                 1111111111111111111111111111111 31
 > 111111111111111111111111111111111111111111111111111111111111111 63

Standard#

Fortran 2008

See Also#

There are many procedures that operator or query values at the bit level:

poppar(3), leadz(3), trailz(3) atomic_and(3), atomic_fetch_and(3), atomic_fetch_or(3), atomic_fetch_xor(3), atomic_or(3), atomic_xor(3), bge(3), bgt(3), bit_size(3), ble(3), blt(3), btest(3), dshiftl(3), dshiftr(3), iall(3), iand(3), iany(3), ibclr(3), ibits(3), ibset(3), ieor(3), ior(3), iparity(3), ishftc(3), ishft(3), maskl(3), maskr(3), merge_bits(3), mvbits(3), not(3), shifta(3), shiftl(3), shiftr(3), storage_size(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

poppar#

Name#

poppar(3) - [BIT:COUNT] Parity of the number of bits set

Synopsis#

    result = poppar(i)
     elemental integer function poppar(i)

      integer(kind=KIND), intent(in) :: i

Characteristics#

  • i is an integer of any kind

  • the return value is a default kind integer

Description#

poppar(3) returns the parity of an integer’s binary representation (i.e., the parity of the number of bits set).

The parity is expressed as

  • 0 (zero) if i has an even number of bits set to 1.

  • 1 (one) if the number of bits set to one 1 is odd,

Options#

  • i

    The value to query for its bit parity

Result#

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.

Examples#

Sample program:

program demo_poppar
use, intrinsic :: iso_fortran_env, only : integer_kinds, &
   & int8, int16, int32, int64
implicit none
character(len=*),parameter :: pretty='(b64,1x,i0)'
   ! basic usage
   print pretty, 127,     poppar(127)
   print pretty, 128,     poppar(128)
   print pretty, int(b"01010"), poppar(int(b"01010"))

   ! any kind of an integer can be used
   print pretty, huge(0_int8),  poppar(huge(0_int8))
   print pretty, huge(0_int16), poppar(huge(0_int16))
   print pretty, huge(0_int32), poppar(huge(0_int32))
   print pretty, huge(0_int64), poppar(huge(0_int64))
end program demo_poppar

Results:

 >                                                          1111111 1
 >                                                         10000000 1
 >                                                             1010 0
 >                                  1111111111111111111111111111111 1
 >                                                          1111111 1
 >                                                  111111111111111 1
 >                                  1111111111111111111111111111111 1
 >  111111111111111111111111111111111111111111111111111111111111111 1

Standard#

Fortran 2008

See Also#

There are many procedures that operator or query values at the bit level:

popcnt(3), leadz(3), trailz(3) atomic_and(3), atomic_fetch_and(3), atomic_fetch_or(3), atomic_fetch_xor(3), atomic_or(3), atomic_xor(3), bge(3), bgt(3), bit_size(3), ble(3), blt(3), btest(3), dshiftl(3), dshiftr(3), iall(3), iand(3), iany(3), ibclr(3), ibits(3), ibset(3), ieor(3), ior(3), iparity(3), ishftc(3), ishft(3), maskl(3), maskr(3), merge_bits(3), mvbits(3), not(3), shifta(3), shiftl(3), shiftr(3), storage_size(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

trailz#

Name#

trailz(3) - [BIT:COUNT] Number of trailing zero bits of an integer

Synopsis#

 result = trailz(i)
  elemental integer function trailz(i)

   integer(kind=**),intent(in) :: i

Characteristics#

  • i is an integer of any kind.

  • the result is an integer of default kind

Description#

trailz(3) returns the number of trailing zero bits of an integer value.

Options#

  • i

    the value to count trailing zero bits in

Result#

The number of trailing rightmost zero bits in an integer value after the last non-zero bit.

       >      right-most non-zero bit
       >                 V
       >  |0|0|0|1|1|1|0|1|0|0|0|0|0|0|
       >  ^               |___________| trailing zero bits
       >   bit_size(i)

If all the bits of i are zero, the result is the size of the input value in bits, ie. bit_size(i).

The result may also be seen as the position of the rightmost 1 bit in i, starting with the rightmost bit being zero and counting to the left.

Examples#

Sample program:

program demo_trailz

! some common integer kinds
use, intrinsic :: iso_fortran_env, only : &
 & integer_kinds, int8, int16, int32, int64

implicit none

! a handy format
character(len=*),parameter :: &
 & show = '(1x,"value=",i4,", value(bits)=",b32.32,1x,", trailz=",i3)'

integer(kind=int64) :: bigi
  ! basics
   write(*,*)'Note default integer is',bit_size(0),'bits'
   print  show,  -1, -1,  trailz(-1)
   print  show,   0,  0,  trailz(0)
   print  show,   1,  1,  trailz(1)
   print  show,  96, 96,  trailz(96)
  ! elemental
   print *, 'elemental and any integer kind:'
   bigi=2**5
   write(*,*) trailz( [ bigi, bigi*256, bigi/2 ] )
   write(*,'(1x,b64.64)')[ bigi, bigi*256, bigi/2 ]

end program demo_trailz

Results:

    Note default integer is          32 bits
    value=  -1, value(bits)=11111111111111111111111111111111 , trailz=  0
    value=   0, value(bits)=00000000000000000000000000000000 , trailz= 32
    value=   1, value(bits)=00000000000000000000000000000001 , trailz=  0
    value=  96, value(bits)=00000000000000000000000001100000 , trailz=  5
    elemental and any integer kind:
              5          13           4
    0000000000000000000000000000000000000000000000000000000000100000
    0000000000000000000000000000000000000000000000000010000000000000
    0000000000000000000000000000000000000000000000000000000000010000

Standard#

Fortran 2008

See Also#

bit_size(3), popcnt(3), poppar(3), leadz(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

dshiftl#

Name#

dshiftl(3) - [BIT:COPY] Combined left shift of the bits of two integers

Synopsis#

    result = dshiftl(i, j, shift)
     elemental integer(kind=KIND) function dshiftl(i, j, shift)

      integer(kind=KIND),intent(in) :: i
      integer(kind=KIND),intent(in) :: j
      integer(kind=**),intent(in) :: shift

Characteristics#

  • the kind of i, j, and the return value are the same. An exception is that one of i and j may be a BOZ literal constant (A BOZ literal constant is a binary, octal or hex constant).

  • If either I or J is a BOZ-literal-constant (but not both), it is first converted as if by the intrinsic function int(3) to type integer with the kind type parameter of the other.

  • a kind designated as ** may be any supported kind for the type

Description#

dshiftl(3) 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 bitsize(i)-shift of i.

Hence dshiftl is designated as a “combined left shift”, because it is like we appended i and j together, shifted it shift bits to the left, and then kept the same number of bits as i or j had.

For example, for two 16-bit values if shift=6

      SHIFT=6
      I =             1111111111111111
      J =             0000000000000000
      COMBINED        11111111111111110000000000000000
      DROP LEFT BITS  11111111110000000000000000
      KEEP LEFT 16    1111111111000000

NOTE#

This is equivalent to

     ior( shiftl(i, shift), shiftr(j, bit_size(j) - shift) )

Also note that using this last representation of the operation is can be derived that when both i and j have the same value as in

      dshiftl(i, i, shift)

the result has the same value as a circular shift:

      ishftc(i, shift)

Options#

  • i

    used to define the left pattern of bits in the combined pattern

  • j

    used for the right pattern of bits in the combined pattern

  • shift

    shall be nonnegative and less than or equal to the number of bits in an integer input value (ie. the bit size of either one that is not a BOZ literal constant).

Result#

The leftmost shift bits of j are copied to the rightmost bits of the result, and the remaining bits are the rightmost bits of i.

Examples#

Sample program:

program demo_dshiftl
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer(kind=int32) :: i, j
integer             :: shift

  ! basic usage
   write(*,*) dshiftl (1, 2**30, 2) ! int32 values on little-endian => 5

  ! print some simple calls as binary to better visual the results
   i=-1
   j=0
   shift=5
   call printit()

   ! the leftmost SHIFT bits of J are copied to the rightmost result bits
   j=int(b"11111000000000000000000000000000")
   ! and the other bits are the rightmost bits of I
   i=int(b"00000000000000000000000000000000")
   call printit()

   j=int(b"11111000000000000000000000000000")
   i=int(b"00000111111111111111111111111111")
   ! result should be all 1s
   call printit()

contains
subroutine printit()
   ! print i,j,shift and then i,j, and the result as binary values
    write(*,'(*(g0))')'I=',i,' J=',j,' SHIFT=',shift
    write(*,'(b32.32)') i,j, dshiftl (i, j, shift)
end subroutine printit

end program demo_dshiftl

Results:

   > I=-1 J=0 SHIFT=5
   > 11111111111111111111111111111111
   > 00000000000000000000000000000000
   > 11111111111111111111111111100000
   > I=0 J=-134217728 SHIFT=5
   > 00000000000000000000000000000000
   > 11111000000000000000000000000000
   > 00000000000000000000000000011111
   > I=134217727 J=-134217728 SHIFT=5
   > 00000111111111111111111111111111
   > 11111000000000000000000000000000
   > 11111111111111111111111111111111

Standard#

Fortran 2008

See Also#

dshiftr(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

dshiftr#

Name#

dshiftr(3) - [BIT:COPY] Combined right shift of the bits of two integers

Synopsis#

    result = dshiftr(i, j, shift)
     elemental integer(kind=KIND) function dshiftr(i, j, shift)

      integer(kind=KIND),intent(in) :: i
      integer(kind=KIND),intent(in) :: j
      integer(kind=**),intent(in) :: shift

Characteristics#

  • a kind designated as ** may be any kind value for the integer type

  • the kind of i, j, and the return value are the same. An exception is that one of i and j may be a BOZ literal constant (A BOZ literal constant is a binary, octal or hex constant).

  • If either I or J is a BOZ-literal-constant, it is first converted as if by the intrinsic function int(3) to type integer with the kind type parameter of the other.

Description#

dshiftr(3) 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.

It may be thought of as appending the bits of i and j, dropping off the shift rightmost bits, and then retaining the same number of rightmost bits as an input value, hence the name “combined right shift”…

Given two 16-bit values labeled alphabetically …

   i=ABCDEFGHIJKLMNOP
   j=abcdefghijklmnop

Append them together

   ABCDEFGHIJKLMNOPabcdefghijklmnop

Shift them N=6 bits to the right dropping off bits

         ABCDEFGHIJKLMNOPabcdefghij

Keep the 16 right-most bits

                   KLMNOPabcdefghij

NOTE#

dshifr(i,j,shift) is equivalent to

     ior(shiftl (i, bit_size(i) - shift), shiftr(j, shift) )

it can also be seen that if i and j have the same value

     dshiftr( i, i, shift )

this has the same result as a negative circular shift

     ishftc( i,   -shift ).

Options#

  • i

    left value of the pair of values to be combine-shifted right

  • j

    right value of the pair of values to be combine-shifted right

  • shift

    the shift value is non-negative and less than or equal to the number of bits in an input value as can be computed by bit_size(3).

Result#

The result is a combined right shift of i and j that is the same as the bit patterns of the inputs being combined left to right, dropping off shift bits on the right and then retaining the same number of bits as an input value from the rightmost bits.

Examples#

Sample program:

program demo_dshiftr
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer(kind=int32) :: i, j
integer             :: shift

  ! basic usage
   write(*,*) dshiftr (1, 2**30, 2)

  ! print some calls as binary to better visualize the results
   i=-1
   j=0
   shift=5

   ! print values
    write(*,'(*(g0))')'I=',i,' J=',j,' SHIFT=',shift
    write(*,'(b32.32)') i,j, dshiftr (i, j, shift)

  ! visualizing a "combined right shift" ...
   i=int(b"00000000000000000000000000011111")
   j=int(b"11111111111111111111111111100000")
   ! appended together ( i//j )
   ! 0000000000000000000000000001111111111111111111111111111111100000
   ! shifted right SHIFT values dropping off shifted values
   !      00000000000000000000000000011111111111111111111111111111111
   ! keep enough rightmost bits to fill the kind
   !                                 11111111111111111111111111111111
   ! so the result should be all 1s bits ...

    write(*,'(*(g0))')'I=',i,' J=',j,' SHIFT=',shift
    write(*,'(b32.32)') i,j, dshiftr (i, j, shift)

end program demo_dshiftr

Results:

 >    1342177280
 >  I=-1 J=0 SHIFT=5
 >  11111111111111111111111111111111
 >  00000000000000000000000000000000
 >  11111000000000000000000000000000
 >  I=31 J=-32 SHIFT=5
 >  00000000000000000000000000011111
 >  11111111111111111111111111100000
 >  11111111111111111111111111111111

Standard#

Fortran 2008

See Also#

dshiftl(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

merge_bits#

Name#

merge_bits(3) - [BIT:COPY] Merge bits using a mask

Synopsis#

    result = merge_bits(i, j, mask)
     elemental integer(kind=KIND) function merge_bits(i,j,mask)

      integer(kind=KIND), intent(in) :: i, j, mask

Characteristics#

  • 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(3) 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.

Options#

  • 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

Result#

The bits blended from i and j using the mask mask.

Examples#

Sample program:

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

See also#

****(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

mvbits#

Name#

mvbits(3) - [BIT:COPY] Reproduce bit patterns found in one integer in another

Synopsis#

   call mvbits(from, frompos, len, to, topos)
    elemental subroutine mvbits( from, frompos, len, to, topos )

     integer(kind=KIND),intent(in)    :: from
     integer(kind=**),intent(in)      :: frompos
     integer(kind=**),intent(in)      :: len
     integer(kind=KIND),intent(inout) :: to
     integer(kind=**),intent(in)      :: topos

Characteristics#

  • from is an integer

  • frompos is an integer

  • len is an integer

  • to is an integer of the same kind as from.

  • topos is an integer

Description#

mvbits(3) 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.

Options#

  • 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, or associated to it.

    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).

Examples#

Sample program that populates a new 32-bit integer with its bytes in reverse order from the input value (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
    ! can copy bit from a value to itself
    call mvbits(intfrom,0,1,intfrom,31)
    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:

   2147483647                   01111111111111111111111111111111
   0                            00000000000000000000000000000000
   1                            00000000000000000000000000000001
   -1                           11111111111111111111111111111111
    native
   1684234849                   abcd      01100100011000110110001001100001
    non-native
   1633837924                   dcba      01100001011000100110001101100100

Standard#

Fortran 95

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] Extraction of a subset of bits

Synopsis#

    result = ibits(i, pos, len)
     elemental integer(kind=KIND) function ibits(i,pos,len)

      integer(kind=KIND),intent(in) :: i
      integer(kind=**),intent(in) :: pos
      integer(kind=**),intent(in) :: len

Characteristics#

  • a kind designated as ** may be any supported integer kind

  • i may be any supported integer kind as well

  • the return value will be the same kind as i

Description#

ibits(3) extracts a field of bits from i, starting from bit position pos and extending left for a total of len bits.

The result is then right-justified and the remaining left-most bits in the result are zeroed.

The position pos is calculated assuming the right-most bit is zero and the positions increment to the left.

Options#

  • i

    The value to extract bits from

  • pos

    The position of the bit to start copying at. pos is non-negative.

  • len

    the number of bits to copy from i. It must be non-negative.

pos + len shall be less than or equal to bit_size(i).

Result#

The return value is composed of the selected bits right-justified, left-padded with zeros.

Examples#

Sample program:

program demo_ibits
use,intrinsic :: iso_fortran_env,  only : int8, int16, int32, int64
implicit none
integer(kind=int16) :: i,j
  ! basic usage
   print *,ibits (14, 1, 3) ! should be seven
   print *,ibits(-1,10,3)   ! and so is this
   ! it is easier to see using binary representation
   i=int(b'0101010101011101',kind=int16)
   write(*,'(b16.16,1x,i0)') ibits(i,3,3), ibits(i,3,3)

  ! we can illustrate this as
   !        #-- position 15
   !        |              #-- position 0
   !        |   <-- +len   |
   !        V              V
   !        5432109876543210
   i =int(b'1111111111111111',kind=int16)
   !          ^^^^
   j=ibits(i,10,4) ! start at 10th from left and proceed
                   ! left for a total of 4 characters
   write(*,'(a,b16.16)')'j=',j
  ! lets do something less ambiguous
   i =int(b'0010011000000000',kind=int16)
   j=ibits(i,9,5)
   write(*,'(a,b16.16)')'j=',j
end program demo_ibits

Results:

 > 7
 > 7
 > 0000000000000011 3
 > j=0000000000001111
 > j=0000000000010011

Standard#

Fortran 95

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 (license: MIT) @urbanjost

ibclr#

Name#

ibclr(3) - [BIT:SET] Clear a bit

Synopsis#

    result = ibclr(i, pos)
     elemental integer(kind=KIND) function ibclr(i,pos)

      integer(kind=KIND),intent(in) :: i
      integer(kind=**),intent(in) :: pos

Characteristics#

  • i shall be type integer.

  • pos shall be type integer.

  • The return value is of the same kind as i.

  • a kind designated as ** may be any supported kind for the type

Description#

ibclr(3) returns the value of i with the bit at position pos set to zero.

Options#

  • i

    The initial value to be modified

  • pos

    The position of the bit to change in the input value. A value of zero refers to the right-most bit. The value of pos must be nonnegative and less than (bit_size(i)).

Result#

The returned value has the same bit sequence as i except the designated bit is unconditionally set to 0

Examples#

Sample program:

program demo_ibclr
use,intrinsic :: iso_fortran_env,  only : int8, int16, int32, int64
implicit none
integer(kind=int16) :: i
  ! basic usage
   print *,ibclr (16, 1), ' ==> ibclr(16,1) has the value 15'

   ! it is easier to see using binary representation
   i=int(b'0000000000111111',kind=int16)
   write(*,'(b16.16,1x,i0)') ibclr(i,3), ibclr(i,3)

  ! elemental
   print *,'an array of initial values may be given as well'
   print *,ibclr(i=[7,4096,9], pos=2)
   print *
   print *,'a list of positions results in multiple returned values'
   print *,'not multiple bits set in one value, as the routine is  '
   print *,'a scalar function; calling it elementally essentially  '
   print *,'calls it multiple times.                               '
   write(*,'(b16.16)') ibclr(i=-1_int16, pos=[1,2,3,4])

   ! both may be arrays if of the same size

end program demo_ibclr

Results:

 >           16  ==> ibclr(16,1) has the value 15
 > 0000000000110111 55
 >  an array of initial values may be given as well
 >            3        4096           9
 >
 >  a list of positions results in multiple returned values
 >  not multiple bits set in one value, as the routine is
 >  a scalar function; calling it elementally essentially
 >  calls it multiple times.
 > 1111111111111101
 > 1111111111111011
 > 1111111111110111
 > 1111111111101111

Standard#

Fortran 95

See Also#

ieor(3), not(3), btest(3), ibset(3), ibits(3), iand(3), ior(3), ieor(3), mvbits(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

ibset#

Name#

ibset(3) - [BIT:SET] Set a bit to one in an integer value

Synopsis#

    result = ibset(i, pos)
     elemental integer(kind=KIND) function ibset(i,pos)

      integer(kind=KIND),intent(in) :: i
      integer(kind=**),intent(in) :: pos

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • The return value is of the same kind as i. Otherwise, any integer kinds are allowed.

Description#

ibset(3) returns the value of i with the bit at position pos set to one.

Options#

  • i

    The initial value to be modified

  • pos

    The position of the bit to change in the input value. A value of zero refers to the right-most bit. The value of pos must be nonnegative and less than (bit_size(i)).

Result#

The returned value has the same bit sequence as i except the designated bit is unconditionally set to 1.

Examples#

Sample program:

program demo_ibset
use,intrinsic :: iso_fortran_env,  only : int8, int16, int32, int64
implicit none
integer(kind=int16) :: i
  ! basic usage
   print *,ibset (12, 1), 'ibset(12,1) has the value 14'

   ! it is easier to see using binary representation
   i=int(b'0000000000000110',kind=int16)
   write(*,'(b16.16,1x,i0,1x,i0)') ibset(i,12), ibset(i,12), i

  ! elemental
   print *,'an array of initial values may be given as well'
   print *,ibset(i=[0,4096], pos=2)
   print *
   print *,'a list of positions results in multiple returned values'
   print *,'not multiple bits set in one value, as the routine is  '
   print *,'a scalar function; calling it elementally essentially  '
   print *,'calls it multiple times.                               '
   write(*,'(b16.16)') ibset(i=0, pos=[1,2,3,4])

   ! both may be arrays if of the same size

end program demo_ibset

Results:

 >           14 ibset(12,1) has the value 14
 > 0001000000000110 4102 6
 >  an array of initial values may be given as well
 >            4        4100
 >
 >  a list of positions results in multiple returned values
 >  not multiple bits set in one value, as the routine is
 >  a scalar function; calling it elementally essentially
 >  calls it multiple times.
 > 0000000000000010
 > 0000000000000100
 > 0000000000001000
 > 0000000000010000

Standard#

Fortran 95

See Also#

ibclr(3)

ieor(3), not(3), btest(3), ibits(3), iand(3), ior(3), ieor(3), mvbits(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

maskl#

Name#

maskl(3) - [BIT:SET] Generates a left justified mask

Synopsis#

    result = maskl( i [,kind] )
     elemental integer(kind=KIND) function maskl(i,KIND)

      integer(kind=**),intent(in) :: i
      integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i is an integer

  • kind Shall be a scalar constant expression of type integer whose value is a supported integer kind.

  • The result is an integer of the same kind as i unless kind is present, which is then used to specify the kind of the result.

Description#

maskl(3) has its leftmost i bits set to 1, and the remaining bits set to 0.

Options#

  • i

    the number of left-most bits to set in the integer result. It must be from 0 to the number of bits for the kind of the result. The default kind of the result is the same as i unless the result size is specified by kind. That is, these Fortran statements must be .true. :

   i >= 0 .and. i < bitsize(i) ! if KIND is not specified
   i >= 0 .and. i < bitsize(0_KIND) ! if KIND is specified
  • kind

    designates the kind of the integer result.

Result#

The leftmost i bits of the output integer are set to 1 and the other bits are set to 0.

Examples#

Sample program:

program demo_maskl
implicit none
integer :: i
  ! basics
   i=3
   write(*,'(i0,1x,b0)') i, maskl(i)

  ! elemental
   write(*,'(*(i11,1x,b0.32,1x,/))') maskl([(i,i,i=0,bit_size(0),4)])
end program demo_maskl

Results:

 > 3 11100000000000000000000000000000
 >           0 00000000000000000000000000000000
 >  -268435456 11110000000000000000000000000000
 >   -16777216 11111111000000000000000000000000
 >    -1048576 11111111111100000000000000000000
 >      -65536 11111111111111110000000000000000
 >       -4096 11111111111111111111000000000000
 >        -256 11111111111111111111111100000000
 >         -16 11111111111111111111111111110000
 >          -1 11111111111111111111111111111111

Standard#

Fortran 2008

See Also#

maskr(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

maskr#

Name#

maskr(3) - [BIT:SET] Generates a right-justified mask

Synopsis#

    result = maskr( i [,kind] )
     elemental integer(kind=KIND) function maskr(i,KIND)

      integer(kind=**),intent(in) :: i
      integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i is an integer

  • kind Shall be a scalar constant expression of type integer whose value is a supported integer kind.

  • The result is an integer of the same kind as i unless kind is present, which is then used to specify the kind of the result.

Description#

maskr(3) generates an integer with its rightmost i bits set to 1, and the remaining bits set to 0.

Options#

  • i

    the number of right-most bits to set in the integer result. It must be from 0 to the number of bits for the kind of the result. The default kind of the result is the same as i unless the result size is specified by kind. That is, these Fortran statements must be .true. :

   i >= 0 .and. i < bitsize(i) ! if KIND is not specified
   i >= 0 .and. i < bitsize(0_KIND) ! if KIND is specified
  • kind

    designates the kind of the integer result.

Result#

The rightmost i bits of the output integer are set to 1 and the other bits are set to 0.

Examples#

Sample program:

program demo_maskr
implicit none
integer :: i

  ! basics
   print *,'basics'
   write(*,'(i0,t5,b32.32)') 1, maskr(1)
   write(*,'(i0,t5,b32.32)') 5,  maskr(5)
   write(*,'(i0,t5,b32.32)') 11, maskr(11)
   print *,"should be equivalent on two's-complement processors"
   write(*,'(i0,t5,b32.32)') 1,  shiftr(-1,bit_size(0)-1)
   write(*,'(i0,t5,b32.32)') 5,  shiftr(-1,bit_size(0)-5)
   write(*,'(i0,t5,b32.32)') 11, shiftr(-1,bit_size(0)-11)

  ! elemental
   print *,'elemental '
   print *,'(array argument accepted like called with each element)'
   write(*,'(*(i11,1x,b0.32,1x,/))') maskr([(i,i,i=0,bit_size(0),4)])

end program demo_maskr

Results:

 >   basics
 >  1   00000000000000000000000000000001
 >  5   00000000000000000000000000011111
 >  11  00000000000000000000011111111111
 >   should be equivalent on two's-complement processors
 >  1   00000000000000000000000000000001
 >  5   00000000000000000000000000011111
 >  11  00000000000000000000011111111111
 >   elemental
 >   (array argument accepted like called with each element)
 >            0 00000000000000000000000000000000
 >           15 00000000000000000000000000001111
 >          255 00000000000000000000000011111111
 >         4095 00000000000000000000111111111111
 >        65535 00000000000000001111111111111111
 >      1048575 00000000000011111111111111111111
 >     16777215 00000000111111111111111111111111
 >    268435455 00001111111111111111111111111111
 >           -1 11111111111111111111111111111111

Standard#

Fortran 2008

See Also#

maskl(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

iparity#

Name#

iparity(3) - [BIT:LOGICAL] Bitwise exclusive OR of array elements

Synopsis#

    result = iparity( array [,mask] ) | iparity( array, dim [,mask] )
     integer(kind=KIND) function iparity(array, dim, mask )

      integer(kind=KIND),intent(in) :: array(..)
      logical(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)
  • array - An integer array.

  • dim - an integer scalar from 1 to the rank of array

  • mask - logical conformable with array.

Description#

iparity(3) reduces with bitwise xor (exclusive or) the elements of array along dimension dim if the corresponding element in mask is .true..

Options#

  • array

    an array of integer values

  • dim a value from 1 to the rank of array.

  • mask

    a logical mask either a scalar or an array of the same shape as array.

Result#

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.

Case (i): The result of IPARITY (ARRAY) has a value equal to the bitwise exclusive OR of all the elements of ARRAY. If ARRAY has size zero the result has the value zero.

Case (ii): The result of IPARITY (ARRAY, MASK=MASK) has a value equal to that of

               IPARITY (PACK (ARRAY, MASK)).

Case (iii): The result of IPARITY (ARRAY, DIM=DIM [, MASK=MASK]) has a value equal to that of IPARITY (ARRAY [, MASK=MASK]) if ARRAY has rank one.

           Otherwise, an array of values reduced along the dimension
           **dim** 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

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

Synopsis#

    result = iall(array [,mask]) | iall(array ,dim [,mask])
     integer(kind=KIND) function iall(array,dim,mask)

      integer(kind=KIND),intent(in)        :: array(*)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(*)

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • array must be an integer array

  • mask is a logical array that conforms to array of any logical kind.

  • dim may be of any integer kind.

  • The result will by of the same type and kind as array.

Description#

iall(3) reduces with a bitwise and the elements of array along dimension dim if the corresponding element in mask is .true..

Options#

  • 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.

Result#

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

See Also#

iany(3), iparity(3), iand(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

iand#

Name#

iand(3) - [BIT:LOGICAL] Bitwise logical AND

Synopsis#

    result = iand(i, j)
     elemental integer(kind=KIND) function iand(i,j)

      integer(kind=KIND),intent(in) :: i
      integer(kind=KIND),intent(in) :: j

Characteristics#

  • i, j and the result shall have the same integer type and kind, with the exception that one of i or j may be a BOZ constant.

Description#

iand(3) returns the bitwise logical and of two values.

Options#

  • i

    one of the pair of values to compare the bits of

  • j

    one of the pair of values to compare the bits of

If either i or j is a BOZ-literal-constant, it is first converted as if by the intrinsic function int(3) to type integer with the kind type parameter of the other.

Result#

The result has the value obtained by combining i and i bit-by-bit according to the following table:

    I  |  J  |  IAND (I, J)
  ----------------------------
    1  |  1  |    1
    1  |  0  |    0
    0  |  1  |    0
    0  |  0  |    0

So if both the bit in i and j are on the resulting bit is on (a one); else the resulting bit is off (a zero).

This is commonly called the “bitwise logical AND” of the two values.

Examples#

Sample program:

program demo_iand
implicit none
integer :: a, b
 data a / z'f' /, b / z'3' /
 write (*,*) 'a=',a,' b=',b,'iand(a,b)=',iand(a, b)
 write (*,'(b32.32)') a,b,iand(a,b)
end program demo_iand

Results:

    a= 15  b= 3 iand(a,b)= 3
   00000000000000000000000000001111
   00000000000000000000000000000011
   00000000000000000000000000000011

Standard#

Fortran 95

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 (license: MIT) @urbanjost

iany#

Name#

iany(3) - [BIT:LOGICAL] Bitwise OR of array elements

Synopsis#

    result = iany(array [,mask]) | iany(array ,dim [,mask])
     integer(kind=KIND) function iany(array,dim,mask)

      integer(kind=KIND),intent(in)        :: array(..)
      integer(kind=**),intent(in),optional :: dim
      logical(kind=**),intent(in),optional :: mask(..)

Characteristics#

  • array is an integer array

  • dim may be of any integer kind.

  • mask is a logical array that conforms to array

  • The result will by of the same type and kind as array. It is scalar if dim does not appear or is 1. Otherwise, it is the shape and rank of array reduced by the dimension dim.

note a kind designated as ** may be any supported kind for the type

Description#

iany(3) reduces with bitwise OR (inclusive OR) the elements of array along dimension dim if the corresponding element in mask is .true..

Options#

  • array

    an array of elements to selectively OR based on the mask.

  • dim

    a value in the range from 1 to n, where n equals the rank of array.

  • mask

    a logical scalar; or an array of the same shape as array.

Result#

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
logical,parameter :: T=.true., F=.false.
integer(kind=int8) :: a(3)
   a(1) = int(b'00100100',int8)
   a(2) = int(b'01101010',int8)
   a(3) = int(b'10101010',int8)
   write(*,*)'A='
   print '(1x,b8.8)', a
   print *
   write(*,*)'IANY(A)='
   print '(1x,b8.8)', iany(a)
   print *
   write(*,*)'IANY(A) with a mask'
   print '(1x,b8.8)', iany(a,mask=[T,F,T])
   print *
   write(*,*)'should match '
   print '(1x,b8.8)', iany([a(1),a(3)])
   print *
   write(*,*)'does it?'
   write(*,*)iany(a,[T,F,T]) == iany([a(1),a(3)])
end program demo_iany

Results:

    A=
    00100100
    01101010
    10101010

    IANY(A)=
    11101110

    IANY(A) with a mask
    10101110

    should match
    10101110

    does it?
    T

Standard#

Fortran 2008

See Also#

iparity(3), iall(3), ior(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

ieor#

Name#

ieor(3) - [BIT:LOGICAL] Bitwise exclusive OR

Synopsis#

    result = ieor(i, j)
     elemental integer(kind=**) function ieor(i,j)

      integer(kind=**),intent(in) :: i
      integer(kind=**),intent(in) :: j

Characteristics#

  • i, j and the result must be of the same integer kind.

  • An exception is that one of i and j may be a BOZ literal constant

Description#

ieor(3) returns a bitwise exclusive-or of i and j.

An exclusive OR or “exclusive disjunction” is a logical operation that is true if and only if its arguments differ. In this case a one-bit and a zero-bit substitute for true and false.

This is often represented with the notation “XOR”, for “eXclusive OR”.

An alternate way to view the process is that the result has the value obtained by combining i and j bit-by-bit according to the following table:

  >  I | J |IEOR (I, J)
  >  --#---#-----------
  >  1 | 1 |  0
  >  1 | 0 |  1
  >  0 | 1 |  1
  >  0 | 0 |  0

Options#

  • i

    the first of the two values to XOR

  • j

    the second of the two values to XOR

If either I or J is a boz-literal-constant, it is first converted as if by the intrinsic function INT to type integer with the kind type parameter of the other.

Result#

If a bit is different at the same location in i and j the corresponding bit in the result is 1, otherwise it is 0.

Examples#

Sample program:

program demo_ieor
use,intrinsic :: iso_fortran_env,  only : int8, int16, int32, int64
implicit none
integer(kind=int16) :: i,j
  ! basic usage
   print *,ieor (16, 1), ' ==> ieor(16,1) has the value 17'

   ! it is easier to see using binary representation
   i=int(b'0000000000111111',kind=int16)
   j=int(b'0000001111110000',kind=int16)
   write(*,'(a,b16.16,1x,i0)')'i=     ',i, i
   write(*,'(a,b16.16,1x,i0)')'j=     ',j, j
   write(*,'(a,b16.16,1x,i0)')'result=',ieor(i,j), ieor(i,j)

  ! elemental
   print *,'arguments may be arrays. If both are arrays they '
   print *,'must have the same shape.                        '
   print *,ieor(i=[7,4096,9], j=2)

   ! both may be arrays if of the same size

end program demo_ieor

Results:

 >           17  ==> ieor(16,1) has the value 17
 > i=     0000000000111111 63
 > j=     0000001111110000 1008
 > result=0000001111001111 975
 >  arguments may be arrays. If both are arrays they
 >  must have the same shape.
 >            5        4098          11

Standard#

Fortran 95

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 (license: MIT) @urbanjost

ior#

Name#

ior(3) - [BIT:LOGICAL] Bitwise logical inclusive OR

Synopsis#

    result = ior(i, j)
     elemental integer(kind=KIND) function ior(i,j)

      integer(kind=KIND ,intent(in) :: i
      integer(kind=KIND ,intent(in) :: j

Characteristics#

  • i, j and the result shall have the same integer type and kind, with the exception that one of i or j may be a BOZ constant.

Description#

ior(3) returns the bit-wise Boolean inclusive-or of i and j.

Options#

  • i

    one of the pair of values to compare the bits of

  • j

    one of the pair of values to compare the bits of

If either i or j is a BOZ-literal-constant, it is first converted as if by the intrinsic function int(3) to type integer with the kind type parameter of the other.

Result#

The result has the value obtained by combining I and J bit-by-bit according to the following table:

          I   J   IOR (I, J)
          1   1        1
          1   0        1
          0   1        1
          0   0        0

Where if the bit is set in either input value, it is set in the result. Otherwise the result bit is zero.

This is commonly called the “bitwise logical inclusive OR” of the two values.

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

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 (license: MIT) @urbanjost

not#

Name#

not(3) - [BIT:LOGICAL] Logical negation; flips all bits in an integer

Synopsis#

    result = not(i)
    elemental integer(kind=KIND) function not(i)

     integer(kind=KIND), intent(in) :: i

Characteristics#

  • i may be an integer of any valid kind

  • The returned integer is of the same kind as the argument i.

Description#

not(3) returns the bitwise Boolean inverse of i. This is also known as the “Bitwise complement” or “Logical negation” of the value.

If an input bit is a one, that position is a zero on output. Conversely any input bit that is zero is a one on output.

Options#

  • i

    The value to flip the bits of.

Result#

The result has the value obtained by complementing i bit-by-bit according to the following truth table:

   >    I   |  NOT(I)
   >    ----#----------
   >    1   |   0
   >    0   |   1

That is, every input bit is flipped.

Examples#

Sample program

program demo_not
implicit none
integer :: i
  ! basics
   i=-13741
   print *,'the input value',i,'represented in bits is'
   write(*,'(1x,b32.32,1x,i0)') i, i
   i=not(i)
   print *,'on output it is',i
   write(*,'(1x,b32.32,1x,i0)') i, i
   print *, " on a two's complement machine flip the bits and add 1"
   print *, " to get the value with the sign changed, for example."
   print *, 1234, not(1234)+1
   print *, -1234, not(-1234)+1
   print *, " of course 'x=-x' works just fine and more generally."
end program demo_not

Results:

    the input value      -13741 represented in bits is
    11111111111111111100101001010011 -13741
    on output it is       13740
    00000000000000000011010110101100 13740
     on a two's complement machine flip the bits and add 1
     to get the value with the sign changed, for example.
           1234       -1234
          -1234        1234
     of course 'x=-x' works just fine and more generally.

Standard#

Fortran 95

See Also#

iand(3), ior(3), ieor(3), ibits(3), ibset(3),

ibclr(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

ishftc#

Name#

ishftc(3) - [BIT:SHIFT] Shift rightmost bits circularly, AKA. a logical shift

Synopsis#

    result = ishftc( i, shift [,size] )
     elemental integer(kind=KIND) function ishftc(i, shift, size)

      integer(kind=KIND),intent(in)        :: i
      integer(kind=**),intent(in)          :: shift
      integer(kind=**),intent(in),optional :: size

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i may be an integer of any kind

  • shift and size may be integers of any kind

  • the kind for i dictates the kind of the returned value.

Description#

ishftc(3) circularly shifts just the specified rightmost bits of an integer.

ishftc(3) returns a value corresponding to i with the rightmost size bits shifted circularly shift places; that is, bits shifted out one end of the section are shifted into the opposite end of the section.

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.

Options#

  • i

    The value specifying the pattern of bits to shift

  • shift

    If shift is positive, the shift is to the left; if shift is negative, the shift is to the right; and if shift is zero, no shift is performed.

    The absolute value of shift must be less than size (simply put, the number of positions to shift must be less than or equal to the number of bits specified to be shifted).

  • size

    The value must be greater than zero and less than or equal to bit_size(i).

    The default if bit_size(i) is absent is to circularly shift the entire value i.

Result#

The result characteristics (kind, shape, size, rank, …) are the same as i.

The result has the value obtained by shifting the size rightmost bits of i circularly by shift positions.

No bits are lost.

The unshifted bits are unaltered.

Examples#

Sample program:

program demo_ishftc
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer             :: i
character(len=*),parameter :: g='(b32.32,1x,i0)'
  ! basics
   write(*,*) ishftc(3, 1),' <== typically should have the value 6'

   print *, 'lets start with this:'
   write(*,'(b32.32)')huge(0)
   print *, 'shift the value by various amounts, negative and positive'
   do i= -bit_size(0), bit_size(0), 8
      write(*,g) ishftc(huge(0),i), i
   enddo
  print *,'elemental'
  i=huge(0)
  write(*,*)ishftc(i,[2,3,4,5])
  write(*,*)ishftc([2**1,2**3,-2**7],3)
  print *,'note the arrays have to conform when elemental'
  write(*,*)ishftc([2**1,2**3,-2**7],[5,20,0])

end program demo_ishftc

Results:

 >            6  <== typically should have the value 6
 >  lets start with this:
 > 01111111111111111111111111111111
 >  shift the value by various amounts, negative and positive
 > 01111111111111111111111111111111 -32
 > 11111111111111111111111101111111 -24
 > 11111111111111110111111111111111 -16
 > 11111111011111111111111111111111 -8
 > 01111111111111111111111111111111 0
 > 11111111111111111111111101111111 8
 > 11111111111111110111111111111111 16
 > 11111111011111111111111111111111 24
 > 01111111111111111111111111111111 32
 >  elemental
 >           -3          -5          -9         -17
 >           16          64       -1017
 >  note the arrays have to conform when elemental
 >           64     8388608        -128

Standard#

Fortran 95

See Also#

  • ishft(3) - Logical shift of bits in an integer

  • shifta(3) - Right shift with fill

  • shiftl(3) - Shift bits left

  • shiftr(3) - Combined right shift of the bits of two int…

  • dshiftl(3) - Combined left shift of the bits of two inte…

  • dshiftr(3) - Combined right shift of the bits of two int…

  • cshift(3) - Circular shift elements of an array

  • eoshift(3) - End-off shift elements of an array

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

ishft#

Name#

ishft(3) - [BIT:SHIFT] Logical shift of bits in an integer

Synopsis#

    result = ishftc( i, shift )
     elemental integer(kind=KIND) function ishft(i, shift )

      integer(kind=KIND),intent(in) :: i
      integer(kind=**),intent(in) :: shift

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i is an integer of any kind. the kind for i dictates the kind of the returned value.

  • shift is an integer of any kind.

Description#

ishft(3) returns a value corresponding to i with all of the bits shifted shift places left or right as specified by the sign and magnitude of shift.

Bits shifted out from the left end or right end are lost; zeros are shifted in from the opposite end.

Options#

  • i

    The value specifying the pattern of bits to shift

  • shift

    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.

Result#

The result has the value obtained by shifting the bits of i by shift positions.

  1. If shift is positive, the shift is to the left

  2. if shift is negative, the shift is to the right

  3. if shift is zero, no shift is performed.

Bits shifted out from the left or from the right, as appropriate, are lost. Zeros are shifted in from the opposite end.

Examples#

Sample program:

program demo_ishft
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer             :: shift
character(len=*),parameter :: g='(b32.32,1x,i0)'

   write(*,*) ishft(3, 1),' <== typically should have the value 6'

   shift=4
   write(*,g) ishft(huge(0),shift), shift
   shift=0
   write(*,g) ishft(huge(0),shift), shift
   shift=-4
   write(*,g) ishft(huge(0),shift), shift
end program demo_ishft

Results:

>              6  <== typically should have the value 6
>   11111111111111111111111111110000 4
>   01111111111111111111111111111111 0
>   00000111111111111111111111111111 -4

Standard#

Fortran 95

See Also#

ishftc(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

shifta#

Name#

shifta(3) - [BIT:SHIFT] Right shift with fill

Synopsis#

    result = shifta(i, shift )
     elemental integer(kind=KIND) function shifta(i, shift)

      integer(kind=KIND),intent(in) :: i
      integer(kind=**),intent(in) :: shift

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i is an integer of any kind

  • shift is an integer of any kind

  • the result will automatically be of the same type, kind and rank as i.

Description#

shifta(3) returns a value corresponding to i with all of the bits shifted right by shift places and the vacated bits on the left filled with the value of the original left-most bit.

Options#

  • i

    The initial value to shift and fill

  • shift

    how many bits to shift right. It shall be nonnegative and less than or equal to bit_size(i). or the value is undefined. If shift is zero the result is i.

Result#

The result has the value obtained by shifting the bits of i to the right shift bits and replicating the leftmost bit of i in the left shift bits (Note the leftmost bit in “two’s complement” representation is the sign bit).

Bits shifted out from the right end are lost.

If shift is zero the result is i.

Examples#

Sample program:

program demo_shifta
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer(kind=int32) :: ival
integer             :: shift
integer(kind=int32) :: oval
integer(kind=int32),allocatable :: ivals(:)
integer             :: i
integer(kind=int8)  :: arr(2,2)=reshape([2,4,8,16],[2,2])

  ! basic usage
  write(*,*)shifta(100,3)

  ! loop through some interesting values
   shift=5

   ivals=[ -1, -0, +0, +1, &
   & int(b"01010101010101010101010101010101"), &
   & int(b"10101010101010101010101010101010"), &
   & int(b"00000000000000000000000000011111") ]

   ! does your platform distinguish between +0 and -0?
   ! note the original leftmost bit is used to fill in the vacated bits

   write(*,'(/,"SHIFT =  ",i0)') shift
   do i=1,size(ivals)
      ival=ivals(i)
      write(*,'(  "I =      ",b32.32," == ",i0)') ival,ival
      oval=shifta(ival,shift)
      write(*,'(  "RESULT = ",b32.32," == ",i0)') oval,oval
   enddo
   ! elemental
   write(*,*)"characteristics of the result are the same as input"
   write(*,'(*(g0,1x))') &
     & "kind=",kind(shifta(arr,3)), "shape=",shape(shifta(arr,3)), &
     & "size=",size(shifta(arr,3)) !, "rank=",rank(shifta(arr,3))

end program demo_shifta

Results:

 >           12
 >
 > SHIFT =  5
 > I =      11111111111111111111111111111111 == -1
 > RESULT = 11111111111111111111111111111111 == -1
 > I =      00000000000000000000000000000000 == 0
 > RESULT = 00000000000000000000000000000000 == 0
 > I =      00000000000000000000000000000000 == 0
 > RESULT = 00000000000000000000000000000000 == 0
 > I =      00000000000000000000000000000001 == 1
 > RESULT = 00000000000000000000000000000000 == 0
 > I =      01010101010101010101010101010101 == 1431655765
 > RESULT = 00000010101010101010101010101010 == 44739242
 > I =      10101010101010101010101010101010 == -1431655766
 > RESULT = 11111101010101010101010101010101 == -44739243
 > I =      00000000000000000000000000011111 == 31
 > RESULT = 00000000000000000000000000000000 == 0
 >  characteristics of the result are the same as input
 > kind= 1 shape= 2 2 size= 4

Standard#

Fortran 2008

See Also#

shiftl(3), shiftr(3), ishft(3), ishftc(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

shiftl#

Name#

shiftl(3) - [BIT:SHIFT] Shift bits left

Synopsis#

    result = shiftl( i, shift )
     elemental integer(kind=KIND) function shiftl(i, shift)

      integer(kind=KIND),intent(in) :: i
      integer(kind=**),intent(in) :: shift

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i is an integer of any kind

  • shift is an integer of any kind

  • the result will automatically be of the same type, kind and rank as i.

Description#

shiftl(3) returns a value corresponding to i with all of the bits shifted left by shift places.

Bits shifted out from the left end are lost, and bits shifted in from the right end are set to 0.

If the absolute value of shift is greater than bit_size(i), the value is undefined.

For example, for a 16-bit integer left-shifted five …

    >  |a|b|c|d|e|f|g|h|i|j|k|l|m|n|o|p| <- original 16-bit example
    >  |f|g|h|i|j|k|l|m|n|o|p|           <- left-shifted five
    >  |f|g|h|i|j|k|l|m|n|o|p|0|0|0|0|0| <- right-padded with zeros

Note the value of the result is the same as ishft (i, shift).

Options#

  • i

    The initial value to shift and fill in with zeros

  • shift

    how many bits to shift left. It shall be nonnegative and less than or equal to bit_size(i).

Result#

The return value is of type integer and of the same kind as i.

Examples#

Sample program:

program demo_shiftl
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer             :: shift
integer(kind=int32) :: oval
integer(kind=int32) :: ival
integer(kind=int32),allocatable :: ivals(:)
integer             :: i

  print *, ' basic usage'
  ival=100
  write(*,*)ival, shiftl(ival,3)

 ! elemental (input values may be conformant arrays)
  print *, ' elemental'

 ! loop through some ivalues
   shift=9
   ivals=[ &
   & int(b"01010101010101010101010101010101"), &
   & int(b"10101010101010101010101010101010"), &
   & int(b"11111111111111111111111111111111") ]

   write(*,'(/,"SHIFT =  ",i0)') shift
   do i=1,size(ivals)
      ! print initial value as binary and decimal
      write(*,'(  "I =      ",b32.32," == ",i0)') ivals(i),ivals(i)
      ! print shifted value as binary and decimal
      oval=shiftl(ivals(i),shift)
      write(*,'(  "RESULT = ",b32.32," == ",i0)') oval,oval
   enddo

  ! more about elemental
   ELEM : block
   integer(kind=int8)  :: arr(2,2)=reshape([2,4,8,16],[2,2])
   write(*,*)"characteristics of the result are the same as input"
   write(*,'(*(g0,1x))') &
     & "kind=",kind(shiftl(arr,3)), "shape=",shape(shiftl(arr,3)), &
     & "size=",size(shiftl(arr,3)) !, "rank=",rank(shiftl(arr,3))
   endblock ELEM

end program demo_shiftl

Results:

 >    basic usage
 >           100         800
 >    elemental
 >
 >  SHIFT =  9
 >  I =      01010101010101010101010101010101 == 1431655765
 >  RESULT = 10101010101010101010101000000000 == -1431655936
 >  I =      10101010101010101010101010101010 == -1431655766
 >  RESULT = 01010101010101010101010000000000 == 1431655424
 >  I =      11111111111111111111111111111111 == -1
 >  RESULT = 11111111111111111111111000000000 == -512
 >   characteristics of the result are the same as input
 >  kind= 1 shape= 2 2 size= 4

Standard#

Fortran 2008

See Also#

shifta(3), shiftr(3), ishft(3), ishftc(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

shiftr#

Name#

shiftr(3) - [BIT:SHIFT] Shift bits right

Synopsis#

    result = shiftr( i, shift )
     elemental integer(kind=KIND) function shiftr(i, shift)

      integer(kind=KIND),intent(in) :: i
      integer(kind=**),intent(in) :: shift

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i is an integer of any kind

  • shift is an integer of any kind

  • the result will automatically be of the same type, kind and rank as i.

Description#

shiftr(3) 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.

For example, for a 16-bit integer right-shifted five …

    >  |a|b|c|d|e|f|g|h|i|j|k|l|m|n|o|p| <- original 16-bit example
    >            |a|b|c|d|e|f|g|h|i|j|k| <- right-shifted five
    >  |0|0|0|0|0|f|g|h|i|j|k|l|m|n|o|p| <- left-padded with zeros

Note the value of the result is the same as ishft (i, -shift).

Options#

  • i

    The value to shift

  • shift

    How many bits to shift right. It shall be nonnegative and less than or equal to bit_size(i).

Result#

The remaining bits shifted right shift positions. Vacated positions on the left are filled with zeros.

Examples#

Sample program:

program demo_shiftr
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer             :: shift
integer(kind=int32) :: oval
integer(kind=int32) :: ival
integer(kind=int32),allocatable :: ivals(:)
integer             :: i

  print *,' basic usage'
  ival=100
  write(*,*)ival, shiftr(100,3)

  ! elemental (input values may be conformant arrays)
  print *,' elemental'
   shift=9
   ivals=[ &
   & int(b"01010101010101010101010101010101"), &
   & int(b"10101010101010101010101010101010"), &
   & int(b"11111111111111111111111111111111") ]

   write(*,'(/,"SHIFT =  ",i0)') shift
   do i=1,size(ivals)
      ! print initial value as binary and decimal
      write(*,'(  "I =      ",b32.32," == ",i0)') ivals(i),ivals(i)
      ! print shifted value as binary and decimal
      oval=shiftr(ivals(i),shift)
      write(*,'(  "RESULT = ",b32.32," == ",i0,/)') oval,oval
   enddo

   ! more on elemental
   ELEM : block
   integer(kind=int8)  :: arr(2,2)=reshape([2,4,8,16],[2,2])
   write(*,*)"characteristics of the result are the same as input"
   write(*,'(*(g0,1x))') &
     & "kind=",kind(shiftr(arr,3)), "shape=",shape(shiftr(arr,3)), &
     & "size=",size(shiftr(arr,3)) !, "rank=",rank(shiftr(arr,3))
   endblock ELEM

end program demo_shiftr

Results:

  >    basic usage
  >           100          12
  >    elemental
  >
  >  SHIFT =  9
  >  I =      01010101010101010101010101010101 == 1431655765
  >  RESULT = 00000000001010101010101010101010 == 2796202
  >
  >  I =      10101010101010101010101010101010 == -1431655766
  >  RESULT = 00000000010101010101010101010101 == 5592405
  >
  >  I =      11111111111111111111111111111111 == -1
  >  RESULT = 00000000011111111111111111111111 == 8388607
  >
  >   characteristics of the result are the same as input
  >  kind= 1 shape= 2 2 size= 4

Standard#

Fortran 2008

See Also#

shifta(3), shiftl(3), ishft(3), ishftc(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost