Trying to convert a number to a string

Hi all,
I am trying to do the problem 4 of the Euler project.

My approach is to convert the number to a string and compare the last half with the first half.
However, I am having trouble converting a number to a string. Here is my code so far ( ifort -O3 )

PROGRAM pr4
  IMPLICIT NONE

  INTEGER(KIND=4) :: number_1,number_2,product_of_numbers
  INTEGER(KIND=4),PARAMETER :: lower_limit=10,upper_limit=99
  CHARACTER(LEN=:),ALLOCATABLE :: palindrome_check_string


  DO number_1 = lower_limit,upper_limit
     DO number_2 = lower_limit,upper_limit
        product_of_numbers = number_1 * number_2
        WRITE(palindrome_check_string,*) product_of_numbers
        DEALLOCATE(palindrome_check_string)

     END DO
  END DO



END PROGRAM pr4

The code compiles, however returns an error.
Hereā€™s the error:

forrtl: severe (66): output statement overflows record, unit -5, file Internal List-Directed Write
Image              PC                Routine            Line        Source                        
pr4                000000000042BCC9  Unknown               Unknown  Unknown                       
pr4                000000000040FAFE  Unknown               Unknown  Unknown                       
pr4                000000000040DCC3  Unknown               Unknown  Unknown                       
pr4                0000000000403918  Unknown               Unknown  Unknown                       
pr4                0000000000403862  Unknown               Unknown  Unknown                       
libc.so.6          00007F69C9829510  Unknown               Unknown  Unknown                       
libc.so.6          00007F69C98295C9  __libc_start_main     Unknown  Unknown                       
pr4                0000000000403765  Unknown               Unknown  Unknown                       

@Aurelius_Nero ,

Re: your comment, ā€œI am having trouble converting a number to a stringā€, see the ā€œparseā€ method in this comment in the following thread:

For reference, you can also check the work by @lkedward to update the Fortran code at the Julia microbenchmark site mentioned in the above thread.

2 Likes

You are writing into an unallocated character string. There is nothing to gain by making the string allocatable. For 32-bit integers, it needs to be 11 characters in order hold the largest values and a negative sign, so just make it 11 characters. Iā€™m assuming here that you will eventually change lower_limit and upper_limit to larger values. As written, you only need 5 characters.

If you change integer kinds, then you will need to change the size of the string. Given an integer of some kind, you can easily compute the number of decimal digits in huge(i), but I donā€™t know of an easy way to do that at compile time. One needs something like the inverse function of selected_int_kind(). If precision() would take an integer argument, that would work, but it doesnā€™t, it only works with real and complex kinds. You can scale storage_size(i), which is the bit size, but with simple expressions like storage_size(i)/3+1 you will overcount the decimal digit count for large integer kinds. However, that may be close enough for this purpose.

One other comment might be appropriate for this too. You are using list-directed i/o to write to the string. If you want more control over leading and trailing spaces, then use something like an ā€˜(i0)ā€™ format. That always results in the minimal number of digits written to the string. You can also avoid the internal i/o entirely and just compute the characters yourself from the integer value.

1 Like

Well, if you really wanted a constant for the string length required, this old technique would work, I think:

 program testit
use,intrinsic :: iso_fortran_env,  only : int8, int16, int32, int64
! find how many characters to use for integers
integer(kind=int8),parameter  :: b8=ceiling(log10(real(huge(0_int8))))+1
integer(kind=int16),parameter :: b16=ceiling(log10(real(huge(0_int16))))+1
integer(kind=int32),parameter :: b32=ceiling(log10(real(huge(0_int32))))+1
integer(kind=int64),parameter :: b64=ceiling(log10(real(huge(0_int64))))+1
   write(*,'(i0,/,a,1x,i0)')huge(b8),repeat('=',b8),b8
   write(*,'(i0,/,a,1x,i0)')huge(b16),repeat('=',b16),b16
   write(*,'(i0,/,a,1x,i0)')huge(b32),repeat('=',b32),b32
   write(*,'(i0,/,a,1x,i0)')huge(b64),repeat('=',b64),b64
end program testit

But as suggested, just using a character(len=20) variable would work. The formula used here without the +1 would work for finding the string length of the number as well, but not sure that a len_trim() call might be faster, in which case minimizing the string length would probably be faster.

For two digits just going through them all, duplicates, factors, and such aside would be reasonably fast, but you might want to look at the ā€œGreedy Algorithmā€ as one method of finding it faster

for bigger number of digits, or at least starting with the bigger numbers first and skipping values smaller, as converting to a string is pretty expensive. Some really eye-catching patterns of factors and primes in those palidrome numbers.

