How to perform sign-extension?

What is the optimal way to sign-extend the lowest n bits of an integer?

For example, let’s take a 16-bit integer (the decimal value 34)

0000000000100010

The sign-extend function sext(x,n), with n = 6 should return:

1111111111100010
          ^
FEDCBA9876543210   ! bit index

In other words, the function is supposed to pad the left side with ones, if the bit at position n-1 is set.

The solution I have right now is

! Sign-extend the lowest n bits of x
pure function sext(x,n)
integer(int16), value :: x
integer, value :: n
integer(int16) :: sext
sext = shiftl(ibits(x,0,n),bit_size(x)-n)
sext = shifta(sext,bit_size(x)-n)
end function

Is there a better combination of bit intrinsics to achieve this?

A full program is provided in Compiler Explorer at the link: https://godbolt.org/z/Ko8nscjPq

That is the way I would have done it.

My only suggestion is that the ibits() function in your expression is unnecessary.

sext = shifta(shiftl(x,bit_size(x)-n),bit_size(x)-n)

would work just as well.

1 Like

Assuming you understand that the exact bit representation of integer values may change between systems, and that you actually did want the “if the bit at position n-1 is set”, I did it this way.

program main
  use iso_fortran_env, only: int16

  implicit none

  integer(int16), parameter :: to_test = int(b"0000000001100010", int16)

  print '(b16)', to_test
  print '(b16)', sign_extend(to_test, 5)
  print '(b16)', sign_extend(to_test, 6)
  print '(b16)', sign_extend(to_test, 7)
  print '(b16)', sign_extend(to_test, 8)
contains
  function sign_extend(x, n)
    integer(int16), intent(in) :: x
    integer, intent(in) :: n
    integer(int16) :: sign_extend

    integer(int16) :: mask

    if (btest(x, n-1)) then
      mask = shifta(ibset(0_int16, bit_size(x)-1), bit_size(mask)-n)
      sign_extend = ior(x, mask)
    else
      sign_extend = x
    end if
  end function
end program

This creates a mask with the leftmost bits set and the riightmost bits off. There is already a fortran intrinsic maskl() that does exactly this operation. One would need to time the options, or at least look at the assembler, to see which approach is best.

1 Like

I knew there was probably an intrinsic for that. Just didn’t spend enough time looking for it.

Edit: to add the updated example.

program main
  use iso_fortran_env, only: int16

  implicit none

  integer(int16), parameter :: to_test = int(b"0000000001100010", int16)

  print '(b16)', to_test
  print '(b16)', sign_extend(to_test, 5)
  print '(b16)', sign_extend(to_test, 6)
  print '(b16)', sign_extend(to_test, 7)
  print '(b16)', sign_extend(to_test, 8)
contains
  function sign_extend(x, n)
    integer(int16), intent(in) :: x
    integer, intent(in) :: n
    integer(kind(x)) :: sign_extend

    if (btest(x, n-1)) then
      sign_extend = ior(x, maskl(bit_size(x) - n, kind(x)))
    else
      sign_extend = x
    end if
  end function
end program

Modern fortran now has a pretty complete set of these standard operators for masks, pop counts, parity tests, and so on. This is in contrast to f77 and earlier which had no standard bit operators at all.

Consequently, there are now often many ways to accomplish some given operation. In addition to runtime efficiency, code clarity also plays into which way one should write the code.

For this particular operation of creating a mask, some hardware already has all 64 possible left masks available in readonly memory, so if the compiler simply grabs the right mask at compile time, or at least indexes into that array of masks, that would be hard to beat with some sequence of run time instructions. However, different hardware might require different approaches, so to that extent it requires the compiler to do the right things in the right way, not just the fortran programmer.

2 Likes

Thanks for spotting the simplification @RonShepard.

The shifta(shiftl(...)...) gives reasonably short x86-64 instructions:

; gfortran -O2 -march=x86-64
__extend_MOD_sext:
        mov     ecx, 16
        xor     eax, eax
        sub     ecx, esi
        sal     edi, cl
        sar     di, cl
        cmp     ecx, 16
        cmovl   eax, edi
        ret
; ifx -O2
extend_mp_sext_:
        mov     cx, 16
        sub     cx, word ptr [rsi]
        movzx   eax, word ptr [rdi]
        shl     eax, cl
        mov     edx, ecx
        neg     dx
        cmovs   dx, cx
        xor     esi, esi
        cmp     dx, 16
        cwde
        cmovge  eax, esi
        sar     eax, cl
        cmp     dx, 16
        cmovge  eax, esi
        ret

