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/45827] mio_component_ref(): Component not found when mixing f90 and f03 in large projects


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

Daniel Franke <dfranke at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |dfranke at gcc dot gnu.org

--- Comment #32 from Daniel Franke <dfranke at gcc dot gnu.org> 2010-12-27 02:22:45 UTC ---
Same error for this testcase:

MODULE abstract_weight_policy
  TYPE, ABSTRACT :: abstract_weight
    PRIVATE
    INTEGER              :: n
    REAL(8), ALLOCATABLE :: w(:)
  CONTAINS
    PROCEDURE(create), DEFERRED :: create
    PROCEDURE                   :: get
    PROCEDURE                   :: destroy
  END TYPE

  ABSTRACT INTERFACE
    SUBROUTINE create(this, n, s, I)
      IMPORT abstract_weight
      CLASS(abstract_weight), INTENT(inout) :: this
      INTEGER, INTENT(in)           :: n
      REAL(8), INTENT(in)           :: s(n), I(n)
    END SUBROUTINE
  END INTERFACE

CONTAINS
  PURE FUNCTION get(this)
    CLASS(abstract_weight), INTENT(in) :: this
    REAL(8), DIMENSION(this%n) :: get
    get = this%w
  END FUNCTION

  SUBROUTINE destroy(this)
    CLASS(abstract_weight), INTENT(inout) :: this
    IF (ALLOCATED(this%w)) DEALLOCATE(this%w)
    this%n = 0
  END SUBROUTINE
END MODULE

MODULE myweights_policy
  USE abstract_weight_policy
END MODULE

$> gfortran-svn -Wall -W polytest.f90 
polytest.f90:36.28:

  USE abstract_weight_policy
                            1
Internal Error at (1):
mio_component_ref(): Component not found

$ gfortran-svn -v
gcc version 4.6.0 20101226 (experimental) (GCC) 


The error is consistent and reproducible for me, nothing fishy from valgrind.
Although the error is identical, no idea if the reason to trigger it is the
same as the reporter's.


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