view gcc/testsuite/gfortran.dg/dependency_46.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 71783 - this used to ICE due to a missing charlen for the temporary.
! Test case by Toon Moene.

SUBROUTINE prtdata(ilen)
  INTEGER :: ilen
  character(len=ilen), allocatable :: cline(:)
  allocate(cline(2))
  cline(1) = 'a'
  cline(2) = cline(1)
END SUBROUTINE prtdata