Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / typeinfo02.f90
blob076f1b3499b62c5cfe09b2920f51ff515962578e
1 !RUN: bbc --dump-symbols %s | FileCheck %s
2 !RUN: %flang_fc1 -fdebug-dump-symbols %s | FileCheck %s
4 module m1
5 type base
6 contains
7 procedure :: wf => wf1
8 generic :: write(formatted) => wf
9 end type
10 type, extends(base) :: extended
11 contains
12 procedure :: wf => wf2
13 end type
14 contains
15 subroutine wf1(x,u,iot,v,iostat,iomsg)
16 class(base), intent(in) :: x
17 integer, intent(in) :: u
18 character(len=*), intent(in) :: iot
19 integer, intent(in) :: v(:)
20 integer, intent(out) :: iostat
21 character(len=*), intent(inout) :: iomsg
22 end subroutine
23 subroutine wf2(x,u,iot,v,iostat,iomsg)
24 class(extended), intent(in) :: x
25 integer, intent(in) :: u
26 character(len=*), intent(in) :: iot
27 integer, intent(in) :: v(:)
28 integer, intent(out) :: iostat
29 character(len=*), intent(inout) :: iomsg
30 end subroutine
31 end module
32 !CHECK: .s.base, SAVE, TARGET (CompilerCreated, ReadOnly): ObjectEntity type: TYPE(specialbinding) shape: 0_8:0_8 init:[specialbinding::specialbinding(which=5_1,isargdescriptorset=1_1,proc=wf1)]
33 !CHECK: .s.extended, SAVE, TARGET (CompilerCreated, ReadOnly): ObjectEntity type: TYPE(specialbinding) shape: 0_8:0_8 init:[specialbinding::specialbinding(which=5_1,isargdescriptorset=1_1,proc=wf2)]