LAA: improve code in getStrideFromPointer (NFC) (#124780)
[llvm-project.git] / flang / test / Evaluate / rewrite05.f90
blobf81974f24fd97173fce07d6864fb31afe7eae965
1 ! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
2 program main
3 type t
4 integer, allocatable :: component(:)
5 end type
6 type(t) :: x
7 call init(10)
8 !CHECK: PRINT *, [INTEGER(4)::int(lbound(x%component,dim=1,kind=8),kind=4)]
9 print *, lbound(x%component)
10 !CHECK: PRINT *, [INTEGER(4)::int(size(x%component,dim=1,kind=8)+lbound(x%component,dim=1,kind=8)-1_8,kind=4)]
11 print *, ubound(x%component)
12 !CHECK: PRINT *, int(size(x%component,dim=1,kind=8),kind=4)
13 print *, size(x%component)
14 !CHECK: PRINT *, 4_8*size(x%component,dim=1,kind=8)
15 print *, sizeof(x%component)
16 !CHECK: PRINT *, 1_4
17 print *, lbound(iota(10), 1)
18 !CHECK: PRINT *, ubound(iota(10_4),1_4)
19 print *, ubound(iota(10), 1)
20 !CHECK: PRINT *, size(iota(10_4))
21 print *, size(iota(10))
22 !CHECK: PRINT *, sizeof(iota(10_4))
23 print *, sizeof(iota(10))
24 contains
25 function iota(n) result(result)
26 integer, intent(in) :: n
27 integer, allocatable :: result(:)
28 result = [(j,j=1,n)]
29 end
30 subroutine init(n)
31 integer, intent(in) :: n
32 allocate(x%component(0:n-1))
33 end
34 end