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