blob: 11927619db4b2b2d2c3a2f345876faae7ad17e2e (
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
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
|
! { dg-do run }
! { dg-options "-fdump-tree-original" }
!
! PR fortran/51435
!
! Contributed by darmar.xxl@gmail.com
!
module arr_m
type arr_t
real(8), dimension(:), allocatable :: rsk
end type
type arr_t2
integer :: a = 77
end type
end module arr_m
!*********************
module list_m
use arr_m
implicit none
type(arr_t2), target :: tgt
type my_list
type(arr_t), pointer :: head => null()
end type my_list
type my_list2
type(arr_t2), pointer :: head => tgt
end type my_list2
end module list_m
!***********************
module worker_mod
use list_m
implicit none
type data_all_t
type(my_list) :: my_data
end type data_all_t
type data_all_t2
type(my_list2) :: my_data
end type data_all_t2
contains
subroutine do_job()
type(data_all_t) :: dum
type(data_all_t2) :: dum2
if (associated(dum%my_data%head)) then
call abort()
else
print *, 'OK: do_job my_data%head is NOT associated'
end if
if (dum2%my_data%head%a /= 77) &
call abort()
end subroutine
end module
!***************
program hello
use worker_mod
implicit none
call do_job()
end program
! { dg-final { scan-tree-dump-times "my_data.head = 0B" 1 "original" } }
! { dg-final { scan-tree-dump-times "my_data.head = &tgt" 1 "original" } }
! { dg-final { cleanup-tree-dump "original" } }
! { dg-final { cleanup-modules "arr_m list_m worker_mod" } }
|