Optimizing conversion of integer arrays into integers

Dear friends,

I’m writing a Fortran code in which I have to convert integer arrays into integers; for example, [2, 5, 6] into 256. I know 2 methods:

a) Converting the array into a string, concatenate its elements and then converting the resulting string into an integer.
b) The mathematical method

y = 0
DO x = 1, n
y = 10*y + A(x) ! (As are the array elements)
END DO

According to your experience, which one is the most efficient in terms of code speed? Or perhaps there exists a better procedure?

Many thanks for your help.

1 Like

@CConde,

Welcome. Chances are high you’ll have to try things yourself to know what you think is “most efficient” especially with code speed. My hunch is it’ll be nearly impossible to gage the speed differences with the methods that catch your interest. An alternate view you can consider is simplicity of the approach and quite a few readers of your code will likely find the “internal” IO facility in Fortran trump all other!

   integer, allocatable :: x(:)
   character(len=:), allocatable :: s
   character(len=256) :: fmts
   integer :: i
   x = [ 42, 99, 1, 0 ]
   allocate( character(len=range(x)*size(x)) :: s )
   write( s, fmt="(*(g0))") x
   write( fmts, "(g0)" ) len_trim(s)
   fmts = "(i" // trim(fmts) // ")"
   read( s, fmt=fmts ) i
   print *, "i = ", i
end

Expected output is

i = 429910

2 Likes

FortranFan, many thanks for your help

1 Like

pmk, thank you for your help.

1 Like

@CConde welcome to the forum! Thank you @FortranFan and @pmk for answering. @CConde if you have any other questions regarding this or anything else, please do not hesitate to ask.

Other solution using ’ do concurrent’

program array_to_integer
    integer, parameter:: a(3) = [2, 5, 6]
    integer, parameter:: a_size = ubound(a, 1)
    integer:: result
    integer:: i, pos

    do concurrent (i = 1:a_size)
        pos = a_size - i
        result = result + a(i) * 10**pos
    end do

    print *, "Result ", result

end program array_to_integer

“That’s not a conforming DO CONCURRENT. You can’t reduce like that.”

I tested it and it worked properly. How can I fix it?

May be this?:

program array_to_integer
    implicit none

    integer, allocatable:: a(:)
    integer:: a_size, result, i, pos

    ! Setup
    a = [2, 5, 6]
    a_size = size(a)
    result = 0

    ! Main loop
    do concurrent (i = 1:a_size) shared(result)
        pos = a_size - i
        result = result + a(i) * 10**pos
    end do

    ! Show result
    print *, "Result ", result

end program array_to_integer

and compiled in this way:

$ ifort -parallel array_to_integer.f90

If your problems are going to be large enough that performance is an
issue, you will want to learn how to use profiling tools such as GNU
gprof(1) as time goes by.

For simple timing tests when you want to try things like DO CONCURRENT
versus a DO loop or coarrays or OpenMP or MPI, … note that you can
empirically get basic timing information with simple Fortran intrinsics,
as is shown below in a basic form.

Be careful with simple tests. Sometimes the compiler will see something
like the results never being used for anything and will actually
eliminate the code, giving you great performance numbers!

You can usually get the compiler to not throw your code out by turning
off optimization, which is usually done with switches like “-g -O0”.
Otherwise, minimally “use” the answers or stick in a global variable the
compiler will not be able to determine is unused or look for a compiler
switch to not eliminate code or other dumb tricks but turning off
optimization is usually a good place to start.

With more substantial procedures you generally want to test with various
optimizations and options on (Discussing that would fill a tome by
itself). You will sometimes be surprised by how different various
compilers can be too.

In the basic case you have mentioned you would probably just want to
do the conversions in-line in a DO loop, as the overhead of calling the
function might overwhelm the time taken to compute. The following sample
code is purely just to show the concept, but here is a simple program
(remembering all the caveats mentioned and many more unmentioned)
composed of three functions that would do what you want using a few
different-looking methods and a simplistic timing of them.

** I am assuming your values are single digits. This would need tweeked otherwise.
Did not really test this much!**

