Refactoring code into a subroutine

I often create a subroutine by

  • pasting a block of code into an empty subroutine
  • compiling with IMPLICIT NONE
  • copying declarations from the source file the code was copied from. Sometimes what the compiler thinks is an undeclared variable is actually a function which needs to be imported from a module.
  • making some variables INTENT(IN) or INTENT(out) arguments

I wonder if there are any tools to automate this. Something that did 80% of the job would still be useful.

A Windows batch file that uses Unix tools to list undeclared variables is

@ echo off
:: list undeclared variables in Fortran source file, compiled with gfortran
:: usage: gfundec.bat foo.f90
setlocal
set gfout=temp_gf.txt
gfortran -c -Wall %1 2> %gfout%
echo undeclared in %1:
grep IMPLICIT %gfout% | tr -d "'" | cut -d ' ' -f 3

When run on the code

module foo_mod
implicit none
contains
subroutine bar()
! code below copied from another source file
ndays = size(xx,1)
nret = ndays - 1
nsym = size(xx,2)
allocate (profits(nret,nsym),xpos(ndays))
do nma2=nma2_min,nma2_max
   write (*,"(/,a,1x,i0)") "nma2",nma2
   xpos = merge(1.0_dp,-0.5_dp,rollmean_ratio(xx(:,1),1,nma2) > 1.0_dp)
   profits = spread(xpos(:nret),2,nsym) * xret
   if (.false.) call print_stats(cstats_ret,profits,sym,title="profits")
   call print_tangent_port(profits,sym,cstats_ret=cstats_ret,print_uncon=print_tangent_portfolio, &
                        print_long_only=print_tangent_port_long_only)
end do
end subroutine bar

it says

undeclared in temp_mac_tangent.f90:
cstats_ret
ndays
nma2
nma2_max
nma2_min
nret
nsym
print_tangent_port_long_only
print_tangent_portfolio
profits
sym
xx

You could pass the report through a small, almost trivial, Fortran program to generate default declarations:

  • Variable names that start with one of i … n are probably meant to be integers (given that they are not declared makes that likely)
  • Variable names that start with something else are probably reals

The program could also make a copy of the code and insert these declarations and do the other boilerplating stuff (module … end module, etc.)
Running it through the compiler again will alert you to the flagrant mistakes: taking a substring from a real variable for instance.

Instead of IMPLICIT NONE you might consider IMPLICIT NONE(TYPE,EXTERNAL) that would require declaration of functions as well.

Note that an IMPLICIT NONE in the specification part of a module also applies to any contained subprograms in the module, which explains the error messages you got for subroutine bar.

What compiler supports that? Ifort still chokes .

The Cray compiler supports it (along with most of F2018). Intel claims ifort supports 2018. Are you using an old version? A newish Intel compiler seems to work:

% /opt/intel/oneapi/compiler/2021.1.1/mac/bin/intel64/ifort -c test.f90
% cat test.f90
implicit none (type,external)
end program
%

The Eclipse IDE photran plug-in has a refactoring set of functionalities that do what you are after and more.

Latest ifort. It “supports” it but it does not work.