Declared double precision Function in F90 and return type mismatch error

I am having an issue with a very simple Fortran 90 program. I am calculating three combinations and using a declared Double Precision function to do the calcs and return the results. At present the numbers are quite small, and I have declared the Function as double precision, but I may wish to go to Quad precision in future. I have added some Write(,) statements in my Function to show stages of the calculations as part of the program development and error checking.

The issue I am having is that on compiling the program, I am getting Error: Return type mismatch of function ‘cnk’ at (1) (REAL(8)/REAL(4) for each of the three calls of CNK.

My simple program is:

  PROGRAM CNKtest
  IMPLICIT NONE

  integer, parameter :: dp = selected_real_kind(15,307)
  integer, parameter :: qp = selected_real_kind(33,4931)
  integer :: a,b,c,d,e
  real (kind=dp) :: CNK

  a = 90
  b = 910
  c = 50
  d = 1000
  e = 0

  open(22,file='CNKTest.csv',STATUS='new') 

  write(22,405) (CNK(a,e)*CNK(b,c)/CNK(d,c))*100

405 format (f5.2,‘,’)

  END PROGRAM CNKtest 

  REAL FUNCTION CNK (n,k)      ! Combinations formula
  IMPLICIT NONE  
  integer :: i,n,k             ! n = sample size, k = choices
  integer, parameter :: dp = selected_real_kind(15,307)
  integer, parameter :: qp = selected_real_kind(33,4931)
  real (kind=dp) :: tmp 

  tmp = 1

  write(*,*) n,k

  if (k==0) then                ! k = 0 combination of no choices
  CNK = 1
  else if (k>0) then
   do i = 1,k
    tmp = (REAL(n-(i-1))/REAL(i))*tmp
   end do
  end if

  CNK = tmp 

  write(*,*) tmp,cnk

  END FUNCTION CNK

If I declare CNK as single precision (e.g. real :: CNK), it compiles without error, and calculates ‘tmp’ without any issue, but on the handover to CNK (e.g. CNK = tmp), I get CNK = Infinity and Not a Number ‘NaN’ output to my .csv file - as I expected given single precision is not sufficient for the numbers I am using. I am using the MinGW compiler with simple compile comment -o e.g. CNKTest.f90 -o CNKText.exe.

Any help would be gratefully received.

hello, @BigNish7. Welcome to the Fortran-discourse!!

  1. First i put the function inside a module
  2. declare the function CNK as double precision

Here is the working fortran program:

module testMod

  IMPLICIT NONE  

contains


  !REAL FUNCTION CNK (n,k)      ! Combinations formula
  FUNCTION CNK (n,k)      ! Combinations formula
  IMPLICIT NONE  
  integer :: i,n,k             ! n = sample size, k = choices
  integer, parameter :: dp = selected_real_kind(15,307)
  integer, parameter :: qp = selected_real_kind(33,4931)
  real (kind=dp) :: tmp 
  real (kind=dp) cnk
  tmp = 1

  write(*,*) n,k

  if (k==0) then                ! k = 0 combination of no choices
  CNK = 1
  else if (k>0) then
   do i = 1,k
    tmp = (REAL(n-(i-1))/REAL(i))*tmp
   end do
  end if

  CNK = tmp 

  write(*,*) tmp,cnk

  END FUNCTION CNK

end module testMod


PROGRAM CNKtest
  use testMod
  IMPLICIT NONE

  integer, parameter :: dp = selected_real_kind(15,307)
  integer, parameter :: qp = selected_real_kind(33,4931)
  integer :: a,b,c,d,e
  !real (kind=dp) :: CNK

  a = 90
  b = 910
  c = 50
  d = 1000
  e = 0

  open(22,file='CNKTest.csv',STATUS='new') 

  write(22,405) (CNK(a,e)*CNK(b,c)/CNK(d,c))*100

  405 format (f5.2,',')
END PROGRAM CNKtest 

Output:

(base) ~: gfortran -o test_double.x test_double.f90  && ./test_double.x
          90           0
   1.0000000000000000        1.0000000000000000
         910          50
   7.4725520125964010E+082   7.4725520125964010E+082
        1000          50
   9.4604609459043961E+084   9.4604609459043961E+084

Hopefully, it will provide some insight.

1 Like

Wonderful. Thank you so much for your valuable assistance and your very prompt rely.

You can’t use function CNK in a write statement, as CNK performs I/O

Use
real (kind=dp) :: val
val = (CNK(a,e)*CNK(b,c)/CNK(d,c))*100
write(22,405) val

2 Likes

Replace

    tmp = (REAL(n-(i-1))/REAL(i))*tmp

by

    tmp = (n-(i-1))*tmp/i

or replace REAL by DBLE and observe the effect.

Hi mecej4 - Thank you for your suggestions. I tried both, but neither of them solved my issue unfortunately. I do very much like the more sophisticated equation for calculating combinations which I shall use in the future - thank you!

The ‘module’ based solution from snano does solve my issue nicely, but I am still in the dark as to why my original program was triggering the return type mismatch error.

@BigNish7 ,

Note the “module based solution” provides an explicit interface and declares both the function CNK result and the local variable “tmp” as objects of type REAL with a KIND corresponding to selected_real_kind(15,307). Thus there is no mismatch.

The code in your original post has a “mismatch” in a couple of places:

  1. the real(dp) CNK statement is disagreement with the real function CNK declaration.
  2. :the `CNK = tmp" assignment. The compiler will stop complaining if you reauthor this statement as
CNK = real( tmp, kind=kind(CNK) )

but the issue with #1 will remain.

Note without explicit interface the onus remains on the program author to ensure consistency and that the program response is as expected e.g., with the precision of the computed objects.

2 Likes

Hi JohnCampbell - thank you for your prompt response and suggested edits - they are very much appreciated. However, even ater I made the edits to my program, I still received the ‘return type mismatch of function ‘cnk’ (REAL(8)/REAL(4)’ when trying to compile - I must be missing something, I just at a loss to know what it is. snano’s ‘module’ based solution works nicely, but I would like to know what is behind my issue as it is not working even after your suggested edits. .

Hi FortranFan - thank you for your clear explanation. Is there a way in F90 to fix the mismatch of item 1? Is there any alternative to the REAL FUNCTION declaration to allow higher levels or precision? NOTE - I am not aware of any.

An alternative I am considering is to do the double precision calcs currently in my Write statement within the FUNCTION itself and return the single precision equation value to the main program.

To understand why you have loss of precision and range, you need to learn the rules of Fortran and understand how mixed precision arithmetic works in the language.

In your initial post, you declared CNK with type REAL(dp) in the main program. In contradiction to this, in the body of the function CNK, you declared it as default REAL. The compiler caught this discrepancy because both the subprograms were contained in a single source file. Had the main program and the function been put into separate files, or if you used a compiler with options that did not lead to doing thorough type checking, the discrepancy could have gone undetected.

The intrinsic function REAL returns the single-precision real representation of its integer argument. If you want double-precision you should use DBLE instead.

You clearly have multiple problems with your approach, I only highlighted one that was not mentioned elsewhere !

Are you saying instead of declaring REAL FUNCTION CNK (n,k) , I instead use DBLE FUNCTION CNK (n,k)? If this is correct, I tried it and got an ‘unclassified error’ on compiling. I have likely misunderstood what you were suggesting.

Please consult a Fortran reference book.

@BigNish7 ,

Note the current specification of the Fortran language. per the year 2023 ISO IEC standard revision, does not allow generic resolution of FUNCTIONs 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 factorials 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>
1 Like

Thank you all for considering my issue and providing your responses - I really appreciated it. I learnt FORTRAN 77 back when doing my mechanical engineering degree back in the late 80s and am getting back into it again for pleasure (not work) - trying to get my head around F90 as a starting point - as you can tell I am quite rusty.

1 Like

Many Web pages cover the calculation of _nC_r and naively recommend calculating n!, r! and (n-r)!. To your credit, you did not take that route. You can make your program slightly faster by replacing

   do i = 1,k

by

   do i = 1, min(k, n-k)
1 Like

It will be useful to OP if you can demonstrate how the calculation you claim to be “naive” is indeed so under the practical circumstances likely to be of interest to OP on the processor available to OP now.

@mecej4 said the intrinsic function REAL returns the single-precision real representation of its integer argument. That is true if and only if the optional second argument is omitted, but real(x,dp) returns a real(dp) value of x, which may be integer, real, complex, or a ‘boz’ constant, if dp is a valid real kind.

Yep - love it.

To @BigNish7 and any other reader coming to Fortran afresh or “getting back into it again for pleasure” …

I am rather disappointed with the comment (I quote above) about naiveté but without proper explanation.

Note with many computations around pure mathematics such as with combinations brought up in this thread, the author of a program can choose to follow, depending on the needs and circumstances:

  • either formula translation (or a “blackboard abstraction” pattern)
  • or “clever programming”
  • or a hybrid approach

As long as the program author and the consumer base can constantly make attempts to understand the pros and cons and be on a continuous learning and improvement path, it will help.

For the specific case of combinations brought up here, some food for thought will be to write code for the method as

   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

      ! Elided are any checks

      nCr = 1.0_mp
      ..
  • with formula translation as
   nCr = factorial(n) / factorial(r) / factorial(n-r)
  • or the traditional FORTRANNIC approach that has always held dear aspects of clever programming
      do i = max(n-r, r) + 1, n 
         nCr = nCr * i 
      end do 
      do i = min(n - r, r), 2, -1 
         nCr = nCr / i 
      end do 
  • or a variant of this with array-based support introduced starting Fortran 90:
    nCr = product(Idx(n-r+1:n))/factorial(r)

In my opinion, the key is to keep in mind the processor capabilities, what they are currently and where are they heading.

And to eschew clever programming, unless there is a clear need for it.