I originally had two files (parm.h
and xvar.h
) that were then included throughout two programs I have…
parm.h
IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N)
PARAMETER (MJ=4000,MH=4,ME=9,MTAU=20000)
parameter(SIG=5.67051d-5 , PI=3.14159265359d0)
parameter(GRAV=6.6704d-8 , CC=2.99792458d10)
parameter(HMASS=1.6732d-24)
parameter ( xm_sun = 1.989d33 ) ! Solar Mass (g)
parameter ( r_sun = 6.9599d10 ) ! Solar Radius (cm)
parameter ( xl_sun = 3.83d33 ) ! Solar Luminosity (erg/s)
parameter ( yr = 3.1556736d+7 ) ! yr in sec
parameter ( xmdot_sunyr = 6.30268d25 )! acc. Rate in M_sun/yr
xvar.h
COMMON/ GIC / X(MJ,MH), VX(MJ,MH), GRV(MJ), &
& zM(MJ),dM(MJ),Zmass,Zflux,dflux,xTimod,xCorm, &
& TIME,DTIME,FACTIM,DTMIN,DTMAX,CHGMIN,CHGMAX,CHANGE, &
& dLmx,dLmn,dPmx,dPmn,dXmn,dXmx,dZmax,dZmin,dZdt, &
& dMat,Atmn,TAUx,dPat,RLH,Crad,Cwrk,xH2,ener,Arad3,taujk, &
& dTmn,dMix,zMmn,zMmx,RHmn,Enorm,zMold,zRold,zLold, &
& JRIT,NRIT,MODEL,N,NG,METHD,NPROB,NMOD,kUNIT,jUNIT,NREC,NATM, &
& Nadd,Nsub,IPRT,Jatm,Katm,Latm,MREC,iGRV,massloss
COMMON/ HY /HA(MH,2*MH+1),HW(MH,MH+1,MJ),HX(MH,MH+1), &
& E(MH),G(MH),HC(MH,MH),HD(MH,MH),HE(MH,MH)
COMMON/ CORR /DG(MH),SMIN(MH),SMAX(MH),EPS(MH), &
& JG(MH),JC(MH),ITMIN,ITMAX,ITER
real*8 element(MJ,ME),velement(MJ,ME)
real*8 nitrogen,lithium
COMMON/helium/hydrogen(MJ),deuterium(MJ),helium3(MJ), &
& helium4(MJ),carbon(MJ),nitrogen(MJ),oxygen(MJ), &
& lithium(MJ),erest(MJ), &
& vhydrogen(MJ),vdeuterium(MJ),vhelium3(MJ), &
& vhelium4(MJ),vcarbon(MJ),vnitrogen(MJ),voxygen(MJ), &
& vlithium(MJ),verest(MJ)
equivalence (element,hydrogen) , (velement,vhydrogen)
common/ahycopacity/rhyr(23),thyr(28),auxchyop(23,28)
common/ahecopacity/rhel(25),thel(32),auxcheop(25,32)
COMMON/MIX/ICONVECT(MJ),ienergy(MJ)
character*48 SFILE,OFILE,PFILE,LFILE,FILEZ
integer unitz,start_zones,increment_zones,iunit,lunit
real*8 radM(10),radR(10)
COMMON/ZONES/ SFILE,OFILE,PFILE,LFILE,FILEZ,radM,radR,Nrad, &
& unitz,start_zones,increment_zones,iunit,lunit
I’m not too sure where the lines between the COMMON
blocks should go (with the preceeding common
, subsequent common
or independently - where they could exist within the parm.h
)
However, given the above advice and following some reading around, I have arrived at this…
modules.h
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
real, save :: auxcheop(25,32), rhel(25), thel(32)
end module
module ahycopacity
real save :: auxchyop(23,28), rhyr(23), thyr(28)
end module
module gic
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
real, save :: dg(mh), lithium, nitrogen, radM(10), radR(10), eps(mh), smax(mh), smin(mh)
real, save :: element(mj, me), velement(mj, me)
integer, save :: itmin, itmax, iter, jc(mh), jg(mh)
end module
module helium
real, save :: carbon(mj), deuterium(mj), erest(mj), helium3(mj), helium4(mj), hydrogen(mj), oxygen(mj)
real, save :: vcarbon(mj), vdeuterium(mj), verest(mj), vhelium3(mj), vhelium4(mj), vhydrogen(mj), vlithium(mj)
real, save :: vnitrogen(mj), voxygen(mj)
integer, save :: lithium(mj), nitrogen(mj)
real, pointer, save :: element, velement
real, target, save :: hydrogen, vhydrogen
element => hydrogen
velement => vhydrogen
end module
module hy
real, save :: e(mh), g(mh), ha(mh, 2 * mh + 1), hc(mh, mh), hd(mh, mh), he(mh, mh), hw(mh, mh + 1, mj), hx(mh, mh + 1)
end module
module mix
character(48), save :: filez, lfile, ofile, pfile, sfile
integer, save :: iconvect(mj), ienergy(mj)
real, save :: radM(10), radR(10)
end module
module zones
real, save :: nrad, radm, radr
integer, save :: increment_zones, iunit, lunit, start_zones, unitz
end module
I intend to include this as per the way parm.h
and xvar.h
were included (though I believe someone has stated this is not actually an accepted methodology?), or I can simply place this at the top of each program file and then include the modules as needed.
How close am I?