2 ! { dg-options "-fdec-structure" }
4 ! Runtime tests for rules governing dot ('.') as a member accessor, including
5 ! voodoo with aliased user-defined vs. intrinsic operators and nested members.
6 ! See gcc/fortran/match.c (gfc_match_member_sep).
9 module dec_structure_10
10 ! Operator overload tests with .ne. and constant member
17 ! Operator overload tests with .eq., .test. and nested members
25 ! Deep nested access tests
42 ! Operator overloads to mess with nested member accesses
43 interface operator (.ne
.)
44 module procedure ne_func
45 end interface operator (.ne
.)
46 interface operator (.eq
.)
47 module procedure eq_func
48 end interface operator (.eq
.)
49 interface operator (.test
.)
50 module procedure tstfunc
51 end interface operator (.test
.)
53 ! ne_func will be called on (x) .ne. (y)
54 function ne_func (r
, i
)
55 integer, intent(in
) :: i
56 type(s1
), intent(in
) :: r
60 ! eq_func will be called on (x) .eq. (y)
61 function eq_func (r
, i
)
62 integer, intent(in
) :: i
63 type(s2
), intent(in
) :: r
67 ! tstfunc will be called on (x) .test. (y)
68 function tstfunc (r
, i
)
69 integer, intent(in
) :: i
70 type(s2
), intent(in
) :: r
86 ! Nested access: struct has a member and which has a member b
87 l
= struct
.and
. b
! struct%and%b
88 l
= struct
.and
. b
.or
. .false
. ! (struct%and%b) .or. (.false.)
90 ! Intrinsic op: r has no member 'ne'
91 j
= r
.ne
. i
! <intrinsic> ne(r, i)
92 j
= (r
) .ne
. i
! <intrinsic> ne(r, i)
94 ! Intrinsic op; r has a member 'ne' but it is not a record
95 j
= r
.ne
. i
! <intrinsic> ne(r, i)
96 j
= (r
) .ne
. i
! <intrinsic> ne(r, i)
98 ! Nested access: struct has a member eq which has a member i
99 j
= struct
.eq
. i
! struct%eq%i
100 if ( j
.ne
. struct
%eq
%i
) call abort()
102 ! User op: struct is compared to i with eq_func
103 j
= (struct
) .eq
. i
! eq_func(struct, i) -> struct%eq%i + i
104 if ( j
.ne
. struct
%eq
%i
+ i
) call abort()
106 ! User op: struct has a member test which has a member i, but test is a uop
107 j
= struct
.test
. i
! tstfunc(struct, i) -> struct%i + i
108 if ( j
.ne
. struct
%i
+ i
) call abort()
110 ! User op: struct is compared to i with eq_func
111 j
= (struct
) .test
. i
! tstfunc(struct, i) -> struct%i + i
112 if ( j
.ne
. struct
%i
+ i
) call abort()
114 ! Deep nested access tests
115 r7
.r6
.r5
.r4
.r3
.r2
.i
= 1337
116 j
= r7
.r6
.r5
.r4
.r3
.r2
.i
117 if ( j
.ne
. 1337 ) call abort()