c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / internal_pack_22.f90
blob4e9fe59ceab7a7d095d341dc54ae18eb7fc6433b
1 ! { dg-do run }
2 ! { dg-additional-options "-fdump-tree-original -O" }
3 ! Check that absent and present dummy arguments work with
4 ! packing when handing them down to an old-fashioned argument.
6 module x
7 implicit none
8 contains
9 subroutine foo (a,b)
10 real, dimension(:), intent(inout), optional :: a, b
11 if (present(a)) stop 1
12 if (.not. present(b)) stop 2
13 call bar (a, b)
14 end subroutine foo
16 subroutine bar (a,b)
17 real, dimension(2), intent(inout), optional :: a, b
18 real :: tmp
19 if (present(a)) stop 3
20 if (.not. present(b)) stop 4
21 tmp = b(2)
22 b(2) = b(1)
23 b(1) = tmp
24 end subroutine bar
25 end module x
27 program main
28 use x
29 implicit none
30 real, dimension(2) :: b
31 b(1) = 1.
32 b(2) = 42.
33 call foo(b=b)
34 if (b(1) /= 42. .or. b(2) /= 1.) stop 5
35 end program main
36 ! { dg-final { scan-tree-dump-not "_gfortran_internal_unpack" "original" } }