Skip to content

IO#

Storage IO#

The generic package Storage_IO provides for reading from and writing to an in-memory buffer. This generic package supports the construction of user-defined input-output packages.

with Ada.IO_Exceptions;
with System.Storage_Elements;

generic
   type Element_Type is private;
package Ada.Storage_IO
   with Preelaborate, Global => in out synchronized is

   Buffer_Size: constant System.Storage_Elements.Storage_Count := <implementation-defined>;

   subtype Buffer_Type is System.Storage_Elements.Storage_Array(1 .. Buffer_Size);

   -- Input and output operations
   procedure Read (Buffer:     Buffer_Type; Item: out Element_Type);
   procedure Write(Buffer: out Buffer_Type; Item:     Element_Type);

   Data_Error: exception renames IO_Exceptions.Data_Error;
end Ada.Storage_IO;

Direct IO#

with Ada.IO_Exceptions;

generic
   type Element_Type is private;
package Ada.Direct_IO
   with Global => in out synchronized is

   type File_Type is limited private;

   type File_Mode is (In_File, Inout_File, Out_File);
   type Count     is range 0 .. <implementation-defined>;
   subtype Positive_Count is Count range 1 .. Count'Last;

   -- File management
   procedure Create(File: in out File_Type;
                    Mode: File_Mode := Inout_File;
                    Name: String    := "";
                    Form: String    := "");
   procedure Open(File: in out File_Type;
                  Mode: File_Mode;
                  Name: String;
                  Form: String := "");
   procedure Close (File: in out File_Type);
   procedure Delete(File: in out File_Type);
   procedure Reset (File: in out File_Type; Mode: File_Mode);
   procedure Reset (File: in out File_Type);

   function Mode(File: File_Type) return File_Mode;
   function Name(File: File_Type) return String;
   function Form(File: File_Type) return String;

   function Is_Open(File: File_Type) return Boolean;

   procedure Flush(File: File_Type)
      with Global => overriding in out File;

   -- Input and output operations
   procedure Read(File: File_Type; Item: out Element_Type; From: Positive_Count)
      with Global => overriding in out File;
   procedure Read(File: File_Type; Item: out Element_Type)
      with Global => overriding in out File;
   procedure Write(File: File_Type; Item: Element_Type; To: Positive_Count)
      with Global => overriding in out File;
   procedure Write(File: File_Type; Item: Element_Type)
      with Global => overriding in out File;

   procedure Set_Index(File: File_Type; To: Positive_Count)
      with Global => overriding in out File;
   function Index(File: File_Type) return Positive_Count;
   function Size (File: File_Type) return Count;

   function End_Of_File(File: File_Type) return Boolean;

   Status_Error: exception renames IO_Exceptions.Status_Error;
   Mode_Error  : exception renames IO_Exceptions.Mode_Error;
   Name_Error  : exception renames IO_Exceptions.Name_Error;
   Use_Error   : exception renames IO_Exceptions.Use_Error;
   Device_Error: exception renames IO_Exceptions.Device_Error;
   End_Error   : exception renames IO_Exceptions.End_Error;
   Data_Error  : exception renames IO_Exceptions.Data_Error;

   package Wide_File_Names is
      procedure Create(File: in out File_Type;
                       Mode: File_Mode   := Inout_File;
                       Name: Wide_String := "";
                       Form: Wide_String := "");
      procedure Open(File: in out File_Type;
                     Mode: File_Mode;
                     Name: Wide_String;
                     Form: Wide_String := "");
      function Name(File: File_Type) return Wide_String;
      function Form(File: File_Type) return Wide_String;
   end Wide_File_Names;

   package Wide_Wide_File_Names is
      procedure Create(File: in out File_Type;
                       Mode: File_Mode        := Inout_File;
                       Name: Wide_Wide_String := "";
                       Form: Wide_Wide_String := "");
      procedure Open(File: in out File_Type;
                     Mode: File_Mode;
                     Name: Wide_Wide_String;
                     Form: Wide_Wide_String := "");
      function Name(File: File_Type) return Wide_Wide_String;
      function Form(File: File_Type) return Wide_Wide_String;
   end Wide_Wide_File_Names;
