blob: b82564ff4ca8a3c3ef527a0e1168e083c2451e9b (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
|
! { dg-do compile }
!
! PR 41978: [F03] ICE in gfc_conv_expr_descriptor for array PPC assignment
!
! Contributed by Daniel Kraft <domob@gcc.gnu.org>
MODULE m
IMPLICIT NONE
TYPE t
PROCEDURE(myproc), POINTER, PASS :: myproc
END TYPE t
CONTAINS
INTEGER FUNCTION myproc (me)
CLASS(t), INTENT(IN) :: me
myproc = 42
END FUNCTION myproc
END MODULE m
PROGRAM main
USE m
IMPLICIT NONE
TYPE(t) :: arr(2)
arr%myproc => myproc ! { dg-error "must not have the POINTER attribute" }
END PROGRAM main
! { dg-final { cleanup-modules "m" } }
|