Why I can access private module variable in this program?

Well, I am sure tastes will vary, but if something like uc%qp%pi standing for “universal constant, quad precision, PI” does not bother you the closest I think we got was a real version of the little example above … it tries to address some of those very questions :slight_smile:

M_constants
module M_constants
!>
!!##NAME
!!    M_constants(3f) - [M_constants:INTRO] Useful constants
!!
!!##SYNOPSIS
!!
!!    use M_constants,  only : uc
!!
!!       ! real128 constants
!!       uc%qp%pi
!!       uc%qp%gamma
!!       uc%qp%e
!!       uc%qp%golden_ratio
!!       uc%qp%euler
!!
!!       ! real64 constants
!!       uc%dp%pi
!!       uc%dp%gamma
!!       uc%dp%e
!!       uc%dp%golden_ratio
!!       uc%dp%euler
!!
!!       ! real32 constants
!!       uc%sp%pi
!!       uc%sp%gamma
!!       uc%sp%e
!!       uc%sp%golden_ratio
!!       uc%sp%euler
!!
!!    use M_constants,  only : f
!!       ! formats
!!
!!       f%all
!!
!!##DESCRIPTION
!!  Useful universal constants, physical constants, formats, ...
!!
!!
!!  UNIVERSAL CONSTANTS
!!
!!      "e"              The base of the natural logarithm system. "e"
!!                       was named in honor of Euler, but is known as
!!                       Napier's constant.
!!      "euler"
!!      "gamma"          The Euler-Mascheroni constant is often denoted by
!!                       a lower-case Gamma.
!!      "golden_ratio"
!!
!!      "pi"             The ratio of the circumference of a circle to the
!!                       diameter of the circle
!!
!!  PHYSICAL CONSTANTS
!!
!!      "deg_per_rad"
!!      "rad_per_deg"
!!      "c__m_per_sec"   Speed of light in a vacuum
!!      "c__ft_per_sec"  Speed of light in a vacuum
!!
!!##NOTES
!!
!!   Gamma is defined as
!!
!!    Gamma = limit ( M -> Infinity ) ( Sum ( 1 <= N <= M ) 1 / N ) - Log ( M )
!!
!!##EXAMPLE
!!
!!  Sample program:
!!
!!     program test_universal_constants
!!     use M_constants, only : uc, f
!!     ! give a local name to a constant
!!     real,parameter :: e=uc%sp%e ! universal constant, single-precision, e
!!     character(len=*),parameter :: all=f%all
!!
!!     ! use just use it
!!     print f%all, 'gamma=',uc%qp%gamma    ! universal constant, quad-precision, gamma
!!     print all, 'e=',e
!!
!!     ! or rename it with ASSOCIATE
!!     associate (gamma => uc%dp%gamma)
!!        print all,'gamma=',gamma
!!     end associate
!!
!!     end program test_universal_constants
use,intrinsic :: iso_fortran_env, only : real32, real64, real128
use,intrinsic :: iso_fortran_env, only : int8,   int16,  int32,  int64
use,intrinsic :: iso_fortran_env, only : r4 => real32, r8 => real64, r16 => real128
implicit none
private

!!integer, public, parameter :: DP = selected_real_kind(15)

real(kind=real128),parameter :: &

!------------------------!-----------------------------------------------------------------------------
   pi                      = 3.141592653589793238462643383279502884197169399375105820974944592307_real128, &
!------------------------!-----------------------------------------------------------------------------
                         ! The Euler-Mascheroni constant is often denoted by a lower-case Gamma.  Gamma is defined as
                         ! Gamma = limit ( M -> Infinity ) ( Sum ( 1 <= N <= M ) 1 / N ) - Log ( M )
   gamma                   = 0.577215664901532860606512090082402431042_real128,        &
!------------------------!-----------------------------------------------------------------------------
                         ! "e" is the base of the natural logarithm system.
                         ! "e" was named in honor of Euler, but is known as Napier's constant.
   e                       = 2.71828182845904523536028747135266249775724709369995_real128, &
!------------------------!-----------------------------------------------------------------------------
                         ! for two values A+B is to A as A is to B
   Golden_Ratio            = 1.6180339887498948482045868_real128,                      &
