URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [der_pointer_2.f90] - Rev 154
Compare with Previous | Blame | View Log
! { 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) call abort ()
END SUBROUTINE N
program test_pr15975
call n ()
end program test_pr15975