Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / io15.f90
bloba00732a9e5044d269742630cafb24ee2263f2241
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Test visibility restrictions
3 module m
4 type t1
5 integer, private :: ip1 = 123
6 contains
7 procedure :: fwrite1
8 generic :: write(formatted) => fwrite1
9 end type t1
10 type t2
11 integer, private :: ip2 = 234
12 type(t1) x1
13 end type t2
14 type t3
15 type(t1) x1
16 type(t2) x2
17 end type t3
18 type, extends(t2) :: t4
19 end type t4
20 contains
21 subroutine fwrite1(x, unit, iotype, vlist, iostat, iomsg)
22 class(t1), intent(in) :: x
23 integer, intent(in) :: unit
24 character(*), intent(in) :: iotype
25 integer, intent(in) :: vlist(:)
26 integer, intent(out) :: iostat
27 character(*), intent(in out) :: iomsg
28 write(unit, *, iostat=iostat, iomsg=iomsg) '(', iotype, ':', vlist, ':', x%ip1, ')'
29 end subroutine
30 subroutine local ! all OK since type is local
31 type(t1) :: x1
32 type(t2) :: x2
33 type(t3) :: x3
34 type(t4) :: x4
35 print *, x1
36 print *, x2
37 print *, x3
38 print *, x4
39 end subroutine
40 end module
42 program main
43 use m
44 type(t1) :: x1
45 type(t2) :: x2
46 type(t3) :: x3
47 type(t4) :: x4
48 print *, x1 ! ok
49 !ERROR: I/O of the derived type 't2' may not be performed without defined I/O in a scope in which a direct component like 'ip2' is inaccessible
50 print *, x2
51 !ERROR: I/O of the derived type 't3' may not be performed without defined I/O in a scope in which a direct component like 'ip2' is inaccessible
52 print *, x3
53 !ERROR: I/O of the derived type 't4' may not be performed without defined I/O in a scope in which a direct component like 'ip2' is inaccessible
54 print *, x4
55 end