Compiling modules in F77

I am still slowly converting my Fortran 77 code into F90. Currently, I have shifted a lot of aspects into a module file (called modules.f) and am trying to compile this. Previously this produced a series of .mod files; each .mod file being based upon one of the modules defined in that single file.

However, I cannot seem to get this to work again?

I am using gfortran and have tried gfortran modules.f but to no avail.

What should I do to create the .mod files?

this link could be useful: https://camfort.github.io/

Could you show the code?

2 Likes

I can indeed.

I’m not looking for any additional tools, as such, since I am working through the code line-by-line to identify how it is working and how I might make it more efficient.

This module file (modules.f) is my construction taken from the original parm.h and xvar.h files that accompanied the previous version. The final module is my construct to handle a data recording file.

module stellar_values

	implicit none
	
	integer, parameter	::	mj    		= 4000
	integer, parameter	::	mh    		= 4
	integer, parameter	::	me    		= 9
	integer, parameter	::  MTau  		= 20000
	
	real, parameter		::	sig   		= 5.67051d-5
	real, parameter		::	pi    		= 3.14159265359d0	! Pi
	real, parameter		::	grav  		= 6.6704d-8
	real, parameter		::	cc    		= 2.99792458d10
	real, parameter		::	hmass 		= 1.6732d-24
	real, parameter		::	xm_sun      = 1.989d33      	! Solar mass (g)
	real, parameter 	::	r_sun       = 6.9599d10   		! Solar radius (cm)
	real, parameter 	::	xl_sun      = 3.83d33     		! Solar luminosity (erg/s)
	real, parameter 	::	yr          = 3.1556736d7		! yr in sec
	real, parameter 	::	xmdot_sunyr = 6.30268d25		! acc. rate in M_sun/yr	
	
end module



!	MODULE:	ahecopacity

module ahecopacity

	real, save			::	auxcheop(25,32), rhel(25), thel(32)
	
end module



!	MODULE: ahycopacity

module ahycopacity

	real, save			::	auxchyop(23,28), rhyr(23), thyr(28)
	
end module



!	MODULE:	gic

module gic

	use stellar_values, 	only: mh, mj

	real, save			:: 	arad3, atmn, change, chgmax, chgmin, crad, cwrk, dflux, dlmn, dlmx, dm(mj), dmat, dmix, dpat, dpmx
	real, save			::	dpmn, dtime, dtmax, dtmin, dtmn, dxmn, dxmx, dzdt, dzmax, dzmin, ener, enorm, factim, grv(mj), rhmn
	real, save			::	rlh, taujk, taux, time, vx(mj, mh), x(mj, mh), xcorm, xh2, xtimod, zflux, zlold, zm(mj), zmass, zmmn
	real, save			::	zmmx, zmold, zrold
	integer, save		:: 	igrv, iprt, jatm, jrit, junit, katm, kunit, latm, massLoss, methd, model, mrec, n, nadd, natm, ng
	integer, save		::	nmod, nprob, nrec, nrit, nsub
	
end module



!	MODULE:	corr

module corr

	use stellar_values, 	only: me, mh, mj

	real, save			::	dg(mh), lithium, nitrogen, radM(10), radR(10), eps(mh), smax(mh), smin(mh)
	integer, save		::	itmin, itmax, iter, jc(mh), jg(mh)
	
end module



!	MODULE: helium

module helium

	use stellar_values, 	only: me, mh, mj

	real, save			::	element(mj, me), velement(mj, me)
	real, save			::	hydrogen(mj), vhydrogen(mj)
	real, save			::	carbon(mj), deuterium(mj), erest(mj), helium3(mj), helium4(mj), oxygen(mj)
	real, save			::	vcarbon(mj), vdeuterium(mj), verest(mj), vhelium3(mj), vhelium4(mj), vlithium(mj)
	real, save			::	vnitrogen(mj), voxygen(mj)
	integer, save		::	lithium(mj), nitrogen(mj)
	
	Equivalence (hydrogen, element(1,1))
    Equivalence (deuterium, element(1,2))
    Equivalence (helium3, element(1,3))
    Equivalence (helium4, element(1,4))
    Equivalence (carbon, element(1,5))
    Equivalence (nitrogen, element(1,6))
    Equivalence (oxygen, element(1,7))
    Equivalence (lithium, element(1,8))
    Equivalence (erest, element(1,9))
    Equivalence (vhydrogen, velement(1,1))
    Equivalence (vdeuterium, velement(1,2))
    Equivalence (vhelium3, velement(1,3))
    Equivalence (vhelium4, velement(1,4))
    Equivalence (vcarbon, velement(1,5))
    Equivalence (vnitrogen, velement(1,6))
    Equivalence (voxygen, velement(1,7))
    Equivalence (vlithium, velement(1,8))
    Equivalence (verest, velement(1,9))
	   
