Is there a way to specify a function(not type-bounded) result kind based on input argument value(not type)? For example, intrinsic function real(x, kind). This function returns different kind result based on input kind value.
No, it is not possible. But you can come close by passing a mold rather than a kind. A little tedious, but it’s the closest approximation I know of.
Module Myreal_m
Use, intrinsic :: iso_fortran_env, only: real32, real64
Private
Public :: myreal
Interface myreal
Myreal_r32
Myreal_r64
End interface
Contains
Function myreal_r32(x, mold) result(y)
Integer, intent(in) :: x
Real(real32), intent(in) :: mold
Real(real32) :: y
...
End function
Function myreal_r64(x, mold) result(y)
Integer, intent(in) :: x
Real(real64), intent(in) :: mold
Real(real64) :: y
...
End function
End module myreal_m
Not directly, but you can get this effect with an interface having module procedures for the various types. Here is an example:
module twice_mod
implicit none
integer, parameter :: sp = kind(1.0), dp = kind(1.0d0)
interface twice
module procedure twice_r_sp, twice_r_dp
end interface twice
contains
function twice_r_sp(x) result(y)
real(kind=sp), intent(in) :: x
real(kind=sp) :: y
y = 2*x
end function twice_r_sp
!
function twice_r_dp(x) result(y)
real(kind=dp), intent(in) :: x
real(kind=dp) :: y
y = 2*x
end function twice_r_dp
end module twice_mod
!
program main
use twice_mod, only: twice, sp, dp
implicit none
print*,twice(3.1_sp),twice(3.1_dp)
print*,kind(twice(3.1_sp)),kind(twice(3.1_dp))
end program main
! gfortran output:
! 6.19999981 6.2000000000000002
! 4 8
Related thread at Discourse: Fortran function return value polymorphism
Proposition in the J3-Fortran GitHub: Function kind specified by optional input · Issue #91 · j3-fortran/fortran_proposals · GitHub