Convert Fortran code to lower case

The Python script below tries to convert free source form Fortran code to lower case, except for comments, but it
(1) assumes that ! always begins a comment, although ! within quotes does not.
(2) converts string literals to lower case, which one may not want.

Has anyone written a program that converts Fortran code to lower case more carefully?

"""convert Fortran code to lower case except for comments
usage: python xlower_case_fortran.py <source_file>
The script writes lower case code to standard output.
"""
from sys import argv
source_file = argv[1] 
fp = open(source_file,"r")
for line in fp:
    text = line.rstrip()
    ipos = text.find("!")
    if ipos >= 0:
        print(text[:ipos].lower() + text[ipos:])
    else:
        print(text.lower())

I once saw (and I believe we tried it on a project I was working on) a tool called flower. I can’t seem to find it just now, but a more thorough search should be able to uncover it.

GitHub - ylikx/fortran-legacy-tools: Three tools to deal with Fortran code: fixed to free source f has a minimalist tool for case conversion;
there are other utilities for updating code, since ! was a common extension especially on VAX machines even pre-f90 standards I am not sure other tools might be what you want. The Fortran Wiki has a list of such tools.

Yes, lfortran fmt does this. It also does more aggressive formatting, which you might not like, but it preserves comments and empty lines now and the formatting is configurable (and we are happy to add more configurations if people request them). Modulo bugs that we will fix if you report them.

About 20 or so years ago I wrote my own F77 fixed format to F90 free format conversion program (in Fortran of course) that does case conversion as well as converts continuations to & , and comments to !. The user has the option of converting a single file or all the files in a directory in one run. I was working towards adding other features like converting common blocks to modules etc but decided it wasn’t worth the effort. The code has proved fairly reliable over the years but I still encounter what I like to call “stupid programmer tricks” that I didn’t anticipate and causes the program to generate output that won’t compile without a syntax error. My favorite examples were in a DoD code where someone thought putting a space between the letters of SUBROUTINE and FUNCTION (id S U B R O U T I N E etc) was cool and a programmer who liked to wrap numbers in DATA statements at the 72 character boundary instead of starting the entire number on a new line. Thankfully, those kinds of stupidity are rare and I’ve used the program to convert old F77 code bases with tens and sometimes hundreds of thousands of lines of code. Time to convert 100 or so files is usually on the order of a few seconds on modern processors.

i haven’t looked at my original code in about 15 years so there are probably some things I want to change or fix but if folks are interested I’ll go back over it and make a copy available on github

1 Like

I am using a small Python script. Sorry, no time to translate from French. Just know that a “fichier” is a file and a “rĂ©pertoire” means a directory. All the .f90 files in the given directory are “translated”. Only the Fortran instructions listed in the list are put in lower case. A copy .f90~ of each file is made before transformation. The input files must be encoded in UTF-8. A command such as $ recode ISO-8859-15..UTF-8 *.f90 can be useful.

#!/usr/bin/env python3
# -*- coding: utf-8 -*-
#
# Mettre en minuscule les instructions Fortran de fichiers *.f90
# 
# ATTENTION, il faut d'abord convertir les fichiers en UTF-8 pour Ă©viter les problĂšmes de codage :
# recode ISO-8859-15..UTF-8 *.f90
# Ensuite, mettre dans la variable répertoire le chemin à traiter.
#
# vmagnin, 06-10-2016, mis Ă  jour le 05-12-2016

import os
import shutil

