Fix compilation failure with C++98 compilers
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr82253.f90
blob4dc681012a0f98d3c81c1190b5cacbc546396a73
1 ! PR middle-end/82253
2 ! { dg-do compile { target fortran_real_16 } }
3 ! { dg-options "-Og" }
5 module pr82253
6 implicit none
7 private
8 public :: static_type
9 type, public :: T
10 procedure(), nopass, pointer :: testProc => null()
11 end type
12 type, public :: S
13 complex(kind=16), pointer :: ptr
14 end type
15 type(T), target :: type_complex32
16 interface static_type
17 module procedure foo
18 end interface
19 interface
20 subroutine bar (testProc)
21 procedure(), optional :: testProc
22 end subroutine
23 end interface
24 contains
25 function foo (self) result(res)
26 complex(kind=16) :: self
27 type(T), pointer :: res
28 call bar (testProc = baz)
29 end function
30 subroutine baz (buffer, status)
31 character(len=*) :: buffer
32 integer(kind=4) :: status
33 complex(kind=16), target :: obj
34 type(S) :: self
35 integer(kind=1), parameter :: zero(storage_size(obj)/8) = 0
36 obj = transfer (zero, obj)
37 self%ptr => obj
38 write (buffer, *, iostat=status) self%ptr, '#'
39 end subroutine
40 end module pr82253