aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/dec_bitwise_ops_2.f90
blob: 33ae8fa6be0daef04009a22cc3583e9f50f8b839 (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
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
! { dg-do run }
! { dg-options "-fdec" }
!
! Runtime tests to verify bitwise ops perform appropriate conversions
! with -fdec.
!

subroutine assert(expected, actual, str)
  implicit none
  character(*), intent(in) :: str
  integer, intent(in)      :: expected, actual(9)
  integer :: i
  do i=1,9
    if (expected .ne. actual(i)) then
      write (*, '(A,I8,I8)') str, expected, actual(i)
      STOP 1
    endif
  enddo
end subroutine

implicit none

logical(1), volatile :: op1_1l
integer(1), volatile :: op1_1, op2_1

logical(2), volatile :: op1_2l
integer(2), volatile :: op1_2, op2_2

logical(4), volatile :: op1_4l
integer(4), volatile :: op1_4, op2_4

integer, volatile :: expect, outs(9)


op1_1l = .true.
op1_2l = .true.
op1_4l = .true.
op1_1 = 117_1
op1_2 = 117_2
op1_4 = 117_4
op2_1 =  49_1
op2_2 =  49_2
op2_4 =  49_4

!!! Explicit integer operands

expect = IAND(op1_1, op2_1)
outs(1) = op1_1 .AND. op2_1
outs(2) = op1_1 .AND. op2_2
outs(3) = op1_1 .AND. op2_4
outs(4) = op1_2 .AND. op2_1
outs(5) = op1_2 .AND. op2_2
outs(6) = op1_2 .AND. op2_4
outs(7) = op1_4 .AND. op2_1
outs(8) = op1_4 .AND. op2_2
outs(9) = op1_4 .AND. op2_4
call assert(expect, outs, "AND")

expect = IOR(op1_1, op2_1)
outs(1) = op1_1 .OR. op2_1
outs(2) = op1_1 .OR. op2_2
outs(3) = op1_1 .OR. op2_4
outs(4) = op1_2 .OR. op2_1
outs(5) = op1_2 .OR. op2_2
outs(6) = op1_2 .OR. op2_4
outs(7) = op1_4 .OR. op2_1
outs(8) = op1_4 .OR. op2_2
outs(9) = op1_4 .OR. op2_4

call assert(expect, outs, "OR")

expect = NOT(IEOR(op1_1, op2_1))
outs(1) = op1_1 .EQV. op2_1
outs(2) = op1_1 .EQV. op2_2
outs(3) = op1_1 .EQV. op2_4
outs(4) = op1_2 .EQV. op2_1
outs(5) = op1_2 .EQV. op2_2
outs(6) = op1_2 .EQV. op2_4
outs(7) = op1_4 .EQV. op2_1
outs(8) = op1_4 .EQV. op2_2
outs(9) = op1_4 .EQV. op2_4

call assert(expect, outs, "EQV")

expect = IEOR(op1_1, op2_1)
outs(1) = op1_1 .NEQV. op2_1
outs(2) = op1_1 .NEQV. op2_2
outs(3) = op1_1 .NEQV. op2_4
outs(4) = op1_2 .NEQV. op2_1
outs(5) = op1_2 .NEQV. op2_2
outs(6) = op1_2 .NEQV. op2_4
outs(7) = op1_4 .NEQV. op2_1
outs(8) = op1_4 .NEQV. op2_2
outs(9) = op1_4 .NEQV. op2_4

call assert(expect, outs, "NEQV")

!!! Logical -> Integer operand conversions
op1_1 = op1_1l
op1_2 = op1_2l
op1_4 = op1_4l

expect = IAND(op1_1, op2_1)
outs(1) = op1_1l .AND. op2_1 ! implicit conversions
outs(2) = op1_1l .AND. op2_2
outs(3) = op1_1l .AND. op2_4
outs(4) = op1_2l .AND. op2_1
outs(5) = op1_2l .AND. op2_2
outs(6) = op1_2l .AND. op2_4
outs(7) = op1_4l .AND. op2_1
outs(8) = op1_4l .AND. op2_2
outs(9) = op1_4l .AND. op2_4
call assert(expect, outs, "AND")

expect = IOR(op1_1, op2_1)
outs(1) = op1_1l .OR. op2_1 ! implicit conversions
outs(2) = op1_1l .OR. op2_2
outs(3) = op1_1l .OR. op2_4
outs(4) = op1_2l .OR. op2_1
outs(5) = op1_2l .OR. op2_2
outs(6) = op1_2l .OR. op2_4
outs(7) = op1_4l .OR. op2_1
outs(8) = op1_4l .OR. op2_2
outs(9) = op1_4l .OR. op2_4

call assert(expect, outs, "OR")

expect = NOT(IEOR(op1_1, op2_1))
outs(1) = op1_1l .EQV. op2_1 ! implicit conversions
outs(2) = op1_1l .EQV. op2_2
outs(3) = op1_1l .EQV. op2_4
outs(4) = op1_2l .EQV. op2_1
outs(5) = op1_2l .EQV. op2_2
outs(6) = op1_2l .EQV. op2_4
outs(7) = op1_4l .EQV. op2_1
outs(8) = op1_4l .EQV. op2_2
outs(9) = op1_4l .EQV. op2_4

call assert(expect, outs, "EQV")

expect = IEOR(op1_1, op2_1)
outs(1) = op1_1l .NEQV. op2_1 ! implicit conversions
outs(2) = op1_1l .NEQV. op2_2
outs(3) = op1_1l .NEQV. op2_4
outs(4) = op1_2l .NEQV. op2_1
outs(5) = op1_2l .NEQV. op2_2
outs(6) = op1_2l .NEQV. op2_4
outs(7) = op1_4l .NEQV. op2_1
outs(8) = op1_4l .NEQV. op2_2
outs(9) = op1_4l .NEQV. op2_4

call assert(expect, outs, "NEQV")


end