instructions = ("IMPLICIT NONE", "INTEGER", "DOUBLE PRECISION", "CHARACTER(", "COMPLEX(", "LOGICAL", "PARAMETER", "TYPE(", "TYPE (", "DIMENSION(", "DIMENSION (", "SIZE(", "PROGRAM ", "SUBROUTINE", "FUNCTION", "RETURN", "PURE ", "RESULT(", "NINT(", "INT(", "HUGE(", "USE ", "MODULE", "CONTAINS", "WHILE ", "REAL(", "AIMAG(", "KIND", "CALL ", "ALLOCATE(", "ALLOCATABLE", "SELECT CASE", "CASE(", "CASE (", "CASE DEFAULT", "END SELECT", "IF (", "IF(", "END IF", "ENDIF", "ELSE", " THEN", ".TRUE.", ".FALSE.", ".AND.", ".OR.", ".NOT.", ".EQ.", ".NE.", ".LT.", ".LE.", ".GT.", ".GE.", "OPEN(", "UNIT=", "FILE=", "TITLE=", "WRITE(", "FORMAT(", "CLOSE(", "END DO", "ENDDO", "DO ", "INTENT(IN)", "INTENT(OUT)", "INTENT(INOUT)", "ABS", "DSQRT(", "SQRT(", "MOD(", "MIN(", "MAX(", "DBLE(", "EXP(", "SIN(", "COS(", "SUM(", "LOG(", "DATE_AND_TIME(", "RANDOM_NUMBER(", "RANDOM_SEED(", "STOP", "PRINT", "END ", "LEN=", "SETMESSAGEQQ(", "QWIN$MSG_RUNNING", "QWIN$MSG_TERM", "QWIN$MSG_EXITQ", "ABOUTBOXQQ", "QWIN$MAX", "QWIN$FRAMEWINDOW", "GETACTIVEQQ(", "SETWSIZEQQ(", "SETCOLORRGB", "SETBKCOLORRGB(", "$GCLEARSCREEN", "CLEARSCREEN", "QWIN$SET", "SETACTIVEQQ(", "SAVEIMAGE(", "GETWINDOWCONFIG(", "SETWINDOWCONFIG(", "SETPIXELrgb_w", "MOVETO_W", "LINETO_W", "GETTIM(",  )

repertoire = "/home/vmagnin/workingdir/"

fichiers = tuple(os.walk(repertoire))
for fichier in fichiers[0][2]:
    if fichier.endswith(".f90"):
        print(fichier)
        # Sauvegarde du fichier :
        shutil.copy2(repertoire+fichier, repertoire+fichier+"~")
        # On charge le fichier (attention à l'encodage du fichier de départ...) :
        whole_file = open(repertoire+fichier, 'r').read()
        # Instructions Fortran en minuscules :
        for instruction in instructions:
            whole_file2 = whole_file.replace(instruction, instruction.lower())
            whole_file = whole_file2
        # On Ă©crase le fichier initial :
        whole_file3 = open(repertoire+fichier, 'w').write(whole_file)

print("N'oubliez pas d'effacer les fichiers de sauvegarde aprÚs vérification !")