2 Likes

@FortranFan @RonShepard @urbanjost , Thank you all for your suggestions.
Here is my slightly amateurish way of doing it :

PROGRAM pr4
  IMPLICIT NONE

  INTEGER(KIND=4) :: i,j,ipos,number_1,number_2,product_of_numbers,length_of_digit,largest_palindrome
  INTEGER(KIND=4),PARAMETER :: lower_limit=100,upper_limit=999,length=11
  CHARACTER(LEN=length) :: palindrome_input_string,palindrome_check_string
  LOGICAL :: is_palindrome

  100 FORMAT (i0)
  largest_palindrome = 0

  DO number_1 = lower_limit,upper_limit
     DO number_2 = lower_limit,upper_limit
        product_of_numbers = number_1 * number_2
        is_palindrome = .FALSE.
        WRITE(palindrome_input_string,100) product_of_numbers
        ipos = 0
        length_of_digit = 0
        DO i=1,length
           IF (palindrome_input_string(i:i) .NE. ' ') THEN
              ipos = ipos + 1
              palindrome_check_string(ipos:ipos) = palindrome_input_string(i:i)
              length_of_digit = length_of_digit + 1
           END IF
        END DO
        j=0
        DO i=1,length_of_digit/2
           IF (palindrome_input_string(i:i) .NE. palindrome_input_string((length_of_digit-j):(length_of_digit-j))) EXIT
           IF (i .EQ. length_of_digit/2) THEN
              is_palindrome = .TRUE.
              IF (product_of_numbers .GT. largest_palindrome) largest_palindrome = product_of_numbers
           END IF
           j=j+1
        END DO
     END DO
  END DO

  PRINT *, "The largest palindrome is : ",largest_palindrome



END PROGRAM pr4

I hope to in future probably use urbanjostā€™s really cool module from the Fortran wiki :
https://fortranwiki.org/fortran/show/tostring
I am hoping for some more feedback regarding programming style, good practices etc.
Thank you all once again.

These are just minor comments. I think the i0 format left justifies the characters within palindrome_input_string. Since you are just dealing with positive values, you donā€™t need to watch for a leading negative sign. That means you can count the number of digits with the len_trim() intrinsic, and you donā€™t need a do loop to do that.

It isnā€™t clear if you want to count just the strings with an even number of digits, or also those with an odd number. I think your code is counting both.

Finally, you are considering all possible products of the integers. Since i*j == j*i, you really only need to consider the unique pairs in the search. There is an easy way to limit the nested do loops to achieve that.

1 Like

As noted, skipping unneeded calculations can give a big gain. Just flipping the order of the loops from large to small values and not processing candidates smaller than the most recent answer speeds it up
by a factor of 40 to 60 depending on the compiler and compiler options; which is an additional way to
reduce computation in addition to skipping the duplicates. For example, just changing a few lines
and running them with the ā€œtimeā€ command (assuming you are on a Unix-like system) shows a significant speed-up without getting into some fancy reductions. ā€¦

Summary
PROGRAM pr4
  IMPLICIT NONE

  INTEGER(KIND=4) :: i,j,number_1,number_2,product_of_numbers,length_of_digit,largest_palindrome
  INTEGER(KIND=4),PARAMETER :: lower_limit=100,upper_limit=999,length=11
  CHARACTER(LEN=length) :: palindrome_input_string,palindrome_check_string

  100 FORMAT (i0)
  largest_palindrome = 0

  ! big to little
  DO number_1 = upper_limit,lower_limit,-1
     DO number_2 = upper_limit,lower_limit,-1
        product_of_numbers = number_1 * number_2
        ! if smaller than found not a candidate
        if(product_of_numbers < largest_palindrome) exit

        WRITE(palindrome_input_string,100) product_of_numbers

        ! len_trim can replace loop
        length_of_digit = len_trim(palindrome_input_string)
        !length_of_digit = ceiling(log10(real(product_of_numbers)))

        j=0
        DO i=1,length_of_digit/2
           IF (palindrome_input_string(i:i) .NE. palindrome_input_string((length_of_digit-j):(length_of_digit-j))) EXIT
           IF (i .EQ. length_of_digit/2) THEN
              IF (product_of_numbers .GT. largest_palindrome) largest_palindrome = product_of_numbers
           END IF
           j=j+1
        END DO
     END DO
  END DO

  PRINT *, "The largest palindrome is : ",largest_palindrome
END PROGRAM pr4
1 Like

I was looking for both even and odd number of digits :slight_smile: , and thank you once again for the help.