AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / char_pointer_assign_7.f90
blob08bdf176d8b42df9961e90d59c31d56816b0601e
1 ! { dg-do compile }
2 ! PR fortran/50549 - should reject pointer assignments of different lengths
3 ! in structure constructors
5 program test
6 implicit none
7 type t
8 character(2), pointer :: p2
9 end type t
10 type t2
11 character(2), pointer :: p(:)
12 end type t2
13 type td
14 character(:), pointer :: pd
15 end type td
16 interface
17 function f1 ()
18 character(1), pointer :: f1
19 end function f1
20 function f2 ()
21 character(2), pointer :: f2
22 end function f2
23 end interface
25 character(1), target :: p1
26 character(1), pointer :: q1(:)
27 character(2), pointer :: q2(:)
28 type(t) :: u
29 type(t2) :: u2
30 type(td) :: v
31 u = t(p1) ! { dg-error "Unequal character lengths" }
32 u = t(f1()) ! { dg-error "Unequal character lengths" }
33 u = t(f2()) ! OK
34 u2 = t2(q1) ! { dg-error "Unequal character lengths" }
35 u2 = t2(q2) ! OK
36 v = td(p1) ! OK
37 v = td(f1()) ! OK
38 end