OSDN Git Service

2009-11-30 Jerome Lambourg <lambourg@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    -- EOF_Char --
442    --------------
443
444    function EOF_Char return Integer is
445    begin
446       return EOF;
447    end EOF_Char;
448
449    -----------
450    -- Flush --
451    -----------
452
453    procedure Flush (File : File_Type) is
454    begin
455       FIO.Flush (AP (File));
456    end Flush;
457
458    procedure Flush is
459    begin
460       Flush (Current_Out);
461    end Flush;
462
463    ----------
464    -- Form --
465    ----------
466
467    function Form (File : File_Type) return String is
468    begin
469       return FIO.Form (AP (File));
470    end Form;
471
472    ---------
473    -- Get --
474    ---------
475
476    procedure Get
477      (File : File_Type;
478       Item : out Character)
479    is
480       ch : int;
481
482    begin
483       FIO.Check_Read_Status (AP (File));
484
485       if File.Before_Upper_Half_Character then
486          File.Before_Upper_Half_Character := False;
487          Item := File.Saved_Upper_Half_Character;
488
489       elsif File.Before_LM then
490          File.Before_LM := False;
491          File.Col := 1;
492
493          if File.Before_LM_PM then
494             File.Line := 1;
495             File.Page := File.Page + 1;
496             File.Before_LM_PM := False;
497          else
498             File.Line := File.Line + 1;
499          end if;
500       end if;
501
502       loop
503          ch := Getc (File);
504
505          if ch = EOF then
506             raise End_Error;
507
508          elsif ch = LM then
509             File.Line := File.Line + 1;
510             File.Col := 1;
511
512          elsif ch = PM and then File.Is_Regular_File then
513             File.Page := File.Page + 1;
514             File.Line := 1;
515
516          else
517             Item := Character'Val (ch);
518             File.Col := File.Col + 1;
519             return;
520          end if;
521       end loop;
522    end Get;
523
524    procedure Get (Item : out Character) is
525    begin
526       Get (Current_In, Item);
527    end Get;
528
529    procedure Get
530      (File : File_Type;
531       Item : out String)
532    is
533       ch : int;
534       J  : Natural;
535
536    begin
537       FIO.Check_Read_Status (AP (File));
538
539       if File.Before_LM then
540          File.Before_LM := False;
541          File.Before_LM_PM := False;
542          File.Col := 1;
543
544          if File.Before_LM_PM then
545             File.Line := 1;
546             File.Page := File.Page + 1;
547             File.Before_LM_PM := False;
548
549          else
550             File.Line := File.Line + 1;
551          end if;
552       end if;
553
554       J := Item'First;
555       while J <= Item'Last loop
556          ch := Getc (File);
557
558          if ch = EOF then
559             raise End_Error;
560
561          elsif ch = LM then
562             File.Line := File.Line + 1;
563             File.Col := 1;
564
565          elsif ch = PM and then File.Is_Regular_File then
566             File.Page := File.Page + 1;
567             File.Line := 1;
568
569          else
570             Item (J) := Character'Val (ch);
571             J := J + 1;
572             File.Col := File.Col + 1;
573          end if;
574       end loop;
575    end Get;
576
577    procedure Get (Item : out String) is
578    begin
579       Get (Current_In, Item);
580    end Get;
581
582    -------------------
583    -- Get_Immediate --
584    -------------------
585
586    procedure Get_Immediate
587      (File : File_Type;
588       Item : out Character)
589    is
590       ch          : int;
591
592    begin
593       FIO.Check_Read_Status (AP (File));
594
595       if File.Before_Upper_Half_Character then
596          File.Before_Upper_Half_Character := False;
597          Item := File.Saved_Upper_Half_Character;
598
599       elsif File.Before_LM then
600          File.Before_LM := False;
601          File.Before_LM_PM := False;
602          Item := Character'Val (LM);
603
604       else
605          ch := Getc_Immed (File);
606
607          if ch = EOF then
608             raise End_Error;
609          else
610             Item :=
611               (if not Is_Start_Of_Encoding (Character'Val (ch), File.WC_Method)
612                then Character'Val (ch)
613                else Get_Upper_Half_Char_Immed (Character'Val (ch), File));
614          end if;
615       end if;
616    end Get_Immediate;
617
618    procedure Get_Immediate
619      (Item : out Character)
620    is
621    begin
622       Get_Immediate (Current_In, Item);
623    end Get_Immediate;
624
625    procedure Get_Immediate
626      (File      : File_Type;
627       Item      : out Character;
628       Available : out Boolean)
629    is
630       ch          : int;
631       end_of_file : int;
632       avail       : int;
633
634       procedure getc_immediate_nowait
635         (stream      : FILEs;
636          ch          : out int;
637          end_of_file : out int;
638          avail       : out int);
639       pragma Import (C, getc_immediate_nowait, "getc_immediate_nowait");
640
641    begin
642       FIO.Check_Read_Status (AP (File));
643       Available := True;
644
645       if File.Before_Upper_Half_Character then
646          File.Before_Upper_Half_Character := False;
647          Item := File.Saved_Upper_Half_Character;
648
649       elsif File.Before_LM then
650          File.Before_LM := False;
651          File.Before_LM_PM := False;
652          Item := Character'Val (LM);
653
654       else
655          getc_immediate_nowait (File.Stream, ch, end_of_file, avail);
656
657          if ferror (File.Stream) /= 0 then
658             raise Device_Error;
659
660          elsif end_of_file /= 0 then
661             raise End_Error;
662
663          elsif avail = 0 then
664             Available := False;
665             Item := ASCII.NUL;
666
667          else
668             Available := True;
669
670             Item :=
671               (if Is_Start_Of_Encoding (Character'Val (ch), File.WC_Method)
672                then Character'Val (ch)
673                else Get_Upper_Half_Char_Immed (Character'Val (ch), File));
674          end if;
675       end if;
676
677    end Get_Immediate;
678
679    procedure Get_Immediate
680      (Item      : out Character;
681       Available : out Boolean)
682    is
683    begin
684       Get_Immediate (Current_In, Item, Available);
685    end Get_Immediate;
686
687    --------------
688    -- Get_Line --
689    --------------
690
691    procedure Get_Line
692      (File : File_Type;
693       Item : out String;
694       Last : out Natural)
695    is
696       ch : int;
697
698    begin
699       FIO.Check_Read_Status (AP (File));
700       Last := Item'First - 1;
701
702       --  Immediate exit for null string, this is a case in which we do not
703       --  need to test for end of file and we do not skip a line mark under
704       --  any circumstances.
705
706       if Last >= Item'Last then
707          return;
708       end if;
709
710       --  Here we have at least one character, if we are immediately before
711       --  a line mark, then we will just skip past it storing no characters.
712
713       if File.Before_LM then
714          File.Before_LM := False;
715          File.Before_LM_PM := False;
716
717       --  Otherwise we need to read some characters
718
719       else
720          ch := Getc (File);
721
722          --  If we are at the end of file now, it means we are trying to
723          --  skip a file terminator and we raise End_Error (RM A.10.7(20))
724
725          if ch = EOF then
726             raise End_Error;
727          end if;
728
729          --  Loop through characters. Don't bother if we hit a page mark,
730          --  since in normal files, page marks can only follow line marks
731          --  in any case and we only promise to treat the page nonsense
732          --  correctly in the absense of such rogue page marks.
733
734          loop
735             --  Exit the loop if read is terminated by encountering line mark
736
737             exit when ch = LM;
738
739             --  Otherwise store the character, note that we know that ch is
740             --  something other than LM or EOF. It could possibly be a page
741             --  mark if there is a stray page mark in the middle of a line,
742             --  but this is not an official page mark in any case, since
743             --  official page marks can only follow a line mark. The whole
744             --  page business is pretty much nonsense anyway, so we do not
745             --  want to waste time trying to make sense out of non-standard
746             --  page marks in the file! This means that the behavior of
747             --  Get_Line is different from repeated Get of a character, but
748             --  that's too bad. We only promise that page numbers etc make
749             --  sense if the file is formatted in a standard manner.
750
751             --  Note: we do not adjust the column number because it is quicker
752             --  to adjust it once at the end of the operation than incrementing
753             --  it each time around the loop.
754
755             Last := Last + 1;
756             Item (Last) := Character'Val (ch);
757
758             --  All done if the string is full, this is the case in which
759             --  we do not skip the following line mark. We need to adjust
760             --  the column number in this case.
761
762             if Last = Item'Last then
763                File.Col := File.Col + Count (Item'Length);
764                return;
765             end if;
766
767             --  Otherwise read next character. We also exit from the loop if
768             --  we read an end of file. This is the case where the last line
769             --  is not terminated with a line mark, and we consider that there
770             --  is an implied line mark in this case (this is a non-standard
771             --  file, but it is nice to treat it reasonably).
772
773             ch := Getc (File);
774             exit when ch = EOF;
775          end loop;
776       end if;
777
778       --  We have skipped past, but not stored, a line mark. Skip following
779       --  page mark if one follows, but do not do this for a non-regular
780       --  file (since otherwise we get annoying wait for an extra character)
781
782       File.Line := File.Line + 1;
783       File.Col := 1;
784
785       if File.Before_LM_PM then
786          File.Line := 1;
787          File.Before_LM_PM := False;
788          File.Page := File.Page + 1;
789
790       elsif File.Is_Regular_File then
791          ch := Getc (File);
792
793          if ch = PM and then File.Is_Regular_File then
794             File.Line := 1;
795             File.Page := File.Page + 1;
796          else
797             Ungetc (ch, File);
798          end if;
799       end if;
800    end Get_Line;
801
802    procedure Get_Line
803      (Item : out String;
804       Last : out Natural)
805    is
806    begin
807       Get_Line (Current_In, Item, Last);
808    end Get_Line;
809
810    function Get_Line (File : File_Type) return String is
811       Buffer : String (1 .. 500);
812       Last   : Natural;
813
814       function Get_Rest (S : String) return String;
815       --  This is a recursive function that reads the rest of the line and
816       --  returns it. S is the part read so far.
817
818       --------------
819       -- Get_Rest --
820       --------------
821
822       function Get_Rest (S : String) return String is
823
824          --  Each time we allocate a buffer the same size as what we have
825          --  read so far. This limits us to a logarithmic number of calls
826          --  to Get_Rest and also ensures only a linear use of stack space.
827
828          Buffer : String (1 .. S'Length);
829          Last   : Natural;
830
831       begin
832          Get_Line (File, Buffer, Last);
833
834          declare
835             R : constant String := S & Buffer (1 .. Last);
836          begin
837             if Last < Buffer'Last then
838                return R;
839             else
840                return Get_Rest (R);
841             end if;
842          end;
843       end Get_Rest;
844
845    --  Start of processing for Get_Line
846
847    begin
848       Get_Line (File, Buffer, Last);
849
850       if Last < Buffer'Last then
851          return Buffer (1 .. Last);
852       else
853          return Get_Rest (Buffer (1 .. Last));
854       end if;
855    end Get_Line;
856
857    function Get_Line return String is
858    begin
859       return Get_Line (Current_In);
860    end Get_Line;
861
862    -------------------------
863    -- Get_Upper_Half_Char --
864    -------------------------
865
866    function Get_Upper_Half_Char
867      (C    : Character;
868       File : File_Type) return Character
869    is
870       Result : Wide_Character;
871
872       function In_Char return Character;
873       --  Function used to obtain additional characters it the wide character
874       --  sequence is more than one character long.
875
876       function WC_In is new Char_Sequence_To_Wide_Char (In_Char);
877
878       -------------
879       -- In_Char --
880       -------------
881
882       function In_Char return Character is
883          ch : constant Integer := Getc (File);
884       begin
885          if ch = EOF then
886             raise End_Error;
887          else
888             return Character'Val (ch);
889          end if;
890       end In_Char;
891
892    --  Start of processing for Get_Upper_Half_Char
893
894    begin
895       Result := WC_In (C, File.WC_Method);
896
897       if Wide_Character'Pos (Result) > 16#FF# then
898          raise Constraint_Error with
899            "invalid wide character in Text_'I'O input";
900       else
901          return Character'Val (Wide_Character'Pos (Result));
902       end if;
903    end Get_Upper_Half_Char;
904
905    -------------------------------
906    -- Get_Upper_Half_Char_Immed --
907    -------------------------------
908
909    function Get_Upper_Half_Char_Immed
910      (C    : Character;
911       File : File_Type) return Character
912    is
913       Result : Wide_Character;
914
915       function In_Char return Character;
916       --  Function used to obtain additional characters it the wide character
917       --  sequence is more than one character long.
918
919       function WC_In is new Char_Sequence_To_Wide_Char (In_Char);
920
921       -------------
922       -- In_Char --
923       -------------
924
925       function In_Char return Character is
926          ch : constant Integer := Getc_Immed (File);
927       begin
928          if ch = EOF then
929             raise End_Error;
930          else
931             return Character'Val (ch);
932          end if;
933       end In_Char;
934
935    --  Start of processing for Get_Upper_Half_Char_Immed
936
937    begin
938       Result := WC_In (C, File.WC_Method);
939
940       if Wide_Character'Pos (Result) > 16#FF# then
941          raise Constraint_Error with
942            "invalid wide character in Text_'I'O input";
943       else
944          return Character'Val (Wide_Character'Pos (Result));
945       end if;
946    end Get_Upper_Half_Char_Immed;
947
948    ----------
949    -- Getc --
950    ----------
951
952    function Getc (File : File_Type) return int is
953       ch : int;
954
955    begin
956       ch := fgetc (File.Stream);
957
958       if ch = EOF and then ferror (File.Stream) /= 0 then
959          raise Device_Error;
960       else
961          return ch;
962       end if;
963    end Getc;
964
965    ----------------
966    -- Getc_Immed --
967    ----------------
968
969    function Getc_Immed (File : File_Type) return int is
970       ch          : int;
971       end_of_file : int;
972
973       procedure getc_immediate
974         (stream : FILEs; ch : out int; end_of_file : out int);
975       pragma Import (C, getc_immediate, "getc_immediate");
976
977    begin
978       FIO.Check_Read_Status (AP (File));
979
980       if File.Before_LM then
981          File.Before_LM := False;
982          File.Before_LM_PM := False;
983          ch := LM;
984
985       else
986          getc_immediate (File.Stream, ch, end_of_file);
987
988          if ferror (File.Stream) /= 0 then
989             raise Device_Error;
990          elsif end_of_file /= 0 then
991             return EOF;
992          end if;
993       end if;
994
995       return ch;
996    end Getc_Immed;
997
998    ------------------------------
999    -- Has_Upper_Half_Character --
1000    ------------------------------
1001
1002    function Has_Upper_Half_Character (Item : String) return Boolean is
1003    begin
1004       for J in Item'Range loop
1005          if Character'Pos (Item (J)) >= 16#80# then
1006             return True;
1007          end if;
1008       end loop;
1009
1010       return False;
1011    end Has_Upper_Half_Character;
1012
1013    -------------------------------
1014    -- Initialize_Standard_Files --
1015    -------------------------------
1016
1017    procedure Initialize_Standard_Files is
1018    begin
1019       Standard_Err.Stream            := stderr;
1020       Standard_Err.Name              := Err_Name'Access;
1021       Standard_Err.Form              := Null_Str'Unrestricted_Access;
1022       Standard_Err.Mode              := FCB.Out_File;
1023       Standard_Err.Is_Regular_File   := is_regular_file (fileno (stderr)) /= 0;
1024       Standard_Err.Is_Temporary_File := False;
1025       Standard_Err.Is_System_File    := True;
1026       Standard_Err.Is_Text_File      := True;
1027       Standard_Err.Access_Method     := 'T';
1028       Standard_Err.Self              := Standard_Err;
1029       Standard_Err.WC_Method         := Default_WCEM;
1030
1031       Standard_In.Stream             := stdin;
1032       Standard_In.Name               := In_Name'Access;
1033       Standard_In.Form               := Null_Str'Unrestricted_Access;
1034       Standard_In.Mode               := FCB.In_File;
1035       Standard_In.Is_Regular_File    := is_regular_file (fileno (stdin)) /= 0;
1036       Standard_In.Is_Temporary_File  := False;
1037       Standard_In.Is_System_File     := True;
1038       Standard_In.Is_Text_File       := True;
1039       Standard_In.Access_Method      := 'T';
1040       Standard_In.Self               := Standard_In;
1041       Standard_In.WC_Method          := Default_WCEM;
1042
1043       Standard_Out.Stream            := stdout;
1044       Standard_Out.Name              := Out_Name'Access;
1045       Standard_Out.Form              := Null_Str'Unrestricted_Access;
1046       Standard_Out.Mode              := FCB.Out_File;
1047       Standard_Out.Is_Regular_File   := is_regular_file (fileno (stdout)) /= 0;
1048       Standard_Out.Is_Temporary_File := False;
1049       Standard_Out.Is_System_File    := True;
1050       Standard_Out.Is_Text_File      := True;
1051       Standard_Out.Access_Method     := 'T';
1052       Standard_Out.Self              := Standard_Out;
1053       Standard_Out.WC_Method         := Default_WCEM;
1054
1055       FIO.Make_Unbuffered (AP (Standard_Out));
1056       FIO.Make_Unbuffered (AP (Standard_Err));
1057    end Initialize_Standard_Files;
1058
1059    -------------
1060    -- Is_Open --
1061    -------------
1062
1063    function Is_Open (File : File_Type) return Boolean is
1064    begin
1065       return FIO.Is_Open (AP (File));
1066    end Is_Open;
1067
1068    ----------
1069    -- Line --
1070    ----------
1071
1072    --  Note: we assume that it is impossible in practice for the line
1073    --  to exceed the value of Count'Last, i.e. no check is required for
1074    --  overflow raising layout error.
1075
1076    function Line (File : File_Type) return Positive_Count is
1077    begin
1078       FIO.Check_File_Open (AP (File));
1079       return File.Line;
1080    end Line;
1081
1082    function Line return Positive_Count is
1083    begin
1084       return Line (Current_Out);
1085    end Line;
1086
1087    -----------------
1088    -- Line_Length --
1089    -----------------
1090
1091    function Line_Length (File : File_Type) return Count is
1092    begin
1093       FIO.Check_Write_Status (AP (File));
1094       return File.Line_Length;
1095    end Line_Length;
1096
1097    function Line_Length return Count is
1098    begin
1099       return Line_Length (Current_Out);
1100    end Line_Length;
1101
1102    ----------------
1103    -- Look_Ahead --
1104    ----------------
1105
1106    procedure Look_Ahead
1107      (File        : File_Type;
1108       Item        : out Character;
1109       End_Of_Line : out Boolean)
1110    is
1111       ch : int;
1112
1113    begin
1114       FIO.Check_Read_Status (AP (File));
1115
1116       --  If we are logically before a line mark, we can return immediately
1117
1118       if File.Before_LM then
1119          End_Of_Line := True;
1120          Item := ASCII.NUL;
1121
1122       --  If we are before an upper half character just return it (this can
1123       --  happen if there are two calls to Look_Ahead in a row).
1124
1125       elsif File.Before_Upper_Half_Character then
1126          End_Of_Line := False;
1127          Item := File.Saved_Upper_Half_Character;
1128
1129       --  Otherwise we must read a character from the input stream
1130
1131       else
1132          ch := Getc (File);
1133
1134          if ch = LM
1135            or else ch = EOF
1136            or else (ch = PM and then File.Is_Regular_File)
1137          then
1138             End_Of_Line := True;
1139             Ungetc (ch, File);
1140             Item := ASCII.NUL;
1141
1142          --  Case where character obtained does not represent the start of an
1143          --  encoded sequence so it stands for itself and we can unget it with
1144          --  no difficulty.
1145
1146          elsif not Is_Start_Of_Encoding
1147                      (Character'Val (ch), File.WC_Method)
1148          then
1149             End_Of_Line := False;
1150             Ungetc (ch, File);
1151             Item := Character'Val (ch);
1152
1153          --  For the start of an encoding, we read the character using the
1154          --  Get_Upper_Half_Char routine. It will occupy more than one byte
1155          --  so we can't put it back with ungetc. Instead we save it in the
1156          --  control block, setting a flag that everyone interested in reading
1157          --  characters must test before reading the stream.
1158
1159          else
1160             Item := Get_Upper_Half_Char (Character'Val (ch), File);
1161             End_Of_Line := False;
1162             File.Saved_Upper_Half_Character := Item;
1163             File.Before_Upper_Half_Character := True;
1164          end if;
1165       end if;
1166    end Look_Ahead;
1167
1168    procedure Look_Ahead
1169      (Item        : out Character;
1170       End_Of_Line : out Boolean)
1171    is
1172    begin
1173       Look_Ahead (Current_In, Item, End_Of_Line);
1174    end Look_Ahead;
1175
1176    ----------
1177    -- Mode --
1178    ----------
1179
1180    function Mode (File : File_Type) return File_Mode is
1181    begin
1182       return To_TIO (FIO.Mode (AP (File)));
1183    end Mode;
1184
1185    ----------
1186    -- Name --
1187    ----------
1188
1189    function Name (File : File_Type) return String is
1190    begin
1191       return FIO.Name (AP (File));
1192    end Name;
1193
1194    --------------
1195    -- New_Line --
1196    --------------
1197
1198    procedure New_Line
1199      (File    : File_Type;
1200       Spacing : Positive_Count := 1)
1201    is
1202    begin
1203       --  Raise Constraint_Error if out of range value. The reason for this
1204       --  explicit test is that we don't want junk values around, even if
1205       --  checks are off in the caller.
1206
1207       if not Spacing'Valid then
1208          raise Constraint_Error;
1209       end if;
1210
1211       FIO.Check_Write_Status (AP (File));
1212
1213       for K in 1 .. Spacing loop
1214          Putc (LM, File);
1215          File.Line := File.Line + 1;
1216
1217          if File.Page_Length /= 0
1218            and then File.Line > File.Page_Length
1219          then
1220             Putc (PM, File);
1221             File.Line := 1;
1222             File.Page := File.Page + 1;
1223          end if;
1224       end loop;
1225
1226       File.Col := 1;
1227    end New_Line;
1228
1229    procedure New_Line (Spacing : Positive_Count := 1) is
1230    begin
1231       New_Line (Current_Out, Spacing);
1232    end New_Line;
1233
1234    --------------
1235    -- New_Page --
1236    --------------
1237
1238    procedure New_Page (File : File_Type) is
1239    begin
1240       FIO.Check_Write_Status (AP (File));
1241
1242       if File.Col /= 1 or else File.Line = 1 then
1243          Putc (LM, File);
1244       end if;
1245
1246       Putc (PM, File);
1247       File.Page := File.Page + 1;
1248       File.Line := 1;
1249       File.Col := 1;
1250    end New_Page;
1251
1252    procedure New_Page is
1253    begin
1254       New_Page (Current_Out);
1255    end New_Page;
1256
1257    -----------
1258    -- Nextc --
1259    -----------
1260
1261    function Nextc (File : File_Type) return int is
1262       ch : int;
1263
1264    begin
1265       ch := fgetc (File.Stream);
1266
1267       if ch = EOF then
1268          if ferror (File.Stream) /= 0 then
1269             raise Device_Error;
1270          end if;
1271
1272       else
1273          if ungetc (ch, File.Stream) = EOF then
1274             raise Device_Error;
1275          end if;
1276       end if;
1277
1278       return ch;
1279    end Nextc;
1280
1281    ----------
1282    -- Open --
1283    ----------
1284
1285    procedure Open
1286      (File : in out File_Type;
1287       Mode : File_Mode;
1288       Name : String;
1289       Form : String := "")
1290    is
1291       Dummy_File_Control_Block : Text_AFCB;
1292       pragma Warnings (Off, Dummy_File_Control_Block);
1293       --  Yes, we know this is never assigned a value, only the tag
1294       --  is used for dispatching purposes, so that's expected.
1295
1296    begin
1297       FIO.Open (File_Ptr  => AP (File),
1298                 Dummy_FCB => Dummy_File_Control_Block,
1299                 Mode      => To_FCB (Mode),
1300                 Name      => Name,
1301                 Form      => Form,
1302                 Amethod   => 'T',
1303                 Creat     => False,
1304                 Text      => True);
1305
1306       File.Self := File;
1307       Set_WCEM (File);
1308    end Open;
1309
1310    ----------
1311    -- Page --
1312    ----------
1313
1314    --  Note: we assume that it is impossible in practice for the page
1315    --  to exceed the value of Count'Last, i.e. no check is required for
1316    --  overflow raising layout error.
1317
1318    function Page (File : File_Type) return Positive_Count is
1319    begin
1320       FIO.Check_File_Open (AP (File));
1321       return File.Page;
1322    end Page;
1323
1324    function Page return Positive_Count is
1325    begin
1326       return Page (Current_Out);
1327    end Page;
1328
1329    -----------------
1330    -- Page_Length --
1331    -----------------
1332
1333    function Page_Length (File : File_Type) return Count is
1334    begin
1335       FIO.Check_Write_Status (AP (File));
1336       return File.Page_Length;
1337    end Page_Length;
1338
1339    function Page_Length return Count is
1340    begin
1341       return Page_Length (Current_Out);
1342    end Page_Length;
1343
1344    ---------
1345    -- Put --
1346    ---------
1347
1348    procedure Put
1349      (File : File_Type;
1350       Item : Character)
1351    is
1352    begin
1353       FIO.Check_Write_Status (AP (File));
1354
1355       if File.Line_Length /= 0 and then File.Col > File.Line_Length then
1356          New_Line (File);
1357       end if;
1358
1359       --  If lower half character, or brackets encoding, output directly
1360
1361       if Character'Pos (Item) < 16#80#
1362         or else File.WC_Method = WCEM_Brackets
1363       then
1364          if fputc (Character'Pos (Item), File.Stream) = EOF then
1365             raise Device_Error;
1366          end if;
1367
1368       --  Case of upper half character with non-brackets encoding
1369
1370       else
1371          Put_Encoded (File, Item);
1372       end if;
1373
1374       File.Col := File.Col + 1;
1375    end Put;
1376
1377    procedure Put (Item : Character) is
1378    begin
1379       FIO.Check_Write_Status (AP (Current_Out));
1380
1381       if Current_Out.Line_Length /= 0
1382         and then Current_Out.Col > Current_Out.Line_Length
1383       then
1384          New_Line (Current_Out);
1385       end if;
1386
1387       --  If lower half character, or brackets encoding, output directly
1388
1389       if Character'Pos (Item) < 16#80#
1390         or else Default_WCEM = WCEM_Brackets
1391       then
1392          if fputc (Character'Pos (Item), Current_Out.Stream) = EOF then
1393             raise Device_Error;
1394          end if;
1395
1396       --  Case of upper half character with non-brackets encoding
1397
1398       else
1399          Put_Encoded (Current_Out, Item);
1400       end if;
1401
1402       Current_Out.Col := Current_Out.Col + 1;
1403    end Put;
1404
1405    ---------
1406    -- Put --
1407    ---------
1408
1409    procedure Put
1410      (File : File_Type;
1411       Item : String)
1412    is
1413    begin
1414       FIO.Check_Write_Status (AP (File));
1415
1416       --  Only have something to do if string is non-null
1417
1418       if Item'Length > 0 then
1419
1420          --  If we have bounded lines, or if the file encoding is other than
1421          --  Brackets and the string has at least one upper half character,
1422          --  then output the string character by character.
1423
1424          if File.Line_Length /= 0
1425            or else (File.WC_Method /= WCEM_Brackets
1426                       and then Has_Upper_Half_Character (Item))
1427          then
1428             for J in Item'Range loop
1429                Put (File, Item (J));
1430             end loop;
1431
1432          --  Otherwise we can output the entire string at once. Note that if
1433          --  there are LF or FF characters in the string, we do not bother to
1434          --  count them as line or page terminators.
1435
1436          else
1437             FIO.Write_Buf (AP (File), Item'Address, Item'Length);
1438             File.Col := File.Col + Item'Length;
1439          end if;
1440       end if;
1441    end Put;
1442
1443    procedure Put (Item : String) is
1444    begin
1445       Put (Current_Out, Item);
1446    end Put;
1447
1448    -----------------
1449    -- Put_Encoded --
1450    -----------------
1451
1452    procedure Put_Encoded (File : File_Type; Char : Character) is
1453       procedure Out_Char (C : Character);
1454       --  Procedure to output one character of an upper half encoded sequence
1455
1456       procedure WC_Out is new Wide_Char_To_Char_Sequence (Out_Char);
1457
1458       --------------
1459       -- Out_Char --
1460       --------------
1461
1462       procedure Out_Char (C : Character) is
1463       begin
1464          Putc (Character'Pos (C), File);
1465       end Out_Char;
1466
1467    --  Start of processing for Put_Encoded
1468
1469    begin
1470       WC_Out (Wide_Character'Val (Character'Pos (Char)), File.WC_Method);
1471    end Put_Encoded;
1472
1473    --------------
1474    -- Put_Line --
1475    --------------
1476
1477    procedure Put_Line
1478      (File : File_Type;
1479       Item : String)
1480    is
1481       Ilen   : Natural := Item'Length;
1482       Istart : Natural := Item'First;
1483
1484    begin
1485       FIO.Check_Write_Status (AP (File));
1486
1487       --  If we have bounded lines, or if the file encoding is other than
1488       --  Brackets and the string has at least one upper half character, then
1489       --  output the string character by character.
1490
1491       if File.Line_Length /= 0
1492         or else (File.WC_Method /= WCEM_Brackets
1493                    and then Has_Upper_Half_Character (Item))
1494       then
1495          for J in Item'Range loop
1496             Put (File, Item (J));
1497          end loop;
1498
1499          New_Line (File);
1500          return;
1501       end if;
1502
1503       --  Normal case where we do not need to output character by character
1504
1505       --  We setup a single string that has the necessary terminators and
1506       --  then write it with a single call. The reason for doing this is
1507       --  that it gives better behavior for the use of Put_Line in multi-
1508       --  tasking programs, since often the OS will treat the entire put
1509       --  operation as an atomic operation.
1510
1511       --  We only do this if the message is 512 characters or less in length,
1512       --  since otherwise Put_Line would use an unbounded amount of stack
1513       --  space and could cause undetected stack overflow. If we have a
1514       --  longer string, then output the first part separately to avoid this.
1515
1516       if Ilen > 512 then
1517          FIO.Write_Buf (AP (File), Item'Address, size_t (Ilen - 512));
1518          Istart := Istart + Ilen - 512;
1519          Ilen   := 512;
1520       end if;
1521
1522       --  Now prepare the string with its terminator
1523
1524       declare
1525          Buffer : String (1 .. Ilen + 2);
1526          Plen   : size_t;
1527
1528       begin
1529          Buffer (1 .. Ilen) := Item (Istart .. Item'Last);
1530          Buffer (Ilen + 1) := Character'Val (LM);
1531
1532          if File.Page_Length /= 0
1533            and then File.Line > File.Page_Length
1534          then
1535             Buffer (Ilen + 2) := Character'Val (PM);
1536             Plen := size_t (Ilen) + 2;
1537             File.Line := 1;
1538             File.Page := File.Page + 1;
1539
1540          else
1541             Plen := size_t (Ilen) + 1;
1542             File.Line := File.Line + 1;
1543          end if;
1544
1545          FIO.Write_Buf (AP (File), Buffer'Address, Plen);
1546
1547          File.Col := 1;
1548       end;
1549    end Put_Line;
1550
1551    procedure Put_Line (Item : String) is
1552    begin
1553       Put_Line (Current_Out, Item);
1554    end Put_Line;
1555
1556    ----------
1557    -- Putc --
1558    ----------
1559
1560    procedure Putc (ch : int; File : File_Type) is
1561    begin
1562       if fputc (ch, File.Stream) = EOF then
1563          raise Device_Error;
1564       end if;
1565    end Putc;
1566
1567    ----------
1568    -- Read --
1569    ----------
1570
1571    --  This is the primitive Stream Read routine, used when a Text_IO file
1572    --  is treated directly as a stream using Text_IO.Streams.Stream.
1573
1574    procedure Read
1575      (File : in out Text_AFCB;
1576       Item : out Stream_Element_Array;
1577       Last : out Stream_Element_Offset)
1578    is
1579       Discard_ch : int;
1580       pragma Warnings (Off, Discard_ch);
1581
1582    begin
1583       --  Need to deal with Before_Upper_Half_Character ???
1584
1585       if File.Mode /= FCB.In_File then
1586          raise Mode_Error;
1587       end if;
1588
1589       --  Deal with case where our logical and physical position do not match
1590       --  because of being after an LM or LM-PM sequence when in fact we are
1591       --  logically positioned before it.
1592
1593       if File.Before_LM then
1594
1595          --  If we are before a PM, then it is possible for a stream read
1596          --  to leave us after the LM and before the PM, which is a bit
1597          --  odd. The easiest way to deal with this is to unget the PM,
1598          --  so we are indeed positioned between the characters. This way
1599          --  further stream read operations will work correctly, and the
1600          --  effect on text processing is a little weird, but what can
1601          --  be expected if stream and text input are mixed this way?
1602
1603          if File.Before_LM_PM then
1604             Discard_ch := ungetc (PM, File.Stream);
1605             File.Before_LM_PM := False;
1606          end if;
1607
1608          File.Before_LM := False;
1609
1610          Item (Item'First) := Stream_Element (Character'Pos (ASCII.LF));
1611
1612          if Item'Length = 1 then
1613             Last := Item'Last;
1614
1615          else
1616             Last :=
1617               Item'First +
1618                 Stream_Element_Offset
1619                   (fread (buffer => Item'Address,
1620                           index  => size_t (Item'First + 1),
1621                           size   => 1,
1622                           count  => Item'Length - 1,
1623                           stream => File.Stream));
1624          end if;
1625
1626          return;
1627       end if;
1628
1629       --  Now we do the read. Since this is a text file, it is normally in
1630       --  text mode, but stream data must be read in binary mode, so we
1631       --  temporarily set binary mode for the read, resetting it after.
1632       --  These calls have no effect in a system (like Unix) where there is
1633       --  no distinction between text and binary files.
1634
1635       set_binary_mode (fileno (File.Stream));
1636
1637       Last :=
1638         Item'First +
1639           Stream_Element_Offset
1640             (fread (Item'Address, 1, Item'Length, File.Stream)) - 1;
1641
1642       if Last < Item'Last then
1643          if ferror (File.Stream) /= 0 then
1644             raise Device_Error;
1645          end if;
1646       end if;
1647
1648       set_text_mode (fileno (File.Stream));
1649    end Read;
1650
1651    -----------
1652    -- Reset --
1653    -----------
1654
1655    procedure Reset
1656      (File : in out File_Type;
1657       Mode : File_Mode)
1658    is
1659    begin
1660       --  Don't allow change of mode for current file (RM A.10.2(5))
1661
1662       if (File = Current_In  or else
1663           File = Current_Out or else
1664           File = Current_Error)
1665         and then To_FCB (Mode) /= File.Mode
1666       then
1667          raise Mode_Error;
1668       end if;
1669
1670       Terminate_Line (File);
1671       FIO.Reset (AP (File)'Unrestricted_Access, To_FCB (Mode));
1672       File.Page := 1;
1673       File.Line := 1;
1674       File.Col  := 1;
1675       File.Line_Length := 0;
1676       File.Page_Length := 0;
1677       File.Before_LM := False;
1678       File.Before_LM_PM := False;
1679    end Reset;
1680
1681    procedure Reset (File : in out File_Type) is
1682    begin
1683       Terminate_Line (File);
1684       FIO.Reset (AP (File)'Unrestricted_Access);
1685       File.Page := 1;
1686       File.Line := 1;
1687       File.Col  := 1;
1688       File.Line_Length := 0;
1689       File.Page_Length := 0;
1690       File.Before_LM := False;
1691       File.Before_LM_PM := False;
1692    end Reset;
1693
1694    -------------
1695    -- Set_Col --
1696    -------------
1697
1698    procedure Set_Col
1699      (File : File_Type;
1700       To   : Positive_Count)
1701    is
1702       ch : int;
1703
1704    begin
1705       --  Raise Constraint_Error if out of range value. The reason for this
1706       --  explicit test is that we don't want junk values around, even if
1707       --  checks are off in the caller.
1708
1709       if not To'Valid then
1710          raise Constraint_Error;
1711       end if;
1712
1713       FIO.Check_File_Open (AP (File));
1714
1715       --  Output case
1716
1717       if Mode (File) >= Out_File then
1718
1719          --  Error if we attempt to set Col to a value greater than the
1720          --  maximum permissible line length.
1721
1722          if File.Line_Length /= 0 and then To > File.Line_Length then
1723             raise Layout_Error;
1724          end if;
1725
1726          --  If we are behind current position, then go to start of new line
1727
1728          if To < File.Col then
1729             New_Line (File);
1730          end if;
1731
1732          --  Loop to output blanks till we are at the required column
1733
1734          while File.Col < To loop
1735             Put (File, ' ');
1736          end loop;
1737
1738       --  Input case
1739
1740       else
1741          --  If we are logically before a LM, but physically after it, the
1742          --  file position still reflects the position before the LM, so eat
1743          --  it now and adjust the file position appropriately.
1744
1745          if File.Before_LM then
1746             File.Before_LM := False;
1747             File.Before_LM_PM := False;
1748             File.Line := File.Line + 1;
1749             File.Col := 1;
1750          end if;
1751
1752          --  Loop reading characters till we get one at the required Col value
1753
1754          loop
1755             --  Read next character. The reason we have to read ahead is to
1756             --  skip formatting characters, the effect of Set_Col is to set
1757             --  us to a real character with the right Col value, and format
1758             --  characters don't count.
1759
1760             ch := Getc (File);
1761
1762             --  Error if we hit an end of file
1763
1764             if ch = EOF then
1765                raise End_Error;
1766
1767             --  If line mark, eat it and adjust file position
1768
1769             elsif ch = LM then
1770                File.Line := File.Line + 1;
1771                File.Col := 1;
1772
1773             --  If recognized page mark, eat it, and adjust file position
1774
1775             elsif ch = PM and then File.Is_Regular_File then
1776                File.Page := File.Page + 1;
1777                File.Line := 1;
1778                File.Col := 1;
1779
1780             --  Otherwise this is the character we are looking for, so put it
1781             --  back in the input stream (we have not adjusted the file
1782             --  position yet, so everything is set right after this ungetc).
1783
1784             elsif To = File.Col then
1785                Ungetc (ch, File);
1786                return;
1787
1788             --  Keep skipping characters if we are not there yet, updating the
1789             --  file position past the skipped character.
1790
1791             else
1792                File.Col := File.Col + 1;
1793             end if;
1794          end loop;
1795       end if;
1796    end Set_Col;
1797
1798    procedure Set_Col (To : Positive_Count) is
1799    begin
1800       Set_Col (Current_Out, To);
1801    end Set_Col;
1802
1803    ---------------
1804    -- Set_Error --
1805    ---------------
1806
1807    procedure Set_Error (File : File_Type) is
1808    begin
1809       FIO.Check_Write_Status (AP (File));
1810       Current_Err := File;
1811    end Set_Error;
1812
1813    ---------------
1814    -- Set_Input --
1815    ---------------
1816
1817    procedure Set_Input (File : File_Type) is
1818    begin
1819       FIO.Check_Read_Status (AP (File));
1820       Current_In := File;
1821    end Set_Input;
1822
1823    --------------
1824    -- Set_Line --
1825    --------------
1826
1827    procedure Set_Line
1828      (File : File_Type;
1829       To   : Positive_Count)
1830    is
1831    begin
1832       --  Raise Constraint_Error if out of range value. The reason for this
1833       --  explicit test is that we don't want junk values around, even if
1834       --  checks are off in the caller.
1835
1836       if not To'Valid then
1837          raise Constraint_Error;
1838       end if;
1839
1840       FIO.Check_File_Open (AP (File));
1841
1842       if To = File.Line then
1843          return;
1844       end if;
1845
1846       if Mode (File) >= Out_File then
1847          if File.Page_Length /= 0 and then To > File.Page_Length then
1848             raise Layout_Error;
1849          end if;
1850
1851          if To < File.Line then
1852             New_Page (File);
1853          end if;
1854
1855          while File.Line < To loop
1856             New_Line (File);
1857          end loop;
1858
1859       else
1860          while To /= File.Line loop
1861             Skip_Line (File);
1862          end loop;
1863       end if;
1864    end Set_Line;
1865
1866    procedure Set_Line (To : Positive_Count) is
1867    begin
1868       Set_Line (Current_Out, To);
1869    end Set_Line;
1870
1871    ---------------------
1872    -- Set_Line_Length --
1873    ---------------------
1874
1875    procedure Set_Line_Length (File : File_Type; To : Count) is
1876    begin
1877       --  Raise Constraint_Error if out of range value. The reason for this
1878       --  explicit test is that we don't want junk values around, even if
1879       --  checks are off in the caller.
1880
1881       if not To'Valid then
1882          raise Constraint_Error;
1883       end if;
1884
1885       FIO.Check_Write_Status (AP (File));
1886       File.Line_Length := To;
1887    end Set_Line_Length;
1888
1889    procedure Set_Line_Length (To : Count) is
1890    begin
1891       Set_Line_Length (Current_Out, To);
1892    end Set_Line_Length;
1893
1894    ----------------
1895    -- Set_Output --
1896    ----------------
1897
1898    procedure Set_Output (File : File_Type) is
1899    begin
1900       FIO.Check_Write_Status (AP (File));
1901       Current_Out := File;
1902    end Set_Output;
1903
1904    ---------------------
1905    -- Set_Page_Length --
1906    ---------------------
1907
1908    procedure Set_Page_Length (File : File_Type; To : Count) is
1909    begin
1910       --  Raise Constraint_Error if out of range value. The reason for this
1911       --  explicit test is that we don't want junk values around, even if
1912       --  checks are off in the caller.
1913
1914       if not To'Valid then
1915          raise Constraint_Error;
1916       end if;
1917
1918       FIO.Check_Write_Status (AP (File));
1919       File.Page_Length := To;
1920    end Set_Page_Length;
1921
1922    procedure Set_Page_Length (To : Count) is
1923    begin
1924       Set_Page_Length (Current_Out, To);
1925    end Set_Page_Length;
1926
1927    --------------
1928    -- Set_WCEM --
1929    --------------
1930
1931    procedure Set_WCEM (File : in out File_Type) is
1932       Start : Natural;
1933       Stop  : Natural;
1934
1935    begin
1936       File.WC_Method := WCEM_Brackets;
1937       FIO.Form_Parameter (File.Form.all, "wcem", Start, Stop);
1938
1939       if Start = 0 then
1940          File.WC_Method := WCEM_Brackets;
1941
1942       else
1943          if Stop = Start then
1944             for J in WC_Encoding_Letters'Range loop
1945                if File.Form (Start) = WC_Encoding_Letters (J) then
1946                   File.WC_Method := J;
1947                   return;
1948                end if;
1949             end loop;
1950          end if;
1951
1952          Close (File);
1953          raise Use_Error with "invalid WCEM form parameter";
1954       end if;
1955    end Set_WCEM;
1956
1957    ---------------
1958    -- Skip_Line --
1959    ---------------
1960
1961    procedure Skip_Line
1962      (File    : File_Type;
1963       Spacing : Positive_Count := 1)
1964    is
1965       ch : int;
1966
1967    begin
1968       --  Raise Constraint_Error if out of range value. The reason for this
1969       --  explicit test is that we don't want junk values around, even if
1970       --  checks are off in the caller.
1971
1972       if not Spacing'Valid then
1973          raise Constraint_Error;
1974       end if;
1975
1976       FIO.Check_Read_Status (AP (File));
1977
1978       for L in 1 .. Spacing loop
1979          if File.Before_LM then
1980             File.Before_LM := False;
1981
1982             --  Note that if File.Before_LM_PM is currently set, we also have
1983             --  to reset it (because it makes sense for Before_LM_PM to be set
1984             --  only when Before_LM is also set). This is done later on in this
1985             --  subprogram, as soon as Before_LM_PM has been taken into account
1986             --  for the purpose of page and line counts.
1987
1988          else
1989             ch := Getc (File);
1990
1991             --  If at end of file now, then immediately raise End_Error. Note
1992             --  that we can never be positioned between a line mark and a page
1993             --  mark, so if we are at the end of file, we cannot logically be
1994             --  before the implicit page mark that is at the end of the file.
1995
1996             --  For the same reason, we do not need an explicit check for a
1997             --  page mark. If there is a FF in the middle of a line, the file
1998             --  is not in canonical format and we do not care about the page
1999             --  numbers for files other than ones in canonical format.
2000
2001             if ch = EOF then
2002                raise End_Error;
2003             end if;
2004
2005             --  If not at end of file, then loop till we get to an LM or EOF.
2006             --  The latter case happens only in non-canonical files where the
2007             --  last line is not terminated by LM, but we don't want to blow
2008             --  up for such files, so we assume an implicit LM in this case.
2009
2010             loop
2011                exit when ch = LM or else ch = EOF;
2012                ch := Getc (File);
2013             end loop;
2014          end if;
2015
2016          --  We have got past a line mark, now, for a regular file only,
2017          --  see if a page mark immediately follows this line mark and
2018          --  if so, skip past the page mark as well. We do not do this
2019          --  for non-regular files, since it would cause an undesirable
2020          --  wait for an additional character.
2021
2022          File.Col := 1;
2023          File.Line := File.Line + 1;
2024
2025          if File.Before_LM_PM then
2026             File.Page := File.Page + 1;
2027             File.Line := 1;
2028             File.Before_LM_PM := False;
2029
2030          elsif File.Is_Regular_File then
2031             ch := Getc (File);
2032
2033             --  Page mark can be explicit, or implied at the end of the file
2034
2035             if (ch = PM or else ch = EOF)
2036               and then File.Is_Regular_File
2037             then
2038                File.Page := File.Page + 1;
2039                File.Line := 1;
2040             else
2041                Ungetc (ch, File);
2042             end if;
2043          end if;
2044       end loop;
2045
2046       File.Before_Upper_Half_Character := False;
2047    end Skip_Line;
2048
2049    procedure Skip_Line (Spacing : Positive_Count := 1) is
2050    begin
2051       Skip_Line (Current_In, Spacing);
2052    end Skip_Line;
2053
2054    ---------------
2055    -- Skip_Page --
2056    ---------------
2057
2058    procedure Skip_Page (File : File_Type) is
2059       ch : int;
2060
2061    begin
2062       FIO.Check_Read_Status (AP (File));
2063
2064       --  If at page mark already, just skip it
2065
2066       if File.Before_LM_PM then
2067          File.Before_LM := False;
2068          File.Before_LM_PM := False;
2069          File.Page := File.Page + 1;
2070          File.Line := 1;
2071          File.Col  := 1;
2072          return;
2073       end if;
2074
2075       --  This is a bit tricky, if we are logically before an LM then
2076       --  it is not an error if we are at an end of file now, since we
2077       --  are not really at it.
2078
2079       if File.Before_LM then
2080          File.Before_LM := False;
2081          File.Before_LM_PM := False;
2082          ch := Getc (File);
2083
2084       --  Otherwise we do raise End_Error if we are at the end of file now
2085
2086       else
2087          ch := Getc (File);
2088
2089          if ch = EOF then
2090             raise End_Error;
2091          end if;
2092       end if;
2093
2094       --  Now we can just rumble along to the next page mark, or to the
2095       --  end of file, if that comes first. The latter case happens when
2096       --  the page mark is implied at the end of file.
2097
2098       loop
2099          exit when ch = EOF
2100            or else (ch = PM and then File.Is_Regular_File);
2101          ch := Getc (File);
2102       end loop;
2103
2104       File.Page := File.Page + 1;
2105       File.Line := 1;
2106       File.Col  := 1;
2107       File.Before_Upper_Half_Character := False;
2108    end Skip_Page;
2109
2110    procedure Skip_Page is
2111    begin
2112       Skip_Page (Current_In);
2113    end Skip_Page;
2114
2115    --------------------
2116    -- Standard_Error --
2117    --------------------
2118
2119    function Standard_Error return File_Type is
2120    begin
2121       return Standard_Err;
2122    end Standard_Error;
2123
2124    function Standard_Error return File_Access is
2125    begin
2126       return Standard_Err'Access;
2127    end Standard_Error;
2128
2129    --------------------
2130    -- Standard_Input --
2131    --------------------
2132
2133    function Standard_Input return File_Type is
2134    begin
2135       return Standard_In;
2136    end Standard_Input;
2137
2138    function Standard_Input return File_Access is
2139    begin
2140       return Standard_In'Access;
2141    end Standard_Input;
2142
2143    ---------------------
2144    -- Standard_Output --
2145    ---------------------
2146
2147    function Standard_Output return File_Type is
2148    begin
2149       return Standard_Out;
2150    end Standard_Output;
2151
2152    function Standard_Output return File_Access is
2153    begin
2154       return Standard_Out'Access;
2155    end Standard_Output;
2156
2157    --------------------
2158    -- Terminate_Line --
2159    --------------------
2160
2161    procedure Terminate_Line (File : File_Type) is
2162    begin
2163       FIO.Check_File_Open (AP (File));
2164
2165       --  For file other than In_File, test for needing to terminate last line
2166
2167       if Mode (File) /= In_File then
2168
2169          --  If not at start of line definition need new line
2170
2171          if File.Col /= 1 then
2172             New_Line (File);
2173
2174          --  For files other than standard error and standard output, we
2175          --  make sure that an empty file has a single line feed, so that
2176          --  it is properly formatted. We avoid this for the standard files
2177          --  because it is too much of a nuisance to have these odd line
2178          --  feeds when nothing has been written to the file.
2179
2180          --  We also avoid this for files opened in append mode, in
2181          --  accordance with (RM A.8.2(10))
2182
2183          elsif (File /= Standard_Err and then File /= Standard_Out)
2184            and then (File.Line = 1 and then File.Page = 1)
2185            and then Mode (File) = Out_File
2186          then
2187             New_Line (File);
2188          end if;
2189       end if;
2190    end Terminate_Line;
2191
2192    ------------
2193    -- Ungetc --
2194    ------------
2195
2196    procedure Ungetc (ch : int; File : File_Type) is
2197    begin
2198       if ch /= EOF then
2199          if ungetc (ch, File.Stream) = EOF then
2200             raise Device_Error;
2201          end if;
2202       end if;
2203    end Ungetc;
2204
2205    -----------
2206    -- Write --
2207    -----------
2208
2209    --  This is the primitive Stream Write routine, used when a Text_IO file
2210    --  is treated directly as a stream using Text_IO.Streams.Stream.
2211
2212    procedure Write
2213      (File : in out Text_AFCB;
2214       Item : Stream_Element_Array)
2215    is
2216       pragma Warnings (Off, File);
2217       --  Because in this implementation we don't need IN OUT, we only read
2218
2219       function Has_Translated_Characters return Boolean;
2220       --  return True if Item array contains a character which will be
2221       --  translated under the text file mode. There is only one such
2222       --  character under DOS based systems which is character 10.
2223
2224       text_translation_required : Boolean;
2225       for text_translation_required'Size use Character'Size;
2226       pragma Import (C, text_translation_required,
2227                      "__gnat_text_translation_required");
2228
2229       Siz : constant size_t := Item'Length;
2230
2231       -------------------------------
2232       -- Has_Translated_Characters --
2233       -------------------------------
2234
2235       function Has_Translated_Characters return Boolean is
2236       begin
2237          for K in Item'Range loop
2238             if Item (K) = 10 then
2239                return True;
2240             end if;
2241          end loop;
2242          return False;
2243       end Has_Translated_Characters;
2244
2245       Needs_Binary_Write : constant Boolean :=
2246                              text_translation_required
2247                                and then Has_Translated_Characters;
2248
2249    --  Start of processing for Write
2250
2251    begin
2252       if File.Mode = FCB.In_File then
2253          raise Mode_Error;
2254       end if;
2255
2256       --  Now we do the write. Since this is a text file, it is normally in
2257       --  text mode, but stream data must be written in binary mode, so we
2258       --  temporarily set binary mode for the write, resetting it after. This
2259       --  is done only if needed (i.e. there is some characters in Item which
2260       --  needs to be written using the binary mode).
2261       --  These calls have no effect in a system (like Unix) where there is
2262       --  no distinction between text and binary files.
2263
2264       --  Since the character translation is done at the time the buffer is
2265       --  written (this is true under Windows) we first flush current buffer
2266       --  with text mode if needed.
2267
2268       if Needs_Binary_Write then
2269          if fflush (File.Stream) = -1 then
2270             raise Device_Error;
2271          end if;
2272
2273          set_binary_mode (fileno (File.Stream));
2274       end if;
2275
2276       if fwrite (Item'Address, 1, Siz, File.Stream) /= Siz then
2277          raise Device_Error;
2278       end if;
2279
2280       --  At this point we need to flush the buffer using the binary mode then
2281       --  we reset to text mode.
2282
2283       if Needs_Binary_Write then
2284          if fflush (File.Stream) = -1 then
2285             raise Device_Error;
2286          end if;
2287
2288          set_text_mode (fileno (File.Stream));
2289       end if;
2290    end Write;
2291
2292 begin
2293    --  Initialize Standard Files
2294
2295    for J in WC_Encoding_Method loop
2296       if WC_Encoding = WC_Encoding_Letters (J) then
2297          Default_WCEM := J;
2298       end if;
2299    end loop;
2300
2301    Initialize_Standard_Files;
2302
2303    FIO.Chain_File (AP (Standard_In));
2304    FIO.Chain_File (AP (Standard_Out));
2305    FIO.Chain_File (AP (Standard_Err));
2306
2307 end Ada.Text_IO;