Trying to understand implied do loops

Hi all, I am doing the Euler project exercise number 8

I don’t need help with the code, but here it is anyways :

PROGRAM pr8
  USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY: int64
  IMPLICIT NONE

  CHARACTER(len=1000) :: the_number
  INTEGER(KIND=int64),ALLOCATABLE :: number_array_tmp(:),number_array_best(:)
  INTEGER(KIND=int64) :: greatest_product,product_tmp,number_array_size,i,j
  INTEGER(KIND=int64) :: array_pos,parser_stop_var

  OPEN (UNIT=10,FILE='pr8_input.txt')
  READ (10,*) the_number
  CLOSE(10)

  PRINT *, the_number
  PRINT *, " "

  WRITE(unit=*, FMT="(a)", ADVANCE="no") &
       "Please enter the amount of numbers in a sequence "
  READ *, number_array_size

  ALLOCATE(number_array_tmp(number_array_size))
  ALLOCATE(number_array_best(number_array_size))

  array_pos = INT(1, KIND=int64)
  parser_stop_var = number_array_size + array_pos
  parser_stop_var = array_pos
  greatest_product = 1

  DO WHILE((array_pos+(number_array_size)) .LE. LEN(the_number, KIND=int64))
     product_tmp = 1

     DO i=1,number_array_size
        READ(the_number(parser_stop_var:parser_stop_var),*)&
             number_array_tmp(i)
        parser_stop_var = parser_stop_var + INT(1, KIND=int64)
     END DO

     product_tmp = PRODUCT(number_array_tmp)
     IF (product_tmp .GT. greatest_product) THEN
        greatest_product = product_tmp
        number_array_best = number_array_tmp
     END IF

     array_pos = array_pos + INT(1, KIND=int64)
     parser_stop_var = array_pos

  END DO


  PRINT *, " "
  PRINT *, "The greatest product is "
  PRINT *, greatest_product

END PROGRAM pr8

Here is the input file :

7316717653133062491922511967442657474235534919493496983520312774506326239578318016984801869478851843858615607891129494954595017379583319528532088055111254069874715852386305071569329096329522744304355766896648950445244523161731856403098711121722383113622298934233803081353362766142828064444866452387493035890729629049156044077239071381051585930796086670172427121883998797908792274921901699720888093776657273330010533678812202354218097512545405947522435258490771167055601360483958644670632441572215539753697817977846174064955149290862569321978468622482839722413756570560574902614079729686524145351004748216637048440319989000889524345065854122758866688116427171479924442928230863465674813919123162824586178664583591245665294765456828489128831426076900422421902267105562632111110937054421750694165896040807198403850962455444362981230987879927244284909188845801561660979191338754992005240636899125607176060588611646710940507754100225698315520005593572972571636269561882670428252483600823257530420752963450

I would like to know if it is possible to turn this do loop into an implied do loop :

DO i=1,number_array_size                                 
   READ(the_number(parser_stop_var:parser_stop_var),*)&  
        number_array_tmp(i)                              
   parser_stop_var = parser_stop_var + INT(1, KIND=int64)
END DO                                                   

Also, feel free to provide any suggestions on improving the code.

You can’t put a read statement (or any other statement, only expressions) in an implied do-loop, but you can define a read function:

integer function read(s) result(i)
  character, intent(in) :: s
  read(s, *) i
end function read

and then do something like:

array = [(read(string(n:n)), n = 1, 10)]

which may be close enough to what you’re asking. The read is now a function and its result an expression, so it can be used in an implied do loop. I don’t recommend this for serious code, only for fun.

2 Likes

Thank you !

People can still improve the code if they’d like :slight_smile:

Hi, glad to see someone else doing Project Euler in this forum! I guess you could do something like this, it’s not implied-do but it saves a do loop for you

program main

use iso_fortran_env, only: int64
implicit none

character(:), allocatable :: str
integer(int64) :: i

str = '123456788901212034801298430192239485792384343'
read(str(1:13), *) i
print *, i
end program main

