An `eye` function that accepts the default integer and another integer kind simultaneously

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.

  1. 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.

  2. On the user’s platform, size(INTEGER_KINDS) > 1. This is not guaranteed by the standard, but not too stringent.

  3. 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).

1 Like

How about setting IK = kind(1) and defining the rest of the kinds like,

module Constants_mod
    use iso_fortran_env, only: IK8 => int8
    use iso_fortran_env, only: IK16 => int16
    use iso_fortran_env, only: IK32 => int32
    use iso_fortran_env, only: IK64 => int64
    integer, parameter :: IK = kind(1)
end module

It may be tempting to use the iso_fortran_env kinds directly everywhere in the codebase. But it will make it difficult for any future changes to the kinds, for example, via selected_int_kind().

Thank you @shahmoradi for the prompt response. Maybe I did not make myself clear enough. My concern is not how to define IK but how to implement eye to support both integer(IK) and integer at the same time without knowing whether the two are the same or not.

The question has been extended a bit, so here is the corresponding extension to my answer. Implementing eye(n) for different kinds of integer for n seems rather unnecessary to me. I would actually implement eye as a subroutine getEye(Eye) rather than a function eye(n)`, for two reasons:

  1. The subroutine version avoids an extra allocation and copy on exit that is typically needed with the function implementation. It is, therefore, likely faster than the function implementation.
  2. The type and kind of the output Eye are directly inferred from the matrix type and kind. With the function implementation, one will have to also pass an extra like argument to specify the kind and type of the output.
1 Like

maybe,

interface eye
   module procedure :: fun_int, fun_ik
end interface eye

1 Like

Thenk you @alozada . But this would be invalid if integer and integer(IK) are the same.

This may be a solution, but I am still interested in the function version, as it can be used in an expression like ‘A = B + sigma*eye(size(B, 1))’.

1 Like

Ideally, one would have to implement the function for different kinds of integers. Then the default kind or any kind associated with IK will be automatically supported because all integer kinds are supported. But, from my perspective, support for different types and kinds of Eye is much more critical than support for different kinds of the integer size of Eye specified by n. The issue of kind of n is completely eliminated if one implements the procedure as a subroutine. Here is a subroutine interface for Eye in the ParaMonte library and a similar function interface.

1 Like

Size does take a kind argument so you can control the kind of your size(x. Kind=)

1 Like

@zaikunzhang , see the example in this thread.

My suggestion will be to think like a library developer and provide generic facilities which make use of options such as integer_kinds array named constant in ISO_FORTRAN_ENV rather than the individual named constants. You can then use some preprocessor, say fypp, to effectively “loop” over such a named constant array in the generic authoring of your function.

While there is no guarantee for anything, a conforming processor can be expected to support a default integer with a decimal exponent range of at least 5; in addition, it is required to support an integer with a minimum decimal exponent of 18 or greater. Thus a library developer knows the size of integer_kinds array will be at least 1; but on modern processors, the size is likely to be 2 or more.

Then on the caller side, no what option is chosen for integer kind - whether using SELECTED_INT_KIND or ISO_FORTRAN_ENV or ISO_C_BINDING (c_int, etc.), you can expect a generic resolution with one specific interface of your eye function that is based on integer_kinds array element value.

2 Likes

Hi @kargl . Thank you for the detailed answer. Does it work if one of int8, int16, int32, and int64 is not supported by the user’s platform?

Thank you @FortranFan for the detailed solution and explanation!

Does this work if on the user’s platform real_kind has only two elements rather than three? Or does the standard ensure that size(real_kind) == 3?

A minor side note is that real_kinds and integer_kinds are F2008 but I hope to have an implementation compatible with F2003.

Thank you @NormanKirkby. Yes, this would completely resolve the problem provided that I am not so lazy and careless to forget to include the kind argument almost every time.

I totally agree. The problem is, which kinds should be included in “different kinds of integers”? Is there a way to figure out which kinds are supported on the user’s platform before the compilation? Thank you.

Thank you @kargl for the explanation. Is there a way to do this data mining automatically so that I include it in my code and the users do not even need to know about it?

It would not be exactly ideal if the users have to modify the code manually, since they may not be capable of doing so.

This has been discussed previously here:

2 Likes

Thank you @certik for pointing this out. According to this nice blog by @everythingfunctional , the answer is “no, there is no automatic way”. The “most automatic” way is to write a program that outputs integer_kinds, and then write some code that acts according to the output. Do I understand it correctly or do I overlook something?

1 Like

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.

  1. 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.

  2. On the user’s platform, size(INTEGER_KINDS) > 1. This is not guaranteed by the standard, but not too stringent.

  3. 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).

1 Like

Here is a standalone generic subroutine and function implementation of the Eye matrix for all kinds of complex and real types (but only with default input integer kind in the function interface. Any non-default integer has really no practical storage or performance advantage from my perspective). The interface and usage doc is the same as getEye() subroutine and genEye function I posted above.

The test can be compiled and run with

gfortran -cpp -DRK64_ENABLED Constants_mod.f90 MatrixDiag_mod.f90 MatrixDiag_mod@Routines_smod.f90 main.f90 -o main.exe
./main.exe

To enable or disable interfaces, one has to set or remove the corresponding preprocessor flags in the compile command,

-DRK128_ENABLED 
-DRK64_ENABLED 
-DRK32_ENABLED 
-DCK128_ENABLED 
-DCK64_ENABLED 
-DCK32_ENABLED 

like -DRK64_ENABLED that is set for the example.

1 Like

I agree, but I do not think we can decide which integer kind will be used by the user.

For example, the latest MATLAB uses 64-bit integer as the default in MEX files even if it is not the default integer. I do not know whether this is reasonable, but it is a fact.

1 Like