2 ! Test the fix for PRs29396, 29606, 30625 and 30871, in which pointers
3 ! to arrays with subreferences did not work.
11 ! Contributed by Francois-Xavier Coudert <fxcoudert@gcc.gnu.org>
12 CHARACTER(LEN
=2), DIMENSION(:), POINTER :: a
13 CHARACTER(LEN
=4), DIMENSION(3), TARGET
:: b
14 b
=(/"bbbb","bbbb","bbbb"/)
17 IF (ANY(b
.NE
.(/"baab","baab","baab"/))) CALL ABORT()
21 ! Contributed by Daniel Franke <franke.daniel@gmail.com>
26 TYPE(foo
), DIMENSION(:), POINTER :: array
28 TYPE(foo_array
) :: array_holder
29 INTEGER, DIMENSION(:), POINTER :: array_ptr
30 ALLOCATE( array_holder
%array(3) )
31 array_holder
%array
= (/ foo(1), foo(2), foo(3) /)
32 array_ptr
=> array_holder
%array
%value
33 if (any (array_ptr
.ne
. (/1,2,3/))) call abort ()
37 ! Contributed by Paul Thomas <pault@gcc.gnu.org>
42 type(a
), target
:: dt(2)
43 integer, pointer :: ip(:)
45 if (any (ip
.ne
. 42)) call abort ()
49 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
53 TYPE(data), DIMENSION(10), TARGET
:: Z
54 CHARACTER(LEN
=1), DIMENSION(:), POINTER :: ptr
57 if (any (ptr
.ne
. "2")) call abort ()