Silverfrost Forums

Welcome to our forums

Program aborts with spurious error report

6 Jan 2018 8:36 #21074

When the program below is compiled with FTN95 8.10 using the /check option, the resulting EXE aborts with the message 'Attempt to call a routine with argument number four containing too few array elements at address xxx'. The array in question, FVEC, has exactly the correct size, 5.

This happens with or without /64. When the EXE is run from the command line, the line number where the abort occurred is not shown, only an offset is displayed. When the program is run inside SDBG or SDBG64, the line number is shown. At the point where the program stops in SDBG64, the variables display gives some puzzling and inconsistent information:

(Alternate address of FVEC) = REAL*4 Array size not known
(Alternate address of M) = 5
(Alternate address of N) = 3
(Alternate address of P) = REAL*4 Array size not known
FVEC = REAL*4 (5)
M = 5
N = 3
P = REAL*4 (3)

Here is the test program source:

MODULE fit_data
   IMPLICIT NONE
   INTEGER, PARAMETER :: NDAT = 5, NCOEF = 3
   REAL, SAVE  :: x(NDAT) = (/ 28.93, 29.57, 31.30, 33.43, 33.84 /), &
                  y(NDAT) = (/ 0.943, 0.892, 1.089, 1.504, 1.418 /)
END MODULE fit_data

PROGRAM DOFIT

USE fit_data
IMPLICIT NONE

REAL     :: fvec(NDAT)
INTEGER  :: n = NCOEF                 ! number of parameters in model
INTEGER  :: m = NDAT                  ! number of observations
REAL     :: p(NCOEF) = (/ 1e1,-1e-1,5e-2 /)   ! trial values of parameters

CALL lmdif(m, n, p, fvec)

STOP

CONTAINS

SUBROUTINE ffcn(p, fvec)

USE fit_data
IMPLICIT NONE
REAL, INTENT(IN)      :: p(:)
REAL, INTENT(OUT)     :: fvec(:)

fvec = -y + (p(2)*x+p(1))/ (p(3)*x+1d0)

RETURN
END SUBROUTINE ffcn

SUBROUTINE lmdif(m, n, p, fvec)
implicit none

INTEGER, INTENT(IN)   :: m
INTEGER, INTENT(IN)   :: n
REAL, INTENT(IN OUT)  :: p(:)
REAL, INTENT(OUT)     :: fvec(:)

 CALL ffcn(p, fvec)
 CALL fdjac2(m, n, p, fvec)

 RETURN
END SUBROUTINE lmdif

SUBROUTINE fdjac2(m, n, p, fvec)
implicit none

INTEGER, INTENT(IN)   :: m
INTEGER, INTENT(IN)   :: n
REAL, INTENT(IN OUT)  :: p(n)
REAL, INTENT(IN)      :: fvec(m)

INTEGER   :: j
REAL :: eps, h, temp, wa(m), fjac(m)
REAL, PARAMETER :: zero = 0.0

eps = 3e-4
DO  j = 1, n
  temp = p(j)
  h = eps*ABS(temp)
  IF (h == zero) h = eps
  p(j) = temp + h
  CALL ffcn(p, wa)
  p(j) = temp
  fjac = (wa(1:m) - fvec(1:m))/h
END DO

RETURN

END SUBROUTINE fdjac2

END PROGRAM DOFIT
8 Jan 2018 7:43 #21079

Thank you for this bug report. I have made a note that it needs to be fixed.

13 Feb 2018 1:49 #21417

More searching in these forums turned up the following reports of what may be the same issue:

'What sometimes 64bit mode with /check /full_debug generates', http://forums.silverfrost.com/viewtopic.php?p=24012

'FTN95 8.10 false error report: Array arg w too few elements', http://forums.silverfrost.com/viewtopic.php?p=24009

13 Feb 2018 5:13 #21421

This issue has now been fixed for the next release.

13 Feb 2018 11:14 #21426

I find the use of CONTAINS in the following code to be confusing and could be error prone.

CONTAINS 

SUBROUTINE ffcn(p, fvec) 

USE fit_data 
IMPLICIT NONE 
REAL, INTENT(IN)      :: p(:) 
REAL, INTENT(OUT)     :: fvec(:) 

fvec = -y + (p(2)*x+p(1))/ (p(3)*x+1d0) 

RETURN 
END SUBROUTINE ffcn 

Subroutine ffcn uses arrays fvec, p, x & y All these arrays are in scope, but p & fvec are supplied as arguments. ( is USE fit_data required here or am I misunderstanding the scope implied by CONTAINS ? )

Shouldn't there be a warning that the subroutine arguments conflict with in scope arrays ? ( which are the same arrays ! ) I am assuming the subroutine arguments take precedence over the arrays provided by CONTAINS or USE.

I don't like the use of CONTAINS at all. If you want variables to be in scope, wouldn't a MODULE be a better approach ? This example has x and y available via both CONTAINS and USE.

What do others think of this ?

John

14 Feb 2018 12:13 #21427

John, this code was intended only to exhibit the compiler bug. As with many other codes that are derived from a real application by cutting out as many lines as possible, what is left is quite silly and does no useful calculations.

