modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / contiguous_14.f90
blob21e42311e9c7405d6b8c0e76776df5e37cd2c738
1 ! { dg-do compile }
2 ! PR fortran/111503 - passing NULL() to POINTER, OPTIONAL, CONTIGUOUS dummy
4 program test
5 implicit none
6 integer, pointer, contiguous :: p(:) => null()
7 integer, allocatable, target :: a(:)
8 type t
9 integer, pointer, contiguous :: p(:) => null()
10 integer, allocatable :: a(:)
11 end type t
12 type(t), target :: z
13 class(t), allocatable, target :: c
14 print *, is_contiguous (p)
15 allocate (t :: c)
16 call one (p)
17 call one ()
18 call one (null ())
19 call one (null (p))
20 call one (a)
21 call one (null (a))
22 call one (z% p)
23 call one (z% a)
24 call one (null (z% p))
25 call one (null (z% a))
26 call one (c% p)
27 call one (c% a)
28 call one (null (c% p))
29 call one (null (c% a))
30 contains
31 subroutine one (x)
32 integer, pointer, optional, contiguous, intent(in) :: x(:)
33 print *, present (x)
34 if (present (x)) then
35 print *, "->", associated (x)
36 if (associated (x)) stop 99
37 end if
38 end subroutine one
39 end