PS: sounds like LFortran is promising, and I was really sure some of the tools listed on the Fortran Wiki did that; and the fixed-format tool sounds interesting but I did have similar needs at one time, so if the code is really free-format and does not have things like Hollerith and pre-processor directives (macros in particular; easy to skip a line starting with # but the macros would need something far more sophisticated than this) I found my old filter program. Here is a short version:

  use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit, iostat_end
implicit none
character(len=4096)    :: filename        
character(len=256)     :: message          
integer,parameter      :: fd=10             
integer                :: ios,ios1
character              :: c1,previous=achar(0)
logical                :: incomment=.false., insingle=.false., indouble=.false., tolower=.true.
   call get_command_argument(1,filename)
   open(unit=fd,file=filename,access='stream',status='old',iostat=ios,action='read',form='unformatted',iomsg=message)
   if(ios.ne.0)then
      write(stderr,'(a)') '*flower* ERROR: could not open '//trim(filename)//':'//trim(message)
      stop 5
   endif
! reading one character at a time is much more limiting than reading tokens but is sufficient for the vast majority of cases
ONE_CHAR_AT_A_TIME: do                                                ! loop through read of file one character at a time
   read(fd,iostat=ios1) c1
   if(ios1.eq.iostat_end)then                                         ! reached end of file so stop
      stop
   elseif(ios1.ne.0 )then                                             ! error or end of file
      write(stderr,*)'*flower* ERROR: EOF or error on '//trim(filename)//' before end of '//trim(filename)
      stop 1
   endif
   select case(c1)
   case('!')
      if(any([insingle,indouble]))then
         continue
       else
         incomment=.true.
      endif
   case('"')
      if(any([incomment,insingle]))then
         continue
      elseif(indouble)then
         indouble=.false.
      else
         indouble=.true.
      endif
   case("'")
      if(any([incomment,indouble]))then
         write(*,*)'HUH',insingle,indouble
         continue
      elseif(insingle)then
         insingle=.false.
      else
         insingle=.true.
      endif
   case(NEW_LINE('A'))
      if(previous.ne.'&')then
         incomment=.false.
         insingle=.false.
         indouble=.false.
      elseif(incomment)then
         incomment=.false.
      endif
   case('a':'z')
      if(.not.tolower)then
         if(.not.any([incomment,insingle,indouble]))then
            c1=char(iachar(c1)-32)
         endif
      endif
   case('A':'Z')
      if(tolower)then
         if(.not.any([incomment,insingle,indouble]))then
            c1=char(iachar(c1)+32)
         endif
      endif
   end select
   write(*,'(a)',advance='no')c1
   if(c1.ne.' ')then
      if(.not.any([incomment]))then
         previous=c1
      endif
   endif
enddo ONE_CHAR_AT_A_TIME
end program flower

It is called “flower” but has no association with the other “flower” utility mentioned here. I tried it with three compilers and it worked on what I tested it on, but it really expects simple cases. ```text
PROGRAM TEST_flower ! TEST
WRITE(,)‘Hello World!’,VAR, & ! and This too
& VAR2,VAR3, “and ““STUFF””” ! Ok?
WRITE(,)‘HELLO and’,“GoodBye”
WRITE(,)‘HELLO and’&
,“GoodBye”
A=10
B=20
C=A*B
END PROGRAM TEST_flower

```text
program test_flower ! TEST
   write(*,*)'Hello World!',var, & ! and This too
&  var2,var3, "and ""STUFF""" ! Ok?
write(*,*)'HELLO and',"GoodBye"
write(*,*)'HELLO and'&
           ,"GoodBye"
           a=10
           b=20
           c=a*b
end program test_flower

It is also a utility program in the General Purpose Fortran repository. The man-page shows that the same
basic approach is useful for getting a measure of what percentage of a code is comments or for extracting comments for running through a spell-checker or a translator, for example.

I’m also trying to find a solution on this topic.
I use VSCode to develop Fortran program, and I have installed findent, but I’m not sure if it can convert Fortran code to lower case.
If it has that function, can anyone tell me how to configure it? Thanks a lot!

You can use the Vim editor or one of its variants to convert a single file by just doing the following command. Be aware that it will convert everything even things embedded in character strings that you might want to keep upper case.

:%s/[A-Z]/\L&/g

Thank you for your time, but what I want to achieve is only making the keywords,functions,etc. lowercase.
I actually found that fprettify can realize this objective, but the weakness is that it can’t process a source file which contains Chinese character, that is, it can only process a utf-8 file.
So, findent can’t do case converting, and fprettify can’t adjust my language environment, I am really upset.

I apologize for my inaccuracy, actually utf-8 support Chinese, so there is no problem in it, just use fprettify to convert case is enough!

fpt (http://simconglobal.com) reformats Fortran code according to user-written rules. You can specify the upper or lower case separately for keywords, intrinsics, user-defined symbols, exponent charaters (E, D, Q) etc. To convert everything to lower case just set them all to lower. It doesn’t touch comments or strings (and knows about ! in strings). It will do fixed format, and knows about C, c, , / (Yes, some Fortrans allow it) and D-, X and Y lines. It treats DEC$, MPI and associated keywords as keywords.

Please download it and try it. It is free for academic and personal use.

And please let me know if you experience problems. fpt understands (we believe) all of the VMS and MPX extensions and almost everything in the standard except sub-modules and a few recent intrinsics (which it will simply treat as externals).

Best wishes,

John

1 Like

You can transform a whole file or a code selection to lowercase/uppercase/camelcase etc. from the VSCode command pallete, this is a naive approach

How to switch text case in visual studio code - Stack Overflow.

I seem to vaguely recall findent and fprettify both having an option but you will have to check their docs.

EDIT: just noticed your later comment and looks like you figured it out. Glad you were able to solve this.