OSDN Git Service

2010-07-29 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / equiv_7.f90
1 ! { dg-do run }
2 ! { dg-options "-std=gnu" }
3 ! Tests the fix for PR29786, in which initialization of overlapping
4 ! equivalence elements caused a compile error.
5 !
6 ! Contributed by Bernhard Fischer <aldot@gcc.gnu.org>
7 !
8 block data
9   common /global/ ca (4)
10   integer(4) ca, cb
11   equivalence (cb, ca(3))
12   data (ca(i), i = 1, 2) /42,43/, ca(4) /44/
13   data cb /99/
14 end block data
15
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"
19
20   call int4_int4
21   call real4_real4
22   call complex_real
23   call check_block_data
24   call derived_types         ! Thanks to Tobias Burnus for this:)
25 !
26 ! This came up in PR29786 comment #9 - Note the need to treat endianess
27 ! Thanks Dominique d'Humieres:)
28 !
29   if (bigendian) then
30     if (d1mach_little (1) .ne. transfer ((/0_4, 1048576_4/), 1d0)) call abort ()
31     if (d1mach_little (2) .ne. transfer ((/-1_4,2146435071_4/), 1d0)) call abort ()
32   else
33     if (d1mach_big (1) .ne. transfer ((/1048576_4, 0_4/), 1d0)) call abort ()
34     if (d1mach_big (2) .ne. transfer ((/2146435071_4,-1_4/), 1d0)) call abort ()
35   end if 
36 !
37 contains
38   subroutine int4_int4
39       integer(4)         a(4)
40       integer(4)         b
41       equivalence (b,a(3))
42       data b/3/
43       data (a(i), i=1,2) /1,2/, a(4) /4/
44       if (any (a .ne. (/1, 2, 3, 4/))) call abort ()
45   end subroutine int4_int4
46   subroutine real4_real4
47       real(4)         a(4)
48       real(4)         b
49       equivalence (b,a(3))
50       data b/3.0_4/
51       data (a(i), i=1,2) /1.0_4, 2.0_4/, &
52             a(4) /4.0_4/
53       if (sum (abs (a -  &
54           (/1.0_4, 2.0_4, 3.0_4, 4.0_4/))) > 1.0e-6) call abort ()
55   end subroutine real4_real4
56   subroutine complex_real
57       complex(4)         a(4)
58       real(4)            b(2)
59       equivalence (b,a(3))
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)/, &
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), &
64           (3.0_4, 4.0_4),(0.0_4, 5.0_4)/)))  > 1.0e-6) call abort ()
65   end subroutine complex_real
66   subroutine check_block_data
67       common /global/ ca (4)
68       equivalence (ca(3), cb)
69       integer(4) ca
70       if (any (ca .ne. (/42, 43, 99, 44/))) call abort ()
71   end subroutine check_block_data
72   function d1mach_little(i) result(d1mach)
73     implicit none
74     double precision d1mach,dmach(5)
75     integer i
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/
81     d1mach = dmach(i) 
82   end function d1mach_little
83   function d1mach_big(i) result(d1mach)
84     implicit none
85     double precision d1mach,dmach(5)
86     integer i
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/
92     d1mach = dmach(i) 
93   end function d1mach_big
94     subroutine derived_types
95       TYPE T1
96         sequence
97         character (3) :: chr
98         integer :: i = 1
99         integer :: j
100         END TYPE T1
101       TYPE T2
102         sequence
103         character (3) :: chr = "wxy"
104         integer :: i = 1
105         integer :: j = 4
106       END TYPE T2
107       TYPE(T1) :: a1
108       TYPE(T2) :: a2
109       EQUIVALENCE(a1,a2)         ! { dg-warning="mixed|components" }
110       if (a1%chr .ne. "wxy") call abort ()
111       if (a1%i .ne. 1) call abort ()
112       if (a1%j .ne. 4) call abort ()
113       end subroutine derived_types
114 end