How to correctly use type extension and polymorphism?

Hello everyone,
I’m currently stuck on a homework and would appreciate if you could give me a hint on how to solve the problem. The task is to correctly execute the provided test.f90 file, which uses parameterized derived types with a resolution of real32 or real64. The idea is to assign parameterized operators to the derived types that can handle this. However, I do not currently understand what I am doing wrong. I am getting the following errors:

Non-polymorphic passed-object dummy argument of 'point_multiply_scalar_vct_32' at (1) [15,17]
Non-polymorphic passed-object dummy argument of 'point_multiply_scalar_vct_64' at (1) [15,17]
Undefined specific binding 'point_multiply_scalar_vct_64' as target of GENERIC '*' at (1) [19,63]
'point_64' at (1) is not a member of the 'point' structure [78,53]
'point_64' at (1) is not a member of the 'point' structure [79,53]
'point_64' at (1) is not a member of the 'point' structure [80,53]
'point_64' at (1) is not a member of the 'point' structure [86,53]
'point_64' at (1) is not a member of the 'point' structure [87,53]
'point_64' at (1) is not a member of the 'point' structure [88,53]

The provided file is as follows:

program test
    use coords
    use iso_fortran_env

    implicit none
    real(real32)    ::  r4
    real(real64)    ::  r8
    type(point)     ::  p1, p2, p3
    type(pointT)    :: pT1, pT2

    

    !test
    r4  = p1
    r8  = p1
    r4  = p1.dot.p2
    p3  = p1.cros.p2
    p3  = p1 * r4
    p3  = p1 * r8
    p3  = r4 * p1
    p3  = r8 * p1
    p3  = p1 / r4
    p3  = p1 / r8
    r4  = pT1%Tplus(pT2)
    r4  = pT1%Tminus(pT2)

end program test

And I wrote my code in the following module:


