This is the mail archive of the gcc-bugs@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[Bug fortran/44549] New: [OOP][F2008] Type-bound procedure: bogus error from list after PROCEDURE


After the fix for pr40117 with r160646, the following code (borrowed from
somewhere)

MODULE rational_numbers
  IMPLICIT NONE
  PRIVATE
  TYPE,PUBLIC :: rational
    PRIVATE
    INTEGER n,d

    CONTAINS
    ! ordinary type-bound procedure
    PROCEDURE :: real => rat_to_real
    ! specific type-bound procedures for generic support
    PROCEDURE,PRIVATE :: rat_asgn_i, rat_plus_rat, rat_plus_i
    PROCEDURE,PRIVATE,PASS(b) :: i_plus_rat
    ! generic type-bound procedures
    GENERIC :: ASSIGNMENT(=) => rat_asgn_i
    GENERIC :: OPERATOR(+) => rat_plus_rat, rat_plus_i, i_plus_rat
  END TYPE
  CONTAINS
    ELEMENTAL REAL FUNCTION rat_to_real(this) RESULT(r)
      CLASS(rational),INTENT(IN) :: this
      r = REAL(this%n)/this%d
    END FUNCTION

    ELEMENTAL SUBROUTINE rat_asgn_i(a,b)
      CLASS(rational),INTENT(OUT) :: a
      INTEGER,INTENT(IN) :: b
      a%n = b
      a%d = 1
    END SUBROUTINE

    ELEMENTAL TYPE(rational) FUNCTION rat_plus_i(a,b) RESULT(r)
      CLASS(rational),INTENT(IN) :: a
      INTEGER,INTENT(IN) :: b
      r%n = a%n + b*a%d
      r%d = a%d
    END FUNCTION

    ELEMENTAL TYPE(rational) FUNCTION i_plus_rat(a,b) RESULT(r)
      INTEGER,INTENT(IN) :: a
      CLASS(rational),INTENT(IN) :: b
      r%n = b%n + a*b%d
      r%d = b%d
    END FUNCTION

    ELEMENTAL TYPE(rational) FUNCTION rat_plus_rat(a,b) RESULT(r)
      CLASS(rational),INTENT(IN) :: a,b
      r%n = a%n*b%d + b%n*a%d
      r%d = a%d*b%d
    END FUNCTION
END

gives the following bogus error:


class_test.f90:31.48:

    ELEMENTAL TYPE(rational) FUNCTION rat_plus_i(a,b) RESULT(r)
                                                1
Error: Assignment operator interface at (1) must be a SUBROUTINE

and gives an ICE when compiled with -std=f2003


class_test.f90:12.49:

    PROCEDURE,PRIVATE :: rat_asgn_i, rat_plus_rat, rat_plus_i
                                                 1
Error: Fortran 2008: PROCEDURE list at (1)
class_test.f90:16.29:

    GENERIC :: OPERATOR(+) => rat_plus_rat, rat_plus_i, i_plus_rat
                             1
Error: Undefined specific binding 'rat_plus_i' as target of GENERIC '+' at (1)
f951: internal compiler error: Segmentation fault


-- 
           Summary: [OOP][F2008] Type-bound procedure: bogus error from list
                    after PROCEDURE
           Product: gcc
           Version: 4.6.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dominiq at lps dot ens dot fr
 GCC build triplet: x86_64-apple-darwin10.3.0
  GCC host triplet: x86_64-apple-darwin10.3.0
GCC target triplet: x86_64-apple-darwin10.3.0


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


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]