1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT RUN-TIME COMPONENTS                         --
4--                                                                          --
5--                          A D A . T E X T _ I O                           --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2021, 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-- GNAT was originally developed  by the GNAT team at  New York University. --
32-- Extensive contributions were provided by Ada Core Technologies Inc.      --
33--                                                                          --
34------------------------------------------------------------------------------
35
36--  Preconditions in this unit are meant for analysis only, not for run-time
37--  checking, so that the expected exceptions are raised. This is enforced by
38--  setting the corresponding assertion policy to Ignore. These preconditions
39--  are partial. They protect fully against Status_Error and Mode_Error,
40--  partially against Layout_Error (see SPARK User's Guide for details), and
41--  not against other types of errors.
42
43pragma Assertion_Policy (Pre => Ignore);
44
45--  Note: the generic subpackages of Text_IO (Integer_IO, Float_IO, Fixed_IO,
46--  Modular_IO, Decimal_IO and Enumeration_IO) appear as private children in
47--  GNAT. These children are with'ed automatically if they are referenced, so
48--  this rearrangement is invisible to user programs, but has the advantage
49--  that only the needed parts of Text_IO are processed and loaded.
50
51with Ada.IO_Exceptions;
52with Ada.Streams;
53
54with System;
55with System.File_Control_Block;
56with System.WCh_Con;
57
58package Ada.Text_IO with
59  SPARK_Mode,
60  Abstract_State    => File_System,
61  Initializes       => File_System,
62  Initial_Condition => Line_Length = 0 and Page_Length = 0
63is
64   pragma Elaborate_Body;
65
66   type File_Type is limited private with
67     Default_Initial_Condition => (not Is_Open (File_Type));
68   type File_Mode is (In_File, Out_File, Append_File);
69
70   --  The following representation clause allows the use of unchecked
71   --  conversion for rapid translation between the File_Mode type
72   --  used in this package and System.File_IO.
73
74   for File_Mode use
75     (In_File     => 0,  -- System.File_IO.File_Mode'Pos (In_File)
76      Out_File    => 2,  -- System.File_IO.File_Mode'Pos (Out_File)
77      Append_File => 3); -- System.File_IO.File_Mode'Pos (Append_File)
78
79   type Count is range 0 .. Natural'Last;
80   --  The value of Count'Last must be large enough so that the assumption that
81   --  the Line, Column and Page counts can never exceed this value is valid.
82
83   subtype Positive_Count is Count range 1 .. Count'Last;
84
85   Unbounded : constant Count := 0;
86   --  Line and page length
87
88   subtype Field is Integer range 0 .. 255;
89
90   subtype Number_Base is Integer range 2 .. 16;
91
92   type Type_Set is (Lower_Case, Upper_Case);
93
94   ---------------------
95   -- File Management --
96   ---------------------
97
98   procedure Create
99     (File : in out File_Type;
100      Mode : File_Mode := Out_File;
101      Name : String := "";
102      Form : String := "")
103   with
104     Pre    => not Is_Open (File),
105     Post   =>
106       Is_Open (File)
107       and then Ada.Text_IO.Mode (File) = Mode
108       and then (if Mode /= In_File
109                   then (Line_Length (File) = 0
110                         and then Page_Length (File) = 0)),
111     Global => (In_Out => File_System);
112
113   procedure Open
114     (File : in out File_Type;
115      Mode : File_Mode;
116      Name : String;
117      Form : String := "")
118   with
119     Pre    => not Is_Open (File),
120     Post   =>
121      Is_Open (File)
122      and then Ada.Text_IO.Mode (File) = Mode
123      and then (if Mode /= In_File
124                  then (Line_Length (File) = 0
125                        and then Page_Length (File) = 0)),
126     Global => (In_Out => File_System);
127
128   procedure Close  (File : in out File_Type) with
129     Pre    => Is_Open (File),
130     Post   => not Is_Open (File),
131     Global => (In_Out => File_System);
132   procedure Delete (File : in out File_Type) with
133     Pre    => Is_Open (File),
134     Post   => not Is_Open (File),
135     Global => (In_Out => File_System);
136   procedure Reset  (File : in out File_Type; Mode : File_Mode) with
137     Pre    => Is_Open (File),
138     Post   =>
139       Is_Open (File)
140       and then Ada.Text_IO.Mode (File) = Mode
141       and then (if Mode /= In_File
142                   then (Line_Length (File) = 0
143                         and then Page_Length (File) = 0)),
144     Global => (In_Out => File_System);
145   procedure Reset  (File : in out File_Type) with
146     Pre    => Is_Open (File),
147     Post   =>
148       Is_Open (File)
149       and Mode (File)'Old = Mode (File)
150       and (if Mode (File) /= In_File
151                then (Line_Length (File) = 0
152                      and then Page_Length (File) = 0)),
153     Global => (In_Out => File_System);
154
155   function Mode (File : File_Type) return File_Mode with
156     Pre    => Is_Open (File),
157     Global => null;
158   function Name (File : File_Type) return String with
159     Pre    => Is_Open (File),
160     Global => null;
161   function Form (File : File_Type) return String with
162     Pre    => Is_Open (File),
163     Global => null;
164
165   function Is_Open (File : File_Type) return Boolean with
166     Global => null;
167
168   ------------------------------------------------------
169   -- Control of default input, output and error files --
170   ------------------------------------------------------
171
172   procedure Set_Input  (File : File_Type) with SPARK_Mode => Off;
173   procedure Set_Output (File : File_Type) with SPARK_Mode => Off;
174   procedure Set_Error  (File : File_Type) with SPARK_Mode => Off;
175
176   function Standard_Input  return File_Type with SPARK_Mode => Off;
177   function Standard_Output return File_Type with SPARK_Mode => Off;
178   function Standard_Error  return File_Type with SPARK_Mode => Off;
179
180   function Current_Input  return File_Type with SPARK_Mode => Off;
181   function Current_Output return File_Type with SPARK_Mode => Off;
182   function Current_Error  return File_Type with SPARK_Mode => Off;
183
184   type File_Access is access constant File_Type;
185
186   function Standard_Input  return File_Access with SPARK_Mode => Off;
187   function Standard_Output return File_Access with SPARK_Mode => Off;
188   function Standard_Error  return File_Access with SPARK_Mode => Off;
189
190   function Current_Input  return File_Access with SPARK_Mode => Off;
191   function Current_Output return File_Access with SPARK_Mode => Off;
192   function Current_Error  return File_Access with SPARK_Mode => Off;
193
194   --------------------
195   -- Buffer control --
196   --------------------
197
198   --  Note: The parameter file is IN OUT in the RM, but this is clearly
199   --  an oversight, and was intended to be IN, see AI95-00057.
200
201   procedure Flush (File : File_Type) with
202     Pre    => Is_Open (File) and then Mode (File) /= In_File,
203     Post   =>
204       Line_Length (File)'Old = Line_Length (File)
205       and Page_Length (File)'Old = Page_Length (File),
206     Global => (In_Out => File_System);
207   procedure Flush with
208     Post   =>
209       Line_Length'Old = Line_Length
210       and Page_Length'Old = Page_Length,
211     Global => (In_Out => File_System);
212
213   --------------------------------------------
214   -- Specification of line and page lengths --
215   --------------------------------------------
216
217   procedure Set_Line_Length (File : File_Type; To : Count) with
218     Pre    => Is_Open (File)  and then Mode (File) /= In_File,
219     Post   =>
220       Line_Length (File) = To
221       and Page_Length (File)'Old = Page_Length (File),
222     Global => (In_Out => File_System);
223   procedure Set_Line_Length (To : Count) with
224     Post   =>
225       Line_Length = To
226       and Page_Length'Old = Page_Length,
227     Global => (In_Out => File_System);
228
229   procedure Set_Page_Length (File : File_Type; To : Count) with
230     Pre    => Is_Open (File) and then Mode (File) /= In_File,
231     Post   =>
232       Page_Length (File) = To
233       and Line_Length (File)'Old = Line_Length (File),
234     Global => (In_Out => File_System);
235   procedure Set_Page_Length (To : Count) with
236     Post   =>
237       Page_Length = To
238       and Line_Length'Old = Line_Length,
239     Global => (In_Out => File_System);
240
241   function Line_Length (File : File_Type) return Count with
242     Pre    => Is_Open (File) and then Mode (File) /= In_File,
243     Global => (Input => File_System);
244   function Line_Length return Count with
245     Global => (Input => File_System);
246
247   function Page_Length (File : File_Type) return Count with
248     Pre    => Is_Open (File) and then Mode (File) /= In_File,
249     Global => (Input => File_System);
250   function Page_Length return Count with
251     Global => (Input => File_System);
252
253   ------------------------------------
254   -- Column, Line, and Page Control --
255   ------------------------------------
256
257   procedure New_Line (File : File_Type; Spacing : Positive_Count := 1) with
258     Pre    => Is_Open (File) and then Mode (File) /= In_File,
259     Post   =>
260       Line_Length (File)'Old = Line_Length (File)
261       and Page_Length (File)'Old = Page_Length (File),
262     Global => (In_Out => File_System);
263   procedure New_Line (Spacing : Positive_Count := 1) with
264     Post   =>
265       Line_Length'Old = Line_Length
266       and Page_Length'Old = Page_Length,
267     Global => (In_Out => File_System);
268
269   procedure Skip_Line (File : File_Type; Spacing : Positive_Count := 1) with
270     Pre    => Is_Open (File) and then Mode (File) = In_File,
271     Global => (In_Out => File_System);
272   procedure Skip_Line (Spacing : Positive_Count := 1) with
273     Post   =>
274       Line_Length'Old = Line_Length
275       and Page_Length'Old = Page_Length,
276     Global => (In_Out => File_System);
277
278   function End_Of_Line (File : File_Type) return Boolean with
279     Pre    => Is_Open (File) and then Mode (File) = In_File,
280     Global => (Input => File_System);
281   function End_Of_Line return Boolean with
282     Global => (Input => File_System);
283
284   procedure New_Page (File : File_Type) with
285     Pre    => Is_Open (File) and then Mode (File) /= In_File,
286     Post   =>
287       Line_Length (File)'Old = Line_Length (File)
288       and Page_Length (File)'Old = Page_Length (File),
289     Global => (In_Out => File_System);
290   procedure New_Page with
291     Post   =>
292       Line_Length'Old = Line_Length
293       and Page_Length'Old = Page_Length,
294     Global => (In_Out => File_System);
295
296   procedure Skip_Page (File : File_Type) with
297     Pre    => Is_Open (File) and then Mode (File) = In_File,
298     Global => (In_Out => File_System);
299   procedure Skip_Page with
300     Post   =>
301       Line_Length'Old = Line_Length
302       and Page_Length'Old = Page_Length,
303     Global => (In_Out => File_System);
304
305   function End_Of_Page (File : File_Type) return Boolean with
306     Pre    => Is_Open (File) and then Mode (File) = In_File,
307     Global => (Input => File_System);
308   function End_Of_Page return Boolean with
309     Global => (Input => File_System);
310
311   function End_Of_File (File : File_Type) return Boolean with
312     Pre    => Is_Open (File) and then Mode (File) = In_File,
313     Global => (Input => File_System);
314   function End_Of_File return Boolean with
315     Global => (Input => File_System);
316
317   procedure Set_Col (File : File_Type;  To : Positive_Count) with
318     Pre            =>
319       Is_Open (File)
320       and then (if Mode (File) /= In_File
321                     then (Line_Length (File) = 0
322                           or else To <= Line_Length (File))),
323     Contract_Cases =>
324       (Mode (File) /= In_File =>
325              Line_Length (File)'Old = Line_Length (File)
326              and Page_Length (File)'Old = Page_Length (File),
327        others                 => True),
328     Global         => (In_Out => File_System);
329   procedure Set_Col (To : Positive_Count) with
330     Pre    => Line_Length = 0 or To <= Line_Length,
331     Post   =>
332       Line_Length'Old = Line_Length
333       and Page_Length'Old = Page_Length,
334     Global => (In_Out => File_System);
335
336   procedure Set_Line (File : File_Type; To : Positive_Count) with
337     Pre            =>
338       Is_Open (File)
339       and then (if Mode (File) /= In_File
340                     then (Page_Length (File) = 0
341                           or else To <= Page_Length (File))),
342     Contract_Cases =>
343       (Mode (File) /= In_File =>
344              Line_Length (File)'Old = Line_Length (File)
345              and Page_Length (File)'Old = Page_Length (File),
346        others                 => True),
347     Global         => (In_Out => File_System);
348   procedure Set_Line (To : Positive_Count) with
349     Pre    => Page_Length = 0 or To <= Page_Length,
350     Post   =>
351       Line_Length'Old = Line_Length
352       and Page_Length'Old = Page_Length,
353     Global => (In_Out => File_System);
354
355   function Col (File : File_Type) return Positive_Count with
356     Pre    => Is_Open (File),
357     Global => (Input => File_System);
358   function Col return Positive_Count with
359     Global => (Input => File_System);
360
361   function Line (File : File_Type) return Positive_Count with
362     Pre    => Is_Open (File),
363     Global => (Input => File_System);
364   function Line return Positive_Count with
365     Global => (Input => File_System);
366
367   function Page (File : File_Type) return Positive_Count with
368     Pre => Is_Open (File),
369     Global => (Input => File_System);
370   function Page return Positive_Count with
371     Global => (Input => File_System);
372
373   ----------------------------
374   -- Character Input-Output --
375   ----------------------------
376
377   procedure Get (File : File_Type; Item : out Character) with
378     Pre    => Is_Open (File) and then Mode (File) = In_File,
379     Global => (In_Out => File_System);
380   procedure Get (Item : out Character) with
381     Post   =>
382       Line_Length'Old = Line_Length
383       and Page_Length'Old = Page_Length,
384     Global => (In_Out => File_System);
385   procedure Put (File : File_Type; Item : Character) with
386     Pre    => Is_Open (File) and then Mode (File) /= In_File,
387     Post   =>
388       Line_Length (File)'Old = Line_Length (File)
389       and Page_Length (File)'Old = Page_Length (File),
390     Global => (In_Out => File_System);
391   procedure Put (Item : Character) with
392     Post   =>
393       Line_Length'Old = Line_Length
394       and Page_Length'Old = Page_Length,
395     Global => (In_Out => File_System);
396
397   procedure Look_Ahead
398     (File        : File_Type;
399      Item        : out Character;
400      End_Of_Line : out Boolean)
401   with
402     Pre    => Is_Open (File) and then Mode (File) = In_File,
403     Global => (Input => File_System);
404
405   procedure Look_Ahead
406     (Item        : out Character;
407      End_Of_Line : out Boolean)
408   with
409     Post   =>
410       Line_Length'Old = Line_Length
411       and Page_Length'Old = Page_Length,
412     Global => (Input => File_System);
413
414   procedure Get_Immediate
415     (File : File_Type;
416      Item : out Character)
417   with
418     Pre    => Is_Open (File) and then Mode (File) = In_File,
419     Global => (In_Out => File_System);
420
421   procedure Get_Immediate
422     (Item : out Character)
423   with
424     Post   =>
425       Line_Length'Old = Line_Length
426       and Page_Length'Old = Page_Length,
427     Global => (In_Out => File_System);
428
429   procedure Get_Immediate
430     (File      : File_Type;
431      Item      : out Character;
432      Available : out Boolean)
433   with
434     Pre    => Is_Open (File) and then Mode (File) = In_File,
435     Global => (In_Out => File_System);
436
437   procedure Get_Immediate
438     (Item      : out Character;
439      Available : out Boolean)
440   with
441     Post   =>
442       Line_Length'Old = Line_Length
443       and Page_Length'Old = Page_Length,
444     Global => (In_Out => File_System);
445
446   -------------------------
447   -- String Input-Output --
448   -------------------------
449
450   procedure Get (File : File_Type; Item : out String) with
451     Pre    => Is_Open (File) and then Mode (File) = In_File,
452     Global => (In_Out => File_System);
453   procedure Get (Item : out String) with
454     Post   =>
455       Line_Length'Old = Line_Length
456       and Page_Length'Old = Page_Length,
457     Global => (In_Out => File_System);
458   procedure Put (File : File_Type; Item : String) with
459     Pre    => Is_Open (File) and then Mode (File) /= In_File,
460     Post   =>
461       Line_Length (File)'Old = Line_Length (File)
462       and Page_Length (File)'Old = Page_Length (File),
463     Global => (In_Out => File_System);
464   procedure Put (Item : String) with
465     Post   =>
466       Line_Length'Old = Line_Length
467       and Page_Length'Old = Page_Length,
468     Global => (In_Out => File_System);
469
470   procedure Get_Line
471     (File : File_Type;
472      Item : out String;
473      Last : out Natural)
474   with
475     Pre    => Is_Open (File) and then Mode (File) = In_File,
476     Post   => (if Item'Length > 0 then Last in Item'First - 1 .. Item'Last
477               else Last = Item'First - 1),
478     Global => (In_Out => File_System);
479
480   procedure Get_Line
481     (Item : out String;
482      Last : out Natural)
483   with
484     Post   =>
485       Line_Length'Old = Line_Length
486       and Page_Length'Old = Page_Length
487       and (if Item'Length > 0 then Last in Item'First - 1 .. Item'Last
488            else Last = Item'First - 1),
489     Global => (In_Out => File_System);
490
491   function Get_Line (File : File_Type) return String with SPARK_Mode => Off;
492   pragma Ada_05 (Get_Line);
493
494   function Get_Line return String with SPARK_Mode => Off;
495   pragma Ada_05 (Get_Line);
496
497   procedure Put_Line
498     (File : File_Type;
499      Item : String)
500   with
501     Pre    => Is_Open (File) and then Mode (File) /= In_File,
502     Post   =>
503       Line_Length (File)'Old = Line_Length (File)
504       and Page_Length (File)'Old = Page_Length (File),
505     Global => (In_Out => File_System);
506
507   procedure Put_Line
508     (Item : String)
509   with
510     Post   =>
511       Line_Length'Old = Line_Length
512       and Page_Length'Old = Page_Length,
513     Global => (In_Out => File_System);
514
515   ---------------------------------------
516   -- Generic packages for Input-Output --
517   ---------------------------------------
518
519   --  The generic packages:
520
521   --    Ada.Text_IO.Integer_IO
522   --    Ada.Text_IO.Modular_IO
523   --    Ada.Text_IO.Float_IO
524   --    Ada.Text_IO.Fixed_IO
525   --    Ada.Text_IO.Decimal_IO
526   --    Ada.Text_IO.Enumeration_IO
527
528   --  are implemented as separate child packages in GNAT, so the
529   --  spec and body of these packages are to be found in separate
530   --  child units. This implementation detail is hidden from the
531   --  Ada programmer by special circuitry in the compiler that
532   --  treats these child packages as though they were nested in
533   --  Text_IO. The advantage of this special processing is that
534   --  the subsidiary routines needed if these generics are used
535   --  are not loaded when they are not used.
536
537   ----------------
538   -- Exceptions --
539   ----------------
540
541   Status_Error : exception renames IO_Exceptions.Status_Error;
542   Mode_Error   : exception renames IO_Exceptions.Mode_Error;
543   Name_Error   : exception renames IO_Exceptions.Name_Error;
544   Use_Error    : exception renames IO_Exceptions.Use_Error;
545   Device_Error : exception renames IO_Exceptions.Device_Error;
546   End_Error    : exception renames IO_Exceptions.End_Error;
547   Data_Error   : exception renames IO_Exceptions.Data_Error;
548   Layout_Error : exception renames IO_Exceptions.Layout_Error;
549
550private
551   pragma SPARK_Mode (Off);
552
553   --  The following procedures have a File_Type formal of mode IN OUT because
554   --  they may close the original file. The Close operation may raise an
555   --  exception, but in that case we want any assignment to the formal to
556   --  be effective anyway, so it must be passed by reference (or the caller
557   --  will be left with a dangling pointer).
558
559   pragma Export_Procedure
560     (Internal  => Close,
561      External  => "",
562      Mechanism => Reference);
563   pragma Export_Procedure
564     (Internal  => Delete,
565      External  => "",
566      Mechanism => Reference);
567   pragma Export_Procedure
568     (Internal        => Reset,
569      External        => "",
570      Parameter_Types => (File_Type),
571      Mechanism       => Reference);
572   pragma Export_Procedure
573     (Internal        => Reset,
574      External        => "",
575      Parameter_Types => (File_Type, File_Mode),
576      Mechanism       => (File => Reference));
577
578   -----------------------------------
579   -- Handling of Format Characters --
580   -----------------------------------
581
582   --  Line marks are represented by the single character ASCII.LF (16#0A#).
583   --  In DOS and similar systems, underlying file translation takes care
584   --  of translating this to and from the standard CR/LF sequences used in
585   --  these operating systems to mark the end of a line. On output there is
586   --  always a line mark at the end of the last line, but on input, this
587   --  line mark can be omitted, and is implied by the end of file.
588
589   --  Page marks are represented by the single character ASCII.FF (16#0C#),
590   --  The page mark at the end of the file may be omitted, and is normally
591   --  omitted on output unless an explicit New_Page call is made before
592   --  closing the file. No page mark is added when a file is appended to,
593   --  so, in accordance with the permission in (RM A.10.2(4)), there may
594   --  or may not be a page mark separating preexisting text in the file
595   --  from the new text to be written.
596
597   --  A file mark is marked by the physical end of file. In DOS translation
598   --  mode on input, an EOF character (SUB = 16#1A#) gets translated to the
599   --  physical end of file, so in effect this character is recognized as
600   --  marking the end of file in DOS and similar systems.
601
602   LM : constant := Character'Pos (ASCII.LF);
603   --  Used as line mark
604
605   PM : constant := Character'Pos (ASCII.FF);
606   --  Used as page mark, except at end of file where it is implied
607
608   --------------------------------
609   -- Text_IO File Control Block --
610   --------------------------------
611
612   Default_WCEM : System.WCh_Con.WC_Encoding_Method :=
613                    System.WCh_Con.WCEM_UTF8;
614   --  This gets modified during initialization (see body) using
615   --  the default value established in the call to Set_Globals.
616
617   package FCB renames System.File_Control_Block;
618
619   type Text_AFCB;
620   type File_Type is access all Text_AFCB;
621
622   type Text_AFCB is new FCB.AFCB with record
623      Page        : Count := 1;
624      Line        : Count := 1;
625      Col         : Count := 1;
626      Line_Length : Count := 0;
627      Page_Length : Count := 0;
628
629      Self : aliased File_Type;
630      --  Set to point to the containing Text_AFCB block. This is used to
631      --  implement the Current_{Error,Input,Output} functions which return
632      --  a File_Access, the file access value returned is a pointer to
633      --  the Self field of the corresponding file.
634
635      Before_LM : Boolean := False;
636      --  This flag is used to deal with the anomalies introduced by the
637      --  peculiar definition of End_Of_File and End_Of_Page in Ada. These
638      --  functions require looking ahead more than one character. Since
639      --  there is no convenient way of backing up more than one character,
640      --  what we do is to leave ourselves positioned past the LM, but set
641      --  this flag, so that we know that from an Ada point of view we are
642      --  in front of the LM, not after it. A little odd, but it works.
643
644      Before_LM_PM : Boolean := False;
645      --  This flag similarly handles the case of being physically positioned
646      --  after a LM-PM sequence when logically we are before the LM-PM. This
647      --  flag can only be set if Before_LM is also set.
648
649      WC_Method : System.WCh_Con.WC_Encoding_Method := Default_WCEM;
650      --  Encoding method to be used for this file. Text_IO does not deal with
651      --  wide characters, but it does deal with upper half characters in the
652      --  range 16#80#-16#FF# which may need encoding, e.g. in UTF-8 mode.
653
654      Before_Upper_Half_Character : Boolean := False;
655      --  This flag is set to indicate that an encoded upper half character has
656      --  been read by Text_IO.Look_Ahead. If it is set to True, then it means
657      --  that the stream is logically positioned before the character but is
658      --  physically positioned after it. The character involved must be in
659      --  the range 16#80#-16#FF#, i.e. if the flag is set, then we know the
660      --  next character has a code greater than 16#7F#, and the value of this
661      --  character is saved in Saved_Upper_Half_Character.
662
663      Saved_Upper_Half_Character : Character;
664      --  This field is valid only if Before_Upper_Half_Character is set. It
665      --  contains an upper-half character read by Look_Ahead. If Look_Ahead
666      --  reads a character in the range 16#00# to 16#7F#, then it can use
667      --  ungetc to put it back, but ungetc cannot be called more than once,
668      --  so for characters above this range, we don't try to back up the
669      --  file. Instead we save the character in this field and set the flag
670      --  Before_Upper_Half_Character to True to indicate that we are logically
671      --  positioned before this character even though the stream is physically
672      --  positioned after it.
673
674   end record;
675
676   function AFCB_Allocate (Control_Block : Text_AFCB) return FCB.AFCB_Ptr;
677
678   procedure AFCB_Close (File : not null access Text_AFCB);
679   procedure AFCB_Free  (File : not null access Text_AFCB);
680
681   procedure Read
682     (File : in out Text_AFCB;
683      Item : out Ada.Streams.Stream_Element_Array;
684      Last : out Ada.Streams.Stream_Element_Offset);
685   --  Read operation used when Text_IO file is treated directly as Stream
686
687   procedure Write
688     (File : in out Text_AFCB;
689      Item : Ada.Streams.Stream_Element_Array);
690   --  Write operation used when Text_IO file is treated directly as Stream
691
692   ------------------------
693   -- The Standard Files --
694   ------------------------
695
696   Standard_In_AFCB  : aliased Text_AFCB;
697   Standard_Out_AFCB : aliased Text_AFCB;
698   Standard_Err_AFCB : aliased Text_AFCB;
699
700   Standard_In  : aliased File_Type := Standard_In_AFCB'Access with
701     Part_Of => File_System;
702   Standard_Out : aliased File_Type := Standard_Out_AFCB'Access with
703     Part_Of => File_System;
704   Standard_Err : aliased File_Type := Standard_Err_AFCB'Access with
705     Part_Of => File_System;
706   --  Standard files
707
708   Current_In   : aliased File_Type := Standard_In with
709     Part_Of => File_System;
710   Current_Out  : aliased File_Type := Standard_Out with
711     Part_Of => File_System;
712   Current_Err  : aliased File_Type := Standard_Err with
713     Part_Of => File_System;
714   --  Current files
715
716   function EOF_Char return Integer;
717   --  Returns the system-specific character indicating the end of a text file.
718   --  This is exported for use by child packages such as Enumeration_Aux to
719   --  eliminate their needing to depend directly on Interfaces.C_Streams,
720   --  which might not be available in certain target environments.
721
722   procedure Initialize_Standard_Files;
723   --  Initializes the file control blocks for the standard files. Called from
724   --  the elaboration routine for this package, and from Reset_Standard_Files
725   --  in package Ada.Text_IO.Reset_Standard_Files.
726
727end Ada.Text_IO;
728