module coords
    use iso_fortran_env
    implicit none
  
    private
    public :: point
    
    type point
       real :: x,y,z
     contains
       procedure,private            :: pointplus, pointminus, pointseparation
       procedure,private            :: vecotr_dot, vecotr_cros
       procedure,private            :: point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       procedure,private            :: point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       procedure,private,pass(this) :: absvec_real32, absvec_real64
       generic,public               :: operator(+)          => pointplus
       generic,public               :: operator(-)          => pointminus
       generic,public               :: operator(*)          => point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       generic,public               :: operator(*)          => point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       generic,public               :: operator(.distance.) => pointseparation
       generic,public               :: assignment(=)        => absvec_real32, absvec_real64
       generic,public               :: operator(.dot.)      => vecotr_dot
       generic,public               :: operator(.cros.)     => vecotr_cros
    end type point

    type, extends(point)            :: pointT
      real, PUBLIC            :: T
      contains
      procedure,PRIVATE :: Tplus,Tminus
    end type pointT

    type, extends(point)            :: point_64
      real(real64),PUBLIC   :: x_64, y_64, z_64     
    end type point_64

    interface absvec
      module procedure absvec_real32, absvec_real64
    end interface absvec
    
  contains
    type(point) function Tplus(this,b)   ! for +
      class(pointT),intent(in)      :: this, b
      Tplus%x = this%T + b%T
    end function Tplus

    type(point) function Tminus(this,b)   ! for +
      class(pointT),intent(in)      :: this, b
      Tminus%x = this%T - b%T
    end function Tminus
  
    type(point) function pointplus(this,b)   ! for +
      class(point),intent(in)      :: this, b
      pointplus%x = this%x + b%x
      pointplus%y = this%y + b%y
      pointplus%z = this%z + b%z
    end function pointplus

    type(point) function point_multiply_vct_scalar_32(this,scalar)   ! for +
      class(point),intent(in)      :: this
      real(real32), INTENT(IN)     :: scalar
      point_multiply_vct_scalar_32%x = this%x * scalar
      point_multiply_vct_scalar_32%y = this%y * scalar
      point_multiply_vct_scalar_32%z = this%z * scalar
    end function point_multiply_vct_scalar_32

    type(point) function point_multiply_scalar_vct_32(scalar,this)   ! for +
      class(point),intent(in)      :: this
      real(real32), INTENT(IN)     :: scalar
      point_multiply_scalar_vct_32%x = this%x * scalar
      point_multiply_scalar_vct_32%y = this%y * scalar
      point_multiply_scalar_vct_32%z = this%z * scalar
    end function point_multiply_scalar_vct_32

    type(point_64) function point_multiply_vct_scalar_64(this,scalar)   ! for +
      class(point),intent(in)      :: this
      real(real64), INTENT(IN)     :: scalar
      point_multiply_vct_scalar_64%x = this%point_64%x_64 * scalar
      point_multiply_vct_scalar_64%y = this%point_64%y_64 * scalar
      point_multiply_vct_scalar_64%z = this%point_64%z_64 * scalar
    end function point_multiply_vct_scalar_64

    type(point) function point_multiply_scalar_vct_64(scalar,this)   ! for +
      class(point),intent(in)      :: this
      real(real64), INTENT(IN)     :: scalar
      point_multiply_scalar_vct_64%x = this%point_64%x_64 * scalar
      point_multiply_scalar_vct_64%y = this%point_64%y_64 * scalar
      point_multiply_scalar_vct_64%z = this%point_64%z_64 * scalar
    end function point_multiply_scalar_vct_64

    type(point) function pointminus(this,b)  !  for -
      class(point),intent(in):: this, b

      pointminus%x = this%x - b%x
      pointminus%y = this%y - b%y
      pointminus%z = this%z - b%z
    end function pointminus
  
    real function pointseparation(this,b) ! for .distance.
      class(point),intent(in)   :: this,b

      pointseparation = sqrt(  &
           (this%x-b%x)**2+(this%y-b%y)**2+(this%z-b%z)**2)
    end function pointseparation
  
    subroutine absvec_real64(a,this)  ! for = (distance
      real(real64),intent(out)  :: a     !  from origin)
      class(point),intent(in)   :: this
      a = sqrt(this%x**2+this%y**2+this%z**2)
    end subroutine absvec_real64

    subroutine absvec_real32(a,this)  ! for = (distance
      real(real32),intent(out)  :: a     !  from origin)
      class(point),intent(in)   :: this
      a = sqrt(this%x**2 + this%y**2 + this%z**2)
    end subroutine absvec_real32

    real function vecotr_dot(this,b) ! for .distance.
      class(point),intent(in)   :: this,b
      vecotr_dot = (this%x*b%x)+(this%y*b%y)+(this%z*b%z)
    end function vecotr_dot

    type(point) function vecotr_cros(this,b)  !  for -
      class(point),intent(in):: this, b

      vecotr_cros%x = this%y * b%z - this%z * b%y
      vecotr_cros%y = this%z * b%x - this%x * b%z
      vecotr_cros%z = this%x * b%y - this%y * b%x
    end function vecotr_cros
    
  end module coords

So far I have not been able to resolve and understand these error messages. Could you maybe help me to accomplish this? I would be very grateful for any help.

Best regards,
fidu13

1 Like

Welcome to the Fortran discourse!

The thing you need to understand about these error messages is that they are about the type/class point. If you later define another type, the compiler cannot automatically determine that you mean that other type. For instance: the fields for point_64, x_64, y64 and z_64, might also appear in a type/class “point_double_precision” and be declared as character string of length 64 (completely arbitrary example :slight_smile:). So, how would the compiler know what you mean?

Instead you need to tell it what you mean, for instance via the select type construct:


    type(point_64) function point_multiply_vct_scalar_64(this,scalar)   ! for +
      class(point),intent(in)      :: this
      real(real64), INTENT(IN)     :: scalar

      select type (this)
          class is (point_64)
              point_multiply_vct_scalar_64%x = this%x_64 * scalar
              point_multiply_vct_scalar_64%y = this%y_64 * scalar
              point_multiply_vct_scalar_64%z = this%z_64 * scalar
      end select
    end function point_multiply_vct_scalar_64

The point_64 component you have is not needed, although it works because that allows you to access parent components.

The “select type” tells the compiler to “cast” the incoming argument “this” into a point_64 object. You could use that to join this overloaded routine with the 32-bits variant.

