Clarity on modules and addressing arrays

I have the following module that I have created, called modules.f90, that contains all of the variables and parameters that I know my current program uses across the entire system…

module stellar_values

	implicit none

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

    character(48) :: sfile, ofile, pfile, lfile, filez
    
    integer :: unitz, start_zones, increment_zones
    integer :: iunit, lunit, junit, kunit
    integer :: jrit, nrit, model, n, ng, methd, nprob, nmod
    integer :: nrec, natm, nadd, nsub, iprt, jatm, katm, latm
    integer :: mrec, igrv, massloss, itmin, itmax, iter, itau23
    
    integer :: icv(mtau)
    
    integer, dimension(mh) :: jg, jc 
    integer, dimension(mj) :: iconvect, ienergy
    
    double precision :: zmass, zflux
    double precision :: dflux, xtimod, xcorm, time, dtime, factim, dtmin
    double precision :: dtmax,chgmin,chgmax,change, dlmx, dlmn, dpmx
    double precision :: dpmn, dxmn, dxmx, dzmax, dzmin, dzdt, dmat, atmn
    double precision :: taux, dpat, rlh, crad, cwrk, xh2, ener, arad3, taujk
    double precision :: dtmn, dmix, zmmn, zmmx, rhmn, enorm, zmold, zrold
    double precision :: zlold, rtau23, rpp, rhe3he3, rcno, r3a, r12a, r16a
    double precision :: rcc, rlip, xpd, xpc, xpn, xpo, xpp23
     
    double precision, dimension(10) :: radm, radr
    double precision, dimension(15) :: xba, h1, a
      
    double precision, dimension(mh) :: dg, smin, smax, eps, e, g
      
	double precision, dimension(mj) :: grv, zm, dm, hydrogen, deuterium, helium3, helium4
    double precision, dimension(mj) :: carbon, nitrogen, oxygen, lithium,erest
    double precision, dimension(mj) :: vhydrogen, vdeuterium, vhelium3, vhelium4
    double precision, dimension(mj) :: vcarbon, vnitrogen, voxygen, vlithium, verest
      
	double precision, dimension(mtau) :: tau, ttau, rhotau, ptau, rtau
	double precision, dimension(mtau) :: zmtau, zatg, zradg, ztrug
	    
	double precision, dimension(mh, mh) :: hc, hd, he
	  
    double precision, dimension(mj, me) :: element, velement
      
    double precision, dimension(mj, mh) :: x, vx
	  
    double precision :: ha(mh, 2 * mh + 1), hw(mh, mh + 1, mj)
    double precision :: hx(mh, mh + 1)
	
    double precision :: rhyr(23), thyr(28), auxchyop(23, 28)
    double precision :: rhel(25), thel(32), auxcheop(25, 32)
	
end module

I have tested this slowly and have had success generally with the code, but this was a BIG step, to combine everything into a single block.

Most of the code compiled but when I ran the code, the variables defined within modules.f90 were not holding their values within the calling routine (stelcor.f90, which has, in each subroutine use stellar_values)

Since I have implicit set to none, the compiler is confirming that all variables are now declared in all routines (the code compiles) and if I physically set values within modules.f90 then the values are accessible in all parts of the calling program (stelcor.f90).

Yet, if the calling program sets a value, it is only held within that subroutine, and lost on exiting (despite having save set in all subroutines; and these appearing to be globals).

Equally, arrays are complaining at present, stating that I cannot simply set the array values…

a(1) = 8.9d0

but must use a pointer?

I am compiling the modules.f90 and getting a stellar_values.mod file, as well as a modules.o file, by doing this…

gfortran -c modules.f90

I can then compile the main two routines (dummymain,f90, which uses stelcor.f90) by doing this…

gfortran stelcor.f90 dummymain.f90

I get the resultant a.out file.

Am I wildly wrong? :laughing:

Are you re-declaring the variables in each procedure where you use them? If so, this is creating a new variable, not using the one from the module. Don’t repeat the declarations anywhere.

