End of file error

Dear colleagues,

the following code gives me an end of file error.
This is a FORTRAN 75 file from the book “CFD for wind engineering” I tried to translate to a more modern style.
The error: At line 27 of file freq3.f90 (unit = 15, file = ‘fs-i.txt’)
Fortran runtime error: End of file

Error termination. Backtrace:

Could not print backtrace: libbacktrace could not find executable to open

program freq3
    
    use, intrinsic :: iso_fortran_env
    implicit none
    real(real64) :: ttime, dt, fre, fre1
    real(real64) :: xa, temp, time, an, bn, amb
    real(real64), parameter :: pi=4.0_real64*atan(1.0_real64), pi2=2.0_real64*pi
    integer :: i, n, nfreq, np, iostat
    character(len=13), parameter :: fmt="(4(1x,f10.4))"
    
    open(15, file="fs-i.txt")
    open(20, file="fs-o.plt")

    write(20,*) "freq, an, bn, amb"
    read(15,*) np, ttime, dt, nfreq
    fre = 1.0_real64/ttime

    do n = 1, nfreq
        if (n /= 1) then
            if (iostat /= 0) exit ! Exit loop if read fails
        end if
        fre1 = fre*n
        an = 0.0_real64
        bn = 0.0_real64
        
        do i = 1, np
            read(15,*) time, xa
            temp = n*pi2*time/ttime
            an = an + xa*cos(temp)
            bn = bn + xa*sin(temp)
        end do
        
        an = 2.0_real64*an*dt/ttime
        bn = 2.0_real64*bn*dt/ttime
        amb = sqrt(an*an + bn*bn)
        print *, fre1, an, bn, amb
        write(20,fmt) fre1, an, bn, amb
        rewind 15
    end do
    
    close(15)
    close(20)
end program freq3

Roger

1 Like

Post your fs-i.txt file. The Fortran code is trying to read past its end, so it fails.

fs-i.txt:
4,1.,0.25,2
Original code:


2 Introduction to Fluid Mechanics
freq3. f, calculates spectrum implicit real 8 (a-h, o-z) open (5, file='fs-i.txt')
open (2, file='fs-o.plt') phi-4.*atan (1.)
phi2=2.phi
write (2,*)' freq, an, bn, amb' read (5, *) np, ttime, dt, nfreq
fre=1./ttime
do n=1,nfreq
if (n.ne.1) read (5, *)
frel=fre*n
an=0.0
bn=0.0
doi=1,np
read (5, *) time, xa
temp=n*phi2*time/ttime
an=an+xa*cos (temp)
bn=bn+xa*sin(temp)
end do
an=2.*an*dt/ttime
bn=2.*bn*dt/ttime
amb=sqrt (an*an+bn*bn)
print *, frel, an, bn, amb
write (2,10) frel, an, bn, amb
rewind 5
end do
format (4 (1x, f10.4))
stop
end



Check to make sure that line in the file has the correct line termination character (e.g. a <lf> on posix/unix file systems.

I added line terminate character, but now I get:
Fortran runtime error: Bad real number in item 1 of list input
Item 1 is supposed to be an integer.
When I make it a real I get:
Fortran runtime error: Bad integer number in item 1 of list input

You need more data in the input file fs-i.txt and there is a bug in the new implementation

The original program

  1. reads the first line of data using the line read (5, *) np, ttime, dt, nfreq. I think this succeeds for you
  2. It then executes the loop starting do n=1,nfreq
  3. On all but the first loop it reads and discards the first line of unit 5 (see below)
  4. It then executes the loop do i=1,np and at each iteration it reads a line from unit 5. You don’t appear to have supplied this data and therefore that read fails.
  5. After the inner loop there is a rewind statement to move back to the start of unit 5. (This is why you need to skip the first line for subsequent iterations.

To fix the new code I would try

  1. replace the line if (iostat /= 0) exit with read(15,*) to discard the first line on subsequent iterations)
  2. work out what to put on the np lines of data required for the input file

This is a common idiom from the days before Fortran 90 gave us dynamic memory allocation. There was no need to store the subsequent data (of unknown size). These days most of us would declare a couple of allocatable arrays (or a single array of a user defined type) , allocate them once we have read the problem size np, then read the rest of the data into those arrays and use that within the inner loop.

Thank you!
It was as simple as that, I did not provide enough data.
Now it works.
e.g. fs-i.txt :

4	 1.	 0.25	 2 	
0	0
0.25	1.
0.5	0
0.75	-1 

FYI : a similar program generated by Claude (AI)
I didn’t test it yet.

program spectral_density
    implicit none
    
    ! Parameters
    integer, parameter :: dp = kind(0.d0)
    integer :: N, i, j, k
    real(dp) :: pi, dt, df, freq
    real(dp), allocatable :: t(:), x(:), window(:)
    complex(dp), allocatable :: X(:)
    real(dp), allocatable :: PSD(:), frequencies(:)
    
    ! Constants
    pi = 4.0_dp * atan(1.0_dp)
    
    ! Read input parameters
    print *, "Enter number of data points (N):"
    read *, N
    
    print *, "Enter time step (dt):"
    read *, dt
    
    ! Allocate arrays
    allocate(t(N), x(N), window(N), X(N), PSD(N/2+1), frequencies(N/2+1))
    
    ! Create time array and read input data
    print *, "Enter data points (", N, " values):"
    do i = 1, N
        t(i) = (i-1) * dt
        read *, x(i)
    end do
    
    ! Apply Hanning window to reduce spectral leakage
    do i = 1, N
        window(i) = 0.5_dp * (1.0_dp - cos(2.0_dp * pi * (i-1) / (N-1)))
        x(i) = x(i) * window(i)
    end do
    
    ! Perform DFT
    X = cmplx(0.0_dp, 0.0_dp, dp)
    do k = 1, N
        do j = 1, N
            X(k) = X(k) + x(j) * exp(cmplx(0.0_dp, -2.0_dp * pi * (j-1) * (k-1) / N, dp))
        end do
    end do
    
    ! Calculate frequency resolution
    df = 1.0_dp / (N * dt)
    
    ! Calculate Power Spectral Density (one-sided)
    do i = 1, N/2+1
        ! Convert to density by normalizing
        PSD(i) = (abs(X(i))**2) / (N**2)
        ! Scale by 2 for one-sided spectrum (except DC and Nyquist)
        if (i /= 1 .and. i /= N/2+1) then
            PSD(i) = 2.0_dp * PSD(i)
        end if
        ! Correct for windowing
        PSD(i) = PSD(i) / sum(window**2) * N
        
        ! Calculate frequency
        frequencies(i) = (i-1) * df
    end do
    
    ! Output results
    print *, "Frequency (Hz)   |   Spectral Density"
    print *, "--------------------------------------"
    do i = 1, N/2+1
        print *, frequencies(i), PSD(i)
    end do
    
    ! Write to file
    open(unit=10, file="spectral_density.dat", status="replace")
    write(10,*) "# Frequency (Hz)   Spectral Density"
    do i = 1, N/2+1
        write(10,*) frequencies(i), PSD(i)
    end do
    close(10)
    
    print *, "Results saved to 'spectral_density.dat'"
    
    ! Clean up
    deallocate(t, x, window, X, PSD, frequencies)
    
end program spectral_density
1 Like

A second set of eyeballs will do that. Glad to help out.