2 Likes

Just out of curiosity I am asking - can I know in which institute this homework has been given? As far as I know hardly anybody is teaching modern Fortran right now. It is nice to see that such modern features are being taught and assignments are being given on them.

Given the description of the assignment, which is to use PDT, I think you are aiming for a derived type like this:

type :: point(point_kind)
  integer, kind :: point_kind
  real(point_kind) :: x, y, z
contains
  ! ...
end type

In your current solution you are using inheritance, meaning an instance of type(point_64) will have members x, y, z of type real and additionally members x_64, y_64, z_64.

There’s an introduction to PDT available here: Parameterized derived types in Fortran - introduction | QMUL ITS Research Blog

With PDT you can also achieve static polymorphism, where the resolution of operators will be done at compile time (as far as your point objects are not given the allocatable attribute).

2 Likes

Dear Arjen
First of all, thank you for the warm welcome. And also for the help and clarification. I have now tried to implement your suggestion and I receive a warning about a possible value conversion from Real(4) to Real(8) of the value%x and so on. Also I still get the errors in line 15 and 19:

Non-polymorphic passed-object dummy argument of 'point_multiply_scalar_vct_32' at (1) [15,17]
Non-polymorphic passed-object dummy argument of 'point_multiply_scalar_vct_64' at (1) [15,17]
Undefined specific binding 'point_multiply_scalar_vct_64' as target of GENERIC '*' at (1) [19,63]

How can resolve them? And how can I make sure that no value conversion is happening?

Dear Ashok
Yes sure. The assignment was given in the Swiss Federal Institute of Technology and it is a introduction in numerical modelling using fortran. I hope this helps :slight_smile:

2 Likes

Thank you very much for your reply. I actually tried this approach but received a bunch of error messages. I tried to implement it as follows:

    type point(k)
      integer, kind :: k = kind(0.)
      real(kind=k) :: x,y,z
     contains
       procedure,private            :: pointplus, pointminus, pointseparation
       procedure,private            :: vecotr_dot, vecotr_cros
       procedure,private            :: point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       procedure,private            :: point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       procedure,private,pass(this) :: absvec_real32, absvec_real64
       generic,public               :: operator(+)          => pointplus
       generic,public               :: operator(-)          => pointminus
       generic,public               :: operator(*)          => point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       generic,public               :: operator(*)          => point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       generic,public               :: operator(.distance.) => pointseparation
       generic,public               :: assignment(=)        => absvec_real32, absvec_real64
       generic,public               :: operator(.dot.)      => vecotr_dot
       generic,public               :: operator(.cros.)     => vecotr_cros
    end type point

However I get quite a lot errors using the “integer, kind :: k = kind(0.)” statement:

Unclassifiable statement at (1) [10,5]  ->  type point(k)
Invalid character in name at (1) [11,15] -> integer, kind :: k = kind(0.)
Symbol 'k' at (1) has no IMPLICIT type [12,18] -> real(kind=k) :: x,y,z

What is my mistake here and how can I avoid it? Or did I misunderstandsomething?

Can you post the code that the compiler is complaining about? In my copy lines 15 and 19 are very different from yours it seems :slight_smile:

That is located in Zürich? (The team of Tiziano Müller, perhaps?)

Yes sure. y compiler gives the following error:

module_cords.f90:10:4:

     type point(k)
    1
Error: Unclassifiable statement at (1)
module_cords.f90:11:14:

       integer, kind :: k = kind(0.)
              1
Error: Invalid character in name at (1)
module_cords.f90:12:17:

       real(kind=k) :: x,y,z
                 1
Error: Symbol ‘k’ at (1) has no IMPLICIT type
module_cords.f90:14:7:

        procedure,private            :: pointplus, pointminus, pointseparation
       1
Error: Unclassifiable statement at (1)
module_cords.f90:15:7:

        procedure,private            :: vecotr_dot, vecotr_cros
       1
Error: Unclassifiable statement at (1)
module_cords.f90:16:7:

        procedure,private            :: point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       1
Error: Unclassifiable statement at (1)
module_cords.f90:17:7:

        procedure,private            :: point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       1
