1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT LIBRARY COMPONENTS                          --
4--                                                                          --
5--                 ADA.CONTAINERS.INDEFINITE_ORDERED_MAPS                   --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 2004-2020, 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
36private with Ada.Containers.Red_Black_Trees;
37private with Ada.Finalization;
38private with Ada.Streams;
39private with Ada.Strings.Text_Output;
40
41generic
42   type Key_Type (<>) is private;
43   type Element_Type (<>) is private;
44
45   with function "<" (Left, Right : Key_Type) return Boolean is <>;
46   with function "=" (Left, Right : Element_Type) return Boolean is <>;
47
48package Ada.Containers.Indefinite_Ordered_Maps with
49  SPARK_Mode => Off
50is
51   pragma Annotate (CodePeer, Skip_Analysis);
52   pragma Preelaborate;
53   pragma Remote_Types;
54
55   function Equivalent_Keys (Left, Right : Key_Type) return Boolean;
56
57   type Map is tagged private
58   with Constant_Indexing => Constant_Reference,
59        Variable_Indexing => Reference,
60        Default_Iterator  => Iterate,
61        Iterator_Element  => Element_Type,
62        Aggregate         => (Empty     => Empty,
63                              Add_Named => Insert);
64
65   pragma Preelaborable_Initialization (Map);
66
67   type Cursor is private;
68   pragma Preelaborable_Initialization (Cursor);
69
70   Empty_Map : constant Map;
71
72   function Empty return Map;
73
74   No_Element : constant Cursor;
75   function Has_Element (Position : Cursor) return Boolean;
76
77   package Map_Iterator_Interfaces is new
78     Ada.Iterator_Interfaces (Cursor, Has_Element);
79
80   function "=" (Left, Right : Map) return Boolean;
81
82   function Length (Container : Map) return Count_Type;
83
84   function Is_Empty (Container : Map) return Boolean;
85
86   procedure Clear (Container : in out Map);
87
88   function Key (Position : Cursor) return Key_Type;
89
90   function Element (Position : Cursor) return Element_Type;
91
92   procedure Replace_Element
93     (Container : in out Map;
94      Position  : Cursor;
95      New_Item  : Element_Type);
96
97   procedure Query_Element
98     (Position : Cursor;
99      Process  : not null access procedure (Key     : Key_Type;
100                                            Element : Element_Type));
101
102   procedure Update_Element
103     (Container : in out Map;
104      Position  : Cursor;
105      Process   : not null access procedure (Key     : Key_Type;
106                                             Element : in out Element_Type));
107
108   type Constant_Reference_Type
109      (Element : not null access constant Element_Type) is private
110   with
111      Implicit_Dereference => Element;
112
113   type Reference_Type (Element : not null access Element_Type) is private
114   with
115      Implicit_Dereference => Element;
116
117   function Constant_Reference
118     (Container : aliased Map;
119      Position  : Cursor) return Constant_Reference_Type;
120   pragma Inline (Constant_Reference);
121
122   function Reference
123     (Container : aliased in out Map;
124      Position  : Cursor) return Reference_Type;
125   pragma Inline (Reference);
126
127   function Constant_Reference
128     (Container : aliased Map;
129      Key       : Key_Type) return Constant_Reference_Type;
130   pragma Inline (Constant_Reference);
131
132   function Reference
133     (Container : aliased in out Map;
134      Key       : Key_Type) return Reference_Type;
135   pragma Inline (Reference);
136
137   procedure Assign (Target : in out Map; Source : Map);
138
139   function Copy (Source : Map) return Map;
140
141   procedure Move (Target : in out Map; Source : in out Map);
142
143   procedure Insert
144     (Container : in out Map;
145      Key       : Key_Type;
146      New_Item  : Element_Type;
147      Position  : out Cursor;
148      Inserted  : out Boolean);
149
150   procedure Insert
151     (Container : in out Map;
152      Key       : Key_Type;
153      New_Item  : Element_Type);
154
155   procedure Include
156     (Container : in out Map;
157      Key       : Key_Type;
158      New_Item  : Element_Type);
159
160   procedure Replace
161     (Container : in out Map;
162      Key       : Key_Type;
163      New_Item  : Element_Type);
164
165   procedure Exclude (Container : in out Map; Key : Key_Type);
166
167   procedure Delete (Container : in out Map; Key : Key_Type);
168
169   procedure Delete (Container : in out Map; Position : in out Cursor);
170
171   procedure Delete_First (Container : in out Map);
172
173   procedure Delete_Last (Container : in out Map);
174
175   function First (Container : Map) return Cursor;
176
177   function First_Element (Container : Map) return Element_Type;
178
179   function First_Key (Container : Map) return Key_Type;
180
181   function Last (Container : Map) return Cursor;
182
183   function Last_Element (Container : Map) return Element_Type;
184
185   function Last_Key (Container : Map) return Key_Type;
186
187   function Next (Position : Cursor) return Cursor;
188
189   procedure Next (Position : in out Cursor);
190
191   function Previous (Position : Cursor) return Cursor;
192
193   procedure Previous (Position : in out Cursor);
194
195   function Find (Container : Map; Key : Key_Type) return Cursor;
196
197   function Element (Container : Map; Key : Key_Type) return Element_Type;
198
199   function Floor (Container : Map; Key : Key_Type) return Cursor;
200
201   function Ceiling (Container : Map; Key : Key_Type) return Cursor;
202
203   function Contains (Container : Map; Key : Key_Type) return Boolean;
204
205   function "<" (Left, Right : Cursor) return Boolean;
206
207   function ">" (Left, Right : Cursor) return Boolean;
208
209   function "<" (Left : Cursor; Right : Key_Type) return Boolean;
210
211   function ">" (Left : Cursor; Right : Key_Type) return Boolean;
212
213   function "<" (Left : Key_Type; Right : Cursor) return Boolean;
214
215   function ">" (Left : Key_Type; Right : Cursor) return Boolean;
216
217   procedure Iterate
218     (Container : Map;
219      Process   : not null access procedure (Position : Cursor));
220
221   procedure Reverse_Iterate
222     (Container : Map;
223      Process   : not null access procedure (Position : Cursor));
224
225   --  The map container supports iteration in both the forward and reverse
226   --  directions, hence these constructor functions return an object that
227   --  supports the Reversible_Iterator interface.
228
229   function Iterate
230     (Container : Map)
231      return Map_Iterator_Interfaces.Reversible_Iterator'Class;
232
233   function Iterate
234     (Container : Map;
235      Start     : Cursor)
236      return Map_Iterator_Interfaces.Reversible_Iterator'Class;
237
238private
239
240   pragma Inline (Next);
241   pragma Inline (Previous);
242
243   type Node_Type;
244   type Node_Access is access Node_Type;
245
246   type Key_Access is access Key_Type;
247   type Element_Access is access all Element_Type;
248
249   type Node_Type is limited record
250      Parent  : Node_Access;
251      Left    : Node_Access;
252      Right   : Node_Access;
253      Color   : Red_Black_Trees.Color_Type := Red_Black_Trees.Red;
254      Key     : Key_Access;
255      Element : Element_Access;
256   end record;
257
258   package Tree_Types is new Red_Black_Trees.Generic_Tree_Types
259     (Node_Type,
260      Node_Access);
261
262   type Map is new Ada.Finalization.Controlled with record
263      Tree : Tree_Types.Tree_Type;
264   end record with Put_Image => Put_Image;
265
266   procedure Put_Image
267     (S : in out Ada.Strings.Text_Output.Sink'Class; V : Map);
268
269   overriding procedure Adjust (Container : in out Map);
270
271   overriding procedure Finalize (Container : in out Map) renames Clear;
272
273   use Red_Black_Trees;
274   use Tree_Types, Tree_Types.Implementation;
275   use Ada.Finalization;
276   use Ada.Streams;
277
278   procedure Write
279     (Stream    : not null access Root_Stream_Type'Class;
280      Container : Map);
281
282   for Map'Write use Write;
283
284   procedure Read
285     (Stream    : not null access Root_Stream_Type'Class;
286      Container : out Map);
287
288   for Map'Read use Read;
289
290   type Map_Access is access all Map;
291   for Map_Access'Storage_Size use 0;
292
293   type Cursor is record
294      Container : Map_Access;
295      Node      : Node_Access;
296   end record;
297
298   procedure Write
299     (Stream : not null access Root_Stream_Type'Class;
300      Item   : Cursor);
301
302   for Cursor'Write use Write;
303
304   procedure Read
305     (Stream : not null access Root_Stream_Type'Class;
306      Item   : out Cursor);
307
308   for Cursor'Read use Read;
309
310   subtype Reference_Control_Type is Implementation.Reference_Control_Type;
311   --  It is necessary to rename this here, so that the compiler can find it
312
313   type Constant_Reference_Type
314     (Element : not null access constant Element_Type) is
315      record
316         Control : Reference_Control_Type :=
317           raise Program_Error with "uninitialized reference";
318         --  The RM says, "The default initialization of an object of
319         --  type Constant_Reference_Type or Reference_Type propagates
320         --  Program_Error."
321      end record;
322
323   procedure Read
324     (Stream : not null access Root_Stream_Type'Class;
325      Item   : out Constant_Reference_Type);
326
327   for Constant_Reference_Type'Read use Read;
328
329   procedure Write
330     (Stream : not null access Root_Stream_Type'Class;
331      Item   : Constant_Reference_Type);
332
333   for Constant_Reference_Type'Write use Write;
334
335   type Reference_Type
336     (Element : not null access Element_Type) is
337      record
338         Control : Reference_Control_Type :=
339           raise Program_Error with "uninitialized reference";
340         --  The RM says, "The default initialization of an object of
341         --  type Constant_Reference_Type or Reference_Type propagates
342         --  Program_Error."
343      end record;
344
345   procedure Read
346     (Stream : not null access Root_Stream_Type'Class;
347      Item   : out Reference_Type);
348
349   for Reference_Type'Read use Read;
350
351   procedure Write
352     (Stream : not null access Root_Stream_Type'Class;
353      Item   : Reference_Type);
354
355   for Reference_Type'Write use Write;
356
357   --  Three operations are used to optimize in the expansion of "for ... of"
358   --  loops: the Next(Cursor) procedure in the visible part, and the following
359   --  Pseudo_Reference and Get_Element_Access functions.  See Sem_Ch5 for
360   --  details.
361
362   function Pseudo_Reference
363     (Container : aliased Map'Class) return Reference_Control_Type;
364   pragma Inline (Pseudo_Reference);
365   --  Creates an object of type Reference_Control_Type pointing to the
366   --  container, and increments the Lock. Finalization of this object will
367   --  decrement the Lock.
368
369   function Get_Element_Access
370     (Position : Cursor) return not null Element_Access;
371   --  Returns a pointer to the element designated by Position.
372
373   Empty_Map : constant Map := (Controlled with others => <>);
374   function Empty return Map is (Empty_Map);
375
376   No_Element : constant Cursor := Cursor'(null, null);
377
378   type Iterator is new Limited_Controlled and
379     Map_Iterator_Interfaces.Reversible_Iterator with
380   record
381      Container : Map_Access;
382      Node      : Node_Access;
383   end record
384     with Disable_Controlled => not T_Check;
385
386   overriding procedure Finalize (Object : in out Iterator);
387
388   overriding function First (Object : Iterator) return Cursor;
389   overriding function Last  (Object : Iterator) return Cursor;
390
391   overriding function Next
392     (Object   : Iterator;
393      Position : Cursor) return Cursor;
394
395   overriding function Previous
396     (Object   : Iterator;
397      Position : Cursor) return Cursor;
398
399end Ada.Containers.Indefinite_Ordered_Maps;
400