annotate gcc/testsuite/gfortran.dg/coarray_lib_token_1.f90 @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900
parents 04ced10e8804
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 "-fcoarray=lib -fdump-tree-original" }
kono
parents:
diff changeset
3 !
kono
parents:
diff changeset
4 ! Check whether TOKEN and OFFSET are correctly propagated
kono
parents:
diff changeset
5 !
kono
parents:
diff changeset
6
kono
parents:
diff changeset
7 program main
kono
parents:
diff changeset
8 implicit none
kono
parents:
diff changeset
9 type t
kono
parents:
diff changeset
10 integer(4) :: a, b
kono
parents:
diff changeset
11 end type t
kono
parents:
diff changeset
12 integer :: caf[*]
kono
parents:
diff changeset
13 type(t) :: caf_dt[*]
kono
parents:
diff changeset
14
kono
parents:
diff changeset
15 caf = 42
kono
parents:
diff changeset
16 caf_dt = t (1,2)
kono
parents:
diff changeset
17 call sub (caf, caf_dt%b)
kono
parents:
diff changeset
18 print *,caf, caf_dt%b
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
19 if (caf /= -99 .or. caf_dt%b /= -101) STOP 1
111
kono
parents:
diff changeset
20 call sub_opt ()
kono
parents:
diff changeset
21 call sub_opt (caf)
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
22 if (caf /= 124) STOP 2
111
kono
parents:
diff changeset
23 contains
kono
parents:
diff changeset
24
kono
parents:
diff changeset
25 subroutine sub (x1, x2)
kono
parents:
diff changeset
26 integer :: x1[*], x2[*]
kono
parents:
diff changeset
27
kono
parents:
diff changeset
28 call sub2 (x1, x2)
kono
parents:
diff changeset
29 end subroutine sub
kono
parents:
diff changeset
30
kono
parents:
diff changeset
31 subroutine sub2 (y1, y2)
kono
parents:
diff changeset
32 integer :: y1[*], y2[*]
kono
parents:
diff changeset
33
kono
parents:
diff changeset
34 print *, y1, y2
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
35 if (y1 /= 42 .or. y2 /= 2) STOP 3
111
kono
parents:
diff changeset
36 y1 = -99
kono
parents:
diff changeset
37 y2 = -101
kono
parents:
diff changeset
38 end subroutine sub2
kono
parents:
diff changeset
39
kono
parents:
diff changeset
40 subroutine sub_opt (z)
kono
parents:
diff changeset
41 integer, optional :: z[*]
kono
parents:
diff changeset
42 if (present (z)) then
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
43 if (z /= -99) STOP 4
111
kono
parents:
diff changeset
44 z = 124
kono
parents:
diff changeset
45 end if
kono
parents:
diff changeset
46 end subroutine sub_opt
kono
parents:
diff changeset
47
kono
parents:
diff changeset
48 end program main
kono
parents:
diff changeset
49
kono
parents:
diff changeset
50 ! SCAN TREE DUMP AND CLEANUP
kono
parents:
diff changeset
51 !
kono
parents:
diff changeset
52 ! PROTOTYPE 1:
kono
parents:
diff changeset
53 !
kono
parents:
diff changeset
54 ! sub (integer(kind=4) * restrict x1, integer(kind=4) * restrict x2,
kono
parents:
diff changeset
55 ! void * restrict caf_token.4, integer(kind=8) caf_offset.5,
kono
parents:
diff changeset
56 ! void * restrict caf_token.6, integer(kind=8) caf_offset.7)
kono
parents:
diff changeset
57 !
kono
parents:
diff changeset
58 ! { dg-final { scan-tree-dump-times "sub \\(integer.kind=4. . restrict x1, integer.kind=4. . restrict x2, void . restrict caf_token.\[0-9\]+, integer.kind=.. caf_offset.\[0-9\]+, void . restrict caf_token.\[0-9\]+, integer.kind=.. caf_offset.\[0-9\]+\\)" 1 "original" } }
kono
parents:
diff changeset
59 !
kono
parents:
diff changeset
60 ! PROTOTYPE 2:
kono
parents:
diff changeset
61 !
kono
parents:
diff changeset
62 ! sub2 (integer(kind=4) * restrict y1, integer(kind=4) * restrict y2,
kono
parents:
diff changeset
63 ! void * restrict caf_token.0, integer(kind=8) caf_offset.1,
kono
parents:
diff changeset
64 ! void * restrict caf_token.2, integer(kind=8) caf_offset.3)
kono
parents:
diff changeset
65 !
kono
parents:
diff changeset
66 ! { dg-final { scan-tree-dump-times "sub2 \\(integer.kind=4. . restrict y1, integer.kind=4. . restrict y2, void . restrict caf_token.\[0-9\]+, integer.kind=.. caf_offset.\[0-9\]+, void . restrict caf_token.\[0-9\]+, integer.kind=.. caf_offset.\[0-9\]+\\)" 1 "original" } }
kono
parents:
diff changeset
67 !
kono
parents:
diff changeset
68 ! CALL 1
kono
parents:
diff changeset
69 !
kono
parents:
diff changeset
70 ! sub ((integer(kind=4) *) caf, &caf_dt->b, caf_token.9, 0, caf_token.10, 4);
kono
parents:
diff changeset
71 !
kono
parents:
diff changeset
72 ! { dg-final { scan-tree-dump-times "sub \\(\[^,\]*caf, &caf_dt->b, caf_token.\[0-9\]+, 0, caf_token.\[0-9\]+, 4\\)" 1 "original" } }
kono
parents:
diff changeset
73 !
kono
parents:
diff changeset
74 ! sub2 ((integer(kind=4) *) x1, (integer(kind=4) *) x2,
kono
parents:
diff changeset
75 ! caf_token.4, NON_LVALUE_EXPR <caf_offset.5>,
kono
parents:
diff changeset
76 ! caf_token.6, NON_LVALUE_EXPR <caf_offset.7>);
kono
parents:
diff changeset
77 !
kono
parents:
diff changeset
78 ! { dg-final { scan-tree-dump-times "sub2 \\(\[^,\]*x1, \[^,\]*x2, caf_token.\[0-9]+, \[^,\]*caf_offset\[^,\]*, caf_token.\[0-9\]+, \[^,\]*caf_offset\[^,\]*\\)" 1 "original" } }
kono
parents:
diff changeset
79 !
kono
parents:
diff changeset
80 ! CALL 3
kono
parents:
diff changeset
81 !
kono
parents:
diff changeset
82 ! { dg-final { scan-tree-dump-times "sub_opt \\(0B, 0B, 0\\)" 1 "original" } }
kono
parents:
diff changeset
83 !
kono
parents:
diff changeset
84 ! CALL 4
kono
parents:
diff changeset
85 !
kono
parents:
diff changeset
86 ! { dg-final { scan-tree-dump-times "sub_opt \\(.integer.kind=4. .. caf, caf_token.\[0-9\]+, 0\\)" 1 "original" } }
kono
parents:
diff changeset
87 !