program testit
implicit none
integer,parameter :: itimes=1000000
integer           :: i
integer           :: value
real              :: start, finish
   write(*,*)silly([4,5,9,1,3])
   write(*,*)multiply([4,5,9,1,3])
   write(*,*)string([4,5,9,1,3])

   call cpu_time(start)
   do i=1,itimes ! put code to test here
    value=silly([4,5,9,1,3])
   enddo
   call cpu_time(finish)
   print '("<SILLY   >Processor Time = ",f6.3," seconds.")',finish-start

   call cpu_time(start)
   do i=1,itimes ! put code to test here
    value=multiply([4,5,9,1,3])
   enddo
   call cpu_time(finish)
   print '("<MULTIPLY>Processor Time = ",f6.3," seconds.")',finish-start

   call cpu_time(start)
   do i=1,itimes ! put code to test here
    value=string([4,5,9,1,3])
   enddo
   call cpu_time(finish)
   print '("<STRING  >Processor Time = ",f6.3," seconds.")',finish-start

contains

function string(list) result(answer)
integer,intent(in) :: list(:)
integer            :: answer
integer            :: i
character(len=10)  :: str
   write(str,'(*(i1))')(list(i),i=1,size(list))
   read(str,'(i10)')answer
end function string

function multiply(list) result(answer)
integer,intent(in) :: list(:)
integer            :: answer
integer            :: i
answer = 0
   do i = 1, size(list)
      answer = 10*answer + list(i)
   enddo
end function multiply

function silly(list) result(answer)
integer,intent(in) :: list(:)
integer            :: answer
integer            :: i
   answer=list(1)
   do i=2,size(list)
      answer=shiftl(answer,3)+shiftl(answer,1)+list(i)
   enddo
end function silly

end program testit

Always run your tests multiple times if you can afford to,
as there are often things like I/O cacheing that can affect it.
Go for the clearer or more maintainable method if what you are
tuning it not going to get massive use.

But I am only going to run this once with optimization off, and
then show the magic times this test can get with optimization
on (the compiler was “smart” and realized I never used the answers
and there were no side-effects so it just did not call the code!)

driving the point home

As mentioned, make sure you can trust the results. Seeing should
not always be believing …

gfortran -O0 -g simple_times.f90
./a.out
       45913
       45913
       45913
<SILLY   >Processor Time =  0.052 seconds.
<MULTIPLY>Processor Time =  0.060 seconds.
<STRING  >Processor Time =  4.666 seconds.

gfortran -O3 -g simple_times.f90
./a.out
       45913
       45913
       45913
<SILLY   >Processor Time =  0.000 seconds.
<MULTIPLY>Processor Time =  0.000 seconds.
<STRING  >Processor Time =  0.000 seconds.

So a good old multiply is not all that bad for this compiler.
No need to do something “sophisticated” unless you are going
to be converting a boat-load of values.

Do NOT use the silly(3f) function. If it is significantly
faster than a multiply try a different compiler.

I found two other compilers seemed to do a bit better with the string
function, and actually did the multiply faster than the bit-shifting
example (although you could tune that a bit) backing up that the multiply
is simple to understand and has good performance.

other compilers

Always test with as many compilers as you can. Two others gave
similar results:

<SILLY   >Processor Time =  0.067 seconds.
<MULTIPLY>Processor Time =  0.058 seconds.
<STRING  >Processor Time =  2.461 seconds.

<SILLY   >Processor Time =  0.068 seconds.
<MULTIPLY>Processor Time =  0.058 seconds.
<STRING  >Processor Time =  2.463 seconds.

SUMMARY

Three compilers did fine with multiply and it is significantly faster
than internal I/O. If you were going to use the result as a string instead
of as an INTEGER you might select the I/O method though.

Now, add the SUM method and any other suggestions and feel the power as you figure out the answers :slight_smile:

Do you care about retaining leading zeros or producing results bigger than huge(0)? Those will
be issues if so. ** if your values are not single positive digits several of the solutions including this one will not all work. Test with different types of values you need to use, which this example does not do. I’m primarily showing how you can do simple timing!

3 Likes