I would like to code an eye
function that accepts an integer n
and returns the n by n identity matrix.
In my project, the type of n
can be either integer
or integer(IK)
. Here, IK
is an integer of the parameter
attribute. Imagine, for example, that IK
is defined by a module that looks like the following.
module consts_mod
use, intrinsic :: iso_fortran_env, only : int32
! `IK` is the integer kind used in the project.
! This is **only an example**. It can also be `int16`, `int64`, `1`, `2`, ...
integer, parameter :: IK = int32
end module consts_mod
Why do I need eye
to support both integer
and integer(IK)
? Because I want to use it for both eye(size(x))
and eye(n)
, where the first is the integer
case, while the second can be the integer(IK)
case if n
is declared so.
The difficulty is, I do not know whether integer(IK)
is identical to the default integer
or not. It depends on the user’s platform and the user’s choice that determines IK
. No assumption should be made about IK
except that integer(IK)
is valid on the user’s platform.
In addition, it is undesirable/non-portable to assume what kind of integers the user’s platform supports. Surely, integer
is supported, but int16
, int32
, or int64
may not. Thus we should not implement eye
by simply wrapping eye_16
, eye_32
, and eye_64
in a generic interface, as some of them may be invalid on the user’s platform. You may believe this is too pedantic, but it is indeed not: I do have compilers that do not support all the three aforementioned integer kinds on my laptop.
How should I implement eye
so that it works for both integer
and integer(IK)
simultaneously no matter whether the two kinds are the same or not? I hope the implementation conforms to F2003.
This seems to be a simple question that does not have a simple answer. Mathematicians enjoy discussing this kind of question. Maybe not everyone agrees with this point, but I have not seen a “simple” answer yet … up to 12:09 am UTC Tuesday, 9 November 2021.
Summary (02:40 am UTC Tuesday, 9 November 2021)
Thank everyone for the valuable input!
The best solution I have seen up to now is the following (it is not by me).
module eye_mod
use, intrinsic :: iso_fortran_env, only : INTEGER_KINDS
implicit none
integer, parameter :: IK = INTEGER_KINDS(1) ! Only an example. It can be whatever kind that is valid
integer, parameter, private :: ID = kind(1)
integer, parameter, private :: IOTHER = merge(ID, minval(INTEGER_KINDS, INTEGER_KINDS /= IK), ID /= IK)
interface eye
module procedure eye_ik, eye_iother
end interface eye
contains
function eye_ik(n)
implicit none
integer(IK), intent(in) :: n
real :: eye_ik(n, n)
integer(IK) :: j, k
eye_ik = reshape([1.0, ([(0.0, k=1, n)], 1.0, j=1, n - 1)], shape(eye_ik))
end function
function eye_iother(n)
implicit none
integer(IOTHER), intent(in) :: n
real :: eye_iother(n, n)
integer(IOTHER) :: j, k
eye_iother = reshape([1.0, ([(0.0, k=1, n)], 1.0, j=1, n - 1)], shape(eye_iother))
end function
end module eye_mod
program testeye
use eye_mod
implicit none
print *, eye(3)
print *, eye(3_IK)
end program testeye
It works provided that the following assumptions hold.
-
The user’s platform supports
use, intrinsic :: iso_fortran_env, only : INTEGER_KINDS
. This is F2008 rather than F2003 as I wanted, but it is OK since there is no better solution yet. -
On the user’s platform,
size(INTEGER_KINDS) > 1
. This is not guaranteed by the standard, but not too stringent. -
The user’s platform allows us to use ‘minval’ for initialization. Absoft 21.0 does not allow this. Does the standard say anything about it?
I have tested the code by the following compilers: gfortran (pass), ifort (pass), ifx (pass), nagfor (pass), nvfortran (pass), sunf95 (pass), flang (pass), AOCC flang (fail), absoft Fortran 21.0 (fail), g95 (fail).