位级查询和操作#

bge#

名称#

bge(3) - [BIT:COMPARE] 按位大于或等于

语法#

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

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

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • ij整数种类不一定相同。此外,值可以是 BOZ 常量,其值对于当前平台上可用的具有最多位的整数种类有效。

  • 返回值的类型为默认逻辑类型。

描述#

bge(3) 确定一个整数是否按位大于或等于另一个整数

值的位级表示是平台相关的。例如,系统的字节序和系统是否使用符号的“二进制补码”表示形式都会影响结果。

BOZ 常量(二进制、八进制、十六进制)本身没有种类类型,因此请注意,当它传输到整数类型时会受到截断的影响。常量可以包含的最大位数受编译支持的任何整数种类所能表示的最大位数限制。

位序列比较#

当比较长度不相等的位序列时,较短的序列会在左侧用零位填充到与较长序列相同的长度(最多任何可用整数种类支持的最大位数)。

位序列从左到右逐位比较,直到找到不相等的位或直到所有位都被比较并发现相等。

这些位始终按此顺序计算,不一定是从 MSB 到 LSB(最高有效位到最低有效位)。

如果找到不相等的位,则在不相等位置为零的序列被认为小于在不相等位置为一的序列。

选项#

  • i

    要测试的值,基于值的位表示是否 >= j

  • j

    要与 i 进行比较的值。

结果#

如果 i 按位大于 j,则返回.true.,否则返回.false.

示例#

示例程序

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

结果

整数在位级上的表示方式可能会有所不同。这些只是当今最常见平台上预期的值……

    > 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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

bgt#

名称#

bgt(3) - [BIT:COMPARE] 按位大于

语法#

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

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

特性#

  • i 是一个整数或一个 boz-literal-constant。

  • j 是一个整数或一个 boz-literal-constant。

  • 指定为 ** 的种类可以是该类型支持的任何种类。i 和 **j** 的整数种类不一定相同。种类。此外,值可以是 BOZ 常量,其值对于当前平台上可用的具有最多位的整数种类有效。

  • 返回值的类型为逻辑类型,且为默认种类。

描述#

bgt 确定一个整数是否按位大于另一个整数。值的位级表示是平台相关的。

选项#

  • i

    要比较的参考值。

  • j

    要与 i 进行比较的值。

结果#

返回值的类型为逻辑类型,且为默认种类。如果由i表示的位序列大于由j表示的位序列,则结果为真,否则结果为假。

位从右到左比较。

示例#

示例程序

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

结果

 > 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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ble#

名称#

ble(3) - [BIT:COMPARE] 按位小于或等于

语法#

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

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

特性#

  • ij 可以是任何支持的整数种类,不一定相同。例外情况是,值可以是 BOZ 常量,其值对于当前平台上可用的具有最多位的整数种类有效。

  • 返回值为默认种类的逻辑标量。

描述#

ble(3) 确定一个整数是否按位小于或等于另一个整数,假设任何较短的值都在左侧用零填充到较长值的长度。

选项#

  • i

    要将 j 与之比较的值。

  • j

    要测试的值,以查看其是否小于或等于 i

结果#

如果 j 中的任何位小于 i 中的任何位(从最右边的位开始,并继续向左测试),则返回值为.true.

示例#

示例程序

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

结果

   -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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

blt#

名称#

blt(3) - [BIT:COMPARE] 按位小于

语法#

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

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

特性#

  • i 是任何种类的整数或 BOZ-literal-constant。

  • j 是任何种类的整数或 BOZ-literal-constant,不一定与 i 相同。

  • 结果为默认逻辑种类。

BOZ 常量必须具有对于当前平台上可用的具有最多位的整数种类有效的值。

描述#

blt(3) 确定一个整数是否按位小于另一个整数

选项#

  • i

    应为整数类型或 BOZ 字面常量。

  • j

    应为整数类型或 BOZ 常量。

结果#

返回值的类型为逻辑类型,且为默认种类。

示例#

示例程序

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

结果

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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

bit_size#

名称#

bit_size(3) - [BIT:INQUIRY] 位大小查询函数

语法#

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

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

