Writing a function that accepts any two numbers (any real or any integer)

最后都变了- 提交于 2019-12-24 02:18:08

问题


I have a function that accepts two numbers and I don't care if they are integers or real or 32bits or 64bits. For the example below, I just write it as a simple multiplication. In Fortran 90 you could do this with an interface block, but you'd have to write 16 (!) functions if you wanted to cover all the possible interactions of multiplying two numbers, each of which could be int32, int64, real32, or real64.

With Fortran 2003 you have some other options like class(*) for polymorphism and I found one way to do this by simply converting all the inputs to reals, before multiplying:

! compiled on linux with gfortran 4.8.5

program main

   integer,   target :: i = 2
   real(4),   target :: x = 2.0
   real(8),   target :: y = 2.0
   character, target :: c = 'a'

   print *, multiply(i,x)
   print *, multiply(x,i)
   print *, multiply(i,i)
   print *, multiply(y,y) 
   print *, multiply(c,c)

contains

function multiply(p,q)

   real :: multiply
   class(*) :: p, q

   real :: r, s

   r = 0.0 ; s = 0.0

   select type(p)

      type is (integer(4)) ; r = p
      type is (integer(8)) ; r = p
      type is (real(4)) ;    r = p
      type is (real(8)) ;    r = p

      class default ; print *, "p is not a real or int"

   end select

   select type(q)

      type is (integer(4)) ; s = q
      type is (integer(8)) ; s = q
      type is (real(4)) ;    s = q
      type is (real(8)) ;    s = q

      class default ; print *, "q is not a real or int"

   end select

   multiply = r * s

end function multiply

end program main

This seems like an improvement. At least the amount of code here is linear in the number of types rather than quadratic, but I wonder if there is still a better way to do this? As you can see I still have to write the select type code twice, changing 'r' to 's' and 'p' to 'q'.

I tried to convert the select type blocks into a function but couldn't get that to work. But I am interested in any and all alternatives that can further improve on this. It seems like this would be a common problem but I so far haven't found any general approach that is better than this.

Edit to add: Apparently there are plans to improve Fortran w.r.t. this issue in the future as noted in the comment by @SteveLionel. @roygvib further provides a link to a specific proposal which also does a nice job of explaining the issue: https://j3-fortran.org/doc/year/13/13-236.txt


回答1:


Not a solution for generics, but for "converting the select type blocks into a function", the following code seems to work (which might be useful if some nontrivial conversion is included (?)).

program main
    implicit none
    integer      :: i = 2
    real*4       :: x = 2.0
    real*8       :: y = 2.0
    character(3) :: c = 'abc'

    print *, multiply( i, x )
    print *, multiply( x, i )
    print *, multiply( i, i )
    print *, multiply( y, y )
    print *, multiply( c, c )

contains

function toreal( x ) result( y )
    class(*) :: x
    real :: y

    select type( x )
        type is (integer)      ; y = x
        type is (real(4))      ; y = x
        type is (real(8))      ; y = x
        type is (character(*)) ; y = len(x)
        class default          ; stop "no match for x"
    endselect
end

function multiply( p, q ) result( ans )
    class(*) :: p, q
    real :: ans
    ans = toreal( p ) * toreal( q )
end

end program

! gfortran-8 test.f90 && ./a.out
   4.00000000    
   4.00000000    
   4.00000000    
   4.00000000    
   9.00000000  

Another approach may be just converting the actual arguments to reals (although it may not be useful for more practical purposes...)

program main
    implicit none
    integer   :: i = 2
    real*4    :: x = 2.0
    real*8    :: y = 2.0
    character :: c = 'a'

    print *, multiply( real(i), real(x) )
    print *, multiply( real(x), real(i) )
    print *, multiply( real(i), real(i) )
    print *, multiply( real(y), real(y) )
    ! print *, multiply( real(c), real(c) )  ! error

contains

function multiply( p, q ) result( ans )
    real :: p, q
    real :: ans
    ans = p * q
end

end program



回答2:


Here's an alternate approach using a statically overloaded function via an interface block as implicitly referred to in my question and @roygvib's answer. (I figured it makes sense to have this written explicitly, especially if it someone can improve on it.)

Two advantages of the interface block method are:

  • It's approximately 3x faster (as @roygvib also found, although I don't know exactly how he wrote the function)
  • It only requires Fortran 90 (not Fortran 2003)

The main disadvantage is that you have to write the function multiple times. As noted in the question, in this example you'd have to write the multiplication function 16 times, to handle all combos of 32 & 64 bit reals and ints. It's not that terrible here, with the function being a single line of code, but you can easily see that this is more serious for many realistic use cases.

Below is the code I used to test the interface block method. To keep it relatively concise, I tested only the 4 permutations of 32 bit reals and ints. I re-used the main program to also test the @roygvib code. On my 2015 macbook, it took about 16 seconds (interface block) vs 48 seconds (class(*) method).

Module:

module mult_mod

use, intrinsic :: iso_fortran_env, only: i4 => int32, r4 => real32

interface mult
   module procedure mult_real4_real4
   module procedure mult_int4_real4
   module procedure mult_real4_int4
   module procedure mult_int4_int4
end interface mult

contains

function mult_real4_real4( p, q ) result( ans )
    real(r4) :: p, q
    real(r4) :: ans
    ans = p * q
end function mult_real4_real4

function mult_int4_real4( p, q ) result( ans )
    integer(i4) :: p
    real(r4)    :: q
    real(r4) :: ans
    ans = p * q
end function mult_int4_real4

function mult_real4_int4( p, q ) result( ans )
    real(r4)    :: p
    integer(i4) :: q
    real(r4) :: ans
    ans = p * q
end function mult_real4_int4

function mult_int4_int4( p, q ) result( ans )
    integer(i4) :: p, q
    real(r4) :: ans
    ans = p * q
end function mult_int4_int4

end module mult_mod

Program:

program main

    use mult_mod

    integer(i4) :: i = 2
    real(r4)    :: x = 2.0

    integer(i4) :: i_end = 1e9
    real(r4)    :: result

    do j = 1, i_end

        result = mult( x, x )
        result = mult( x, i )
        result = mult( i, x )
        result = mult( i, i )

    end do

end program main


来源:https://stackoverflow.com/questions/57792982/writing-a-function-that-accepts-any-two-numbers-any-real-or-any-integer

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!