xref: /llvm-project/flang/test/Semantics/associate02.f90 (revision 16c4b320fe9544f9556c0d1d733f5c50f1ba0da3)
1! RUN: %flang_fc1 -fdebug-unparse  %s  2>&1 | FileCheck %s
2! Sometimes associations with named constants involving non-default
3! lower bounds expose those bounds to LBOUND()/UBOUND(), sometimes
4! they do not.
5subroutine s(n)
6  integer, intent(in) :: n
7  type t
8    real component(0:1,2:3)
9  end type
10  real, parameter :: abcd(2,2) = reshape([1.,2.,3.,4.], shape(abcd))
11  real, parameter :: namedConst1(-1:0,-2:-1) = abcd
12  type(t), parameter :: namedConst2 = t(abcd)
13  type(t), parameter :: namedConst3(2:3,3:4) = reshape([(namedConst2,j=1,size(namedConst3))], shape(namedConst3))
14!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
15  print *, lbound(abcd), ubound(abcd), shape(abcd)
16!CHECK: PRINT *, [INTEGER(4)::-1_4,-2_4], [INTEGER(4)::0_4,-1_4], [INTEGER(4)::2_4,2_4]
17  print *, lbound(namedConst1), ubound(namedConst1), shape(namedConst1)
18!CHECK: PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
19  print *, lbound(namedConst2%component), ubound(namedConst2%component), shape(namedConst2%component)
20!CHECK: PRINT *, [INTEGER(4)::2_4,3_4], [INTEGER(4)::3_4,4_4], [INTEGER(4)::2_4,2_4]
21  print *, lbound(namedConst3), ubound(namedConst3), shape(namedConst3)
22!CHECK: PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
23  print *, lbound(namedConst3(n,n)%component), ubound(namedConst3(n,n)%component), shape(namedConst3(n,n)%component)
24!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
25  print *, lbound(namedConst3%component(0,2)), ubound(namedConst3%component(0,2)), shape(namedConst3%component(0,2))
26  associate (a => abcd)
27!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
28    print *, lbound(a), ubound(a), shape(a)
29  end associate
30  associate (a => namedConst1)
31!CHECK:  PRINT *, [INTEGER(4)::-1_4,-2_4], [INTEGER(4)::0_4,-1_4], [INTEGER(4)::2_4,2_4]
32    print *, lbound(a), ubound(a), shape(a)
33  end associate
34  associate (a => (namedConst1))
35!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
36    print *, lbound(a), ubound(a), shape(a)
37  end associate
38  associate (a => namedConst1 * 2.)
39!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
40    print *, lbound(a), ubound(a), shape(a)
41  end associate
42  associate (a => namedConst2%component)
43!CHECK:  PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
44    print *, lbound(a), ubound(a), shape(a)
45  end associate
46  associate (a => (namedConst2%component))
47!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
48    print *, lbound(a), ubound(a), shape(a)
49  end associate
50  associate (a => namedConst2%component * 2.)
51!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
52    print *, lbound(a), ubound(a), shape(a)
53  end associate
54  associate (a => namedConst3)
55!CHECK:  PRINT *, [INTEGER(4)::2_4,3_4], [INTEGER(4)::3_4,4_4], [INTEGER(4)::2_4,2_4]
56    print *, lbound(a), ubound(a), shape(a)
57  end associate
58  associate (a => (namedConst3))
59!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
60    print *, lbound(a), ubound(a), shape(a)
61  end associate
62  associate (a => namedConst3(n,n)%component)
63!CHECK:  PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
64    print *, lbound(a), ubound(a), shape(a)
65  end associate
66  associate (a => (namedConst3(n,n)%component))
67!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
68    print *, lbound(a), ubound(a), shape(a)
69  end associate
70  associate (a => namedConst3(n,n)%component * 2.)
71!CHECK:  PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
72    print *, lbound(a), ubound(a), shape(a)
73  end associate
74  associate (a => namedConst3%component(0,2))
75!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
76    print *, lbound(a), ubound(a), shape(a)
77  end associate
78end
79