1 !RUN: %flang_fc1 -fdebug-dump-symbols %s | FileCheck %s
4 integer function ifunc(n
)
5 integer, intent(in
) :: n
14 integer(kind
=1), kind
:: kind
= 4
15 integer(kind
=2), len
:: len
= 1
16 integer(kind
=kind
) :: j
17 real(kind
=kind
) :: x(2,2)
18 complex(kind
=kind
) :: z
19 logical(kind
=kind
) :: t
20 character(kind
=5-kind
) :: c(2)
21 real(kind
=kind
), pointer :: xp(:,:)
22 procedure(ifunc
), pointer, nopass
:: ifptr
23 procedure(rfunc
), pointer, nopass
:: rp
24 procedure(real), pointer, nopass
:: xrp
28 procedure(ifunc
), pointer :: ifptr
! CHECK: ifptr, EXTERNAL, POINTER (Function, InDataStmt) size=24 offset=0: ProcEntity ifunc => ifunc
32 integer(kind
=1) :: j1
! CHECK: j1 (InDataStmt) size=1 offset=0: ObjectEntity type: INTEGER(1) init:66_1
36 integer :: jd
! CHECK: jd (InDataStmt) size=4 offset=0: ObjectEntity type: INTEGER(4) init:666_4
40 logical :: lv(2) ! CHECK: lv (InDataStmt) size=8 offset=0: ObjectEntity type: LOGICAL(4) shape: 1_8:2_8 init:[LOGICAL(4)::.false._4,.true._4]
45 real :: rm(2,2) ! CHECK: rm (InDataStmt) size=16 offset=0: ObjectEntity type: REAL(4) shape: 1_8:2_8,1_8:2_8 init:reshape([REAL(4)::1._4,2._4,3._4,4._4],shape=[2,2])
49 character(len
=8) :: ssd
! CHECK: ssd (InDataStmt) size=8 offset=0: ObjectEntity type: CHARACTER(8_4,1) init:"abcdefgh"
50 data ssd(1:4)/'abcd'/,ssd(5:8)/'efgh'/
53 complex(kind
=16) :: zv(-1:1) ! CHECK: zv (InDataStmt) size=96 offset=0: ObjectEntity type: COMPLEX(16) shape: -1_8:1_8 init:[COMPLEX(16)::(1._16,2._16),(3._16,4._16),(5._16,6._16)]
54 data (zv(j
), j
=1,0,-1)/(5,6),(3,4)/
55 data (zv(j
)%im
, zv(j
)%re
, j
=-1,-1,-9)/2,1/
57 real function rfunc2(x
)
62 procedure(rfunc
), pointer :: rfptr
! CHECK: rfptr, EXTERNAL, POINTER (Function, InDataStmt) size=24 offset=0: ProcEntity rfunc => rfunc2
66 real, target
, save :: arr(3,4) ! CHECK: arr, SAVE, TARGET size=48 offset=0: ObjectEntity type: REAL(4) shape: 1_8:3_8,1_8:4_8
67 real, pointer :: xpp(:,:) ! CHECK: xpp, POINTER (InDataStmt) size=72 offset=48: ObjectEntity type: REAL(4) shape: :,: init:arr
70 integer function ifunc2(n
)
71 integer, intent(in
) :: n
75 real, target
, save :: arr(3,4) ! CHECK: arr, SAVE, TARGET size=48 offset=0: ObjectEntity type: REAL(4) shape: 1_8:3_8,1_8:4_8
76 type(t1
) :: d1
= t1(1,reshape([1,2,3,4],[2,2]),(6.,7.),.false
.,'ab',arr
,ifunc2
,rfunc
,extrfunc
) ! CHECK: d1 size=168 offset=48: ObjectEntity type: TYPE(t1(kind=4_1,len=1_2)) init:t1(kind=4_1,len=1_2)(j=1_4,x=reshape([REAL(4)::1._4,2._4,3._4,4._4],shape=[2,2]),z=(6._4,7._4),t=.false._4,c=[CHARACTER(KIND=1,LEN=1)::"a","a"],xp=arr,ifptr=ifunc2,rp=rfunc,xrp=extrfunc)
77 type(t1(4,len
=1)) :: d2
= t1(4)(xrp
=extrfunc
,rp
=rfunc
,ifptr
=ifunc2
,xp
=arr
,c
='a&
78 &b',t
=.false
.,z
=(6.,7.),x
=reshape([1,2,3,4],[2,2]),j
=1) ! CHECK: d2 size=168 offset=216: ObjectEntity type: TYPE(t1(kind=4_1,len=1_2)) init:t1(kind=4_1,len=1_2)(j=1_4,x=reshape([REAL(4)::1._4,2._4,3._4,4._4],shape=[2,2]),z=(6._4,7._4),t=.false._4,c=[CHARACTER(KIND=1,LEN=1)::"a","a"],xp=arr,ifptr=ifunc2,rp=rfunc,xrp=extrfunc)
79 type(t1(2+2)) :: d3
! CHECK: d3 (InDataStmt) size=168 offset=384: ObjectEntity type: TYPE(t1(kind=4_1,len=1_2)) init:t1(kind=4_1,len=1_2)(j=1_4,x=reshape([REAL(4)::1._4,2._4,3._4,4._4],shape=[2,2]),z=(6._4,7._4),t=.false._4,c=[CHARACTER(KIND=1,LEN=1)::"a","a"],xp=arr,ifptr=ifunc2,rp=rfunc,xrp=extrfunc)
80 data d3
/t1(1,reshape([1,2,3,4],[2,2]),(6.,7.),.false
.,'ab',arr
,ifunc2
,rfunc
,extrfunc
)/
81 type(t1
) :: d4
! CHECK: d4 (InDataStmt) size=168 offset=552: ObjectEntity type: TYPE(t1(kind=4_1,len=1_2)) init:t1(kind=4_1,len=1_2)(j=1_4,x=reshape([REAL(4)::1._4,2._4,3._4,4._4],shape=[2,2]),z=(6._4,7._4),t=.false._4,c=[CHARACTER(KIND=1,LEN=1)::"a","a"],xp=arr,ifptr=ifunc2,rp=rfunc,xrp=extrfunc)
82 data d4
/t1(4)(xrp
=extrfunc
,rp
=rfunc
,ifptr
=ifunc2
,xp
=arr
,c
='ab',t
=.false
.,z
=(6&
83 &.,7.),x
=reshape([1,2,3,4],[2,2]),j
=1)/
84 type(t1
) :: d5
! CHECK: d5 (InDataStmt) size=168 offset=720: ObjectEntity type: TYPE(t1(kind=4_1,len=1_2)) init:t1(kind=4_1,len=1_2)(j=1_4,x=reshape([REAL(4)::1._4,2._4,3._4,4._4],shape=[2,2]),z=(6._4,7._4),t=.false._4,c=[CHARACTER(KIND=1,LEN=1)::"a","b"],xp=arr,ifptr=ifunc2,rp=rfunc,xrp=extrfunc)
85 data d5
%j
/1/,d5
%x
/1,2,3,4/,d5
%z
%re
/6./,d5
%z
%im
/7./,d5
%t
/.false
./,d5
%c(1:1)/'a'/,d5
%c(2:&
86 &2)/'b'/,d5
%xp
/arr
/,d5
%ifptr
/ifunc2
/,d5
%rp
/rfunc
/,d5
%xrp
/extrfunc
/
89 procedure(rfunc
), pointer :: pp
! CHECK: pp, EXTERNAL, POINTER (Function, InDataStmt) size=24 offset=0: ProcEntity rfunc => rfunc2