Overloading functions with optional arguments

In the “ifthen” proposal that got written up for the Fortran committee, ifthen was specified to be an intrinsic FUNCTION, which pretty much killed the idea immediately.

Can you remove the extra allocation? I believe this is unneeded.

So a complete example would be something like this.

module types
use, intrinsic :: iso_fortran_env, only: real64
type :: FooType
endtype

type :: BarType
endtype

interface FooType
   module procedure foo_create
endinterface

interface BarType
   module procedure bar_create
endinterface

interface fun
   module procedure noarg_fun
   module procedure real64_fun
   module procedure foo_fun
   module procedure bar_fun
endinterface

contains

subroutine noarg_fun()
   print *, 'fun()'
endsubroutine

subroutine real64_fun(num)
   real(real64), intent(in) :: num
   print *, 'fun(real64)', num
endsubroutine

function foo_create() result(constructed)
   type(FooType), allocatable :: constructed
   allocate(constructed)
endfunction

subroutine foo_fun(foo)
   type(FooType), allocatable, intent(in) :: foo
   if(allocated(foo)) then
      print *, 'fun(FooType())'
   else
      print *, 'fun(foo)'
   endif
endsubroutine

function bar_create() result(constructed)
   type(BarType), allocatable :: constructed
   allocate(constructed)
endfunction

subroutine bar_fun(bar)
   type(BarType), allocatable, intent(in) :: bar
   if(allocated(bar)) then
      print *, 'fun(BarType())'
   else
      print *, 'fun(bar)'
   endif
endsubroutine
endmodule types

program test
use, intrinsic :: iso_fortran_env, only: real64
use types
type(FooType), allocatable :: foo ! An unallocated constant
type(BarType), allocatable :: bar ! An unallocated constant
type(FooType), allocatable :: foo1
type(BarType), allocatable :: bar1

foo1 = FooType()
bar1 = BarType()
call fun()           ! No argument
call fun(foo)        ! A FooType argument which is not allocated
call fun(foo1)       ! A FooType argument which is allocated
call fun(bar)        ! A BarType argument which is not allocated
call fun(bar1)       ! A BarType argument which is allocated
call fun(1.0_real64) ! A real(real64)

endprogram test

with the output

fun()
fun(foo)
fun(FooType())
fun(bar)
fun(BarType())
fun(real64) 1.000000000000000

2 Likes

Yes, it’s a dead allocation, the subsequent assignment takes care of it. Better add a deallocate for them at the end (so the code can be copy-pasted into a subroutine).

I wouldn’t normally deallocate an allocatable, I don’t think there is any reason to do it manually in most situations.

You are right, it’s a foible of mine that I have trouble controlling!