Does Fortran have dynamic dispatch?

There is this new post on Julia’s forum that claims Fortran does not have dynamic dispatch. How is “dynamic dispatch” different from “dynamic polymorphism” and if it is different, then how and why Fortran does not have it? Thanks in advance from experts who can shed light on this matter.

1 Like

You’ve a strong point with support toward polymorphism in Fortran. Verbosity and any performance considerations apart, one can argue with polymorphic types and the associated semantics in Fortran, the language steers processors toward implementations involving dynamic dispatch that may call for both early binding as well as late binding, even though none of these terms are part of the official lexicon.

Thus the details and “mileage” may vary from compiler implementation to implementation as to how the tables and symbol lookups are setup, but from a coder’s perspective at least, it will appear the wiring is there:

module animal_m
   type, abstract :: animal_t
   contains
      procedure(IGreet), nopass, deferred :: Greet
   end type
   abstract interface
      subroutine IGreet()
      end subroutine 
   end interface
end module
module activities_with_pet_m
   use animal_m
contains
   subroutine play_with_pet( pet )
      class(animal_t) :: pet
      call pet%Greet() !<-- "dynamic" dispatch but with late binding
   end subroutine 
end module 
module cat_m
   use animal_m
   type, extends(animal_t) :: cat_t
   contains
      procedure, nopass :: Greet => Greet_cat
   end type
contains
   subroutine Greet_cat()
      print *, "Meow"
   end subroutine
end module 
module dog_m
   use animal_m
   type, extends(animal_t) :: dog_t
   contains
      procedure, nopass :: Greet => Greet_dog
   end type
contains
   subroutine Greet_dog()
      print *, "Woof! Woof!"
   end subroutine
end module
   use animal_m
   use activities_with_pet_m 
   use cat_m
   use dog_m 
   class(animal_t), pointer :: mypet
   type(cat_t) :: Julia
   type(dog_t), target :: Lassie
   call Julia%Greet() !<-- "dynamic" dispatch though with possible early binding
   mypet => Lassie
   call play_with_pet( mypet )
end 

C:\Temp>ifort d.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.2.0 > Build 20210228_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.28.29337.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:d.exe
-subsystem:console
d.obj

C:\Temp>d.exe
Meow
Woof! Woof!

3 Likes

Thanks @FortranFan for the example. My understanding is that there are two polymorphism possibilities: static and dynamic. Now, in some cases, it may be clear at compile time what the code intends to do, which leads to early binding (or basically, if I understand it correctly, static polymorphism) like the Julia object scenario in your example code. Whether this happens or not, depends on the compiler. In such a case, the argument presented in the Julia-forum comment about Fortran seems to be inaccurate.

2 Likes

Polymorphism only allows dispatching on 1 argument, also called a single dispatch. Multiple dispatch (what Julia has) allows dispatching based on multiple arguments:

def f(a, b, c)
...

it will compile your function (at runtime I think) depending on the actual types of the arguments that you call it with.

4 Likes

Thanks, @certik, but what is the potential performance (or other types of) benefits of multiple dispatch vs. single dispatch? I see “multiple dispatch” appearing in every discussion of Julia and performance. But I never understood how multiple vs. single dispatch can make code more performant.

2 Likes

I don’t know what the performance benefit is, but I think it simplifies code and allows Julia code to be more interoperable (i.e., work with user types that your library was not initially tested with). So you can write a library that works with single and double precision floats, and then somebody can use your library with interval arithmetic, and things should work.

The Julia people should be able to explain this better. You can ask them at their discourse.

3 Likes

I mentioned verbosity earlier and implied in it was the notion of “syntactic sugar”. I also mentioned performance considerations, I should have instead written productivity considerations and compiler developer time + code developer time + run-time performance being all part of this.

Fortran, with its own legacy and history, tends to use its own terminology that is separate from the computer jargon post the rise of C++. Plus there are inconsistencies in its evolution with its advancing identity as “modern Fortran” as to whether it wants to remain a language with a lower level of abstraction like C or be a true multiparadigm, multipurpose language. Consequently a lot of existing features in the language meet many of the practical criteria of present-day considerations such as multiple dispatch but they always remain arguable because some “purist” can come in and complain that no, the onus here is on the coder and/or the “syntactic sugar” is lacking and therefore Fortran does not support X or Y, etc. a case on hand being “multiple dispatch”. I tend to disagree with this.