!------------------------!-----------------------------------------------------------------------------
   euler                   = 0.577215664901532860606512090082402431042_real128,        &
!------------------------!-----------------------------------------------------------------------------
                         ! velocity of light in a vacuum
   c__m_per_sec            = 2.99792458e+8_real128,                                    & ! m/sec
   c__ft_per_sec           = 9.83571056e+8_real128,                                    & ! ft/sec
!------------------------!-----------------------------------------------------------------------------
   Deg_Per_Rad             = 57.2957795130823208767981548_real128,                     &
   Rad_Per_Deg             = 0.01745329251994329576923691_real128,                     &
   degrees_to_radians      = PI/ 180.0_real128,                                    &
!------------------------!-----------------------------------------------------------------------------

end_of_constants = huge(0.0_real128)

type r128; real(r16) :: pi,gamma,e,golden_ratio,euler; endtype r128
type r64;  real(r8)  :: pi,gamma,e,golden_ratio,euler; endtype r64
type r32;  real(r4)  :: pi,gamma,e,golden_ratio,euler; endtype r32

type rall
   type(r128) :: qp
   type(r64)  :: dp
   type(r32)  :: sp
end type rall

type(rall),parameter,public :: uc=rall( &
& r128(pi=     pi,    gamma=     gamma,    e=     e,    golden_ratio=     golden_ratio,    euler=     euler),      &
&  r64(pi=real(pi,r8),gamma=real(gamma,r8),e=real(e,r8),golden_ratio=real(golden_ratio,r8),euler=real(euler,r8) ), &
&  r32(pi=real(pi,r4),gamma=real(gamma,r4),e=real(e,r4),golden_ratio=real(golden_ratio,r4),euler=real(euler,r4) )  &
& )

type fmt
   character(len=128) :: all='(*(g0,1x))'
end type fmt

type(fmt),public,parameter  :: f=fmt( )

end module M_constants

Fortran standard has had to, in its history including recent, make exceptions about backward compatibility and codes get broken. Fortran 2023 will do so as well. Thus the proposal remains to override backward compatibility considerations for two more aspects, implicit mapping and implied save.

As to the rest of your comments, it comes to the basic question, “For whom Fortran, for what?” Re: things such as wrapper, config file, etc. - been there, tried that and it didn’t work out well at all with large and/or distributed teams spread out globally, particularly when a lot of restrictions from global and/or local IT department started getting enforced. So should the language be for certain groups of users only?

Copy-paste = run out of ideas!

GitHub itself now has over 4,575,000 hits for implicit none, none of which should be needed in a modern language because that should be the default.

It is only the few who seek implicit typing (e.g., implicit double precision(a-h,o-z) or implicit mapping (e.g., implicit integer(i-n), real(a-h,o-z) that should have to type the relevant characters in their code.

Fortran standard instead indulges in a tyranny by the few by making everyone else take some action such as having to type implicit none in each relevant program unit - and which becomes extremely expensive to the community when the small cost has to be borne millions of times - only because the tyrannical few refuse to change.

1 Like

Well, using wrappers has worked on a global scale for decades for us, and I think some of the (perhaps too many) methods for distributing commands available today make it even more viable than it used to be. Anyone can theoretically make a script, package it, and make it globally available. A lot of commands people are using are just scripts written in perl, bash, python, … that they pull with “apt get”, … … … .
fpm(1) can now be installed with 1/2 a dozen different methods, for example. Creating an “F90” command for a few compilers seems feasible. It cannot be distributed, but I have a super-wrapper on my machine where I just enter “ccall FILENAME” and the file can be Fortran, C, C++, a man-page file, a man-page written for txt2man, … and it is build with over 20 libraries available and installed in a compler and platform-specific subdirectory and senses which compilers are available and it has worked for decades without much maintenance so I know from experience it can work; just not so sure what the general appetite for it is versus local wrappers for working groups. fpm(1) and profiles seems like a good vehicle or foundation for something like that; although fpm(1) currently needs you to set up a project directory first. So it could be done in several ways, but distributing a “compiler” command for fpm that you could use like other compiler commands that calls gfortran and/or other compilers with all the strictest options on could prove whether there is a demand for such a feature; like an “F” compiler for fpm(1). That would be more modular than adding alternate profiles to fpm(1); which would be another approach.