As Ron says, there is an extensive set of bit operators for different purposes. They are described here: Bit-level inquiry and manipulation — Fortran Programming Language


In the actual problem I was solving I realized afterward that I don’t need a variable length, but only three fixed values (5,6,9). In this case the approach of @kargl is also a valid one:

! Sign-extend the lowest 6 bits of x
pure function sext6(x)
integer(int16), value :: x
integer(int16) :: sext6
sext6 = ieor(x,int(z'FFE0',int16))
end function

It translates to directly to the xor instruction as one would expect:

; ifx -O2
extend_mp_sext6_:
        movzx   eax, word ptr [rdi]
        xor     eax, 65504
        ret
; gfortran -O2 -march=x86-64
__extend_MOD_sext6:
        mov     eax, edi
        xor     eax, -32
        ret
# flang-new -O2
_QMextendPsext6:
        movzwl  (%rdi), %eax
        xorl    $65504, %eax
        movw    %ax, -2(%rsp)
        retq

Btw, when the position falls on the boundary of a full byte, the shifta(shiftl(x,8)8) approach tends to translate to the movsx instruction. The ieor on the other hand with the mask z'FFC0' (b'1111111110000000') still produces xor.

Don’t you want ior and not ieor? If any of the left bits are 1, you’ll end up with 0 with ieor.

Oh, you are right. I didn’t consider that using the OR (XOR) like @kargl suggested still needs the branch to check the “sign” bit (position 5 in the function below):

! Sign-extend the lowest n bits of x
pure function sext6(x) result(sext)
integer(int16), value :: x
integer(int16) :: sext
if (btest(x,5)) then
    sext = ior(x,maskl(10,int16))
else
    sext = x
end if
end function

which brings us to your solution.

I’ve put the two approaches against each other at the link: Compiler Explorer

With both gfortran and ifx the shifting based approach tends to produce between 1 to 4 less instructions. That is both for the n variable case, or the fixed n = 6 case.

In the bit test fails, do you need to mask out any high-order bits? If so, then something like

sext = ibits(x,0,6)

or

sext = iand( x, maskr(6_int16) )

is indicated. Of these two choices, they both look pretty clear and simple, so the one that performs best should be selected.

This extra step is unnecessary with the shifta(shiftl(...)...) approach. That one has no tests or special cases.

1 Like

I am a bit confused. My definition of sign extension is basically what an
assign statement in Fortran does when the LHS is a larger kind than the
RHS; or that you could do with the INT() function. That is, when storing
a signed integer value that is stored in a smaller kind to one with more
bits do it so the value and sign are preserved. What you describe seems
to be a function where you force all bits to the left of a particular
position to be the same as that position (?).

Sign extension has to take into account the way negative values are
represented and endianness. Basically it needs to reflect the numeric
model for signed integers the processor uses.

Now-a-days that often does currently mean to look at the left-most bit
and assign all the new bits that same state. In your example the bit
size of the input and output is the same, and you can select a bit other
than the sign bit as the one to propogate to the left of that position,
which is quite different.

So there are good answers here for something I would not call sign
extension. But if you really want sign extension as I think it is commonly
defined it is built into Fortran’s casting rules and/or is part of what
the INT() function does.

program main
   use, intrinsic :: iso_fortran_env, only: int8, int16, int32, int64
   implicit none
   integer(kind=int8) :: i
   integer(kind=int16) :: ii
   integer(kind=int32) :: iii
   integer(kind=int64) :: iiii
   integer :: j
   i = 34
   do j = 1, 2
      ii = i
      iii = i
      iiii = i
      write (*, '(B8.8,t70,1x,spi0ss,1x,i0)') i, i, bit_size(i)
      write (*, '(B16.16,t70,1x,spi0ss,1x,i0)') ii, ii, bit_size(ii)
      write (*, '(B32.32,t70,1x,spi0ss,1x,i0)') iii, iii, bit_size(iii)
      write (*, '(B64.64,t70,1x,spi0ss,1x,i0)') iiii, iiii, bit_size(iiii)
      i = -i
   end do
end program main
00100010                                                              +34 8
0000000000100010                                                      +34 16
00000000000000000000000000100010                                      +34 32
0000000000000000000000000000000000000000000000000000000000100010      +34 64
11011110                                                              -34 8
1111111111011110                                                      -34 16
11111111111111111111111111011110                                      -34 32
1111111111111111111111111111111111111111111111111111111111011110      -34 64

Yep, that’s what I need. I’m writing a virtual machine for the educational computer architecture Little Computer 3 (LC3).