Error: Unclassifiable statement at (1)
module_cords.f90:18:7:

        procedure,private,pass(this) :: absvec_real32, absvec_real64
       1
Error: Unclassifiable statement at (1)
module_cords.f90:19:7:

        generic,public               :: operator(+)          => pointplus
       1
Error: Unclassifiable statement at (1)
module_cords.f90:20:7:

        generic,public               :: operator(-)          => pointminus
       1
Error: Unclassifiable statement at (1)
module_cords.f90:21:7:

        generic,public               :: operator(*)          => point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       1
Error: Unclassifiable statement at (1)
module_cords.f90:22:7:

        generic,public               :: operator(*)          => point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       1
Error: Unclassifiable statement at (1)
module_cords.f90:23:7:

        generic,public               :: operator(.distance.) => pointseparation
       1
Error: Unclassifiable statement at (1)
module_cords.f90:24:7:

        generic,public               :: assignment(=)        => absvec_real32, absvec_real64
       1
Error: Unclassifiable statement at (1)
module_cords.f90:25:7:

        generic,public               :: operator(.dot.)      => vecotr_dot
       1
Error: Unclassifiable statement at (1)
module_cords.f90:26:7:

        generic,public               :: operator(.cros.)     => vecotr_cros
       1
Error: Unclassifiable statement at (1)
module_cords.f90:27:7:

     end type point
       1
Error: Expecting END MODULE statement at (1)
module_cords.f90:29:24:

     type, extends(point)            :: pointT
                        1
Error: Symbol ‘point’ at (1) has not been previously defined
module_cords.f90:30:18:

       real, PUBLIC            :: T
                  1
Error: PUBLIC attribute at (1) is not allowed outside of the specification part of a module
module_cords.f90:31:14:

       contains
              1
Error: Unexpected CONTAINS statement in CONTAINS section at (1)
module_cords.f90:32:6:

       procedure,PRIVATE :: Tplus,Tminus
      1
Error: Unclassifiable statement at (1)
module_cords.f90:33:7:

     end type pointT
       1
Error: Expecting END MODULE statement at (1)
module_cords.f90:35:24:

     type, extends(point)            :: point_64
                        1
Error: Symbol ‘point’ at (1) has not been previously defined
module_cords.f90:36:25:

       real(real64),PUBLIC   :: x_64, y_64, z_64
                         1
Error: PUBLIC attribute at (1) is not allowed outside of the specification part of a module
module_cords.f90:37:7:

     end type point_64
       1
Error: Expecting END MODULE statement at (1)
module_cords.f90:39:20:

     interface absvec
                    1
Error: Unexpected INTERFACE statement in CONTAINS section at (1)
module_cords.f90:40:22:

       module procedure absvec_real32, absvec_real64
                      1
Error: MODULE PROCEDURE at (1) must be in a generic module interface
module_cords.f90:41:7:

     end interface absvec
       1
Error: Expecting END MODULE statement at (1)
module_cords.f90:43:10:

   contains
          1
Error: Unexpected CONTAINS statement in CONTAINS section at (1)
module_cords.f90:45:19:

       class(pointT),intent(in)      :: this, b
                   1
Error: Derived type ‘pointt’ at (1) is being used before it is defined
module_cords.f90:46:11:

       Tplus%x = this%T + b%T
           1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:50:19:

       class(pointT),intent(in)      :: this, b
                   1
Error: Derived type ‘pointt’ at (1) is being used before it is defined
module_cords.f90:51:12:

       Tminus%x = this%T - b%T
            1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:55:18:

       class(point),intent(in)      :: this, b
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:56:15:

       pointplus%x = this%x + b%x
               1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:57:15:

       pointplus%y = this%y + b%y
               1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:58:15:

       pointplus%z = this%z + b%z
               1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:62:18:

       class(point),intent(in)      :: this
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:64:34:

       point_multiply_vct_scalar_32%x = this%x * scalar
                                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:65:34:

       point_multiply_vct_scalar_32%y = this%y * scalar
                                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:66:34:

       point_multiply_vct_scalar_32%z = this%z * scalar
                                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:70:18:

       class(point),intent(in)      :: this
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:72:34:

       point_multiply_scalar_vct_32%x = this%x * scalar
                                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:73:34:

       point_multiply_scalar_vct_32%y = this%y * scalar
                                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:74:34:

       point_multiply_scalar_vct_32%z = this%z * scalar
                                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:78:18:

       class(point),intent(in)      :: this
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:77:4:

     type(point_64) function point_multiply_vct_scalar_64(this,scalar)   ! for +
    1
