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