I do not think that it is worthwhile to edit the code to make it respectable. I plead that codes of this nature (minimum working examples) not be held up as examples of well-written code.

15 Feb 2018 1:49 #21437

mecej4,

More a complaint about how CONTAINS can disguise the scope of local and used variables from the containing routine.

Perhaps there could be a warning that an in-scope variable name conflicts with a routine argument or module, which does happen in other cases, such as MODULE vs local declaration. Compiling SUBROUTINE ffcn should provide warnings of conflict.

15 Feb 2018 2:57 #21441

Is a CONTAINS routine put in-line like a statement function, or is it the same as any other subprogram apart from scoping?

15 Feb 2018 4:30 #21442

Quoted from JohnCampbell ...CONTAINS can disguise the scope of local and used variables from the containing routine.

That is a problem. More generally, the same exists in any subprogram that has overlapping scope and/or storage/host association of variable names. For me, this happens when I am studying someone else's program that is not working quite right, and create temporary variables for use in PRINT statements to let me view the values of some suspicious expressions. In these situations, I also wish that we could have local implied do index variables as in C:

for(*int *i=0; i<N; i++)printf(\'...\',A[i]);

Perhaps there could be a warning that an in-scope variable name conflicts with a routine argument or module, which does happen in other cases, such as MODULE vs local declaration. Compiling SUBROUTINE ffcn should provide warnings of conflict.[/quote] I'd definitely like that and use it often.

15 Feb 2018 5:16 #21443

The scoping rules are plain for the case you request, and have, as far as I know, always been so. The scope of a loop index variable in (say) a DATA statement is local to the statement (as it can be dealt with by the compiler) but the scope of a loop index variable in an input or output list is the whole subprogram in which it appears. Hence,

      PROGRAM SCOPE
      DIMENSION A(3)
      A(1) = 1.0; A(2) = 2.0; A(3) = 3.0
      DO 10 I=1,3
      WRITE(*,*) (A(I),I=1,3)
   10 CONTINUE
      END

MUST fail. (In FTN95 at compile time. If not, because you are using something inferior, then at run time, possibly mysteriously).

If the implied DO loop variable was scoped only to the statement you used it in, then it wouldn't be Fortran.

Surely there are enough implicitly INTEGER variables you could use that probably won't conflict: 'Mecej4' being one unlikely that anyone else would use. In old code, it is probably sufficient that it is more than 6 characters long.

For instance:

      WRITE(*,*) (A(Meghan_Markle),Meghan_Markle=1,3)

Another approach is to use a routine like:

      SUBROUTINE DEBUG_VARS ( A, I,  J)
      DIMENSION A(*)
      WRITE(*,*) (A(K), K = I, J)
      END

and insert CALL DEBUG_VARS (A, I, J) instead of putting the write statement in. It might even be shorter.

Eddie

16 Feb 2018 2:20 #21444

Quoted from LitusSaxonicum The scope of a loop index variable in (say) a DATA statement is local to the statement (as it can be dealt with by the compiler) but the scope of a loop index variable in an input or output list is the whole subprogram in which it appears.

Eddie, you are probably not the one to ask about this, but it always puzzles me how I can use a loop index that is local to a data statement, when I use 'IMPLICIT NONE' or /implicit_none. With /imp, I have to declare the loop index as integer, so then it's scope becomes the whole routine. Just means that the loop index in the data statement must be a unique name, if the variable I is used elsewhere in the routine or worse still, in a module or common.

16 Feb 2018 2:54 #21447

John, I have read through the scope rules, but gave up after sensing that I would not be able to remember all the details while writing code. For most people, it may be best not to use the same names for implied DO variables as variables used elsewhere.

In the program

program vtest
implicit none
integer :: x(4) = [(i*4, i=2,5)], j,i
print *,(x(j),j=1,4)
print *,i,j
end program

the variable i is undefined except within the initialization. The variable j, on the other hand, is undefined before line 4, but has the value 5 after that line (according to FTN95 8.10).

16 Feb 2018 5:49 #21448

John,

No I'm not the best person As , but what you describe is a side effect of IMPLICIT NONE. The scoping rules used to be simple:

Global - subroutine and function names, intrinsics, named common names Local - everything in a subroutine Even more local - implied DO loop in an initialisation (which you lose with IMPLICIT NONE).

Now, as above, but anything in a CONTAINing supprogram also applies in CONTAINed routines. Modules may further obscure this.

As long as you remember that a DO loop index is undefined on exit from the loop by virtue of finishing (it is defined on a jump out) then you can use it as often as you like. As the number of variables you can use is essentially infinite, I prefer to use separate loop variables if the subroutine code is lengthy, but i,j,k if it is short. The former case always has the loop index name starting with i, and the final count with N, as in

DO 120 iNODES = 1, nNODES

or

DO 80 iELES = 1, nELES

but i and j in shorter subprograms. For me, it is the need to read it decades later.

(and usually all in capitals!)

Eddie

16 Feb 2018 6:07 #21449

Quoted from LitusSaxonicum ...As long as you remember that a DO loop index is undefined on exit from the loop by virtue of finishing (it is defined on a jump out) ...

Eddie, that was true in the old days, but not in Fortran 9X and later. For example, F2003 says in 8.1.6.4.4 'Loop termination':

When a DO construct becomes inactive, the DO variable, if any, of the DO construct retains its last defined value.

Another feature that one could have in old Fortran: the DO index variable could be REAL. This is no longer permitted.

17 Feb 2018 8:51 #21451

In FTN95, I found that on exit from DO 10 I=1,3 that I was 4, which is not undefined, but is defined in a way that is relatively useless. Integers can't be undefined in the way that REALs can. As for loop variables being REAL, that was a stupid and unnecessary insertion, and deserved to be removed.

20 Feb 2018 4:24 #21472

As mecej4 notes the value of the do loop variable after the loop is carefully defined. I often find the most natural way to code something makes use of this value.

The following code attempts to find the first instance when the test is true. Here n may be 0, in which case the code prints 'Not found'. And if the test is always false the code also prints 'Not found'.

! Simple search
do i=1, n
   if (test) exit
end do
! Use the result
if (i > n) then
   print *, 'Not found'
else
   print *, 'Found at pass ', i
end if

Without this facility in the language you have to write code like this using another variable:

! Simple search (without using index variable after loop).
j = n + 1
do i=1, n
   if (test) then
      j = i
      exit
   end if
end do
! Use the result
if (j > n) then
   print *, 'Not found'
else
   print *, 'Found at pass', j
end if
20 Feb 2018 5:36 #21474

Another common situation where one needs the last used value of the index variable of a DO loop: nested loops where the inner loop may terminate either by satisfying the loop criterion or by a conditional EXIT statement, and the work to be done in the outer loop is along the lines of:

IF (INNER LOOP RAN FULL COUNT) THEN
      BLOCK A1
   ELSE        ! shortened run of inner loop
     BLOCK A2
  ENDIF

We could maintain a separate logical variable to keep track of the matter, but often the terminal value of the inner loop index is sufficient.

20 Feb 2018 7:07 #21475

davidb,

It just shows that one is never too old to learn something. In Fortran 66 the DO loop index was definitely undefined after normal completion exit, and I definitely remember various machines producing a zero, as well as the final count. It seems that the Fortran 77 standard imposed the requirement that it should be the final count + 1, which is a good thing to know, but something I never used, because assuming its value is meaningless is rather safe.

Sadly my copy of McCracken was never returned from a loan, so I can't check the original advice. Presumably one needs to know if one uses EXIT and CYCLE, or the exiting GOTO from my old-fashioned approach is the next statement after the DO loop. I'd better find out how the test works for other forms of loop in order to complete my education.

I'd always avoided decrementing, but I found a decrementing loop on the web that works:

      program decrement
      do i = 10, 1, -2
         write(*,*) 'inner i =', i
      end do
         write(*,*) 'exit i =', i
      end

'exit i' is zero, but the final i through the loop was 2 (having been 10,8,6,4, and 2 in the loop). On balance, I think I'll carry on pretending I don't know what the final value is - it's my safe space.

Eddie

20 Feb 2018 7:27 #21477

I recollect somewhat vaguely that the reason that the DO index became undefined was because some of the mainframes, such as CDC 6xxx, on which early Fortran ran. had 18-bit index registers and 60-bit registers for integers and reals, and it was quite a bit of work to do general arithmetic on index register contents. See http://www.60bits.net/msu/mycomp/cdc6000/65frame.htm .

Some of the early Fortrans limited you to use expressions of the form c*K+d for subscripts, where c and d were constants known at compile time and K was a DO index variable.

20 Feb 2018 9:43 #21479

The rules for calculating i on normal exit.

Given

do i=m1,m2,m3

m1 is the initial value of i. m2 is a final value of i (not necessarily achieved). m3 is the optional increment value (cannot be zero, default is 1).

An iteration count (=number of loop passes) is calculated using

count = max(int((m2 - m1 + m3)/m3), 0)

Note that count is 0 if: m3 > 0 and m1 > m2 or m3 < 0 and m1 < m2

The do loop is equivalent to:

i = m1
count = max(int((m2 - m1 + m3)/m3), 0)
c = count
10 if (c .eq. 0) goto 20
   <body of loop>
   c = c - 1
   i = i + m3
   goto 10
20 continue

On exit i has the value m1 + count*m3 when statement label 20 is reached.

Compilers don't need to generate exactly this code but it must be equivalent. Long ago I used the Hewlett-Packard F77 compiler, which could vectorise the loop, but then made sure the final value was correctly set up using:

call vectorize routine
i = m1 + m3*max(int((m2 - m1 + m3)/m3), 0)

example 1

do i=1, n
end do

count = max(int((n - 1 + 1)/1), 0) = n On exit i = n + 1

example 2

do i=1, 0
end do

count = max(int((0 - 1 + 1)/1), 0) = 0 on exit i = 1

example 3

do i=1, 6, 2
end do

count = max(int((6 - 1 + 2)/2), 0) = 3 on exit i = 7

example 4

do i=1, 5, 3
end do

count = max(int(5 - 1 + 3)/3), 0) = 2 on exit i = 7

Please login to reply.