blob: a50a9b751b1f07a66f483a2e3720822438242826 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
|
! { dg-do compile }
! Some errors pointed out in the development of the patch.
!
! Contributed by Tobias Burnus <burnus@net-b.de>
!
module m
type :: date
private
integer :: yr, mon
integer,public :: day
end type
type :: dt
integer :: yr, mon
integer :: day
end type
end module m
use m
type, extends(date) :: datetime
integer :: hr, min, sec
end type
type(datetime) :: o_dt
type :: one
integer :: i
end type one
type, extends(one) :: two
real :: r
end type two
o_dt%day = 5 ! VALID but failed in first version of EXTENDS patch
o_dt%yr = 5 ! { dg-error "is a PRIVATE component of" }
t = two(one = one(4), i = 5, r=4.4) ! { dg-error "has already been set" }
call foo
contains
subroutine foo
use m, date_type => dt
type, extends(date_type) :: dt_type
end type
type (dt_type) :: foo_dt
foo_dt%date_type%day = 1
foo_dt%dt%day = 1 ! { dg-error "not a member" }
end subroutine
end
! { dg-final { cleanup-modules "m" } }
|