Previous

Contents

Next

Appendix B: Selected standard packages


B.1 The hierarchy of the standard packages
B.2 The package Standard
B.3 The package Ada.Text_IO
B.4 The package Ada.Sequential_IO
B.5 The package Ada.Streams.Stream_IO
B.6 The package Ada.Characters.Handling
B.7 The package Ada.Characters.Latin_1

This appendix gives the specifications of the standard Ada library packages used in this book. For full details of the packages available, refer to Annex A of the Ada 95 Language Reference Manual, which is where the packages described in this appendix were copied from (with minor formatting changes). The following copyright notice applies:

Copyright © 1992, 1993, 1994, 1995 Intermetrics, Inc. This copyright is assigned to the U.S. Government. All rights reserved. This document may be copied, in whole or in part, in any form or by any means, as is or with alterations, provided that (1) alterations are clearly marked as alterations and (2) this copyright notice is included unmodified in any copy. Compiled copies of standard library units and examples need not contain this copyright notice so long as the notice is included in all copies of source code and documentation.

In addition to the packages listed here, chapter 9 gives the declaration of the package Ada.Calendar (section 9.10).


B.1 The hierarchy of the standard packages

All the packages in the standard library are descended from one of the parent packages Ada, System or Interfaces. The child packages of Ada are as follows:

    Asynchronous_Task_Control               Streams
    Calendar                                    Stream_IO
    Characters                              Strings
        Handling                                Bounded
        Latin_1                                 Fixed
    Command_Line                                Maps
    Decimal                                         Constants
    Direct_IO                                   Unbounded
        Dynamic_Priorities                      Wide_Bounded
    Exceptions                                  Wide_Fixed
    Finalisation                                    Wide_Maps
    Interrupts                                      Wide_Constants
        Names                                   Wide_Unbounded
    IO_Exceptions                           Synchronous_Task_Control
    Numerics                                Tags
        Complex_Elementary_Functions        Task_Attributes
        Complex_Types                       Task_Identification
        Discrete_Random                     Text_IO
        Elementary_Functions                    Complex_IO
        Float_Random                            Editing
        Generic_Complex_Elementary_Funct        Text_Streamsions
        Generic_Complex_Types               Unchecked_Conversion
        Generic_Elementary_Functions        Unchecked_Deallocation
    Real_Time                               Wide_Text_IO
    Sequential_IO                               Complex_IO
    Storage_IO                                  Editing
                                                Text_Streams

B.2 The package Standard

