PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / internal_pack_9.f90
blob9ce53f443543e9ce3dc2948a2d3623c3db2c7b69
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 ! During the discussion of the fix for PR43072, in which unnecessary
5 ! calls to internal PACK/UNPACK were being generated, the following,
6 ! further unnecessary temporaries or PACk/UNPACK were found.
8 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
10 ! Case 1: Substring encompassing the whole string
11 subroutine foo2
12 implicit none
13 external foo
14 character(len=20) :: str(2) = '1234567890'
15 call foo(str(:)(1:20)) ! This is still not fixed.
16 end
18 ! Case 2: Contiguous array section
19 subroutine bar
20 implicit none
21 external foo
22 integer :: a(3,3,3)
23 call foo(a(:,:,:)) ! OK, no temporary
24 call foo(a(:,:,1)) ! OK, no temporary
25 call foo(a(:,2,2)) ! Used unnecessarily a temporary -FIXED
26 call foo(a(2,:,1)) ! OK, creates a temporary(1)
27 end
29 ! Case 3: Stride 1 section.
30 subroutine foobar
31 implicit none
32 external foo
33 integer :: A(10,10)
34 call foo(A(3:7,4)) ! Used unnecessarily a temporary - FIXED
35 call foo(A(:,3:7)) ! OK (no temporary)
36 call foo(A(1:10,3:7)) ! OK (no temporary)
37 call foo(A(4,3:7)) ! temporary OK(2)
38 call foo(A(:,3:7:-1)) ! temporary(3) OK because of stride
39 end
40 ! { dg-final { scan-tree-dump-times "unpack" 3 "original" } }