Error: The type for function ‘point_multiply_vct_scalar_64’ at (1) is not accessible
module_cords.f90:77:4:

     type(point_64) function point_multiply_vct_scalar_64(this,scalar)   ! for +
    1
Error: Function result ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:82:20:

           class is (point_64)
                    1
Error: Syntax error in CLASS IS specification at (1)
module_cords.f90:83:43:

               point_multiply_vct_scalar_64%x = this%x_64 * scalar
                                           1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:84:43:

               point_multiply_vct_scalar_64%y = this%y_64 * scalar
                                           1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:85:43:

               point_multiply_vct_scalar_64%z = this%z_64 * scalar
                                           1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:87:43:

               point_multiply_vct_scalar_64%x = this%x * scalar
                                           1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:88:43:

               point_multiply_vct_scalar_64%y = this%y * scalar
                                           1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:89:43:

               point_multiply_vct_scalar_64%z = this%z * scalar
                                           1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:95:18:

       class(point),intent(in)      :: this
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:99:20:

           class is (point_64)
                    1
Error: Syntax error in CLASS IS specification at (1)
module_cords.f90:100:40:

             point_multiply_scalar_vct_64%x = this%x_64 * scalar
                                        1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:101:40:

             point_multiply_scalar_vct_64%y = this%y_64 * scalar
                                        1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:102:40:

             point_multiply_scalar_vct_64%z = this%z_64 * scalar
                                        1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:107:18:

       class(point),intent(in):: this, b
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:109:16:

       pointminus%x = this%x - b%x
                1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:110:16:

       pointminus%y = this%y - b%y
                1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:111:16:

       pointminus%z = this%z - b%z
                1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:115:18:

       class(point),intent(in)   :: this,b
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:118:17:

            (this%x-b%x)**2+(this%y-b%y)**2+(this%z-b%z)**2)
                 1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:123:18:

       class(point),intent(in)   :: this
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:124:20:

       a = sqrt(this%x**2+this%y**2+this%z**2)
                    1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:129:18:

       class(point),intent(in)   :: this
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:130:20:

       a = sqrt(this%x**2 + this%y**2 + this%z**2)
                    1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:134:18:

       class(point),intent(in)   :: this,b
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:135:25:

       vecotr_dot = (this%x*b%x)+(this%y*b%y)+(this%z*b%z)
                         1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:139:18:

       class(point),intent(in):: this, b
                  1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:141:17:

       vecotr_cros%x = this%y * b%z - this%z * b%y
                 1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:142:17:

       vecotr_cros%y = this%z * b%x - this%x * b%z
                 1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:143:17:

       vecotr_cros%z = this%x * b%y - this%y * b%x
                 1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:127:35:

     subroutine absvec_real32(a,this)  ! for = (distance
                                   1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:121:35:

     subroutine absvec_real64(a,this)  ! for = (distance
                                   1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:69:65:

     type(point) function point_multiply_scalar_vct_32(scalar,this)   ! for +
                                                                 1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:94:65:

     type(point) function point_multiply_scalar_vct_64(scalar,this)   ! for +
                                                                 1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:61:58:

     type(point) function point_multiply_vct_scalar_32(this,scalar)   ! for +
                                                          1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:77:61:

     type(point_64) function point_multiply_vct_scalar_64(this,scalar)   ! for +
                                                             1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:106:40:

     type(point) function pointminus(this,b)  !  for -
                                        1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:106:42:

     type(point) function pointminus(this,b)  !  for -
                                          1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:54:39:

     type(point) function pointplus(this,b)   ! for +
                                       1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:54:41:

     type(point) function pointplus(this,b)   ! for +
                                         1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:114:38:

     real function pointseparation(this,b) ! for .distance.
                                      1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:114:40:

     real function pointseparation(this,b) ! for .distance.
                                        1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:49:36:

     type(point) function Tminus(this,b)   ! for +
                                    1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:49:38:

     type(point) function Tminus(this,b)   ! for +
                                      1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:44:35:

     type(point) function Tplus(this,b)   ! for +
                                   1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:44:37:

     type(point) function Tplus(this,b)   ! for +
                                     1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:138:41:

     type(point) function vecotr_cros(this,b)  !  for -
                                         1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:138:43:

     type(point) function vecotr_cros(this,b)  !  for -
                                           1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:133:33:

     real function vecotr_dot(this,b) ! for .distance.
                                 1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:133:35:

     real function vecotr_dot(this,b) ! for .distance.
                                   1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:69:53:

     type(point) function point_multiply_scalar_vct_32(scalar,this)   ! for +
                                                     1
Error: The derived type ‘point_multiply_scalar_vct_32’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:94:53:

     type(point) function point_multiply_scalar_vct_64(scalar,this)   ! for +
                                                     1
Error: The derived type ‘point_multiply_scalar_vct_64’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:61:53:

     type(point) function point_multiply_vct_scalar_32(this,scalar)   ! for +
                                                     1
Error: The derived type ‘point_multiply_vct_scalar_32’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:106:35:

     type(point) function pointminus(this,b)  !  for -
                                   1
Error: The derived type ‘pointminus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:54:34:

     type(point) function pointplus(this,b)   ! for +
                                  1
Error: The derived type ‘pointplus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:49:31:

     type(point) function Tminus(this,b)   ! for +
                               1
Error: The derived type ‘tminus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:44:30:

     type(point) function Tplus(this,b)   ! for +
                              1
Error: The derived type ‘tplus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:138:36:

     type(point) function vecotr_cros(this,b)  !  for -
                                    1
Error: The derived type ‘vecotr_cros’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:138:36:

     type(point) function vecotr_cros(this,b)  !  for -
                                    1
Error: Function ‘vecotr_cros’ at (1) has no IMPLICIT type
module_cords.f90:106:35:

     type(point) function pointminus(this,b)  !  for -
                                   1
Error: Function ‘pointminus’ at (1) has no IMPLICIT type
module_cords.f90:94:53:

     type(point) function point_multiply_scalar_vct_64(scalar,this)   ! for +
                                                     1
Error: Function ‘point_multiply_scalar_vct_64’ at (1) has no IMPLICIT type
module_cords.f90:69:53:

     type(point) function point_multiply_scalar_vct_32(scalar,this)   ! for +
                                                     1
Error: Function ‘point_multiply_scalar_vct_32’ at (1) has no IMPLICIT type
module_cords.f90:61:53:

     type(point) function point_multiply_vct_scalar_32(this,scalar)   ! for +
                                                     1
Error: Function ‘point_multiply_vct_scalar_32’ at (1) has no IMPLICIT type
module_cords.f90:54:34:

     type(point) function pointplus(this,b)   ! for +
                                  1
Error: Function ‘pointplus’ at (1) has no IMPLICIT type
module_cords.f90:49:31:

     type(point) function Tminus(this,b)   ! for +
                               1
Error: Function ‘tminus’ at (1) has no IMPLICIT type
module_cords.f90:44:30:

     type(point) function Tplus(this,b)   ! for +
                              1
Error: Function ‘tplus’ at (1) has no IMPLICIT type
module_cords.f90:98:24:

       select type (this)
                        1
Error: Selector shall be polymorphic in SELECT TYPE statement at (1)
module_cords.f90:81:24:

       select type (this)
                        1
Error: Selector shall be polymorphic in SELECT TYPE statement at (1)
exercise_10_1.f90:2:8:

     use coords
        1

And my module looks as follows:


module coords
    use iso_fortran_env
    implicit none
  
    private
    public :: point


    type point(k)
      integer, kind :: k = kind(0.)
      real(kind=k) :: x,y,z
     contains
       procedure,private            :: pointplus, pointminus, pointseparation
       procedure,private            :: vecotr_dot, vecotr_cros
       procedure,private            :: point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       procedure,private            :: point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       procedure,private,pass(this) :: absvec_real32, absvec_real64
       generic,public               :: operator(+)          => pointplus
       generic,public               :: operator(-)          => pointminus
       generic,public               :: operator(*)          => point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
       generic,public               :: operator(*)          => point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
       generic,public               :: operator(.distance.) => pointseparation
       generic,public               :: assignment(=)        => absvec_real32, absvec_real64
       generic,public               :: operator(.dot.)      => vecotr_dot
       generic,public               :: operator(.cros.)     => vecotr_cros
    end type point

    type, extends(point)            :: pointT
      real, PUBLIC            :: T
      contains
      procedure,PRIVATE :: Tplus,Tminus
    end type pointT

    type, extends(point)            :: point_64
      real(real64),PUBLIC   :: x_64, y_64, z_64     
    end type point_64

    interface absvec
      module procedure absvec_real32, absvec_real64
    end interface absvec
    
  contains
    type(point) function Tplus(this,b)   ! for +
      class(pointT),intent(in)      :: this, b
      Tplus%x = this%T + b%T
    end function Tplus

    type(point) function Tminus(this,b)   ! for +
      class(pointT),intent(in)      :: this, b
      Tminus%x = this%T - b%T
    end function Tminus
  
    type(point) function pointplus(this,b)   ! for +
      class(point),intent(in)      :: this, b
      pointplus%x = this%x + b%x
      pointplus%y = this%y + b%y
      pointplus%z = this%z + b%z
    end function pointplus

    type(point) function point_multiply_vct_scalar_32(this,scalar)   ! for +
      class(point),intent(in)      :: this
      real(real32), INTENT(IN)     :: scalar
      point_multiply_vct_scalar_32%x = this%x * scalar
      point_multiply_vct_scalar_32%y = this%y * scalar
      point_multiply_vct_scalar_32%z = this%z * scalar
    end function point_multiply_vct_scalar_32

    type(point) function point_multiply_scalar_vct_32(scalar,this)   ! for +
      class(point),intent(in)      :: this
      real(real32), INTENT(IN)     :: scalar
      point_multiply_scalar_vct_32%x = this%x * scalar
      point_multiply_scalar_vct_32%y = this%y * scalar
      point_multiply_scalar_vct_32%z = this%z * scalar
    end function point_multiply_scalar_vct_32

    type(point_64) function point_multiply_vct_scalar_64(this,scalar)   ! for +
      class(point),intent(in)      :: this
      real(real64), INTENT(IN)     :: scalar

      select type (this)
          class is (point_64)
              point_multiply_vct_scalar_64%x = this%x_64 * scalar
              point_multiply_vct_scalar_64%y = this%y_64 * scalar
              point_multiply_vct_scalar_64%z = this%z_64 * scalar
          class is (point)
              point_multiply_vct_scalar_64%x = this%x * scalar
              point_multiply_vct_scalar_64%y = this%y * scalar
              point_multiply_vct_scalar_64%z = this%z * scalar
      end select

    end function point_multiply_vct_scalar_64

    type(point) function point_multiply_scalar_vct_64(scalar,this)   ! for +
      class(point),intent(in)      :: this
      real(real64), INTENT(IN)     :: scalar

      select type (this)
          class is (point_64)
            point_multiply_scalar_vct_64%x = this%x_64 * scalar
            point_multiply_scalar_vct_64%y = this%y_64 * scalar
            point_multiply_scalar_vct_64%z = this%z_64 * scalar
      end select
    end function point_multiply_scalar_vct_64

    type(point) function pointminus(this,b)  !  for -
      class(point),intent(in):: this, b

      pointminus%x = this%x - b%x
      pointminus%y = this%y - b%y
      pointminus%z = this%z - b%z
    end function pointminus
  
    real function pointseparation(this,b) ! for .distance.
      class(point),intent(in)   :: this,b

      pointseparation = sqrt(  &
           (this%x-b%x)**2+(this%y-b%y)**2+(this%z-b%z)**2)
    end function pointseparation
  
    subroutine absvec_real64(a,this)  ! for = (distance
      real(real64),intent(out)  :: a     !  from origin)
      class(point),intent(in)   :: this
      a = sqrt(this%x**2+this%y**2+this%z**2)
    end subroutine absvec_real64

    subroutine absvec_real32(a,this)  ! for = (distance
      real(real32),intent(out)  :: a     !  from origin)
      class(point),intent(in)   :: this
      a = sqrt(this%x**2 + this%y**2 + this%z**2)
    end subroutine absvec_real32

    real function vecotr_dot(this,b) ! for .distance.
      class(point),intent(in)   :: this,b
      vecotr_dot = (this%x*b%x)+(this%y*b%y)+(this%z*b%z)
    end function vecotr_dot

    type(point) function vecotr_cros(this,b)  !  for -
      class(point),intent(in):: this, b

      vecotr_cros%x = this%y * b%z - this%z * b%y
      vecotr_cros%y = this%z * b%x - this%x * b%z
      vecotr_cros%z = this%x * b%y - this%y * b%x
    end function vecotr_cros
    
  end module coords

I am not quite sure to be honest. The lecture is offered by Professor Dr. Paul Tackley.

Btw, which version of compiler are you using?

    type point(k)
      integer, kind :: k = kind(0.)
      real(kind=k) :: x,y,z
    end type point

With gfortran v10.3 this derived type gets compiled fine. The first error occurs in line 17 for the member method absvec.

(Maybe with an older version, the :: symbol is required between type and point(k)?)

1 Like

I have currently this gfortran compiler installed:

GNU Fortran (Ubuntu 7.5.0-3ubuntu1~18.04) 7.5.0
Copyright (C) 2017 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

I also tried to put the :: symbol between the type and point(k) with no avail.

@fidu13 ,

Welcome to the forum and all the very best with your studies.

Will it be possible to share what Fortran study material do you use for this class that has this homework assignment? Toward such material, I suggest you complement them with references such as the following unless these are already included for you:

  1. Fortran for Scientists and Engineers by Chapman
  2. Numerical Computing with Modern Fortran by Hanson and Hopkins

With the code posted in your original post, start by looking into PASS attribute connected with the so-called “passed-object dummy argument”, the Fortran equivalent to this/me in object-oriented programming languages. For example, see this online reference.

Also, if you can, try to use the latest Intel oneAPI IFORT compiler in conjunction with the one you are using which I presume is gfortran(?). Intel oneAPI HPC toolkit, which includes IFORT, is currently free for anyone to use.

The reason for me to suggest IFORT is your statement, " The idea is to assign parameterized operators to the derived types that can handle this." Others have pointed you to parameterized derived types (PDTs) toward this. But gfortran currently has some problems with PDTs. So trying out another compiler will help you differentiate between what may be actual coding issues versus those that are in the compiler itself.

1 Like

I thnk the error message is due to the class argument not being the first argument. Use the pass(this) attribute to solve it.

1 Like

Thank your very much for your help. We are actually following your suggested materials. Thank your for your suggestions. In this case will have a look into other compilers :slight_smile:

Do you mean something like this?

procedure,private,pass(this) :: point_multiply_vct_scalar_32

Yes, that is exactly what I mean :slight_smile: The name between parentheses is the name of the argument that is to be passed as the “owning” object.

1 Like

Some minor points. Once one error is encountered many other bogus errors may follow. You might want to limit the amount of errors generated so you don’t spend too much time on the wrong issue. Adding something like “-fmax-errors=1” on your gfortran command might be useful.
That is a really old version of gfortran, and you are using relatively new features. In addition to the Intel compiler mentioned, you really want to use a newer version of gfortran.

You might want to ask your instructor what compiler versions are required/recommended(?)

@fidu13, note parameterized derived types first made their appearance in gfortran in v8.0.0 (Experimental) version. And it does not appear the facility was backported to earlier versions. Regardless, there are some issues with PDTs in gfortran. So you may want to either go with another compiler such as Intel oneAPI 2021.4 if you plan to use PDTs or consider an alternate approach if you need to remain with gfortran 7.5.0.