Is it possible to introduce CONSTANT in Fortran?

Perhaps similar questions have been asked before. But I dare to ask again, LOL.

Usually in the code, we read in variables from a file, say a variable called AAA.
So we can use the same code without re-compile and build again each time the variable AAA changes.

Now I am just curious, if this AAA is read in once, and never change in the code. Can we make it a CONSTANT?

I know we have parameter already, but this is for setting a parameter to a fixed number which is known before runtime.

While the CONSTANT is know at runtime. However since AAA is CONSTANT, it can only be set value for only once. So perhaps this can help the compiler to do some runtime optimization?

I mean, you know so then, for example, if I have another variable BBB which is

BBB = sqrt(abs(log(sin(cos(atan(tan(exp(asin(acos(AAA)))**5)))))))

the compiler once know the CONSTANT value of AAA, it knows BBB is also a CONSTANT, and BBB’s value can be calculated when it is first called, and then stored. So no need to repeatedly calculate BBB anymore in the rest of the code.
Things like that may help further speedup the code perhaps.

btw,
is there similar idea in C/C++ or Python or something?

No, but some workarounds are discussed in the thread Immutable declaration

1 Like

One way to do this is:

module constants
   implicit none
   logical, protected, private :: init = .true.
   real, protected, public :: ABC, BBB

   contains
      subroutine set_consts()
      if(init)then
         read (*,*) ABC
         BBB = sqrt(log(abs(ABC)))
         init = .false.
      endif
      return
      end subroutine
end module

program xyz
   use constants
   real :: aa,bb
   !
   bb = 2.3
   call set_consts()
   aa = bb + BBB
   print *,'aa = ',aa
end program
2 Likes

In C, since C99 standard, one can mix declarations and instructions, so it is possible to have

#include <stdio.h>
int main() {
  double x;
  scanf("%lf", &x);
  const double y=x;
  printf("%f\n", y);
  // y += 2.0;  // if uncommented, gives compiler error: assignment of read-only variable ‘y’ 
}
1 Like

The Fortran analog is to associate the constant to an expression:

program main
implicit none
integer, parameter :: dp = kind(1.0d0)
real(kind=dp) :: x
print*,"enter a double"
read (*,*) x
associate (y => (x))
print*,"y =",y
! if line below uncommented, get gfortran error
! Error: 'y' at (1) associated to expression cannot be used in a variable definition context (assignment)
y = 2*y
end associate
end program main

A variable associated to another variable is not a constant, so the following code, with y => x instead of y => (x), compiles:

program main
implicit none
integer, parameter :: dp = kind(1.0d0)
real(kind=dp) :: x
print*,"enter a double"
read (*,*) x
associate (y => x)
print*,"y =",y
y = 2*y
print*,"y =",y
end associate
end program main
4 Likes