Besides answering your question, I have some comments regarding Project Euler for new Fortran learners who don’t have a computer science background. I started solving PE problems after reading my first Fortran book and hoping that by practicing, I could master Fortran. And I did solve around 60 problems (PE-Fortran). PE problems are really interesting, but most of the more difficult PE problems are math-oriented, which is hard regardless of your Fortran skills. The easier problems could have been solved very quickly if I had read a textbook on data structure beforehand. But no, I spent a lot of time coming up with nasty and non-standard algorithms until someday, I realized what I did was just reinventing lists, dictionaries, or graphs. I didn’t have handy tools like stdlib back when I started PE problems, and I had to reinvent many, many wheels (it’s terrible for a beginner). I even wrote a multi-precision library for big integers. So, if you (not you specifically but any reader) are like me, I recommend learning data structure and other computer science knowledge before you start solving those problems. Also, after solving one problem, go to the problem thread. That’s where the real fun is!

4 Likes

Would it be possible for you to please recommend me and others some good data structure and computer science knowledge sources ? (It can be free or open source, In fact I’d like both)

The only one I read is Introduction to Algorithms. Also, I believe many experts in this forum are far more qualified than me to answer that question, and I would like to hear their answers too. In fact, let me add one more question to yours. Among all the resources listed in the Learn page, there is a gap between introductory-level books and more advanced domain-specific books (like HPC, Numerical Computation, etc.). In order to fill the gap, learning other languages like C/C++ is often unavoidable. I feel like many Fortran experts assume people already know C/C++ fairly well or how compilers work underneath. I’ve seen tips like Fortran For C Programmers, but not the other way around. So, my question is, to really advance Fortran, what are the recommended C/C++ textbooks /sources for Fortran programmers?

2 Likes

Most of the recent Fortran texts will cover implementing lists and sometimes trees in Fortran. However, if you want to learn more about the theory of data structures, your Fortran options are pretty thin and you will be forced to learn another language (not a bad thing). R. A. Vowels book, " Algorithms and Data Structures in F and Fortran", is the only Fortran book I know targeted specifically at data structures but I don’t know if its still in print. Another Fortran specific source (again I don’t think still in print) is Loren Meissner’s collection of notes on “Fortran 90 & 95 Array and Pointer Techniques” that was sold on the old Fortran Company web site. It covered lists, trees etc. My personal favorite somewhat language agnostic data structures book is the old Aho, Hopcraft and Ullman text, " Data Structures and Algorithms", which uses a Pascal like pseueo-language. which I find easier to translate into Fortran than some actual language (C++ etc) based texts. Your best bet for the Vowel and Meissner texts would be a local library. You can probably get a copy on an inter-library loan

1 Like

Do the techniques of these older books still hold up ? even today ?

I feel like some of the posters of this discourse need to get together and write a book on algorithms and data structures in modern Fortran. :sweat_smile:

2 Likes

I would encourage you to take a look at “Introduction to Programming with Fortran” by Ian Chivers and Jane Sleightholme; it’s a tour de force of modern Fortran, and goes into several examples of algorithms and data structures. (It is not a comprehensive survey of data structures, but there are lots of examples.)

1 Like

I completely agree that there is a major need for a new data structures and algorithms book written from a Modern Fortran perspecitve (something on the order of the Corman book). On the plus side, how you implement a list, tree, dictionary etc. is for the most part the same in all the languages and hasn’t changed (at least in the languages that support pointers) in years (at least to my knowledge}. Therefore the implementations given in Fortran 90 plus texts are perfectly valid. Also, one reason I mentioned the Aho, Hopcraft and Ullman text is that it gives array based as well as pointer based implementations of lists. Something I don’t think you will find in more modern texts.

3 Likes

It is a implicit-implicit-do but you could just write

read(the_number(parser_stop_var:),'(*(i1))') number_array_tmp

which is simpler form of a true-implicit-do:

read(the_number(parser_stop_var:),'(*(i1))') (number_array_tmp(i),i=1,number_array_size)
3 Likes

I have this book and use it extensively as a reference manual, thanks for the suggestion :+1:

1 Like

Thanks for the suggestions, I am gonna try and get a hold of those books :+1:

In this case, how do I get parser_stop_var to increase as well ?

Two remarks:

parser_stop_var = number_array_size + array_pos
parser_stop_var = array_pos

The first assignment seems redundant.

Second remark is that if the input data allows zeros (as it seems fro the sample input data) which, for product computing is a bit weird, then the initial value of greatest_product should be zero rather than one. As it is now, if the longest string of non-zeros is shorter than number_array_size, the true answer should be zero but it will show as one

1 Like

It gets increased here:

  array_pos = array_pos + INT(1, KIND=int64)
  parser_stop_var = array_pos
1 Like

I agree with both your points, the second is an oversight by me. Thanks

Thank you for this, I will try implementing it.

Isn’t this simply 1_int64?

1 Like