end module



!	MODULE: hy

module hy

	use stellar_values, 	only: mh, mj

	real, save			::	e(mh), g(mh), ha(mh, 2 * mh + 1), hc(mh, mh), hd(mh, mh)
	real, save			::	he(mh, mh), hw(mh, mh + 1, mj), hx(mh, mh + 1)
end module




!	MODULE: mix

module mix

	use stellar_values, 	only: mj

	character(48), save	::	filez, lfile, ofile, pfile, sfile
	integer, save		::	iconvect(mj), ienergy(mj)
    real, save			::	radM(10), radR(10)
    
end module



!	MODULE:	zones

module zones

	real, save			::	nrad, radm, radr
	integer, save		::	increment_zones, iunit, lunit, start_zones, unitz
	
end module



!	subroutine: record_time

!	purpose:	records execution time

!	parameters:	sf	input	"begin"		records the start time
!							"end"		records the finish time and then stores this in a file called 'data.lst'

!	author:		g newport	18-10-2021

module dummy_routines

	contains
	


		subroutine record_time(sf)

			character (len = *), intent(in), optional	::	sf

			character (100) ::	sf_
			character (8) 	:: 	curdate
			character (10)  :: 	curtime

			logical			:: 	fileexist	= .false.

			real, save		:: 	start		= 0.00
			real, save 		:: 	finish		= 0.00
			
			if (present(sf)) then
				sf_ = sf
			else
				sf_ = "begin"
			end if
			
			inquire (file = "data.lst", exist = fileexist)

			if (fileexist) then
				open(7, file = "data.lst", status = "old", position = "append")
			else
				open(7, file = "data.lst", status = "new")
			end if

			call date_and_time(date = curdate, time = curtime)

			if (sf_ == "begin") then
				write (7, *) "date of run (yyyymmdd) = ", curdate
				write (7, *) "time of run (hhmmss.mmm) = ", curtime
				call cpu_time (start)
			else
				call cpu_time (finish)
				open (7, file = "data.lst", position = "append")
				write (7, *) "execution time (s) = ", finish - start
			end if
				
			call flush (7)
			close (7)
			
		end subroutine
	

end module

Ok:

gfortran -c mod.f90  


ahecopacity.mod
ahycopacity.mod
corr.mod
dummy_routines.mod
gic.mod
helium.mod
hy.mod
mix.mod
stellar_values.mod
zones.mod

Some warnings about conversion real (8) to real (4), and Nonconforming tab

FWIW Your code compiles fine in OneApi Classic 32 and 64 bit
“equivalence” is brave
is “unit = 7” sacred, try newunit?

Best wishes

1 Like

Yes, I wondered if it was simply an issue with the extension. I got the 4 to 8 issue, but I’ll chase that down when I get a chance.

Thank you.

newunit?

Sorry, unsure what you mean by this.

Equally the same for being brave. :slight_smile:

