File: allocatable-and-pointer-subparts.f90

package info (click to toggle)
llvm-toolchain-19 1%3A19.1.7-3~deb12u1
  • links: PTS, VCS
  • area: main
  • in suites: bookworm-proposed-updates
  • size: 1,998,492 kB
  • sloc: cpp: 6,951,680; ansic: 1,486,157; asm: 913,598; python: 232,024; f90: 80,126; objc: 75,281; lisp: 37,276; pascal: 16,990; sh: 10,009; ml: 5,058; perl: 4,724; awk: 3,523; makefile: 3,167; javascript: 2,504; xml: 892; fortran: 664; cs: 573
file content (54 lines) | stat: -rw-r--r-- 2,991 bytes parent folder | download | duplicates (10)
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
! Test lowering of allocatable and pointer sub-part reference to HLFIR
! As opposed to whole reference, a pointer/allocatable dereference must
! be inserted and addressed in a following hlfir.designate to address
! the sub-part.

! RUN: bbc -emit-hlfir -o - %s -I nw | FileCheck %s

module m
  type t1
    real :: x
  end type
  type t2
    type(t1), pointer :: p
  end type
  type t3
    character(:), allocatable :: a(:)
  end type
end module

subroutine test_pointer_component_followed_by_component_ref(x)
  use m
  type(t2) :: x
  call takes_real(x%p%x)
end subroutine
! CHECK-LABEL: func.func @_QPtest_pointer_component_followed_by_component_ref(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare %{{.*}} {{.*}}Ex
! CHECK:  %[[VAL_2:.*]] = hlfir.designate %[[VAL_1]]#0{"p"}   {fortran_attrs = #fir.var_attrs<pointer>} : (!fir.ref<!fir.type<_QMmTt2{p:!fir.box<!fir.ptr<!fir.type<_QMmTt1{x:f32}>>>}>>) -> !fir.ref<!fir.box<!fir.ptr<!fir.type<_QMmTt1{x:f32}>>>>
! CHECK:  %[[VAL_3:.*]] = fir.load %[[VAL_2]] : !fir.ref<!fir.box<!fir.ptr<!fir.type<_QMmTt1{x:f32}>>>>
! CHECK:  %[[VAL_4:.*]] = fir.box_addr %[[VAL_3:.*]] : (!fir.box<!fir.ptr<!fir.type<_QMmTt1{x:f32}>>>) -> !fir.ptr<!fir.type<_QMmTt1{x:f32}>>
! CHECK:  hlfir.designate %[[VAL_4]]{"x"}   : (!fir.ptr<!fir.type<_QMmTt1{x:f32}>>) -> !fir.ref<f32>

subroutine test_symbol_followed_by_ref(x)
  character(:), allocatable :: x(:)
  call test_char(x(10))
end subroutine
! CHECK-LABEL: func.func @_QPtest_symbol_followed_by_ref(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare %{{.*}} {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = {{.*}}Ex"
! CHECK:  %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>>
! CHECK:  %[[VAL_3:.*]] = fir.box_elesize %[[VAL_2]] : (!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>) -> index
! CHECK:  %[[VAL_4:.*]] = arith.constant 10 : index
! CHECK:  %[[VAL_5:.*]] = hlfir.designate %[[VAL_2]] (%[[VAL_4]])  typeparams %[[VAL_3]] : (!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>, index, index) -> !fir.boxchar<1>

subroutine test_component_followed_by_ref(x)
  use m
  type(t3) :: x
  call test_char(x%a(10))
end subroutine
! CHECK-LABEL: func.func @_QPtest_component_followed_by_ref(
! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare %{{.*}} {{.*}}Ex
! CHECK:  %[[VAL_2:.*]] = hlfir.designate %[[VAL_1]]#0{"a"}   {fortran_attrs = #fir.var_attrs<allocatable>} : (!fir.ref<!fir.type<_QMmTt3{a:!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>}>>) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>>
! CHECK:  %[[VAL_3:.*]] = fir.load %[[VAL_2]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>>
! CHECK:  %[[VAL_4:.*]] = fir.box_elesize %[[VAL_3]] : (!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>) -> index
! CHECK:  %[[VAL_5:.*]] = arith.constant 10 : index
! CHECK:  %[[VAL_6:.*]] = hlfir.designate %[[VAL_3]] (%[[VAL_5]])  typeparams %[[VAL_4]] : (!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>, index, index) -> !fir.boxchar<1>