Easy features of Fortran 2003 on

I am happy with Fortran 95 (with the allocatable array extensions of F2003), but I want to overcome inertia and use features from later standards when helpful. I believe the two big features beyond F95 are OOP and coarrays. What are some features beyond F95 that don’t take much new mental effort but are useful?

Some examples of easy features of earlier standards are
(1) END DO instead of CONTINUE with a numbered line
(2) brackets [] instead of (//) to enclose arrays

An example of an easy feature beyond F95 is the unlimited format:

write (*,"(*(f0.4,1x))") x(:) ! unlimited format
write (*,"(1000(f0.4,1x))") x(:) ! old way
2 Likes

I like and use:

  • Allocatable character strings (F2003)
  • Automatic allocation on assignment for strings and arrays (F2003)
  • do concurrent (F2008) as a more restrictive and potentially parallelizable do. It uses the same syntax as now obsolescent forall assignment.
  • Coarrays (F2008) and collectives (F2018) in place of MPI. This one is perhaps not so easy but sure easier than MPI.

And probably some others that I forgot.

Submodules are also new and not that complicated. The C interoperability features are new, but perhaps not needed for your code. Also there are lots of additional intrinsic procedures.

Some of my favorites not yet mentioned:

  • The error stop statement (F2008). A big plus for some people is that it can be used in pure procedures as of F2018.
  • The block ... end block construct (F2008). I use this usually when I’m debugging or experimenting inside a long subprogram. It lets me declare additional variables and keeps them close to the bit of code I’m messing with. It also stands out visually, which helps when tidying up the code later on. It can also be given a descriptive label like debug: block ... end block debug.
  • Easy access to the real and imaginary parts of complex values with z%re and z%im (F2008).
  • Sourced and molded allocations (F2008). allocate (x, source=a) allocates x to have the same bounds and values as a. allocate (x, mold=a) allocates x to have the same bounds as a, but does not copy the values. This is a generally useful thing, but is also heavily used in dealing with polymorphic variables.
  • newunit option to the open statement (F2008). You can request an available unit number and have it assigned to an integer variable for later use. E.g., open (newunit=u) ... write (u, *) .... close (u)
  • Tons of great intrinsics in F2008: complex trig functions and their inverses, hyperbolic functions and inverses, gamma and error functions, minloc and maxloc
6 Likes

I use “associate” quite often to extract components of derived types into a local scope, so as to minimize the amount of typing :slight_smile:

(In practice, I define a CPP macro “let” and “endlet” for this, because “associate”
and “end associate” is too tedious to type… <-- I am not using any editor macros for this.)

#define let associate
#define endlet end assocate
subroutine myproc( obj )
   type(mytype_t) :: obj
   let( foo => obj % foo, &
         baa => obj % baa, &
         baz => obj % baz )
   !! ... some calc using foo, baa, baz
   endlet
end

(but I guess “let” is not a good word for mutable things… XD)

@ivanpribec mentioned findloc, introduced in Fortran 2008, which finds the location of the first matching element in an array. It works with at least gfortran and Intel Fortran. The output of

implicit none
integer :: imat(2,3)
print*,findloc([0,1,0],1),findloc([0,0,0],1),findloc([1,0,1],1,back=.true.)
imat = 0
imat(1,3) = 1
imat(2,1) = 1
! imat = [0 0 1
!         1 0 1]
print*,findloc(imat,1,dim=1)
print*,findloc(imat,1,dim=2)
end

is

   2           0           3
   2           0           1
   3           1
1 Like