Pointers / Free Literature on Fortran

There are a couple of use cases in which I like using ASSOCIATE:

  1. Pure aesthetics and easier-to-read code:

Lets say that one has an intricated derived type (more than 3 levels of indirection), it is then quite nice to have an ASSOCIATE wrapping the actual implementation of the method to facilitate the mental picture of what is happening

imaging handling a mesh with coordinates and connectivities in such a way:

associate( X=>mytype%list_objects(index)%coordinates , &
        & connectivity=>mytype%list_objects(index)%connectivity )
! here work with X(:,:) and connectivity(:,:)
end associate
  1. Data buffers recycling

Lets say that one would like to allocate just once a buffer to then work with small batches of data to avoid reallocations ā€¦
you could do something like

real, allocatable :: data(:)
...
allocate( data(big_size) )
...
associate( variable1 => data(1) , variable2 => data(2:5) )
! do something with variable1  & variable2 
end associate
.. ! later on in the same scope
associate( variable3 => data(1:10) , variable4 => data(11) )
! do something with variable3  & variable4
end associate

No data copied, no risks with pointers being nullified with the data hanging somewhere, and no need of declaration at the header.

3 Likes

hkvzjal, thank you very much for your information re ā€œassociateā€. I shall study what you wrote with great interest. Patrick.

The language is mostly backward compatible. If you donā€™t like modern features, you donā€™t need to use them. Take for example this minimization procedure by Richard Brent extracted from Algorithms for Minimization Without Derivatives, published in 1973:

localmin
C     A FORTRAN TRANSLATION OF THE ALGOL PROCEDURE LOCALMIN.
C     SEE PROCEDURE LOCALMIN, SECTION 5.8, FOR COMMENTS ETC.
      REAL FUNCTION LOCALM(A, B, EPS, T, F, X)
      REAL A,B,EPS,T,F,X,SA,SB,D,E,M,P,Q,R,TOL,T2,U,V,W,FU,FV,FW,FX
      SA = A
      SB = B
      X = SA + 0.381966*(SB - SA)
      W = X
      V = W
      E = 0.0
      FX = F(X)
      FW = FX
      FV = FW
   10 M = 0.5*(SA + SB)
      TOL = EPS*ABS(X) + T
      T2 = 2.0*TOL
      IF (ABS(X-M).LE.T2-0.5*(SB-SA)) GO TO 190
      R = 0.0
      Q = R
      P = Q
      IF (ABS(E).LE.TOL) GO TO 40
      R = (X - W)*(FX - FV)
      Q = (X - V)*(FX - FW)
      P = (X - V)*Q - (X - W)*R
      Q = 2.0*(Q - R)
      IF (Q.LE.0.0) GO TO 20
      P = -P
      GO TO 30
   20 Q = -Q
   30 R = E
      E = D
   40 IF (ABS(P).GE.ABS(0.5*Q*R)) GO TO 60
      IF ((P.LE.Q*(SA-X)).OR.(P.GE.Q*(SB-X))) GO TO 60
      D = P/Q
      U = X + D
      IF ((U-SA.GE.T2).AND.(SB-U.GE.T2)) GO TO 90
      IF (X.GE.M) GO TO 50
      D = TOL
      GO TO 90
   50 D = -TOL
      GO TO 90
   60 IF (X.GE.M) GO TO 70
      E = SB - X
      GO TO 80
   70 E = SA - X
   80 D = 0.381966*E
   90 IF(ABS(D).LT.TOL) GO TO 100
      U = X + D 
      GO TO 120
  100 IF (D.LE.0.0) GO TO 110
      U = X + TOL
      GO TO 120
  110 U = X - TOL
  120 FU = F(U)
      IF (FU.GT.FX) GO TO 150
      IF (U.GE.X) GO TO 130
      SB = X
      GO TO 140
  130 SA = X
  140 V = W
      FV = FW
      W = X
      FW = FX
      X = U
      FX = FU
      GO TO 10
  150 IF (U.GE.X) GO TO 160
      SA = U
      GO TO 170
  160 SB = U
  170 IF ((FU.GT.FW).AND.(W.NE.X)) GO TO 180
      V = W
      FV = FW
      W = U
      FW = FU
      GO TO 10
  180 IF ((FU.GT.FV).AND.(V.NE.X).AND.(V.NE.W)) GO TO 10
      V = U
      FV = FU
      GO TO 10 
  190 LOCALM = FX
      RETURN
      END

(Variations of the routine appear under the name fmin in the ā€œgolden oldiesā€ folder on Netlib.)

