comparison gcc/testsuite/gfortran.dg/equiv_7.f90 @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900 (2018-10-24)
parents 04ced10e8804
children
comparison
equal deleted inserted replaced
111:04ced10e8804 131:84e7813d76e9
25 ! 25 !
26 ! This came up in PR29786 comment #9 - Note the need to treat endianess 26 ! This came up in PR29786 comment #9 - Note the need to treat endianess
27 ! Thanks Dominique d'Humieres:) 27 ! Thanks Dominique d'Humieres:)
28 ! 28 !
29 if (bigendian) then 29 if (bigendian) then
30 if (d1mach_little (1) .ne. transfer ((/0_4, 1048576_4/), 1d0)) call abort () 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)) call abort () 31 if (d1mach_little (2) .ne. transfer ((/-1_4,2146435071_4/), 1d0)) STOP 2
32 else 32 else
33 if (d1mach_big (1) .ne. transfer ((/1048576_4, 0_4/), 1d0)) call abort () 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)) call abort () 34 if (d1mach_big (2) .ne. transfer ((/2146435071_4,-1_4/), 1d0)) STOP 4
35 end if 35 end if
36 ! 36 !
37 contains 37 contains
38 subroutine int4_int4 38 subroutine int4_int4
39 integer(4) a(4) 39 integer(4) a(4)
40 integer(4) b 40 integer(4) b
41 equivalence (b,a(3)) 41 equivalence (b,a(3))
42 data b/3/ 42 data b/3/
43 data (a(i), i=1,2) /1,2/, a(4) /4/ 43 data (a(i), i=1,2) /1,2/, a(4) /4/
44 if (any (a .ne. (/1, 2, 3, 4/))) call abort () 44 if (any (a .ne. (/1, 2, 3, 4/))) STOP 5
45 end subroutine int4_int4 45 end subroutine int4_int4
46 subroutine real4_real4 46 subroutine real4_real4
47 real(4) a(4) 47 real(4) a(4)
48 real(4) b 48 real(4) b
49 equivalence (b,a(3)) 49 equivalence (b,a(3))
50 data b/3.0_4/ 50 data b/3.0_4/
51 data (a(i), i=1,2) /1.0_4, 2.0_4/, & 51 data (a(i), i=1,2) /1.0_4, 2.0_4/, &
52 a(4) /4.0_4/ 52 a(4) /4.0_4/
53 if (sum (abs (a - & 53 if (sum (abs (a - &
54 (/1.0_4, 2.0_4, 3.0_4, 4.0_4/))) > 1.0e-6) call abort () 54 (/1.0_4, 2.0_4, 3.0_4, 4.0_4/))) > 1.0e-6) STOP 6
55 end subroutine real4_real4 55 end subroutine real4_real4
56 subroutine complex_real 56 subroutine complex_real
57 complex(4) a(4) 57 complex(4) a(4)
58 real(4) b(2) 58 real(4) b(2)
59 equivalence (b,a(3)) 59 equivalence (b,a(3))
60 data b(1)/3.0_4/, b(2)/4.0_4/ 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)/, & 61 data (a(i), i=1,2) /(0.0_4, 1.0_4),(2.0_4,0.0_4)/, &
62 a(4) /(0.0_4,5.0_4)/ 62 a(4) /(0.0_4,5.0_4)/
63 if (sum (abs (a - (/(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) call abort () 64 (3.0_4, 4.0_4),(0.0_4, 5.0_4)/))) > 1.0e-6) STOP 7
65 end subroutine complex_real 65 end subroutine complex_real
66 subroutine check_block_data 66 subroutine check_block_data
67 common /global/ ca (4) 67 common /global/ ca (4)
68 equivalence (ca(3), cb) 68 equivalence (ca(3), cb)
69 integer(4) ca 69 integer(4) ca
70 if (any (ca .ne. (/42, 43, 99, 44/))) call abort () 70 if (any (ca .ne. (/42, 43, 99, 44/))) STOP 8
71 end subroutine check_block_data 71 end subroutine check_block_data
72 function d1mach_little(i) result(d1mach) 72 function d1mach_little(i) result(d1mach)
73 implicit none 73 implicit none
74 double precision d1mach,dmach(5) 74 double precision d1mach,dmach(5)
75 integer i 75 integer i
105 integer :: j = 4 105 integer :: j = 4
106 END TYPE T2 106 END TYPE T2
107 TYPE(T1) :: a1 107 TYPE(T1) :: a1
108 TYPE(T2) :: a2 108 TYPE(T2) :: a2
109 EQUIVALENCE(a1,a2) ! { dg-warning="mixed|components" } 109 EQUIVALENCE(a1,a2) ! { dg-warning="mixed|components" }
110 if (a1%chr .ne. "wxy") call abort () 110 if (a1%chr .ne. "wxy") STOP 9
111 if (a1%i .ne. 1) call abort () 111 if (a1%i .ne. 1) STOP 10
112 if (a1%j .ne. 4) call abort () 112 if (a1%j .ne. 4) STOP 11
113 end subroutine derived_types 113 end subroutine derived_types
114 end 114 end