So the alternative approach illustrated here shows how the example “sum two numbers” can be implemented as “sum up to ten intrinsic scalars” very generically. Of course this simple example
is not too exciting, but it still illustrates something that would take a huge number of procedures if done as a generic; where the number of arguments can vary and the arguments can be of many different types.
module m_anything
use, intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
use, intrinsic :: iso_fortran_env, only : real32, real64, real128
implicit none
private
integer,parameter :: dp=kind(0.0d0)
public anyscalar_to_double
public generic_sum
contains
impure elemental function anyscalar_to_double(valuein) result(d_out)
class(*),intent(in) :: valuein
real(kind=dp) :: d_out
select type(valuein)
type is (integer(kind=int8)); d_out=dble(valuein)
type is (integer(kind=int16)); d_out=dble(valuein)
type is (integer(kind=int32)); d_out=dble(valuein)
type is (integer(kind=int64)); d_out=dble(valuein)
type is (real(kind=real32)); d_out=dble(valuein)
type is (real(kind=real64)); d_out=dble(valuein)
type is (real(kind=real128)); d_out=dble(valuein)
type is (complex); d_out=abs(valuein)
type is (logical); d_out=merge(0.0d0,1.0d0,valuein)
type is (character(len=*)); read(valuein,*) d_out
class default; stop '*anyscalar_to_double* <ERROR> unknown type'
end select
end function anyscalar_to_double
function generic_sum(a,b,c,d,e,f,g,h,i,j) result (dvalue)
class(*),intent(in),optional :: a,b,c,d,e,f,g,h,i,j
doubleprecision :: dvalue
dvalue=0.0d0
if(present(a))dvalue=dvalue+anyscalar_to_double(a)
if(present(b))dvalue=dvalue+anyscalar_to_double(b)
if(present(c))dvalue=dvalue+anyscalar_to_double(c)
if(present(d))dvalue=dvalue+anyscalar_to_double(d)
if(present(e))dvalue=dvalue+anyscalar_to_double(e)
if(present(f))dvalue=dvalue+anyscalar_to_double(f)
if(present(g))dvalue=dvalue+anyscalar_to_double(g)
if(present(h))dvalue=dvalue+anyscalar_to_double(h)
if(present(i))dvalue=dvalue+anyscalar_to_double(i)
if(present(j))dvalue=dvalue+anyscalar_to_double(j)
end function generic_sum
end module m_anything
program demo_anyscalar_to_double
use m_anything, only : gsum=>generic_sum
use, intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
use, intrinsic :: iso_fortran_env, only : real32, real64, real128
implicit none
! call same function with different type and number of scalar input types
write(*,*)gsum(2,3.0,4.0d0,(3.0,4.0))
write(*,*)gsum(1,2,3,4,5,6,7,8,9)
write(*,*)gsum('123',456,.true.,.false.,1>=2,10==5*2)
! something more interesting
if (gsum(1>=2,10==5*2,10>3,3+3==6) < 2) then
write(*,*)'close enough, less than 2 conditions not met'
else
write(*,*)'two or more conditions not met'
endif
end program demo_anyscalar_to_double