For example the the STR instruction (Store Base+offset) has the following encoding and behaviour [1]:

In Fortran (on a two’s complement machine) this becomes something like:

code = mem(PC)    ! Fetch instruction from memory
PC = PC + 1    ! Increment program counter

op = ibits(code,12,4)
select case(op)
! ...
case(STR)
  ! (Priviliged mode is ignored)

  sr     = ibits(code,9,3)
  b      = ibits(code,6,3)
  offset = ibits(code,0,6)

  mem(R(b) + sext6(offset)) = R(sr)

! ...
end select 

I suppose I could merge the offset extraction and sign-extension as @RonShepard suggested in his previous answer:

! Get offset6 from instruction x
pure function offset6(x) result(offset)
integer(int16), value :: x
integer(int16) :: offset
if (btest(x,5)) then
    offset = ior(x,maskl(10,int16))
else
    offset = ibits(x,0,6)
end if
end function

The STR instruction would then become:

  sr     = ibits(code,9,3)
  b      = ibits(code,6,3)
  offset = offset6(code)

  mem(R(b) + offset) = R(sr)

I haven’t got everything figured out yet. You can follow my progress or contribute here: GitHub - ivan-pi/lc3-fm: LC-3 computer as a Fortran virtual machine


[1] Patt, Yale N.; Patel, Sanjay (2003). Introduction to Computing Systems: From Bits and Gates to C and Beyond. New York, NY: McGraw-Hill Higher Education.

I don’t know what is the application here, but your description of sign extension is the same as that in the original post. The difference is that your description applies specifically to the 8-, 16-, 32-, and 64-bit twos-complement integers supported by the compiler, whereas in the original post the effective integer size n is arbitrarily used within the int16 value; the effective sign bit is then at position n-1, the leftmost bit within that field. When converting the twos-complement n-bit field into a twos-complement int16, that sign bit must be propagated, while the lower order bits remain the same. The fortran shifta() operator is included in the language because this kind of shifta(shiftl(...)...) operation is so common. As shown in the thread, there are many ways to achieve that sign extension using masks and bitwise iand(), ior(), etc. operations. The original post was asking about the optimal way to do that conversion using the various fortran intrinsic operators. There are also numeric ways to do the same thing, using integer arithmetic. There exists a lot of trickery in this respect, built up over the 75+ years of digital computing.

The only definitions of sign extension are when adding bits to an existing value. The original post used the term sign extension but the bitsize of the input and output remained the same and existing bits in the value were changed. The wikipedia description of sign extension matches the restrictions I mentioned. It applies to when increasing the number of bits in a value and retains the value including its sign. The OP confirmed he was actually looking for an operation that sets all the upper bits above a specified position to the state of that position and why he needed it. It is a useful function but is more general than sign extension in the operations and does not involve changing the number of bits used to represent the value. So it was just a difference in terminology but it applied to what the function should do. There are at least a dozen other ways to get the desired result now that Fortran has standard bit functions. That was not an issue. Which one is most efficient is an interesting issue though.

Please read my previous post where this is explained.

In the original post, an effective 6-bit twos-complement value was sign-extended to produce a 16-bit twos-complement value.

That 6-bit value was embedded within a 16-bit integer, but that is tangential to the overall operation. The result was an INT16 integer, but that is also tangential to the general question. That 6-bit value could have been extracted from a different integer kind, or even from a real or logical or character type, or if we had a string type in the language, it could have been originally a native 6-bit string, or a 6-bit field within a larger string. In all these cases, there would still be the question of what is the best way in fortran to convert that 6-bit twos-complement value to a twos-complement value with a different number of bits. And the output value could also be a different integer kind, or a bit field within some other type, and it would still have resulted in this same general question of what is the best way to do that conversion.

For example, suppose we wanted to extract a 6-bit field from a 64-bit integer and sign-extend it to a 32-bit integer. We would still be talking about the same kind of shifta(shiftl(...)...) operations, or the equivalent maskl() and ior() operations, and so on.

Ron is correct, think of it as an “effective” sign-extension, where a two-complements value of limited range is stored in a larger type. This is the case in the LC-3 instruction set architecture.

I consider this topic solved for now, unless someone wants to offer a more efficient way of doing it. Thank you all for the insightful answers. :slight_smile:

Yes. I understand all of that. It seems obvious I do to me at this point. I wrote the descriptions of the bit functions that were referenced earlier. That operation does not technically meet the traditional meaning of sign extension, which is fine. Thanks for the earlier clarification and description of the needed functionality which resolved the question for me.

1 Like