Difference between assumed-size and assumed-shape arrays?

Can someone help me understand the difference between assumed-shape and assumed-size arrays?

subroutine example(A,B)
    real :: A(:) ! Assumed-shape
    real :: B(*) ! Assumed-size
end subroutine

I know that with an assumed-shape array the compiler tells the subroutine what the shape of the array is, so you can do whole-array operations and you can run size(A), shape(A), sum(A), etc; and those don’t work with B.

So… why do assumed-size arrays exist? What do they do?

I read that with an assumed-shape array, the “interface of the subroutine must be explicit in the caller”. I’m not sure what that means. I tried to write an example, but I got it wrong. This is what I tried, but it doesn’t compile:

module Alpha
  implicit none
contains
  subroutine foo(A,val)
    real :: val, A(:) ! Assumed-shape
    val = 10 + sum(A)
  end subroutine
end module
...
program main
  use Alpha, only: foo
  implicit none
  interface
    subroutine foo(X,val)
      real :: X(:),val
    end subroutine
  end interface
contains
  subroutine bar()
    real :: val, X(10)
    call foo(X, val)
  end subroutine
end program

Standards before Fortran 90 had only assumed-size arrays, not assumed shape, so one reason assumed-size arrays are still in Fortran is backward compatibility.

Your code does not compile because you can either put a procedure in a module that is USEd, or provide an INTERFACE block, but you should not do both. Thus, both the program

module Alpha
  implicit none
contains
  subroutine foo(A,val)
    real :: val, A(:) ! Assumed-shape
    val = 10 + sum(A)
  end subroutine
end module
!
program main
  use Alpha, only: foo
  implicit none
  real :: x(10), val
  x = -4.0
  call bar()
  print*,val
contains
  subroutine bar()
    call foo(X, val)
  end subroutine
end program

without an interface block and the program below with an interface block for subroutine foo that is outside of a module

subroutine foo(A,val)
   real :: val, A(:) ! Assumed-shape
   val = 10 + sum(A)
end subroutine
!
program main
  implicit none
  interface
    subroutine foo(X,val)
      real :: X(:),val
    end subroutine
  end interface
  real :: x(10), val
  x = -4.0
  call bar()
  print*,val
contains
  subroutine bar()
    call foo(X, val)
  end subroutine
end program

compile and run, giving output -30.0000000.

1 Like

Thanks!

Wait… you’re allowed to just write a subroutine just dangling outside program or module? I didn’t realize that that was an option. I had assumed that before modules were introduced Fortran programs were entirely contained inside a program.

Unfortunately, it is allowed. Stick to what you believe though - don’t write free functions and subroutines. Being outside of a module prevents the compiler from checking interfaces at compile time, and makes cross-file LTO more finicky to get working - at least in my experience.

1 Like

Before Fortran 90 neither modules nor the contains statement were existing, so basically all routines were “dangling around”. This is of course still allowed, otherwise it would break tons of legacy codes. But this is now highly recommended to use modules.

1 Like
  • Assumed size = array is purely passed by reference, you decide what size it should be. Whatever the array is like outside of the subroutine does not matter (rank, size, bounds…).
    Nice because you can “reshape” arrays if you like only inside a particular subroutine, but also very dangerous (no bounds checking is possible)

  • Assumed shape = array size information (only rank, size) is passed along with the data, but not bounds information (all dimensions are assumed to start at 1, unless you specify a different bound manually like real :: A(0:)).
    Much safer, but careful! you cannot pass unallocated allocatable arrays into this interface.

  • Allocatable = array size information (rank, size AND bounds) and presence (allocated(array)) is passed along with the data. Safest, but may be slower as far as I’m told. Also: cannot differentiate between allocatable and assumed-shape arguments in generic interfaces.

2 Likes

I like to call them “stray subroutines” - and yes, it is an option. But, as you can see from the answers above, nobody recommends their use in “serious work”. In addition, I don’t like stray functions (not subroutines) at all.

The difference between stray subroutines and subroutines contained into a program (with contains) is that stray subroutines are completely independent, while contained ones inherit and are aware of everything declared in the unit that contains them (including uses.) This may or may not be desirable. Sometimes it is convenient to have a main program with a few contained procedures - but again, not for serious work.
Note that the above is about procedures contained in the main program. Modules with lots of procedures contained is typical in serious work - but even there, make sure the module is private, and whatever is meant to be available outside the module should be explicitly declared as public.

Now, this is just personal programming style and others may disagree, but in simple examples, I think there is nothing wrong with using a few stray and/or contained subroutines, as appropriate. For example, a stray subroutine is perfectly ok when I want to emphasize this is independent code, and at the same time I want to keep the example short. I just save the few lines of code needed to make it a module.
Let’s say you want to introduce a new library and how to use it. The goal is not to teach newcomers good programming style. You can assume they already know about that (if they don’t then they don’t need your library yet.) In such cases, you just want to keep the example short, and one stray subroutine or two won’t hurt. If you feel you need more, it’s time to consider a module instead, even in simple examples.

One thing you may want to remember (and that’s about the original question as well) is that Fortran has a long history - in fact, it is as long as it gets with high-level programming languages. Countless of quality software is written in legacy FORTRAN so, unlike other languages, backwards compatibility is very much a valued thing. This means the language gives you some tools that may be obsolete, but still available (even though really ancient features are already forbidden by default.) This may be frustrating for people learning the language. That’s why some compilers have a flag to prevent the use of legacy features.

1 Like

A problem with stray procedures is that a program that calls them with the wrong argument types can still compile and run, giving wrong results. For example, the program

double precision function twice(x)
implicit none
double precision :: x
twice = 2*x
end function twice

program main
implicit none
double precision :: twice
print*,twice(3.14159265359) ! should be 3.14159265359d0
end program main

where the function and main program are in separate files compiles and runs but gives nonsense with gfortran. When they are in the same file or if the function is put in a module gfortran says

   10 | print*,twice(3.14159265359) ! should be 3.14159265359d0
      |       1
Error: Type mismatch in argument 'x' at (1); passed REAL(4) to REAL(8)

So Fortran has had separate compilation of procedures for decades, but with modules you get separate compilation and interprocedural type checking.

2 Likes

I tend to agree. But when asking for help to debug some code for instance, putting everything in modules whenever possible, specifying IMPLICIT NONE, and enabling compiler runtime checks, are all good things to do.

1 Like