As a side note, it’s generally considered bad practice to use globally accessible module variables. It makes it much harder to later track where and how the values in your program are created and/or used. I.e. how does the data flow through your program?

No, I am not (the compiler wouldn’t let me anyway).

And, my intention is to move these to become parsed by the subroutines themselves; leaving only the parameters at the end. I need to get there first.

I have mapped out all the subroutines and where the connect, so slowly getting there. :slight_smile:

1 Like

It is not illegal to have a locally declared variable with the same name as a module variable. The local variable will be used in the routine. This probably should be illegal ?
The compiler will let you, but hopefully it will give a warning.

Yes, I got a shed load of warnings on ambiguous variables. Hahaha

This is legal

module answer_m
  integer, parameter :: the_answer = 24
end module

program the_ultimate_question
  use answer_m

  integer :: the_answer

  print *, the_answer ! This is undefined here, so who knows what will be printed
end program

but this is not

module answer_m
  integer, parameter :: the_answer = 24
end module

program the_ultimate_question
  use answer_m, only: the_answer ! cannot explicitly import something with the same name
                                 ! as another entity in this scope

  integer :: the_answer

  print *, the_answer
end program

At least, that’s my understanding. Many compilers will likely be nice enough to warn you about the first one though.

At least in f2018 anything use-associated is assumed declared so the first example should produce an error, not a warning. You can still get into trouble like that with contained procedures and with implicit typing (which is one of the things that makes using IMPLICIT NONE in anything with a USE statement in it critical), especially if the module declares a lot of non-private variables. Of course, using ONLY on the use statement is preferable but is not always convenient when there are a huge number of variables you WANT to import and a few you do not. I have occasionally wished there were something like an EXCEPT option on USE so you could say “import everything except NNN”; but the only way I know to do that is to rename the ones you do not want; like in this little sample where I want a-h but not “the_answer”; but it is either what you list with ONLY or everthing as far as I know. old COMMON block had a block name and a name you had to give the variables local in it, I think it is a good idea to put a lot of constants in a user-defined type instead of as individual names or to use some naming pattern like an unusual prefix or suffix like G_ for any variables I declare public in modules.

module answer_m
  integer, parameter :: the_answer = 24
  integer :: a=1,b=2,c=3,d=4,e=5,f=6,g=7,h=8
end module

program the_ultimate_question
  use :: answer_m , donotwant1=>the_answer

  integer :: the_answer
  the_answer=100

  print *, the_answer ! This is undefined here, so who knows what will be printed
  print *, a,b,c,d,e,f,g,h
end program

Here is an example that actually models how implicit typing (no implicit none) can let something fall through the cracks, which models a user code bug I saw recently, where they did not know why they were getting that “b” had been called 83 times no matter how many times it was called …

  module A
  integer :: i=0 ! count how many times B is called
  integer, parameter :: the_answer=42
end module A

program the_ultimate_question
  use :: A
  write(*,'(*(a))')('=',i=1,80)
  call b()
  call b()
  write(*,'(*(a))')('=',i=1,80)
  write(*,*)'The answer:',the_answer
end program

subroutine b()
use :: A
   i=i+1
   write(*,*)'I=',i
end subroutine b

Now that I think about it you’re right. My usual pattern is to have all use statements at the top of a module (since some compilers seem to have hard to isolate bugs that crop up at random otherwise), and then declaring variables in procedures with the same name is allowed and shadows the variables imported by the use statements. So to correct my examples:

This is legal:

module answer_m
  integer, parameter :: the_answer = 24
end module

program the_ultimate_question
  use answer_m
  call main
contains
  subroutine main
    integer :: the_answer

    print *, the_answer ! This is undefined here, so who knows what will be printed
  end subroutine
end program

but this is not

module answer_m
  integer, parameter :: the_answer = 24
end module

program the_ultimate_question
  use answer_m

  integer :: the_answer ! there's already a variable with this name

  print *, the_answer
end program