File: call-by-value.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 (96 lines) | stat: -rw-r--r-- 4,329 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
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
! Test for PassBy::Value
! RUN: bbc -emit-fir %s -o - | FileCheck %s

!CHECK-LABEL: func @_QQmain()
!CHECK: %[[LOGICAL:.*]] = fir.alloca !fir.logical<1>
!CHECK: %false = arith.constant false
!CHECK: %[[VALUE:.*]] = fir.convert %false : (i1) -> !fir.logical<1>
!CHECK: fir.store %[[VALUE]] to %[[LOGICAL]]
!CHECK: %[[LOAD:.*]] = fir.load %[[LOGICAL]]
!CHECK: fir.call @omp_set_nested(%[[LOAD]]) {{.*}}: {{.*}}

program call_by_value
  use iso_c_binding, only: c_bool
  interface
     subroutine omp_set_nested(enable) bind(c)
       import c_bool
       logical(c_bool), value :: enable
     end subroutine omp_set_nested
  end interface

  logical(c_bool) do_nested
  do_nested = .FALSE.
  call omp_set_nested(do_nested)
end program call_by_value

! CHECK-LABEL: func.func @test_integer_value(
! CHECK-SAME:                                %[[VAL_0:.*]]: i32 {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_integer_value"} {
! CHECK:         %[[VAL_1:.*]] = fir.alloca i32
! CHECK:         fir.store %[[VAL_0]] to %[[VAL_1]] : !fir.ref<i32>
! CHECK:         fir.call @_QPinternal_call(%[[VAL_1]]) {{.*}}: (!fir.ref<i32>) -> ()
! CHECK:         return
! CHECK:       }

subroutine test_integer_value(x) bind(c)
  integer, value :: x
  call internal_call(x)
end

! CHECK-LABEL: func.func @test_real_value(
! CHECK-SAME:                             %[[VAL_0:.*]]: f32 {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_real_value"} {
! CHECK:         %[[VAL_1:.*]] = fir.alloca f32
! CHECK:         fir.store %[[VAL_0]] to %[[VAL_1]] : !fir.ref<f32>
! CHECK:         fir.call @_QPinternal_call2(%[[VAL_1]]) {{.*}}: (!fir.ref<f32>) -> ()
! CHECK:         return
! CHECK:       }

subroutine test_real_value(x) bind(c)
  real, value :: x
  call internal_call2(x)
end

! CHECK-LABEL: func.func @test_complex_value(
! CHECK-SAME:                                %[[VAL_0:.*]]: !fir.complex<4> {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_complex_value"} {
! CHECK:         %[[VAL_1:.*]] = fir.alloca !fir.complex<4>
! CHECK:         fir.store %[[VAL_0]] to %[[VAL_1]] : !fir.ref<!fir.complex<4>>
! CHECK:         fir.call @_QPinternal_call3(%[[VAL_1]]) {{.*}}: (!fir.ref<!fir.complex<4>>) -> ()
! CHECK:         return
! CHECK:       }

subroutine test_complex_value(x) bind(c)
  complex, value :: x
  call internal_call3(x)
end

! CHECK-LABEL:   func.func @test_char_value(
! CHECK-SAME:                               %[[VAL_0:.*]]: !fir.boxchar<1> {fir.bindc_name = "x"}) attributes {fir.bindc_name = "test_char_value"} {
! CHECK:           %[[VAL_1:.*]]:2 = fir.unboxchar %[[VAL_0]] : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
! CHECK:           %[[VAL_2:.*]] = arith.constant 1 : index
! CHECK:           %[[VAL_3:.*]] = fir.convert %[[VAL_1]]#0 : (!fir.ref<!fir.char<1,?>>) -> !fir.ref<!fir.char<1>>
! CHECK:           %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.ref<!fir.char<1>>) -> !fir.ref<!fir.char<1,?>>
! CHECK:           %[[VAL_5:.*]] = fir.emboxchar %[[VAL_4]], %[[VAL_2]] : (!fir.ref<!fir.char<1,?>>, index) -> !fir.boxchar<1>
! CHECK:           fir.call @_QPinternal_call4(%[[VAL_5]]) fastmath<contract> : (!fir.boxchar<1>) -> ()
! CHECK:           return
! CHECK:         }

subroutine test_char_value(x) bind(c)
  character(1), value :: x
  call internal_call4(x)
end

! CHECK-LABEL: func.func @_QPtest_cptr_value(
! CHECK-SAME:                                %[[VAL_0:.*]]: !fir.ref<i64> {fir.bindc_name = "x"}) {
! CHECK:         %[[VAL_1:.*]] = fir.alloca !fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>
! CHECK:         %[[VAL_2:.*]] = fir.field_index __address, !fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>
! CHECK:         %[[VAL_3:.*]] = fir.coordinate_of %[[VAL_1]], %[[VAL_2]] : (!fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>, !fir.field) -> !fir.ref<i64>
! CHECK:         %[[VAL_4:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<i64>) -> i64
! CHECK:         fir.store %[[VAL_4]] to %[[VAL_3]] : !fir.ref<i64>
! CHECK:         fir.call @_QPinternal_call5(%[[VAL_1]]) {{.*}}: (!fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>) -> ()
! CHECK:         return
! CHECK:       }

subroutine test_cptr_value(x)
  use iso_c_binding
  type(c_ptr), value :: x
  call internal_call5(x)
end