URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [data_pointer_1.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do compile }! Test the fixes for PR38917 and 38918, in which the NULL values caused errors.!! Contributed by Dick Hendrickson <dick.hendrickson@gmail.com>! and Tobias Burnus <burnus@gcc.gnu.org>!SUBROUTINE PF0009! PR38918TYPE :: HAS_POINTERINTEGER, POINTER :: PTR_SEND TYPE HAS_POINTERTYPE (HAS_POINTER) :: PTR_ARRAY(5)DATA PTR_ARRAY(1)%PTR_S /NULL()/end subroutine pf0009SUBROUTINE PF0005! PR38917REAL, SAVE, POINTER :: PTR1INTEGER, POINTER :: PTR2(:,:,:)CHARACTER(LEN=1), SAVE, POINTER :: PTR3(:)DATA PTR1 / NULL() /DATA PTR2 / NULL() /DATA PTR3 / NULL() /end subroutine pf0005! Tobias pointed out that this would cause an ICE rather than an error.subroutine tobiasinteger, pointer :: ptr(:)data ptr(1) /NULL()/ ! { dg-error "must be a full array" }end subroutine tobias
