File: associate-construct.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 (97 lines) | stat: -rw-r--r-- 5,162 bytes parent folder | download | duplicates (7)
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
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
! Test lowering of associate construct to HLFIR
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s

subroutine associate_expr(x)
  integer :: x(:)
  associate(y => x + 42)
    print *, y
  end associate
end subroutine
! CHECK-LABEL: func.func @_QPassociate_expr(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
! CHECK:  %[[VAL_3:.*]] = arith.constant 0 : index
! CHECK:  %[[VAL_4:.*]]:3 = fir.box_dims %[[VAL_1]]#0, %[[VAL_3]] : (!fir.box<!fir.array<?xi32>>, index) -> (index, index, index)
! CHECK:  %[[VAL_6:.*]] = hlfir.elemental {{.*}}
! CHECK:  %[[VAL_11:.*]]:3 = hlfir.associate %[[VAL_6]]{{.*}}
! CHECK:  %[[VAL_13:.*]] = fir.shape %[[VAL_4]]#1 : (index) -> !fir.shape<1>
! CHECK:  %[[VAL_14:.*]]:2 = hlfir.declare %[[VAL_11]]#1(%[[VAL_13]]) {uniq_name = "_QFassociate_exprEy"} : (!fir.ref<!fir.array<?xi32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.ref<!fir.array<?xi32>>)
! CHECK:  fir.call @_FortranAioEndIoStatement
! CHECK:  hlfir.end_associate %[[VAL_11]]#1, %[[VAL_11]]#2 : !fir.ref<!fir.array<?xi32>>, i1

subroutine associate_var(x)
  integer :: x
  associate(y => x)
    print *, y
  end associate
end subroutine
! CHECK-LABEL: func.func @_QPassociate_var(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
! CHECK:  %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_1]]#1 {uniq_name = "_QFassociate_varEy"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
! CHECK:  fir.call @_FortranAioEndIoStatement
! CHECK-NEXT:  return

subroutine associate_pointer(x)
  integer, pointer, contiguous :: x(:)
  ! Check that "y" has the target attribute.
  associate(y => x)
    print *, y
  end associate
end subroutine
! CHECK-LABEL: func.func @_QPassociate_pointer(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
! CHECK:  %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>>
! CHECK:  %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.ptr<!fir.array<?xi32>>>) -> !fir.ptr<!fir.array<?xi32>>
! CHECK:  %[[VAL_4:.*]] = arith.constant 0 : index
! CHECK:  %[[VAL_5:.*]]:3 = fir.box_dims %[[VAL_2]], %[[VAL_4]] : (!fir.box<!fir.ptr<!fir.array<?xi32>>>, index) -> (index, index, index)
! CHECK:  %[[VAL_6:.*]] = fir.shape_shift %[[VAL_5]]#0, %[[VAL_5]]#1 : (index, index) -> !fir.shapeshift<1>
! CHECK:  %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_3]](%[[VAL_6]]) {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFassociate_pointerEy"} : (!fir.ptr<!fir.array<?xi32>>, !fir.shapeshift<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.ptr<!fir.array<?xi32>>)
! CHECK:  fir.call @_FortranAioEndIoStatement
! CHECK-NEXT:  return

subroutine associate_allocatable(x)
  integer, allocatable :: x(:)
  associate(y => x)
    print *, y
  end associate
end subroutine
! CHECK-LABEL: func.func @_QPassociate_allocatable(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
! CHECK:  %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
! CHECK:  %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>) -> !fir.heap<!fir.array<?xi32>>
! CHECK:  %[[VAL_4:.*]] = arith.constant 0 : index
! CHECK:  %[[VAL_5:.*]]:3 = fir.box_dims %[[VAL_2]], %[[VAL_4]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>, index) -> (index, index, index)
! CHECK:  %[[VAL_6:.*]] = fir.shape_shift %[[VAL_5]]#0, %[[VAL_5]]#1 : (index, index) -> !fir.shapeshift<1>
! CHECK:  %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_3]](%[[VAL_6]]) {uniq_name = "_QFassociate_allocatableEy"} : (!fir.heap<!fir.array<?xi32>>, !fir.shapeshift<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.heap<!fir.array<?xi32>>)
! CHECK:  fir.call @_FortranAioEndIoStatement
! CHECK-NEXT:  return

subroutine associate_optional(x)
  integer, optional :: x(:)
  ! Check that "y" is not given the optional attribute: x must be present as per
  ! Fortran 2018 11.1.3.2 point 4.
  associate(y => x)
    print *, y
  end associate
end subroutine
! CHECK-LABEL: func.func @_QPassociate_optional(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
! CHECK:  %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_1]]#1 {uniq_name = "_QFassociate_optionalEy"} : (!fir.box<!fir.array<?xi32>>) -> (!fir.box<!fir.array<?xi32>>, !fir.box<!fir.array<?xi32>>)
! CHECK:  fir.call @_FortranAioEndIoStatement
! CHECK-NEXT:  return

subroutine associate_pointer_section(x)
  integer , pointer, contiguous :: x(:)
  associate (y => x(1:20:1))
    print *, y
  end associate
end subroutine
! CHECK-LABEL: func.func @_QPassociate_pointer_section(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare {{.*}}Ex"
! CHECK:  %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xi32>>>>
! CHECK:  %[[VAL_4:.*]] = arith.constant 20 : index
! CHECK:  %[[VAL_6:.*]] = arith.constant 20 : index
! CHECK:  %[[VAL_8:.*]] = hlfir.designate %[[VAL_2]]{{.*}}
! CHECK:  %[[VAL_9:.*]] = fir.shape %[[VAL_6]] : (index) -> !fir.shape<1>
! CHECK:  %[[VAL_10:.*]]:2 = hlfir.declare %[[VAL_8]](%[[VAL_9]]) {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFassociate_pointer_sectionEy"} : (!fir.ref<!fir.array<20xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<20xi32>>, !fir.ref<!fir.array<20xi32>>)
! CHECK:  fir.call @_FortranAioEndIoStatement
! CHECK-NEXT:  return