Fixed- vs allocatable-length string return value

Is there a difference between the two functions below and if yes, which is the preferable method? The function returns the underlying binary string representation (dynamically-sized) of an integer.

Allocatable-length string:

  function bin(x) result(str)
    integer, intent(in) :: x
    character(len=:), allocatable :: str

    integer :: n, i

    n = max(1,bit_size(x)-leadz(x))
    allocate(character(len=n) :: str)
    if (x == 0) then
      str(1:1) = '0'
      return
    end if

    str = repeat('0',n)
    do concurrent (i = 0:n-1, btest(x,i))
      str(n-i:n-i) = '1'
    end do
  end function

Fixed-length string:

  function bin(x) result(str)
    integer, intent(in) :: x
    character(len=max(1,bit_size(x)-leadz(x))) :: str

    integer :: n, i

    if (x == 0) then
      str(1:1) = '0'
      return
    end if
    n = len(str)
    str = repeat('0',n)
    do concurrent (i = 0:n-1, btest(x,i))
      str(n-i:n-i) = '1'
    end do
  end function
1 Like

@ivanpribec,

The issue is similar to this thread. Ultimately only you can decide on your preferred method. Depending on the processor which includes the hardware, the OS and its stack settings, the compiler, and the run-time, the method with the automatic size string result can prove advantageous. Outside of any extreme concerns with performance, I remain biased toward internal IO. So I suggest looking at the following as well:

   print *, "0 in binary: ", bin(0)
   print *, "42 in binary: ", bin(42)
   print *, "huge(int) in binary: ", bin(huge(0))
contains
   function bin(x) result(str)
      integer, intent(in) :: x
      character(len=max(1,bit_size(x)-leadz(x))) :: str
      write( str, fmt="(b0)" ) x
      return
   end function
end

0 in binary: 0
42 in binary: 101010
huge(int) in binary: 1111111111111111111111111111111

1 Like

Thanks for the answer. I will go for the automatic (fixed-) sizing.

I was just playing around with do concurrent after reading the thread you linked. I also noticed later that the body of my function can be simplified to:

  function bin(x) result(str)
    integer, intent(in) :: x
    character(len=max(1,bit_size(x)-leadz(x))) :: str
    integer :: i
    associate(n => len(str))
      str = repeat('0',n)
      do i = 0,n-1
        if (btest(x,i)) str(n-i:n-i) = '1'
      end do
    end associate
  end function

I agree the internal file solution is more straightforward.

I borrowed @urbanjost’s benchmark code and adapted it to the binary string code (without do concurrent):

  call cpu_time(start)
  do i=1,itimes ! put code to test here
  value=bin_io(i)
  enddo
  call cpu_time(finish)
  print '("<bin_internal_io> Processor Time = ",f6.3," seconds.")',finish-start

  call cpu_time(start)
  do i=1,itimes ! put code to test here
  value=bin_f(i)
  enddo
  call cpu_time(finish)
  print '("<bin_automatic  > Processor Time = ",f6.3," seconds.")',finish-start

  call cpu_time(start)
  do i=1,itimes ! put code to test here
  value=bin_a(i)
  enddo
  call cpu_time(finish)
  print '("<bin_allocatable> Processor Time = ",f6.3," seconds.")',finish-start

Here are a few measurements from my ThinkPad T530:

$ ifort -O0 bin_mod.f90 -o bin_test 
$ ./bin_test 
<bin_internal_io> Processor Time =  0.482 seconds.
<bin_automatic  > Processor Time =  0.285 seconds.
<bin_allocatable> Processor Time =  0.341 seconds.
$ ifort -O3 bin_mod.f90 -o bin_test 
$ ./bin_test 
<bin_internal_io> Processor Time =  0.479 seconds.
<bin_automatic  > Processor Time =  0.124 seconds.
<bin_allocatable> Processor Time =  0.177 seconds.
$ gfortran -O0 bin_mod.f90 -o bin_test
$ ./bin_test 
<bin_internal_io> Processor Time =  0.795 seconds.
<bin_automatic  > Processor Time =  0.172 seconds.
<bin_allocatable> Processor Time =  0.170 seconds.
$ gfortran -O3 bin_mod.f90 -o bin_test
$ ./bin_test 
<bin_internal_io> Processor Time =  0.778 seconds.
<bin_automatic  > Processor Time =  0.102 seconds.
<bin_allocatable> Processor Time =  0.114 seconds.
2 Likes

I tried and got 0.000 for all the times output. Mainly because the variable VALUE is never used so the loops are all eliminated by the compiler.

1 Like

I have seen that happen on a few other occasions. I added some print*, value statements, just to be sure the value is used (although an optimizing compiler might only calculate the value from the last iteration). The value of itimes in the loop is 1000000. The timings remained the same. I am using gfortran 10.1.0 and ifort 19.1.0.