public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/47845] New: Polymorphic deferred function: Not matched class
@ 2011-02-22  7:14 Kdx1999 at gmail dot com
  2011-02-22  8:08 ` [Bug fortran/47845] [OOP] " burnus at gcc dot gnu.org
                   ` (3 more replies)
  0 siblings, 4 replies; 5+ messages in thread
From: Kdx1999 at gmail dot com @ 2011-02-22  7:14 UTC (permalink / raw)
  To: gcc-bugs

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!


^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/47845] [OOP] Polymorphic deferred function: Not matched class
  2011-02-22  7:14 [Bug fortran/47845] New: Polymorphic deferred function: Not matched class Kdx1999 at gmail dot com
@ 2011-02-22  8:08 ` burnus at gcc dot gnu.org
  2011-02-22 12:57 ` Kdx1999 at gmail dot com
                   ` (2 subsequent siblings)
  3 siblings, 0 replies; 5+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-02-22  8:08 UTC (permalink / raw)
  To: gcc-bugs

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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu.org
            Summary|Polymorphic deferred        |[OOP] Polymorphic deferred
                   |function: Not matched class |function: Not matched class

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-02-22 07:06:48 UTC ---
The following is in any case wrong:

  TYPE,ABSTRACT::vec
   CONTAINS
     PROCEDURE,PASS::set_vec=>set_vec_sub
with
  SUBROUTINE set_vec_sub(this,x,y)

and

  TYPE,EXTENDS(vec),PUBLIC::vec3d
   CONTAINS
     PROCEDURE,PUBLIC,PASS::set_vec=>set_vec_3d
with
  SUBROUTINE set_vec_3d(this,x,y,z)


NAG's error message is

Error: Overriding type-bound procedure SET_VEC of type VEC3D has 4 arguments,
but overridden one has 3 arguments


Which matches gfortran's

     PROCEDURE,PUBLIC,PASS::set_vec=>set_vec_3d
              1
Error: 'set_vec' at (1) must have the same number of formal arguments as the
overridden procedure

See Fortran 2008, "4.5.7.3 Type-bound procedure overriding":
"The overriding and overridden type-bound procedures shall satisfy the
following conditions. [...] They shall have the same number of dummy
arguments."
See: http://gcc.gnu.org/wiki/GFortranStandards


I have not checked the other error messages.


^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/47845] [OOP] Polymorphic deferred function: Not matched class
  2011-02-22  7:14 [Bug fortran/47845] New: Polymorphic deferred function: Not matched class Kdx1999 at gmail dot com
  2011-02-22  8:08 ` [Bug fortran/47845] [OOP] " burnus at gcc dot gnu.org
@ 2011-02-22 12:57 ` Kdx1999 at gmail dot com
  2011-02-22 14:46 ` burnus at gcc dot gnu.org
  2011-03-12 17:23 ` janus at gcc dot gnu.org
  3 siblings, 0 replies; 5+ messages in thread
From: Kdx1999 at gmail dot com @ 2011-02-22 12:57 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from KePu <Kdx1999 at gmail dot com> 2011-02-22 12:54:10 UTC ---
Thank you for respond this issue, I have modified the definition of vec:). But
it seems that only the first argument can be set to subclass of vec, the other
must be strictly set to vec, so the additional coordinate z can't be used in
newly overriding procedures.


^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/47845] [OOP] Polymorphic deferred function: Not matched class
  2011-02-22  7:14 [Bug fortran/47845] New: Polymorphic deferred function: Not matched class Kdx1999 at gmail dot com
  2011-02-22  8:08 ` [Bug fortran/47845] [OOP] " burnus at gcc dot gnu.org
  2011-02-22 12:57 ` Kdx1999 at gmail dot com
@ 2011-02-22 14:46 ` burnus at gcc dot gnu.org
  2011-03-12 17:23 ` janus at gcc dot gnu.org
  3 siblings, 0 replies; 5+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-02-22 14:46 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-02-22 13:50:24 UTC ---
(In reply to comment #2)
> Thank you for respond this issue, I have modified the definition of vec:). But
> it seems that only the first argument can be set to subclass of vec, the other
> must be strictly set to vec, so the additional coordinate z can't be used in
> newly overriding procedures.

You could use "GENERIC" to generate different versions of "vec" - and make the
two argument version set "z == 0". (Similar to "GENERIC :: OPERATOR(+)" but for
type-bound procedures.)


Are there other issues in the bug report? From comment 0 it is a bit unclear to
me what the issue is - besides the non-issue mentioned in comment 1.

If there is no issue left, I would like to close this problem report (PR).

 * * *

For general Fortran questions, I would recommend the comp.lang.fortran news
group which is available on *any* (net) news server. It is also available via
Google, but they do not filter spam - thus, your university's or ISP's server
should be preferred. Cf. also http://groups.google.com/group/comp.lang.fortran/

For specific gfortran question, the fortran mailing list at
http://gcc.gnu.org/lists.html


^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/47845] [OOP] Polymorphic deferred function: Not matched class
  2011-02-22  7:14 [Bug fortran/47845] New: Polymorphic deferred function: Not matched class Kdx1999 at gmail dot com
                   ` (2 preceding siblings ...)
  2011-02-22 14:46 ` burnus at gcc dot gnu.org
@ 2011-03-12 17:23 ` janus at gcc dot gnu.org
  3 siblings, 0 replies; 5+ messages in thread
From: janus at gcc dot gnu.org @ 2011-03-12 17:23 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |INVALID

--- Comment #4 from janus at gcc dot gnu.org 2011-03-12 17:23:17 UTC ---
(In reply to comment #3)
> Are there other issues in the bug report? From comment 0 it is a bit unclear to
> me what the issue is - besides the non-issue mentioned in comment 1.
> 
> If there is no issue left, I would like to close this problem report (PR).

Closing as invalid.


^ permalink raw reply	[flat|nested] 5+ messages in thread

end of thread, other threads:[~2011-03-12 17:23 UTC | newest]

Thread overview: 5+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-02-22  7:14 [Bug fortran/47845] New: Polymorphic deferred function: Not matched class Kdx1999 at gmail dot com
2011-02-22  8:08 ` [Bug fortran/47845] [OOP] " burnus at gcc dot gnu.org
2011-02-22 12:57 ` Kdx1999 at gmail dot com
2011-02-22 14:46 ` burnus at gcc dot gnu.org
2011-03-12 17:23 ` janus at gcc dot gnu.org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).