File: constant.f90

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (52 lines) | stat: -rw-r--r-- 3,281 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
! Test lowering of Constant<T>.
! RUN: bbc -emit-hlfir -o - %s 2>&1 | FileCheck %s

! CHECK-LABEL: func.func @_QPtest_constant_scalar()
subroutine test_constant_scalar()
  print *, (10., 20.)
  ! CHECK-DAG:  %[[VAL_0:.*]] = arith.constant 2.000000e+01 : f32
  ! CHECK-DAG:  %[[VAL_1:.*]] = arith.constant 1.000000e+01 : f32
  ! CHECK:  %[[VAL_7:.*]] = fir.undefined !fir.complex<4>
  ! CHECK:  %[[VAL_8:.*]] = fir.insert_value %[[VAL_7]], %[[VAL_1]], [0 : index] : (!fir.complex<4>, f32) -> !fir.complex<4>
  ! CHECK:  %[[VAL_9:.*]] = fir.insert_value %[[VAL_8]], %[[VAL_0]], [1 : index] : (!fir.complex<4>, f32) -> !fir.complex<4>
end subroutine

! CHECK-LABEL: func.func @_QPtest_constant_scalar_char()
subroutine test_constant_scalar_char()
  print *, "hello"
! CHECK:  %[[VAL_5:.*]] = fir.address_of(@[[name:.*]]) : !fir.ref<!fir.char<1,5>>
! CHECK:  %[[VAL_6:.*]] = arith.constant 5 : index
! 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>>)
end subroutine

! CHECK-LABEL: func.func @_QPtest_constant_array()
subroutine test_constant_array()
  print *, [1., 2., 3.]
! CHECK:  %[[VAL_5:.*]] = fir.address_of(@[[name:.*]]) : !fir.ref<!fir.array<3xf32>>
! CHECK:  %[[VAL_6:.*]] = arith.constant 3 : index
! CHECK:  %[[VAL_7:.*]] = fir.shape %[[VAL_6]] : (index) -> !fir.shape<1>
! 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>>)
end subroutine

! CHECK-LABEL: func.func @_QPtest_constant_array_char()
subroutine test_constant_array_char()
  print *, ["abc", "cde"]
! CHECK:  %[[VAL_5:.*]] = fir.address_of(@[[name:.*]]) : !fir.ref<!fir.array<2x!fir.char<1,3>>>
! CHECK:  %[[VAL_6:.*]] = arith.constant 2 : index
! CHECK:  %[[VAL_7:.*]] = arith.constant 3 : index
! CHECK:  %[[VAL_8:.*]] = fir.shape %[[VAL_6]] : (index) -> !fir.shape<1>
! 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>>>)
end subroutine

! CHECK-LABEL: func.func @_QPtest_constant_with_lower_bounds()
subroutine test_constant_with_lower_bounds()
  integer, parameter :: i(-1:0, -1:0) = reshape([1,2,3,4], shape=[2,2])
  print *, i
! CHECK:  %[[VAL_12:.*]] = fir.address_of(@_QQro[[name:.*]]) : !fir.ref<!fir.array<2x2xi32>>
! CHECK:  %[[VAL_13:.*]] = arith.constant 2 : index
! CHECK:  %[[VAL_14:.*]] = arith.constant 2 : index
! CHECK:  %[[VAL_15:.*]] = arith.constant -1 : index
! CHECK:  %[[VAL_16:.*]] = arith.constant -1 : index
! CHECK:  %[[VAL_17:.*]] = fir.shape_shift %[[VAL_15]], %[[VAL_13]], %[[VAL_16]], %[[VAL_14]] : (index, index, index, index) -> !fir.shapeshift<2>
! CHECK:  hlfir.declare %[[VAL_12]](%[[VAL_17]]) {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "_QQro[[name]]"} : (!fir.ref<!fir.array<2x2xi32>>, !fir.shapeshift<2>) -> (!fir.box<!fir.array<2x2xi32>>, !fir.ref<!fir.array<2x2xi32>>)
end subroutine