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