lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / null_actual_5.f90
blob1198715b7c8d6b85a6475328c978e4509b850737
1 ! { dg-do compile }
2 ! PR fortran/55978
4 ! Passing of NULL() with and without MOLD as actual argument
6 ! Testcase derived from pr55978 comment#16
8 program pr55978_c16
9 implicit none
11 integer, pointer :: p(:)
12 integer, allocatable :: a(:)
13 character(10), pointer :: c
14 character(10), pointer :: cp(:)
16 type t
17 integer, pointer :: p(:)
18 integer, allocatable :: a(:)
19 end type
21 type(t) :: d
23 ! (1) pointer
24 p => null()
25 call sub (p)
27 ! (2) allocatable
28 call sub (a)
29 call sub (d%a)
31 ! (3) pointer component
32 d%p => null ()
33 call sub (d%p)
35 ! (4) NULL
36 call sub (null (a)) ! OK
37 call sub (null (p)) ! OK
38 call sub (null (d%a)) ! OK
39 call sub (null (d%p)) ! OK
40 call sub (null ()) ! was erroneously rejected with:
41 ! Actual argument contains too few elements for dummy argument 'x' (1/4)
43 call bla (null(c))
44 call bla (null()) ! was erroneously rejected with:
45 ! Actual argument contains too few elements for dummy argument 'x' (1/10)
47 call foo (null(cp))
48 call foo (null())
50 call bar (null(cp))
51 call bar (null()) ! was erroneously rejected with:
52 ! Actual argument contains too few elements for dummy argument 'x' (1/70)
54 contains
56 subroutine sub(x)
57 integer, intent(in), optional :: x(4)
58 if (present (x)) stop 1
59 end
61 subroutine bla(x)
62 character(len=10), intent(in), optional :: x
63 if (present (x)) stop 2
64 end
66 subroutine foo(x)
67 character(len=10), intent(in), optional :: x(:)
68 if (present (x)) stop 3
69 end
71 subroutine bar(x)
72 character(len=10), intent(in), optional :: x(7)
73 if (present (x)) stop 4
74 end
76 end