4 ! This ICE'd because the temporary-creation in the MVBITS call was wrong.
6 ! Contributed by Paul Richard Thomas <paul.richard.thomas@gmail.com>
14 x
= reshape ([((t (i
*j
, "a"),i
= 1,4), j
=1,3)], [4,3])
16 y
= reshape ([((t (i
*j
*2, "a"),i
= 1,4), j
=1,3)], [4,3])
17 call bar(y
, 4, 3, 1, -1, -4, -3)
18 if (any (x
%i
.ne
. y
%i
)) call abort
21 TYPE(t
) x(4, 3) ! No dependency at all
22 CALL MVBITS (x
%i
, 0, 6, x
%i
, 8)
25 SUBROUTINE bar (x
, NF4
, NF3
, NF1
, MF1
, MF4
, MF3
)
26 TYPE(t
) x(NF4
, NF3
) ! Dependency through variable indices
27 CALL MVBITS (x(NF4
:NF1
:MF1
, NF1
:NF3
)%i
, 1, &
28 6, x(-MF4
:-MF1
:-NF1
, -MF1
:-MF3
)%i
, 9)
32 ! { dg-prune-output "reading \[0-9\]+ bytes from a region" }