Note: Some of the contents of this package are not expressible in Ada. These parts are shown in italics to emphasise that they are given for explanatory purposes rather than being part of the language. For example, there are no types called root_integer or universal_integer; these are just conceptual types which are used in the language definition to formulate the rules for the way integer types work in Ada. For further information see section A.1 of the Ada 95 Reference Manual.

    package Standard is
        pragma Pure(Standard);

        type Boolean is (False, True);

        -- The predefined relational operators for this type
        -- are as follows:

        -- function "="   (Left, Right : Boolean) return Boolean;
        -- function "/="  (Left, Right : Boolean) return Boolean;
        -- function "<"   (Left, Right : Boolean) return Boolean;
        -- function "<="  (Left, Right : Boolean) return Boolean;
        -- function ">"   (Left, Right : Boolean) return Boolean;
        -- function ">="  (Left, Right : Boolean) return Boolean;

        -- The predefined logical operators and the predefined
        -- logical negation operator are as follows:

        -- function "and" (Left, Right : Boolean) return Boolean;
        -- function "or"  (Left, Right : Boolean) return Boolean;
        -- function "xor" (Left, Right : Boolean) return Boolean;

        -- function "not" (Right : Boolean) return Boolean;

        -- The integer type root_integer is predefined.
        -- The corresponding universal type is universal_integer.

        type Integer is range implementation-defined;

        subtype Natural  is Integer range 0 .. Integer'Last;
        subtype Positive is Integer range 1 .. Integer'Last;

        -- The predefined operators for type Integer are as follows:

        -- function "="   (Left, Right : Integer'Base) return Boolean;
        -- function "/="  (Left, Right : Integer'Base) return Boolean;
        -- function "<"   (Left, Right : Integer'Base) return Boolean;
        -- function "<="  (Left, Right : Integer'Base) return Boolean;
        -- function ">"   (Left, Right : Integer'Base) return Boolean;
        -- function ">="  (Left, Right : Integer'Base) return Boolean;

        -- function "+"   (Right : Integer'Base) return Integer'Base;
        -- function "-"   (Right : Integer'Base) return Integer'Base;
        -- function "abs" (Right : Integer'Base) return Integer'Base;

        -- function "+"   (Left, Right : Integer'Base) return Integer'Base;
        -- function "-"   (Left, Right : Integer'Base) return Integer'Base;

        -- function "*"   (Left, Right : Integer'Base) return Integer'Base;
        -- function "/"   (Left, Right : Integer'Base) return Integer'Base;
        -- function "rem" (Left, Right : Integer'Base) return Integer'Base;
        -- function "mod" (Left, Right : Integer'Base) return Integer'Base;

        -- function "**"  (Left : Integer'Base; Right : Natural)
        --         return Integer'Base;

        -- The specification of each operator for the type root_integer,
        -- or for any additional predefined integer type, is obtained by
        -- replacing Integer by the name of the type in the specification
        -- of the corresponding operator of the type Integer. The right
        -- operand of the exponentiation operator remains as subtype Natural.

        -- The floating point type root_real is predefined.
        -- The corresponding universal type is universal_real.

        type Float is digits implementation-defined;

        -- The predefined operators for this type are as follows:

        -- function "="   (Left, Right : Float) return Boolean;
        -- function "/="  (Left, Right : Float) return Boolean;
        -- function "<"   (Left, Right : Float) return Boolean;
        -- function "<="  (Left, Right : Float) return Boolean;
        -- function ">"   (Left, Right : Float) return Boolean;
        -- function ">="  (Left, Right : Float) return Boolean;

        -- function "+"   (Right : Float) return Float;
        -- function "-"   (Right : Float) return Float;
        -- function "abs" (Right : Float) return Float;

        -- function "+"   (Left, Right : Float) return Float;
        -- function "-"   (Left, Right : Float) return Float;
        -- function "*"   (Left, Right : Float) return Float;
        -- function "/"   (Left, Right : Float) return Float;

        -- function "**"  (Left : Float; Right : Integer'Base)
        --     return Float;

        -- The specification of each operator for the type root_real, or for
        -- any additional predefined floating point type, is obtained by
        -- replacing Float by the name of the type in the specification of
        -- the corresponding operator of the type Float.

        -- In addition, the following operators are predefined for
        -- the root numeric types:

        function "*" (Left : root_integer; Right : root_real) return root_real;

        function "*" (Left : root_real; Right : root_integer) return root_real;
        function "/" (Left : root_real; Right : root_integer) return root_real;

        -- The type universal_fixed is predefined.
        -- The only multiplying operators defined between fixed point types
        -- are:

        function "*" (Left  : universal_fixed;
                      Right : universal_fixed) return universal_fixed;

        function "/" (Left  : universal_fixed;
                      Right : universal_fixed) return universal_fixed;


        -- The declaration of type Character is based on the
        -- standard ISO 8859-1 character set.
        -- There are no character literals corresponding to the
        -- positions for control characters.
        -- They are indicated in italics in this definition.

        type Character is
          (nul,   soh,   stx,   etx,      eot,   enq,   ack,   bel,
           bs,    ht,    lf,    vt,       ff,    cr,    so,    si,
           dle,   dc1,   dc2,   dc3,      dc4,   nak,   syn,   etb,
           can,   em,    sub,   esc,      fs,    gs,    rs,    us,

           ' ',   '!',   '"',   '#',      '$',   '%',   '&',   ''',
           '(',   ')',   '*',   '+',      ',',   '-',   '.',   '/',

           '0',   '1',   '2',   '3',      '4',   '5',   '6',   '7',
           '8',   '9',   ':',   ';',      '<',   '=',   '>',   '?',

           '@',   'A',   'B',   'C',      'D',   'E',   'F',   'G',
           'H',   'I',   'J',   'K',      'L',   'M',   'N',   'O',

           'P',   'Q',   'R',   'S',      'T',   'U',   'V',   'W',
           'X',   'Y',   'Z',   '[',      '\',   ']',   '^',   '_',

           '`',   'a',   'b',   'c',      'd',   'e',   'f',   'g',
           'h',   'i',   'j',   'k',      'l',   'm',   'n',   'o',

           'p',   'q',   'r',   's',      't',   'u',   'v',   'w',
           'x',   'y',   'z',   '{',      '|',   '}',   '~',   del,

           reserved_128, reserved_129,    bph,   nbh,
           reserved_132, nel,   ssa,      esa,

           hts,   htj,   vts,   pld,      plu,   ri,    ss2,   ss3,

           dcs,   pu1,   pu2,   sts,      cch,   mw,    spa,   epa,

           sos,   reserved_153, sci,      csi,
           st,    osc,   pm,    apc,

           ' ',   '¡',   '¢',   '£',      '¤',   '¥',   '¦',   '§',
           '¨',   '©',   'ª',   '«',      '¬',   '­',   '®',   '¯ ',

           '°',   '±',   '²',   '³',      '´ ',  'µ',   '¶',   '·',
           '¸',   '¹',   'º',   '»',      '¼',   '½',   '¾',   '¿',

           'À',   'Á',   'Â',   'Ã',      'Ä',   'Å',   'Æ',   'Ç',
           'È',   'É',   'Ê',   'Ë',      'Ì',   'Í',   'Î',   'Ï',

           'Ð',   'Ñ',   'Ò',   'Ó',      'Ô',   'Õ',   'Ö',   '×',
           'Ø',   'Ù',   'Ú',   'Û',      'Ü',   'Ý',   'Þ',   'ß',

           'à',   'á',   'â',   'ã',      'ä',   'å',   'æ',   'ç',
           'è',   'é',   'ê',   'ë',      'ì',   'í',   'î',   'ï',

           'ð',   'ñ',   'ò',   'ó',      'ô',   'õ',   'ö',   '÷ ',
           'ø',   'ù',   'ú',  'û',       'ü',   'ý',   'þ',   'ÿ');

        -- The predefined operators for the type Character are the
        -- same as for any enumeration type.

        -- The declaration of type Wide_Character is based on the standard
        -- ISO 10646 BMP character set.
        -- The first 256 positions have the same contents as type Character.

        type Wide_Character is (nul, soh ... FFFE, FFFF);

        package ASCII is ... end ASCII;     -- Obsolescent


        -- Predefined string types:

        type String is array(Positive range <>) of Character;
        pragma Pack(String);

        -- The predefined operators for this type are as follows:

        -- function "="  (Left, Right: String) return Boolean;
        -- function "/=" (Left, Right: String) return Boolean;
        -- function "<"  (Left, Right: String) return Boolean;
        -- function "<=" (Left, Right: String) return Boolean;
        -- function ">"  (Left, Right: String) return Boolean;
        -- function ">=" (Left, Right: String) return Boolean;

        -- function "&"  (Left: String;    Right: String)    return String;
        -- function "&"  (Left: Character; Right: String)    return String;
        -- function "&"  (Left: String;    Right: Character) return String;
        -- function "&"  (Left: Character; Right: Character) return String;

        type Wide_String is array (Positive range <>) of Wide_Character;
        pragma Pack(Wide_String);
        -- The predefined operators for this type correspond to
        -- those for String

        type Duration is delta implementation-defined
                         range implementation-defined;

        -- The predefined operators for the type Duration are the
        -- same as for any fixed point type.

        -- The predefined exceptions:

        Constraint_Error : exception;
        Program_Error    : exception;
        Storage_Error    : exception;
        Tasking_Error    : exception;

    end Standard;

B.3 The package Ada.Text_IO

Note: The package Ada.Integer_Text_IO is functionally identical to an instantiation of Ada.Text_IO.Integer_IO for the standard type Integer, and similarly Ada.Float_Text_IO is functionally identical to an instantiation of Ada.Text_IO.Float_IO for the standard type Float. For further information see section A.10 of the Ada 95 Reference Manual.

with Ada.IO_Exceptions;
package Ada.Text_IO 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 : in File_Mode := Out_File;
                      Name : in String    := "";
                      Form : in String    := "");

    procedure Open   (File : in out File_Type;
                      Mode : in File_Mode;
                      Name : in String;
                      Form : in String := "");

    procedure Close  (File : in out File_Type);
    procedure Delete (File : in out File_Type);

    procedure Reset  (File : in out File_Type;
                      Mode : in File_Mode);
    procedure Reset  (File : in out File_Type);

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

    function Is_Open (File : in File_Type) return Boolean;

    -- Control of default input and output files
    procedure Set_Input (File : in File_Type);
    procedure Set_Output(File : in File_Type);
    procedure Set_Error (File : in 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 out File_Type);
    procedure Flush;

    -- Specification of line and page lengths
    procedure Set_Line_Length (File : in File_Type;
                               To   : in Count);
    procedure Set_Line_Length (To   : in Count);

    procedure Set_Page_Length (File : in File_Type;
                               To   : in Count);
    procedure Set_Page_Length (To   : in Count);

    function Line_Length (File : in File_Type) return Count;
    function Line_Length return Count;

    function Page_Length (File : in File_Type) return Count;
    function Page_Length return Count;

    -- Column, Line, and Page Control
    procedure New_Line    (File    : in File_Type;
                           Spacing : in Positive_Count := 1);
    procedure New_Line    (Spacing : in Positive_Count := 1);
    procedure Skip_Line   (File    : in File_Type;
                           Spacing : in Positive_Count := 1);
    procedure Skip_Line   (Spacing : in Positive_Count := 1);
    function End_Of_Line  (File    : in File_Type) return Boolean;
    function End_Of_Line   return Boolean;

    procedure New_Page    (File : in File_Type);
    procedure New_Page;

    procedure Skip_Page   (File : in File_Type);
    procedure Skip_Page;

    function End_Of_Page  (File : in File_Type) return Boolean;
    function End_Of_Page   return Boolean;

    function End_Of_File  (File : in File_Type) return Boolean;
    function End_Of_File   return Boolean;

    procedure Set_Col  (File : in File_Type;
                        To   : in Positive_Count);
    procedure Set_Col  (To   : in Positive_Count);

    procedure Set_Line (File : in File_Type;
                        To   : in Positive_Count);
    procedure Set_Line (To   : in Positive_Count);

    function Col  (File : in File_Type) return Positive_Count;
    function Col   return Positive_Count;

    function Line (File : in File_Type) return Positive_Count;
    function Line  return Positive_Count;

    function Page (File : in File_Type) return Positive_Count;
    function Page  return Positive_Count;

    -- Character Input-Output
    procedure Get (File : in File_Type; Item : out Character);
    procedure Get (Item : out Character);

    procedure Put (File : in File_Type; Item : in Character);
    procedure Put (Item : in Character);

    procedure Look_Ahead    (File        : in File_Type;
                             Item        : out Character;
                             End_Of_Line : out Boolean);
    procedure Look_Ahead    (Item        : out Character;
                             End_Of_Line : out Boolean);
    procedure Get_Immediate (File        : in File_Type;
                             Item        : out Character);
    procedure Get_Immediate (Item        : out Character);

    procedure Get_Immediate (File        : in File_Type;
                             Item        : out Character;
                             Available   : out Boolean);
    procedure Get_Immediate (Item        : out Character;
                             Available   : out Boolean);

    -- String Input-Output
    procedure Get (File : in File_Type; Item : out String);
    procedure Get (Item : out String);

    procedure Put (File : in File_Type; Item : in String);
    procedure Put (Item : in String);

    procedure Get_Line (File : in File_Type;
                        Item : out String;
                        Last : out Natural);
    procedure Get_Line (Item : out String; Last : out Natural);

    procedure Put_Line (File : in File_Type; Item : in String);
    procedure Put_Line (Item : in String);

    -- 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  : in File_Type;
                       Item  : out Num;
                       Width : in Field := 0);
        procedure Get (Item  : out Num;
                       Width : in Field := 0);
        procedure Put (File  : in File_Type;
                       Item  : in Num;
                       Width : in Field := Default_Width;
                       Base  : in Number_Base := Default_Base);
        procedure Put (Item  : in Num;
                       Width : in Field := Default_Width;
                       Base  : in Number_Base := Default_Base);
        procedure Get (From  : in String;
                       Item  : out Num;
                       Last  : out Positive);

        procedure Put (To    : out String;
                       Item  : in Num;
                       Base  : in Number_Base := Default_Base);
    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  : in File_Type;
                       Item  : out Num;
                       Width : in Field := 0);
        procedure Get (Item  : out Num;
                       Width : in Field := 0);

        procedure Put (File  : in File_Type;
                       Item  : in Num;
                       Width : in Field := Default_Width;
                       Base  : in Number_Base := Default_Base);
        procedure Put (Item  : in Num;
                       Width : in Field := Default_Width;
                       Base  : in Number_Base := Default_Base);

        procedure Get (From  : in String;
                       Item  : out Num;
                       Last  : out Positive);
        procedure Put (To    : out String;
                       Item  : in Num;
                       Base  : in Number_Base := Default_Base);
    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  : in File_Type;
                       Item  : out Num;
                       Width : in Field := 0);
        procedure Get (Item  : out Num;
                       Width : in Field := 0);

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

        procedure Get (From  : in String;
                       Item  : out Num;
                       Last  : out Positive);

        procedure Put (To    : out String;
                       Item  : in Num;
                       Aft   : in Field := Default_Aft;
                       Exp   : in Field := Default_Exp);
    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  : in File_Type;
                       Item  : out Num;
                       Width : in Field := 0);
        procedure Get (Item  : out Num;
                       Width : in Field := 0);

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

        procedure Get (From  : in String;
                       Item  : out Num;
                       Last  : out Positive);
        procedure Put (To    : out String;
                       Item  : in Num;
                       Aft   : in Field := Default_Aft;
                       Exp   : in Field := Default_Exp);
    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  : in File_Type;
                       Item  : out Num;
                       Width : in Field := 0);
        procedure Get (Item  : out Num;
                       Width : in Field := 0);

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

        procedure Put (Item  : in Num;
                       Fore  : in Field := Default_Fore;
                       Aft   : in Field := Default_Aft;
                       Exp   : in Field := Default_Exp);

        procedure Get (From  : in String;
                       Item  : out Num;
                       Last  : out Positive);

        procedure Put (To    : out String;
                       Item  : in Num;
                       Aft   : in Field := Default_Aft;
                       Exp   : in Field := Default_Exp);
    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  : in File_Type;
                       Item  : out Enum);
        procedure Get (Item  : out Enum);

        procedure Put (File  : in File_Type;
                       Item  : in Enum;
                       Width : in Field    := Default_Width;
                       Set   : in Type_Set := Default_Setting);
        procedure Put (Item  : in Enum;
                       Width : in Field    := Default_Width;
                       Set   : in Type_Set := Default_Setting);

        procedure Get (From  : in String;
                       Item  : out Enum;
                       Last  : out Positive);
        procedure Put (To    : out String;
                       Item  : in Enum;
                       Set   : in Type_Set := Default_Setting);
    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;

private
    ... -- not specified by the language
end Ada.Text_IO;

B.4 The package Ada.Sequential_IO

For further information see section A.8 of the Ada 95 Reference Manual.

    with Ada.IO_Exceptions;
    generic
        type Element_Type(<>) is private;
    package Ada.Sequential_IO 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 : in File_Mode := Out_File;
                          Name : in String := "";
                          Form : in String := "");

        procedure Open   (File : in out File_Type;
                          Mode : in File_Mode;
                          Name : in String;
                          Form : in String := "");

        procedure Close  (File : in out File_Type);
        procedure Delete (File : in out File_Type);

        procedure Reset  (File : in out File_Type;
                          Mode : in File_Mode);
        procedure Reset  (File : in out File_Type);

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

        function Is_Open (File : in File_Type) return Boolean;

        -- Input and output operations

        procedure Read   (File : in File_Type;
                          Item : out Element_Type);
        procedure Write  (File : in File_Type;
                          Item : in Element_Type);

        function End_Of_File (File : in File_Type) return Boolean;

        -- 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;

    private
        ... -- not specified by the language
    end Ada.Sequential_IO;

B.5 The package Ada.Streams.Stream_IO

For further information see section A.12.1 of the Ada 95 Reference Manual.

    with Ada.IO_Exceptions;
    package Ada.Streams.Stream_IO is
        type Stream_Access is access all Root_Stream_Type'Class;

        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;
                                            -- Index into file, in stream elements.

        procedure Create (File : in out File_Type;
                          Mode : in File_Mode := Out_File;
                          Name : in String := "";
                          Form : in String := "");

        procedure Open   (File : in out File_Type;
                          Mode : in File_Mode;
                          Name : in String;
                          Form : in String := "");

        procedure Close  (File : in out File_Type);
        procedure Delete (File : in out File_Type);
        procedure Reset  (File : in out File_Type;
                          Mode : in File_Mode);
        procedure Reset  (File : in out File_Type);

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

        function  Is_Open     (File : in File_Type) return Boolean;
        function  End_Of_File (File : in File_Type) return Boolean;

        function Stream (File : in File_Type) return Stream_Access;
                -- Return stream access for use with T'Input and T'Output

        -- Read array of stream elements from file

        procedure Read  (File : in File_Type;
                         Item : out Stream_Element_Array;
                         Last : out Stream_Element_Offset;
                         From : in Positive_Count);

        procedure Read  (File : in File_Type;
                         Item : out Stream_Element_Array;
                         Last : out Stream_Element_Offset);

        -- Write array of stream elements into file

        procedure Write (File : in File_Type;
                         Item : in Stream_Element_Array;
                         To : in Positive_Count);

        procedure Write (File : in File_Type;
                         Item : in Stream_Element_Array);

        -- Operations on position within file

        procedure Set_Index (File : in File_Type;
                             To   : in Positive_Count);

        function  Index     (File : in File_Type) return Positive_Count;
        function  Size      (File : in File_Type) return Count;

        procedure Set_Mode  (File : in out File_Type;
                             Mode : in File_Mode);

        procedure Flush     (File : in out File_Type);

        -- 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;

    private
        ... -- not specified by the language
    end Ada.Streams.Stream_IO;

B.6 The package Ada.Characters.Handling

For further information see section A.3.2 of the Ada 95 Reference Manual.

    package Ada.Characters.Handling is
        pragma Preelaborate(Handling);

        -- Character classification functions

        function Is_Control  (Item : in Character) return Boolean;
        function Is_Graphic  (Item : in Character) return Boolean;
        function Is_Letter   (Item : in Character) return Boolean;
        function Is_Lower    (Item : in Character) return Boolean;
        function Is_Upper    (Item : in Character) return Boolean;
        function Is_Basic    (Item : in Character) return Boolean;
        function Is_Digit    (Item : in Character) return Boolean;
        function Is_Decimal_Digit
                             (Item : in Character) return Boolean renames Is_Digit;
        function Is_Hexadecimal_Digit
                             (Item : in Character) return Boolean;
        function Is_Alphanumeric
                             (Item : in Character) return Boolean;
        function Is_Special  (Item : in Character) return Boolean;

        -- Conversion functions for Character and String

        function To_Lower (Item : in Character) return Character;
        function To_Upper (Item : in Character) return Character;
        function To_Basic (Item : in Character) return Character;
        function To_Lower (Item : in String) return String;
        function To_Upper (Item : in String) return String;
        function To_Basic (Item : in String) return String;

        -- Classifications of and conversions between Character and ISO 646

        subtype ISO_646 is Character range Character'Val(0) .. Character'Val(127);

        function Is_ISO_646 (Item : in Character) return Boolean;
        function Is_ISO_646 (Item : in String) return Boolean;

        function To_ISO_646 (Item       : in Character;
                             Substitute : in ISO_646 := ' ') return ISO_646;

        function To_ISO_646 (Item       : in String;
                             Substitute : in ISO_646 := ' ') return String;

        -- Classifications of and conversions between Wide_Character and Character

        function Is_Character (Item : in Wide_Character) return Boolean;
        function Is_String (Item : in Wide_String)       return Boolean;

        function To_Character (Item       : in Wide_Character;
                               Substitute : in Character := ' ')
                                                         return Character;

        function To_String (Item       : in Wide_String;
                            Substitute : in Character := ' ')
                                                         return String;

        function To_Wide_Character (Item : in Character) return Wide_Character;

        function To_Wide_String    (Item : in String)    return Wide_String;

    end Ada.Characters.Handling;

B.7 The package Ada.Characters.Latin_1

For further information see section A.3.3 of the Ada 95 Reference Manual.

    package Ada.Characters.Latin_1 is
        pragma Pure(Latin_1);

        -- Control characters:

        NUL                  : constant Character := Character'Val(0);
        SOH                  : constant Character := Character'Val(1);
        STX                  : constant Character := Character'Val(2);
        ETX                  : constant Character := Character'Val(3);
        EOT                  : constant Character := Character'Val(4);
        ENQ                  : constant Character := Character'Val(5);
        ACK                  : constant Character := Character'Val(6);
        BEL                  : constant Character := Character'Val(7);

        BS                   : constant Character := Character'Val(8);
        HT                   : constant Character := Character'Val(9);
        LF                   : constant Character := Character'Val(10);
        VT                   : constant Character := Character'Val(11);
        FF                   : constant Character := Character'Val(12);
        CR                   : constant Character := Character'Val(13);
        SO                   : constant Character := Character'Val(14);
        SI                   : constant Character := Character'Val(15);

        DLE                  : constant Character := Character'Val(16);
        DC1                  : constant Character := Character'Val(17);
        DC2                  : constant Character := Character'Val(18);
        DC3                  : constant Character := Character'Val(19);
        DC4                  : constant Character := Character'Val(20);
        NAK                  : constant Character := Character'Val(21);
        SYN                  : constant Character := Character'Val(22);
        ETB                  : constant Character := Character'Val(23);

        CAN                  : constant Character := Character'Val(24);
        EM                   : constant Character := Character'Val(25);
        SUB                  : constant Character := Character'Val(26);
        ESC                  : constant Character := Character'Val(27);
        FS                   : constant Character := Character'Val(28);
        GS                   : constant Character := Character'Val(29);
        RS                   : constant Character := Character'Val(30);
        US                   : constant Character := Character'Val(31);

        -- ISO 646 graphic characters:

        Space                : constant Character := ' '; --Character'Val(32)
        Exclamation          : constant Character := '!'; --Character'Val(33)
        Quotation            : constant Character := '"'; --Character'Val(34)
        Number_Sign          : constant Character := '#'; --Character'Val(35)
        Dollar_Sign          : constant Character := '$'; --Character'Val(36)
        Percent_Sign         : constant Character := '%'; --Character'Val(37)
        Ampersand            : constant Character := '&'; --Character'Val(38)
        Apostrophe           : constant Character := '''; --Character'Val(39)
        Left_Parenthesis     : constant Character := '('; --Character'Val(40)
        Right_Parenthesis    : constant Character := ')'; --Character'Val(41)
        Asterisk             : constant Character := '*'; --Character'Val(42)
        Plus_Sign            : constant Character := '+'; --Character'Val(43)
        Comma                : constant Character := ','; --Character'Val(44)
        Hyphen               : constant Character := '-'; --Character'Val(45)
        Minus_Sign           : Character renames Hyphen;
        Full_Stop            : constant Character := '.'; --Character'Val(46)
        Solidus              : constant Character := '/'; --Character'Val(47)

        -- Decimal digits '0' through '9' are at positions 48 through 57

        Colon                : constant Character := ':'; --Character'Val(58)
        Semicolon            : constant Character := ';'; --Character'Val(59)
        Less_Than_Sign       : constant Character := '<'; --Character'Val(60)
        Equals_Sign          : constant Character := '='; --Character'Val(61)
        Greater_Than_Sign    : constant Character := '>'; --Character'Val(62)
        Question             : constant Character := '?'; --Character'Val(63)
        Commercial_At        : constant Character := '@'; --Character'Val(64)

        -- Letters 'A' through 'Z' are at positions 65 through 90

        Left_Square_Bracket  : constant Character := '['; --Character'Val(91)
        Reverse_Solidus      : constant Character := '\'; --Character'Val(92)
        Right_Square_Bracket : constant Character := ']'; --Character'Val(93)
        Circumflex           : constant Character := '^'; --Character'Val(94)
        Low_Line             : constant Character := '_'; --Character'Val(95)

        Grave                : constant Character := '`'; --Character'Val(96)
        LC_A                 : constant Character := 'a'; --Character'Val(97)
        LC_B                 : constant Character := 'b'; --Character'Val(98)
        LC_C                 : constant Character := 'c'; --Character'Val(99)
        LC_D                 : constant Character := 'd'; --Character'Val(100)
        LC_E                 : constant Character := 'e'; --Character'Val(101)
        LC_F                 : constant Character := 'f'; --Character'Val(102)
        LC_G                 : constant Character := 'g'; --Character'Val(103)
        LC_H                 : constant Character := 'h'; --Character'Val(104)
        LC_I                 : constant Character := 'i'; --Character'Val(105)
        LC_J                 : constant Character := 'j'; --Character'Val(106)
        LC_K                 : constant Character := 'k'; --Character'Val(107)
        LC_L                 : constant Character := 'l'; --Character'Val(108)
        LC_M                 : constant Character := 'm'; --Character'Val(109)
        LC_N                 : constant Character := 'n'; --Character'Val(110)
        LC_O                 : constant Character := 'o'; --Character'Val(111)

        LC_P                 : constant Character := 'p'; --Character'Val(112)
        LC_Q                 : constant Character := 'q'; --Character'Val(113)
        LC_R                 : constant Character := 'r'; --Character'Val(114)
        LC_S                 : constant Character := 's'; --Character'Val(115)
        LC_T                 : constant Character := 't'; --Character'Val(116)
        LC_U                 : constant Character := 'u'; --Character'Val(117)
        LC_V                 : constant Character := 'v'; --Character'Val(118)
        LC_W                 : constant Character := 'w'; --Character'Val(119)
        LC_X                 : constant Character := 'x'; --Character'Val(120)
        LC_Y                 : constant Character := 'y'; --Character'Val(121)
        LC_Z                 : constant Character := 'z'; --Character'Val(122)
        Left_Curly_Bracket   : constant Character := '{'; --Character'Val(123)
        Vertical_Line        : constant Character := '|'; --Character'Val(124)
        Right_Curly_Bracket  : constant Character := '}'; --Character'Val(125)
        Tilde                : constant Character := '~'; --Character'Val(126)

        DEL                  : constant Character := Character'Val(127);

        -- ISO 6429 control characters:

        IS4                  : Character renames FS;
        IS3                  : Character renames GS;
        IS2                  : Character renames RS;
        IS1                  : Character renames US;

        Reserved_128         : constant Character := Character'Val(128);
        Reserved_129         : constant Character := Character'Val(129);
        BPH                  : constant Character := Character'Val(130);
        NBH                  : constant Character := Character'Val(131);
        Reserved_132         : constant Character := Character'Val(132);
        NEL                  : constant Character := Character'Val(133);
        SSA                  : constant Character := Character'Val(134);
        ESA                  : constant Character := Character'Val(135);
        HTS                  : constant Character := Character'Val(136);
        HTJ                  : constant Character := Character'Val(137);
        VTS                  : constant Character := Character'Val(138);
        PLD                  : constant Character := Character'Val(139);
        PLU                  : constant Character := Character'Val(140);
        RI                   : constant Character := Character'Val(141);
        SS2                  : constant Character := Character'Val(142);
        SS3                  : constant Character := Character'Val(143);

        DCS                  : constant Character := Character'Val(144);
        PU1                  : constant Character := Character'Val(145);
        PU2                  : constant Character := Character'Val(146);
        STS                  : constant Character := Character'Val(147);
        CCH                  : constant Character := Character'Val(148);
        MW                   : constant Character := Character'Val(149);
        SPA                  : constant Character := Character'Val(150);
        EPA                  : constant Character := Character'Val(151);

        SOS                  : constant Character := Character'Val(152);
        Reserved_153         : constant Character := Character'Val(153);
        SCI                  : constant Character := Character'Val(154);
        CSI                  : constant Character := Character'Val(155);
        ST                   : constant Character := Character'Val(156);
        OSC                  : constant Character := Character'Val(157);
        PM                   : constant Character := Character'Val(158);
        APC                  : constant Character := Character'Val(159);

        -- Other graphic characters:

        -- Character positions 160 (16#A0#) .. 175 (16#AF#):
        No_Break_Space              : constant Character := ' ';  -- Character'Val(160)
        NBSP                        : Character renames No_Break_Space;
        Inverted_Exclamation        : constant Character := '¡';  -- Character'Val(161);
        Cent_Sign                   : constant Character := '¢';  -- Character'Val(162);
        Pound_Sign                  : constant Character := '£';  -- Character'Val(163);
        Currency_Sign               : constant Character := '¤';  -- Character'Val(164);
        Yen_Sign                    : constant Character := '¥';  -- Character'Val(165);
        Broken_Bar                  : constant Character := '¦';  -- Character'Val(166);
        Section_Sign                : constant Character := '§';  -- Character'Val(167);
        Diaeresis                   : constant Character := '¨';  -- Character'Val(168);
        Copyright_Sign              : constant Character := '©';  -- Character'Val(169);
        Feminine_Ordinal_Indication : constant Character := 'ª';  -- Character'Val(170);
        Left_Angle_Quotation        : constant Character := '«';  -- Character'Val(171);
        Not_Sign                    : constant Character := '¬';  -- Character'Val(172);
        Soft_Hyphen                 : constant Character := '­';  -- Character'Val(173);
        Registered_Trade_Mark       : constant Character := '®';  -- Character'Val(174);
        Macron                      : constant Character := '¯';  -- Character'Val(175);

        -- Character positions 176 (16#B0#) .. 191 (16#BF#):
        Degree_Sign                 : constant Character := '°';  -- Character'Val(176);
        Ring_Above                  : Character renames Degree_Sign;
        Plus_Minus_Sign             : constant Character := '±';  -- Character'Val(177);
        Superscript_Two             : constant Character := '²';  -- Character'Val(178);
        Superscript_Three           : constant Character := '³';  -- Character'Val(179);
        Acute                       : constant Character := '´';  -- Character'Val(180);
        Micro_Sign                  : constant Character := 'µ';  -- Character'Val(181);
        Pilcrow_Sign                : constant Character := '¶';  -- Character'Val(182);
        Paragraph_Sign              : Character renames Pilcrow_Sign;
        Middle_Dot                  : constant Character := '·';  -- Character'Val(183);
        Cedilla                     : constant Character := '¸';  -- Character'Val(184);
        Superscript_One             : constant Character := '¹';  -- Character'Val(185);
        Masculine_Ordinal_Indicator : constant Character := 'º';  -- Character'Val(186);
        Right_Angle_Quotation       : constant Character := '»';  -- Character'Val(187);
        Fraction_One_Quarter        : constant Character := '¼';  -- Character'Val(188);
        Fraction_One_Half           : constant Character := '½';  -- Character'Val(189);
        Fraction_Three_Quarters     : constant Character := '¾';  -- Character'Val(190);
        Inverted_Question           : constant Character := '¿';  -- Character'Val(191);

        -- Character positions 192 (16#C0#) .. 207 (16#CF#):
        UC_A_Grave                  : constant Character := 'À';  -- Character'Val(192);
        UC_A_Acute                  : constant Character := 'Á';  -- Character'Val(193);
        UC_A_Circumflex             : constant Character := 'Â';  -- Character'Val(194);
        UC_A_Tilde                  : constant Character := 'Ã';  -- Character'Val(195);
        UC_A_Diaeresis              : constant Character := 'Ä';  -- Character'Val(196);
        UC_A_Ring                   : constant Character := 'Å';  -- Character'Val(197);
        UC_AE_Diphthong             : constant Character := 'Æ';  -- Character'Val(198);
        UC_C_Cedilla                : constant Character := 'Ç';  -- Character'Val(199);
        UC_E_Grave                  : constant Character := 'È';  -- Character'Val(200);
        UC_E_Acute                  : constant Character := 'É';  -- Character'Val(201);
        UC_E_Circumflex             : constant Character := 'Ê';  -- Character'Val(202);
        UC_E_Diaeresis              : constant Character := 'Ë';  -- Character'Val(203);
        UC_I_Grave                  : constant Character := 'Ì';  -- Character'Val(204);
        UC_I_Acute                  : constant Character := 'Í';  -- Character'Val(205);
        UC_I_Circumflex             : constant Character := 'Î';  -- Character'Val(206);
        UC_I_Diaeresis              : constant Character := 'Ï';  -- Character'Val(207);

        -- Character positions 208 (16#D0#) .. 223 (16#DF#):
        UC_Icelandic_Eth            : constant Character := 'Ð';  -- Character'Val(208);
        UC_N_Tilde                  : constant Character := 'Ñ';  -- Character'Val(209);
        UC_O_Grave                  : constant Character := 'Ò';  -- Character'Val(210);
        UC_O_Acute                  : constant Character := 'Ó';  -- Character'Val(211);
        UC_O_Circumflex             : constant Character := 'Ô';  -- Character'Val(212);
        UC_O_Tilde                  : constant Character := 'Õ';  -- Character'Val(213);
        UC_O_Diaeresis              : constant Character := 'Ö';  -- Character'Val(214);
        Multiplication_Sign         : constant Character := '×';  -- Character'Val(215);
        UC_O_Oblique_Stroke         : constant Character := 'Ø';  -- Character'Val(216);
        UC_U_Grave                  : constant Character := 'Ù';  -- Character'Val(217);
        UC_U_Acute                  : constant Character := 'Ú';  -- Character'Val(218);
        UC_U_Circumflex             : constant Character := 'Û';  -- Character'Val(219);
        UC_U_Diaeresis              : constant Character := 'Ü';  -- Character'Val(220);
        UC_Y_Acute                  : constant Character := 'Ý';  -- Character'Val(221);
        UC_Icelandic_Thorn          : constant Character := 'Þ';  -- Character'Val(222);
        LC_German_Sharp_S           : constant Character := 'ß';  -- Character'Val(223);

        -- Character positions 224 (16#E0#) .. 239 (16#EF#):
        LC_A_Grave                  : constant Character := 'à';  -- Character'Val(224);
        LC_A_Acute                  : constant Character := 'á';  -- Character'Val(225);
        LC_A_Circumflex             : constant Character := 'â';  -- Character'Val(226);
        LC_A_Tilde                  : constant Character := 'ã';  -- Character'Val(227);
        LC_A_Diaeresis              : constant Character := 'ä';  -- Character'Val(228);
        LC_A_Ring                   : constant Character := 'å';  -- Character'Val(229);
        LC_AE_Diphthong             : constant Character := 'æ';  -- Character'Val(230);
        LC_C_Cedilla                : constant Character := 'ç';  -- Character'Val(231);
        LC_E_Grave                  : constant Character := 'è';  -- Character'Val(232);
        LC_E_Acute                  : constant Character := 'é';  -- Character'Val(233);
        LC_E_Circumflex             : constant Character := 'ê';  -- Character'Val(234);
        LC_E_Diaeresis              : constant Character := 'ë';  -- Character'Val(235);
        LC_I_Grave                  : constant Character := 'ì';  -- Character'Val(236);
        LC_I_Acute                  : constant Character := 'í';  -- Character'Val(237);
        LC_I_Circumflex             : constant Character := 'î';  -- Character'Val(238);
        LC_I_Diaeresis              : constant Character := 'ï';  -- Character'Val(239);

        -- Character positions 240 (16#F0#) .. 255 (16#FF#):
        LC_Icelandic_Eth            : constant Character := 'ð';  -- Character'Val(240);
        LC_N_Tilde                  : constant Character := 'ñ';  -- Character'Val(241);
        LC_O_Grave                  : constant Character := 'ò';  -- Character'Val(242);
        LC_O_Acute                  : constant Character := 'ó';  -- Character'Val(243);
        LC_O_Circumflex             : constant Character := 'ô';  -- Character'Val(244);
        LC_O_Tilde                  : constant Character := 'õ';  -- Character'Val(245);
        LC_O_Diaeresis              : constant Character := 'ö';  -- Character'Val(246);
        Division_Sign               : constant Character := '÷';  -- Character'Val(247);
        LC_O_Oblique_Stroke         : constant Character := 'ø';  -- Character'Val(248);
        LC_U_Grave                  : constant Character := 'ù';  -- Character'Val(249);
        LC_U_Acute                  : constant Character := 'ú';  -- Character'Val(250);
        LC_U_Circumflex             : constant Character := 'û';  -- Character'Val(251);
        LC_U_Diaeresis              : constant Character := 'ü';  -- Character'Val(252);
        LC_Y_Acute                  : constant Character := 'ý';  -- Character'Val(253);
        LC_Icelandic_Thorn          : constant Character := 'þ';  -- Character'Val(254);
        LC_Y_Diaeresis              : constant Character := 'ÿ';  -- Character'Val(255);

    end Ada.Characters.Latin_1;



Previous

Contents

Next

This file is part of Ada 95: The Craft of Object-Oriented Programming by John English.
Copyright © John English 2000. All rights reserved.
Permission is given to redistribute this work for non-profit educational use only, provided that all the constituent files are distributed without change.


$Revision: 1.2 $
$Date: 2001/11/17 12:00:00 $