[Bug fortran/47845] New: Polymorphic deferred function: Not matched class

Kdx1999 at gmail dot com gcc-bugzilla@gcc.gnu.org
Tue Feb 22 07:14:00 GMT 2011


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=47845

           Summary: Polymorphic deferred function: Not matched class
           Product: gcc
           Version: 4.6.0
            Status: UNCONFIRMED
          Severity: major
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: Kdx1999@gmail.com


I'm trying to work out an Exercise in Stephen Chapman's book Fortran 95/2003
for Scientists & Engineers. Create a abstract class vec and subclass vec2d and
vec3d, override some deferred functions, then test the classes.

--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
Here is my construction of vec:
MODULE class_vec
  !
  ! Brief Description:
  ! 1. Superclass of vec2d and vec3d 
  ! 2. Perform vector addition and subtraction
  ! 3. Perform vector dot product
  !
  ! 4. Common fields:
  !  a.x
  !  b.y
  !  
  ! Record of revisions:
  ! Date          Programmer          Description of change
  ! 02/21/2011    KePu                Original code
  !
  IMPLICIT NONE

  TYPE,ABSTRACT::vec
     ! Common fields
     REAL::x
     REAL::y

     ! Declare methods
   CONTAINS
     GENERIC::OPERATOR(+)=>add
     GENERIC::OPERATOR(-)=>subtract
     GENERIC::OPERATOR(*)=>dot
     PROCEDURE,PASS::set_vec=>set_vec_sub
     PROCEDURE(addx),PASS,DEFERRED::add
     PROCEDURE(subtractx),PASS,DEFERRED::subtract
     PROCEDURE(dotx),PASS,DEFERRED::dot

  END TYPE vec

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  ! Interfaces to deferred procedures
  ABSTRACT INTERFACE

     FUNCTION  addx(this,other) RESULT(add_vec)
       !
       ! Purpose:
       ! Add two vector
       !
       ! Record of revisions:
       ! Date          Programmer          Description of change
       ! 02/21/2011    KePu                Original code
       !
       IMPORT vec 
       IMPLICIT NONE
       CLASS(vec),INTENT(in)::this            ! This object
       CLASS(vec),INTENT(in)::other           ! The other object
       CLASS(vec),POINTER::add_vec            ! Return value

     END FUNCTION addx

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

     FUNCTION subtractx(this,other) RESULT(subtract_vec)
       !
       ! Purpose:
       ! Subtract two vector
       !
       ! Reord of revisions:
       ! Date          Programmer          Description of change
       ! 02/21/2011    KePu                Original code
       !
       IMPORT vec
       IMPLICIT NONE
       CLASS(vec),INTENT(in)::this            ! This object
       CLASS(vec),INTENT(in)::other           ! The other object
       CLASS(vec),Pointer::subtract_vec   ! Return value
     END FUNCTION subtractx

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

     FUNCTION dotx(this,other)
       !
       ! Purpose:
       ! Dot product of two vectors
       !
       ! Record of revisions:
       ! Date          Programmer          Description of change
       ! 02/21/2011    KePu                Original code
       !
       IMPORT vec
       IMPLICIT NONE
       CLASS(vec),INTENT(in)::this            ! This object
       CLASS(vec),INTENT(in)::other           ! The other object
       REAL::dotx                             ! Return value
     END FUNCTION dotx
  END INTERFACE

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  ! Define methods
CONTAINS

  SUBROUTINE set_vec_sub(this,x,y)
    !
    ! Purpose:
    ! Set coordinate of vector
    !
    ! Record of revisions:
    ! Date          Programmer          Description of change
    ! 02/21/2011    KePu                Original code
    !
    IMPLICIT NONE

    ! Data dictionary:
    CLASS(vec),INTENT(inout)::this ! Input object
    REAL,INTENT(in)::x,y           ! Coordinate 

    this%x=x
    this%y=y 

  END SUBROUTINE set_vec_sub
END MODULE class_vec

------------------------------------------------------------------------------
------------------------------------------------------------------------------

Subclass vec3d will override all the functions and subroutines defined above

