LAA: improve code in getStrideFromPointer (NFC) (#124780)
[llvm-project.git] / flang / test / Evaluate / folding08.f90
blob53603474fe1c8834c52bbd00422f7e03eb9d720f
1 ! RUN: %python %S/test_folding.py %s %flang_fc1
2 ! Test folding of LBOUND and UBOUND
4 module m
5 real :: a3(42:52)
6 real :: empty(52:42, 2:3, 10:1)
7 integer, parameter :: lba3(*) = lbound(a3)
8 logical, parameter :: test_lba3 = all(lba3 == [42])
9 type :: t
10 real :: a
11 end type
12 type(t) :: ta(0:2)
13 character(len=2) :: ca(-1:1)
14 interface
15 function foo()
16 real :: foo(2:3,4:6)
17 end function
18 end interface
19 integer, parameter :: lbtadim = lbound(ta,1)
20 logical, parameter :: test_lbtadim = lbtadim == 0
21 integer, parameter :: ubtadim = ubound(ta,1)
22 logical, parameter :: test_ubtadim = ubtadim == 2
23 integer, parameter :: lbta1(*) = lbound(ta)
24 logical, parameter :: test_lbta1 = all(lbta1 == [0])
25 integer, parameter :: ubta1(*) = ubound(ta)
26 logical, parameter :: test_ubta1 = all(ubta1 == [2])
27 integer, parameter :: lbta2(*) = lbound(ta(:))
28 logical, parameter :: test_lbta2 = all(lbta2 == [1])
29 integer, parameter :: ubta2(*) = ubound(ta(:))
30 logical, parameter :: test_ubta2 = all(ubta2 == [3])
31 integer, parameter :: lbta3(*) = lbound(ta%a)
32 logical, parameter :: test_lbta3 = all(lbta3 == [1])
33 integer, parameter :: ubta3(*) = ubound(ta%a)
34 logical, parameter :: test_ubta3 = all(ubta3 == [3])
35 integer, parameter :: lbca1(*) = lbound(ca)
36 logical, parameter :: test_lbca1 = all(lbca1 == [-1])
37 integer, parameter :: ubca1(*) = ubound(ca)
38 logical, parameter :: test_ubca1 = all(ubca1 == [1])
39 integer, parameter :: lbca2(*) = lbound(ca(:)(1:1))
40 logical, parameter :: test_lbca2 = all(lbca2 == [1])
41 integer, parameter :: ubca2(*) = ubound(ca(:)(1:1))
42 logical, parameter :: test_ubca2 = all(ubca2 == [3])
43 integer, parameter :: lbfoo(*) = lbound(foo())
44 logical, parameter :: test_lbfoo = all(lbfoo == [1,1])
45 integer, parameter :: ubfoo(*) = ubound(foo())
46 logical, parameter :: test_ubfoo = all(ubfoo == [2,3])
48 integer, parameter :: lbs_empty(*) = lbound(empty)
49 logical, parameter :: test_lbs_empty = all(lbs_empty == [1, 2, 1])
50 integer, parameter :: ubs_empty(*) = ubound(empty)
51 logical, parameter :: test_ubs_empty = all(ubs_empty == [0, 3, 0])
52 logical, parameter :: test_lb_empty_dim = lbound(empty, 1) == 1
53 logical, parameter :: test_ub_empty_dim = ubound(empty, 1) == 0
54 contains
55 subroutine test(n1,a1,a2)
56 integer, intent(in) :: n1
57 real, intent(in) :: a1(1:n1), a2(0:*)
58 integer, parameter :: lba1(*) = lbound(a1)
59 logical, parameter :: test_lba1 = all(lba1 == [1])
60 integer, parameter :: lba2(*) = lbound(a2)
61 logical, parameter :: test_lba2 = all(lba2 == [0])
62 end subroutine
63 subroutine test2
64 real :: a(2:3,4:6)
65 associate (b => a)
66 block
67 integer, parameter :: lbb(*) = lbound(b)
68 logical, parameter :: test_lbb = all(lbb == [2,4])
69 integer, parameter :: ubb(*) = ubound(b)
70 logical, parameter :: test_ubb = all(ubb == [3,6])
71 end block
72 end associate
73 associate (b => a + 0)
74 block
75 integer, parameter :: lbb(*) = lbound(b)
76 logical, parameter :: test_lbb = all(lbb == [1,1])
77 integer, parameter :: ubb(*) = ubound(b)
78 logical, parameter :: test_ubb = all(ubb == [2,3])
79 end block
80 end associate
81 end subroutine
82 subroutine test3_bound_parameter
83 ! Test [ul]bound with parameter arrays
84 integer, parameter :: a1(1) = 0
85 integer, parameter :: lba1(*) = lbound(a1)
86 logical, parameter :: test_lba1 = all(lba1 == [1])
87 integer, parameter :: uba1(*) = ubound(a1)
88 logical, parameter :: test_uba1 = all(lba1 == [1])
90 integer, parameter :: a2(0:1) = 0
91 integer, parameter :: lba2(*) = lbound(a2)
92 logical, parameter :: test_lba2 = all(lba2 == [0])
93 integer, parameter :: uba2(*) = ubound(a2)
94 logical, parameter :: test_uba2 = all(uba2 == [1])
96 integer, parameter :: a3(-10:-5,1,4:6) = 0
97 integer, parameter :: lba3(*) = lbound(a3)
98 logical, parameter :: test_lba3 = all(lba3 == [-10, 1, 4])
99 integer, parameter :: uba3(*) = ubound(a3)
100 logical, parameter :: test_uba3 = all(uba3 == [-5, 1, 6])
102 ! Exercise with DIM=
103 logical, parameter :: test_lba3_dim = lbound(a3, 1) == -10 .and. &
104 lbound(a3, 2) == 1 .and. &
105 lbound(a3, 3) == 4
106 logical, parameter :: test_uba3_dim = ubound(a3, 1) == -5 .and. &
107 ubound(a3, 2) == 1 .and. &
108 ubound(a3, 3) == 6
109 end subroutine
110 subroutine test4_bound_parentheses
111 ! Test [ul]bound with (x) expressions
112 integer :: a1(1) = 0
113 logical, parameter :: test_lba1 = all(lbound((a1)) == [1])
114 logical, parameter :: test_uba1 = all(ubound((a1)) == [1])
115 integer :: a2(0:2) = 0
116 logical, parameter :: test_lba2 = all(lbound((a2)) == [1])
117 logical, parameter :: test_uba2 = all(ubound((a2)) == [3])
118 integer :: a3(-1:0) = 0
119 logical, parameter :: test_lba3 = all(lbound((a3)) == [1])
120 logical, parameter :: test_uba3 = all(ubound((a3)) == [2])
121 integer :: a4(-5:-1, 2:5) = 0
122 logical, parameter :: test_lba4 = all(lbound((a4)) == [1, 1])
123 logical, parameter :: test_uba4 = all(ubound((a4)) == [5, 4])
125 ! Exercise with DIM=
126 logical, parameter :: test_lba4_dim = lbound((a4), 1) == 1 .and. &
127 lbound((a4), 2) == 1
128 logical, parameter :: test_uba4_dim = ubound((a4), 1) == 5 .and. &
129 ubound((a4), 2) == 4
131 ! Exercise with parameter types
132 integer, parameter :: pa1(1) = 0
133 logical, parameter :: test_lbpa1 = all(lbound((pa1)) == [1])
134 logical, parameter :: test_ubpa1 = all(ubound((pa1)) == [1])
135 integer, parameter :: pa2(0:2) = 0
136 logical, parameter :: test_lbpa2 = all(lbound((pa2)) == [1])
137 logical, parameter :: test_ubpa2 = all(ubound((pa2)) == [3])
138 integer, parameter :: pa3(-1:0) = 0
139 logical, parameter :: test_lbpa3 = all(lbound((pa3)) == [1])
140 logical, parameter :: test_ubpa3 = all(ubound((pa3)) == [2])
141 integer, parameter :: pa4(-5:-1, 2:5) = 0
142 logical, parameter :: test_lbpa4 = all(lbound((pa4)) == [1, 1])
143 logical, parameter :: test_ubpa4 = all(ubound((pa4)) == [5, 4])
145 ! Exercise with DIM=
146 logical, parameter :: test_lbpa4_dim = lbound((pa4), 1) == 1 .and. &
147 lbound((pa4), 2) == 1
148 logical, parameter :: test_ubpa4_dim = ubound((pa4), 1) == 5 .and. &
149 ubound((pa4), 2) == 4
151 subroutine test5_max_ubound
152 ! Test maximum ubound value
153 integer(8), parameter :: I64_MAX = INT(z'7fffffffffffffff', kind=8)
154 integer, parameter :: a5(I64_MAX - 2 : I64_MAX) = [1, 2, 3]
155 logical, parameter :: test_uba5 = ubound(a5, 1, kind=8) == I64_MAX
156 end subroutine