[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / dec_bitwise_ops_1.f90
blob6ada8d7d993dd0207d71f4ec46f883086b25ecc0
1 ! { dg-do run }
2 ! { dg-options "-fdec" }
4 ! Runtime tests to verify logical-to-bitwise operations perform as expected
5 ! with -fdec.
8 subroutine assert(expected, actual, str)
9 implicit none
10 character(*), intent(in) :: str
11 integer, intent(in) :: expected, actual
12 if (actual .ne. expected) then
13 write (*, '(A,I4,I4)') str, expected, actual
14 STOP 1
15 endif
16 end subroutine
18 implicit none
20 integer expected, expected_expr
21 integer output_vars, output_const, output_expr
22 integer op1, op2, mult
24 mult = 3
25 op1 = 3
26 op2 = 5
28 !!!! AND -> IAND
30 expected = IAND(op1, op2)
31 expected_expr = mult*expected
33 output_const = 3 .AND. 5
34 output_vars = op1 .AND. op2
35 output_expr = mult * (op1 .AND. op2)
37 call assert(expected, output_vars, "( ) and")
38 call assert(expected, output_const, "(c) and")
39 call assert(expected_expr, output_expr, "(x) and")
41 !!!! EQV -> NOT IEOR
43 expected = NOT(IEOR(op1, op2))
44 expected_expr = mult*expected
46 output_const = 3 .EQV. 5
47 output_vars = op1 .EQV. op2
48 output_expr = mult * (op1 .EQV. op2)
50 call assert(expected, output_vars, "( ) EQV")
51 call assert(expected, output_const, "(c) EQV")
52 call assert(expected_expr, output_expr, "(x) EQV")
54 !!!! NEQV -> IEOR
56 expected = IEOR(op1, op2)
57 expected_expr = mult*expected
59 output_const = 3 .NEQV. 5
60 output_vars = op1 .NEQV. op2
61 output_expr = mult * (op1 .NEQV. op2)
63 call assert(expected, output_vars, "( ) NEQV")
64 call assert(expected, output_const, "(c) NEQV")
65 call assert(expected_expr, output_expr, "(x) NEQV")
67 !!!! NOT -> NOT
69 expected = NOT(op2)
70 expected_expr = mult*expected
72 output_const = .NOT. 5
73 output_vars = .NOT. op2
74 output_expr = mult * (.NOT. op2)
76 call assert(expected, output_vars, "( ) NOT")
77 call assert(expected, output_const, "(c) NOT")
78 call assert(expected_expr, output_expr, "(x) NOT")
80 !!!! OR -> IOR
82 expected = IOR(op1, op2)
83 expected_expr = mult*expected
85 output_const = 3 .OR. 5
86 output_vars = op1 .OR. op2
87 output_expr = mult * (op1 .OR. op2)
89 call assert(expected, output_vars, "( ) OR")
90 call assert(expected, output_const, "(c) OR")
91 call assert(expected_expr, output_expr, "(x) OR")
93 !!!! XOR -> IEOR, not to be confused with .XOR.
95 expected = IEOR(op1, op2)
96 expected_expr = mult*expected
98 output_const = 3 .XOR. 5
99 output_vars = op1 .XOR. op2
100 output_expr = mult * (op1 .XOR. op2)
102 call assert(expected, output_vars, "( ) XOR")
103 call assert(expected, output_const, "(c) XOR")
104 call assert(expected_expr, output_expr, "(x) XOR")