But please note when Microsoft implemented in C# the “dynamic” keyword and semantics around 2010 and multiple dispatch with it started getting used in COM-.NET applications (e.g., Microsoft Excel spreadsheet app with managed code applications) i.e., before the official launch of Julia, the “textbook” example of multiple dispatch was that at the Wikipedia page - see here.

One can emulate the example in Fortran, an approach can be as follows:

module SpaceObject_m
   type, abstract :: SpaceObject_t
      integer :: size
   end type
   type, extends(SpaceObject_t) :: Asteroid_t
   end type
   type, extends(SpaceObject_t) :: Spaceship_t
   end type
   generic :: CollideWith => CollideWith_a_a, CollideWith_a_s, CollideWith_s_a, CollideWith_s_s 
contains
   function Collide( x, y ) result(r) !<-- Dynamic, multiple dispatch
      class(SpaceObject_t), intent(in) :: x, y
      character(len=:), allocatable :: r
      if ( (x%size > 100).and.(y%size > 100) ) then
         r = "Big boom!"
      else
         select type ( x )
            type is ( Asteroid_t )
               select type ( y )
                  type is ( Asteroid_t )
                     r = CollideWith(x, y)
                  type is ( Spaceship_t )
                     r = CollideWith(x, y)
                  class default
                     error stop "y unsupported"
               end select
            type is ( Spaceship_t )
               select type ( y )
                  type is ( Asteroid_t )
                     r = CollideWith(x, y)
                  type is ( Spaceship_t )
                     r = CollideWith(x, y)
                  class default
                     error stop "y unsupported"
               end select
            class default
               error stop "x unsupported"
         end select
      end if 
   end function
   function CollideWith_a_a( x, y ) result(r)
      type(Asteroid_t), intent(in) :: x, y
      character(len=:), allocatable :: r
      if ( (x%size < 100).or.(y%size < 100) ) then
         r = "a/a"
      end if
   end function
   function CollideWith_s_s( x, y ) result(r)
      type(Spaceship_t), intent(in) :: x, y
      character(len=:), allocatable :: r
      if ( (x%size < 100).or.(y%size < 100) ) then
         r = "s/s"
      end if
   end function
   function CollideWith_a_s( x, y ) result(r)
      type(Asteroid_t), intent(in) :: x
      type(Spaceship_t), intent(in) :: y
      character(len=:), allocatable :: r
      if ( (x%size < 100).or.(y%size < 100) ) then
         r = "a/s"
      end if
   end function
   function CollideWith_s_a( x, y ) result(r)
      type(Spaceship_t), intent(in) :: x
      type(Asteroid_t), intent(in)  :: y
      character(len=:), allocatable :: r
      if ( (x%size < 100).or.(y%size < 100) ) then
         r = "s/a"
      end if
   end function
end module
   use SpaceObject_m
   print *, Collide( Asteroid_t(101), Spaceship_t(101) )  
   print *, Collide( Asteroid_t(10), Asteroid_t(10) )  
   print *, Collide( Asteroid_t(10), Spaceship_t(10) )  
   print *, Collide( Spaceship_t(101), Spaceship_t(10) )  
   print *, Collide( Spaceship_t(101), Asteroid_t(10) )  
end

Program output:

C:\Temp>ifort p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.2.0 Build 20210228_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.28.29337.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\Temp>p.exe
Big boom!
a/a
a/s
s/s
s/a

Functionally the Fortran program above achieves “multiple dispatch”, but it places the onus on the coder via SELECT TYPE .. and GENERIC statements that in the case of other dynamic languages such as Julia is “under the hood”.

What Microsoft sets up in C# with its MSIL intermediate language toward the JIT compiler via the use of dynamic keywords is rather similar to what a coder might do in Fortran with the SELECT TYPE .. statements you see above:

public static string Collide(SpaceObject x, SpaceObject y) =>
        ((x.Size > 100) && (y.Size > 100)) ?
            "Big boom!" : CollideWith(x as dynamic, y as dynamic);

