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