view gcc/testsuite/gfortran.dg/deferred_character_21.f90 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do compile }
! { dg-options "-O3" }
!
! Tests the fix for PR85954 in which the gimplifier could not determine
! the space required for the dummy argument data types, when inlining the
! subroutines.
!
! Contributed by G.Steinmetz  <gscfq@t-online.de>
!
program p
   character(kind=1,len=:), allocatable :: z(:)
   allocate (z, source = ["xyz"])
   print *, allocated(z), size(z), len(z), z
   call s(z)
   call t(z)
contains
   subroutine s(x)
      character(kind=1,len=:), allocatable :: x(:)
      x = ['abcd']
      print *, allocated(x), size(x), len(x), x
   end
   subroutine t(x)
      character(kind=1,len=:), allocatable :: x(:)
      associate (y => x)
         y = ['abc']
      end associate
      print *, allocated(x), size(x), len(x), x
   end
end