2 ! { dg-options "-std=f2003 -fall-intrinsics" }
11 integer, pointer :: point
14 type(myT
), pointer :: t
28 if(t2
%point
/= 7) call abort()
31 integer, pointer,intent(in
) :: p
32 type(myT
), pointer, intent(in
) :: t
33 integer, pointer :: tmp
34 if(.not
.associated(p
)) return
35 if(p
/= 33) call abort()
37 if (associated(t
)) then
38 ! allocating is valid as we don't change the status
39 ! of the pointer "t", only of it's target
41 if(.not
.associated(t
%point
)) call abort()
42 if(t
%point
/= 55) call abort()
47 t
%point
=> null(t
%point
)
51 if(t
%point
/= 27) call abort()
52 if(t
%x
/= -15) call abort()
54 if(t
%x
/= 32) call abort()
55 if(t
%point
/= -98) call abort()
58 if(p
/= 5) call abort()
61 integer, intent(out
) :: v
65 type(myT
), intent(inout
) :: comp
66 if(comp
%x
/= -15) call abort()
67 if(comp
%point
/= 27) call abort()
71 subroutine nonpointer(t
)
72 type(myT
), intent(in
) :: t
73 if(t
%x
/= 5 ) call abort()
74 if(t
%point
/= 42) call abort()
76 end subroutine nonpointer