It was written for a 1966 IBM machine, but it still compiles just fine today:

ivan:~/fortran$ gfortran -Wall -c -std=f2018 localm.f 
ivan:~/fortran$ 

If you feel that the language is complex, you can reduce the complexity intentionally through self-restraint. (Similar to how monks practice asceticism.)

2 Likes

One use of pointers which hasnā€™t been mentioned yet is bounds-remapping, e.g.

real, target :: a(2,3)
real, pointer :: aflat(:)
aflat(1:6) => a

This can be useful to temporarily modify the rank of an array, or use custom bounds. While this may inhibit optimization in some cases, it can help avoid copies in others. In case you know for certain there is no aliasing, you can help the compiler by passing the pointer array as a dummy argument.

With Fortran 2003, you donā€™t even need a select case construct, but you can use an array to make a dispatch table:

! foo.f90
module foo
implicit none
abstract interface
   subroutine void()
   end subroutine
end interface
contains
   subroutine a()
      print *, "Foo"
   end subroutine
   subroutine b()
      print *, "Bar"
   end subroutine
   subroutine c()
      print *, "Baz"
   end subroutine
end module
program main
use foo, only: void, a, b, c
implicit none
type :: pp
   procedure(void), pointer, nopass :: pf => null()
end type
type(pp) :: table(3)
integer ::i
table = [pp(a),pp(b),pp(c)]
do i = 1, 3
   call table(i)%pf()
end do
end program

The NAG Fortran compiler already supports default initialisation of procedure pointer components:

type(pp), parameter :: table(3) = [pp(a),pp(b),pp(c)]

Due to the additional derived type needed, the syntax is a bit more verbose when compared to C:

#include <stdio.h>
void a(void) { puts("foo"); }
void b(void) { puts("bar"); }
void c(void) { puts("baz"); }
typedef void (*pp)(void);
static const pp table[] = { a, b, c };
int main(void)
{
  for (int i = 0; i < 3; ++i) 
    table[i]();
  return 0;
}

I was interested recently, in comparing select case and computed goto, vs a procedure pointer dispatch table. You can look at here on compiler explorer: Compiler Explorer. The outcome was both generate very similar machine instructions. For the procedure pointer solution, gfortran just unrolled the whole loop:

        call    __foo_MOD_a
        call    [QWORD PTR table.0[rip+8]]
        call    [QWORD PTR table.0[rip+16]]
4 Likes

As stated by other contributors, modern Fortran has often high level alternatives to pointers, that C does not offer (C++ is another story). Also, keep in mind that Fortran pointers are fairly different from C pointers.

When pointers were introduced in Fortran 90 there were more usage cases for pointers than there are now. For instance in the recent versions of the standard allocatable objects are allowed in derived types or as dummy arguments, which was not the case in F90, so pointers had to be used instead.

You mean ā€œstarting with Fortran 2003ā€? Your shown example conforms with Fortran 2003.

1 Like

Quoting Rob Pike (co-creator of UTF-8 and also the Go programming language):

Pointers are sharp tools, and like any such tool, used well they can be delightfully productive, but used badly they can do great damage (I sunk a wood chisel into my thumb a few days before writing this).

While pointers can be very elegant when used correctly, the NSA and US Department of Commerce sent the C/C++ world into panic, when they published an information sheet on memory safety, in light of the increased amount of cyber attacks. Here are some popular articles on the topic:

In the 2022 list of Top 25 most dangerous software weaknesses, you have 5 related to memory safety, the #1 weakness being out-of-bounds write. Some of the C/C++ colleagues I work with, wonā€™t even look at my code unless Iā€™ve ran it through a code sanitizer such as LSan.

I used to think the attack threat is blown out of proportion, but a few weeks ago, a scientific research institute in Munich was left completely paralyzed as a result of one.

IMO, Fortran pointers with the target concept were ahead of their time, judging by the repercussions we see today for C/C++.

3 Likes

Thanks for the correction. (Iā€™ve verified that the example compiles successfully with gfortran and the flag -std=f2003)

Does that apply also to the default initialization?

type(pp), parameter :: table(3) = [pp(a),pp(b),pp(c)]

Great question, I think so, that it conforms to Fortran 2003 but Iā€™m not 100% sure. Both Intel Fortran and gfortran donā€™t support the named constant declaration.

With NAG Fortran, is it possible to do standards checking similar to -std= with GCC?

It is possible:

