5 ! The checks for assignments were too strict.
8 INTERFACE ASSIGNMENT(=)
10 REAL,INTENT(OUT
) :: a(1,*)
11 REAL,INTENT(IN
) :: b(:)
16 REAL,POINTER :: p(:,:),q(:)
23 INTERFACE ASSIGNMENT(=)
25 REAL,INTENT(OUT
),VOLATILE :: a(1,*)
26 REAL,INTENT(IN
) :: b(:)
31 REAL,POINTER :: p(:,:),q(:)
32 CALL s(p
,q
) ! { dg-error "requires an assumed-shape or pointer-array dummy" }
33 !TODO: The following is rightly rejected but the error message is misleading.
34 ! The actual reason is the mismatch between pointer array and VOLATILE
35 p
= q
! { dg-error "Incompatible ranks" }
40 INTERFACE ASSIGNMENT(=)
44 SUBROUTINE s(a
,b
) ! { dg-error "must not redefine an INTRINSIC type" }
45 REAL,INTENT(OUT
),VOLATILE :: a(1,*)
46 REAL,INTENT(IN
) :: b(:,:)
50 ! { dg-final { cleanup-modules "m1 m2 m3" } }