end Ada.Direct_IO;

Sequential IO#

with Ada.IO_Exceptions;

generic
   type Element_Type(<>) is private;
package Ada.Sequential_IO
   with Global => in out synchronized is

   type File_Type is limited private;
   type File_Mode is (In_File, Out_File, Append_File);

   -- File management
   procedure Create(File: in out File_Type;
                    Mode: File_Mode := Out_File;
                    Name: String    := "";
                    Form: String    := "");
   procedure Open(File: in out File_Type;
                  Mode: File_Mode;
                  Name: String;
                  Form: String := "");
   procedure Close (File: in out File_Type);
   procedure Delete(File: in out File_Type);
   procedure Reset (File: in out File_Type; Mode: File_Mode);
   procedure Reset (File: in out File_Type);

   function Mode(File: File_Type) return File_Mode;
   function Name(File: File_Type) return String;
   function Form(File: File_Type) return String;

   function Is_Open(File: File_Type) return Boolean;

   procedure Flush(File: File_Type)
      with Global => overriding in out File;

   -- Input and output operations
   procedure Read(File: File_Type; Item: out Element_Type)
       with Global => overriding in out File;
   procedure Write(File: File_Type; Item: Element_Type)
       with Global => overriding in out File;

   function End_Of_File(File: File_Type) return Boolean;

   Status_Error: exception renames IO_Exceptions.Status_Error;
   Mode_Error  : exception renames IO_Exceptions.Mode_Error;
   Name_Error  : exception renames IO_Exceptions.Name_Error;
   Use_Error   : exception renames IO_Exceptions.Use_Error;
   Device_Error: exception renames IO_Exceptions.Device_Error;
   End_Error   : exception renames IO_Exceptions.End_Error;
   Data_Error  : exception renames IO_Exceptions.Data_Error;

   package Wide_File_Names is
      procedure Create(File: in out File_Type;
                       Mode: File_Mode   := Out_File;
                       Name: Wide_String := "";
                       Form: Wide_String := "");
      procedure Open(File: in out File_Type;
                     Mode: File_Mode;
                     Name: Wide_String;
                     Form: Wide_String := "");
      function Name(File: File_Type) return Wide_String;
      function Form(File: File_Type) return Wide_String;
   end Wide_File_Names;

   package Wide_Wide_File_Names is
      procedure Create(File: in out File_Type;
                       Mode: File_Mode        := Out_File;
                       Name: Wide_Wide_String := "";
                       Form: Wide_Wide_String := "");
      procedure Open(File: in out File_Type;
                     Mode: File_Mode;
                     Name: Wide_Wide_String;
                     Form: Wide_Wide_String := "");
      function Name(File: File_Type) return Wide_Wide_String;
      function Form(File: File_Type) return Wide_Wide_String;
   end Wide_Wide_File_Names;
end Ada.Sequential_IO;

Text IO#

with Ada.IO_Exceptions;

