xref: /llvm-project/flang/test/Lower/HLFIR/private-components.f90 (revision e45f6e93d0b90e917eff61ac104a673c52ee2322)
1! Test that private component names are mangled inside fir.record
2! in a way that allow components with the same name to be added in
3! type extensions.
4! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
5
6module name_clash
7  type:: t
8    integer, private :: i
9  end type
10  type(t), parameter :: cst = t(42)
11end module
12
13!CHECK-LABEL: func.func @_QPuser_clash(
14!CHECK-SAME: !fir.ref<!fir.type<_QFuser_clashTt2{t:!fir.type<_QMname_clashTt{_QMname_clashTt.i:i32}>,i:i32}>>
15!CHECK-SAME: !fir.ref<!fir.type<_QMname_clashTt{_QMname_clashTt.i:i32}>>
16subroutine user_clash(a, at)
17  use name_clash
18  type,extends(t) :: t2
19    integer :: i = 2
20  end type
21  type(t2) :: a, b
22  type(t) :: at
23  print *, a%i
24  print *, t2(t=at)
25  a = b
26end subroutine
27
28! CHECK-LABEL: func.func @_QPclash_with_intrinsic_module(
29! CHECK-SAME: !fir.ref<!fir.type<_QFclash_with_intrinsic_moduleTmy_class{ieee_class_type:!fir.type<_QMieee_arithmeticTieee_class_type{_QMieee_arithmeticTieee_class_type.which:i8}>,which:i8}>>
30subroutine clash_with_intrinsic_module(a)
31 use ieee_arithmetic
32 type, extends(ieee_class_type) :: my_class
33    integer(1) :: which
34 end type
35 type(my_class) :: a
36end subroutine
37