File: dec_bitwise_ops_1.f90

package info (click to toggle)
gcc-arm-none-eabi 15%3A14.2.rel1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,099,328 kB
  • sloc: cpp: 3,627,108; ansic: 2,571,498; ada: 834,230; f90: 235,082; makefile: 79,231; asm: 74,984; xml: 51,692; exp: 39,736; sh: 33,298; objc: 15,629; python: 15,069; fortran: 14,429; pascal: 7,003; awk: 5,070; perl: 3,106; ml: 285; lisp: 253; lex: 204; haskell: 135
file content (106 lines) | stat: -rw-r--r-- 2,569 bytes parent folder | download | duplicates (3)
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
! { dg-do run }
! { dg-options "-fdec" }
!
! Runtime tests to verify logical-to-bitwise operations perform as expected
! with -fdec.
!

subroutine assert(expected, actual, str)
  implicit none
  character(*), intent(in) :: str
  integer, intent(in)      :: expected, actual
  if (actual .ne. expected) then
    write (*, '(A,I4,I4)') str, expected, actual
    STOP 1
  endif
end subroutine

implicit none

integer expected, expected_expr
integer output_vars, output_const, output_expr
integer op1, op2, mult

mult = 3
op1 = 3
op2 = 5

!!!! AND -> IAND

expected      = IAND(op1, op2)
expected_expr = mult*expected

output_const  = 3 .AND. 5
output_vars   = op1 .AND. op2
output_expr   = mult * (op1 .AND. op2)

call assert(expected, output_vars,      "( ) and")
call assert(expected, output_const,     "(c) and")
call assert(expected_expr, output_expr, "(x) and")

!!!! EQV -> NOT IEOR

expected   = NOT(IEOR(op1, op2))
expected_expr = mult*expected

output_const    = 3 .EQV. 5
output_vars     = op1 .EQV. op2
output_expr     = mult * (op1 .EQV. op2)

call assert(expected, output_vars,       "( ) EQV")
call assert(expected, output_const,      "(c) EQV")
call assert(expected_expr, output_expr,  "(x) EQV")

!!!! NEQV -> IEOR

expected   = IEOR(op1, op2)
expected_expr = mult*expected

output_const    = 3 .NEQV. 5
output_vars     = op1 .NEQV. op2
output_expr     = mult * (op1 .NEQV. op2)

call assert(expected, output_vars,       "( ) NEQV")
call assert(expected, output_const,      "(c) NEQV")
call assert(expected_expr, output_expr,  "(x) NEQV")

!!!! NOT -> NOT

expected   = NOT(op2)
expected_expr = mult*expected

output_const    = .NOT. 5
output_vars     = .NOT. op2
output_expr     = mult * (.NOT. op2)

call assert(expected, output_vars,       "( ) NOT")
call assert(expected, output_const,      "(c) NOT")
call assert(expected_expr, output_expr,  "(x) NOT")

!!!! OR -> IOR

expected   = IOR(op1, op2)
expected_expr = mult*expected

output_const    = 3 .OR. 5
output_vars     = op1 .OR. op2
output_expr     = mult * (op1 .OR. op2)

call assert(expected, output_vars,       "( ) OR")
call assert(expected, output_const,      "(c) OR")
call assert(expected_expr, output_expr,  "(x) OR")

!!!! XOR -> IEOR, not to be confused with .XOR.

expected  = IEOR(op1, op2)
expected_expr = mult*expected

output_const    = 3 .XOR. 5
output_vars     = op1 .XOR. op2
output_expr     = mult * (op1 .XOR. op2)

call assert(expected, output_vars,       "( ) XOR")
call assert(expected, output_const,      "(c) XOR")
call assert(expected_expr, output_expr,  "(x) XOR")

end