$ nagfor -f2018 foo.f90 
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7101
[NAG Fortran Compiler normal termination]
$ nagfor -f2008 foo.f90 
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7101
[NAG Fortran Compiler normal termination]
$ nagfor -f2003 foo.f90 
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7101
Extension(F2008): foo.f90, line 24: Value A for procedure pointer component PF in PP structure constructor in constant expression is not a disassociated pointer
Extension(F2008): foo.f90, line 24: Value B for procedure pointer component PF in PP structure constructor in constant expression is not a disassociated pointer
Extension(F2008): foo.f90, line 24: Value C for procedure pointer component PF in PP structure constructor in constant expression is not a disassociated pointer
[NAG Fortran Compiler normal termination, 3 warnings]
1 Like

Forgive my noobish question, but can associate be used to create things like linked lists ?

I tried to implement a linked list without pointers, but it was more difficult than I thought. The only way I found to traverse the list and append something was by using recursive functions because they allow you to pass by reference.

associate doesnā€™t work as I expected. Whatā€™s the problem here?

associate(next => current_node%next)
    if(.not. allocated(next)) then
        allocate(next)
        next%data = data
    else
        call append_node(next, data) ! recursion
    end if
end associate
gfortran a.f90 -g
a.f90:29:25:

   29 |                 allocate(next)
      |                         1
Error: Allocate-object at (1) is neither a data pointer nor an allocatable variable
a.f90:28:31:

   28 |             if(.not. allocated(next)) then
      |                               1
Error: ā€˜arrayā€™ argument of ā€˜allocatedā€™ intrinsic at (1) must be ALLOCATABLE

Here is a functioning program:

Whole code
program linked_list
    implicit none

    type node
        integer :: val
        type(node), allocatable :: next
    end type node

    type(node) :: head, last
    integer    :: i

    head%val = 0

    ! Add some nodes to the linked list
    do i=1,3
        call append_node(head, i)
    end do

    last = get_last_node(head)
    print *, "last =", last%val

contains

    recursive subroutine append_node(current_node, val)
        type(node), intent(inout) :: current_node
        integer,    intent(in) :: val

        if(.not. allocated(current_node%next)) then
            allocate(current_node%next)
            current_node%next%val = val
        else
            call append_node(current_node%next, val)
        end if
    end subroutine append_node

    recursive function get_last_node(current_node) result(last_node)
        type(node), intent(in) :: current_node
        type(node) :: last_node

        print *, "current =", current_node%val

        if(.not. allocated(current_node%next)) then
            last_node = current_node
        else
            last_node = get_last_node(current_node%next)
        end if
    end function get_last_node

end program linked_list

Does anyone has an idea how to make single linked list properly?

1 Like

The standard says

19.5.1.6 Construct association
2 In an ASSOCIATE or SELECT TYPE construct, the following rules apply.
  ā€¢ If a selector is allocatable, it shall be allocated; the associate name is 
    associated with the data object and does not have the ALLOCATABLE attribute.
  ā€¢ If a selector has the POINTER attribute, it shall be associated; 
    the associate name is associated with the target of the pointer and 
    does not have the POINTER attribute.

so, technically if you associate(next => current_node%next) you are assuming it is already allocated and cannot be deallocated within the associate construct. Then, the if(.not. allocated(next)) is probably a bit confusing.

3 Likes

Iā€™d be tempted to report this as a bug to gfortran. As @han190 quoted

So gfortran should have flagged the use of the allocated intrinsic on an object that does not have the allocatable attribute as an error at compile time.

2 Likes

ifort/ifx also would return a compile time error:

error #8306: Associate name defined in ASSOCIATE or SELECT TYPE statements doesn't have ALLOCATABLE or POINTER attribute.   [NEXT]
            allocate(next)

I usually use associate for already allocated or pointing-to data, not for such dynamic creation precisely because of such kind of issues, and I donā€™t think it was designed to be used for such purposes ā€¦ ?

3 Likes

Well, the error message is correct, but at least it is also misleading. If the error message said, that next is not allocatable because it is the nature of association, my error would be obvious.

Oops. My bad. The error message wasnā€™t mentioned so I didnā€™t think to look for it/at it. It could potentially be improved, but I donā€™t know how easy it would be. I donā€™t know if it knows why the object doesnā€™t have the allocatable attribute at the point it produces those errors.

FWIW, I do not recommend including standard section numbers in diagnostic messages, for two reasons:

  1. Much effort will be required to update them for future revisions
  2. The user is unlikely to have a copy of the standard handy, and even if they do, there can be multiple possibilities of violations.

I much prefer clearly worded, self-contained, and actionable diagnostic messages. I agree with @kargl that when there are multiple violations, the compiler will just report the first one found, which may still end up confusing the user.

4 Likes