OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [protected_8.f90] - Rev 704

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do compile }
!
! PR fortran/46122
!
! PROTECT check
!
! Contributed by Jared Ahern
!

MODULE amod
   IMPLICIT NONE
   TYPE foo
      INTEGER :: i = 4
      INTEGER, POINTER :: j => NULL()
   END TYPE foo
   TYPE(foo), SAVE, PROTECTED :: a
   TYPE(foo), SAVE, PROTECTED, POINTER :: b
   INTEGER, SAVE, PROTECTED :: i = 5
   INTEGER, SAVE, PROTECTED, POINTER :: j => NULL()
contains
  subroutine alloc()
    allocate(b,j)
  end subroutine alloc
END MODULE amod

PROGRAM test
   USE amod
   IMPLICIT NONE
   INTEGER, TARGET :: k
   TYPE(foo), TARGET :: c
   k = 2   ! local
   c%i = 9 ! local

   call alloc()

   i = k    ! { dg-error "is PROTECTED" }
   j => k   ! { dg-error "is PROTECTED" }
   j = 3    ! OK 1
   a = c    ! { dg-error "is PROTECTED" }
   a%i = k  ! { dg-error "is PROTECTED" }
   a%j => k ! { dg-error "is PROTECTED" }
   a%j = 5  ! OK 2
   b => c   ! { dg-error "is PROTECTED" }
   b%i = k  ! OK 3
   b%j => k ! OK 4
   b%j = 5  ! OK 5

END PROGRAM test

! { dg-final { cleanup-modules "amod" } }

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.