PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / select_type_4.f90
blob06a61a519e063340bc79ece47ccdf1c29c8f1c58
1 ! { dg-do run }
3 ! Contributed by by Richard Maine
4 ! http://coding.derkeiler.com/Archive/Fortran/comp.lang.fortran/2006-10/msg00104.html
6 module poly_list
8 !-- Polymorphic lists using type extension.
10 implicit none
12 type, public :: node_type
13 private
14 class(node_type), pointer :: next => null()
15 end type node_type
17 type, public :: list_type
18 private
19 class(node_type), pointer :: head => null(), tail => null()
20 end type list_type
22 contains
24 subroutine append_node (list, new_node)
26 !-- Append a node to a list.
27 !-- Caller is responsible for allocating the node.
29 !---------- interface.
31 type(list_type), intent(inout) :: list
32 class(node_type), target :: new_node
34 !---------- executable code.
36 if (.not.associated(list%head)) list%head => new_node
37 if (associated(list%tail)) list%tail%next => new_node
38 list%tail => new_node
39 return
40 end subroutine append_node
42 function first_node (list)
44 !-- Get the first node of a list.
46 !---------- interface.
48 type(list_type), intent(in) :: list
49 class(node_type), pointer :: first_node
51 !---------- executable code.
53 first_node => list%head
54 return
55 end function first_node
57 function next_node (node)
59 !-- Step to the next node of a list.
61 !---------- interface.
63 class(node_type), target :: node
64 class(node_type), pointer :: next_node
66 !---------- executable code.
68 next_node => node%next
69 return
70 end function next_node
72 subroutine destroy_list (list)
74 !-- Delete (and deallocate) all the nodes of a list.
76 !---------- interface.
77 type(list_type), intent(inout) :: list
79 !---------- local.
80 class(node_type), pointer :: node, next
82 !---------- executable code.
84 node => list%head
85 do while (associated(node))
86 next => node%next
87 deallocate(node)
88 node => next
89 end do
90 nullify(list%head, list%tail)
91 return
92 end subroutine destroy_list
94 end module poly_list
96 program main
98 use poly_list
100 implicit none
101 integer :: cnt
103 type, extends(node_type) :: real_node_type
104 real :: x
105 end type real_node_type
107 type, extends(node_type) :: integer_node_type
108 integer :: i
109 end type integer_node_type
111 type, extends(node_type) :: character_node_type
112 character(1) :: c
113 end type character_node_type
115 type(list_type) :: list
116 class(node_type), pointer :: node
117 type(integer_node_type), pointer :: integer_node
118 type(real_node_type), pointer :: real_node
119 type(character_node_type), pointer :: character_node
121 !---------- executable code.
123 !----- Build the list.
125 allocate(real_node)
126 real_node%x = 1.23
127 call append_node(list, real_node)
129 allocate(integer_node)
130 integer_node%i = 42
131 call append_node(list, integer_node)
133 allocate(node)
134 call append_node(list, node)
136 allocate(character_node)
137 character_node%c = "z"
138 call append_node(list, character_node)
140 allocate(real_node)
141 real_node%x = 4.56
142 call append_node(list, real_node)
144 !----- Retrieve from it.
146 node => first_node(list)
148 cnt = 0
149 do while (associated(node))
150 cnt = cnt + 1
151 select type (node)
152 type is (real_node_type)
153 write (*,*) node%x
154 if (.not.( (cnt == 1 .and. node%x == 1.23) &
155 .or. (cnt == 5 .and. node%x == 4.56))) then
156 STOP 1
157 end if
158 type is (integer_node_type)
159 write (*,*) node%i
160 if (cnt /= 2 .or. node%i /= 42) STOP 2
161 type is (node_type)
162 write (*,*) "Node with no data."
163 if (cnt /= 3) STOP 3
164 class default
165 Write (*,*) "Some other node type."
166 if (cnt /= 4) STOP 4
167 end select
169 node => next_node(node)
170 end do
171 if (cnt /= 5) STOP 5
172 call destroy_list(list)
173 stop
174 end program main