Implementing a procedure of derived type extending abstract type

144 views Asked by At

I want the derived types to have the same behavior, so I want to define an interface to the abstract class. So I wrote my program as follows, but I got a compile error.

How do I fix my program?

PROGRAM main
  IMPLICIT NONE

  TYPE, ABSTRACT :: Point
    REAL :: x, y
  CONTAINS
    PROCEDURE(Imove), DEFERRED :: move
  END TYPE Point
  INTERFACE
    SUBROUTINE Imove(self, d)
      IMPORT Point
      CLASS(Point), INTENT(INOUT) :: self
      REAL, INTENT(IN) :: d
    END SUBROUTINE Imove
  END INTERFACE

  TYPE, EXTENDS(Point) :: Point3d
    REAL :: z
  CONTAINS
    PROCEDURE :: move => Point3d_move
  END TYPE Point3d

  TYPE(Point3d) :: p1

  p1 = Point3d(1.0, 2.0, 3.0)
  p1%move(4.0)
  PRINT *, p1%x, p1%y, p1%z

CONTAINS
  SUBROUTINE Point3d_move(self, d)
    TYPE(Point3d), INTENT(INOUT) :: self
    REAL :: d

    self%x = self%x + d
    self%y = self%y + d
    self%z = self%z + d
  END SUBROUTINE Point3d_move
END PROGRAM main

Environment

  • OS: macOS Catalina
  • Fortran compiler: GNU Fortran (Homebrew GCC 10.2.0) 10.2.0
  • Error: 'point3d_move' must be a module procedure or an external procedure with an explicit interface at (1)
1

There are 1 answers

0
francescalus On

As the error message and several comments say, the procedure to be bound must be either a module procedure or an external procedure with an explicit interface. A procedure internal to a main program is neither of these.

The interface name for a deferred type-bound procedure (here binding move) must be that of an abstract interface or a procedure with an explicit interface (which an internal procedure would have) but there is no additional constraint to where that procedure may be.1

However, the constraint C769 of Fortran 2018 is the one which gives the error message your compiler reports for Point3d_move when implementing.

Moving the derived type definition and related entities (those procedures) to a module should be your approach.

Note that this constraint is not specific to implementing a deferred binding or extending an abstract type. You can see exactly the same error report with the simpler case below.

program main
  implicit none

  type :: Point3d
   contains
     procedure :: move
  end type Point3d

contains

  subroutine move(self)
    class(Point3d) :: self
  end subroutine move
  
end program main

In the case of the question, the interface name of the deferred binding is that of an external procedure with explicit interface, but it is just as valid to use the name of an otherwise useless internal procedure as an interface name.