package Ada.Text_IO
   with Global => in out synchronized is

   type File_Type is limited private;
   type File_Mode is (In_File, Out_File, Append_File);

   type Count is range 0 .. <implementation-defined>;
   subtype Positive_Count is Count range 1 .. Count'Last;
   Unbounded: constant Count := 0; -- line and page length

   subtype Field       is Integer range 0 .. <implementation-defined>;
   subtype Number_Base is Integer range 2 .. 16;
   type Type_Set is (Lower_Case, Upper_Case);

   -- File Management
   procedure Create(File: in out File_Type;
                    Mode: File_Mode := Out_File;
                    Name: String    := "";
                    Form: String    := "");
   procedure Open(File: in out File_Type;
                  Mode: File_Mode;
                  Name: String;
                  Form: String := "");
   procedure Close (File: in out File_Type);
   procedure Delete(File: in out File_Type);
   procedure Reset (File: in out File_Type; Mode: File_Mode);
   procedure Reset (File: in out File_Type);

   function Mode(File: File_Type) return File_Mode;
   function Name(File: File_Type) return String;
   function Form(File: File_Type) return String;

   function Is_Open(File: File_Type) return Boolean;

   -- Control of default input and output files
   procedure Set_Input (File: File_Type);
   procedure Set_Output(File: File_Type);
   procedure Set_Error (File: File_Type);

   function Standard_Input  return File_Type;
   function Standard_Output return File_Type;
   function Standard_Error  return File_Type;

   function Current_Input  return File_Type;
   function Current_Output return File_Type;
   function Current_Error  return File_Type;

   type File_Access is access constant File_Type;

   function Standard_Input  return File_Access;
   function Standard_Output return File_Access;
   function Standard_Error  return File_Access;

   function Current_Input  return File_Access;
   function Current_Output return File_Access;
   function Current_Error  return File_Access;

   -- Buffer control
   procedure Flush(File: in File_Type)
      with Global => overriding in out File;
   procedure Flush
      with Global => in out all;

   -- Specification of line and page lengths
   procedure Set_Line_Length(File: File_Type; To: Count) with Global => overriding in out File;
   procedure Set_Page_Length(File: File_Type; To: Count) with Global => overriding in out File;
   procedure Set_Line_Length(To: Count) with Global => in out all;
   procedure Set_Page_Length(To: Count) with Global => in out all;

   function Line_Length(File: File_Type) return Count;
   function Page_Length(File: File_Type) return Count;
   function Line_Length return Count with Global => in all;
   function Page_Length return Count with Global => in all;

   -- Column, Line, and Page Control
   procedure New_Line(File: File_Type; Spacing: Positive_Count := 1)
      with Global => overriding in out File;
   procedure New_Line(Spacing: Positive_Count := 1)
      with Global => in out all;
   procedure Skip_Line(File: File_Type; Spacing: Positive_Count := 1)
      with Global => overriding in out File;
   procedure Skip_Line(Spacing: Positive_Count := 1)
      with Global => in out all;

   function End_Of_Line(File: File_Type) return Boolean;
   function End_Of_Line return Boolean;

   procedure New_Page (File: File_Type) with Global => overriding in out File;
   procedure Skip_Page(File: File_Type) with Global => overriding in out File;
   procedure New_Page  with Global => in out all;
   procedure Skip_Page with Global => in out all;

   function End_Of_Page(File: File_Type) return Boolean;
   function End_Of_File(File: File_Type) return Boolean;
   function End_Of_Page return Boolean with Global => in all;
   function End_Of_File return Boolean with Global => in all;

   procedure Set_Col (File: File_Type; To: Positive_Count) with Global => overriding in out File;
   procedure Set_Line(File: File_Type; To: Positive_Count) with Global => overriding in out File;
   procedure Set_Col (To: Positive_Count) with Global => in out all;
   procedure Set_Line(To: Positive_Count) with Global => in out all;

   function Col (File: File_Type) return Positive_Count;
   function Line(File: File_Type) return Positive_Count;
   function Page(File: File_Type) return Positive_Count;
   function Col  return Positive_Count with Global => in all;
   function Line return Positive_Count with Global => in all;
   function Page return Positive_Count with Global => in all;

   -- Character Input-Output
   procedure Get(File: File_Type; Item: out Character) with Global => overriding in out File;
   procedure Put(File: File_Type; Item: Character)     with Global => overriding in out File;
   procedure Get(Item: out Character) with Global => in out all;
   procedure Put(Item: Character)     with Global => in out all;
   procedure Look_Ahead(File: File_Type; Item: out Character; End_Of_Line: out Boolean)
      with Global => overriding in out File;
   procedure Look_Ahead(Item: out Character; End_Of_Line: out Boolean)
      with Global => in out all;
   procedure Get_Immediate(File: File_Type; Item: out Character)
      with Global => overriding in out File;
   procedure Get_Immediate(Item: out Character)
      with Global => in out all;
   procedure Get_Immediate(File: File_Type; Item: out Character; Available: out Boolean)
      with Global => overriding in out File;
   procedure Get_Immediate(Item: out Character; Available: out Boolean)
      with Global => in out all;

   -- String Input-Output
   procedure Get     (File: File_Type; Item: out String) with Global => overriding in out File;
   procedure Put     (File: File_Type; Item:     String) with Global => overriding in out File;
   procedure Put_Line(File: File_Type; Item:     String) with Global => overriding in out File;
   procedure Get     (Item: out String)  with Global => in out all;
   procedure Put     (Item:     String)  with Global => in out all;
   procedure Put_Line(Item:     String)  with Global => in out all;
   procedure Get_Line(File: File_Type; Item: out String; Last: out Natural)
      with Global => overriding in out File;
   procedure Get_Line(Item: out String; Last: out Natural)
      with Global => in out all;

   function Get_Line(File: File_Type) return String with Global => overriding in out File;
   function Get_Line                  return String with Global => in out all;

   -- Generic packages for Input-Output of Integer Types
   generic
      type Num is range <>;
   package Integer_IO is
      Default_Width: Field       := Num'Width;
      Default_Base : Number_Base := 10;

      procedure Get(File: File_Type; Item: out Num; Width: Field := 0)
         with Global => overriding in out File;
      procedure Get(Item: out Num; Width: Field := 0)
         with Global => in out all;
      procedure Put(File : File_Type;
                    Item : Num;
                    Width: Field       := Default_Width;
                    Base : Number_Base := Default_Base)
         with Global => overriding in out File;
      procedure Put(Item : Num;
                    Width: Field       := Default_Width;
                    Base : Number_Base := Default_Base)
         with Global => in out all;
      procedure Get(From: String; Item: out Num; Last: out Positive)
         with Nonblocking;
      procedure Put(To: out String; Item: Num; Base: Number_Base := Default_Base)
         with Nonblocking;
   end Integer_IO;

   generic
      type Num is mod <>;
   package Modular_IO is
      Default_Width: Field       := Num'Width;
      Default_Base : Number_Base := 10;

      procedure Get(File: File_Type; Item: out Num; Width: Field := 0)
         with Global => overriding in out File;
      procedure Get(Item: out Num; Width: Field := 0)
         with Global => in out all;

      procedure Put(File : File_Type;
                    Item : Num;
                    Width: Field       := Default_Width;
                    Base : Number_Base := Default_Base)
         with Global => overriding in out File;
      procedure Put(Item : Num;
                    Width: Field       := Default_Width;
                    Base : Number_Base := Default_Base)
         with Global => in out all;
      procedure Get(From: String; Item: out Num; Last: out Positive)
         with Nonblocking;
      procedure Put(To: out String; Item: Num; Base: Number_Base := Default_Base)
         with Nonblocking;
   end Modular_IO;

   -- Generic packages for Input-Output of Real Types
   generic
      type Num is digits <>;
   package Float_IO is
      Default_Fore: Field := 2;
      Default_Aft : Field := Num'Digits-1;
      Default_Exp : Field := 3;

      procedure Get(File: File_Type; Item: out Num; Width: Field := 0)
         with Global => overriding in out File;
      procedure Get(Item: out Num; Width: Field := 0)
         with Global => in out all;
      procedure Put(File: File_Type;
                    Item: Num;
                    Fore: Field := Default_Fore;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Global => overriding in out File;
      procedure Put(Item: Num;
                    Fore: Field := Default_Fore;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Global => in out all;
      procedure Get(From: String; Item: out Num; Last: out Positive)
         with Nonblocking;
      procedure Put(To  : out String;
                    Item: Num;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Nonblocking;
   end Float_IO;

   generic
      type Num is delta <>;
   package Fixed_IO is
      Default_Fore: Field := Num'Fore;
      Default_Aft : Field := Num'Aft;
      Default_Exp : Field := 0;

      procedure Get(File: File_Type; Item: out Num; Width: Field := 0)
         with Global => overriding in out File;
      procedure Get(Item: out Num; Width: Field := 0)
         with Global => in out all;

      procedure Put(File: File_Type;
                    Item: Num;
                    Fore: Field := Default_Fore;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Global => overriding in out File;
      procedure Put(Item: Num;
                    Fore: Field := Default_Fore;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Global => in out all;
      procedure Get(From: String; Item: out Num; Last: out Positive)
         with Nonblocking;
      procedure Put(To  : out String;
                    Item: Num;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Nonblocking;
   end Fixed_IO;

   generic
      type Num is delta <> digits <>;
   package Decimal_IO is
      Default_Fore: Field := Num'Fore;
      Default_Aft : Field := Num'Aft;
      Default_Exp : Field := 0;

      procedure Get(File : File_Type; Item: out Num; Width: Field := 0)
         with Global => overriding in out File;
      procedure Get(Item: out Num; Width: Field := 0)
         with Global => in out all;
      procedure Put(File: File_Type;
                    Item: Num;
                    Fore: Field := Default_Fore;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Global => overriding in out File;
      procedure Put(Item: Num;
                    Fore: Field := Default_Fore;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Global => in out all;
      procedure Get(From: String; Item: out Num; Last: out Positive)
         with Nonblocking;
      procedure Put(To  : out String;
                    Item: Num;
                    Aft : Field := Default_Aft;
                    Exp : Field := Default_Exp)
         with Nonblocking;
   end Decimal_IO;

   -- Generic package for Input-Output of Enumeration Types
   generic
      type Enum is (<>);
   package Enumeration_IO is
      Default_Width  : Field    := 0;
      Default_Setting: Type_Set := Upper_Case;

      procedure Get(File: File_Type; Item: out Enum)
         with Global => overriding in out File;
      procedure Get(Item: out Enum)
         with Global => in out all;
      procedure Put(File : File_Type;
                    Item : Enum;
                    Width: Field    := Default_Width;
                    Set  : Type_Set := Default_Setting)
         with Global => overriding in out File;
      procedure Put(Item : Enum;
                    Width: Field    := Default_Width;
                    Set  : Type_Set := Default_Setting)
         with Global => in out all;

      procedure Get(From: String; Item: out Enum; Last: out Positive)
         with Nonblocking;
      procedure Put(To: out String; Item: Enum; Set: Type_Set := Default_Setting)
         with Nonblocking;
   end Enumeration_IO;

   -- Exceptions
   Status_Error: exception renames IO_Exceptions.Status_Error;
   Mode_Error  : exception renames IO_Exceptions.Mode_Error;
   Name_Error  : exception renames IO_Exceptions.Name_Error;
   Use_Error   : exception renames IO_Exceptions.Use_Error;
   Device_Error: exception renames IO_Exceptions.Device_Error;
   End_Error   : exception renames IO_Exceptions.End_Error;
   Data_Error  : exception renames IO_Exceptions.Data_Error;
   Layout_Error: exception renames IO_Exceptions.Layout_Error;

   package Wide_File_Names is
         procedure Create(File: in out File_Type;
                          Mode: File_Mode   := Out_File;
                          Name: Wide_String := "";
                          Form: Wide_String := "");
         procedure Open(File: in out File_Type;
                        Mode: File_Mode;
                        Name: Wide_String;
                        Form: Wide_String := "");

         function Name(File: File_Type) return Wide_String;
         function Form(File: File_Type) return Wide_String;
   end Wide_File_Names;

   package Wide_Wide_File_Names is
         procedure Create(File: in out File_Type;
                          Mode: File_Mode        := Out_File;
                          Name: Wide_Wide_String := "";
                          Form: Wide_Wide_String := "");
         procedure Open(File: in out File_Type;
                        Mode: File_Mode;
                        Name: Wide_Wide_String;
                        Form: Wide_Wide_String := "");
         function Name(File: File_Type) return Wide_Wide_String;
         function Form(File: File_Type) return Wide_Wide_String;
   end Wide_Wide_File_Names;
end Ada.Text_IO;
Examples of use of an instantiation of Text_IO.Float_IO
package Real_IO is new Float_IO(Real); use Real_IO;

-- default format used at instantiation, Default_Exp = 3
X: Real := -123.4567; -- digits

Put(X);                 -- default format "–​1.2345670E+02"
Put(X, Fore => 5, Aft => 3, Exp => 2); -- "bbb–​1.235E+2"
Put(X, 5, 3, 0);                       -- "b–​123.457"

Wide Text IO and Wide Wide Text IO#

The packages Wide_Text_IO and Wide_Wide_Text_IO provide facilities for input and output in human-readable form. Each file is read or written sequentially, as a sequence of wide characters (or wide wide characters) grouped into lines, and as a sequence of lines grouped into pages.

The specification of package Wide_Text_IO is the same as that for Text_IO, except that in each Get, Look_Ahead, Get_Immediate, Get_Line, Put, and Put_Line subprogram, any occurrence of Character is replaced by Wide_Character, and any occurrence of String is replaced by Wide_String. Nongeneric equivalents of Wide_Text_IO.Integer_IO and Wide_Text_IO.Float_IO are provided (as for Text_IO) for each predefined numeric type, with names such as Ada.Integer_Wide_Text_IO, Ada.Long_Integer_Wide_Text_IO, Ada.Float_Wide_Text_IO, Ada.Long_Float_Wide_Text_IO.

The same paragraph applies similarly for:

  • Wide_Text_IO is the same as that for Text_IO
  • Wide_Wide_Text_IO is the same as that for Text_IO
  • Wide_Text_IO.Wide_Bounded_IO is the same as that for Text_IO.Bounded_IO
  • Wide_Text_IO.Wide_Unbounded_IO is the same as that for Text_IO.Unbounded_IO

Unbounded IO#

The package Text_IO.Unbounded_IO provides input-output in human-readable form for Unbounded_Strings.

with Ada.Strings.Unbounded;
package Ada.Text_IO.Unbounded_IO
   with Global => in out synchronized is

   procedure Put     (File: File_Type; Item:     Strings.Unbounded.Unbounded_String);
   procedure Put_Line(File: File_Type; Item:     Strings.Unbounded.Unbounded_String);
   procedure Get_Line(File: File_Type; Item: out Strings.Unbounded.Unbounded_String);
   function  Get_Line(File: File_Type) return Strings.Unbounded.Unbounded_String;

   procedure Put     (Item:     Strings.Unbounded.Unbounded_String);
   procedure Put_Line(Item:     Strings.Unbounded.Unbounded_String);
   procedure Get_Line(Item: out Strings.Unbounded.Unbounded_String);
   function  Get_Line return Strings.Unbounded.Unbounded_String;
end Ada.Text_IO.Unbounded_IO;

Text Streams#

The package Text_IO.Text_Streams provides a function for treating a text file as a stream.

with Ada.Streams;

package Ada.Text_IO.Text_Streams
   with Global => in out synchronized is

   type Stream_Access is access all Streams.Root_Stream_Type'Class;

   function Stream(File: File_Type) return Stream_Access;
end Ada.Text_IO.Text_Streams;

Wide Text Streams#

The package Wide_Text_IO.Text_Streams provides a function for treating a wide text file as a stream.

with Ada.Streams;

package Ada.Wide_Text_IO.Text_Streams
   with Global => in out synchronized is

   type Stream_Access is access all Streams.Root_Stream_Type'Class;

   function Stream(File: File_Type) return Stream_Access;
end Ada.Wide_Text_IO.Text_Streams;

Wide Wide Text Streams#

The package Wide_Wide_Text_IO.Text_Streams provides a function for treating a wide wide text file as a stream.

with Ada.Streams;

package Ada.Wide_Wide_Text_IO.Text_Streams
   with Global => in out synchronized is

   type Stream_Access is access all Streams.Root_Stream_Type'Class;

   function Stream(File: File_Type) return Stream_Access;
end Ada.Wide_Wide_Text_IO.Text_Streams;

Text Editing#

The package Text_IO.Editing provides a private type Picture with associated operations, and a generic package Decimal_Output. An object of type Picture is composed from a well-formed picture String (see F.3.1) and a Boolean item indicating whether a zero numeric value will result in an edited output string of all space characters. The package Decimal_Output contains edited output subprograms implementing the effects defined in F.3.2.

package Ada.Text_IO.Editing
   with Nonblocking, Global => in out synchronized is

   type Picture is private;

   function Valid     (Pic_String: String; Blank_When_Zero: Boolean := False) return Boolean;
   function To_Picture(Pic_String: String; Blank_When_Zero: Boolean := False) return Picture;

   function Pic_String     (Pic: Picture) return String;
   function Blank_When_Zero(Pic: Picture) return Boolean;

   Max_Picture_Length: constant := <implementation_defined>;

   Default_Currency  : constant String    := "$";
   Default_Fill      : constant Character := '*';
   Default_Separator : constant Character := ',';
   Default_Radix_Mark: constant Character := '.';

   Picture_Error: exception;

   generic
      type Num is delta <> digits <>;
      Default_Currency  : String    := Text_IO.Editing.Default_Currency;
      Default_Fill      : Character := Text_IO.Editing.Default_Fill;
      Default_Separator : Character := Text_IO.Editing.Default_Separator;
      Default_Radix_Mark: Character := Text_IO.Editing.Default_Radix_Mark;
   package Decimal_Output is
      function Length(Pic: Picture; Currency: String := Default_Currency) return Natural;
      function Valid(Item: Num; Pic: Picture; Currency: String := Default_Currency) return Boolean;
      function Image(Item      : Num;
                     Pic       : Picture;
                     Currency  : String    := Default_Currency;
                     Fill      : Character := Default_Fill;
                     Separator : Character := Default_Separator;
                     Radix_Mark: Character := Default_Radix_Mark) return String;
      procedure Put(File      : File_Type;
                    Item      : Num;
                    Pic       : Picture;
                    Currency  : String    := Default_Currency;
                    Fill      : Character := Default_Fill;
                    Separator : Character := Default_Separator;
                    Radix_Mark: Character := Default_Radix_Mark)
         with Nonblocking => False;
      procedure Put(Item      : Num;
                    Pic       : Picture;
                    Currency  : String    := Default_Currency;
                    Fill      : Character := Default_Fill;
                    Separator : Character := Default_Separator;
                    Radix_Mark: Character := Default_Radix_Mark)
         with Nonblocking => False;
      procedure Put(To        : out String;
                    Item      : Num;
                    Pic       : Picture;
                    Currency  : String    := Default_Currency;
                    Fill      : Character := Default_Fill;
                    Separator : Character := Default_Separator;
                    Radix_Mark: Character := Default_Radix_Mark);
   end Decimal_Output;
end Ada.Text_IO.Editing;

Wide Text Editing#

The child package Wide_Text_IO.Editing has the same contents as Text_IO.Editing, except that:

  • Each occurrence of Character is replaced by Wide_Character.
  • Each occurrence of Text_IO is replaced by Wide_Text_IO.
  • The subtype of Default_Currency is Wide_String rather than String.
  • Each occurrence of String in the generic package Decimal_Output is replaced by Wide_String.

Wide Wide Text Editing#

The child package Wide_Wide_Text_IO.Editing has the same contents as Text_IO.Editing, except that:

  • Each occurrence of Character is replaced by Wide_Wide_Character.
  • Each occurrence of Text_IO is replaced by Wide_Wide_Text_IO.
  • The subtype of Default_Currency is Wide_Wide_String rather than String.
  • Each occurrence of String in the generic package Decimal_Output is replaced by Wide_Wide_String.

Bounded String IO#

The package Text_IO.Bounded_IO provides input-output in human-readable form for Bounded_Strings.

with Ada.Strings.Bounded;

generic
   with package Bounded is new Ada.Strings.Bounded.Generic_Bounded_Length(<>);
package Ada.Text_IO.Bounded_IO
   with Global => in out synchronized is

   procedure Put(File: File_Type; Item: Bounded.Bounded_String);
   procedure Put(                 Item: Bounded.Bounded_String);

   procedure Put_Line(File: File_Type; Item: Bounded.Bounded_String);
   procedure Put_Line(                 Item: Bounded.Bounded_String);

   function  Get_Line(File: File_Type) return Bounded.Bounded_String;
   procedure Get_Line(File: File_Type; Item: out Bounded.Bounded_String);

   function  Get_Line return Bounded.Bounded_String;
   procedure Get_Line(Item: out Bounded.Bounded_String);
end Ada.Text_IO.Bounded_IO;

Complex IO#

The generic package Text_IO.Complex_IO defines procedures for the formatted input and output of complex values. The generic actual parameter in an instantiation of Text_IO.Complex_IO is an instance of Numerics.Generic_Complex_Types for some floating point subtype. Exceptional conditions are reported by raising the appropriate exception defined in Text_IO.

with Ada.Numerics.Generic_Complex_Types;

generic
   with package Complex_Types is new Ada.Numerics.Generic_Complex_Types(<>);
package Ada.Text_IO.Complex_IO
   with Global => in out synchronized is

   use Complex_Types;

   Default_Fore: Field := 2;
   Default_Aft : Field := Real'Digits - 1;
   Default_Exp : Field := 3;

   procedure Get(File: File_Type; Item: out Complex; Width: Field := 0);
   procedure Get(                 Item: out Complex; Width: Field := 0);

   procedure Put(File: File_Type;
                 Item: Complex;
                 Fore: Field := Default_Fore;
                 Aft : Field := Default_Aft;
                 Exp : Field := Default_Exp);
   procedure Put(Item: Complex;
                 Fore: Field := Default_Fore;
                 Aft : Field := Default_Aft;
                 Exp : Field := Default_Exp);

   procedure Get(From: String; Item: out Complex; Last: out Positive)
      with Nonblocking;
   procedure Put(To  : out String;
                 Item: Complex;
                 Aft : Field := Default_Aft;
                 Exp : Field := Default_Exp)
      with Nonblocking;
end Ada.Text_IO.Complex_IO;

Wide Complex IO#

Implementations shall also provide the generic library package Wide_Text_IO.Complex_IO. Its declaration is obtained from that of Text_IO.Complex_IO by systematically replacing Text_IO by Wide_Text_IO and String by Wide_String; the description of its behavior is obtained by additionally replacing references to particular characters (commas, parentheses, etc.) by those for the corresponding wide characters.

Wide Wide Complex IO#

Implementations shall also provide the generic library package Wide_Wide_Text_IO.Complex_IO. Its declaration is obtained from that of Text_IO.Complex_IO by systematically replacing Text_IO by Wide_Wide_Text_IO and String by Wide_Wide_String; the description of its behavior is obtained by additionally replacing references to particular characters (commas, parentheses, etc.) by those for the corresponding wide wide characters.