But then the coders do need to define each of the specific supported functions as they also do in Julia:

   private static string CollideWith(Asteroid x, Asteroid y) => "a/a";
   private static string CollideWith(Asteroid x, Spaceship y) => "a/s";
   private static string CollideWith(Spaceship x, Asteroid y) => "s/a";
   private static string CollideWith(Spaceship x, Spaceship y) => "s/s";

Thus the other argument there is syntactic sugar that allows for certain brevity in library and client codes with other languages that Fortran lacks.

4 Likes

If you are interested, this thread in the Julia discourse discussed those kind of concepts, and all the experts on the Julia side have intervened there:

But dynamic dispatch, in the most strick sense of the term, is being able to choose method at runtime, like this:

julia> struct Cat end
       struct Dog end
       encounter(p1::Dog,p2::Dog) = println("ok")
       encounter(p1::Cat,p2::Cat) = println("ok")
       encounter(p1::Dog,p2::Cat) = println("fight!")
       encounter(p1::Cat,p2::Dog) = encounter(p2,p1)
       function random_encounter()
          p1 = rand([Cat,Dog])
          p2 = rand([Cat,Dog])
          encounter(p1(),p2())
       end
random_encounter (generic function with 1 method)

julia> random_encounter()
ok

julia> random_encounter()
fight!

julia> random_encounter()
ok

That can be handy many times, but should be avoided in performance-critical code, for sure. In Julia it gets confused with:

julia> function known_type_encounter(p1,p2)
          encounter(p1,p2)
       end
known_type_encounter (generic function with 1 method)

julia> p1 = Cat(); p2 = Dog();

julia> known_type_encounter(p1,p2)
fight!

julia> p1 = Cat(); p2 = Cat();

julia> known_type_encounter(p1,p2)
ok

You can use the generic function known_type_encounter for all type combinations, but the function will be specialized for each combination of types at compilation (on the first call).

4 Likes

Thanks for the link. I see a post mentioning “Julia is good at devirtualization” and another comment stating that Julia does multiple dispatches exclusively at runtime. If both are ought to be true, then one concludes that Julia devirtualizes at runtime, which feels something similar to the “early binding” FortranFan mentioned above that happens in Fortran compilers. Still, it is a mystery to me how “multiple dispatch” could lead to faster runtime (for example, compared to static polymorphism or single dispatch). The other possibility is that those Julia programmers who claimed so were not well informed.

1 Like

I updated my post above showing examples in which Julia dispatches at runtime with all that might mean, and an early binding. The performance thing is this, I think. Take this simple code:

julia> f(x,y) = x*y
f (generic function with 1 method)

Call it with two integers, you get this lowered code:

julia> @code_llvm f(1,1)
;  @ REPL[27]:1 within `f'
define i64 @julia_f_417(i64 signext %0, i64 signext %1) {
top:
; ┌ @ int.jl:88 within `*'
   %2 = mul i64 %1, %0
; └
  ret i64 %2
}

Which uses a special method to multiply two integers. Call it with two floats:

julia> @code_llvm f(1.0,1.0)
;  @ REPL[27]:1 within `f'
define double @julia_f_436(double %0, double %1) {
top:
; ┌ @ float.jl:332 within `*'
   %2 = fmul double %0, %1
; └
  ret double %2
}

and it will use a special method to multiply two floats. There is no type-conversion or promotion anywhere. Is simply like if we had written two separate functions in Fortran, one for integers, one for Floats. That sometimes have a performance impact for the final code run (but I don’t believe this is of major importance, the importance of this is the generic programming, not the performance).

2 Likes

I’d say the second one is untrue or misleading depending on one’s definition of runtime. Julia will devirtualize whenever is convenient, but the behaviour will always be that of a runtime dispatch. However, if the types are knowable at compile time, then julia is free to do the devirtualization at compile time instead of a runtime dynamic dispatch.

Julia’s intermediate representation can be thought of as statically typed, but as soon as it hits something that’s not inferrable, instead of reporting an error, it’ll just wait until runtime when the types are concretely known and then invoke the compiler again, resuming where it left off. So dynamic dispatch is basically just a ‘pause’ in the compilation pipeline. But the semantics are always those of a dynamic language.

5 Likes