view gcc/testsuite/gfortran.dg/der_pointer_2.f90 @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! PR 15975, PR 16606
! Pointers to derived types with initialized components
!
! Contributed by Erik Edelmann <erik.edelmann@iki.fi>
!
SUBROUTINE N
  TYPE T
    INTEGER :: I = 99
  END TYPE T
  TYPE(T), POINTER :: P
  TYPE(T), TARGET  :: Q
  P => Q
  if (P%I.ne.99) STOP 1
END SUBROUTINE N

program test_pr15975
  call n ()
end program test_pr15975