When is "n" in explicit-shape array A(n) implicitly typed

When you declare an explicit-shape array with the dimension declared after the array:

integer, intent(in) :: A(n)
integer, intent(in) :: n

Is the n in A(n) implicitly typed?

Here is a full test program:

program expr2
implicit none
integer :: y(2) = [2, 4]
call f(size(y), y)

contains

    subroutine f(n, A)
    integer, intent(in) :: A(n)
    integer, intent(in) :: n
    print *, A
    end subroutine

end program

Every compiler so far that I tried compiles it without any error.

I’ve seen the above usage in codes (not mine :), so I would like to understand how it should be handled by a compiler. If it is implicitly typed, then I would think the above code should not compile, since I used implicit none.

1 Like

My understanding was that it is the compiler’s job to determine which order variables actually need to be declared in, and their order at the top of a module/suborogram/program itself was meaningless.

In your example, n is never implicitly typed, since it is an integer as you requested in the same declaration section at the top.

Nagfor gives:
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7144
Error: t.f90, line 9: Implicit type for N
detected at N@)
Error: t.f90, line 10: Symbol N has already been implicitly typed
detected at N@
[NAG Fortran Compiler pass 1 error termination, 2 errors]

1 Like

Alas @tyranids, sometimes the order of declarations does matter. Always in parameter statements defining constants whose values may depend on previously defined constants ,and sometimes when defining variables. For example, Modern Fortran Explained (2023 edition) p22 says a derived type may have a component that is of a previously defined derived type. Or see the f2023 standard section 7.3.2.2 paragraph 2.

1 Like

BLAS and LAPACK do this with leading dimensions in the argument list, e.g.:

SUBROUTINE DGEMV(TRANS,M,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)

LDA comes after A and A is defined as

DOUBLE PRECISION A(LDA,*)

I’ve always thought this ordering odd, but no compiler has complained so far.

Edit: LDA does appear before A in the declaration section, which is the point of the OP.

Although I haven’t dug in the standard, I have always heard that declaration order matters. If your code example is compiled with gfortran -pedantic, one gets the following warning message:

   10 |     integer, intent(in) :: A(n)
      |                             1
Warning: GNU Extension: Symbol 'n' is used before it is typed at (1)

The fact is also that most compilers do accept out-of-order declarations, but this is non standard I believe.

When using multiple compilers to test that a code is standard-conforming, one should use their standard-conformance options. Gfortran and ifort compile your code by default, but gfortran -std=f2018 certik.f90

gives

certik.f90:9:29:

    9 |     integer, intent(in) :: A(n)
      |                             1
Error: GNU Extension: Symbol 'n' is used before it is typed at (1)
certik.f90:8:21:

    8 |     subroutine f(n, A)
      |                     1
Error: Symbol 'a' at (1) has no IMPLICIT type
certik.f90:4:18:

    4 | call f(size(y), y)
      |                  1
Error: Type mismatch in argument 'a' at (1); passed INTEGER(4) to UNKNOWN

and ifort -stand:f18 certik.f90 gives

certik.f90(9): warning #8586: Implicit type is given to allow out-of-order declaration. Non-standard extension.   [N]
    integer, intent(in) :: A(n)
-----------------------------^
2 Likes

Yes, the first appearance of n here is an implicit declaration. There is then:

A variable in a specification expression shall have its type and type parameters, if any, specified by a previous declaration in the same scoping unit, by the implicit typing rules in effect for the scoping unit, or by host or use association. If a variable in a specification expression is typed by the implicit typing rules, its appearance in any subsequent type declaration statement shall confirm the implied type and type parameters. If a specification inquiry depends on the type of an object of derived type, that type shall be previously defined.(F2023 10.1.11p6)

Notice the use of “previous declaration” (which may be in the same declaration statement), and that if the variable is implicitly typed and then explicitly typed later, that explicit type must match the implicit type. Use of IMPLICIT NONE means use before declaration is an error, but as noted, many compilers let you get away with this as an extension.

On a related note, some compilers let you do:

integer foo
integer foo

At DEC, we had long arguments about this, as some customers wanted us to support it, but we held our ground and said no. The Intel compiler continues to disallow duplicate typing.

1 Like

You’re right. I forgot about the parameter thing, I’ve seen that for sure. Same with derived types needing to be in order, I forgot about that.

As others mentioned, there are compiler options that will start complaining if you have declarations out of order as well.

@sblionel thank you for the clarification. The above example thus should not compile with implicit none, and NAG doesn’t compile it, and GFortran with -std=f2018 or -pedantic also doesn’t compile it.

One more question regarding:

“previous declaration” (which may be in the same declaration statement)

Definitely this is allowed:

    subroutine f(n, A)
    integer, intent(in) :: n, A(n)
    print *, A
    end subroutine

But how about this:

    subroutine f(n, A)
    integer, intent(in) :: A(n), n
    print *, A
    end subroutine

Here n comes later in the same declaration statement. Is that allowed?

The second example is not allowed. I remember an interp for the first case, but am having trouble finding it. There is explicit wording in the standard for similar cases, such as:

A named constant shall not be referenced unless it has been defined previously; it may be defined previously in the same statement.

but I’ve not yet found a similar statement for specification expressions.

1 Like

Here is a small program that surprises some programmers. I think this is legal fortran, it is just a little tricky.

program xxx
   implicit none
   integer :: n=3, a(3)
   call yyy( a )
contains
   subroutine yyy( a )
      integer :: a(n)
      integer, parameter :: n=2
      write(*,*) 'size=', size(a)
      return
   end subroutine yyy
end program xxx

The tricky part is that there are two variables n within the subroutine, one used in the declaration that is host associated, and then the subsequent local parameter which thereafter masks the host variable. If the parameter statement is moved up a line, then a different value is printed.

It is not legal. For example, NAG complains:

NAG Fortran Compiler Release 7.1(Hanzomon) Build 7120
Error: t.f90, line 8: PARAMETER N referenced before definition
       detected at N@=

And Intel:
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.0.2 Build 20231213
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.

t.f90(8): error #7157: This name has been incorrectly used in a specification expression of a contained procedure.   [N]
      integer, parameter :: n=2
----------------------------^

There can never be one local name for two distinct entities.

1 Like

Thank you @sblionel for all the clarifications. I think it’s clear to me now.

Thank you everybody in this thread for the discussion. Looks like I wasn’t the only one confused. But hopefully all is clear now.

This thread finally explained things for me as I’ve encountered these errors before and wondered what the problem was.

In C, you can also pass the length as an argument, but it must precede the array argument.

void foo(int n, int arr[n]) {
  // ...
}

As an extension, the GNU compiler supports forward declaration, which looks like this:

void foo(int n; int arr[n], int n) {
  // ...
}

The first n before the semi-colon is a parameter forward declaration that serves the parsing phase, to make sure the n is known before the arr argument is parsed.

1 Like