File: pointer-results-as-arguments.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 (85 lines) | stat: -rw-r--r-- 4,041 bytes parent folder | download | duplicates (4)
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
! Test passing pointers results to pointer dummy arguments
! RUN: bbc %s -o - | FileCheck %s

module presults
  interface
    subroutine bar_scalar(x)
      real, pointer :: x
    end subroutine
    subroutine bar(x)
      real, pointer :: x(:, :)
    end subroutine
    function get_scalar_pointer()
      real, pointer :: get_scalar_pointer
    end function
    function get_pointer()
      real, pointer :: get_pointer(:, :)
    end function
  end interface
  real, pointer :: x
  real, pointer :: xa(:, :)
contains

! CHECK-LABEL: test_scalar_null
subroutine test_scalar_null()
! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.ptr<f32>>
! CHECK: %[[VAL_1:.*]] = fir.zero_bits !fir.ptr<f32>
! CHECK: %[[VAL_2:.*]] = fir.embox %[[VAL_1]] : (!fir.ptr<f32>) -> !fir.box<!fir.ptr<f32>>
! CHECK: fir.store %[[VAL_2]] to %[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<f32>>>
! CHECK: fir.call @_QPbar_scalar(%[[VAL_0]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<f32>>>) -> ()
  call bar_scalar(null())
end subroutine

! CHECK-LABEL: test_scalar_null_mold
subroutine test_scalar_null_mold()
! CHECK: %[[VAL_3:.*]] = fir.alloca !fir.box<!fir.ptr<f32>>
! CHECK: %[[VAL_4:.*]] = fir.zero_bits !fir.ptr<f32>
! CHECK: %[[VAL_5:.*]] = fir.embox %[[VAL_4]] : (!fir.ptr<f32>) -> !fir.box<!fir.ptr<f32>>
! CHECK: fir.store %[[VAL_5]] to %[[VAL_3]] : !fir.ref<!fir.box<!fir.ptr<f32>>>
! CHECK: fir.call @_QPbar_scalar(%[[VAL_3]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<f32>>>) -> ()
  call bar_scalar(null(x))
end subroutine

! CHECK-LABEL: test_scalar_result
subroutine test_scalar_result()
! CHECK: %[[VAL_6:.*]] = fir.alloca !fir.box<!fir.ptr<f32>> {bindc_name = ".result"}
! CHECK: %[[VAL_7:.*]] = fir.call @_QPget_scalar_pointer() {{.*}}: () -> !fir.box<!fir.ptr<f32>>
! CHECK: fir.save_result %[[VAL_7]] to %[[VAL_6]] : !fir.box<!fir.ptr<f32>>, !fir.ref<!fir.box<!fir.ptr<f32>>>
! CHECK: fir.call @_QPbar_scalar(%[[VAL_6]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<f32>>>) -> ()
  call bar_scalar(get_scalar_pointer())
end subroutine

! CHECK-LABEL: test_null
subroutine test_null()
! CHECK: %[[VAL_8:.*]] = arith.constant 0 : index
! CHECK: %[[VAL_9:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
! CHECK: %[[VAL_10:.*]] = fir.zero_bits !fir.ptr<!fir.array<?x?xf32>>
! CHECK: %[[VAL_11:.*]] = fir.shape %[[VAL_8]], %[[VAL_8]] : (index, index) -> !fir.shape<2>
! CHECK: %[[VAL_12:.*]] = fir.embox %[[VAL_10]](%[[VAL_11]]) : (!fir.ptr<!fir.array<?x?xf32>>, !fir.shape<2>) -> !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
! CHECK: fir.store %[[VAL_12]] to %[[VAL_9]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>
! CHECK: fir.call @_QPbar(%[[VAL_9]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>) -> ()
  call bar(null())
end subroutine

! CHECK-LABEL: test_null_mold
subroutine test_null_mold()
! CHECK: %[[VAL_13:.*]] = arith.constant 0 : index
! CHECK: %[[VAL_14:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
! CHECK: %[[VAL_15:.*]] = fir.zero_bits !fir.ptr<!fir.array<?x?xf32>>
! CHECK: %[[VAL_16:.*]] = fir.shape %[[VAL_13]], %[[VAL_13]] : (index, index) -> !fir.shape<2>
! CHECK: %[[VAL_17:.*]] = fir.embox %[[VAL_15]](%[[VAL_16]]) : (!fir.ptr<!fir.array<?x?xf32>>, !fir.shape<2>) -> !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
! CHECK: fir.store %[[VAL_17]] to %[[VAL_14]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>
! CHECK: fir.call @_QPbar(%[[VAL_14]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>) -> ()
  call bar(null(xa))
end subroutine

! CHECK-LABEL: test_result
subroutine test_result()
! CHECK: %[[VAL_18:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.array<?x?xf32>>> {bindc_name = ".result"}
! CHECK: %[[VAL_19:.*]] = fir.call @_QPget_pointer() {{.*}}: () -> !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
! CHECK: fir.save_result %[[VAL_19]] to %[[VAL_18]] : !fir.box<!fir.ptr<!fir.array<?x?xf32>>>, !fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>
! CHECK: fir.call @_QPbar(%[[VAL_18]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>) -> ()
  call bar(get_pointer())
end subroutine

end module