1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT LIBRARY COMPONENTS                          --
4--                                                                          --
5--               ADA.CONTAINERS.INDEFINITE_DOUBLY_LINKED_LISTS              --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 2004-2015, Free Software Foundation, Inc.         --
10--                                                                          --
11-- This specification is derived from the Ada Reference Manual for use with --
12-- GNAT. The copyright notice above, and the license provisions that follow --
13-- apply solely to the  contents of the part following the private keyword. --
14--                                                                          --
15-- GNAT is free software;  you can  redistribute it  and/or modify it under --
16-- terms of the  GNU General Public License as published  by the Free Soft- --
17-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
18-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
19-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
20-- or FITNESS FOR A PARTICULAR PURPOSE.                                     --
21--                                                                          --
22-- As a special exception under Section 7 of GPL version 3, you are granted --
23-- additional permissions described in the GCC Runtime Library Exception,   --
24-- version 3.1, as published by the Free Software Foundation.               --
25--                                                                          --
26-- You should have received a copy of the GNU General Public License and    --
27-- a copy of the GCC Runtime Library Exception along with this program;     --
28-- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
29-- <http://www.gnu.org/licenses/>.                                          --
30--                                                                          --
31-- This unit was originally developed by Matthew J Heaney.                  --
32------------------------------------------------------------------------------
33
34with Ada.Iterator_Interfaces;
35
36with Ada.Containers.Helpers;
37private with Ada.Finalization;
38private with Ada.Streams;
39
40generic
41   type Element_Type (<>) is private;
42
43   with function "=" (Left, Right : Element_Type)
44      return Boolean is <>;
45
46package Ada.Containers.Indefinite_Doubly_Linked_Lists is
47   pragma Annotate (CodePeer, Skip_Analysis);
48   pragma Preelaborate;
49   pragma Remote_Types;
50
51   type List is tagged private with
52      Constant_Indexing => Constant_Reference,
53      Variable_Indexing => Reference,
54      Default_Iterator  => Iterate,
55      Iterator_Element  => Element_Type;
56
57   pragma Preelaborable_Initialization (List);
58
59   type Cursor is private;
60   pragma Preelaborable_Initialization (Cursor);
61
62   Empty_List : constant List;
63
64   No_Element : constant Cursor;
65
66   function Has_Element (Position : Cursor) return Boolean;
67
68   package List_Iterator_Interfaces is new
69     Ada.Iterator_Interfaces (Cursor, Has_Element);
70
71   function "=" (Left, Right : List) return Boolean;
72
73   function Length (Container : List) return Count_Type;
74
75   function Is_Empty (Container : List) return Boolean;
76
77   procedure Clear (Container : in out List);
78
79   function Element (Position : Cursor) return Element_Type;
80
81   procedure Replace_Element
82     (Container : in out List;
83      Position  : Cursor;
84      New_Item  : Element_Type);
85
86   procedure Query_Element
87     (Position : Cursor;
88      Process  : not null access procedure (Element : Element_Type));
89
90   procedure Update_Element
91     (Container : in out List;
92      Position  : Cursor;
93      Process   : not null access procedure (Element : in out Element_Type));
94
95   type Constant_Reference_Type
96      (Element : not null access constant Element_Type) is private
97   with
98      Implicit_Dereference => Element;
99
100   type Reference_Type
101     (Element : not null access Element_Type) is private
102   with
103      Implicit_Dereference => Element;
104
105   function Constant_Reference
106     (Container : aliased List;
107      Position  : Cursor) return Constant_Reference_Type;
108   pragma Inline (Constant_Reference);
109
110   function Reference
111     (Container : aliased in out List;
112      Position  : Cursor) return Reference_Type;
113   pragma Inline (Reference);
114
115   procedure Assign (Target : in out List; Source : List);
116
117   function Copy (Source : List) return List;
118
119   procedure Move
120     (Target : in out List;
121      Source : in out List);
122
123   procedure Insert
124     (Container : in out List;
125      Before    : Cursor;
126      New_Item  : Element_Type;
127      Count     : Count_Type := 1);
128
129   procedure Insert
130     (Container : in out List;
131      Before    : Cursor;
132      New_Item  : Element_Type;
133      Position  : out Cursor;
134      Count     : Count_Type := 1);
135
136   procedure Prepend
137     (Container : in out List;
138      New_Item  : Element_Type;
139      Count     : Count_Type := 1);
140
141   procedure Append
142     (Container : in out List;
143      New_Item  : Element_Type;
144      Count     : Count_Type := 1);
145
146   procedure Delete
147     (Container : in out List;
148      Position  : in out Cursor;
149      Count     : Count_Type := 1);
150
151   procedure Delete_First
152     (Container : in out List;
153      Count     : Count_Type := 1);
154
155   procedure Delete_Last
156     (Container : in out List;
157      Count     : Count_Type := 1);
158
159   procedure Reverse_Elements (Container : in out List);
160
161   procedure Swap (Container : in out List; I, J : Cursor);
162
163   procedure Swap_Links (Container : in out List; I, J : Cursor);
164
165   procedure Splice
166     (Target : in out List;
167      Before : Cursor;
168      Source : in out List);
169
170   procedure Splice
171     (Target   : in out List;
172      Before   : Cursor;
173      Source   : in out List;
174      Position : in out Cursor);
175
176   procedure Splice
177     (Container : in out List;
178      Before    : Cursor;
179      Position  : Cursor);
180
181   function First (Container : List) return Cursor;
182
183   function First_Element (Container : List) return Element_Type;
184
185   function Last (Container : List) return Cursor;
186
187   function Last_Element (Container : List) return Element_Type;
188
189   function Next (Position : Cursor) return Cursor;
190
191   procedure Next (Position : in out Cursor);
192
193   function Previous (Position : Cursor) return Cursor;
194
195   procedure Previous (Position : in out Cursor);
196
197   function Find
198     (Container : List;
199      Item      : Element_Type;
200      Position  : Cursor := No_Element) return Cursor;
201
202   function Reverse_Find
203     (Container : List;
204      Item      : Element_Type;
205      Position  : Cursor := No_Element) return Cursor;
206
207   function Contains
208     (Container : List;
209      Item      : Element_Type) return Boolean;
210
211   procedure Iterate
212     (Container : List;
213      Process   : not null access procedure (Position : Cursor));
214
215   procedure Reverse_Iterate
216     (Container : List;
217      Process   : not null access procedure (Position : Cursor));
218
219   function Iterate
220     (Container : List)
221      return List_Iterator_Interfaces.Reversible_Iterator'class;
222
223   function Iterate
224     (Container : List;
225      Start     : Cursor)
226      return List_Iterator_Interfaces.Reversible_Iterator'class;
227
228   generic
229      with function "<" (Left, Right : Element_Type) return Boolean is <>;
230   package Generic_Sorting is
231
232      function Is_Sorted (Container : List) return Boolean;
233
234      procedure Sort (Container : in out List);
235
236      procedure Merge (Target, Source : in out List);
237
238   end Generic_Sorting;
239
240private
241
242   pragma Inline (Next);
243   pragma Inline (Previous);
244
245   use Ada.Containers.Helpers;
246   package Implementation is new Generic_Implementation;
247   use Implementation;
248
249   type Node_Type;
250   type Node_Access is access Node_Type;
251
252   type Element_Access is access all Element_Type;
253
254   type Node_Type is
255      limited record
256         Element : Element_Access;
257         Next    : Node_Access;
258         Prev    : Node_Access;
259      end record;
260
261   use Ada.Finalization;
262   use Ada.Streams;
263
264   type List is
265     new Controlled with record
266        First  : Node_Access := null;
267        Last   : Node_Access := null;
268        Length : Count_Type := 0;
269        TC     : aliased Tamper_Counts;
270     end record;
271
272   overriding procedure Adjust (Container : in out List);
273
274   overriding procedure Finalize (Container : in out List) renames Clear;
275
276   procedure Read
277     (Stream : not null access Root_Stream_Type'Class;
278      Item   : out List);
279
280   for List'Read use Read;
281
282   procedure Write
283     (Stream : not null access Root_Stream_Type'Class;
284      Item   : List);
285
286   for List'Write use Write;
287
288   type List_Access is access all List;
289   for List_Access'Storage_Size use 0;
290
291   type Cursor is
292      record
293         Container : List_Access;
294         Node      : Node_Access;
295      end record;
296
297   procedure Read
298     (Stream : not null access Root_Stream_Type'Class;
299      Item   : out Cursor);
300
301   for Cursor'Read use Read;
302
303   procedure Write
304     (Stream : not null access Root_Stream_Type'Class;
305      Item   : Cursor);
306
307   for Cursor'Write use Write;
308
309   subtype Reference_Control_Type is Implementation.Reference_Control_Type;
310   --  It is necessary to rename this here, so that the compiler can find it
311
312   type Constant_Reference_Type
313     (Element : not null access constant Element_Type) is
314      record
315         Control : Reference_Control_Type :=
316           raise Program_Error with "uninitialized reference";
317         --  The RM says, "The default initialization of an object of
318         --  type Constant_Reference_Type or Reference_Type propagates
319         --  Program_Error."
320      end record;
321
322   procedure Write
323     (Stream : not null access Root_Stream_Type'Class;
324      Item   : Constant_Reference_Type);
325
326   for Constant_Reference_Type'Write use Write;
327
328   procedure Read
329     (Stream : not null access Root_Stream_Type'Class;
330      Item   : out Constant_Reference_Type);
331
332   for Constant_Reference_Type'Read use Read;
333
334   type Reference_Type
335     (Element : not null access Element_Type) is
336      record
337         Control : Reference_Control_Type :=
338           raise Program_Error with "uninitialized reference";
339         --  The RM says, "The default initialization of an object of
340         --  type Constant_Reference_Type or Reference_Type propagates
341         --  Program_Error."
342      end record;
343
344   procedure Write
345     (Stream : not null access Root_Stream_Type'Class;
346      Item   : Reference_Type);
347
348   for Reference_Type'Write use Write;
349
350   procedure Read
351     (Stream : not null access Root_Stream_Type'Class;
352      Item   : out Reference_Type);
353
354   for Reference_Type'Read use Read;
355
356   --  Three operations are used to optimize in the expansion of "for ... of"
357   --  loops: the Next(Cursor) procedure in the visible part, and the following
358   --  Pseudo_Reference and Get_Element_Access functions. See Exp_Ch5 for
359   --  details.
360
361   function Pseudo_Reference
362     (Container : aliased List'Class) return Reference_Control_Type;
363   pragma Inline (Pseudo_Reference);
364   --  Creates an object of type Reference_Control_Type pointing to the
365   --  container, and increments the Lock. Finalization of this object will
366   --  decrement the Lock.
367
368   function Get_Element_Access
369     (Position : Cursor) return not null Element_Access;
370   --  Returns a pointer to the element designated by Position.
371
372   Empty_List : constant List := List'(Controlled with others => <>);
373
374   No_Element : constant Cursor := Cursor'(null, null);
375
376   type Iterator is new Limited_Controlled and
377     List_Iterator_Interfaces.Reversible_Iterator with
378   record
379      Container : List_Access;
380      Node      : Node_Access;
381   end record
382     with Disable_Controlled => not T_Check;
383
384   overriding procedure Finalize (Object : in out Iterator);
385
386   overriding function First (Object : Iterator) return Cursor;
387   overriding function Last  (Object : Iterator) return Cursor;
388
389   overriding function Next
390     (Object   : Iterator;
391      Position : Cursor) return Cursor;
392
393   overriding function Previous
394     (Object   : Iterator;
395      Position : Cursor) return Cursor;
396
397end Ada.Containers.Indefinite_Doubly_Linked_Lists;
398