annotate gcc/testsuite/gfortran.dg/generic_18.f90 @ 111:04ced10e8804

gcc 7
author kono
date Fri, 27 Oct 2017 22:46:09 +0900
parents
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do compile }
kono
parents:
diff changeset
2 ! { dg-options "-fdump-tree-original" }
kono
parents:
diff changeset
3 !
kono
parents:
diff changeset
4 ! Test the fix for PR40443 in which the final call to the generic
kono
parents:
diff changeset
5 ! 'SpecElem' was resolved to the elemental rather than the specific
kono
parents:
diff changeset
6 ! procedure, which is required by the second part of 12.4.4.1.
kono
parents:
diff changeset
7 !
kono
parents:
diff changeset
8 ! Contributed by Ian Harvey <ian_harvey@bigpond.com>
kono
parents:
diff changeset
9 !
kono
parents:
diff changeset
10 MODULE SomeOptions
kono
parents:
diff changeset
11 IMPLICIT NONE
kono
parents:
diff changeset
12 INTERFACE ElemSpec
kono
parents:
diff changeset
13 MODULE PROCEDURE ElemProc
kono
parents:
diff changeset
14 MODULE PROCEDURE SpecProc
kono
parents:
diff changeset
15 END INTERFACE ElemSpec
kono
parents:
diff changeset
16 INTERFACE SpecElem
kono
parents:
diff changeset
17 MODULE PROCEDURE SpecProc
kono
parents:
diff changeset
18 MODULE PROCEDURE ElemProc
kono
parents:
diff changeset
19 END INTERFACE SpecElem
kono
parents:
diff changeset
20 CONTAINS
kono
parents:
diff changeset
21 ELEMENTAL SUBROUTINE ElemProc(a)
kono
parents:
diff changeset
22 CHARACTER, INTENT(OUT) :: a
kono
parents:
diff changeset
23 !****
kono
parents:
diff changeset
24 a = 'E'
kono
parents:
diff changeset
25 END SUBROUTINE ElemProc
kono
parents:
diff changeset
26
kono
parents:
diff changeset
27 SUBROUTINE SpecProc(a)
kono
parents:
diff changeset
28 CHARACTER, INTENT(OUT) :: a(:)
kono
parents:
diff changeset
29 !****
kono
parents:
diff changeset
30 a = 'S'
kono
parents:
diff changeset
31 END SUBROUTINE SpecProc
kono
parents:
diff changeset
32 END MODULE SomeOptions
kono
parents:
diff changeset
33
kono
parents:
diff changeset
34 PROGRAM MakeAChoice
kono
parents:
diff changeset
35 USE SomeOptions
kono
parents:
diff changeset
36 IMPLICIT NONE
kono
parents:
diff changeset
37 CHARACTER scalar, array(2)
kono
parents:
diff changeset
38 !****
kono
parents:
diff changeset
39 CALL ElemSpec(scalar) ! Should choose the elemental (and does)
kono
parents:
diff changeset
40 WRITE (*, 100) scalar
kono
parents:
diff changeset
41 CALL ElemSpec(array) ! Should choose the specific (and does)
kono
parents:
diff changeset
42 WRITE (*, 100) array
kono
parents:
diff changeset
43 !----
kono
parents:
diff changeset
44 CALL SpecElem(scalar) ! Should choose the elemental (and does)
kono
parents:
diff changeset
45 WRITE (*, 100) scalar
kono
parents:
diff changeset
46 CALL SpecElem(array) ! Should choose the specific (but didn't)
kono
parents:
diff changeset
47 WRITE (*, 100) array
kono
parents:
diff changeset
48 !----
kono
parents:
diff changeset
49 100 FORMAT(A,:,', ',A)
kono
parents:
diff changeset
50 END PROGRAM MakeAChoice
kono
parents:
diff changeset
51 ! { dg-final { scan-tree-dump-times "specproc" 3 "original" } }
kono
parents:
diff changeset
52 ! { dg-final { scan-tree-dump-times "elemproc" 3 "original" } }