Saving iterations

The following program saves all iterations. I wish to save every 10th iteration; the total iteration is 100. How I can modify it? The only way I know is somehow using a mod like if(mod(iteration,10)==0) then…

But I still do not understand how and where to use it!

or there is any routine in the stdlib to save step iterations?

iteration.f90 (2.2 KB)

1 Like

You do not want to open and leave open many files, if you
use NEWUNIT= on your open and close the file after you are
done with it you only need one filename open at a time; and
if you build the filename at time of use you do not need to
create an array of names. MOD(3f) is indeed one of several
ways you can selectively choose when to dump the files.

Are you learning Fortran on your own? If this is a homework
assignment please mark it as such, as it is not appropriate
to provide a solution as code if it is, but you are over-complicating
the problem. This would be all that is needed:

program iteration
implicit none
integer, parameter   :: timestep = 100, frequency=10
character(len = 80 ) :: filename 
integer              :: i, lun
real(kind = 8 )      :: r(10)

  do i = 1, timestep
     call random_number(r)
     if(mod(i,frequency).eq.0)then
        write(filename,'("random",i0.3,".txt")')i
        open ( newunit = lun, file = filename, status = 'replace' )
        write(lun,'(e12.4)') r
        close(unit=lun)
     endif
  end do

end program iteration
1 Like

Of course, I am learning it by myself through books or through different websites. It is not homework. I am learning Fortran purely for my personal interest in this language.
one source out of several

OK. The reference examples are showing various cases, such as how to intentionally open and leave open multiple files and so on. It was also written prior to NEWUNIT= being commonly available, so you had to do a little work to make sure you were opening a file with an unused LUN (Logical Unit Number, or more simply the value you specified for UNIT=). For the problem as you described it the file only needs to be open for writing a single checkpoint, so you would not need or want to create an array, especially of a fixed size; but just create the name at time of use. This is assuming you know you want to overwrite any such pre-existing file of that name, as was implied by the use of STATUS=‘REPLACE’ in your example. So those are not incorrect examples, but for the problem you describe a much simpler construct is all that is needed.

1 Like

The e edit descriptor gives the correct output with the 1D. However, for the 2D tabular or matrix data output, it keeps writing the data in a single column.

Is it a bug or this edit descriptor is not sutiable for 2D output? With the default descriptor, it is working fine.

Here is the code I work with:

program TwoD_lun_test
    implicit none
    integer, parameter   :: Nx=5,Ny=5
    integer, parameter   :: timestep = 100, frequency=50
    character(len = 80 ) :: filename 
    integer              :: t, lun,i,j
    real(kind = 8), dimension(Nx,Ny)  :: r
    
    call random_number(r)
    do t = 1, timestep
        
        if(mod(t,frequency).eq.0)then
            write(filename,'("random_",i0.3,".txt")')t
            open ( newunit = lun, file = filename, status = 'replace' )
            do i=1,Nx   
                write(lun,*) (r(i,j), j=1,Ny)              ! Correct Matrix output
!               write(lun,'(e12.4)') (r(i,j), j=1,Ny)      ! Single column output
            end do
            close(unit=lun)
        end if
    end do
end program

That is comes out OK using the list-directed I/O (ie. using the asterisk("*") is essentially luck, as
the asterisk pretty much means the compiler can write as many values on a line as it sees fit. If Ny were larger you would see it it pretty much just writing the values out in a stream-like format occasionally starting a new line.

                write(lun,*) (r(i,j), j=1,Ny)       

The format you have just says how to write one number. It does that, and then starts a new line
and uses the format over — resulting in a single column of numbers. If you changed this line

             write(lun,'(e12.4)') (r(i,j), j=1,Ny)      ! Single column output

to this

            write(lun,'(*(e12.4,1x))')r(i,j),j=1,Ny)

that would mean “repeatedly write on a single line a number and one space until all the values specified by this statement are written”.

You can change the order to produce row-by-column output or column-by-row column. Fortran formats are basically a little language all by themselves and are particularly good at compactly describing how to print tables of values. A good Fortran manual should describe at least the basics. The vendor on-line manuals (Intel, NAG, CRAY, IBM, …) have descriptions. Last I looked (have not looked recently) the IBM manuals had the most complete description of Fortran formats.

PS: If you use fpm(1) just add GitHub - urbanjost/M_display: An fpm(1) package for displaying small matrices based on dispmodule(3f) to your dependencies and you can use the DISP procedure to print little arrays in a number of nice little formats.

2 Likes