开发者

Why do I get a Fortran runtime error for recursive IO operation?

I can compile, but when I run, then I get this error:

"forrtl: severe (40): recursive I/O operation, unit -1, file unknown"

if I set n = 29 or more...

PROGRAM  SOLUTION
IMPLICIT NONE

! Variable Declaration

INTEGER  :: i
REAL  :: dt
DOUBLE PRECISION  :: st(0:9)
DOUBLE PRECISION  :: stmean(0:9)
DOUBLE PRECISION  :: first_argument
DOUBLE PRECISION  :: second_argument
DOUBLE PRECISION  :: lci, uci, mean
REAL  :: exp1, n
REAL  :: r, segma

! Get inputs

WRITE(*,*) 'Please enter number of trials: '
READ(*,*) n

WRITE(*,*)
dt=1.0
segma=0.2
r=0.1

! For n Trials

st(0)=35.0
stmean(0)=35.0
mean = stmean(0)

PRINT *, 'For ', n ,' Trials'
PRINT *,'          1     ',st(0)

! Calculate results

DO i=0, n-2
    first_argument = r-(1/2*(segma*segma))*dt开发者_开发百科
    exp1 = -(1/2)*(i*i)
    second_argument = segma*sqrt(dt)*((1/sqrt(2*3.1416))*exp(exp1))
    st(i+1) = st(i) * exp(first_argument+second_argument)

    IF(st(i+1)<=20) THEN
       stmean(i+1) = 0.0
       st(i+1) = st(i)
       else
       stmean(i+1) = st(i+1)
    ENDIF

    PRINT *,i+2,'     ',stmean(i+1)
    mean = mean+stmean(i+1)
END DO

! Output results

uci = mean+(1.96*(segma/sqrt(n)))
lci = mean-(1.96*(segma/sqrt(n)))
PRINT *,'95% Confidence Interval for ', n, ' trials is between ', lci, ' and ', uci
PRINT *,''

END PROGRAM SOLUTION

Can anyone help with where I might have gone wrong?


I admit, I haven't taken the time to try to understand what the program does, but on the basis of a "quick" compile, a few errors are visible:

  • first, I haven't been able to reproduce your error - quite expected, for I don't see where are you assigning any units to files. Would you mind double checking whether that is indeed the error you're getting and stating on what compiler?
  • the arrays if n is greater than 10 are out of bounds
  • what is that second WRITE just abov dt trying to write out?
  • why do you need double precision ?
  • also, if you using n as an index in a loop, it would be wise to declare it integer instead of real
  • you're using n as an index, but also in a square root ... convert it to a real value before using it in a square root with FLOAT(n) function

Apart from that (and maybe a few other things which slipped my mind), I see nothing wrong with it. For n<=10 it gives out results. Although I repeat, I haven't taken the time to analyze them, so they may be incorrect, but it does give them out.


  program solution; implicit none

  !variable declaration
  integer :: i, n
  real :: dt, first_argument, second_argument, lci, uci, mean, exp1, r, segma
  real, dimension(0:99) :: st, stmean

  WRITE(*,'("Please enter number of trials: ",\)'); read(*,*)n
  dt=1.0; segma=0.2; r=0.1

  st(0)=35.0; stmean(0)=35.0; mean=stmean(0)

  write(*,'("For ",i2.2," trials")')n
  write(*,'("           1   ",f14.5)')st(0)

  DO i=0, n-2
      first_argument = r-(1/2*(segma*segma))*dt
      exp1 = -(1/2)*(i*i)
      second_argument = segma*sqrt(dt)*((1/sqrt(2*3.1416))*exp(exp1))
      st(i+1) = st(i) * exp(first_argument+second_argument)

      IF(st(i+1)<=20) THEN
         stmean(i+1) = 0.0
         st(i+1) = st(i)
         else
         stmean(i+1) = st(i+1)
      ENDIF

      PRINT *,i+2,'     ',stmean(i+1)
      mean = mean+stmean(i+1)
  END DO

  uci = mean+(1.96*(segma/sqrt(float(n))))
  lci = mean-(1.96*(segma/sqrt(float(n))))
  PRINT *,'95% Confidence Interval for ', n, ' trials is between ', lci, ' and ', uci
  END PROGRAM SOLUTION


As @Idigas identified, a problem was arrays were being indexed past their bounds. When developing Fortran programs, it is useful to 1) always turn on all compiler debugging options, and especially bounds checking, and 2) put your subroutines and functions into modules and "use" them -- this will allow the compiler to check the consistency of actual and dummy arguments. These two steps will catch a very large fraction of mistakes.

The elegant way to handle the array-size problem in modern Fortran is to declare the arrays as allocatable and then set their size at run-time, after receiving the user input, rather than guessing the maximum size when you write the program. If you have some reason to set the size at compile time, and user input might cause it to be exceeded, it is wise to test that input.

A sketch of parts of an allocatable solution:

real, dimension (:), allocatable :: st, stmean

read (*, *) n

allocate (st (0:n))
allocate (stmean (0:n))
0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