aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/equiv_7.f90
blob: 23f707b39c4ea87c5193ada950aff0279abdfce9 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
! { dg-do run }
! { dg-options "-std=gnu" }
! Tests the fix for PR29786, in which initialization of overlapping
! equivalence elements caused a compile error.
!
! Contributed by Bernhard Fischer <aldot@gcc.gnu.org>
!
block data
  common /global/ ca (4)
  integer(4) ca, cb
  equivalence (cb, ca(3))
  data (ca(i), i = 1, 2) /42,43/, ca(4) /44/
  data cb /99/
end block data

  integer(4), parameter :: abcd = ichar ("a") + 256_4 * (ichar("b") + 256_4 * &
                                 (ichar ("c") + 256_4 * ichar ("d")))
  logical(4), parameter :: bigendian = transfer (abcd, "wxyz") .eq. "abcd"

  call int4_int4
  call real4_real4
  call complex_real
  call check_block_data
  call derived_types         ! Thanks to Tobias Burnus for this:)
!
! This came up in PR29786 comment #9 - Note the need to treat endianess
! Thanks Dominique d'Humieres:)
!
  if (bigendian) then
    if (d1mach_little (1) .ne. transfer ((/0_4, 1048576_4/), 1d0)) call abort ()
    if (d1mach_little (2) .ne. transfer ((/-1_4,2146435071_4/), 1d0)) call abort ()
  else
    if (d1mach_big (1) .ne. transfer ((/1048576_4, 0_4/), 1d0)) call abort ()
    if (d1mach_big (2) .ne. transfer ((/2146435071_4,-1_4/), 1d0)) call abort ()
  end if 
!
contains
  subroutine int4_int4
      integer(4)         a(4)
      integer(4)         b
      equivalence (b,a(3))
      data b/3/
      data (a(i), i=1,2) /1,2/, a(4) /4/
      if (any (a .ne. (/1, 2, 3, 4/))) call abort ()
  end subroutine int4_int4
  subroutine real4_real4
      real(4)         a(4)
      real(4)         b
      equivalence (b,a(3))
      data b/3.0_4/
      data (a(i), i=1,2) /1.0_4, 2.0_4/, &
            a(4) /4.0_4/
      if (sum (abs (a -  &
          (/1.0_4, 2.0_4, 3.0_4, 4.0_4/))) > 1.0e-6) call abort ()
  end subroutine real4_real4
  subroutine complex_real
      complex(4)         a(4)
      real(4)            b(2)
      equivalence (b,a(3))
      data b(1)/3.0_4/, b(2)/4.0_4/
      data (a(i), i=1,2) /(0.0_4, 1.0_4),(2.0_4,0.0_4)/, &
            a(4) /(0.0_4,5.0_4)/
      if (sum (abs (a - (/(0.0_4, 1.0_4),(2.0_4, 0.0_4), &
          (3.0_4, 4.0_4),(0.0_4, 5.0_4)/)))  > 1.0e-6) call abort ()
  end subroutine complex_real
  subroutine check_block_data
      common /global/ ca (4)
      equivalence (ca(3), cb)
      integer(4) ca
      if (any (ca .ne. (/42, 43, 99, 44/))) call abort ()
  end subroutine check_block_data
  function d1mach_little(i) result(d1mach)
    implicit none
    double precision d1mach,dmach(5)
    integer i
    integer*4 large(4),small(4)
    equivalence ( dmach(1), small(1) )
    equivalence ( dmach(2), large(1) )
    data small(1),small(2) / 0,   1048576/
    data large(1),large(2) /-1,2146435071/
    d1mach = dmach(i) 
  end function d1mach_little
  function d1mach_big(i) result(d1mach)
    implicit none
    double precision d1mach,dmach(5)
    integer i
    integer*4 large(4),small(4)
    equivalence ( dmach(1), small(1) )
    equivalence ( dmach(2), large(1) )
    data small(1),small(2) /1048576,    0/
    data large(1),large(2) /2146435071,-1/
    d1mach = dmach(i) 
  end function d1mach_big
    subroutine derived_types
      TYPE T1
        sequence
        character (3) :: chr
        integer :: i = 1
        integer :: j
        END TYPE T1
      TYPE T2
        sequence
        character (3) :: chr = "wxy"
        integer :: i = 1
        integer :: j = 4
      END TYPE T2
      TYPE(T1) :: a1
      TYPE(T2) :: a2
      EQUIVALENCE(a1,a2)         ! { dg-warning="mixed|components" }
      if (a1%chr .ne. "wxy") call abort ()
      if (a1%i .ne. 1) call abort ()
      if (a1%j .ne. 4) call abort ()
      end subroutine derived_types
end