OSDN Git Service

2009-10-28 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / a-textio.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT RUN-TIME COMPONENTS                         --
4 --                                                                          --
5 --                          A D A . T E X T _ I O                           --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2009, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.                                     --
17 --                                                                          --
18 -- As a special exception under Section 7 of GPL version 3, you are granted --
19 -- additional permissions described in the GCC Runtime Library Exception,   --
20 -- version 3.1, as published by the Free Software Foundation.               --
21 --                                                                          --
22 -- You should have received a copy of the GNU General Public License and    --
23 -- a copy of the GCC Runtime Library Exception along with this program;     --
24 -- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
25 -- <http://www.gnu.org/licenses/>.                                          --
26 --                                                                          --
27 -- GNAT was originally developed  by the GNAT team at  New York University. --
28 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
29 --                                                                          --
30 ------------------------------------------------------------------------------
31
32 with Ada.Streams;          use Ada.Streams;
33 with Interfaces.C_Streams; use Interfaces.C_Streams;
34
35 with System.File_IO;
36 with System.CRTL;
37 with System.WCh_Cnv;       use System.WCh_Cnv;
38 with System.WCh_Con;       use System.WCh_Con;
39
40 with Ada.Unchecked_Conversion;
41 with Ada.Unchecked_Deallocation;
42
43 pragma Elaborate_All (System.File_IO);
44 --  Needed because of calls to Chain_File in package body elaboration
45
46 package body Ada.Text_IO is
47
48    package FIO renames System.File_IO;
49
50    subtype AP is FCB.AFCB_Ptr;
51
52    function To_FCB is new Ada.Unchecked_Conversion (File_Mode, FCB.File_Mode);
53    function To_TIO is new Ada.Unchecked_Conversion (FCB.File_Mode, File_Mode);
54    use type FCB.File_Mode;
55
56    use type System.CRTL.size_t;
57
58    WC_Encoding : Character;
59    pragma Import (C, WC_Encoding, "__gl_wc_encoding");
60    --  Default wide character encoding
61
62    Err_Name : aliased String := "*stderr" & ASCII.NUL;
63    In_Name  : aliased String := "*stdin" & ASCII.NUL;
64    Out_Name : aliased String := "*stdout" & ASCII.NUL;
65    --  Names of standard files
66    --
67    --  Use "preallocated" strings to avoid calling "new" during the elaboration
68    --  of the run time. This is needed in the tasking case to avoid calling
69    --  Task_Lock too early. A filename is expected to end with a null character
70    --  in the runtime, here the null characters are added just to have a
71    --  correct filename length.
72    --
73    --  Note: the names for these files are bogus, and probably it would be
74    --  better for these files to have no names, but the ACVC tests insist!
75    --  We use names that are bound to fail in open etc.
76
77    Null_Str : aliased constant String := "";
78    --  Used as form string for standard files
79
80    -----------------------
81    -- Local Subprograms --
82    -----------------------
83
84    function Get_Upper_Half_Char
85      (C    : Character;
86       File : File_Type) return Character;
87    --  This function is shared by Get and Get_Immediate to extract an encoded
88    --  upper half character value from the given File. The first byte has
89    --  already been read and is passed in C. The character value is returned as
90    --  the result, and the file pointer is bumped past the character.
91    --  Constraint_Error is raised if the encoded value is outside the bounds of
92    --  type Character.
93
94    function Get_Upper_Half_Char_Immed
95      (C    : Character;
96       File : File_Type) return Character;
97    --  This routine is identical to Get_Upper_Half_Char, except that the reads
98    --  are done in Get_Immediate mode (i.e. without waiting for a line return).
99
100    function Getc (File : File_Type) return int;
101    --  Gets next character from file, which has already been checked for being
102    --  in read status, and returns the character read if no error occurs. The
103    --  result is EOF if the end of file was read.
104
105    function Getc_Immed (File : File_Type) return int;
106    --  This routine is identical to Getc, except that the read is done in
107    --  Get_Immediate mode (i.e. without waiting for a line return).
108
109    function Has_Upper_Half_Character (Item : String) return Boolean;
110    --  Returns True if any of the characters is in the range 16#80#-16#FF#
111
112    function Nextc (File : File_Type) return int;
113    --  Returns next character from file without skipping past it (i.e. it is a
114    --  combination of Getc followed by an Ungetc).
115
116    procedure Put_Encoded (File : File_Type; Char : Character);
117    --  Called to output a character Char to the given File, when the encoding
118    --  method for the file is other than brackets, and Char is upper half.
119
120    procedure Putc (ch : int; File : File_Type);
121    --  Outputs the given character to the file, which has already been checked
122    --  for being in output status. Device_Error is raised if the character
123    --  cannot be written.
124
125    procedure Set_WCEM (File : in out File_Type);
126    --  Called by Open and Create to set the wide character encoding method for
127    --  the file, processing a WCEM form parameter if one is present. File is
128    --  IN OUT because it may be closed in case of an error.
129
130    procedure Terminate_Line (File : File_Type);
131    --  If the file is in Write_File or Append_File mode, and the current line
132    --  is not terminated, then a line terminator is written using New_Line.
133    --  Note that there is no Terminate_Page routine, because the page mark at
134    --  the end of the file is implied if necessary.
135
136    procedure Ungetc (ch : int; File : File_Type);
137    --  Pushes back character into stream, using ungetc. The caller has checked
138    --  that the file is in read status. Device_Error is raised if the character
139    --  cannot be pushed back. An attempt to push back and end of file character
140    --  (EOF) is ignored.
141
142    -------------------
143    -- AFCB_Allocate --
144    -------------------
145
146    function AFCB_Allocate (Control_Block : Text_AFCB) return FCB.AFCB_Ptr is
147       pragma Unreferenced (Control_Block);
148    begin
149       return new Text_AFCB;
150    end AFCB_Allocate;
151
152    ----------------
153    -- AFCB_Close --
154    ----------------
155
156    procedure AFCB_Close (File : not null access Text_AFCB) is
157    begin
158       --  If the file being closed is one of the current files, then close
159       --  the corresponding current file. It is not clear that this action
160       --  is required (RM A.10.3(23)) but it seems reasonable, and besides
161       --  ACVC test CE3208A expects this behavior.
162
163       if File_Type (File) = Current_In then
164          Current_In := null;
165       elsif File_Type (File) = Current_Out then
166          Current_Out := null;
167       elsif File_Type (File) = Current_Err then
168          Current_Err := null;
169       end if;
170
171       Terminate_Line (File_Type (File));
172    end AFCB_Close;
173
174    ---------------
175    -- AFCB_Free --
176    ---------------
177
178    procedure AFCB_Free (File : not null access Text_AFCB) is
179       type FCB_Ptr is access all Text_AFCB;
180       FT : FCB_Ptr := FCB_Ptr (File);
181
182       procedure Free is new Ada.Unchecked_Deallocation (Text_AFCB, FCB_Ptr);
183
184    begin
185       Free (FT);
186    end AFCB_Free;
187
188    -----------
189    -- Close --
190    -----------
191
192    procedure Close (File : in out File_Type) is
193    begin
194       FIO.Close (AP (File)'Unrestricted_Access);
195    end Close;
196
197    ---------
198    -- Col --
199    ---------
200
201    --  Note: we assume that it is impossible in practice for the column
202    --  to exceed the value of Count'Last, i.e. no check is required for
203    --  overflow raising layout error.
204
205    function Col (File : File_Type) return Positive_Count is
206    begin
207       FIO.Check_File_Open (AP (File));
208       return File.Col;
209    end Col;
210
211    function Col return Positive_Count is
212    begin
213       return Col (Current_Out);
214    end Col;
215
216    ------------
217    -- Create --
218    ------------
219
220    procedure Create
221      (File : in out File_Type;
222       Mode : File_Mode := Out_File;
223       Name : String := "";
224       Form : String := "")
225    is
226       Dummy_File_Control_Block : Text_AFCB;
227       pragma Warnings (Off, Dummy_File_Control_Block);
228       --  Yes, we know this is never assigned a value, only the tag
229       --  is used for dispatching purposes, so that's expected.
230
231    begin
232       FIO.Open (File_Ptr  => AP (File),
233                 Dummy_FCB => Dummy_File_Control_Block,
234                 Mode      => To_FCB (Mode),
235                 Name      => Name,
236                 Form      => Form,
237                 Amethod   => 'T',
238                 Creat     => True,
239                 Text      => True);
240
241       File.Self := File;
242       Set_WCEM (File);
243    end Create;
244
245    -------------------
246    -- Current_Error --
247    -------------------
248
249    function Current_Error return File_Type is
250    begin
251       return Current_Err;
252    end Current_Error;
253
254    function Current_Error return File_Access is
255    begin
256       return Current_Err.Self'Access;
257    end Current_Error;
258
259    -------------------
260    -- Current_Input --
261    -------------------
262
263    function Current_Input return File_Type is
264    begin
265       return Current_In;
266    end Current_Input;
267
268    function Current_Input return File_Access is
269    begin
270       return Current_In.Self'Access;
271    end Current_Input;
272
273    --------------------
274    -- Current_Output --
275    --------------------
276
277    function Current_Output return File_Type is
278    begin
279       return Current_Out;
280    end Current_Output;
281
282    function Current_Output return File_Access is
283    begin
284       return Current_Out.Self'Access;
285    end Current_Output;
286
287    ------------
288    -- Delete --
289    ------------
290
291    procedure Delete (File : in out File_Type) is
292    begin
293       FIO.Delete (AP (File)'Unrestricted_Access);
294    end Delete;
295
296    -----------------
297    -- End_Of_File --
298    -----------------
299
300    function End_Of_File (File : File_Type) return Boolean is
301       ch : int;
302
303    begin
304       FIO.Check_Read_Status (AP (File));
305
306       if File.Before_Upper_Half_Character then
307          return False;
308
309       elsif File.Before_LM then
310          if File.Before_LM_PM then
311             return Nextc (File) = EOF;
312          end if;
313
314       else
315          ch := Getc (File);
316
317          if ch = EOF then
318             return True;
319
320          elsif ch /= LM then
321             Ungetc (ch, File);
322             return False;
323
324          else -- ch = LM
325             File.Before_LM := True;
326          end if;
327       end if;
328
329       --  Here we are just past the line mark with Before_LM set so that we
330       --  do not have to try to back up past the LM, thus avoiding the need
331       --  to back up more than one character.
332
333       ch := Getc (File);
334
335       if ch = EOF then
336          return True;
337
338       elsif ch = PM and then File.Is_Regular_File then
339          File.Before_LM_PM := True;
340          return Nextc (File) = EOF;
341
342       --  Here if neither EOF nor PM followed end of line
343
344       else
345          Ungetc (ch, File);
346          return False;
347       end if;
348
349    end End_Of_File;
350
351    function End_Of_File return Boolean is
352    begin
353       return End_Of_File (Current_In);
354    end End_Of_File;
355
356    -----------------
357    -- End_Of_Line --
358    -----------------
359
360    function End_Of_Line (File : File_Type) return Boolean is
361       ch : int;
362
363    begin
364       FIO.Check_Read_Status (AP (File));
365
366       if File.Before_Upper_Half_Character then
367          return False;
368
369       elsif File.Before_LM then
370          return True;
371
372       else
373          ch := Getc (File);
374
375          if ch = EOF then
376             return True;
377
378          else
379             Ungetc (ch, File);
380             return (ch = LM);
381          end if;
382       end if;
383    end End_Of_Line;
384
385    function End_Of_Line return Boolean is
386    begin
387       return End_Of_Line (Current_In);
388    end End_Of_Line;
389
390    -----------------
391    -- End_Of_Page --
392    -----------------
393
394    function End_Of_Page (File : File_Type) return Boolean is
395       ch  : int;
396
397    begin
398       FIO.Check_Read_Status (AP (File));
399
400       if not File.Is_Regular_File then
401          return False;
402
403       elsif File.Before_Upper_Half_Character then
404          return False;
405
406       elsif File.Before_LM then
407          if File.Before_LM_PM then
408             return True;
409          end if;
410
411       else
412          ch := Getc (File);
413
414          if ch = EOF then
415             return True;
416
417          elsif ch /= LM then
418             Ungetc (ch, File);
419             return False;
420
421          else -- ch = LM
422             File.Before_LM := True;
423          end if;
424       end if;
425
426       --  Here we are just past the line mark with Before_LM set so that we
427       --  do not have to try to back up past the LM, thus avoiding the need
428       --  to back up more than one character.
429
430       ch := Nextc (File);
431
432       return ch = PM or else ch = EOF;
433    end End_Of_Page;
434
435    function End_Of_Page return Boolean is
436    begin
437       return End_Of_Page (Current_In);
438    end End_Of_Page;
439
440    -----------
441    -- Flush --
442    -----------
443
444    procedure Flush (File : File_Type) is
445    begin
446       FIO.Flush (AP (File));
447    end Flush;
448
449    procedure Flush is
450    begin
451       Flush (Current_Out);
452    end Flush;
453
454    ----------
455    -- Form --
456    ----------
457
458    function Form (File : File_Type) return String is
459    begin
460       return FIO.Form (AP (File));
461    end Form;
462
463    ---------
464    -- Get --
465    ---------
466
467    procedure Get
468      (File : File_Type;
469       Item : out Character)
470    is
471       ch : int;
472
473    begin
474       FIO.Check_Read_Status (AP (File));
475
476       if File.Before_Upper_Half_Character then
477          File.Before_Upper_Half_Character := False;
478          Item := File.Saved_Upper_Half_Character;
479
480       elsif File.Before_LM then
481          File.Before_LM := False;
482          File.Col := 1;
483
484          if File.Before_LM_PM then
485             File.Line := 1;
486             File.Page := File.Page + 1;
487             File.Before_LM_PM := False;
488          else
489             File.Line := File.Line + 1;
490          end if;
491       end if;
492
493       loop
494          ch := Getc (File);
495
496          if ch = EOF then
497             raise End_Error;
498
499          elsif ch = LM then
500             File.Line := File.Line + 1;
501             File.Col := 1;
502
503          elsif ch = PM and then File.Is_Regular_File then
504             File.Page := File.Page + 1;
505             File.Line := 1;
506
507          else
508             Item := Character'Val (ch);
509             File.Col := File.Col + 1;
510             return;
511          end if;
512       end loop;
513    end Get;
514
515    procedure Get (Item : out Character) is
516    begin
517       Get (Current_In, Item);
518    end Get;
519
520    procedure Get
521      (File : File_Type;
522       Item : out String)
523    is
524       ch : int;
525       J  : Natural;
526
527    begin
528       FIO.Check_Read_Status (AP (File));
529
530       if File.Before_LM then
531          File.Before_LM := False;
532          File.Before_LM_PM := False;
533          File.Col := 1;
534
535          if File.Before_LM_PM then
536             File.Line := 1;
537             File.Page := File.Page + 1;
538             File.Before_LM_PM := False;
539
540          else
541             File.Line := File.Line + 1;
542          end if;
543       end if;
544
545       J := Item'First;
546       while J <= Item'Last loop
547          ch := Getc (File);
548
549          if ch = EOF then
550             raise End_Error;
551
552          elsif ch = LM then
553             File.Line := File.Line + 1;
554             File.Col := 1;
555
556          elsif ch = PM and then File.Is_Regular_File then
557             File.Page := File.Page + 1;
558             File.Line := 1;
559
560          else
561             Item (J) := Character'Val (ch);
562             J := J + 1;
563             File.Col := File.Col + 1;
564          end if;
565       end loop;
566    end Get;
567
568    procedure Get (Item : out String) is
569    begin
570       Get (Current_In, Item);
571    end Get;
572
573    -------------------
574    -- Get_Immediate --
575    -------------------
576
577    procedure Get_Immediate
578      (File : File_Type;
579       Item : out Character)
580    is
581       ch          : int;
582
583    begin
584       FIO.Check_Read_Status (AP (File));
585
586       if File.Before_Upper_Half_Character then
587          File.Before_Upper_Half_Character := False;
588          Item := File.Saved_Upper_Half_Character;
589
590       elsif File.Before_LM then
591          File.Before_LM := False;
592          File.Before_LM_PM := False;
593          Item := Character'Val (LM);
594
595       else
596          ch := Getc_Immed (File);
597
598          if ch = EOF then
599             raise End_Error;
600          else
601             Item :=
602               (if not Is_Start_Of_Encoding (Character'Val (ch), File.WC_Method)
603                then Character'Val (ch)
604                else Get_Upper_Half_Char_Immed (Character'Val (ch), File));
605          end if;
606       end if;
607    end Get_Immediate;
608
609    procedure Get_Immediate
610      (Item : out Character)
611    is
612    begin
613       Get_Immediate (Current_In, Item);
614    end Get_Immediate;
615
616    procedure Get_Immediate
617      (File      : File_Type;
618       Item      : out Character;
619       Available : out Boolean)
620    is
621       ch          : int;
622       end_of_file : int;
623       avail       : int;
624
625       procedure getc_immediate_nowait
626         (stream      : FILEs;
627          ch          : out int;
628          end_of_file : out int;
629          avail       : out int);
630       pragma Import (C, getc_immediate_nowait, "getc_immediate_nowait");
631
632    begin
633       FIO.Check_Read_Status (AP (File));
634       Available := True;
635
636       if File.Before_Upper_Half_Character then
637          File.Before_Upper_Half_Character := False;
638          Item := File.Saved_Upper_Half_Character;
639
640       elsif File.Before_LM then
641          File.Before_LM := False;
642          File.Before_LM_PM := False;
643          Item := Character'Val (LM);
644
645       else
646          getc_immediate_nowait (File.Stream, ch, end_of_file, avail);
647
648          if ferror (File.Stream) /= 0 then
649             raise Device_Error;
650
651          elsif end_of_file /= 0 then
652             raise End_Error;
653
654          elsif avail = 0 then
655             Available := False;
656             Item := ASCII.NUL;
657
658          else
659             Available := True;
660
661             Item :=
662               (if Is_Start_Of_Encoding (Character'Val (ch), File.WC_Method)
663                then Character'Val (ch)
664                else Get_Upper_Half_Char_Immed (Character'Val (ch), File));
665          end if;
666       end if;
667
668    end Get_Immediate;
669
670    procedure Get_Immediate
671      (Item      : out Character;
672       Available : out Boolean)
673    is
674    begin
675       Get_Immediate (Current_In, Item, Available);
676    end Get_Immediate;
677
678    --------------
679    -- Get_Line --
680    --------------
681
682    procedure Get_Line
683      (File : File_Type;
684       Item : out String;
685       Last : out Natural)
686    is
687       ch : int;
688
689    begin
690       FIO.Check_Read_Status (AP (File));
691       Last := Item'First - 1;
692
693       --  Immediate exit for null string, this is a case in which we do not
694       --  need to test for end of file and we do not skip a line mark under
695       --  any circumstances.
696
697       if Last >= Item'Last then
698          return;
699       end if;
700
701       --  Here we have at least one character, if we are immediately before
702       --  a line mark, then we will just skip past it storing no characters.
703
704       if File.Before_LM then
705          File.Before_LM := False;
706          File.Before_LM_PM := False;
707
708       --  Otherwise we need to read some characters
709
710       else
711          ch := Getc (File);
712
713          --  If we are at the end of file now, it means we are trying to
714          --  skip a file terminator and we raise End_Error (RM A.10.7(20))
715
716          if ch = EOF then
717             raise End_Error;
718          end if;
719
720          --  Loop through characters. Don't bother if we hit a page mark,
721          --  since in normal files, page marks can only follow line marks
722          --  in any case and we only promise to treat the page nonsense
723          --  correctly in the absense of such rogue page marks.
724
725          loop
726             --  Exit the loop if read is terminated by encountering line mark
727
728             exit when ch = LM;
729
730             --  Otherwise store the character, note that we know that ch is
731             --  something other than LM or EOF. It could possibly be a page
732             --  mark if there is a stray page mark in the middle of a line,
733             --  but this is not an official page mark in any case, since
734             --  official page marks can only follow a line mark. The whole
735             --  page business is pretty much nonsense anyway, so we do not
736             --  want to waste time trying to make sense out of non-standard
737             --  page marks in the file! This means that the behavior of
738             --  Get_Line is different from repeated Get of a character, but
739             --  that's too bad. We only promise that page numbers etc make
740             --  sense if the file is formatted in a standard manner.
741
742             --  Note: we do not adjust the column number because it is quicker
743             --  to adjust it once at the end of the operation than incrementing
744             --  it each time around the loop.
745
746             Last := Last + 1;
747             Item (Last) := Character'Val (ch);
748
749             --  All done if the string is full, this is the case in which
750             --  we do not skip the following line mark. We need to adjust
751             --  the column number in this case.
752
753             if Last = Item'Last then
754                File.Col := File.Col + Count (Item'Length);
755                return;
756             end if;
757
758             --  Otherwise read next character. We also exit from the loop if
759             --  we read an end of file. This is the case where the last line
760             --  is not terminated with a line mark, and we consider that there
761             --  is an implied line mark in this case (this is a non-standard
762             --  file, but it is nice to treat it reasonably).
763
764             ch := Getc (File);
765             exit when ch = EOF;
766          end loop;
767       end if;
768
769       --  We have skipped past, but not stored, a line mark. Skip following
770       --  page mark if one follows, but do not do this for a non-regular
771       --  file (since otherwise we get annoying wait for an extra character)
772
773       File.Line := File.Line + 1;
774       File.Col := 1;
775
776       if File.Before_LM_PM then
777          File.Line := 1;
778          File.Before_LM_PM := False;
779          File.Page := File.Page + 1;
780
781       elsif File.Is_Regular_File then
782          ch := Getc (File);
783
784          if ch = PM and then File.Is_Regular_File then
785             File.Line := 1;
786             File.Page := File.Page + 1;
787          else
788             Ungetc (ch, File);
789          end if;
790       end if;
791    end Get_Line;
792
793    procedure Get_Line
794      (Item : out String;
795       Last : out Natural)
796    is
797    begin
798       Get_Line (Current_In, Item, Last);
799    end Get_Line;
800
801    function Get_Line (File : File_Type) return String is
802       Buffer : String (1 .. 500);
803       Last   : Natural;
804
805       function Get_Rest (S : String) return String;
806       --  This is a recursive function that reads the rest of the line and
807       --  returns it. S is the part read so far.
808
809       --------------
810       -- Get_Rest --
811       --------------
812
813       function Get_Rest (S : String) return String is
814
815          --  Each time we allocate a buffer the same size as what we have
816          --  read so far. This limits us to a logarithmic number of calls
817          --  to Get_Rest and also ensures only a linear use of stack space.
818
819          Buffer : String (1 .. S'Length);
820          Last   : Natural;
821
822       begin
823          Get_Line (File, Buffer, Last);
824
825          declare
826             R : constant String := S & Buffer (1 .. Last);
827          begin
828             if Last < Buffer'Last then
829                return R;
830             else
831                return Get_Rest (R);
832             end if;
833          end;
834       end Get_Rest;
835
836    --  Start of processing for Get_Line
837
838    begin
839       Get_Line (File, Buffer, Last);
840
841       if Last < Buffer'Last then
842          return Buffer (1 .. Last);
843       else
844          return Get_Rest (Buffer (1 .. Last));
845       end if;
846    end Get_Line;
847
848    function Get_Line return String is
849    begin
850       return Get_Line (Current_In);
851    end Get_Line;
852
853    -------------------------
854    -- Get_Upper_Half_Char --
855    -------------------------
856
857    function Get_Upper_Half_Char
858      (C    : Character;
859       File : File_Type) return Character
860    is
861       Result : Wide_Character;
862
863       function In_Char return Character;
864       --  Function used to obtain additional characters it the wide character
865       --  sequence is more than one character long.
866
867       function WC_In is new Char_Sequence_To_Wide_Char (In_Char);
868
869       -------------
870       -- In_Char --
871       -------------
872
873       function In_Char return Character is
874          ch : constant Integer := Getc (File);
875       begin
876          if ch = EOF then
877             raise End_Error;
878          else
879             return Character'Val (ch);
880          end if;
881       end In_Char;
882
883    --  Start of processing for Get_Upper_Half_Char
884
885    begin
886       Result := WC_In (C, File.WC_Method);
887
888       if Wide_Character'Pos (Result) > 16#FF# then
889          raise Constraint_Error with
890            "invalid wide character in Text_'I'O input";
891       else
892          return Character'Val (Wide_Character'Pos (Result));
893       end if;
894    end Get_Upper_Half_Char;
895
896    -------------------------------
897    -- Get_Upper_Half_Char_Immed --
898    -------------------------------
899
900    function Get_Upper_Half_Char_Immed
901      (C    : Character;
902       File : File_Type) return Character
903    is
904       Result : Wide_Character;
905
906       function In_Char return Character;
907       --  Function used to obtain additional characters it the wide character
908       --  sequence is more than one character long.
909
910       function WC_In is new Char_Sequence_To_Wide_Char (In_Char);
911
912       -------------
913       -- In_Char --
914       -------------
915
916       function In_Char return Character is
917          ch : constant Integer := Getc_Immed (File);
918       begin
919          if ch = EOF then
920             raise End_Error;
921          else
922             return Character'Val (ch);
923          end if;
924       end In_Char;
925
926    --  Start of processing for Get_Upper_Half_Char_Immed
927
928    begin
929       Result := WC_In (C, File.WC_Method);
930
931       if Wide_Character'Pos (Result) > 16#FF# then
932          raise Constraint_Error with
933            "invalid wide character in Text_'I'O input";
934       else
935          return Character'Val (Wide_Character'Pos (Result));
936       end if;
937    end Get_Upper_Half_Char_Immed;
938
939    ----------
940    -- Getc --
941    ----------
942
943    function Getc (File : File_Type) return int is
944       ch : int;
945
946    begin
947       ch := fgetc (File.Stream);
948
949       if ch = EOF and then ferror (File.Stream) /= 0 then
950          raise Device_Error;
951       else
952          return ch;
953       end if;
954    end Getc;
955
956    ----------------
957    -- Getc_Immed --
958    ----------------
959
960    function Getc_Immed (File : File_Type) return int is
961       ch          : int;
962       end_of_file : int;
963
964       procedure getc_immediate
965         (stream : FILEs; ch : out int; end_of_file : out int);
966       pragma Import (C, getc_immediate, "getc_immediate");
967
968    begin
969       FIO.Check_Read_Status (AP (File));
970
971       if File.Before_LM then
972          File.Before_LM := False;
973          File.Before_LM_PM := False;
974          ch := LM;
975
976       else
977          getc_immediate (File.Stream, ch, end_of_file);
978
979          if ferror (File.Stream) /= 0 then
980             raise Device_Error;
981          elsif end_of_file /= 0 then
982             return EOF;
983          end if;
984       end if;
985
986       return ch;
987    end Getc_Immed;
988
989    ------------------------------
990    -- Has_Upper_Half_Character --
991    ------------------------------
992
993    function Has_Upper_Half_Character (Item : String) return Boolean is
994    begin
995       for J in Item'Range loop
996          if Character'Pos (Item (J)) >= 16#80# then
997             return True;
998          end if;
999       end loop;
1000
1001       return False;
1002    end Has_Upper_Half_Character;
1003
1004    -------------------------------
1005    -- Initialize_Standard_Files --
1006    -------------------------------
1007
1008    procedure Initialize_Standard_Files is
1009    begin
1010       Standard_Err.Stream            := stderr;
1011       Standard_Err.Name              := Err_Name'Access;
1012       Standard_Err.Form              := Null_Str'Unrestricted_Access;
1013       Standard_Err.Mode              := FCB.Out_File;
1014       Standard_Err.Is_Regular_File   := is_regular_file (fileno (stderr)) /= 0;
1015       Standard_Err.Is_Temporary_File := False;
1016       Standard_Err.Is_System_File    := True;
1017       Standard_Err.Is_Text_File      := True;
1018       Standard_Err.Access_Method     := 'T';
1019       Standard_Err.Self              := Standard_Err;
1020       Standard_Err.WC_Method         := Default_WCEM;
1021
1022       Standard_In.Stream             := stdin;
1023       Standard_In.Name               := In_Name'Access;
1024       Standard_In.Form               := Null_Str'Unrestricted_Access;
1025       Standard_In.Mode               := FCB.In_File;
1026       Standard_In.Is_Regular_File    := is_regular_file (fileno (stdin)) /= 0;
1027       Standard_In.Is_Temporary_File  := False;
1028       Standard_In.Is_System_File     := True;
1029       Standard_In.Is_Text_File       := True;
1030       Standard_In.Access_Method      := 'T';
1031       Standard_In.Self               := Standard_In;
1032       Standard_In.WC_Method          := Default_WCEM;
1033
1034       Standard_Out.Stream            := stdout;
1035       Standard_Out.Name              := Out_Name'Access;
1036       Standard_Out.Form              := Null_Str'Unrestricted_Access;
1037       Standard_Out.Mode              := FCB.Out_File;
1038       Standard_Out.Is_Regular_File   := is_regular_file (fileno (stdout)) /= 0;
1039       Standard_Out.Is_Temporary_File := False;
1040       Standard_Out.Is_System_File    := True;
1041       Standard_Out.Is_Text_File      := True;
1042       Standard_Out.Access_Method     := 'T';
1043       Standard_Out.Self              := Standard_Out;
1044       Standard_Out.WC_Method         := Default_WCEM;
1045
1046       FIO.Make_Unbuffered (AP (Standard_Out));
1047       FIO.Make_Unbuffered (AP (Standard_Err));
1048    end Initialize_Standard_Files;
1049
1050    -------------
1051    -- Is_Open --
1052    -------------
1053
1054    function Is_Open (File : File_Type) return Boolean is
1055    begin
1056       return FIO.Is_Open (AP (File));
1057    end Is_Open;
1058
1059    ----------
1060    -- Line --
1061    ----------
1062
1063    --  Note: we assume that it is impossible in practice for the line
1064    --  to exceed the value of Count'Last, i.e. no check is required for
1065    --  overflow raising layout error.
1066
1067    function Line (File : File_Type) return Positive_Count is
1068    begin
1069       FIO.Check_File_Open (AP (File));
1070       return File.Line;
1071    end Line;
1072
1073    function Line return Positive_Count is
1074    begin
1075       return Line (Current_Out);
1076    end Line;
1077
1078    -----------------
1079    -- Line_Length --
1080    -----------------
1081
1082    function Line_Length (File : File_Type) return Count is
1083    begin
1084       FIO.Check_Write_Status (AP (File));
1085       return File.Line_Length;
1086    end Line_Length;
1087
1088    function Line_Length return Count is
1089    begin
1090       return Line_Length (Current_Out);
1091    end Line_Length;
1092
1093    ----------------
1094    -- Look_Ahead --
1095    ----------------
1096
1097    procedure Look_Ahead
1098      (File        : File_Type;
1099       Item        : out Character;
1100       End_Of_Line : out Boolean)
1101    is
1102       ch : int;
1103
1104    begin
1105       FIO.Check_Read_Status (AP (File));
1106
1107       --  If we are logically before a line mark, we can return immediately
1108
1109       if File.Before_LM then
1110          End_Of_Line := True;
1111          Item := ASCII.NUL;
1112
1113       --  If we are before an upper half character just return it (this can
1114       --  happen if there are two calls to Look_Ahead in a row).
1115
1116       elsif File.Before_Upper_Half_Character then
1117          End_Of_Line := False;
1118          Item := File.Saved_Upper_Half_Character;
1119
1120       --  Otherwise we must read a character from the input stream
1121
1122       else
1123          ch := Getc (File);
1124
1125          if ch = LM
1126            or else ch = EOF
1127            or else (ch = PM and then File.Is_Regular_File)
1128          then
1129             End_Of_Line := True;
1130             Ungetc (ch, File);
1131             Item := ASCII.NUL;
1132
1133          --  Case where character obtained does not represent the start of an
1134          --  encoded sequence so it stands for itself and we can unget it with
1135          --  no difficulty.
1136
1137          elsif not Is_Start_Of_Encoding
1138                      (Character'Val (ch), File.WC_Method)
1139          then
1140             End_Of_Line := False;
1141             Ungetc (ch, File);
1142             Item := Character'Val (ch);
1143
1144          --  For the start of an encoding, we read the character using the
1145          --  Get_Upper_Half_Char routine. It will occupy more than one byte
1146          --  so we can't put it back with ungetc. Instead we save it in the
1147          --  control block, setting a flag that everyone interested in reading
1148          --  characters must test before reading the stream.
1149
1150          else
1151             Item := Get_Upper_Half_Char (Character'Val (ch), File);
1152             End_Of_Line := False;
1153             File.Saved_Upper_Half_Character := Item;
1154             File.Before_Upper_Half_Character := True;
1155          end if;
1156       end if;
1157    end Look_Ahead;
1158
1159    procedure Look_Ahead
1160      (Item        : out Character;
1161       End_Of_Line : out Boolean)
1162    is
1163    begin
1164       Look_Ahead (Current_In, Item, End_Of_Line);
1165    end Look_Ahead;
1166
1167    ----------
1168    -- Mode --
1169    ----------
1170
1171    function Mode (File : File_Type) return File_Mode is
1172    begin
1173       return To_TIO (FIO.Mode (AP (File)));
1174    end Mode;
1175
1176    ----------
1177    -- Name --
1178    ----------
1179
1180    function Name (File : File_Type) return String is
1181    begin
1182       return FIO.Name (AP (File));
1183    end Name;
1184
1185    --------------
1186    -- New_Line --
1187    --------------
1188
1189    procedure New_Line
1190      (File    : File_Type;
1191       Spacing : Positive_Count := 1)
1192    is
1193    begin
1194       --  Raise Constraint_Error if out of range value. The reason for this
1195       --  explicit test is that we don't want junk values around, even if
1196       --  checks are off in the caller.
1197
1198       if not Spacing'Valid then
1199          raise Constraint_Error;
1200       end if;
1201
1202       FIO.Check_Write_Status (AP (File));
1203
1204       for K in 1 .. Spacing loop
1205          Putc (LM, File);
1206          File.Line := File.Line + 1;
1207
1208          if File.Page_Length /= 0
1209            and then File.Line > File.Page_Length
1210          then
1211             Putc (PM, File);
1212             File.Line := 1;
1213             File.Page := File.Page + 1;
1214          end if;
1215       end loop;
1216
1217       File.Col := 1;
1218    end New_Line;
1219
1220    procedure New_Line (Spacing : Positive_Count := 1) is
1221    begin
1222       New_Line (Current_Out, Spacing);
1223    end New_Line;
1224
1225    --------------
1226    -- New_Page --
1227    --------------
1228
1229    procedure New_Page (File : File_Type) is
1230    begin
1231       FIO.Check_Write_Status (AP (File));
1232
1233       if File.Col /= 1 or else File.Line = 1 then
1234          Putc (LM, File);
1235       end if;
1236
1237       Putc (PM, File);
1238       File.Page := File.Page + 1;
1239       File.Line := 1;
1240       File.Col := 1;
1241    end New_Page;
1242
1243    procedure New_Page is
1244    begin
1245       New_Page (Current_Out);
1246    end New_Page;
1247
1248    -----------
1249    -- Nextc --
1250    -----------
1251
1252    function Nextc (File : File_Type) return int is
1253       ch : int;
1254
1255    begin
1256       ch := fgetc (File.Stream);
1257
1258       if ch = EOF then
1259          if ferror (File.Stream) /= 0 then
1260             raise Device_Error;
1261          end if;
1262
1263       else
1264          if ungetc (ch, File.Stream) = EOF then
1265             raise Device_Error;
1266          end if;
1267       end if;
1268
1269       return ch;
1270    end Nextc;
1271
1272    ----------
1273    -- Open --
1274    ----------
1275
1276    procedure Open
1277      (File : in out File_Type;
1278       Mode : File_Mode;
1279       Name : String;
1280       Form : String := "")
1281    is
1282       Dummy_File_Control_Block : Text_AFCB;
1283       pragma Warnings (Off, Dummy_File_Control_Block);
1284       --  Yes, we know this is never assigned a value, only the tag
1285       --  is used for dispatching purposes, so that's expected.
1286
1287    begin
1288       FIO.Open (File_Ptr  => AP (File),
1289                 Dummy_FCB => Dummy_File_Control_Block,
1290                 Mode      => To_FCB (Mode),
1291                 Name      => Name,
1292                 Form      => Form,
1293                 Amethod   => 'T',
1294                 Creat     => False,
1295                 Text      => True);
1296
1297       File.Self := File;
1298       Set_WCEM (File);
1299    end Open;
1300
1301    ----------
1302    -- Page --
1303    ----------
1304
1305    --  Note: we assume that it is impossible in practice for the page
1306    --  to exceed the value of Count'Last, i.e. no check is required for
1307    --  overflow raising layout error.
1308
1309    function Page (File : File_Type) return Positive_Count is
1310    begin
1311       FIO.Check_File_Open (AP (File));
1312       return File.Page;
1313    end Page;
1314
1315    function Page return Positive_Count is
1316    begin
1317       return Page (Current_Out);
1318    end Page;
1319
1320    -----------------
1321    -- Page_Length --
1322    -----------------
1323
1324    function Page_Length (File : File_Type) return Count is
1325    begin
1326       FIO.Check_Write_Status (AP (File));
1327       return File.Page_Length;
1328    end Page_Length;
1329
1330    function Page_Length return Count is
1331    begin
1332       return Page_Length (Current_Out);
1333    end Page_Length;
1334
1335    ---------
1336    -- Put --
1337    ---------
1338
1339    procedure Put
1340      (File : File_Type;
1341       Item : Character)
1342    is
1343    begin
1344       FIO.Check_Write_Status (AP (File));
1345
1346       if File.Line_Length /= 0 and then File.Col > File.Line_Length then
1347          New_Line (File);
1348       end if;
1349
1350       --  If lower half character, or brackets encoding, output directly
1351
1352       if Character'Pos (Item) < 16#80#
1353         or else File.WC_Method = WCEM_Brackets
1354       then
1355          if fputc (Character'Pos (Item), File.Stream) = EOF then
1356             raise Device_Error;
1357          end if;
1358
1359       --  Case of upper half character with non-brackets encoding
1360
1361       else
1362          Put_Encoded (File, Item);
1363       end if;
1364
1365       File.Col := File.Col + 1;
1366    end Put;
1367
1368    procedure Put (Item : Character) is
1369    begin
1370       FIO.Check_Write_Status (AP (Current_Out));
1371
1372       if Current_Out.Line_Length /= 0
1373         and then Current_Out.Col > Current_Out.Line_Length
1374       then
1375          New_Line (Current_Out);
1376       end if;
1377
1378       --  If lower half character, or brackets encoding, output directly
1379
1380       if Character'Pos (Item) < 16#80#
1381         or else Default_WCEM = WCEM_Brackets
1382       then
1383          if fputc (Character'Pos (Item), Current_Out.Stream) = EOF then
1384             raise Device_Error;
1385          end if;
1386
1387       --  Case of upper half character with non-brackets encoding
1388
1389       else
1390          Put_Encoded (Current_Out, Item);
1391       end if;
1392
1393       Current_Out.Col := Current_Out.Col + 1;
1394    end Put;
1395
1396    ---------
1397    -- Put --
1398    ---------
1399
1400    procedure Put
1401      (File : File_Type;
1402       Item : String)
1403    is
1404    begin
1405       FIO.Check_Write_Status (AP (File));
1406
1407       --  Only have something to do if string is non-null
1408
1409       if Item'Length > 0 then
1410
1411          --  If we have bounded lines, or if the file encoding is other than
1412          --  Brackets and the string has at least one upper half character,
1413          --  then output the string character by character.
1414
1415          if File.Line_Length /= 0
1416            or else (File.WC_Method /= WCEM_Brackets
1417                       and then Has_Upper_Half_Character (Item))
1418          then
1419             for J in Item'Range loop
1420                Put (File, Item (J));
1421             end loop;
1422
1423          --  Otherwise we can output the entire string at once. Note that if
1424          --  there are LF or FF characters in the string, we do not bother to
1425          --  count them as line or page terminators.
1426
1427          else
1428             FIO.Write_Buf (AP (File), Item'Address, Item'Length);
1429             File.Col := File.Col + Item'Length;
1430          end if;
1431       end if;
1432    end Put;
1433
1434    procedure Put (Item : String) is
1435    begin
1436       Put (Current_Out, Item);
1437    end Put;
1438
1439    -----------------
1440    -- Put_Encoded --
1441    -----------------
1442
1443    procedure Put_Encoded (File : File_Type; Char : Character) is
1444       procedure Out_Char (C : Character);
1445       --  Procedure to output one character of an upper half encoded sequence
1446
1447       procedure WC_Out is new Wide_Char_To_Char_Sequence (Out_Char);
1448
1449       --------------
1450       -- Out_Char --
1451       --------------
1452
1453       procedure Out_Char (C : Character) is
1454       begin
1455          Putc (Character'Pos (C), File);
1456       end Out_Char;
1457
1458    --  Start of processing for Put_Encoded
1459
1460    begin
1461       WC_Out (Wide_Character'Val (Character'Pos (Char)), File.WC_Method);
1462    end Put_Encoded;
1463
1464    --------------
1465    -- Put_Line --
1466    --------------
1467
1468    procedure Put_Line
1469      (File : File_Type;
1470       Item : String)
1471    is
1472       Ilen   : Natural := Item'Length;
1473       Istart : Natural := Item'First;
1474
1475    begin
1476       FIO.Check_Write_Status (AP (File));
1477
1478       --  If we have bounded lines, or if the file encoding is other than
1479       --  Brackets and the string has at least one upper half character, then
1480       --  output the string character by character.
1481
1482       if File.Line_Length /= 0
1483         or else (File.WC_Method /= WCEM_Brackets
1484                    and then Has_Upper_Half_Character (Item))
1485       then
1486          for J in Item'Range loop
1487             Put (File, Item (J));
1488          end loop;
1489
1490          New_Line (File);
1491          return;
1492       end if;
1493
1494       --  Normal case where we do not need to output character by character
1495
1496       --  We setup a single string that has the necessary terminators and
1497       --  then write it with a single call. The reason for doing this is
1498       --  that it gives better behavior for the use of Put_Line in multi-
1499       --  tasking programs, since often the OS will treat the entire put
1500       --  operation as an atomic operation.
1501
1502       --  We only do this if the message is 512 characters or less in length,
1503       --  since otherwise Put_Line would use an unbounded amount of stack
1504       --  space and could cause undetected stack overflow. If we have a
1505       --  longer string, then output the first part separately to avoid this.
1506
1507       if Ilen > 512 then
1508          FIO.Write_Buf (AP (File), Item'Address, size_t (Ilen - 512));
1509          Istart := Istart + Ilen - 512;
1510          Ilen   := 512;
1511       end if;
1512
1513       --  Now prepare the string with its terminator
1514
1515       declare
1516          Buffer : String (1 .. Ilen + 2);
1517          Plen   : size_t;
1518
1519       begin
1520          Buffer (1 .. Ilen) := Item (Istart .. Item'Last);
1521          Buffer (Ilen + 1) := Character'Val (LM);
1522
1523          if File.Page_Length /= 0
1524            and then File.Line > File.Page_Length
1525          then
1526             Buffer (Ilen + 2) := Character'Val (PM);
1527             Plen := size_t (Ilen) + 2;
1528             File.Line := 1;
1529             File.Page := File.Page + 1;
1530
1531          else
1532             Plen := size_t (Ilen) + 1;
1533             File.Line := File.Line + 1;
1534          end if;
1535
1536          FIO.Write_Buf (AP (File), Buffer'Address, Plen);
1537
1538          File.Col := 1;
1539       end;
1540    end Put_Line;
1541
1542    procedure Put_Line (Item : String) is
1543    begin
1544       Put_Line (Current_Out, Item);
1545    end Put_Line;
1546
1547    ----------
1548    -- Putc --
1549    ----------
1550
1551    procedure Putc (ch : int; File : File_Type) is
1552    begin
1553       if fputc (ch, File.Stream) = EOF then
1554          raise Device_Error;
1555       end if;
1556    end Putc;
1557
1558    ----------
1559    -- Read --
1560    ----------
1561
1562    --  This is the primitive Stream Read routine, used when a Text_IO file
1563    --  is treated directly as a stream using Text_IO.Streams.Stream.
1564
1565    procedure Read
1566      (File : in out Text_AFCB;
1567       Item : out Stream_Element_Array;
1568       Last : out Stream_Element_Offset)
1569    is
1570       Discard_ch : int;
1571       pragma Warnings (Off, Discard_ch);
1572
1573    begin
1574       --  Need to deal with Before_Upper_Half_Character ???
1575
1576       if File.Mode /= FCB.In_File then
1577          raise Mode_Error;
1578       end if;
1579
1580       --  Deal with case where our logical and physical position do not match
1581       --  because of being after an LM or LM-PM sequence when in fact we are
1582       --  logically positioned before it.
1583
1584       if File.Before_LM then
1585
1586          --  If we are before a PM, then it is possible for a stream read
1587          --  to leave us after the LM and before the PM, which is a bit
1588          --  odd. The easiest way to deal with this is to unget the PM,
1589          --  so we are indeed positioned between the characters. This way
1590          --  further stream read operations will work correctly, and the
1591          --  effect on text processing is a little weird, but what can
1592          --  be expected if stream and text input are mixed this way?
1593
1594          if File.Before_LM_PM then
1595             Discard_ch := ungetc (PM, File.Stream);
1596             File.Before_LM_PM := False;
1597          end if;
1598
1599          File.Before_LM := False;
1600
1601          Item (Item'First) := Stream_Element (Character'Pos (ASCII.LF));
1602
1603          if Item'Length = 1 then
1604             Last := Item'Last;
1605
1606          else
1607             Last :=
1608               Item'First +
1609                 Stream_Element_Offset
1610                   (fread (buffer => Item'Address,
1611                           index  => size_t (Item'First + 1),
1612                           size   => 1,
1613                           count  => Item'Length - 1,
1614                           stream => File.Stream));
1615          end if;
1616
1617          return;
1618       end if;
1619
1620       --  Now we do the read. Since this is a text file, it is normally in
1621       --  text mode, but stream data must be read in binary mode, so we
1622       --  temporarily set binary mode for the read, resetting it after.
1623       --  These calls have no effect in a system (like Unix) where there is
1624       --  no distinction between text and binary files.
1625
1626       set_binary_mode (fileno (File.Stream));
1627
1628       Last :=
1629         Item'First +
1630           Stream_Element_Offset
1631             (fread (Item'Address, 1, Item'Length, File.Stream)) - 1;
1632
1633       if Last < Item'Last then
1634          if ferror (File.Stream) /= 0 then
1635             raise Device_Error;
1636          end if;
1637       end if;
1638
1639       set_text_mode (fileno (File.Stream));
1640    end Read;
1641
1642    -----------
1643    -- Reset --
1644    -----------
1645
1646    procedure Reset
1647      (File : in out File_Type;
1648       Mode : File_Mode)
1649    is
1650    begin
1651       --  Don't allow change of mode for current file (RM A.10.2(5))
1652
1653       if (File = Current_In or else
1654           File = Current_Out  or else
1655           File = Current_Error)
1656         and then To_FCB (Mode) /= File.Mode
1657       then
1658          raise Mode_Error;
1659       end if;
1660
1661       Terminate_Line (File);
1662       FIO.Reset (AP (File)'Unrestricted_Access, To_FCB (Mode));
1663       File.Page := 1;
1664       File.Line := 1;
1665       File.Col  := 1;
1666       File.Line_Length := 0;
1667       File.Page_Length := 0;
1668       File.Before_LM := False;
1669       File.Before_LM_PM := False;
1670    end Reset;
1671
1672    procedure Reset (File : in out File_Type) is
1673    begin
1674       Terminate_Line (File);
1675       FIO.Reset (AP (File)'Unrestricted_Access);
1676       File.Page := 1;
1677       File.Line := 1;
1678       File.Col  := 1;
1679       File.Line_Length := 0;
1680       File.Page_Length := 0;
1681       File.Before_LM := False;
1682       File.Before_LM_PM := False;
1683    end Reset;
1684
1685    -------------
1686    -- Set_Col --
1687    -------------
1688
1689    procedure Set_Col
1690      (File : File_Type;
1691       To   : Positive_Count)
1692    is
1693       ch : int;
1694
1695    begin
1696       --  Raise Constraint_Error if out of range value. The reason for this
1697       --  explicit test is that we don't want junk values around, even if
1698       --  checks are off in the caller.
1699
1700       if not To'Valid then
1701          raise Constraint_Error;
1702       end if;
1703
1704       FIO.Check_File_Open (AP (File));
1705
1706       --  Output case
1707
1708       if Mode (File) >= Out_File then
1709
1710          --  Error if we attempt to set Col to a value greater than the
1711          --  maximum permissible line length.
1712
1713          if File.Line_Length /= 0 and then To > File.Line_Length then
1714             raise Layout_Error;
1715          end if;
1716
1717          --  If we are behind current position, then go to start of new line
1718
1719          if To < File.Col then
1720             New_Line (File);
1721          end if;
1722
1723          --  Loop to output blanks till we are at the required column
1724
1725          while File.Col < To loop
1726             Put (File, ' ');
1727          end loop;
1728
1729       --  Input case
1730
1731       else
1732          --  If we are logically before a LM, but physically after it, the
1733          --  file position still reflects the position before the LM, so eat
1734          --  it now and adjust the file position appropriately.
1735
1736          if File.Before_LM then
1737             File.Before_LM := False;
1738             File.Before_LM_PM := False;
1739             File.Line := File.Line + 1;
1740             File.Col := 1;
1741          end if;
1742
1743          --  Loop reading characters till we get one at the required Col value
1744
1745          loop
1746             --  Read next character. The reason we have to read ahead is to
1747             --  skip formatting characters, the effect of Set_Col is to set
1748             --  us to a real character with the right Col value, and format
1749             --  characters don't count.
1750
1751             ch := Getc (File);
1752
1753             --  Error if we hit an end of file
1754
1755             if ch = EOF then
1756                raise End_Error;
1757
1758             --  If line mark, eat it and adjust file position
1759
1760             elsif ch = LM then
1761                File.Line := File.Line + 1;
1762                File.Col := 1;
1763
1764             --  If recognized page mark, eat it, and adjust file position
1765
1766             elsif ch = PM and then File.Is_Regular_File then
1767                File.Page := File.Page + 1;
1768                File.Line := 1;
1769                File.Col := 1;
1770
1771             --  Otherwise this is the character we are looking for, so put it
1772             --  back in the input stream (we have not adjusted the file
1773             --  position yet, so everything is set right after this ungetc).
1774
1775             elsif To = File.Col then
1776                Ungetc (ch, File);
1777                return;
1778
1779             --  Keep skipping characters if we are not there yet, updating the
1780             --  file position past the skipped character.
1781
1782             else
1783                File.Col := File.Col + 1;
1784             end if;
1785          end loop;
1786       end if;
1787    end Set_Col;
1788
1789    procedure Set_Col (To : Positive_Count) is
1790    begin
1791       Set_Col (Current_Out, To);
1792    end Set_Col;
1793
1794    ---------------
1795    -- Set_Error --
1796    ---------------
1797
1798    procedure Set_Error (File : File_Type) is
1799    begin
1800       FIO.Check_Write_Status (AP (File));
1801       Current_Err := File;
1802    end Set_Error;
1803
1804    ---------------
1805    -- Set_Input --
1806    ---------------
1807
1808    procedure Set_Input (File : File_Type) is
1809    begin
1810       FIO.Check_Read_Status (AP (File));
1811       Current_In := File;
1812    end Set_Input;
1813
1814    --------------
1815    -- Set_Line --
1816    --------------
1817
1818    procedure Set_Line
1819      (File : File_Type;
1820       To   : Positive_Count)
1821    is
1822    begin
1823       --  Raise Constraint_Error if out of range value. The reason for this
1824       --  explicit test is that we don't want junk values around, even if
1825       --  checks are off in the caller.
1826
1827       if not To'Valid then
1828          raise Constraint_Error;
1829       end if;
1830
1831       FIO.Check_File_Open (AP (File));
1832
1833       if To = File.Line then
1834          return;
1835       end if;
1836
1837       if Mode (File) >= Out_File then
1838          if File.Page_Length /= 0 and then To > File.Page_Length then
1839             raise Layout_Error;
1840          end if;
1841
1842          if To < File.Line then
1843             New_Page (File);
1844          end if;
1845
1846          while File.Line < To loop
1847             New_Line (File);
1848          end loop;
1849
1850       else
1851          while To /= File.Line loop
1852             Skip_Line (File);
1853          end loop;
1854       end if;
1855    end Set_Line;
1856
1857    procedure Set_Line (To : Positive_Count) is
1858    begin
1859       Set_Line (Current_Out, To);
1860    end Set_Line;
1861
1862    ---------------------
1863    -- Set_Line_Length --
1864    ---------------------
1865
1866    procedure Set_Line_Length (File : File_Type; To : Count) is
1867    begin
1868       --  Raise Constraint_Error if out of range value. The reason for this
1869       --  explicit test is that we don't want junk values around, even if
1870       --  checks are off in the caller.
1871
1872       if not To'Valid then
1873          raise Constraint_Error;
1874       end if;
1875
1876       FIO.Check_Write_Status (AP (File));
1877       File.Line_Length := To;
1878    end Set_Line_Length;
1879
1880    procedure Set_Line_Length (To : Count) is
1881    begin
1882       Set_Line_Length (Current_Out, To);
1883    end Set_Line_Length;
1884
1885    ----------------
1886    -- Set_Output --
1887    ----------------
1888
1889    procedure Set_Output (File : File_Type) is
1890    begin
1891       FIO.Check_Write_Status (AP (File));
1892       Current_Out := File;
1893    end Set_Output;
1894
1895    ---------------------
1896    -- Set_Page_Length --
1897    ---------------------
1898
1899    procedure Set_Page_Length (File : File_Type; To : Count) is
1900    begin
1901       --  Raise Constraint_Error if out of range value. The reason for this
1902       --  explicit test is that we don't want junk values around, even if
1903       --  checks are off in the caller.
1904
1905       if not To'Valid then
1906          raise Constraint_Error;
1907       end if;
1908
1909       FIO.Check_Write_Status (AP (File));
1910       File.Page_Length := To;
1911    end Set_Page_Length;
1912
1913    procedure Set_Page_Length (To : Count) is
1914    begin
1915       Set_Page_Length (Current_Out, To);
1916    end Set_Page_Length;
1917
1918    --------------
1919    -- Set_WCEM --
1920    --------------
1921
1922    procedure Set_WCEM (File : in out File_Type) is
1923       Start : Natural;
1924       Stop  : Natural;
1925
1926    begin
1927       File.WC_Method := WCEM_Brackets;
1928       FIO.Form_Parameter (File.Form.all, "wcem", Start, Stop);
1929
1930       if Start = 0 then
1931          File.WC_Method := WCEM_Brackets;
1932
1933       else
1934          if Stop = Start then
1935             for J in WC_Encoding_Letters'Range loop
1936                if File.Form (Start) = WC_Encoding_Letters (J) then
1937                   File.WC_Method := J;
1938                   return;
1939                end if;
1940             end loop;
1941          end if;
1942
1943          Close (File);
1944          raise Use_Error with "invalid WCEM form parameter";
1945       end if;
1946    end Set_WCEM;
1947
1948    ---------------
1949    -- Skip_Line --
1950    ---------------
1951
1952    procedure Skip_Line
1953      (File    : File_Type;
1954       Spacing : Positive_Count := 1)
1955    is
1956       ch : int;
1957
1958    begin
1959       --  Raise Constraint_Error if out of range value. The reason for this
1960       --  explicit test is that we don't want junk values around, even if
1961       --  checks are off in the caller.
1962
1963       if not Spacing'Valid then
1964          raise Constraint_Error;
1965       end if;
1966
1967       FIO.Check_Read_Status (AP (File));
1968
1969       for L in 1 .. Spacing loop
1970          if File.Before_LM then
1971             File.Before_LM := False;
1972
1973             --  Note that if File.Before_LM_PM is currently set, we also have
1974             --  to reset it (because it makes sense for Before_LM_PM to be set
1975             --  only when Before_LM is also set). This is done later on in this
1976             --  subprogram, as soon as Before_LM_PM has been taken into account
1977             --  for the purpose of page and line counts.
1978
1979          else
1980             ch := Getc (File);
1981
1982             --  If at end of file now, then immediately raise End_Error. Note
1983             --  that we can never be positioned between a line mark and a page
1984             --  mark, so if we are at the end of file, we cannot logically be
1985             --  before the implicit page mark that is at the end of the file.
1986
1987             --  For the same reason, we do not need an explicit check for a
1988             --  page mark. If there is a FF in the middle of a line, the file
1989             --  is not in canonical format and we do not care about the page
1990             --  numbers for files other than ones in canonical format.
1991
1992             if ch = EOF then
1993                raise End_Error;
1994             end if;
1995
1996             --  If not at end of file, then loop till we get to an LM or EOF.
1997             --  The latter case happens only in non-canonical files where the
1998             --  last line is not terminated by LM, but we don't want to blow
1999             --  up for such files, so we assume an implicit LM in this case.
2000
2001             loop
2002                exit when ch = LM or else ch = EOF;
2003                ch := Getc (File);
2004             end loop;
2005          end if;
2006
2007          --  We have got past a line mark, now, for a regular file only,
2008          --  see if a page mark immediately follows this line mark and
2009          --  if so, skip past the page mark as well. We do not do this
2010          --  for non-regular files, since it would cause an undesirable
2011          --  wait for an additional character.
2012
2013          File.Col := 1;
2014          File.Line := File.Line + 1;
2015
2016          if File.Before_LM_PM then
2017             File.Page := File.Page + 1;
2018             File.Line := 1;
2019             File.Before_LM_PM := False;
2020
2021          elsif File.Is_Regular_File then
2022             ch := Getc (File);
2023
2024             --  Page mark can be explicit, or implied at the end of the file
2025
2026             if (ch = PM or else ch = EOF)
2027               and then File.Is_Regular_File
2028             then
2029                File.Page := File.Page + 1;
2030                File.Line := 1;
2031             else
2032                Ungetc (ch, File);
2033             end if;
2034          end if;
2035       end loop;
2036
2037       File.Before_Upper_Half_Character := False;
2038    end Skip_Line;
2039
2040    procedure Skip_Line (Spacing : Positive_Count := 1) is
2041    begin
2042       Skip_Line (Current_In, Spacing);
2043    end Skip_Line;
2044
2045    ---------------
2046    -- Skip_Page --
2047    ---------------
2048
2049    procedure Skip_Page (File : File_Type) is
2050       ch : int;
2051
2052    begin
2053       FIO.Check_Read_Status (AP (File));
2054
2055       --  If at page mark already, just skip it
2056
2057       if File.Before_LM_PM then
2058          File.Before_LM := False;
2059          File.Before_LM_PM := False;
2060          File.Page := File.Page + 1;
2061          File.Line := 1;
2062          File.Col  := 1;
2063          return;
2064       end if;
2065
2066       --  This is a bit tricky, if we are logically before an LM then
2067       --  it is not an error if we are at an end of file now, since we
2068       --  are not really at it.
2069
2070       if File.Before_LM then
2071          File.Before_LM := False;
2072          File.Before_LM_PM := False;
2073          ch := Getc (File);
2074
2075       --  Otherwise we do raise End_Error if we are at the end of file now
2076
2077       else
2078          ch := Getc (File);
2079
2080          if ch = EOF then
2081             raise End_Error;
2082          end if;
2083       end if;
2084
2085       --  Now we can just rumble along to the next page mark, or to the
2086       --  end of file, if that comes first. The latter case happens when
2087       --  the page mark is implied at the end of file.
2088
2089       loop
2090          exit when ch = EOF
2091            or else (ch = PM and then File.Is_Regular_File);
2092          ch := Getc (File);
2093       end loop;
2094
2095       File.Page := File.Page + 1;
2096       File.Line := 1;
2097       File.Col  := 1;
2098       File.Before_Upper_Half_Character := False;
2099    end Skip_Page;
2100
2101    procedure Skip_Page is
2102    begin
2103       Skip_Page (Current_In);
2104    end Skip_Page;
2105
2106    --------------------
2107    -- Standard_Error --
2108    --------------------
2109
2110    function Standard_Error return File_Type is
2111    begin
2112       return Standard_Err;
2113    end Standard_Error;
2114
2115    function Standard_Error return File_Access is
2116    begin
2117       return Standard_Err'Access;
2118    end Standard_Error;
2119
2120    --------------------
2121    -- Standard_Input --
2122    --------------------
2123
2124    function Standard_Input return File_Type is
2125    begin
2126       return Standard_In;
2127    end Standard_Input;
2128
2129    function Standard_Input return File_Access is
2130    begin
2131       return Standard_In'Access;
2132    end Standard_Input;
2133
2134    ---------------------
2135    -- Standard_Output --
2136    ---------------------
2137
2138    function Standard_Output return File_Type is
2139    begin
2140       return Standard_Out;
2141    end Standard_Output;
2142
2143    function Standard_Output return File_Access is
2144    begin
2145       return Standard_Out'Access;
2146    end Standard_Output;
2147
2148    --------------------
2149    -- Terminate_Line --
2150    --------------------
2151
2152    procedure Terminate_Line (File : File_Type) is
2153    begin
2154       FIO.Check_File_Open (AP (File));
2155
2156       --  For file other than In_File, test for needing to terminate last line
2157
2158       if Mode (File) /= In_File then
2159
2160          --  If not at start of line definition need new line
2161
2162          if File.Col /= 1 then
2163             New_Line (File);
2164
2165          --  For files other than standard error and standard output, we
2166          --  make sure that an empty file has a single line feed, so that
2167          --  it is properly formatted. We avoid this for the standard files
2168          --  because it is too much of a nuisance to have these odd line
2169          --  feeds when nothing has been written to the file.
2170
2171          --  We also avoid this for files opened in append mode, in
2172          --  accordance with (RM A.8.2(10))
2173
2174          elsif (File /= Standard_Err and then File /= Standard_Out)
2175            and then (File.Line = 1 and then File.Page = 1)
2176            and then Mode (File) = Out_File
2177          then
2178             New_Line (File);
2179          end if;
2180       end if;
2181    end Terminate_Line;
2182
2183    ------------
2184    -- Ungetc --
2185    ------------
2186
2187    procedure Ungetc (ch : int; File : File_Type) is
2188    begin
2189       if ch /= EOF then
2190          if ungetc (ch, File.Stream) = EOF then
2191             raise Device_Error;
2192          end if;
2193       end if;
2194    end Ungetc;
2195
2196    -----------
2197    -- Write --
2198    -----------
2199
2200    --  This is the primitive Stream Write routine, used when a Text_IO file
2201    --  is treated directly as a stream using Text_IO.Streams.Stream.
2202
2203    procedure Write
2204      (File : in out Text_AFCB;
2205       Item : Stream_Element_Array)
2206    is
2207       pragma Warnings (Off, File);
2208       --  Because in this implementation we don't need IN OUT, we only read
2209
2210       function Has_Translated_Characters return Boolean;
2211       --  return True if Item array contains a character which will be
2212       --  translated under the text file mode. There is only one such
2213       --  character under DOS based systems which is character 10.
2214
2215       text_translation_required : Boolean;
2216       for text_translation_required'Size use Character'Size;
2217       pragma Import (C, text_translation_required,
2218                      "__gnat_text_translation_required");
2219
2220       Siz : constant size_t := Item'Length;
2221
2222       -------------------------------
2223       -- Has_Translated_Characters --
2224       -------------------------------
2225
2226       function Has_Translated_Characters return Boolean is
2227       begin
2228          for K in Item'Range loop
2229             if Item (K) = 10 then
2230                return True;
2231             end if;
2232          end loop;
2233          return False;
2234       end Has_Translated_Characters;
2235
2236       Needs_Binary_Write : constant Boolean :=
2237                              text_translation_required
2238                                and then Has_Translated_Characters;
2239
2240    --  Start of processing for Write
2241
2242    begin
2243       if File.Mode = FCB.In_File then
2244          raise Mode_Error;
2245       end if;
2246
2247       --  Now we do the write. Since this is a text file, it is normally in
2248       --  text mode, but stream data must be written in binary mode, so we
2249       --  temporarily set binary mode for the write, resetting it after. This
2250       --  is done only if needed (i.e. there is some characters in Item which
2251       --  needs to be written using the binary mode).
2252       --  These calls have no effect in a system (like Unix) where there is
2253       --  no distinction between text and binary files.
2254
2255       --  Since the character translation is done at the time the buffer is
2256       --  written (this is true under Windows) we first flush current buffer
2257       --  with text mode if needed.
2258
2259       if Needs_Binary_Write then
2260          if fflush (File.Stream) = -1 then
2261             raise Device_Error;
2262          end if;
2263
2264          set_binary_mode (fileno (File.Stream));
2265       end if;
2266
2267       if fwrite (Item'Address, 1, Siz, File.Stream) /= Siz then
2268          raise Device_Error;
2269       end if;
2270
2271       --  At this point we need to flush the buffer using the binary mode then
2272       --  we reset to text mode.
2273
2274       if Needs_Binary_Write then
2275          if fflush (File.Stream) = -1 then
2276             raise Device_Error;
2277          end if;
2278
2279          set_text_mode (fileno (File.Stream));
2280       end if;
2281    end Write;
2282
2283 begin
2284    --  Initialize Standard Files
2285
2286    for J in WC_Encoding_Method loop
2287       if WC_Encoding = WC_Encoding_Letters (J) then
2288          Default_WCEM := J;
2289       end if;
2290    end loop;
2291
2292    Initialize_Standard_Files;
2293
2294    FIO.Chain_File (AP (Standard_In));
2295    FIO.Chain_File (AP (Standard_Out));
2296    FIO.Chain_File (AP (Standard_Err));
2297
2298 end Ada.Text_IO;