Is it possible to define an “overloaded” parameter in a module? Specifically, I would like to have two definitions of the constant pi in my program. Consider the following code snippet:
Can I somehow use an interface block that defines a variable pi that encapsulates these two parameters so that the appropriate one to use is automatically selected depending on the context of the expression in which the constant is used? For example, auto-select the appropriate type based on the type of the variable on the left-hand-side of the expression that uses the constant?
example:
use constants, only : pi
real(sp) :: area
real(sp) :: r
area = pi * r**2 ! auto-selects pi_sp
use constants, only : pi
real(dp) :: area
real(dp) :: r
area = pi * r**2 ! auto-selects pi_dp
Thinking about this some more I guess it is not possible, but maybe worth asking if there would be a “best practice” for situations like this one.
I’d suggest defining the value in the highest precision available and letting Fortran’s implicit conversion handle things when you use lower precision. I’m usually against using implicit conversion, but I don’t see the harm here.
when you only need one in a particular procedure you can rename one as in
use constants, only: pi=> pi_sp
or somewhat as suggested above you can declare a local copy using implicit rules as in
use constants, only : pi_dp
real, parameter :: pi=pi_dp
And there are things you can do with ASSOCIATE and BLOCK to rename variables in
a region of code, but unless for some reason you do not want to promote to a double
(maybe passing an expression as an argument or printing a value as list-directed, so without an expicit format) defining PI to be double precision all the time starts
to look pretty appealing
module constants
use iso_fortran_env, only : sp=>real32, dp=>real64
implicit none
real(sp), parameter :: pi_sp = 3.1415926_sp
real(dp), parameter :: pi_dp = 3.14159265358979323846_dp
end module constants
program testit
use constants, only : pi_sp, pi_dp, sp, dp
implicit none
SINGLE: associate (pi=>pi_sp, r=>1.0/3.0_sp)
block
real(kind=sp) :: area
area = pi * r**2 ! auto-selects pi_sp
write(*,*) 'AREA=',area
write(*,*) 'REF= ', 3.1415926 * (1.0/3.0)**2
endblock
end associate SINGLE
DOUBLE: associate (pi=>pi_dp, r=>1.0/3.0_dp)
block
real(kind=dp) :: area
area = pi * r**2 ! auto-selects pi_sp
write(*,*) 'AREA=',area
write(*,*) 'REF= ',3.14159265358979323846d0 * (1.0d0/3.0d0)**2
endblock
end associate DOUBLE
end program testit
This will result in promoting sub-expressions to the “wider” type with more precision, and soon you will be calculating everything at double precision.
In the case where both operands are any of type real or complex with different kind type parameters, the kind type parameter of the expression is that of the operand with the greater decimal precision if the decimal precisions are different;
The closest I can get to the requirements is with generic resolution that requires use to be like “pi(x)” to multiply x by pi, with result kind being the kind of x.