view gcc/testsuite/gfortran.dg/result_in_spec_4.f90 @ 128:fe568345ddd5

fix CbC-example
author mir3636
date Wed, 11 Apr 2018 19:32:28 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
!
! PR fortran/49648
! ICE for calls to a use-associated function returning an array whose spec
! depends on a function call.

! Contributed by Tobias Burnus <burnus@net-b.de>

module m2
  COMPLEX, SAVE, ALLOCATABLE :: P(:)
contains
  FUNCTION getPhaseMatrix() RESULT(PM)
    COMPLEX:: PM(SIZE(P),3)
    PM=0.0
  END FUNCTION
end module m2

module m
  use m2
contains
   SUBROUTINE gf_generateEmbPot()
      COMPLEX :: sigma2(3,3)
      sigma2 = MATMUL(getPhaseMatrix(), sigma2)
   END SUBROUTINE
end module m