2 ! { dg-options "-std=gnu" }
3 ! Tests the fix for PR29786, in which initialization of overlapping
4 ! equivalence elements caused a compile error.
6 ! Contributed by Bernhard Fischer <aldot@gcc.gnu.org>
11 equivalence (cb
, ca(3))
12 data (ca(i
), i
= 1, 2) /42,43/, ca(4) /44/
16 integer(4), parameter :: abcd
= ichar ("a") + 256_4 * (ichar("b") + 256_4 * &
17 (ichar ("c") + 256_4 * ichar ("d")))
18 logical(4), parameter :: bigendian
= transfer (abcd
, "wxyz") .eq
. "abcd"
24 call derived_types
! Thanks to Tobias Burnus for this:)
26 ! This came up in PR29786 comment #9 - Note the need to treat endianess
27 ! Thanks Dominique d'Humieres:)
30 if (d1mach_little (1) .ne
. transfer ((/0_4, 1048576_4/), 1d0)) STOP 1
31 if (d1mach_little (2) .ne
. transfer ((/-1_4,2146435071_4/), 1d0)) STOP 2
33 if (d1mach_big (1) .ne
. transfer ((/1048576_4, 0_4/), 1d0)) STOP 3
34 if (d1mach_big (2) .ne
. transfer ((/2146435071_4,-1_4/), 1d0)) STOP 4
43 data (a(i
), i
=1,2) /1,2/, a(4) /4/
44 if (any (a
.ne
. (/1, 2, 3, 4/))) STOP 5
45 end subroutine int4_int4
46 subroutine real4_real4
51 data (a(i
), i
=1,2) /1.0_4
, 2.0_4
/, &
54 (/1.0_4
, 2.0_4
, 3.0_4
, 4.0_4
/))) > 1.0e-6) STOP 6
55 end subroutine real4_real4
56 subroutine complex_real
60 data b(1)/3.0_4
/, b(2)/4.0_4
/
61 data (a(i
), i
=1,2) /(0.0_4
, 1.0_4
),(2.0_4
,0.0_4
)/, &
63 if (sum (abs (a
- (/(0.0_4
, 1.0_4
),(2.0_4
, 0.0_4
), &
64 (3.0_4
, 4.0_4
),(0.0_4
, 5.0_4
)/))) > 1.0e-6) STOP 7
65 end subroutine complex_real
66 subroutine check_block_data
67 common /global
/ ca (4)
68 equivalence (ca(3), cb
)
70 if (any (ca
.ne
. (/42, 43, 99, 44/))) STOP 8
71 end subroutine check_block_data
72 function d1mach_little(i
) result(d1mach
)
74 double precision d1mach
,dmach(5)
76 integer*4 large(4),small(4)
77 equivalence ( dmach(1), small(1) )
78 equivalence ( dmach(2), large(1) )
79 data small(1),small(2) / 0, 1048576/
80 data large(1),large(2) /-1,2146435071/
82 end function d1mach_little
83 function d1mach_big(i
) result(d1mach
)
85 double precision d1mach
,dmach(5)
87 integer*4 large(4),small(4)
88 equivalence ( dmach(1), small(1) )
89 equivalence ( dmach(2), large(1) )
90 data small(1),small(2) /1048576, 0/
91 data large(1),large(2) /2146435071,-1/
93 end function d1mach_big
94 subroutine derived_types
103 character (3) :: chr
= "wxy"
109 EQUIVALENCE(a1
,a2
) ! { dg-warning="mixed|components" }
110 if (a1
%chr
.ne
. "wxy") STOP 9
111 if (a1
%i
.ne
. 1) STOP 10
112 if (a1
%j
.ne
. 4) STOP 11
113 end subroutine derived_types