I am rewriting some old codes from the 1970s and 1980s that pack/unpack and move bits around. Back then, none of the bit operators that we used were standard, so we have typically 5-10 #if blocks of conditional code to handle all of the compiler-specific versions. We sometimes use EQUIVALENCE
with LOGICAL*1
bytes and INTEGER*2
, INTEGER*4
and INTEGER*8
, and also REAL*8
for machines that did not support INTEGER*8. Fortran 77 and earlier was very limited in this respect, so we had to work to make things as consistent, clear, portable, and efficient as possible.
However, since f90, the usual bit operations have been standardized, and since f2008 we now have the INT8, INT16, INT32, and INT64 integer kinds (with INT64 being required, I think), so now we have more to work with than we did 40 years ago. We still do not have an intrinsic bit string type, which would make all of this simple and portable, but we do have more tools in the standard than we used to. So one required operation is to pack 32-bit integer values into an array of 64-bit integer containers. My first thought is something like
integer(int32) :: i32
integer(int64) :: i64
...
call mvbits( i32, 0, 32, i64, ipos )
...
call mvbits( i64, ipos, 32, i32, 0 )
where ipos == 0 or 32 as appropriate for the i64 destination. That syntax seems simple and clear and it avoids all the complications of the sign bit â the bits should just be copied with no interpretation or scaling or sign extending or anything. But of course for those who do this all the time, you immediately recognize the problem that the mvbits()
intrinsic requires the from
and to
arguments to be of the same KIND. Ok, so then I think
call mvbits( int(i32,int64), 0, 32, i64, ipos )
should do the trick. That works for positive i32 values, but that doesnât work when the sign bit is set. So then I think
call mvbits( transfer(i32,i64), 0, 32, i64, ipos )
should work. On my computer, the transfer() leaves the most significant 32 bits in the from
argument unspecified, but that doesnât matter because mvbits()
is not referencing them.
This actually works on my computer, so maybe I should just stop while Iâm ahead. But here is the problem. The transfer()
operation just moves the bits, it doesnât really define where those bits get moved, in contrast to the IOR(), IAND(), SHIFTL(), and so on bit operators. The programmer isnât really supposed to use the results directly from transfer()
, it is just supposed to hold the bits for a later transfer()
operation that reverses the effect. So specifically in this case, the 32 bits that Iâm working with might conceivably end up in either the low-order bits or the high-order bits of the transfer()
result. So now Iâm back to writing machine-dependent code like
call mvbits( transfer(i32,int64), jpos, 32, i64, ipos )
where jpos==0 when transfer moves the bits to the low-order part of the result and jpos==32 when the bits are in the high-order part of the result. Since this whole exercise is to eliminate machine-dependent code, that uncertainty kind of defeats the purpose. BTW, this low/high problem was there in the old 1970s code too when we used equivalence to move the bits around.
integer*4 i32(2)
integer*8 i64
equivalence (i32,i64)
...
i32(jpos) = bits_to_be_placed
If I want the bits placed in the low-order bits of i64, then on little-endian machines, jpos
should be 1, while on big-endian machines, jpos
should be 2. In our legacy code, this was sometimes done by testing a runtime expression, and it was sometimes done with #if conditional compilation. Either way, it is an ugly mess.
Ok, so maybe I should just avoid mvbits()
. I could go back to shifting and masking the bits with SHIFTL, SHIFTR, IOR, etc. instead. For the 32-bit field width case
i64 = 0_int64
...
i64 = IOR(i32,i64)
That should put those bits in the right place, with no complications due to signed integers or anything like that. But again, there is the restriction that the two arguments in IOR should be of the same kind (understandable in this case), so this does not work. So I could go through the same steps as above with
i64 = IOR(int(i32,int64),i64)
or
i64 = IOR(transfer(i32,i64),i64)
to get the kinds to match, but now Iâm back to the sign problem in the first case and to the machine-dependent transfer()
problems in the second case. On my computer, the transfer operation actually places the bits in the right place, but it seems to leave random noise in the high-order bits, so something like
i64 = IOR(ibits(transfer(i32,i64),0,32),i64)
or the equivalent masking operatiion with IAND() is actually required. That seems way too complicated for the simple operation that I want to do, and of course in the end, it is still machine-dependent exactly where transfer()
puts those bits within the result.
So am I overlooking something here. Is there a simple way to place 32 bits from i32 into the low-order bits of i64? If not, than all of this could be avoided if the original expression that I tried
call mvbits( i32, 0, 32, i64, ipos )
with ipos==0 would have worked. That syntax specifies clearly and unambiguously where the bits are coming from and where they are going to. Why oh why did the standard committee screw us over by requiring the from
and to
arguments to have the same KIND in mvbits()
? And what about a bit string data type, which would have solved all of this once and for all 40 years ago.
This issue also gets back to the âeating your own dog foodâ issue that came up in a different thread recently. If compiler writers using fortran had encountered all of these complications 40 years ago, then they would have immediately changed the language to eliminate the problem. All this would have never been an issue in the language.