Steve has given you a full reply on “equivalence”, and I could not see enough of the code to know why it was being used, but usually “equivalence” was a bug waiting to happen.
Explicit unit numbers are like global variables and should be avoided e.g.
Open(unit = 7…
I would suggest you replace this with
Integer :: nin
Open(newunit = nin,… {Then}
Read(nin,…
Close(nin)

The newunit guarantees to pick a unit number that is not already in use anywhere else and will be negative

You may also want to use the iostat and iomsg clauses too to catch and help diagnose problems

Good luck, sorry about the hasty reply from my phone

No problems; thank you for the help.

I’ll need to work on this to get my head around it properly.

Currently I am closing the files as soon as I have opened them and used the file as I need to. I also need to identify how much file access I actually need (there is a LOT of writing to files that has little actual benefit).

I do not understand why you are using “real, save ::” in a module ?
Is this different to “real ::” ?

Although “newunit=” is a new feature to Fortran, “unit=” is still valid and can be preferred functionality.
newunit= can provide a -ve unit number, which clashes with my old code approach that uses a -ve unit number to indicate a file has not been opened.

@garynewport ,

  • A suggestion: try using an IDE that allows easy constructions of projects to build programs and debug them e.g., Code:Blocks with Fortran, Visual Studio with Intel Fortran oneAPI. That will help you greatly to focus on your code itself and your domain aspects.

  • An earnest request: will it be possible for you to use better terminology? Terms such as “F77”, “Fortran 77 code”, “into F90” can be rather unclear to readers for such terms can carry many connotations.

It appears you are working toward refactoring of an existing codebase, correct? It may help you to mostly keep it simple: show relevant sections of existing code and the same with your revised code and with brief and succinct comments on what you hope to achieve. Readers can then quickly give you feedback.

@garynewport doesn’t show all the ways in which element and individual element variables e.g., hydrogen are used in the code.

Chances are high the code is setup to load some data into the rank-2 array for element and the purpose of equivalence is as an alias to the values.

If so, an even braver option, one that will be “kosher” with respect to current Fortran standard, might just be to employ the TARGET and POINTER attributes. And apply the PROTECTED to the aliases i.e., the objects with the POINTER attribute in order to some guard against the pitfalls of working with POINTERs in the code.

That is, what is currently

module helium

	use stellar_values, 	only: me, mh, mj

	real, save			::	element(mj, me), velement(mj, me)
	real, save			::	hydrogen(mj), vhydrogen(mj)
	..
	
	Equivalence (hydrogen, element(1,1))
    ..
    Equivalence (vhydrogen, velement(1,1))

can instead be as follows:

module helium

	use stellar_values, 	only: me, mh, mj

	real, target, save              :: element(mj, me), velement(mj, me)
	real, pointer, save, protected	:: hydrogen(:) => element(:,1)
	real, pointer, save, protected	:: vhydrogen(:) => velement(:,1)
    ..

At the point of use in the rest of OP’s code with objects such as hydrogen and vhydrogen, etc., no change be needed.

An advantage with working with TARGET ↔ POINTER paired attributes as a use case for aliases is type safety besides the fact it is in line with the use case that led to the introduction of the facility in Fortran 90 revision circa 1991.

I wrote the following to get the effect of the newunit= feature with a positive unit number.
You can then use it to write open(newunit(10), …) for example.

  integer function newunit(nin) ! = lowest unopened unit number >= abs(nin)
      integer,intent(in)::   nin
      logical open
      integer ios
      do newunit = abs(nin),huge(1)-1
         inquire(newunit,opened=open,iostat=ios)
           if((ios/=0) .or. .not.open) exit
    end do
    if(newunit==huge(1) .or. newunit<0 .or. ios/=0) stop &
         "Function newunit can't find a unit number" 
  end function newunit

This is not necessarily a trivial question as the standard policy for save attribute of module objects apparently changed in F2008. Before that, a module object could become undefined upon return from a subprogram using that module, unless it had explicit save attribute or the module was still used by another subprogram or main unit. Since F2008 all module objects automatically have save attribute.

Has anyone used a F90+ compiler that behaves in this way ?
I am not aware of any.
Would this mean that most compilers have not been conforming ? and probably with good reason.

I’m using Geany, which offers me a number of strengths, including that it works on all three of the platforms I am using (Windows, macOSX and Linux).

I will endeavour to use the correct terminology. Sorry, it is often difficult when moving to a new language to pick up on the nuances of the community; often harder than learning the actual language! hahahaha!

I do try to display as much of the code, without sharing too much or giving insufficient detail but I undoubtedly get this wrong. It is a mixture of not wanting to make too long a post with not able to share too much of the code anyway.

I’m not aware of any such compiler, either. Still, I think it was the code presuming that module objects are in fact static that was not conforming, not the compilers. I guess no standard required the module data memory to be released.

It seems very much like it was with common blocks. A named common was not guaranteed to be preserved if the control returned from a subprogram declaring it and the parent (and all the parent’s parent units) did not declare that common. Unless it had been save-ed.

Certainly, there WERE compilers which would not preserve COMMON if there was no active procedure using that COMMON. This was common (!) in the days of “overlays” in the 1960s. This was the basis for the wording in the standard for module variables behaving similarly.

In F2008, module variables no longer needed to be SAVEd, but the wording for COMMON was still there. F2018 made the COMMON behavior obsolescent, so that, eventually, COMMON variables would be implicitly SAVEd as well.

Yes, sorry. I did write a longer post showing where the equivalents were used (or, in the case of vhydrogen, never used!?).

Almost all of them are simply mirrors of the calculations carried out on the equivalent (so, whatever calculation was undertaken on element was then carried out on velement) and then this was outputted to a file (that we don’t use) but never read back in.

I think the equivalences are pointless. Tempted to just remove them and see what breaks but not yet.

To keep the code readable you might want to use pointers (e. g. called hydrogen etc) and I think others have suggested this already, it will be your legacy to the next generation of users of this code.