1 ------------------------------------------------------------------------------
3 -- GNAT RUN-TIME COMPONENTS --
5 -- A D A . W I D E _ T E X T _ I O --
9 -- Copyright (C) 1992-2008, Free Software Foundation, Inc. --
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 2, 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. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
22 -- As a special exception, if other files instantiate generics from this --
23 -- unit, or you link this unit with other files to produce an executable, --
24 -- this unit does not by itself cause the resulting executable to be --
25 -- covered by the GNU General Public License. This exception does not --
26 -- however invalidate any other reasons why the executable file might be --
27 -- covered by the GNU Public License. --
29 -- GNAT was originally developed by the GNAT team at New York University. --
30 -- Extensive contributions were provided by Ada Core Technologies Inc. --
32 ------------------------------------------------------------------------------
34 with Ada
.Streams
; use Ada
.Streams
;
35 with Interfaces
.C_Streams
; use Interfaces
.C_Streams
;
39 with System
.WCh_Cnv
; use System
.WCh_Cnv
;
40 with System
.WCh_Con
; use System
.WCh_Con
;
42 with Ada
.Unchecked_Conversion
;
43 with Ada
.Unchecked_Deallocation
;
45 pragma Elaborate_All
(System
.File_IO
);
46 -- Needed because of calls to Chain_File in package body elaboration
48 package body Ada
.Wide_Text_IO
is
50 package FIO
renames System
.File_IO
;
52 subtype AP
is FCB
.AFCB_Ptr
;
54 function To_FCB
is new Ada
.Unchecked_Conversion
(File_Mode
, FCB
.File_Mode
);
55 function To_TIO
is new Ada
.Unchecked_Conversion
(FCB
.File_Mode
, File_Mode
);
56 use type FCB
.File_Mode
;
58 use type System
.CRTL
.size_t
;
60 WC_Encoding
: Character;
61 pragma Import
(C
, WC_Encoding
, "__gl_wc_encoding");
63 -----------------------
64 -- Local Subprograms --
65 -----------------------
67 function Getc_Immed
(File
: File_Type
) return int
;
68 -- This routine is identical to Getc, except that the read is done in
69 -- Get_Immediate mode (i.e. without waiting for a line return).
71 function Get_Wide_Char_Immed
73 File
: File_Type
) return Wide_Character;
74 -- This routine is identical to Get_Wide_Char, except that the reads are
75 -- done in Get_Immediate mode (i.e. without waiting for a line return).
77 procedure Set_WCEM
(File
: in out File_Type
);
78 -- Called by Open and Create to set the wide character encoding method for
79 -- the file, processing a WCEM form parameter if one is present. File is
80 -- IN OUT because it may be closed in case of an error.
86 function AFCB_Allocate
87 (Control_Block
: Wide_Text_AFCB
) return FCB
.AFCB_Ptr
89 pragma Unreferenced
(Control_Block
);
91 return new Wide_Text_AFCB
;
98 procedure AFCB_Close
(File
: not null access Wide_Text_AFCB
) is
100 -- If the file being closed is one of the current files, then close
101 -- the corresponding current file. It is not clear that this action
102 -- is required (RM A.10.3(23)) but it seems reasonable, and besides
103 -- ACVC test CE3208A expects this behavior.
105 if File_Type
(File
) = Current_In
then
107 elsif File_Type
(File
) = Current_Out
then
109 elsif File_Type
(File
) = Current_Err
then
113 Terminate_Line
(File_Type
(File
));
120 procedure AFCB_Free
(File
: not null access Wide_Text_AFCB
) is
121 type FCB_Ptr
is access all Wide_Text_AFCB
;
122 FT
: FCB_Ptr
:= FCB_Ptr
(File
);
125 new Ada
.Unchecked_Deallocation
(Wide_Text_AFCB
, FCB_Ptr
);
135 procedure Close
(File
: in out File_Type
) is
137 FIO
.Close
(AP
(File
));
144 -- Note: we assume that it is impossible in practice for the column
145 -- to exceed the value of Count'Last, i.e. no check is required for
146 -- overflow raising layout error.
148 function Col
(File
: File_Type
) return Positive_Count
is
150 FIO
.Check_File_Open
(AP
(File
));
154 function Col
return Positive_Count
is
156 return Col
(Current_Out
);
164 (File
: in out File_Type
;
165 Mode
: File_Mode
:= Out_File
;
169 Dummy_File_Control_Block
: Wide_Text_AFCB
;
170 pragma Warnings
(Off
, Dummy_File_Control_Block
);
171 -- Yes, we know this is never assigned a value, only the tag
172 -- is used for dispatching purposes, so that's expected.
175 FIO
.Open
(File_Ptr
=> AP
(File
),
176 Dummy_FCB
=> Dummy_File_Control_Block
,
177 Mode
=> To_FCB
(Mode
),
192 function Current_Error
return File_Type
is
197 function Current_Error
return File_Access
is
199 return Current_Err
.Self
'Access;
206 function Current_Input
return File_Type
is
211 function Current_Input
return File_Access
is
213 return Current_In
.Self
'Access;
220 function Current_Output
return File_Type
is
225 function Current_Output
return File_Access
is
227 return Current_Out
.Self
'Access;
234 procedure Delete
(File
: in out File_Type
) is
236 FIO
.Delete
(AP
(File
));
243 function End_Of_File
(File
: File_Type
) return Boolean is
247 FIO
.Check_Read_Status
(AP
(File
));
249 if File
.Before_Wide_Character
then
252 elsif File
.Before_LM
then
253 if File
.Before_LM_PM
then
254 return Nextc
(File
) = EOF
;
268 File
.Before_LM
:= True;
272 -- Here we are just past the line mark with Before_LM set so that we
273 -- do not have to try to back up past the LM, thus avoiding the need
274 -- to back up more than one character.
281 elsif ch
= PM
and then File
.Is_Regular_File
then
282 File
.Before_LM_PM
:= True;
283 return Nextc
(File
) = EOF
;
285 -- Here if neither EOF nor PM followed end of line
294 function End_Of_File
return Boolean is
296 return End_Of_File
(Current_In
);
303 function End_Of_Line
(File
: File_Type
) return Boolean is
307 FIO
.Check_Read_Status
(AP
(File
));
309 if File
.Before_Wide_Character
then
312 elsif File
.Before_LM
then
328 function End_Of_Line
return Boolean is
330 return End_Of_Line
(Current_In
);
337 function End_Of_Page
(File
: File_Type
) return Boolean is
341 FIO
.Check_Read_Status
(AP
(File
));
343 if not File
.Is_Regular_File
then
346 elsif File
.Before_Wide_Character
then
349 elsif File
.Before_LM
then
350 if File
.Before_LM_PM
then
365 File
.Before_LM
:= True;
369 -- Here we are just past the line mark with Before_LM set so that we
370 -- do not have to try to back up past the LM, thus avoiding the need
371 -- to back up more than one character.
375 return ch
= PM
or else ch
= EOF
;
378 function End_Of_Page
return Boolean is
380 return End_Of_Page
(Current_In
);
387 procedure Flush
(File
: File_Type
) is
389 FIO
.Flush
(AP
(File
));
401 function Form
(File
: File_Type
) return String is
403 return FIO
.Form
(AP
(File
));
412 Item
: out Wide_Character)
417 FIO
.Check_Read_Status
(AP
(File
));
419 if File
.Before_Wide_Character
then
420 File
.Before_Wide_Character
:= False;
421 Item
:= File
.Saved_Wide_Character
;
423 -- Ada.Text_IO checks Before_LM_PM here, shouldn't we do the same???
426 Get_Character
(File
, C
);
427 Item
:= Get_Wide_Char
(C
, File
);
431 procedure Get
(Item
: out Wide_Character) is
433 Get
(Current_In
, Item
);
438 Item
: out Wide_String)
441 for J
in Item
'Range loop
442 Get
(File
, Item
(J
));
446 procedure Get
(Item
: out Wide_String) is
448 Get
(Current_In
, Item
);
455 procedure Get_Character
457 Item
: out Character)
462 if File
.Before_LM
then
463 File
.Before_LM
:= False;
464 File
.Before_LM_PM
:= False;
467 if File
.Before_LM_PM
then
469 File
.Page
:= File
.Page
+ 1;
470 File
.Before_LM_PM
:= False;
473 File
.Line
:= File
.Line
+ 1;
484 File
.Line
:= File
.Line
+ 1;
487 elsif ch
= PM
and then File
.Is_Regular_File
then
488 File
.Page
:= File
.Page
+ 1;
492 Item
:= Character'Val (ch
);
493 File
.Col
:= File
.Col
+ 1;
503 procedure Get_Immediate
505 Item
: out Wide_Character)
510 FIO
.Check_Read_Status
(AP
(File
));
512 if File
.Before_Wide_Character
then
513 File
.Before_Wide_Character
:= False;
514 Item
:= File
.Saved_Wide_Character
;
516 elsif File
.Before_LM
then
517 File
.Before_LM
:= False;
518 File
.Before_LM_PM
:= False;
519 Item
:= Wide_Character'Val (LM
);
522 ch
:= Getc_Immed
(File
);
527 Item
:= Get_Wide_Char_Immed
(Character'Val (ch
), File
);
532 procedure Get_Immediate
533 (Item
: out Wide_Character)
536 Get_Immediate
(Current_In
, Item
);
539 procedure Get_Immediate
541 Item
: out Wide_Character;
542 Available
: out Boolean)
547 FIO
.Check_Read_Status
(AP
(File
));
550 if File
.Before_Wide_Character
then
551 File
.Before_Wide_Character
:= False;
552 Item
:= File
.Saved_Wide_Character
;
554 elsif File
.Before_LM
then
555 File
.Before_LM
:= False;
556 File
.Before_LM_PM
:= False;
557 Item
:= Wide_Character'Val (LM
);
560 -- Shouldn't we use getc_immediate_nowait here, like Text_IO???
562 ch
:= Getc_Immed
(File
);
567 Item
:= Get_Wide_Char_Immed
(Character'Val (ch
), File
);
572 procedure Get_Immediate
573 (Item
: out Wide_Character;
574 Available
: out Boolean)
577 Get_Immediate
(Current_In
, Item
, Available
);
586 Item
: out Wide_String;
590 FIO
.Check_Read_Status
(AP
(File
));
591 Last
:= Item
'First - 1;
593 -- Immediate exit for null string, this is a case in which we do not
594 -- need to test for end of file and we do not skip a line mark under
595 -- any circumstances.
597 if Last
>= Item
'Last then
601 -- Here we have at least one character, if we are immediately before
602 -- a line mark, then we will just skip past it storing no characters.
604 if File
.Before_LM
then
605 File
.Before_LM
:= False;
606 File
.Before_LM_PM
:= False;
608 -- Otherwise we need to read some characters
611 -- If we are at the end of file now, it means we are trying to
612 -- skip a file terminator and we raise End_Error (RM A.10.7(20))
614 if Nextc
(File
) = EOF
then
618 -- Loop through characters in string
621 -- Exit the loop if read is terminated by encountering line mark
622 -- Note that the use of Skip_Line here ensures we properly deal
623 -- with setting the page and line numbers.
625 if End_Of_Line
(File
) then
630 -- Otherwise store the character, note that we know that ch is
631 -- something other than LM or EOF. It could possibly be a page
632 -- mark if there is a stray page mark in the middle of a line,
633 -- but this is not an official page mark in any case, since
634 -- official page marks can only follow a line mark. The whole
635 -- page business is pretty much nonsense anyway, so we do not
636 -- want to waste time trying to make sense out of non-standard
637 -- page marks in the file! This means that the behavior of
638 -- Get_Line is different from repeated Get of a character, but
639 -- that's too bad. We only promise that page numbers etc make
640 -- sense if the file is formatted in a standard manner.
642 -- Note: we do not adjust the column number because it is quicker
643 -- to adjust it once at the end of the operation than incrementing
644 -- it each time around the loop.
647 Get
(File
, Item
(Last
));
649 -- All done if the string is full, this is the case in which
650 -- we do not skip the following line mark. We need to adjust
651 -- the column number in this case.
653 if Last
= Item
'Last then
654 File
.Col
:= File
.Col
+ Count
(Item
'Length);
658 -- Exit from the loop if we are at the end of file. This happens
659 -- if we have a last line that is not terminated with a line mark.
660 -- In this case we consider that there is an implied line mark;
661 -- this is a non-standard file, but we will treat it nicely.
663 exit when Nextc
(File
) = EOF
;
669 (Item
: out Wide_String;
673 Get_Line
(Current_In
, Item
, Last
);
676 function Get_Line
(File
: File_Type
) return Wide_String is
677 Buffer
: Wide_String (1 .. 500);
680 function Get_Rest
(S
: Wide_String) return Wide_String;
681 -- This is a recursive function that reads the rest of the line and
682 -- returns it. S is the part read so far.
688 function Get_Rest
(S
: Wide_String) return Wide_String is
690 -- Each time we allocate a buffer the same size as what we have
691 -- read so far. This limits us to a logarithmic number of calls
692 -- to Get_Rest and also ensures only a linear use of stack space.
694 Buffer
: Wide_String (1 .. S
'Length);
698 Get_Line
(File
, Buffer
, Last
);
701 R
: constant Wide_String := S
& Buffer
(1 .. Last
);
703 if Last
< Buffer
'Last then
711 -- Start of processing for Get_Line
714 Get_Line
(File
, Buffer
, Last
);
716 if Last
< Buffer
'Last then
717 return Buffer
(1 .. Last
);
719 return Get_Rest
(Buffer
(1 .. Last
));
723 function Get_Line
return Wide_String is
725 return Get_Line
(Current_In
);
732 function Get_Wide_Char
734 File
: File_Type
) return Wide_Character
736 function In_Char
return Character;
737 -- Function used to obtain additional characters it the wide character
738 -- sequence is more than one character long.
740 function WC_In
is new Char_Sequence_To_Wide_Char
(In_Char
);
746 function In_Char
return Character is
747 ch
: constant Integer := Getc
(File
);
752 return Character'Val (ch
);
756 -- Start of processing for Get_Wide_Char
759 FIO
.Check_Read_Status
(AP
(File
));
760 return WC_In
(C
, File
.WC_Method
);
763 -------------------------
764 -- Get_Wide_Char_Immed --
765 -------------------------
767 function Get_Wide_Char_Immed
769 File
: File_Type
) return Wide_Character
771 function In_Char
return Character;
772 -- Function used to obtain additional characters it the wide character
773 -- sequence is more than one character long.
775 function WC_In
is new Char_Sequence_To_Wide_Char
(In_Char
);
781 function In_Char
return Character is
782 ch
: constant Integer := Getc_Immed
(File
);
787 return Character'Val (ch
);
791 -- Start of processing for Get_Wide_Char_Immed
794 FIO
.Check_Read_Status
(AP
(File
));
795 return WC_In
(C
, File
.WC_Method
);
796 end Get_Wide_Char_Immed
;
802 function Getc
(File
: File_Type
) return int
is
806 ch
:= fgetc
(File
.Stream
);
808 if ch
= EOF
and then ferror
(File
.Stream
) /= 0 then
819 function Getc_Immed
(File
: File_Type
) return int
is
823 procedure getc_immediate
824 (stream
: FILEs
; ch
: out int
; end_of_file
: out int
);
825 pragma Import
(C
, getc_immediate
, "getc_immediate");
828 FIO
.Check_Read_Status
(AP
(File
));
830 if File
.Before_LM
then
831 File
.Before_LM
:= False;
832 File
.Before_LM_PM
:= False;
836 getc_immediate
(File
.Stream
, ch
, end_of_file
);
838 if ferror
(File
.Stream
) /= 0 then
840 elsif end_of_file
/= 0 then
852 function Is_Open
(File
: File_Type
) return Boolean is
854 return FIO
.Is_Open
(AP
(File
));
861 -- Note: we assume that it is impossible in practice for the line
862 -- to exceed the value of Count'Last, i.e. no check is required for
863 -- overflow raising layout error.
865 function Line
(File
: File_Type
) return Positive_Count
is
867 FIO
.Check_File_Open
(AP
(File
));
871 function Line
return Positive_Count
is
873 return Line
(Current_Out
);
880 function Line_Length
(File
: File_Type
) return Count
is
882 FIO
.Check_Write_Status
(AP
(File
));
883 return File
.Line_Length
;
886 function Line_Length
return Count
is
888 return Line_Length
(Current_Out
);
897 Item
: out Wide_Character;
898 End_Of_Line
: out Boolean)
902 -- Start of processing for Look_Ahead
905 FIO
.Check_Read_Status
(AP
(File
));
907 -- If we are logically before a line mark, we can return immediately
909 if File
.Before_LM
then
911 Item
:= Wide_Character'Val (0);
913 -- If we are before a wide character, just return it (this can happen
914 -- if there are two calls to Look_Ahead in a row).
916 elsif File
.Before_Wide_Character
then
917 End_Of_Line
:= False;
918 Item
:= File
.Saved_Wide_Character
;
920 -- otherwise we must read a character from the input stream
927 or else (ch
= EOF
and then File
.Is_Regular_File
)
931 Item
:= Wide_Character'Val (0);
933 -- Case where character obtained does not represent the start of an
934 -- encoded sequence so it stands for itself and we can unget it with
937 elsif not Is_Start_Of_Encoding
938 (Character'Val (ch
), File
.WC_Method
)
940 End_Of_Line
:= False;
942 Item
:= Wide_Character'Val (ch
);
944 -- For the start of an encoding, we read the character using the
945 -- Get_Wide_Char routine. It will occupy more than one byte so we
946 -- can't put it back with ungetc. Instead we save it in the control
947 -- block, setting a flag that everyone interested in reading
948 -- characters must test before reading the stream.
951 Item
:= Get_Wide_Char
(Character'Val (ch
), File
);
952 End_Of_Line
:= False;
953 File
.Saved_Wide_Character
:= Item
;
954 File
.Before_Wide_Character
:= True;
960 (Item
: out Wide_Character;
961 End_Of_Line
: out Boolean)
964 Look_Ahead
(Current_In
, Item
, End_Of_Line
);
971 function Mode
(File
: File_Type
) return File_Mode
is
973 return To_TIO
(FIO
.Mode
(AP
(File
)));
980 function Name
(File
: File_Type
) return String is
982 return FIO
.Name
(AP
(File
));
991 Spacing
: Positive_Count
:= 1)
994 -- Raise Constraint_Error if out of range value. The reason for this
995 -- explicit test is that we don't want junk values around, even if
996 -- checks are off in the caller.
998 if not Spacing
'Valid then
999 raise Constraint_Error
;
1002 FIO
.Check_Write_Status
(AP
(File
));
1004 for K
in 1 .. Spacing
loop
1006 File
.Line
:= File
.Line
+ 1;
1008 if File
.Page_Length
/= 0
1009 and then File
.Line
> File
.Page_Length
1013 File
.Page
:= File
.Page
+ 1;
1020 procedure New_Line
(Spacing
: Positive_Count
:= 1) is
1022 New_Line
(Current_Out
, Spacing
);
1029 procedure New_Page
(File
: File_Type
) is
1031 FIO
.Check_Write_Status
(AP
(File
));
1033 if File
.Col
/= 1 or else File
.Line
= 1 then
1038 File
.Page
:= File
.Page
+ 1;
1043 procedure New_Page
is
1045 New_Page
(Current_Out
);
1052 function Nextc
(File
: File_Type
) return int
is
1056 ch
:= fgetc
(File
.Stream
);
1059 if ferror
(File
.Stream
) /= 0 then
1064 if ungetc
(ch
, File
.Stream
) = EOF
then
1077 (File
: in out File_Type
;
1080 Form
: String := "")
1082 Dummy_File_Control_Block
: Wide_Text_AFCB
;
1083 pragma Warnings
(Off
, Dummy_File_Control_Block
);
1084 -- Yes, we know this is never assigned a value, only the tag
1085 -- is used for dispatching purposes, so that's expected.
1088 FIO
.Open
(File_Ptr
=> AP
(File
),
1089 Dummy_FCB
=> Dummy_File_Control_Block
,
1090 Mode
=> To_FCB
(Mode
),
1105 -- Note: we assume that it is impossible in practice for the page
1106 -- to exceed the value of Count'Last, i.e. no check is required for
1107 -- overflow raising layout error.
1109 function Page
(File
: File_Type
) return Positive_Count
is
1111 FIO
.Check_File_Open
(AP
(File
));
1115 function Page
return Positive_Count
is
1117 return Page
(Current_Out
);
1124 function Page_Length
(File
: File_Type
) return Count
is
1126 FIO
.Check_Write_Status
(AP
(File
));
1127 return File
.Page_Length
;
1130 function Page_Length
return Count
is
1132 return Page_Length
(Current_Out
);
1141 Item
: Wide_Character)
1143 procedure Out_Char
(C
: Character);
1144 -- Procedure to output one character of a wide character sequence
1146 procedure WC_Out
is new Wide_Char_To_Char_Sequence
(Out_Char
);
1152 procedure Out_Char
(C
: Character) is
1154 Putc
(Character'Pos (C
), File
);
1157 -- Start of processing for Put
1160 FIO
.Check_Write_Status
(AP
(File
));
1161 WC_Out
(Item
, File
.WC_Method
);
1162 File
.Col
:= File
.Col
+ 1;
1165 procedure Put
(Item
: Wide_Character) is
1167 Put
(Current_Out
, Item
);
1179 for J
in Item
'Range loop
1180 Put
(File
, Item
(J
));
1184 procedure Put
(Item
: Wide_String) is
1186 Put
(Current_Out
, Item
);
1202 procedure Put_Line
(Item
: Wide_String) is
1204 Put
(Current_Out
, Item
);
1205 New_Line
(Current_Out
);
1212 procedure Putc
(ch
: int
; File
: File_Type
) is
1214 if fputc
(ch
, File
.Stream
) = EOF
then
1223 -- This is the primitive Stream Read routine, used when a Text_IO file
1224 -- is treated directly as a stream using Text_IO.Streams.Stream.
1227 (File
: in out Wide_Text_AFCB
;
1228 Item
: out Stream_Element_Array
;
1229 Last
: out Stream_Element_Offset
)
1232 pragma Unreferenced
(Discard_ch
);
1235 -- Need to deal with Before_Wide_Character ???
1237 if File
.Mode
/= FCB
.In_File
then
1241 -- Deal with case where our logical and physical position do not match
1242 -- because of being after an LM or LM-PM sequence when in fact we are
1243 -- logically positioned before it.
1245 if File
.Before_LM
then
1247 -- If we are before a PM, then it is possible for a stream read
1248 -- to leave us after the LM and before the PM, which is a bit
1249 -- odd. The easiest way to deal with this is to unget the PM,
1250 -- so we are indeed positioned between the characters. This way
1251 -- further stream read operations will work correctly, and the
1252 -- effect on text processing is a little weird, but what can
1253 -- be expected if stream and text input are mixed this way?
1255 if File
.Before_LM_PM
then
1256 Discard_ch
:= ungetc
(PM
, File
.Stream
);
1257 File
.Before_LM_PM
:= False;
1260 File
.Before_LM
:= False;
1262 Item
(Item
'First) := Stream_Element
(Character'Pos (ASCII
.LF
));
1264 if Item
'Length = 1 then
1270 Stream_Element_Offset
1271 (fread
(buffer
=> Item
'Address,
1272 index
=> size_t
(Item
'First + 1),
1274 count
=> Item
'Length - 1,
1275 stream
=> File
.Stream
));
1281 -- Now we do the read. Since this is a text file, it is normally in
1282 -- text mode, but stream data must be read in binary mode, so we
1283 -- temporarily set binary mode for the read, resetting it after.
1284 -- These calls have no effect in a system (like Unix) where there is
1285 -- no distinction between text and binary files.
1287 set_binary_mode
(fileno
(File
.Stream
));
1291 Stream_Element_Offset
1292 (fread
(Item
'Address, 1, Item
'Length, File
.Stream
)) - 1;
1294 if Last
< Item
'Last then
1295 if ferror
(File
.Stream
) /= 0 then
1300 set_text_mode
(fileno
(File
.Stream
));
1308 (File
: in out File_Type
;
1312 -- Don't allow change of mode for current file (RM A.10.2(5))
1314 if (File
= Current_In
or else
1315 File
= Current_Out
or else
1316 File
= Current_Error
)
1317 and then To_FCB
(Mode
) /= File
.Mode
1322 Terminate_Line
(File
);
1323 FIO
.Reset
(AP
(File
), To_FCB
(Mode
));
1327 File
.Line_Length
:= 0;
1328 File
.Page_Length
:= 0;
1329 File
.Before_LM
:= False;
1330 File
.Before_LM_PM
:= False;
1333 procedure Reset
(File
: in out File_Type
) is
1335 Terminate_Line
(File
);
1336 FIO
.Reset
(AP
(File
));
1340 File
.Line_Length
:= 0;
1341 File
.Page_Length
:= 0;
1342 File
.Before_LM
:= False;
1343 File
.Before_LM_PM
:= False;
1352 To
: Positive_Count
)
1357 -- Raise Constraint_Error if out of range value. The reason for this
1358 -- explicit test is that we don't want junk values around, even if
1359 -- checks are off in the caller.
1361 if not To
'Valid then
1362 raise Constraint_Error
;
1365 FIO
.Check_File_Open
(AP
(File
));
1367 if To
= File
.Col
then
1371 if Mode
(File
) >= Out_File
then
1372 if File
.Line_Length
/= 0 and then To
> File
.Line_Length
then
1376 if To
< File
.Col
then
1380 while File
.Col
< To
loop
1392 File
.Line
:= File
.Line
+ 1;
1395 elsif ch
= PM
and then File
.Is_Regular_File
then
1396 File
.Page
:= File
.Page
+ 1;
1400 elsif To
= File
.Col
then
1405 File
.Col
:= File
.Col
+ 1;
1411 procedure Set_Col
(To
: Positive_Count
) is
1413 Set_Col
(Current_Out
, To
);
1420 procedure Set_Error
(File
: File_Type
) is
1422 FIO
.Check_Write_Status
(AP
(File
));
1423 Current_Err
:= File
;
1430 procedure Set_Input
(File
: File_Type
) is
1432 FIO
.Check_Read_Status
(AP
(File
));
1442 To
: Positive_Count
)
1445 -- Raise Constraint_Error if out of range value. The reason for this
1446 -- explicit test is that we don't want junk values around, even if
1447 -- checks are off in the caller.
1449 if not To
'Valid then
1450 raise Constraint_Error
;
1453 FIO
.Check_File_Open
(AP
(File
));
1455 if To
= File
.Line
then
1459 if Mode
(File
) >= Out_File
then
1460 if File
.Page_Length
/= 0 and then To
> File
.Page_Length
then
1464 if To
< File
.Line
then
1468 while File
.Line
< To
loop
1473 while To
/= File
.Line
loop
1479 procedure Set_Line
(To
: Positive_Count
) is
1481 Set_Line
(Current_Out
, To
);
1484 ---------------------
1485 -- Set_Line_Length --
1486 ---------------------
1488 procedure Set_Line_Length
(File
: File_Type
; To
: Count
) is
1490 -- Raise Constraint_Error if out of range value. The reason for this
1491 -- explicit test is that we don't want junk values around, even if
1492 -- checks are off in the caller.
1494 if not To
'Valid then
1495 raise Constraint_Error
;
1498 FIO
.Check_Write_Status
(AP
(File
));
1499 File
.Line_Length
:= To
;
1500 end Set_Line_Length
;
1502 procedure Set_Line_Length
(To
: Count
) is
1504 Set_Line_Length
(Current_Out
, To
);
1505 end Set_Line_Length
;
1511 procedure Set_Output
(File
: File_Type
) is
1513 FIO
.Check_Write_Status
(AP
(File
));
1514 Current_Out
:= File
;
1517 ---------------------
1518 -- Set_Page_Length --
1519 ---------------------
1521 procedure Set_Page_Length
(File
: File_Type
; To
: Count
) is
1523 -- Raise Constraint_Error if out of range value. The reason for this
1524 -- explicit test is that we don't want junk values around, even if
1525 -- checks are off in the caller.
1527 if not To
'Valid then
1528 raise Constraint_Error
;
1531 FIO
.Check_Write_Status
(AP
(File
));
1532 File
.Page_Length
:= To
;
1533 end Set_Page_Length
;
1535 procedure Set_Page_Length
(To
: Count
) is
1537 Set_Page_Length
(Current_Out
, To
);
1538 end Set_Page_Length
;
1544 procedure Set_WCEM
(File
: in out File_Type
) is
1549 File
.WC_Method
:= WCEM_Brackets
;
1550 FIO
.Form_Parameter
(File
.Form
.all, "wcem", Start
, Stop
);
1553 File
.WC_Method
:= WCEM_Brackets
;
1555 elsif Start
/= 0 then
1556 if Stop
= Start
then
1557 for J
in WC_Encoding_Letters
'Range loop
1558 if File
.Form
(Start
) = WC_Encoding_Letters
(J
) then
1559 File
.WC_Method
:= J
;
1566 raise Use_Error
with "invalid WCEM form parameter";
1576 Spacing
: Positive_Count
:= 1)
1581 -- Raise Constraint_Error if out of range value. The reason for this
1582 -- explicit test is that we don't want junk values around, even if
1583 -- checks are off in the caller.
1585 if not Spacing
'Valid then
1586 raise Constraint_Error
;
1589 FIO
.Check_Read_Status
(AP
(File
));
1591 for L
in 1 .. Spacing
loop
1592 if File
.Before_LM
then
1593 File
.Before_LM
:= False;
1594 File
.Before_LM_PM
:= False;
1599 -- If at end of file now, then immediately raise End_Error. Note
1600 -- that we can never be positioned between a line mark and a page
1601 -- mark, so if we are at the end of file, we cannot logically be
1602 -- before the implicit page mark that is at the end of the file.
1604 -- For the same reason, we do not need an explicit check for a
1605 -- page mark. If there is a FF in the middle of a line, the file
1606 -- is not in canonical format and we do not care about the page
1607 -- numbers for files other than ones in canonical format.
1613 -- If not at end of file, then loop till we get to an LM or EOF.
1614 -- The latter case happens only in non-canonical files where the
1615 -- last line is not terminated by LM, but we don't want to blow
1616 -- up for such files, so we assume an implicit LM in this case.
1619 exit when ch
= LM
or ch
= EOF
;
1624 -- We have got past a line mark, now, for a regular file only,
1625 -- see if a page mark immediately follows this line mark and
1626 -- if so, skip past the page mark as well. We do not do this
1627 -- for non-regular files, since it would cause an undesirable
1628 -- wait for an additional character.
1631 File
.Line
:= File
.Line
+ 1;
1633 if File
.Before_LM_PM
then
1634 File
.Page
:= File
.Page
+ 1;
1636 File
.Before_LM_PM
:= False;
1638 elsif File
.Is_Regular_File
then
1641 -- Page mark can be explicit, or implied at the end of the file
1643 if (ch
= PM
or else ch
= EOF
)
1644 and then File
.Is_Regular_File
1646 File
.Page
:= File
.Page
+ 1;
1654 File
.Before_Wide_Character
:= False;
1657 procedure Skip_Line
(Spacing
: Positive_Count
:= 1) is
1659 Skip_Line
(Current_In
, Spacing
);
1666 procedure Skip_Page
(File
: File_Type
) is
1670 FIO
.Check_Read_Status
(AP
(File
));
1672 -- If at page mark already, just skip it
1674 if File
.Before_LM_PM
then
1675 File
.Before_LM
:= False;
1676 File
.Before_LM_PM
:= False;
1677 File
.Page
:= File
.Page
+ 1;
1683 -- This is a bit tricky, if we are logically before an LM then
1684 -- it is not an error if we are at an end of file now, since we
1685 -- are not really at it.
1687 if File
.Before_LM
then
1688 File
.Before_LM
:= False;
1689 File
.Before_LM_PM
:= False;
1692 -- Otherwise we do raise End_Error if we are at the end of file now
1702 -- Now we can just rumble along to the next page mark, or to the
1703 -- end of file, if that comes first. The latter case happens when
1704 -- the page mark is implied at the end of file.
1708 or else (ch
= PM
and then File
.Is_Regular_File
);
1712 File
.Page
:= File
.Page
+ 1;
1715 File
.Before_Wide_Character
:= False;
1718 procedure Skip_Page
is
1720 Skip_Page
(Current_In
);
1723 --------------------
1724 -- Standard_Error --
1725 --------------------
1727 function Standard_Error
return File_Type
is
1729 return Standard_Err
;
1732 function Standard_Error
return File_Access
is
1734 return Standard_Err
'Access;
1737 --------------------
1738 -- Standard_Input --
1739 --------------------
1741 function Standard_Input
return File_Type
is
1746 function Standard_Input
return File_Access
is
1748 return Standard_In
'Access;
1751 ---------------------
1752 -- Standard_Output --
1753 ---------------------
1755 function Standard_Output
return File_Type
is
1757 return Standard_Out
;
1758 end Standard_Output
;
1760 function Standard_Output
return File_Access
is
1762 return Standard_Out
'Access;
1763 end Standard_Output
;
1765 --------------------
1766 -- Terminate_Line --
1767 --------------------
1769 procedure Terminate_Line
(File
: File_Type
) is
1771 FIO
.Check_File_Open
(AP
(File
));
1773 -- For file other than In_File, test for needing to terminate last line
1775 if Mode
(File
) /= In_File
then
1777 -- If not at start of line definition need new line
1779 if File
.Col
/= 1 then
1782 -- For files other than standard error and standard output, we
1783 -- make sure that an empty file has a single line feed, so that
1784 -- it is properly formatted. We avoid this for the standard files
1785 -- because it is too much of a nuisance to have these odd line
1786 -- feeds when nothing has been written to the file.
1788 elsif (File
/= Standard_Err
and then File
/= Standard_Out
)
1789 and then (File
.Line
= 1 and then File
.Page
= 1)
1800 procedure Ungetc
(ch
: int
; File
: File_Type
) is
1803 if ungetc
(ch
, File
.Stream
) = EOF
then
1813 -- This is the primitive Stream Write routine, used when a Text_IO file
1814 -- is treated directly as a stream using Text_IO.Streams.Stream.
1817 (File
: in out Wide_Text_AFCB
;
1818 Item
: Stream_Element_Array
)
1820 pragma Warnings
(Off
, File
);
1821 -- Because in this implementation we don't need IN OUT, we only read
1823 Siz
: constant size_t
:= Item
'Length;
1826 if File
.Mode
= FCB
.In_File
then
1830 -- Now we do the write. Since this is a text file, it is normally in
1831 -- text mode, but stream data must be written in binary mode, so we
1832 -- temporarily set binary mode for the write, resetting it after.
1833 -- These calls have no effect in a system (like Unix) where there is
1834 -- no distinction between text and binary files.
1836 set_binary_mode
(fileno
(File
.Stream
));
1838 if fwrite
(Item
'Address, 1, Siz
, File
.Stream
) /= Siz
then
1842 set_text_mode
(fileno
(File
.Stream
));
1845 -- Use "preallocated" strings to avoid calling "new" during the
1846 -- elaboration of the run time. This is needed in the tasking case to
1847 -- avoid calling Task_Lock too early. A filename is expected to end with
1848 -- a null character in the runtime, here the null characters are added
1849 -- just to have a correct filename length.
1851 Err_Name
: aliased String := "*stderr" & ASCII
.NUL
;
1852 In_Name
: aliased String := "*stdin" & ASCII
.NUL
;
1853 Out_Name
: aliased String := "*stdout" & ASCII
.NUL
;
1856 -------------------------------
1857 -- Initialize Standard Files --
1858 -------------------------------
1860 for J
in WC_Encoding_Method
loop
1861 if WC_Encoding
= WC_Encoding_Letters
(J
) then
1866 -- Note: the names in these files are bogus, and probably it would be
1867 -- better for these files to have no names, but the ACVC test insist!
1868 -- We use names that are bound to fail in open etc.
1870 Standard_Err
.Stream
:= stderr
;
1871 Standard_Err
.Name
:= Err_Name
'Access;
1872 Standard_Err
.Form
:= Null_Str
'Unrestricted_Access;
1873 Standard_Err
.Mode
:= FCB
.Out_File
;
1874 Standard_Err
.Is_Regular_File
:= is_regular_file
(fileno
(stderr
)) /= 0;
1875 Standard_Err
.Is_Temporary_File
:= False;
1876 Standard_Err
.Is_System_File
:= True;
1877 Standard_Err
.Is_Text_File
:= True;
1878 Standard_Err
.Access_Method
:= 'T';
1879 Standard_Err
.Self
:= Standard_Err
;
1880 Standard_Err
.WC_Method
:= Default_WCEM
;
1882 Standard_In
.Stream
:= stdin
;
1883 Standard_In
.Name
:= In_Name
'Access;
1884 Standard_In
.Form
:= Null_Str
'Unrestricted_Access;
1885 Standard_In
.Mode
:= FCB
.In_File
;
1886 Standard_In
.Is_Regular_File
:= is_regular_file
(fileno
(stdin
)) /= 0;
1887 Standard_In
.Is_Temporary_File
:= False;
1888 Standard_In
.Is_System_File
:= True;
1889 Standard_In
.Is_Text_File
:= True;
1890 Standard_In
.Access_Method
:= 'T';
1891 Standard_In
.Self
:= Standard_In
;
1892 Standard_In
.WC_Method
:= Default_WCEM
;
1894 Standard_Out
.Stream
:= stdout
;
1895 Standard_Out
.Name
:= Out_Name
'Access;
1896 Standard_Out
.Form
:= Null_Str
'Unrestricted_Access;
1897 Standard_Out
.Mode
:= FCB
.Out_File
;
1898 Standard_Out
.Is_Regular_File
:= is_regular_file
(fileno
(stdout
)) /= 0;
1899 Standard_Out
.Is_Temporary_File
:= False;
1900 Standard_Out
.Is_System_File
:= True;
1901 Standard_Out
.Is_Text_File
:= True;
1902 Standard_Out
.Access_Method
:= 'T';
1903 Standard_Out
.Self
:= Standard_Out
;
1904 Standard_Out
.WC_Method
:= Default_WCEM
;
1906 FIO
.Chain_File
(AP
(Standard_In
));
1907 FIO
.Chain_File
(AP
(Standard_Out
));
1908 FIO
.Chain_File
(AP
(Standard_Err
));
1910 FIO
.Make_Unbuffered
(AP
(Standard_Out
));
1911 FIO
.Make_Unbuffered
(AP
(Standard_Err
));
1913 end Ada
.Wide_Text_IO
;