Note the current specification of the Fortran language. per the year 2023 ISO IEC standard revision, does not allow generic resolution of FUNCTION
s based on the characteristics (e.g., TYPE
, KIND
, RANK
aka TKR) of the RESULT
declaration. Thus in certain ordinary scenarios, the argument(s) of the function has to be used as some form of a “mold” in a “generic” interface.
In your specific case here involving “combinatorics”, the above “mold” trick will not be too “cool”.
Another option can thus be what you are first advised by @snano and tweaking it a bit to compute the numbers using the highest precision supported and making available an explicit interface for the same. The caller can then decide to scale the precision (down) as needed.
Note with modern Fortran, a suggestion will be to perform as much compile-time math as viable with your processor. A silly example is below as illustration where the factorial
s are computed up to a certain arbitrary limit at compile-time:
Click to see code
module kinds_m
integer, parameter :: SP = kind( 1E0 )
integer, parameter :: DP = kind( 1D0 )
integer, parameter :: QP = selected_real_kind( p=2*precision(1.0_dp) )
integer, parameter :: MP = merge( QP, DP, QP > 0 )
end module
module Combinatorics_m
use kinds_m, only : MP
integer, parameter :: MAXN = 100 !<-- arbitrary "maximum"; change as suitable
real(kind=MP), parameter :: Idx(*) = [( real(i, kind=MP), integer :: i = 1, MAXN )]
real(kind=MP), parameter :: Factorial(*) = [( product(Idx(1:j)), integer :: j = 1, MAXN )]
contains
elemental function n_Choose_r( n, r ) result( nCr )
! Argument list
integer, intent(in) :: n
integer, intent(in) :: r
! Function result
real(kind=MP) :: nCr
nCr = 1.0_mp
! Modify the checks below as appropriate
if ( n > MAXN ) then
! Error Handling
error stop "nCr calculation: n must be less than 50."
return
end if
if ( r > n ) then
! Error Handling
error stop "nCr calculion: n must be greater than r"
return
end if
if ( r == 0 ) return
nCr = factorial(n) / factorial(r) / factorial(n-r)
return
end function
end module
use Combinatorics_m, only : n_Choose_r
print *, " Choose(10,2) = ", n_Choose_r( 10, 2 ), "; expected is 45"
print *, " Choose(99,9) = ", n_Choose_r( 99, 9 ), "; expected is 1731030945644."
end
Program using Intel Fortran processor on Windows 10 OS:
C:\temp>ifx /free /standard-semantics p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation. All rights reserved.
-out:p.exe
-subsystem:console
p.obj
C:\temp>p.exe
Choose(10,2) = 45.0000000000000000000000000000000 ; expected is 45
Choose(99,9) = 1731030945644.00000000000000000000 ; expected is 1731030945644
.
C:\temp>