特征#

  • i 应为整数类型。它可以是标量或数组。

  • KIND 的值是处理器上整数种类参数的任何有效值。

  • 返回值是与输入值相同种类的标量。

描述#

bit_size(3) 返回整数 i 的类型表示的位数(整数精度加上符号位)。

选项#

  • i

    任何种类的整数值,其大小(以位为单位)需要确定。因为只检查参数的类型,所以不需要定义参数;i 可以是标量或数组,但始终返回表示单个元素的标量。

结果#

用于表示i 的类型和种类的值的位数。结果是与i 相同种类的整数标量。

示例#

示例程序

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

典型结果

    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

标准#

Fortran 95

另请参见#

****(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

btest#

名称#

btest(3) - [BIT:INQUIRY] 测试整数值的位。

语法#

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

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

特征#

  • i 是任何种类的整数

  • pos 是任何种类的整数

  • 结果是默认逻辑类型

描述#

如果ipos 位置的位设置为 1,则btest(3) 返回逻辑值.true.。位置零是最右边的位。位位置从右到左增加,直到bitsize(i)-1

选项#

  • i

    包含要测试的位的整数

  • pos

    要查询的位的位号。它必须是值i 的有效位号;即0 <= pos <= bit_size(i)

结果#

如果i 的位位置pos 的值为1,则结果为逻辑值.true.;如果i 的位pos 的值为0,则结果为.false.

序列中位的位号从右到左编号,最右边位的位号为零。

示例#

示例程序

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

结果

  > 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

标准#

Fortran 95

另请参见#

ieor(3)ibclr(3)not(3)ibclr(3)ibits(3)ibset(3)iand(3)ior(3)ieor(3)mvbits(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

storage_size#

名称#

storage_size(3) - [BIT:INQUIRY] 以位为单位的存储大小

语法#

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

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

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • a 可以是任何类型和种类。如果它是多态的,则它不能是未定义的指针。如果它是无限多态的或具有任何延迟类型参数,则它不能是未分配的可分配变量或已分离或未定义的指针。

  • 返回值的种类类型参数是由kind 的值指定的;否则,种类类型参数是默认整数类型的种类类型参数。

  • 结果是默认种类的整数标量,除非指定了kind,在这种情况下,它具有kind 指定的种类。

描述#

storage_size(3) 返回参数a 的存储大小(以位为单位)。

选项#

  • a

    要确定存储大小的实体

  • kind

    定义输出值种类的标量整数常量表达式。

结果#

结果值是以位为单位表示的数组元素的大小,该数组具有a 的动态类型和类型参数。

如果类型和类型参数使得存储关联适用,则结果与内在模块 ISO_FORTRAN_ENV 中定义的命名常量一致。

注释1

数组元素可能需要比孤立标量多“类型”位来存储,因为任何硬件强制的数组元素对齐要求可能不适用于简单的标量变量。

注释2

这旨在表示对象存储时在内存中占据的大小;这可能与它在表达式处理期间占据的大小(可能是本机寄存器大小)或存储在文件中的大小不同。如果对象从未存储在内存中,而仅存储在寄存器中,则此函数仍然返回如果它存储在内存中将占据的大小。

示例#

示例程序

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

结果

    size of integer                 32
    size of real                    32
    size of logical                 32
    size of complex                 64
    size of integer array           32

标准#

Fortran 2008

另请参见#

c_sizeof(3)

fortran-lang 内在描述

leadz#

名称#

leadz(3) - [BIT:COUNT] 整数的前导零位数

语法#

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

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

特征#

  • i 可以是任何种类的整数

  • 返回值是默认整数类型。

描述#

leadz(3) 返回整数的前导零位数。

选项#

  • i

    要计算前导零位数的整数

结果#

前导零位数,考虑输入值的种类。如果i 的所有位都为零,则结果值为bit_size(i)

结果也可以理解为bit_size(i)-1-k,其中k 是输入i 中最左边的 1 位的位置。位号从 0 到 bit-size(),最右边位的位号为 0。

示例#

示例程序

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

结果

  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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

popcnt#

名称#

popcnt(3) - [BIT:COUNT] 设置的位数

语法#

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

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

特征#

  • i 可以是任何种类的整数

  • 返回值是默认整数种类的整数

描述#

popcnt(3) 返回整数的二进制表示形式中设置为 1 的位数。

选项#

  • i

    要计算设置位的数值

结果#

i 中设置为 1 的位数。

示例#

示例程序

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

结果

请注意,在大多数机器上,第一位是符号位,正值使用零;但这与系统相关。这些是典型值,其中 huge(3f) 函数将除第一位之外的所有位都设置为 1。

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

标准#

Fortran 2008

另请参见#

有许多过程在位级操作或查询值

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 内在函数描述(许可证:MIT)@urbanjost

poppar#

名称#

poppar(3) - [BIT:COUNT] 设置位的数量的奇偶校验

概要#

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

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

特征#

  • i 是任何种类的整数

  • 返回值为默认类型的整数

描述#

poppar(3) 返回整数二进制表示的奇偶校验(即设置位的数量的奇偶校验)。

奇偶校验表示为

  • 0(零),如果i中设置为1的位数为偶数。

  • 1(一),如果设置为1的位数为奇数,

选项#

  • i

    要查询其位奇偶校验的值

结果#

如果i中设置的位数为偶数,则返回值等于0;如果设置的位数为奇数,则返回值等于1

示例#

示例程序

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

结果

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

标准#

Fortran 2008

另请参见#

有许多过程在位级操作或查询值

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 内在函数描述(许可证:MIT)@urbanjost

trailz#

名称#

trailz(3) - [BIT:COUNT] 整数的尾随零位数

概要#

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

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

特征#

  • i 是任何类型的整数

  • 结果是默认类型的整数

描述#

trailz(3) 返回整数值的尾随零位数。

选项#

  • i

    要计算尾随零位数的值

结果#

整数值中最后一个非零位之后的右侧最末尾随零位数。

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

如果i的所有位都为零,则结果为输入值的位数,即bit_size(i)

结果也可以看作是i中右侧最末尾1位的位数,从右侧最末尾位为零开始,向左计数。

示例#

示例程序

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

结果

    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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

dshiftl#

名称#

dshiftl(3) - [BIT:COPY] 两个整数的位的组合左移

概要#

    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

特征#

  • ij和返回值的类型相同。例外情况是ij之一可以是BOZ文字常量(BOZ文字常量是二进制、八进制或十六进制常量)。

  • 如果I或J是BOZ文字常量(但两者不是),则首先将其转换为内在函数int(3)一样,转换为类型为integer,其kind类型参数与另一个相同。

  • 指定为 ** 的种类可以是该类型支持的任何种类

描述#

dshiftl(3) 组合ij的位。结果的右侧最末尾shift位是j的左侧最末尾shift位,其余位是i的右侧最末尾bitsize(i)-shift位。

因此,dshiftl被指定为“组合左移”,因为它就像我们将ij连接在一起,将其向左移动shift位,然后保留与ij相同的位数。

例如,对于两个16位值,如果shift=6

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

注意#

这等效于

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

另请注意,使用操作的最后一个表示形式可以得出,当ij都具有相同的值时,如

      dshiftl(i, i, shift)

结果的值与循环移位相同

      ishftc(i, shift)

选项#

  • i

    用于定义组合模式中左侧的位模式

  • j

    用于组合模式中右侧的位模式

  • shift

    应为非负数,且不大于integer输入值中的位数(即不是BOZ文字常量的任一值的位大小)。

结果#

j的左侧最末尾shift位被复制到结果的右侧最末尾位,其余位是i的右侧最末尾位。

示例#

示例程序

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

结果

   > 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

标准#

Fortran 2008

另请参见#

dshiftr(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

dshiftr#

名称#

dshiftr(3) - [BIT:COPY] 两个整数的位的组合右移

概要#

    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

特征#

  • 指定为**的kind可以是integer类型的任何kind值

  • ij和返回值的类型相同。例外情况是ij之一可以是BOZ文字常量(BOZ文字常量是二进制、八进制或十六进制常量)。

  • 如果I或J是BOZ文字常量,则首先将其转换为内在函数int(3)一样,转换为类型为integer,其kind类型参数与另一个相同。

描述#

dshiftr(3) 组合ij的位。结果的左侧最末尾shift位是i的右侧最末尾shift位,其余位是j的左侧最末尾位。

可以将其视为将ij的位连接在一起,丢弃右侧最末尾的shift位,然后保留与输入值相同数量的右侧最末尾位,因此称为“组合右移”……

给定两个用字母标记的16位值……

   i=ABCDEFGHIJKLMNOP
   j=abcdefghijklmnop

将它们连接在一起

   ABCDEFGHIJKLMNOPabcdefghijklmnop

将它们向右移动N=6位,丢弃位

         ABCDEFGHIJKLMNOPabcdefghij

保留16个右侧最末尾的位

                   KLMNOPabcdefghij

注意#

dshifr(i,j,shift)等效于

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

还可以看出,如果ij的值相同

     dshiftr( i, i, shift )

这与负循环移位的结果相同

     ishftc( i,   -shift ).

选项#

  • i

    要组合右移的一对值的左值

  • j

    要组合右移的一对值的右值

  • shift

    移位值是非负数,并且小于或等于输入值中的位数,可以通过bit_size(3)计算得出。

结果#

结果是ij的组合右移,这与输入的位模式从左到右组合相同,在右侧舍弃shift位,然后从最右边的位保留与输入值相同数量的位。

示例#

示例程序

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

结果

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

标准#

Fortran 2008

另请参阅#

dshiftl(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

merge_bits#

名称#

merge_bits(3) - [BIT:COPY] 使用掩码合并位

概要#

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

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

特征#

  • 结果和所有输入值具有相同的整数类型和KIND,但掩码和ij可能是BOZ常量除外。

描述#

三元光栅操作中常见的图形操作是组合来自两个不同来源的位,通常称为位混合。merge_bits(3) 使用mask值的位执行ij的掩码位混合,以确定要从中复制位的输入值。

具体来说,结果的第k位等于i的第k位,如果mask的第k位为1;否则等于j的第k位(因此所有三个输入值都必须具有相同数量的位)。

结果值与以下结果相同

    ior (iand (i, mask),iand (j, not (mask)))

所有值都具有相同整数类型的一个例外是ij和/或掩码可能是BOZ常量(BOZ常量表示它是二进制、八进制或十六进制文字常量)。BOZ值将转换为非BOZ值(s)的整数类型,就像由内在函数int()调用一样,具有非BOZ值(s)的kind,因此BOZ值必须在结果类型的范围内。

选项#

  • i

    当掩码中的关联位为1时,从中选择位的value。

  • j

    当掩码中的关联位为0时,从中选择位的value。

  • mask

    其位用作掩码以从ij中选择位的value

结果#

使用掩码maskij混合的位。

示例#

示例程序

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

结果

    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

标准#

Fortran 2008

另请参阅#

****(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

mvbits#

名称#

mvbits(3) - [BIT:COPY] 在另一个整数中复制在另一个整数中找到的位模式

概要#

   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

特征#

  • from整数

  • frompos是整数

  • len是整数

  • to是与from相同kind的整数。

  • topos是整数

描述#

mvbits(3) 将在整数from中一系列相邻位中找到的位模式复制到另一个整数to(与from具有相同的kind)的指定位置。否则,它会按原样保留to中的位。

复制的位位置必须存在于from的值中。也就是说,frompos+len-1topos+len-1的值必须是非负数,并且小于bit_size(from)。

位从右到左编号为0bit_size(i)-1

选项#

  • from

    要从中读取位的整数

  • frompos

    frompos是要复制的第一个位的position。它是一个非负整数值< bit_size(from)

  • len

    一个非负整数值,指示要从from复制多少位。它不能指定复制超出from末尾的位。也就是说,frompos + len必须小于或等于bit_size(from)

  • to

    要将复制的位放置到其中的整数变量。它必须与from具有相同的kind,甚至可以与from相同,或与其关联。

    to通过复制长度为len的位序列来设置,从fromfrompos位置开始到totopos位置。to的其他位不会更改。在返回时,totopos开始的len位等于fromfrompos开始的len位在输入时的值。

  • topos

    一个非负整数值,指示在to中放置从from复制的指定位的起始位置。topos + len必须小于或等于bit_size(to)

示例#

一个示例程序,使用输入值的字节以相反的顺序填充一个新的32位整数(即更改整数的Endian)。

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

结果

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

标准#

Fortran 95

另请参阅#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ibits#

名称#

ibits(3) - [BIT:COPY] 位子集的提取

概要#

    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

特征#

  • 指定为**的kind可以是任何受支持的整数kind

  • i也可以是任何受支持的整数kind

  • 返回值将与i的kind相同

描述#

ibits(3) 从i中提取一个位字段,从位positionpos开始,向左扩展总共len位。

然后将结果右对齐,结果中剩余的最左边的位将清零。

positionpos的计算假设最右边的位为零,并且position向左递增。

选项#

  • i

    要从中提取位的value

  • pos

    要开始复制的位的position。pos是非负数。

  • len

    要从i复制的位数。它必须是非负数。

pos + len应小于或等于bit_size(i)

结果#

返回值由右对齐的选择的位组成,左侧填充零。

示例#

示例程序

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

结果

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

标准#

Fortran 95

另请参阅#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ibclr#

名称#

ibclr(3) - [BIT:SET] 清除位

概要#

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

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

特征#

  • i应为整数类型。

  • pos应为整数类型。

  • 返回值与i的kind相同。

  • 指定为 ** 的种类可以是该类型支持的任何种类

描述#

ibclr(3) 返回i的值,其中positionpos处的位设置为零。

选项#

  • i

    要修改的初始value

  • pos

    要在输入value中更改位的position。值为零表示最右边的位。pos的值必须是非负数,并且小于(bit_size(i))。

结果#

返回的值与i具有相同的位序列,除了指定的位无条件设置为0

示例#

示例程序

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

结果

 >           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

标准#

Fortran 95

另请参阅#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ibset#

名称#

ibset(3) - [BIT:SET] 将整数中的某一位设置为1

语法#

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

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

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • 返回值与i的类型相同。否则,允许任何整数类型。

描述#

ibset(3) 返回i的值,其中位置pos处的位设置为1。

选项#

  • i

    要修改的初始value

  • pos

    要在输入value中更改位的position。值为零表示最右边的位。pos的值必须是非负数,并且小于(bit_size(i))。

结果#

返回值的位序列与i相同,除了指定的位被无条件设置为1

示例#

示例程序

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

结果

 >           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

标准#

Fortran 95

参见#

ibclr(3)

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

maskl#

名称#

maskl(3) - [BIT:SET] 生成左对齐掩码

语法#

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

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

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • i 是一个整数

  • kind 应为类型为integer的标量常量表达式,其值为受支持的integer类型。

  • 结果为与i相同的kindinteger,除非存在kind,在这种情况下,它用于指定结果的kind。

描述#

maskl(3) 的最左边i位设置为1,其余位设置为0

选项#

  • i

    要设置在integer结果中最左边的位数。它必须在0到结果kind的位数之间。结果的默认kind与i相同,除非kind指定了结果的大小。也就是说,这些Fortran语句必须为.true.

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

    指定integer结果的kind。

结果#

输出integer的最左边i位设置为1,其他位设置为0。

示例#

示例程序

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

结果

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

标准#

Fortran 2008

参见#

maskr(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

maskr#

名称#

maskr(3) - [BIT:SET] 生成右对齐掩码

语法#

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

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

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • i 是一个整数

  • kind 应为类型为integer的标量常量表达式,其值为受支持的integer类型。

  • 结果为与i相同的kindinteger,除非存在kind,在这种情况下,它用于指定结果的kind。

描述#

maskr(3) 生成一个integer,其最右边i位设置为1,其余位设置为0。

选项#

  • i

    要设置在integer结果中最右边的位数。它必须在0到结果kind的位数之间。结果的默认kind与i相同,除非kind指定了结果的大小。也就是说,这些Fortran语句必须为.true.

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

    指定integer结果的kind。

结果#

输出integer的最右边i位设置为1,其他位设置为0。

示例#

示例程序

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

结果

 >   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

标准#

Fortran 2008

参见#

maskl(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

iparity#

名称#

iparity(3) - [BIT:LOGICAL] 数组元素的按位异或

语法#

    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 - integer数组。

  • dim - 从1到array秩的integer标量

  • mask - 与array一致的logical

描述#

iparity(3) 使用按位xor(异或)沿维度dim减少array的元素,如果mask中的对应元素为.true.

选项#

  • array

    integer值的数组

  • dim 从1到array秩的值。

  • mask

    一个logical掩码,可以是标量,也可以是与array形状相同的数组。

结果#

结果与array的类型相同。

如果dim不存在,则返回一个标量,其中包含array中所有元素的按位xor。否则,返回一个秩为n-1的数组,其中n等于array的秩,并且形状类似于array,但去掉了维度dim

情况(i):IPARITY(ARRAY)的结果的值等于ARRAY的所有元素的按位异或。如果ARRAY的大小为零,则结果值为零。

情况(ii):IPARITY(ARRAY,MASK=MASK)的结果的值等于

               IPARITY (PACK (ARRAY, MASK)).

情况(iii):IPARITY(ARRAY,DIM=DIM [, MASK=MASK])的结果的值等于IPARITY(ARRAY [, MASK=MASK])的结果,如果ARRAY的秩为一。

           Otherwise, an array of values reduced along the dimension
           **dim** is returned.

示例#

示例程序

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

结果

   01001110

标准#

Fortran 2008

参见#

iany(3)iall(3)ieor(3)parity(3)

fortran-lang 内在描述

iall#

名称#

iall(3) - [BIT:LOGICAL] 数组元素的按位与

语法#

    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(*)

特性#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • array必须是integer数组

  • mask是与array一致的任何logical类型的logical数组。

  • dim可以是任何integer类型。

  • 结果将与array的类型和kind相同。

描述#

iall(3) 使用按位and沿维度dim减少array的元素,如果mask中的对应元素为.true.

选项#

  • array

    应为类型为integer的数组

  • dim

    (可选)应为类型为integer的标量,其值在1到n的范围内,其中n等于array的秩。

  • mask

    (可选)应为类型为logical,并且可以是标量,也可以是与array形状相同的数组。

结果#

结果与array的类型相同。

如果dim不存在,则返回一个标量,其中包含array中所有元素的按位all。否则,返回一个秩为n-1的数组,其中n等于array的秩,并且形状类似于array,但去掉了维度dim

示例#

示例程序

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

结果

 > 00100000

标准#

Fortran 2008

参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

iand#

名称#

iand(3) - [BIT:LOGICAL] 按位逻辑与

语法#

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

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

特性#

  • ij和结果应具有相同的integer类型和kind,但ij之一可以是BOZ常量除外。

描述#

iand(3) 返回两个值的按位逻辑

选项#

  • i

    要比较其位的两个值之一

  • j

    要比较其位的两个值之一

如果ij是BOZ文字常量,则首先将其转换为类型为integer,kind类型参数与另一个相同,就像由内在函数int(3)转换一样。

结果#

结果的值是根据下表逐位组合ii获得的

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

因此,如果ij中的位都打开,则结果位打开(为1);否则结果位关闭(为0)。

这通常称为两个值的“按位逻辑与”。

示例#

示例程序

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

结果

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

标准#

Fortran 95

参见#

ieor(3)ibclr(3)not(3)btest(3)ibclr(3)ibits(3)ibset(3)ior(3)ieor(3)mvbits(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

iany#

名称#

iany(3) - [BIT:LOGICAL] 数组元素的按位或

概要#

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

特征#

  • array 是一个整数数组

  • dim可以是任何integer类型。

  • mask 是一个与array一致的逻辑数组

  • 结果将与array具有相同的类型和种类。如果dim不存在或为1,则它是标量。否则,它是数组在维度dim上减少后的形状和秩。

注意,指定为 ** 的种类可以是该类型支持的任何种类

描述#

iany(3) 使用按位OR(包含OR)沿着维度dim减少array的元素,如果mask中相应的元素为.true.

选项#

  • array

    一个元素数组,根据掩码选择性地进行OR运算。

  • dim

    一个范围在1到n之间的值,其中n等于array的秩。

  • mask

    一个逻辑标量;或一个与array形状相同的数组。

结果#

结果与array的类型相同。

如果dim不存在,则返回一个包含array中所有元素按位的标量。否则,返回一个秩为n-1的数组,其中n等于array的秩,并且形状类似于array,但去掉了维度dim

示例#

示例程序

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

结果

    A=
    00100100
    01101010
    10101010

    IANY(A)=
    11101110

    IANY(A) with a mask
    10101110

    should match
    10101110

    does it?
    T

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ieor#

名称#

ieor(3) - [BIT:LOGICAL] 按位异或

概要#

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

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

特征#

  • ij和结果必须具有相同的整数种类。

  • 例外情况是ij之一可以是BOZ字面常量

描述#

ieor(3) 返回ij的按位异或。

异或或“排斥析取”是一种逻辑运算,当且仅当其参数不同时才为真。在这种情况下,一位和零位分别代替真和假。

这通常用“XOR”(“eXclusive OR”)表示。

另一种看待该过程的方法是,结果具有通过根据下表按位组合ij获得的值

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

选项#

  • i

    要进行XOR运算的两个值中的第一个

  • j

    要进行XOR运算的两个值中的第二个

如果I或J是boz-literal-constant,则首先将其转换为就像由内在函数INT转换为类型整数,其种类类型参数为另一个。

结果#

如果ij中相同位置的位不同,则结果中对应的位为1,否则为0

示例#

示例程序

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

结果

 >           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

标准#

Fortran 95

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ior#

名称#

ior(3) - [BIT:LOGICAL] 按位逻辑包含或

概要#

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

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

特征#

  • ij和结果应具有相同的integer类型和kind,但ij之一可以是BOZ常量除外。

描述#

ior(3) 返回ij的按位布尔包含或。

选项#

  • i

    要比较其位的两个值之一

  • j

    要比较其位的两个值之一

如果ij是BOZ文字常量,则首先将其转换为类型为integer,kind类型参数与另一个相同,就像由内在函数int(3)转换一样。

结果#

结果具有通过根据下表按位组合I和J获得的值

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

如果在任一输入值中设置了该位,则在结果中设置该位。否则,结果位为零。

这通常称为两个值的“按位逻辑包含或”。

示例#

示例程序

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

结果

         53 00110101
         45 00101101
         61 00111101

标准#

Fortran 95

另请参见#

ieor(3)ibclr(3)not(3)btest(3)ibclr(3)ibits(3)ibset(3)iand(3)ieor(3)mvbits(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

not#

名称#

not(3) - [BIT:LOGICAL] 逻辑非;翻转整数中的所有位

概要#

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

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

特征#

  • i可以是任何有效种类的整数

  • 返回的整数与参数i具有相同的种类。

描述#

not(3) 返回i的按位布尔反值。这也被称为该值的“按位补码”或“逻辑非”。

如果输入位为1,则输出位置为0。相反,任何输入位为0的输出位置为1。

选项#

  • i

    要翻转其位的值。

结果#

结果具有通过根据下表按位对i进行补码获得的值

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

也就是说,每个输入位都被翻转。

示例#

示例程序

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

结果

    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.

标准#

Fortran 95

另请参见#

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

ibclr(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ishftc#

名称#

ishftc(3) - [BIT:SHIFT] 循环右移最右边的位,也称为逻辑移位

概要#

    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

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • i可以是任何种类的整数

  • shiftsize可以是任何种类的整数

  • i的种类决定了返回值的种类。

描述#

ishftc(3) 循环移位整数指定的右侧最右边的位。

ishftc(3) 返回一个对应于i的值,其最右边的size位循环移位shift位;也就是说,从一端移出的位被移到该部分的另一端。

shift大于零的值对应于左移,零值对应于不移位,小于零的值对应于右移。

选项#

  • i

    指定要移位的位模式的值

  • shift

    如果shift为正,则向左移位;如果shift为负,则向右移位;如果shift为零,则不执行移位。

    shift的绝对值必须小于size(简单地说,移位的位数必须小于或等于指定要移位的位数)。

  • size

    该值必须大于零且小于或等于bit_size(i)。

    如果bit_size(i)不存在,则默认情况下是循环移位整个值i

结果#

结果特征(种类、形状、大小、秩等)与i相同。

结果具有通过将isize个最右边的位循环移位shift个位置获得的值。

没有位丢失。

未移位的位保持不变。

示例#

示例程序

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

结果

 >            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

标准#

Fortran 95

另请参见#

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

ishft#

名称#

ishft(3) - [BIT:SHIFT] 整数的位逻辑移位

概要#

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

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

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • i 是任何类型的整数i 的类型决定了返回值的类型。

  • shift 是任何类型的整数

描述#

ishft(3) 返回一个对应于i 的值,其中所有位都根据shift 的符号和大小左移或右移 shift 个位置。

从左端或右端移出的位将丢失;从相反端移入零。

选项#

  • i

    指定要移位的位模式的值

  • shift

    shift大于零的值对应于左移,零值对应于不移位,小于零的值对应于右移。

    如果shift 的绝对值大于bit_size(i),则该值未定义。

结果#

结果具有通过将i 的位移位shift 个位置获得的值。

  1. 如果shift 为正,则移位为左移

  2. 如果shift 为负,则移位为右移

  3. 如果shift 为零,则不执行移位。

根据需要,从左端或右端移出的位将丢失。从相反端移入零。

示例#

示例程序

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

结果

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

标准#

Fortran 95

另请参见#

ishftc(3)

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

shifta#

名称#

shifta(3) - [BIT:SHIFT] 带填充的右移

概要#

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

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

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • i 是任何种类的整数

  • shift 是任何类型的整数

  • 结果将自动与i 具有相同的类型、种类和秩。

描述#

shifta(3) 返回一个对应于i 的值,其中所有位都右移 shift 个位置,并且左侧空出的位用原始最左端位的的值填充。

选项#

  • i

    要移位和填充的初始值

  • shift

    右移多少位。它应是非负数且小于或等于bit_size(i)。否则值为未定义。如果shift 为零,则结果为i

结果#

结果具有通过将i 的位右移 shift 位并在左侧 shift 位中复制i 的最左端位获得的值(注意,“二进制补码”表示形式中的最左端位是符号位)。

从右端移出的位将丢失。

如果shift 为零,则结果为i

示例#

示例程序

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

结果

 >           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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

shiftl#

名称#

shiftl(3) - [BIT:SHIFT] 左移位

概要#

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

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

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • i 是任何种类的整数

  • shift 是任何类型的整数

  • 结果将自动与i 具有相同的类型、种类和秩。

描述#

shiftl(3) 返回一个对应于i 的值,其中所有位都左移 shift 个位置。

从左端移出的位将丢失,从右端移入的位将设置为0

如果shift 的绝对值大于bit_size(i),则该值未定义。

例如,对于左移五位的 16 位整数……

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

请注意,结果的值与ishft (i, shift) 相同。

选项#

  • i

    要移位并用零填充的初始值

  • shift

    左移多少位。它应是非负数且小于或等于bit_size(i)

结果#

返回值为整数类型,与i 的种类相同。

示例#

示例程序

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

结果

 >    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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost

shiftr#

名称#

shiftr(3) - [BIT:SHIFT] 右移位

概要#

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

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

特征#

  • 指定为 ** 的种类可以是该类型支持的任何种类

  • i 是任何种类的整数

  • shift 是任何类型的整数

  • 结果将自动与i 具有相同的类型、种类和秩。

描述#

shiftr(3) 返回一个对应于i 的值,其中所有位都右移 shift 个位置。

如果shift 的绝对值大于bit_size(i),则该值未定义。

从右端移出的位将丢失,从左端移入的位将设置为 0。

例如,对于右移五位的 16 位整数……

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

请注意,结果的值与ishft (i, -shift) 相同。

选项#

  • i

    要移位的值

  • shift

    右移多少位。它应是非负数且小于或等于bit_size(i)

结果#

剩余的位右移 shift 个位置。左侧空出的位置将填充零。

示例#

示例程序

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

结果

  >    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

标准#

Fortran 2008

另请参见#

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

fortran-lang 内在函数描述(许可证:MIT)@urbanjost