MODULE class_vec3d
  !
  ! Brief description:
  ! 1. Subclass of vec
  ! 2. Fields
  !  a. Inherited: real::x real::y
  !  b. Extends: real::z
  ! 3. Method
  !  a. set_vec
  !  b. Addition
  !  c. Subtraction
  !  d. Dot product
  !
  ! Record of revisions:
  ! Date          Programmer          Description of change
  ! 02/22/2011    KePu                Original code
  !
  USE class_vec                 ! Use parent class

  IMPLICIT NONE

  ! Type definition
  TYPE,EXTENDS(vec),PUBLIC::vec3d
     ! Fields
     REAL::z

     ! Declare methods
   CONTAINS
     PROCEDURE,PUBLIC,PASS::set_vec=>set_vec_3d
     PROCEDURE,PUBLIC,PASS::add=>add_fn
     PROCEDURE,PUBLIC,PASS::subtract=>subtract_fn
     PROCEDURE,PUBLIC,PASS::dot=>dot_fn
  END TYPE vec3d

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  ! Define method
CONTAINS

  SUBROUTINE set_vec_3d(this,x,y,z)
    !
    ! Purpose:
    ! Set coordinate of 3d vector
    !
    ! Record of revisions:
    ! Date          Programmer          Description of change
    ! 02/22/2011    KePu                Original code
    !
    IMPLICIT NONE

    ! Data dictionary:
    CLASS(vec3d),INTENT(inout)::this ! Input 3d vector
    REAL,INTENT(in)::x,y,z           ! Input coordinates

    this%x=x
    this%y=y
    this%z=z
  END SUBROUTINE set_vec_3d

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

  FUNCTION add_fn(this,other) RESULT(add_vec_fn) 
    !
    ! Purpose:
    ! Add two 3d vectors
    !
    ! Record of revisons:
    ! Date          Programmer          Description of change
    ! 02/22/2011    KePu                Original code
    !
    IMPLICIT NONE

    ! Data dictionay
    CLASS(vec3d),INTENT(in)::this ! This 3d vector
    CLASS(vec3d),INTENT(in)::other  ! The other 3d vector
    CLASS(vec3d),POINTER::add_vec_fn

    add_vec_fn%x=this%x+other%x
    add_vec_fn%y=this%y+other%y
    add_vec_fn%z=this%z+other%z
  END FUNCTION add_fn

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!


  FUNCTION subtract_fn(this,other) RESULT(sbtract_vec_fn) 
    !
    ! Purpose:
    ! Add two 3d vectors
    !
    ! Record of revisons:
    ! Date          Programmer          Description of change
    ! 02/22/2011    KePu                Original code
    !
    IMPLICIT NONE

    ! Data dictionay
    CLASS(vec3d),INTENT(in)::this ! This 3d vector
    CLASS(vec3d),INTENT(in)::other  ! The other 3d vector
    CLASS(vec3d),POINTER::sbtract_vec_fn

    sbtract_vec_fn%x=this%x+other%x
    sbtract_vec_fn%y=this%y+other%y
    sbtract_vec_fn%z=this%z+other%z
  END FUNCTION subtract_fn

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!


  FUNCTION dot_fn(this,other)
    !
    ! Purpose:
    ! Add two 3d vectors
    !
    ! Record of revisons:
    ! Date          Programmer          Description of change
    ! 02/22/2011    KePu                Original code
    !
    IMPLICIT NONE

    ! Data dictionay
    CLASS(vec3d),INTENT(in)::this ! This 3d vector
    CLASS(vec3d),INTENT(in)::other  ! The other 3d vector
    REAL,POINTER::dot_fn

    dot_fn=this%x*other%x+this%y*other%y+this%z*other%z
  END FUNCTION dot_fn

END MODULE class_vec3d

-----------------------------------------------------------------------------
-----------------------------------------------------------------------------
Subroutine is fine, but compiler said dummy argument "other"(of class vec3d) of
each function is not match with which interface defined in class vec. I'm
confused...vec3d is a subclass of vec, right? I'm not sure if it is a bug, I
just want to know how to solve the problem , any help will be appreciated,
thank you!



More information about the Gcc-bugs mailing list