xref: /llvm-project/flang/test/Lower/HLFIR/constant.f90 (revision c4204c0b29a6721267b1bcbaeedd7b1118e42396)
1! Test lowering of Constant<T>.
2! RUN: bbc -emit-hlfir -o - %s 2>&1 | FileCheck %s
3
4! CHECK-LABEL: func.func @_QPtest_constant_scalar()
5subroutine test_constant_scalar()
6  print *, (10., 20.)
7  ! CHECK-DAG:  %[[VAL_0:.*]] = arith.constant 2.000000e+01 : f32
8  ! CHECK-DAG:  %[[VAL_1:.*]] = arith.constant 1.000000e+01 : f32
9  ! CHECK:  %[[VAL_7:.*]] = fir.undefined complex<f32>
10  ! CHECK:  %[[VAL_8:.*]] = fir.insert_value %[[VAL_7]], %[[VAL_1]], [0 : index] : (complex<f32>, f32) -> complex<f32>
11  ! CHECK:  %[[VAL_9:.*]] = fir.insert_value %[[VAL_8]], %[[VAL_0]], [1 : index] : (complex<f32>, f32) -> complex<f32>
12end subroutine
13
14! CHECK-LABEL: func.func @_QPtest_constant_scalar_char()
15subroutine test_constant_scalar_char()
16  print *, "hello"
17! CHECK:  %[[VAL_5:.*]] = fir.address_of(@[[name:.*]]) : !fir.ref<!fir.char<1,5>>
18! CHECK:  %[[VAL_6:.*]] = arith.constant 5 : index
19! CHECK:  hlfir.declare %[[VAL_5]] typeparams %[[VAL_6]] {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "[[name]]"} : (!fir.ref<!fir.char<1,5>>, index) -> (!fir.ref<!fir.char<1,5>>, !fir.ref<!fir.char<1,5>>)
20end subroutine
21
22! CHECK-LABEL: func.func @_QPtest_constant_array()
23subroutine test_constant_array()
24  print *, [1., 2., 3.]
25! CHECK:  %[[VAL_5:.*]] = fir.address_of(@[[name:.*]]) : !fir.ref<!fir.array<3xf32>>
26! CHECK:  %[[VAL_6:.*]] = arith.constant 3 : index
27! CHECK:  %[[VAL_7:.*]] = fir.shape %[[VAL_6]] : (index) -> !fir.shape<1>
28! CHECK:  hlfir.declare %[[VAL_5]](%[[VAL_7]]) {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "[[name]]"} : (!fir.ref<!fir.array<3xf32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<3xf32>>, !fir.ref<!fir.array<3xf32>>)
29end subroutine
30
31! CHECK-LABEL: func.func @_QPtest_constant_array_char()
32subroutine test_constant_array_char()
33  print *, ["abc", "cde"]
34! CHECK:  %[[VAL_5:.*]] = fir.address_of(@[[name:.*]]) : !fir.ref<!fir.array<2x!fir.char<1,3>>>
35! CHECK:  %[[VAL_6:.*]] = arith.constant 2 : index
36! CHECK:  %[[VAL_7:.*]] = arith.constant 3 : index
37! CHECK:  %[[VAL_8:.*]] = fir.shape %[[VAL_6]] : (index) -> !fir.shape<1>
38! CHECK:  hlfir.declare %[[VAL_5]](%[[VAL_8]]) typeparams %[[VAL_7]] {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "[[name]]"} : (!fir.ref<!fir.array<2x!fir.char<1,3>>>, !fir.shape<1>, index) -> (!fir.ref<!fir.array<2x!fir.char<1,3>>>, !fir.ref<!fir.array<2x!fir.char<1,3>>>)
39end subroutine
40
41! CHECK-LABEL: func.func @_QPtest_constant_with_lower_bounds()
42subroutine test_constant_with_lower_bounds()
43  integer, parameter :: i(-1:0, -1:0) = reshape([1,2,3,4], shape=[2,2])
44  print *, i
45! CHECK:  %[[VAL_12:.*]] = fir.address_of(@_QFtest_constant_with_lower_boundsECi) : !fir.ref<!fir.array<2x2xi32>>
46! CHECK:  %[[VAL_13:.*]] = arith.constant -1 : index
47! CHECK:  %[[VAL_14:.*]] = arith.constant 2 : index
48! CHECK:  %[[VAL_15:.*]] = arith.constant -1 : index
49! CHECK:  %[[VAL_16:.*]] = arith.constant 2 : index
50! CHECK:  %[[VAL_17:.*]] = fir.shape_shift %[[VAL_13]], %[[VAL_14]], %[[VAL_15]], %[[VAL_16]] : (index, index, index, index) -> !fir.shapeshift<2>
51! CHECK:  hlfir.declare %[[VAL_12]](%[[VAL_17]]) {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "_QFtest_constant_with_lower_boundsECi"} : (!fir.ref<!fir.array<2x2xi32>>, !fir.shapeshift<2>) -> (!fir.box<!fir.array<2x2xi32>>, !fir.ref<!fir.array<2x2xi32>>)
52end subroutine
53