Bit manipulation in fortran

Following the previous discussion on this post, I would like to raise more discussion on bit manipulation/representation of real numbers.

What I would like to do is to put the log version of integer vec N = [1, 2, 3, 4], i.e., log2(N), into an array of real numbers. I wish to put it at the last few bits of mantissa.

My goal is to sort this array of real numbers and retrieve the index directly from the sorted array, therefore we need to retrieve those last few bits of mantissa back again.

Thank you so much!

Hui-Jun Chen

One way to retrieve the bits that make up a real number is to use the transfer function. It will copy the contents of the input variable into the result without any further interpretation.

1 Like

After a quick search, is the transfer function copy the whole content of the index and replace the whole real number?

What I want is just to use the last few bits of mantissa to store the index information.

You get the bit pattern in a more convenient form, such as an integer, so that you can extract individual bits via the bit manipulation functions.

So transfer function is to create an integer based on the real number I feed in?

wgt = 0.73980422705616400
write(*, *) transfer(wgt(2), 64)
! output: -536870912

and I can do integer-based bit function? How could I transfer it back to real number?

Well, here is a small, silly, program to illustrate the procedure:

! bitreal.f90 --
!     Go from real to bits to real
!
program bitreal
    use iso_fortran_env
    implicit none

    real(kind=real64)   :: x
    integer(kind=int64) :: y

    x = 0.73980422705616400_real64   ! Note the kind!
    write(*,*) x

    y = transfer( x, y )

    write(*, '(b64)') y

    y = lshift( rshift(y,10), 10 )

    write(*, '(b64)') y

    x = transfer( y, x )

    write(*,*) x
end program bitreal

Do note that you have to specify the kind of the literal number. In your example it is a single-precision real.

The output is:

  0.73980422705616400
  11111111100111101011000111100111101010000101001100001011010100
  11111111100111101011000111100111101010000101001100000000000000
  0.73980422705608362

Thank you so much! I think now I have a better understanding.

May I ask more about bit manipulation? For example, I transfer the real array (double-precision) into an integer array, with the index array also is integer (also double-precision?). How could I incorporate the index array into the last few bits of mantissa? I tried the ibset and I guess if I did it four times it will probably work, but I just wonder whether mvbits or other bit manipulation function can elementally map it to the last few bits of mantissa.

Thanks again!

Actually, yes, MVBITS is an elemental subroutine, so the arguments can be any rank.

Thanks so much! Now I am having the following tries with mvbits and have not been successful:

integer(int64) :: iwgt, idx
real(real64) :: wgt

wgt = 0.73980422705616400
iwgt = transfer(wgt, iwgt)
write(*, '(b64)') iwgt
idx = 1
call mvbits(idx, 4, 4, iwgt, 4)

write(*, '(b64)') iwgt
! iwgt after mvbits is the same as original iwgt

I am no expert in the use of these functions, so I can only guess. Note that your real number is single precision! That could mean a lot of zero bits at the end.

After doing the following additions, it works in compiler explorer with gfortran 13.2 and produces the following output:

use, intrinsic :: iso_fortran_env
integer(int64) :: iwgt, idx
real(real64) :: wgt

wgt = 0.73980422705616400_real64
iwgt = transfer(wgt, iwgt)
write(*, '(b64)') iwgt
idx = 1_int64
call mvbits(idx, 4, 4, iwgt, 4)

write(*, '(b64)') iwgt
! iwgt after mvbits is the same as original iwgt
end
11111111100111101011000111100111101010000101001100001011010100
11111111100111101011000111100111101010000101001100001000000100

Thanks to your testing, I think I figured out the solution to my problem. Somehow it is not fast enough :thinking::thinking::thinking:

I think I have to try out equivalence and reshape to see which way of bit manipulation is the fastest.