view gcc/testsuite/gfortran.dg/pr47008.f03 @ 145:1830386684a0

gcc-9.2.0
author anatofuz
date Thu, 13 Feb 2020 11:34:05 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! PR rtl-optimization/47008
! { dg-do run }
! { dg-options "-Os -fno-asynchronous-unwind-tables -fschedule-insns -fsched-pressure -fno-inline" { target i?86-*-* x86_64-*-* } }

program main
  type :: t
    integer :: i
    character(24) :: c
    type (t), pointer :: p
  end type t
  type(t), pointer :: r, p
  allocate (p)
  p = t (123455, "", p)
  r => entry ("", 123456, 1, "", 99, "", p)
  if (p%i /= 123455) STOP 1
contains
  function entry (x, i, j, c, k, d, p) result (q)
    integer :: i, j, k
    character (*) :: x, c, d
    type (t), pointer :: p, q
    allocate (q)
    q = t (i, c, p)
  end function
end program main