aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/present_1.f90
blob: 22e6c0a5a27884e6f791d2b0dee04b86e93ee7ec (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
! { dg-do compile }
! Test the fix for PR25097, in which subobjects of the optional dummy argument
! could appear as argument A of the PRESENT intrinsic.
! 
! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
!
 MODULE M1
  TYPE T1
   INTEGER :: I
  END TYPE T1
 CONTAINS
  SUBROUTINE S1(D1)
   TYPE(T1), OPTIONAL :: D1(4)
   write(6,*) PRESENT(D1%I)  ! { dg-error "must not be a subobject" }
   write(6,*) PRESENT(D1(1)) ! { dg-error "must not be a subobject" }
   write(6,*) PRESENT(D1)
  END SUBROUTINE S1
 END MODULE
 END