DataMuseum.dk

Presents historical artifacts from the history of:

Rational R1000/400

This is an automatic "excavation" of a thematic subset of
artifacts from Datamuseum.dk's BitArchive.

See our Wiki for more about Rational R1000/400

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - download

⟦511e5609e⟧ TextFile

    Length: 326557 (0x4fb9d)
    Types: TextFile
    Notes: R1k Text-file segment

Derivation

└─⟦8527c1e9b⟧ Bits:30000544 8mm tape, Rational 1000, Arrival backup of disks in PAM's R1000
    └─ ⟦5a81ac88f⟧ »Space Info Vol 1« 
        └─⟦756f8febe⟧ 
            └─⟦this⟧ 

TextFile

with Io_Exceptions;

package Basic_Io is

    type Count is range 0 .. Integer'Last;

    subtype Positive_Count is Count range 1 .. Count'Last;

    function Get_Integer return String;

    -- Skips any leading blanks, line terminators or page
    -- terminators.  Then reads a plus or a minus sign if
    -- present, then reads according to the syntax of an
    -- integer literal, which may be based.  Stores in item
    -- a string containing an optional sign and an integer
    -- literal.
    --
    -- The exception DATA_ERROR is raised if the sequence
    -- of characters does not correspond to the syntax
    -- escribed above.
    --
    -- The exception END_ERROR is raised if the file terminator
    -- is read.  This means that the starting sequence of an
    -- integer has not been met.
    --
    -- Note that the character terminating the operation must
    -- be available for the next get operation.
    --

    function Get_Real return String;

    -- Corresponds to get_integer except that it reads according
    -- to the syntax of a real literal, which may be based.


    function Get_Enumeration return String;

    -- Corresponds to get_integer except that it reads according
    -- to the syntax of an identifier, where upper and lower
    -- case letters are equivalent to a character literal
    -- including the apostrophes.

    function Get_Item (Length : in Integer) return String;

    -- Reads a string from the current line and stores it in
    -- item.  If the remaining number of characters on the
    -- current line is less than the length then only these
    -- characters are returned.  The line terminator is not
    -- skipped.


    procedure Put_Item (Item : in String);

    -- If the length of the string is greater than the current
    -- maximum line (linelength), the exception LAYOUT_ERROR
    -- is raised.
    --
    -- If the string does not fit on the current line a line
    -- terminator is output, then the item is output.


    -- Line and page lengths - ARM 14.3.3.
    --

    procedure Set_Line_Length (To : in Count);


    procedure Set_Page_Length (To : in Count);


    function Line_Length return Count;


    function Page_Length return Count;


    -- Operations oncolumns, lines and pages - ARM 14.3.4.
    --

    procedure New_Line;


    procedure Skip_Line;


    function End_Of_Line return Boolean;


    procedure New_Page;


    procedure Skip_Page;


    function End_Of_Page return Boolean;


    function End_Of_File return Boolean;


    procedure Set_Col (To : in Positive_Count);


    procedure Set_Line (To : in Positive_Count);


    function Col return Positive_Count;


    function Line return Positive_Count;


    function Page return Positive_Count;



    -- Character and string procedures defined is ARM 14.3.6.
    --

    procedure Get_Character (Item : out Character);


    procedure Get_String (Item : out String);


    procedure Get_Line (Item : out String; Last : out Natural);


    procedure Put_Character (Item : in Character);


    procedure Put_String (Item : in String);


    procedure Put_Line (Item : in String);



    -- exceptions:

    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;

end Basic_Io;with Io_Exceptions;

generic
    type Element_Type is private;
package Direct_Io is

    type File_Type is limited private;

    type File_Mode is (In_File, Inout_File, Out_File);
    type Count is new Integer range 0 .. Integer'Last / Element_Type'Size;
    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;

    -- Input and output operations

    procedure Read (File : File_Type;
                    Item : out Element_Type;
                    From : Positive_Count);
    procedure Read (File : File_Type; Item : out Element_Type);

    procedure Write (File : File_Type;
                     Item : Element_Type;
                     To : Positive_Count);
    procedure Write (File : File_Type; Item : Element_Type);

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

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

    function End_Of_File (File : 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

    type File_Type is access Integer;

end Direct_Io;package Io_Exceptions is

    Status_Error : exception;
    Mode_Error : exception;
    Name_Error : exception;
    Use_Error : exception;
    Device_Error : exception;
    End_Error : exception;
    Data_Error : exception;
    Layout_Error : exception;

end Io_Exceptions;-- Source code for SEQUENTIAL_IO

pragma Page;

with Io_Exceptions;

generic

    type Element_Type is private;

package Sequential_Io is

    type File_Type is limited private;

    type File_Mode is (In_File, Out_File);

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

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

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

    pragma Page;
private

    type File_Type is new Integer;

end Sequential_Io;with Basic_Io;
with Io_Exceptions;
package Text_Io is

    type File_Type is limited private;

    type File_Mode is (In_File, Out_File);

    type Count is range 0 .. 16_384;
    subtype Positive_Count is Count range 1 .. Count'Last;
    Unbounded : constant Count := 0; -- line and page length

    -- max. size of an integer output field 2#....#;
    subtype Field is Integer range 0 .. 1000;

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

    function Standard_Input return File_Type;
    function Standard_Output return File_Type;

    function Current_Input return File_Type;
    function Current_Output return File_Type;


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

    -- 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 Package for Input-Output of Intger 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 := 0;
                       Base : in Number_Base := Default_Base);
        procedure Put (Item : in Num;
                       Width : in Field := 0;
                       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 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 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 : 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

    type File_Type is
        record
            Ft : Integer := -1;
        end record;
    -- Unfortunately, we don't know what this is.

end Text_Io;package Calendar is

    type Time is private;

    subtype Year_Number is Integer range 1901 .. 2099;
    subtype Month_Number is Integer range 1 .. 12;
    subtype Day_Number is Integer range 1 .. 31;
    subtype Day_Duration is Duration range 0.0 .. 86_400.0;

    function Clock return Time;

    function Year (Date : Time) return Year_Number;
    function Month (Date : Time) return Month_Number;
    function Day (Date : Time) return Day_Number;
    function Seconds (Date : Time) return Day_Duration;

    procedure Split (Date : Time;
                     Year : out Year_Number;
                     Month : out Month_Number;
                     Day : out Day_Number;
                     Seconds : out Day_Duration);

    function Time_Of (Year : Year_Number;
                      Month : Month_Number;
                      Day : Day_Number;
                      Seconds : Day_Duration := 0.0) return Time;

    function "+" (Left : Time; Right : Duration) return Time;
    function "+" (Left : Duration; Right : Time) return Time;
    function "-" (Left : Time; Right : Duration) return Time;
    function "-" (Left : Time; Right : Time) return Duration;

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

    Time_Error : exception;  -- can be raised by TIME_OF, "+" and "-"

private
    type Time is
        record
            I : Integer;
        end record;
end Calendar;package Machine_Code is
end Machine_Code;package System is

    -- for integer'size use 32;

    type Address is access Integer;
    -- for address'size use 4*storage_unit;

    type Name is (Aix_6000);

    System_Name : constant Name := Aix_6000;

    Storage_Unit : constant := 8;

    Memory_Size : constant := 1024 * 1024 * 256;
    -- 256 Mb.

    -- System-Dependent Named Numbers:

    Min_Int : constant := -(2 ** 31);
    Max_Int : constant := (2 ** 31) - 1;
    Max_Digits : constant := 15;
    Max_Mantissa : constant := 31;
    Fine_Delta : constant := 1.0 / (2 ** Max_Mantissa);
    Tick : constant := 0.00006;


    -- Other System-dependent Declarations

    subtype Priority is Integer range 0 .. 255;


    Max_Object_Size : constant := (32 * 1024) - 1;
    Max_Record_Count : constant := (32 * 1024) - 1;
    Max_Text_Io_Count : constant := 16 * 1024;
    Max_Text_Io_Field : constant := 1000;

end System;package System2 is

    -- for integer'size use 32;

    type Private_Address is limited private;
    -- for address'size use 4*storage_unit;

    type Name is (Aix_6000);

    System_Name : constant Name := Aix_6000;

    Storage_Unit : constant := 8;

    Memory_Size : constant := 1024 * 1024 * 256;
    -- 256 Mb.

    -- System-Dependent Named Numbers:

    Min_Int : constant := -(2 ** 31);
    Max_Int : constant := (2 ** 31) - 1;
    Max_Digits : constant := 15;
    Max_Mantissa : constant := 31;
    Fine_Delta : constant := 1.0 / (2 ** Max_Mantissa);
    Tick : constant := 0.00006;


    -- Other System-dependent Declarations

    subtype Priority is Integer range 0 .. 255;


    Max_Object_Size : constant := (32 * 1024) - 1;
    Max_Record_Count : constant := (32 * 1024) - 1;
    Max_Text_Io_Count : constant := 16 * 1024;
    Max_Text_Io_Field : constant := 1000;

private
    type Private_Address is access Integer;

end System2;generic
    type Source is limited private;
    type Target is limited private;
function Unchecked_Conversion (S : Source) return Target;generic
    type Object is limited private;
    type Name is access Object;
procedure Unchecked_Deallocation (X : in out Name);package Ada_Debugging_Support is
    procedure Report_Current_Exception_Information;
end Ada_Debugging_Support;package Aix_Environment_Variables is
    function Expansion_Of (Variable_Name : in String) return String;
    function Expand_Embedded_Variables (Raw_String : in String) return String;
    procedure Export (Variable_Name, Value : in String);
end Aix_Environment_Variables;package Command_Line is
    subtype Return_Code_Type is Natural range 0 .. 255;
    Maximum_Command_String_Length : constant Natural := 4000;
    function Number_Of_Parameters return Natural;
    function Parameter (Parameter_Number : in Natural) return String;
    function Command_Name return String;
    function Parameters return String;
    procedure Set_Return_Code (Return_Code : in Return_Code_Type);
end Command_Line;with Gl_System_Types;
package Device is
    type Device is new Gl_System_Types.Uint16;
    type Devices_Type is array (Natural range <>) of Device;
    pragma Pack (Devices_Type);
    type Device_Value_Type is new Gl_System_Types.Int16;
    type Device_Values_Type is array (Natural range <>) of Device_Value_Type;
    pragma Pack (Device_Values_Type);
    subtype Valuator_Value_Type is Device_Value_Type;
    type Event_Type is
        record
            The_Device : Device;
            Datum : Device_Value_Type;
        end record;
    for Event_Type use
        record
            The_Device at 0 range 0 .. 15;
            Datum at 0 range 16 .. 31;
        end record;
    type Events_Type is array (Natural range <>) of Event_Type;
    pragma Pack (Events_Type);
    Nulldev : constant Device := 0;
    Butoffset : constant Device := 1;
    Valoffset : constant Device := 256;
    Wmeoffset : constant Device := 513;
    Timoffset : constant Device := 515;
    Xkbdoffset : constant Device := 143;
    Inoffset : constant Device := 1024;
    Outoffset : constant Device := 1033;
    Butcount : constant Device := 173;
    Valcount : constant Device := 20;
    Timcount : constant Device := 4;
    Xkbdcount : constant Device := 31;
    Incount : constant Device := 8;
    Outcount : constant Device := 8;
    Wmecount : constant Device := 32;
    But0 : constant Device := 1;
    But1 : constant Device := 2;
    But2 : constant Device := 3;
    But3 : constant Device := 4;
    But4 : constant Device := 5;
    But5 : constant Device := 6;
    But6 : constant Device := 7;
    But7 : constant Device := 8;
    But8 : constant Device := 9;
    But9 : constant Device := 10;
    But10 : constant Device := 11;
    But11 : constant Device := 12;
    But12 : constant Device := 13;
    But13 : constant Device := 14;
    But14 : constant Device := 15;
    But15 : constant Device := 16;
    But16 : constant Device := 17;
    But17 : constant Device := 18;
    But18 : constant Device := 19;
    But19 : constant Device := 20;
    But20 : constant Device := 21;
    But21 : constant Device := 22;
    But22 : constant Device := 23;
    But23 : constant Device := 24;
    But24 : constant Device := 25;
    But25 : constant Device := 26;
    But26 : constant Device := 27;
    But27 : constant Device := 28;
    But28 : constant Device := 29;
    But29 : constant Device := 30;
    But30 : constant Device := 31;
    But31 : constant Device := 32;
    But32 : constant Device := 33;
    But33 : constant Device := 34;
    But34 : constant Device := 35;
    But35 : constant Device := 36;
    But36 : constant Device := 37;
    But37 : constant Device := 38;
    But38 : constant Device := 39;
    But39 : constant Device := 40;
    But40 : constant Device := 41;
    But41 : constant Device := 42;
    But42 : constant Device := 43;
    But43 : constant Device := 44;
    But44 : constant Device := 45;
    But45 : constant Device := 46;
    But46 : constant Device := 47;
    But47 : constant Device := 48;
    But48 : constant Device := 49;
    But49 : constant Device := 50;
    But50 : constant Device := 51;
    But51 : constant Device := 52;
    But52 : constant Device := 53;
    But53 : constant Device := 54;
    But54 : constant Device := 55;
    But55 : constant Device := 56;
    But56 : constant Device := 57;
    But57 : constant Device := 58;
    But58 : constant Device := 59;
    But59 : constant Device := 60;
    But60 : constant Device := 61;
    But61 : constant Device := 62;
    But62 : constant Device := 63;
    But63 : constant Device := 64;
    But64 : constant Device := 65;
    But65 : constant Device := 66;
    But66 : constant Device := 67;
    But67 : constant Device := 68;
    But68 : constant Device := 69;
    But69 : constant Device := 70;
    But70 : constant Device := 71;
    But71 : constant Device := 72;
    But72 : constant Device := 73;
    But73 : constant Device := 74;
    But74 : constant Device := 75;
    But75 : constant Device := 76;
    But76 : constant Device := 77;
    But77 : constant Device := 78;
    But78 : constant Device := 79;
    But79 : constant Device := 80;
    But80 : constant Device := 81;
    But81 : constant Device := 82;
    But82 : constant Device := 83;
    But83 : constant Device := 84;
    But84 : constant Device := 85;
    But85 : constant Device := 86;
    But86 : constant Device := 87;
    Maxkbdbut : constant Device := 87;
    But100 : constant Device := 101;
    But101 : constant Device := 102;
    But102 : constant Device := 103;
    But110 : constant Device := 111;
    But111 : constant Device := 112;
    But112 : constant Device := 113;
    But113 : constant Device := 114;
    But114 : constant Device := 115;
    But115 : constant Device := 116;
    But116 : constant Device := 117;
    But117 : constant Device := 118;
    But118 : constant Device := 119;
    But119 : constant Device := 120;
    But120 : constant Device := 121;
    But121 : constant Device := 122;
    But122 : constant Device := 123;
    But123 : constant Device := 124;
    But124 : constant Device := 125;
    But125 : constant Device := 126;
    But126 : constant Device := 127;
    But127 : constant Device := 128;
    But128 : constant Device := 129;
    But129 : constant Device := 130;
    But130 : constant Device := 131;
    But131 : constant Device := 132;
    But132 : constant Device := 133;
    But133 : constant Device := 134;
    But134 : constant Device := 135;
    But135 : constant Device := 136;
    But136 : constant Device := 137;
    But137 : constant Device := 138;
    But138 : constant Device := 139;
    But139 : constant Device := 140;
    But140 : constant Device := 141;
    But141 : constant Device := 142;
    But142 : constant Device := 143;
    But143 : constant Device := 144;
    But144 : constant Device := 145;
    But145 : constant Device := 146;
    But146 : constant Device := 147;
    But147 : constant Device := 148;
    But148 : constant Device := 149;
    But149 : constant Device := 150;
    But150 : constant Device := 151;
    But151 : constant Device := 152;
    But152 : constant Device := 153;
    But153 : constant Device := 154;
    But154 : constant Device := 155;
    But155 : constant Device := 156;
    But156 : constant Device := 157;
    But157 : constant Device := 158;
    But158 : constant Device := 159;
    But159 : constant Device := 160;
    But160 : constant Device := 161;
    But161 : constant Device := 162;
    But162 : constant Device := 163;
    But163 : constant Device := 164;
    But164 : constant Device := 165;
    But165 : constant Device := 166;
    But166 : constant Device := 167;
    But167 : constant Device := 168;
    But168 : constant Device := 169;
    But169 : constant Device := 170;
    But170 : constant Device := 171;
    But171 : constant Device := 172;
    Mouse1 : constant Device := 101;
    Mouse2 : constant Device := 102;
    Mouse3 : constant Device := 103;
    Leftmouse : constant Device := 103;
    Middlemouse : constant Device := 102;
    Rightmouse : constant Device := 101;
    Lpenbut : constant Device := 104;
    Bpad0 : constant Device := 105;
    Bpad1 : constant Device := 106;
    Bpad2 : constant Device := 107;
    Bpad3 : constant Device := 108;
    Lpenvalid : constant Device := 109;
    Swbase : constant Device := 111;
    Sw0 : constant Device := 111;
    Sw1 : constant Device := 112;
    Sw2 : constant Device := 113;
    Sw3 : constant Device := 114;
    Sw4 : constant Device := 115;
    Sw5 : constant Device := 116;
    Sw6 : constant Device := 117;
    Sw7 : constant Device := 118;
    Sw8 : constant Device := 119;
    Sw9 : constant Device := 120;
    Sw10 : constant Device := 121;
    Sw11 : constant Device := 122;
    Sw12 : constant Device := 123;
    Sw13 : constant Device := 124;
    Sw14 : constant Device := 125;
    Sw15 : constant Device := 126;
    Sw16 : constant Device := 127;
    Sw17 : constant Device := 128;
    Sw18 : constant Device := 129;
    Sw19 : constant Device := 130;
    Sw20 : constant Device := 131;
    Sw21 : constant Device := 132;
    Sw22 : constant Device := 133;
    Sw23 : constant Device := 134;
    Sw24 : constant Device := 135;
    Sw25 : constant Device := 136;
    Sw26 : constant Device := 137;
    Sw27 : constant Device := 138;
    Sw28 : constant Device := 139;
    Sw29 : constant Device := 140;
    Sw30 : constant Device := 141;
    Sw31 : constant Device := 142;
    Akey : constant Device := 11;
    Bkey : constant Device := 36;
    Ckey : constant Device := 28;
    Dkey : constant Device := 18;
    Ekey : constant Device := 17;
    Fkey : constant Device := 19;
    Gkey : constant Device := 26;
    Hkey : constant Device := 27;
    Ikey : constant Device := 40;
    Jkey : constant Device := 34;
    Kkey : constant Device := 35;
    Lkey : constant Device := 42;
    Mkey : constant Device := 44;
    Nkey : constant Device := 37;
    Okey : constant Device := 41;
    Pkey : constant Device := 48;
    Qkey : constant Device := 10;
    Rkey : constant Device := 24;
    Skey : constant Device := 12;
    Tkey : constant Device := 25;
    Ukey : constant Device := 33;
    Vkey : constant Device := 29;
    Wkey : constant Device := 16;
    Xkey : constant Device := 21;
    Ykey : constant Device := 32;
    Zkey : constant Device := 20;
    Zerokey : constant Device := 46;
    Onekey : constant Device := 8;
    Twokey : constant Device := 14;
    Threekey : constant Device := 15;
    Fourkey : constant Device := 22;
    Fivekey : constant Device := 23;
    Sixkey : constant Device := 30;
    Sevenkey : constant Device := 31;
    Eightkey : constant Device := 38;
    Ninekey : constant Device := 39;
    Breakkey : constant Device := 1;
    Setupkey : constant Device := 2;
    Ctrlkey : constant Device := 3;
    Leftctrlkey : constant Device := Ctrlkey;
    Capslockkey : constant Device := 4;
    Rightshiftkey : constant Device := 5;
    Leftshiftkey : constant Device := 6;
    Noscrlkey : constant Device := 13;
    Esckey : constant Device := 7;
    Tabkey : constant Device := 9;
    Retkey : constant Device := 51;
    Spacekey : constant Device := 83;
    Linefeedkey : constant Device := 60;
    Backspacekey : constant Device := 61;
    Delkey : constant Device := 62;
    Semicolonkey : constant Device := 43;
    Periodkey : constant Device := 52;
    Commakey : constant Device := 45;
    Quotekey : constant Device := 50;
    Accentgravekey : constant Device := 55;
    Minuskey : constant Device := 47;
    Virgulekey : constant Device := 53;
    Backslashkey : constant Device := 57;
    Equalkey : constant Device := 54;
    Leftbracketkey : constant Device := 49;
    Rightbracketkey : constant Device := 56;
    Leftarrowkey : constant Device := 73;
    Downarrowkey : constant Device := 74;
    Rightarrowkey : constant Device := 80;
    Uparrowkey : constant Device := 81;
    Pad0 : constant Device := 59;
    Pad1 : constant Device := 58;
    Pad2 : constant Device := 64;
    Pad3 : constant Device := 65;
    Pad4 : constant Device := 63;
    Pad5 : constant Device := 69;
    Pad6 : constant Device := 70;
    Pad7 : constant Device := 67;
    Pad8 : constant Device := 68;
    Pad9 : constant Device := 75;
    Padpf1 : constant Device := 72;
    Padpf2 : constant Device := 71;
    Padpf3 : constant Device := 79;
    Padpf4 : constant Device := 78;
    Padperiod : constant Device := 66;
    Padminus : constant Device := 76;
    Padcomma : constant Device := 77;
    Padenter : constant Device := 82;
    Leftaltkey : constant Device := 143;
    Rightaltkey : constant Device := 144;
    Rightctrlkey : constant Device := 145;
    F1key : constant Device := 146;
    F2key : constant Device := 147;
    F3key : constant Device := 148;
    F4key : constant Device := 149;
    F5key : constant Device := 150;
    F6key : constant Device := 151;
    F7key : constant Device := 152;
    F8key : constant Device := 153;
    F9key : constant Device := 154;
    F10key : constant Device := 155;
    F11key : constant Device := 156;
    F12key : constant Device := 157;
    Printscreenkey : constant Device := 158;
    Scrolllockkey : constant Device := 159;
    Pausekey : constant Device := 160;
    Insertkey : constant Device := 161;
    Homekey : constant Device := 162;
    Pageupkey : constant Device := 163;
    Endkey : constant Device := 164;
    Pagedownkey : constant Device := 165;
    Numlockkey : constant Device := 166;
    Padvirgulekey : constant Device := 167;
    Padasterkey : constant Device := 168;
    Padpluskey : constant Device := 169;
    Sgireserved : constant Device := 256;
    Dial0 : constant Device := 257;
    Dial1 : constant Device := 258;
    Dial2 : constant Device := 259;
    Dial3 : constant Device := 260;
    Dial4 : constant Device := 261;
    Dial5 : constant Device := 262;
    Dial6 : constant Device := 263;
    Dial7 : constant Device := 264;
    Dial8 : constant Device := 265;
    Mousex : constant Device := 266;
    Mousey : constant Device := 267;
    Lpenx : constant Device := 268;
    Lpeny : constant Device := 269;
    Bpadx : constant Device := 270;
    Bpady : constant Device := 271;
    Cursorx : constant Device := 272;
    Cursory : constant Device := 273;
    Ghostx : constant Device := 274;
    Ghosty : constant Device := 275;
    Timer0 : constant Device := 515;
    Timer1 : constant Device := 516;
    Timer2 : constant Device := 517;
    Timer3 : constant Device := 518;
    Keybd : constant Device := 513;
    Rawkeybd : constant Device := 514;
    Valmark : constant Device := 523;
    Gerror : constant Device := 524;
    Redraw : constant Device := 528;
    Wmsend : constant Device := 529;
    Wmreply : constant Device := 530;
    Wmgfclose : constant Device := 531;
    Wmtxclose : constant Device := 532;
    Modechange : constant Device := 533;
    Inputchange : constant Device := 534;
    Qfull : constant Device := 535;
    Piecechange : constant Device := 536;
    Winclose : constant Device := 537;
    Qreaderror : constant Device := 538;
    Winfreeze : constant Device := 539;
    Winthaw : constant Device := 540;
    Redrawiconic : constant Device := 541;
    Winquit : constant Device := 542;
    Depthchange : constant Device := 543;
    Keybdfnames : constant Device := 544;
    Keybdfstrings : constant Device := 545;
    Winshut : constant Device := 546;
    Input0 : constant Device := 1024;
    Input1 : constant Device := 1025;
    Input2 : constant Device := 1026;
    Input3 : constant Device := 1027;
    Input4 : constant Device := 1028;
    Input5 : constant Device := 1029;
    Input6 : constant Device := 1030;
    Input7 : constant Device := 1032;
    Output0 : constant Device := 1033;
    Output1 : constant Device := 1034;
    Output2 : constant Device := 1035;
    Output3 : constant Device := 1036;
    Output4 : constant Device := 1037;
    Output5 : constant Device := 1038;
    Output6 : constant Device := 1039;
    Output7 : constant Device := 1040;
    Maxsgidevice : constant Device := 20000;
    Menubutton : constant Device := Rightmouse;
    function Isbutton (A_Device : Device) return Boolean;
    function Isvaluator (A_Device : Device) return Boolean;
    function Istimer (A_Device : Device) return Boolean;
    function Iswmevent (A_Device : Device) return Boolean;
    function Isdial (A_Device : Device) return Boolean;
    function Islpen (A_Device : Device) return Boolean;
    function Islpenbut (A_Device : Device) return Boolean;
    function Isbpadbut (A_Device : Device) return Boolean;
    function Issw (A_Device : Device) return Boolean;
    function Isstdkeybd (A_Device : Device) return Boolean;
    function Isxkeybd (A_Device : Device) return Boolean;
    function Iskeybd (A_Device : Device) return Boolean;
    function Isinput (A_Device : Device) return Boolean;
    function Isoutput (A_Device : Device) return Boolean;
    pragma Inline (Isbutton);
    pragma Inline (Isvaluator);
    pragma Inline (Istimer);
    pragma Inline (Iswmevent);
    pragma Inline (Isdial);
    pragma Inline (Islpen);
    pragma Inline (Islpenbut);
    pragma Inline (Isbpadbut);
    pragma Inline (Issw);
    pragma Inline (Isstdkeybd);
    pragma Inline (Isxkeybd);
    pragma Inline (Iskeybd);
    pragma Inline (Isinput);
    pragma Inline (Isoutput);
end Device;with Generic_Elementary_Functions;  
package Elementary_Functions is  
   new Generic_Elementary_Functions (Float);  package Elementary_Functions_Exceptions is  
    Argument_Error : exception;  
end Elementary_Functions_Exceptions;  with Generic_Math;
package Fast_Math is new Generic_Math (True);with Elementary_Functions_Exceptions;  
generic  
    type Float_Type is digits <>;  
package Generic_Elementary_Functions is  
    function Sqrt (X : Float_Type) return Float_Type;  
    function Log (X : Float_Type) return Float_Type;  
    function Log (X, Base : Float_Type) return Float_Type;  
    function Exp (X : Float_Type) return Float_Type;  
    function "**" (X, Y : Float_Type) return Float_Type;  
    function Sin (X : Float_Type) return Float_Type;  
    function Sin (X, Cycle : Float_Type) return Float_Type;  
    function Cos (X : Float_Type) return Float_Type;  
    function Cos (X, Cycle : Float_Type) return Float_Type;  
    function Tan (X : Float_Type) return Float_Type;  
    function Tan (X, Cycle : Float_Type) return Float_Type;  
    function Cot (X : Float_Type) return Float_Type;  
    function Cot (X, Cycle : Float_Type) return Float_Type;  
    function Arcsin (X : Float_Type) return Float_Type;  
    function Arcsin (X, Cycle : Float_Type) return Float_Type;  
    function Arccos (X : Float_Type) return Float_Type;  
    function Arccos (X, Cycle : Float_Type) return Float_Type;  
    function Arctan (Y : Float_Type;  
                     X : Float_Type := 1.0) return Float_Type;  
    function Arctan (Y : Float_Type;  
                     X : Float_Type := 1.0;  
                     Cycle : Float_Type) return Float_Type;  
    function Arccot (X : Float_Type;  
                     Y : Float_Type := 1.0) return Float_Type;  
    function Arccot (X : Float_Type;  
                     Y : Float_Type := 1.0;  
                     Cycle : Float_Type) return Float_Type;  
    function Sinh (X : Float_Type) return Float_Type;  
    function Cosh (X : Float_Type) return Float_Type;  
    function Tanh (X : Float_Type) return Float_Type;  
    function Coth (X : Float_Type) return Float_Type;  
    function Arcsinh (X : Float_Type) return Float_Type;  
    function Arccosh (X : Float_Type) return Float_Type;  
    function Arctanh (X : Float_Type) return Float_Type;  
    function Arccoth (X : Float_Type) return Float_Type;  
    Argument_Error : exception renames Elementary_Functions_Exceptions.  
                                       Argument_Error;  
end Generic_Elementary_Functions;  with System;
generic
    Fast : Boolean := False;
package Generic_Math is
    M_E : constant Long_Float := 2.7182818284590452354E0;
    M_Log2e : constant Long_Float := 1.4426950408889633870E0;
    M_Log10e : constant Long_Float := 4.3429448190325181667E-1;
    M_Ln2 : constant Long_Float := 6.9314718055994530942E-1;
    M_Ln10 : constant Long_Float := 2.3025850929940456840E0;
    M_Pi : constant Long_Float := 3.1415926535897931160E0;
    M_2pi : constant Long_Float := 6.2831853071795862320E0;
    M_Pi_2 : constant Long_Float := 1.5707963267948965580E0;
    M_Pi_4 : constant Long_Float := 7.8539816339744827900E-1;
    M_1_Pi : constant Long_Float := 3.1830988618379067154E-1;
    M_2_Pi : constant Long_Float := 6.3661977236758134308E-1;
    M_2_Sqrtpi : constant Long_Float := 1.1283791670955125739E0;
    M_Sqrt2 : constant Long_Float := 1.4142135623730951455E0;
    M_Sqrt_2 : constant Long_Float := 7.0710678118654752440E-1;
    Erange : constant Integer := 34;  
    Edom : constant Integer := 33;  
    Fp_Plus_Norm : constant Integer := 0;  
    Fp_Minus_Norm : constant Integer := 1;  
    Fp_Plus_Denorm : constant Integer := 6;  
    Fp_Minus_Denorm : constant Integer := 7;  
    Fp_Plus_Zero : constant Integer := 2;  
    Fp_Minus_Zero : constant Integer := 3;  
    Fp_Plus_Inf : constant Integer := 4;  
    Fp_Minus_Inf : constant Integer := 5;  
    Fp_Snan : constant Integer := 8;  
    Fp_Qnan : constant Integer := 9;  
    subtype Long_Positive_Float is
       Long_Float range Long_Float'Safe_Small .. Long_Float'Safe_Large;
    subtype Long_Natural_Float is Long_Float range 0.0 .. Long_Float'Safe_Large;
    subtype Long_Plus1_Float is Long_Float range 1.0 .. Long_Float'Safe_Large;
    subtype Long_Minus1_Float is Long_Float range -1.0 .. Long_Float'Safe_Large;
    subtype Unity_Range is Long_Float range -1.0 .. 1.0;
    type Long_Complex_Float is
        record
            Real : Long_Float;
            Imaginary : Long_Float;
        end record;
    function Errno return Integer;
    pragma Inline (Errno);
    function Exponent (Value : in Long_Float) return Integer;
    pragma Inline (Exponent);
    function Mantissa (Value : in Long_Float) return Long_Float;
    pragma Inline (Mantissa);
    function Ldexp (Mant : in Long_Float; Exp : in Integer) return Long_Float;
    pragma Inline (Ldexp);
    function Fraction (Value : in Long_Float) return Long_Float;
    pragma Inline (Fraction);
    function Integral (Value : in Long_Float) return Long_Float;
    pragma Inline (Integral);
    function Atof (X : in String) return Long_Float;
    pragma Inline (Atof);
    function J0 (X : in Long_Float) return Long_Float;
    pragma Inline (J0);
    function J1 (X : in Long_Float) return Long_Float;
    pragma Inline (J1);
    function Jn (N : in Integer; X : in Long_Float) return Long_Float;
    pragma Inline (Jn);
    function Y0 (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Y0);
    function Y1 (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Y1);
    function Yn (N : in Integer; X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Yn);
    function Erf (X : in Long_Float) return Long_Float;
    pragma Inline (Erf);
    function Erfc (X : in Long_Float) return Long_Float;
    pragma Inline (Erfc);
    function Exp (X : in Long_Float) return Long_Float;
    pragma Inline (Exp);
    function Expm1 (X : in Long_Float) return Long_Float;
    pragma Inline (Expm1);
    function Log (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Log);
    function Log10 (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Log10);
    function Ln (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Ln);
    function "**" (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline ("**");
    function Sqrt (X : in Long_Natural_Float) return Long_Float;
    pragma Inline (Sqrt);
    function Ceil (X : in Long_Float) return Long_Float;
    pragma Inline (Ceil);
    function Floor (X : in Long_Float) return Long_Float;
    pragma Inline (Floor);
    function "abs" (X : in Long_Float) return Long_Float;
    pragma Inline ("abs");
    function "mod" (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline ("mod");
    function Gamma (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Gamma);
    function Signgam (X : in Long_Positive_Float) return Integer;
    pragma Inline (Signgam);
    function Hypot (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline (Hypot);
    function Sin (X : in Long_Float) return Long_Float;
    pragma Inline (Sin);
    function Cos (X : in Long_Float) return Long_Float;
    pragma Inline (Cos);
    function Tan (X : in Long_Float) return Long_Float;
    pragma Inline (Tan);
    function Asin (X : in Unity_Range) return Long_Float;
    pragma Inline (Asin);
    function Acos (X : in Unity_Range) return Long_Float;
    pragma Inline (Acos);
    function Atan (X : in Long_Float) return Long_Float;
    pragma Inline (Atan);
    function Sinh (X : in Long_Float) return Long_Float;
    pragma Inline (Sinh);
    function Cosh (X : in Long_Float) return Long_Float;
    pragma Inline (Cosh);
    function Tanh (X : in Long_Float) return Long_Float;
    pragma Inline (Tanh);
    function Atan2 (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline (Atan2);
    function Copysign (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline (Copysign);
    function "abs" (X : in Long_Complex_Float) return Long_Float;
    pragma Inline ("abs");
    function Nearest (X : in Long_Float) return Long_Float;
    pragma Inline (Nearest);
    function Truncate (X : in Long_Float) return Long_Float;
    pragma Inline (Truncate);
    function Truncate (X : in Long_Float) return Integer;
    pragma Inline (Truncate);
    function Rint (X : in Long_Float) return Long_Float;
    pragma Inline (Rint);
    function Exp_E (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline (Exp_E);
    function Log1p (X : in Long_Minus1_Float) return Long_Float;
    pragma Inline (Log1p);
    function Log_L (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Log_L);
    function Logb (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Logb);
    function Logb (X : in Long_Positive_Float) return Integer;
    pragma Inline (Logb);
    function Lgamma (X : in Long_Positive_Float) return Long_Float;
    pragma Inline (Lgamma);
    function Asinh (X : in Long_Float) return Long_Float;
    pragma Inline (Asinh);
    function Acosh (X : in Long_Plus1_Float) return Long_Float;
    pragma Inline (Acosh);
    function Atanh (X : in Long_Float) return Long_Float;
    pragma Inline (Atanh);
    function "rem" (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline ("rem");
    function Class (X : in Long_Float) return Integer;
    pragma Inline (Class);
    function Isnan (X : in Long_Float) return Integer;
    pragma Inline (Isnan);
    function Finite (X : in Long_Float) return Integer;
    pragma Inline (Finite);
    function Cbrt (X : in Long_Float) return Long_Float;
    pragma Inline (Cbrt);
    function Long_To_Int (X : in Long_Float) return Integer;
    pragma Inline (Long_To_Int);
    function Unordered (X : in Long_Float; Y : in Long_Float) return Integer;
    pragma Inline (Unordered);
    function Next_After
                (X : in Long_Float; Y : in Long_Float) return Long_Float;
    pragma Inline (Next_After);
    function Scalb (X : in Long_Float; N : in Integer) return Long_Float;
    pragma Inline (Scalb);
end Generic_Math;generic
    type Float_Type is digits <>;
    type Exponent_Type is range <>;
package Generic_Primitive_Functions is
    procedure Decompose (X : in Float_Type;
                         Fract : out Float_Type;
                         Exp : out Exponent_Type);
    function Exponent (X : Float_Type) return Exponent_Type;
    function Scale (X : Float_Type; Exp : Exponent_Type) return Float_Type;
    function Round (X : Float_Type) return Float_Type;  
    function Truncate (X : Float_Type) return Float_Type;
    function Leading_Part (X : Float_Type; Ndigits : Integer) return Float_Type;
    function "rem" (X, Y : Float_Type) return Float_Type;
    function Copy_Sign (Value, Sign : Float_Type) return Float_Type;
end Generic_Primitive_Functions;with Gl_System_Types;
with Gl_Flags;
with Device;
package Gl is
    use Gl_System_Types;
    subtype Short_Natural is Natural
                                range 0 .. Natural (Gl_System_Types.Int16'Last);
    subtype Short_Positive is Short_Natural range 1 .. Short_Natural'Last;
    type Angle is new Gl_System_Types.Int16;
    type Colorindex is new Gl_System_Types.Uint16;
    type Coord is new Gl_System_Types.Float32;
    type Icoord is new Gl_System_Types.Int32;
    type Linestyle is new Gl_System_Types.Ushort;
    type Object is new Gl_System_Types.Long;
    type Offset is new Gl_System_Types.Long;
    type Rgbvalue is new Gl_System_Types.Uint8;
    type Scoord is new Gl_System_Types.Int16;
    type Screencoord is new Gl_System_Types.Int16;
    type Tag is new Gl_System_Types.Long;
    Starttag : constant Tag := -2;
    Endtag : constant Tag := -3;
    type X_Display_Pointer is new Gl_System_Types.Int32;
    type X_Window is new Gl_System_Types.Int32;
    type Rgb_Value is new Gl_System_Types.Int16
                             range 0 .. Gl_System_Types.Int16'Last;
    subtype Rgba_Value is Rgb_Value;
    type Basis_Id_Type is new Gl_System_Types.Int32;
    type Cursor_Id_Type is new Gl_System_Types.Int16;
    type Font_Id_Type is new Gl_System_Types.Int32;
    type Linestyle_Id_Type is new Gl_System_Types.Int32;
    Default_Linestyle : constant Linestyle_Id_Type := 0;
    type Lm_Id_Type is new Gl_System_Types.Int32;
    type Map_Id_Type is new Gl_System_Types.Int16;
    type Menu_Id_Type is new Gl_System_Types.Int32;
    type Pattern_Id_Type is new Gl_System_Types.Int32;
    type Window_Id_Type is new Gl_System_Types.Int32;
    type Rgb_Bit_Plane_Type is range 0 .. 7;
    package Rgb_Write_Mask_Flags is new Gl_Flags
                                           (Base_Type => Gl_System_Types.Uint16,
                                            Numbering => Rgb_Bit_Plane_Type);
    type Rgb_Write_Mask_Type is new Rgb_Write_Mask_Flags.Flags_Type;
    package Packed_Rgb_Write_Mask_Flags is
       new Gl_Flags (Base_Type => Gl_System_Types.Uint8,
                     Numbering => Rgb_Bit_Plane_Type);
    type Packed_Rgb_Write_Mask_Type is
       new Packed_Rgb_Write_Mask_Flags.Flags_Type;
    type Packed_Rgba_Write_Masks_Type is
        record
            Alpha : Packed_Rgb_Write_Mask_Type;
            Blue : Packed_Rgb_Write_Mask_Type;
            Green : Packed_Rgb_Write_Mask_Type;
            Red : Packed_Rgb_Write_Mask_Type;
        end record;
    for Packed_Rgba_Write_Masks_Type use
        record
            Alpha at 0 range 0 .. 7;
            Blue at 0 range 8 .. 15;
            Green at 0 range 16 .. 23;
            Red at 0 range 24 .. 31;
        end record;
    type Bit_Plane_Type is range 0 .. 11;
    package Write_Mask_Flags is new Gl_Flags
                                       (Base_Type => Gl_System_Types.Uint16,
                                        Numbering => Bit_Plane_Type);
    type Write_Mask_Type is new Write_Mask_Flags.Flags_Type;
    type Lamp_Number_Type is range 0 .. 7;
    package Lamp_Flags is new Gl_Flags (Base_Type => Gl_System_Types.Uint8,
                                        Numbering => Lamp_Number_Type);
    type Lamps_Type is new Lamp_Flags.Flags_Type;
    type Z_Bit_Plane_Type is range 0 .. 31;
    package Z_Write_Mask_Flags is new Gl_Flags
                                         (Base_Type => Gl_System_Types.Uint32,
                                          Numbering => Z_Bit_Plane_Type);
    type Z_Write_Mask_Type is new Z_Write_Mask_Flags.Flags_Type;
    type Dial_And_Box_Light_Number_Type is range 0 .. 31;
    package Dial_And_Box_Light_Flags is
       new Gl_Flags (Base_Type => Gl_System_Types.Uint32,
                     Numbering => Dial_And_Box_Light_Number_Type);
    type Dial_And_Box_Lights_Type is new Dial_And_Box_Light_Flags.Flags_Type;
    type Floatangle is new Gl_System_Types.Float32;
    type Colorindices is array (Natural range <>) of Colorindex;
    type Colorfloatindex is new Gl_System_Types.Float32;
    type Dcoord is new Gl_System_Types.Float64;
    type Vertical_Retraces_Type is new Gl_System_Types.Int16;
    type Font_Pixels_Type is new Gl_System_Types.Int16;
    type Linestyle_Repeat_Type is new Gl_System_Types.Int32;
    type Z_Value_Type is new Gl_System_Types.Int32
                                range -16#800000# .. 16#7FFFFF#;
    type Z_Values_Type is array (Positive range <>) of Z_Value_Type;
    pragma Pack (Z_Values_Type);
    type Name_Type is new Gl_System_Types.Int16;
    type Names_Type is array (Positive range <>) of Name_Type;
    pragma Pack (Names_Type);
    type Aspect_Ratio_Type is new Gl_System_Types.Float32;
    type Menu_Item_Type is new Gl_System_Types.Int32;
    No_Menu_Item : constant Menu_Item_Type := -1;
    type Pixels is new Gl_System_Types.Int32
                          range 0 .. Gl_System_Types.Int32'Last;
    type Short_Pixels is new Gl_System_Types.Int16
                                range 0 .. Gl_System_Types.Int16'Last;
    No_Object : constant Object := -1;
    subtype Scale_Factor is Float;
    subtype Axis_Type is Character;  
    X_Axis : constant Axis_Type := 'x';
    Y_Axis : constant Axis_Type := 'y';
    Z_Axis : constant Axis_Type := 'z';
    subtype Coordinate_Axis_Type is Natural range 0 .. 3;
    X : constant Coordinate_Axis_Type := 0;
    Y : constant Coordinate_Axis_Type := 1;
    Z : constant Coordinate_Axis_Type := 2;
    W : constant Coordinate_Axis_Type := 3;
    subtype Control_Point_Coordinate_Type is Coordinate_Axis_Type;
    Wx : constant Control_Point_Coordinate_Type := 0;
    Wy : constant Control_Point_Coordinate_Type := 1;
    Wz : constant Control_Point_Coordinate_Type := 2;
    Ww : constant Control_Point_Coordinate_Type := 2;
    type Ivector_2d is array (X .. Y) of Icoord;
    for Ivector_2d'Size use 2 * Icoord'Size;
    type Ivectors_2d is array (Natural range <>) of Ivector_2d;
    pragma Pack (Ivectors_2d);
    type Svector_2d is array (X .. Y) of Scoord;
    for Svector_2d'Size use 2 * Scoord'Size;
    type Svectors_2d is array (Natural range <>) of Svector_2d;
    pragma Pack (Svectors_2d);
    type Vector_2d is array (X .. Y) of Coord;
    for Vector_2d'Size use 2 * Coord'Size;
    type Vectors_2d is array (Natural range <>) of Vector_2d;
    pragma Pack (Vectors_2d);
    type Dvector_2d is array (X .. Y) of Dcoord;
    for Dvector_2d'Size use 2 * Dcoord'Size;
    type Dvectors_2d is array (Natural range <>) of Dvector_2d;
    pragma Pack (Dvectors_2d);
    type Ivector_3d is array (X .. Z) of Icoord;
    for Ivector_3d'Size use 3 * Icoord'Size;
    type Ivectors_3d is array (Natural range <>) of Ivector_3d;
    pragma Pack (Ivectors_3d);
    type Svector_3d is array (X .. Z) of Scoord;
    for Svector_3d'Size use 3 * Scoord'Size;
    type Svectors_3d is array (Natural range <>) of Svector_3d;
    pragma Pack (Svectors_3d);
    type Vector_3d is array (X .. Z) of Coord;
    for Vector_3d'Size use 3 * Coord'Size;
    type Vectors_3d is array (Natural range <>) of Vector_3d;
    pragma Pack (Vectors_3d);
    type Dvector_3d is array (X .. Z) of Dcoord;
    for Dvector_3d'Size use 3 * Dcoord'Size;
    type Dvectors_3d is array (Natural range <>) of Dvector_3d;
    pragma Pack (Dvectors_3d);
    type Svector_4d is array (X .. W) of Scoord;
    for Svector_4d'Size use 4 * Scoord'Size;
    type Svectors_4d is array (Natural range <>) of Svector_4d;
    pragma Pack (Svectors_4d);
    type Ivector_4d is array (X .. W) of Icoord;
    for Ivector_4d'Size use 4 * Icoord'Size;
    type Ivectors_4d is array (Natural range <>) of Ivector_4d;
    pragma Pack (Ivectors_4d);
    type Vector_4d is array (X .. W) of Coord;
    for Vector_4d'Size use 4 * Coord'Size;
    type Vectors_4d is array (Natural range <>) of Vector_4d;
    pragma Pack (Vectors_4d);
    type Dvector_4d is array (X .. W) of Dcoord;
    for Dvector_4d'Size use 4 * Dcoord'Size;
    type Dvectors_4d is array (Natural range <>) of Dvector_4d;
    pragma Pack (Dvectors_4d);
    type Points_3d is array (Natural range <>) of Vector_3d;
    pragma Pack (Points_3d);
    subtype Points4_3d is Points_3d (1 .. 4);
    subtype Rationalcurvecontrol_Type is Vectors_4d;
    subtype Rationalcurvecontrol4_Type is Rationalcurvecontrol_Type (0 .. 3);
    subtype Nurbs_Control_Point_2d is Dvector_2d;
    subtype Nurbs_Control_Point_3d is Dvector_3d;
    subtype Nurbs_Control_Point_4d is Dvector_4d;
    subtype Nurbs_Control_Points_2d is Dvectors_2d;
    subtype Nurbs_Control_Points_3d is Dvectors_3d;
    subtype Nurbs_Control_Points_4d is Dvectors_4d;
    type Nurbs_Control_Matrix_3d is
       array (Natural range <>, Natural range <>) of Nurbs_Control_Point_3d;
    pragma Pack (Nurbs_Control_Matrix_3d);
    type Nurbs_Control_Matrix_4d is
       array (Natural range <>, Natural range <>) of Nurbs_Control_Point_4d;
    pragma Pack (Nurbs_Control_Matrix_4d);
    type Bitplanes_Type is new Gl_System_Types.Int32;
    type Matrix_Element_Type is new Gl_System_Types.Float32;
    type Matrix is array (1 .. 4, 1 .. 4) of Matrix_Element_Type;
    for Matrix'Size use 16 * Matrix_Element_Type'Size;
    type Bitmap_Element_Type is new Gl_System_Types.Uint16;
    type Bitmap_Type is array (Natural range <>) of Bitmap_Element_Type;
    pragma Pack (Bitmap_Type);
    type Rgb_Values is array (Natural range <>) of Rgb_Value;
    pragma Pack (Rgb_Values);
    type Rgbvalues is array (Natural range <>) of Rgbvalue;
    pragma Pack (Rgbvalues);
    type Alphavalue is range 0 .. 255;
    for Alphavalue'Size use 8;
    subtype Rgba_Component_Type is Natural range 0 .. 3;
    subtype Rgb_Component_Type is Rgba_Component_Type range 0 .. 2;
    Red : constant Rgba_Component_Type := 0;
    Green : constant Rgba_Component_Type := 1;
    Blue : constant Rgba_Component_Type := 2;
    Alpha : constant Rgba_Component_Type := 3;
    type Rgb_Float_Value_Type is new Float range 0.0 .. 1.0;
    subtype Rgba_Float_Value_Type is Rgb_Float_Value_Type;
    type Rgb_Color_Type is array (Rgb_Component_Type) of Rgb_Value;
    for Rgb_Color_Type'Size use 48;
    type Rgb_Float_Color_Type is
       array (Rgb_Component_Type) of Rgb_Float_Value_Type;
    for Rgb_Float_Color_Type'Size use 3 * Rgb_Float_Value_Type'Size;
    type Rgba_Color_Type is array (Rgba_Component_Type) of Rgba_Value;
    for Rgba_Color_Type'Size use 64;
    type Rgba_Float_Color_Type is
       array (Rgba_Component_Type) of Rgba_Float_Value_Type;
    for Rgba_Float_Color_Type'Size use 4 * Rgba_Float_Value_Type'Size;
    type S_Rgb_Color_Type is array (Rgb_Component_Type) of Short_Integer;
    for S_Rgb_Color_Type'Size use 48;
    type I_Rgb_Color_Type is array (Rgb_Component_Type) of Integer;
    for I_Rgb_Color_Type'Size use 96;
    type S_Rgba_Color_Type is array (Rgba_Component_Type) of Short_Integer;
    for S_Rgba_Color_Type'Size use 64;
    type I_Rgba_Color_Type is array (Rgba_Component_Type) of Integer;
    for I_Rgba_Color_Type'Size use 128;
    type Buffer_Mode_Type is (Nobuffer, Bckbuffer, Frntbuffer,
                              Bothbuffers, Drawzbuffer);
    for Buffer_Mode_Type use (0, 1, 2, 3, 4);
    type Nurbs_Property_Type is (N_Pixel_Tolerance, N_Culling, N_Display,
                                 N_Errorchecking, N_Subdivisions,
                                 N_S_Steps, N_T_Steps, N_Tiles);
    for Nurbs_Property_Type use (1, 2, 3, 4, 5, 6, 7, 8);
    type Control_Point_Type is (N_St, N_Stw, N_Wst, N_Xyz, N_Xyzw, N_Wxyz);
    for Control_Point_Type use (16#8#, 16#D#, 16#F#, 16#4C#, 16#51#, 16#53#);
    subtype Nurbs_Curve_Control_Point_Type is
       Control_Point_Type range N_St .. N_Stw;
    subtype Nurbs_Surface_Control_Point_Type is
       Control_Point_Type range N_Xyz .. N_Xyzw;
    type Shade_Model_Type is (Flat, Gouraud);
    for Shade_Model_Type use (0, 1);
    type Matrix_Mode_Type is (Msingle, Mprojection, Mviewing);
    for Matrix_Mode_Type use (0, 1, 2);
    type Display_Mode_Type is (Dmrgb, Dmsingle, Dmdouble, Dmrgbdouble);
    for Display_Mode_Type use (0, 1, 2, 5);
    type Lm_Target_Type is (Material, Light0, Light1, Light2, Light3,
                            Light4, Light5, Light6, Light7, Lmodel);
    for Lm_Target_Type use (1000, 1100, 1101, 1102, 1103,
                            1104, 1105, 1106, 1107, 1200);
    type Lm_Definition_Type is (Defmaterial, Deflight, Deflmodel);
    for Lm_Definition_Type use (0, 100, 200);
    type Lm_Property_Type is new Gl_System_Types.Float32;
    type Lm_Property_List_Type is array (Natural range <>) of Lm_Property_Type;
    package Lm_Properties is
        Emission : constant Lm_Property_Type := Lm_Property_Type (1);
        Ambient : constant Lm_Property_Type := Lm_Property_Type (2);
        Diffuse : constant Lm_Property_Type := Lm_Property_Type (3);
        Specular : constant Lm_Property_Type := Lm_Property_Type (4);
        Shininess : constant Lm_Property_Type := Lm_Property_Type (5);
        Colorindexes : constant Lm_Property_Type := Lm_Property_Type (6);
        Alpha : constant Lm_Property_Type := Lm_Property_Type (7);
        Lcolor : constant Lm_Property_Type := Lm_Property_Type (101);
        Position : constant Lm_Property_Type := Lm_Property_Type (102);
        Spotdirection : constant Lm_Property_Type := Lm_Property_Type (103);
        Spotlight : constant Lm_Property_Type := Lm_Property_Type (104);
        Localviewer : constant Lm_Property_Type := Lm_Property_Type (201);
        Attenuation : constant Lm_Property_Type := Lm_Property_Type (202);
        Lmnull : constant Lm_Property_Type := 0.0;
    end Lm_Properties;
    type Lm_Color_Type is (Lmc_Color, Lmc_Emission, Lmc_Ambient,
                           Lmc_Diffuse, Lmc_Specular, Lmc_Ad, Lmc_Null);
    for Lm_Color_Type use (0, 1, 2, 3, 4, 5, 6);
    type Logical_Operation_Type is (Lo_Zero, Lo_And, Lo_Andr, Lo_Src,
                                    Lo_Andi, Lo_Dst, Lo_Xor, Lo_Or, Lo_Nor,
                                    Lo_Xnor, Lo_Ndst, Lo_Orr, Lo_Nsrc,
                                    Lo_Ori, Lo_Nand, Lo_One, Lo_Min, Lo_Max,
                                    Lo_Avg, Lo_Dms, Lo_Smd, Lo_Sum);
    for Logical_Operation_Type use (0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11,
                                    12, 13, 14, 15, 16, 17, 18, 19, 20, 21);
    type Readsource_Type is (Src_Auto, Src_Front, Src_Back, Src_Zbuffer,
                             Src_Pup, Src_Over, Src_Under);
    for Readsource_Type use (0, 1, 2, 3, 4, 5, 6);
    Maxlights : constant := 8;
    type Pop_Up_Enable_Type is (Pup_None, Pup_Grey);
    for Pop_Up_Enable_Type use (0, 1);
    Pup_Clear : constant := 0;
    Pup_Color : constant := 1;
    Pup_Black : constant := 2;
    Pup_White : constant := 3;
    package Map_Colors is
        Black : constant Colorindex := 0;
        White : constant Colorindex := 1;
        Green : constant Colorindex := 2;
        Yellow : constant Colorindex := 3;
        Blue : constant Colorindex := 4;
        Magenta : constant Colorindex := 5;
        Cyan : constant Colorindex := 6;
        Red : constant Colorindex := 7;
    end Map_Colors;
    type Z_Source_Type is (Zsrc_Depth, Zsrc_Color);
    for Z_Source_Type use (0, 1);
    type Z_Function_Type is (Zf_Never, Zf_Less, Zf_Equal, Zf_Lequal,
                             Zf_Greater, Zf_Notequal, Zf_Gequal, Zf_Always);
    for Z_Function_Type use (0, 1, 2, 3, 4, 5, 6, 7);
    type Blending_Factor is (Bf_Zero, Bf_One, Bf_Sc, Bf_Msc,
                             Bf_Sa, Bf_Msa, Bf_Da, Bf_Mda);
    for Blending_Factor use (0, 1, 2, 3, 4, 5, 6, 7);
    Bf_Dc : constant Blending_Factor := Bf_Sc;
    Bf_Mdc : constant Blending_Factor := Bf_Msc;
    subtype Events_Count_Type is Short_Natural
                                    range 0 .. Short_Natural'Last / 2;
    type Packed_Rgba_Type is
        record
            Alpha : Alphavalue;
            Blue, Green, Red : Rgbvalue;
        end record;
    for Packed_Rgba_Type'Size use 32;
    for Packed_Rgba_Type use
        record
            Alpha at 0 range 0 .. 7;
            Blue at 0 range 8 .. 15;
            Green at 0 range 16 .. 23;
            Red at 0 range 24 .. 31;
        end record;
    type Packed_Rgbas_Type is array (Natural range <>) of Packed_Rgba_Type;
    pragma Pack (Packed_Rgbas_Type);
    type Packed_Rgb_Type is new Gl_System_Types.Int32 range 0 .. 16#FFFFFF#;
    type Packed_Rgbs_Type is array (Natural range <>) of Packed_Rgb_Type;
    pragma Pack (Packed_Rgbs_Type);
    type Cursor_Origin_Type is new Gl_System_Types.Int16;
    type Cursor_Kind_Type is (C16x1, C16x2, C32x1, C32x2, Ccross);
    for Cursor_Kind_Type'Size use Gl_System_Types.Int32'Size;
    for Cursor_Kind_Type use (0, 1, 2, 3, 4);
    type Raster_Columns_Type is new Gl_System_Types.Int8;
    subtype Raster_Rows_Type is Raster_Columns_Type;
    type Fontchar is
        record
            Offset : Gl_System_Types.Uint16;
            W : Raster_Columns_Type;
            H : Raster_Rows_Type;
            Xoff : Raster_Columns_Type;
            Yoff : Raster_Rows_Type;
            Width : Short_Pixels;
        end record;
    for Fontchar use
        record
            Offset at 0 range 0 .. 15;
            W at 0 range 16 .. 23;
            H at 0 range 24 .. 31;
            Xoff at 0 range 32 .. 39;
            Yoff at 0 range 40 .. 47;
            Width at 0 range 48 .. 63;
        end record;
    type Fontchars_Type is array (Natural range <>) of Fontchar;
    type Draw_Mode_Type is (Normaldraw, Pupdraw, Overdraw,
                            Underdraw, Cursordraw);
    for Draw_Mode_Type use (0, 1, 2, 3, 4);
    type Gammaramp_Value_Type is new Gl_System_Types.Int16;
    type Gammaramp_Values_Type is
       array (Rgb_Value range 0 .. 255) of Gammaramp_Value_Type;
    type Button_State_Type is new Gl_System_Types.Int32;
    Button_Up : constant Button_State_Type := 0;
    Button_Down : constant Button_State_Type := 1;
    Invalid_Button : constant Button_State_Type := -1;
    type Nurbs_Property_Value is new Gl_System_Types.Float32;
    type Noise_Delta_Type is new Gl_System_Types.Int16;
    type Knot_Type is new Gl_System_Types.Float64;
    type Knots_Type is array (Positive range <>) of Knot_Type;
    type Zoom_Factor_Type is new Gl_System_Types.Float32;
    type Bell_Sound_Type is (Off, Short, Long);
    for Bell_Sound_Type use (Off => 0, Short => 1, Long => 2);
    Sml_On : constant Boolean := True;
    Sml_Off : constant Boolean := False;
    Smp_On : constant Boolean := True;
    Smp_Off : constant Boolean := False;
    type Font_Type is (Ft_Sbcs, Ft_Dbcs);
    for Font_Type'Size use 32;
    for Font_Type use (0, 1);
    type Getgdesc_Inquiry_Type is new Gl_System_Types.Int32;
    Gd_Xpmax : constant Getgdesc_Inquiry_Type := 1;
    Gd_Ypmax : constant Getgdesc_Inquiry_Type := 2;
    Gd_Zmin : constant Getgdesc_Inquiry_Type := 3;
    Gd_Zmax : constant Getgdesc_Inquiry_Type := 4;
    Gd_Bits_Zbuffer : constant Getgdesc_Inquiry_Type := 5;
    Gd_Bits_Overlay : constant Getgdesc_Inquiry_Type := 6;
    Gd_Bits_Underlay : constant Getgdesc_Inquiry_Type := 7;
    Gd_Bits_Norm_Dbl_Rgb : constant Getgdesc_Inquiry_Type := 8;
    Gd_Bits_Norm_Dbl_Cmode : constant Getgdesc_Inquiry_Type := 9;
    Gd_Bits_Norm_Sng_Rgb : constant Getgdesc_Inquiry_Type := 10;
    Gd_Bits_Norm_Sng_Cmode : constant Getgdesc_Inquiry_Type := 11;
    Gd_Bits_Alphabuffer : constant Getgdesc_Inquiry_Type := 12;
    Gd_Bits_Cursor : constant Getgdesc_Inquiry_Type := 13;
    Gd_Bits_Plane_Mask : constant Getgdesc_Inquiry_Type := 14;
    Gd_Overunder_Shared : constant Getgdesc_Inquiry_Type := 15;
    Gd_Large_Map_Size : constant Getgdesc_Inquiry_Type := 16;
    Gd_Small_Map_Size : constant Getgdesc_Inquiry_Type := 17;
    Gd_Num_Small_Maps : constant Getgdesc_Inquiry_Type := 18;
    Gd_Pointsmooth_Cmode : constant Getgdesc_Inquiry_Type := 19;
    Gd_Pointsmooth_Rgb : constant Getgdesc_Inquiry_Type := 20;
    Gd_Linesmooth_Cmode : constant Getgdesc_Inquiry_Type := 21;
    Gd_Linesmooth_Rgb : constant Getgdesc_Inquiry_Type := 22;
    Gd_Shademodel : constant Getgdesc_Inquiry_Type := 23;
    Gd_Shadebuffers : constant Getgdesc_Inquiry_Type := 24;
    Gd_Rgbmode : constant Getgdesc_Inquiry_Type := 25;
    Gd_Dither : constant Getgdesc_Inquiry_Type := 26;
    Gd_Subpixel_Line : constant Getgdesc_Inquiry_Type := 27;
    Gd_Subpixel_Pnt : constant Getgdesc_Inquiry_Type := 28;
    Gd_Subpixel_Poly : constant Getgdesc_Inquiry_Type := 29;
    Gd_Polymode : constant Getgdesc_Inquiry_Type := 30;
    Gd_Bits_Linestyle : constant Getgdesc_Inquiry_Type := 31;
    Gd_Max_Lsrepeat : constant Getgdesc_Inquiry_Type := 32;
    Gd_Max_Nurbs_Order : constant Getgdesc_Inquiry_Type := 33;
    Gd_Max_Trim_Order : constant Getgdesc_Inquiry_Type := 34;
    Gd_Max_Pattern_Size : constant Getgdesc_Inquiry_Type := 35;
    Gd_Max_Verts : constant Getgdesc_Inquiry_Type := 36;
    Gd_Max_Attr_Stackdepth : constant Getgdesc_Inquiry_Type := 37;
    Gd_Max_Matrix_Stackdepth : constant Getgdesc_Inquiry_Type := 38;
    Gd_Max_Viewport_Stackdepth : constant Getgdesc_Inquiry_Type := 39;
    Gd_Zdraw_Geom : constant Getgdesc_Inquiry_Type := 40;
    Gd_Zdraw_Pixels : constant Getgdesc_Inquiry_Type := 41;
    Gd_Blend : constant Getgdesc_Inquiry_Type := 42;
    Gd_Lighting_Twoside : constant Getgdesc_Inquiry_Type := 43;
    Gd_Butbox : constant Getgdesc_Inquiry_Type := 44;
    Gd_Dials : constant Getgdesc_Inquiry_Type := 45;
    Gd_Vert_Retrace_Freq : constant Getgdesc_Inquiry_Type := 46;
    Gd_Textport : constant Getgdesc_Inquiry_Type := 47;
    Gd_Wsys : constant Getgdesc_Inquiry_Type := 48;
    Gd_Xmmax : constant Getgdesc_Inquiry_Type := 49;
    Gd_Ymmax : constant Getgdesc_Inquiry_Type := 50;
    Gd_Bf_Under : constant := 16#01#;
    Gd_Bf_Over : constant := 16#02#;
    Gd_Bf_Main : constant := 16#04#;
    Gd_Bf_Alpha : constant := 16#08#;
    Gd_Shademodel_Flat : constant := 16#01#;
    Gd_Shademodel_Gouraud : constant := 16#02#;
    Gd_Shademodel_Phong : constant := 16#04#;
    Gd_Shademodel_Pseudo_Phong_Flat : constant := 16#08#;
    Gd_Wsys_None : constant := 0;
    Gd_Wsys_4s : constant := 1;
    Gd_Wsys_Aix113 : constant := 2;
    Gd_Wsys_Aix114 : constant := 3;
    type Pixmode_Mode_Type is (Pm_Fastmode, Pm_Ttob, Pm_Size, Pm_Stride);
    for Pixmode_Mode_Type'Size use 32;
    for Pixmode_Mode_Type use (0, 1, 2, 3);
    Xmaxscreen : constant := 1279;
    Ymaxscreen : constant := 1023;
    Xmax170 : constant := 645;
    Ymax170 : constant := 484;
    Xmaxpal : constant := 779;
    Ymaxpal : constant := 574;
    Hash_Table_Size : constant := 128;
    Attribstackdepth : constant := 10;
    Vpstackdepth : constant := 8;
    Matrixstackdepth : constant := 32;
    Namestackdepth : constant := 1025;
    N_Shaded : constant := 1.0;
    Bm_Set : constant := 1;
    Bm_Clr : constant := 2;
    Bm_Xor : constant := 3;
    Bm_Tile : constant := 2048;
    procedure Addtopup (Menu : Menu_Id_Type; Item : String);
    procedure Addtopopup (Menu : Menu_Id_Type; Item : String) renames Addtopup;
    procedure Arc (X, Y : Coord;
                   Radius : Coord;
                   Starting_Angle, Ending_Angle : Angle);
    procedure Arci (X, Y : Icoord;
                    Radius : Icoord;
                    Starting_Angle, Ending_Angle : Angle);
    procedure Arc (X, Y : Icoord;
                   Radius : Icoord;
                   Starting_Angle, Ending_Angle : Angle) renames Arci;
    procedure Arcs (X, Y : Scoord;
                    Radius : Scoord;
                    Starting_Angle, Ending_Angle : Angle);
    procedure Arc (X, Y : Scoord;
                   Radius : Scoord;
                   Starting_Angle, Ending_Angle : Angle) renames Arcs;
    procedure Arcf (X, Y : Coord;
                    Radius : Coord;
                    Starting_Angle, Ending_Angle : Angle);
    procedure Filledarc (X, Y : Coord;
                         Radius : Coord;
                         Starting_Angle, Ending_Angle : Angle) renames Arcf;
    procedure Arcfi (X, Y : Icoord;
                     Radius : Icoord;
                     Starting_Angle, Ending_Angle : Angle);
    procedure Filledarc (X, Y : Icoord;
                         Radius : Icoord;
                         Starting_Angle, Ending_Angle : Angle) renames Arcfi;
    procedure Arcfs (X, Y : Scoord;
                     Radius : Scoord;
                     Starting_Angle, Ending_Angle : Angle);
    procedure Filledarc (X, Y : Scoord;
                         Radius : Scoord;
                         Starting_Angle, Ending_Angle : Angle) renames Arcfs;
    procedure Attachcursor (Device1 : Device.Device; Device2 : Device.Device);
    procedure Backbuffer (Enable_Drawing_Into_Back_Buffer : Boolean);
    procedure Backface (Enable_Backfacing_Polygon_Removal : Boolean);
    procedure Bbox2 (X_Min, Y_Min : Screencoord; X1, Y1, X2, Y2 : Coord);
    procedure Boundingbox (X_Min, Y_Min : Screencoord; X1, Y1, X2, Y2 : Coord)
        renames Bbox2;
    procedure Bbox2s (X_Min, Y_Min : Screencoord; X1, Y1, X2, Y2 : Scoord);
    procedure Boundingbox (X_Min, Y_Min : Screencoord; X1, Y1, X2, Y2 : Scoord)
        renames Bbox2s;
    procedure Bbox2i (X_Min, Y_Min : Screencoord; X1, Y1, X2, Y2 : Icoord);
    procedure Boundingbox (X_Min, Y_Min : Screencoord; X1, Y1, X2, Y2 : Icoord)
        renames Bbox2i;
    procedure Bgnclosedline;
    procedure Beginclosedline renames Bgnclosedline;
    procedure Bgnline;
    procedure Beginline renames Bgnline;
    procedure Bgnpoint;
    procedure Beginpoint renames Bgnpoint;
    procedure Bgnpolygon;
    procedure Beginpolygon renames Bgnpolygon;
    procedure Bgnsurface;
    procedure Beginsurface renames Bgnsurface;
    procedure Bgntmesh;
    procedure Begintrianglemesh renames Bgntmesh;
    procedure Bgntrim;
    procedure Begintrim renames Bgntrim;
    procedure Blankscreen (Blank_The_Screen : Boolean);
    procedure Blanktime (Frames : Natural);
    procedure Blendfunction (Source, Destination : Blending_Factor);
    procedure Blink (Retraces_Per_Blink : Vertical_Retraces_Type;
                     Color : Colorindex;
                     Red, Green, Blue : Rgb_Value);
    procedure Blkqread (Events : out Device.Events_Type;
                        Events_Read : out Events_Count_Type;
                        Maximum_Events : Events_Count_Type);
    procedure Blockqueueread (Events : out Device.Events_Type;
                              Events_Read : out Events_Count_Type;
                              Maximum_Events : Events_Count_Type)
        renames Blkqread;
    procedure Blkqread (Events : out Device.Events_Type;
                        Events_Read : out Events_Count_Type);
    procedure Blockqueueread (Events : out Device.Events_Type;
                              Events_Read : out Events_Count_Type)
        renames Blkqread;
    procedure Color (Color : Colorindex);
    pragma Interface (C, Color);
    procedure C3i (Rgb : I_Rgb_Color_Type);
    procedure Color (Rgb : I_Rgb_Color_Type) renames C3i;
    procedure C3s (Rgb : S_Rgb_Color_Type);
    procedure Color (Rgb : S_Rgb_Color_Type) renames C3s;
    procedure C3f (Rgb : Rgb_Float_Color_Type);
    procedure Color (Rgb : Rgb_Float_Color_Type) renames C3f;
    procedure C4i (Rgba : I_Rgba_Color_Type);
    procedure Color (Rgba : I_Rgba_Color_Type) renames C4i;
    procedure C4s (Rgba : S_Rgba_Color_Type);
    procedure Color (Rgba : S_Rgba_Color_Type) renames C4s;
    procedure C4f (Rgba : Rgba_Float_Color_Type);
    procedure Color (Rgba : Rgba_Float_Color_Type) renames C4f;
    procedure Color (Rgb : Rgb_Color_Type);
    procedure Color (Rgba : Rgba_Color_Type);
    procedure Callobj (The_Object : Object);
    procedure Callobject (The_Object : Object) renames Callobj;
    procedure Charstr (Text : String);
    procedure Characterstring (Text : String) renames Charstr;
    procedure Put (Text : String) renames Charstr;
    procedure Chunksize (Bytes : Natural);
    procedure Circ (X, Y : Coord; Radius : Coord);
    procedure Circle (X, Y : Coord; Radius : Coord) renames Circ;
    procedure Circi (X, Y : Icoord; Radius : Icoord);
    procedure Circle (X, Y : Icoord; Radius : Icoord) renames Circi;
    procedure Circs (X, Y : Scoord; Radius : Scoord);
    procedure Circle (X, Y : Scoord; Radius : Scoord) renames Circs;
    procedure Circf (X, Y : Coord; Radius : Coord);
    procedure Filledcircle (X, Y : Coord; Radius : Coord) renames Circf;
    procedure Circfi (X, Y : Icoord; Radius : Icoord);
    procedure Filledcircle (X, Y : Icoord; Radius : Icoord) renames Circfi;
    procedure Circfs (X, Y : Scoord; Radius : Scoord);
    procedure Filledcircle (X, Y : Scoord; Radius : Scoord) renames Circfs;
    procedure Clear;
    pragma Interface (C, Clear);
    procedure Clkoff;
    procedure Clickoff renames Clkoff;
    procedure Clkon;
    procedure Clickon renames Clkon;
    procedure Closeobj;
    procedure Closeobject renames Closeobj;
    procedure Cmode;
    procedure Colormapmode renames Cmode;
    procedure Cmov (X, Y, Z : Coord);
    procedure Settextposition (X, Y, Z : Coord) renames Cmov;
    procedure Cmovi (X, Y, Z : Icoord);
    procedure Settextposition (X, Y, Z : Icoord) renames Cmovi;
    procedure Cmovs (X, Y, Z : Scoord);
    procedure Settextposition (X, Y, Z : Scoord) renames Cmovs;
    procedure Cmov2 (X, Y : Coord);
    procedure Settextposition (X, Y : Coord) renames Cmov2;
    procedure Cmov2i (X, Y : Icoord);
    procedure Settextposition (X, Y : Icoord) renames Cmov2i;
    procedure Cmov2s (X, Y : Scoord);
    procedure Settextposition (X, Y : Scoord) renames Cmov2s;
    procedure Colorf (Color : Colorfloatindex);
    pragma Interface (C, Colorf);
    procedure Color (Color : Colorfloatindex) renames Colorf;
    procedure Compactify (The_Object : Object);
    procedure Concave (Draw_Accurate_Concave_Polygons : Boolean);
    procedure Cpack (Color : Packed_Rgb_Type);
    pragma Interface (C, Cpack);
    procedure Color (Color : Packed_Rgb_Type) renames Cpack;
    procedure Cpack (Color : Packed_Rgba_Type);
    procedure Color (Color : Packed_Rgba_Type) renames Cpack;
    procedure Crv (Points : Points4_3d);
    procedure Crvn (Number_Of_Points : Natural; Points : Points_3d);
    procedure Curve (Number_Of_Points : Natural; Points : Points_3d)
        renames Crvn;
    procedure Curve (Points : Points_3d);
    procedure Curorigin (Cursor : Cursor_Id_Type; X, Y : Cursor_Origin_Type);
    procedure Cursororigin (Cursor : Cursor_Id_Type; X, Y : Cursor_Origin_Type)
        renames Curorigin;
    procedure Cursoff;
    procedure Cursoroff renames Cursoff;
    procedure Curson;
    procedure Cursoron renames Curson;
    procedure Curstype (Cursor_Type : Cursor_Kind_Type);
    procedure Cursortype (Cursor_Type : Cursor_Kind_Type) renames Curstype;
    procedure Curvebasis (Basis : Basis_Id_Type);
    procedure Curveit (Count : Short_Natural);
    procedure Curveprecision (Segments : Short_Natural);
    procedure Cyclemap (Duration : Vertical_Retraces_Type;
                        Map : Map_Id_Type;
                        Next_Map : Map_Id_Type);
    procedure Czclear (Color : Colorindex; Depth : Z_Value_Type);
    procedure Clear (Color : Colorindex; Depth : Z_Value_Type) renames Czclear;
    procedure Czclear (Color : Packed_Rgb_Type; Depth : Z_Value_Type);
    procedure Clear (Color : Packed_Rgb_Type; Depth : Z_Value_Type)
        renames Czclear;
    pragma Interface (C, Czclear);
    procedure Czclear (Color : Packed_Rgba_Type; Depth : Z_Value_Type);
    procedure Clear (Color : Packed_Rgba_Type; Depth : Z_Value_Type)
        renames Czclear;
    procedure Defbasis (Basis : Basis_Id_Type; M : Matrix);
    procedure Definebasis (Basis : Basis_Id_Type; M : Matrix) renames Defbasis;
    procedure Defcursor (Cursor : Cursor_Id_Type; Bitmap : Bitmap_Type);
    procedure Definecursor (Cursor : Cursor_Id_Type; Bitmap : Bitmap_Type)
        renames Defcursor;
    procedure Deflinestyle
                 (Linestyle : Linestyle_Id_Type; Style : Gl.Linestyle);
    procedure Definelinestyle
                 (Linestyle : Linestyle_Id_Type; Style : Gl.Linestyle)
        renames Deflinestyle;
    procedure Defpattern (Pattern : Pattern_Id_Type;
                          Size : Natural;  
                          Bitmap : Bitmap_Type);
    procedure Definepattern (Pattern : Pattern_Id_Type;
                             Size : Natural;  
                             Bitmap : Bitmap_Type) renames Defpattern;
    function Defpup (Item : String) return Menu_Id_Type;
    function Definepopup (Item : String) return Menu_Id_Type renames Defpup;
    procedure Defrasterfont (Font : Font_Id_Type;
                             Maximum_Height : Short_Pixels;
                             Count : Short_Natural;
                             Characters : Fontchars_Type;
                             Raster_Length : Short_Natural;
                             Raster : Bitmap_Type);
    procedure Definerasterfont (Font : Font_Id_Type;
                                Maximum_Height : Short_Pixels;
                                Count : Short_Natural;
                                Characters : Fontchars_Type;
                                Raster_Length : Short_Natural;
                                Raster : Bitmap_Type) renames Defrasterfont;
    procedure Defrasterfont (Font : Font_Id_Type;
                             Maximum_Height : Short_Pixels;
                             Characters : Fontchars_Type;
                             Raster : Bitmap_Type);
    procedure Definerasterfont (Font : Font_Id_Type;
                                Maximum_Height : Short_Pixels;
                                Characters : Fontchars_Type;
                                Raster : Bitmap_Type) renames Defrasterfont;
    procedure Delobj (The_Object : Object);
    procedure Deleteobject (The_Object : Object) renames Delobj;
    procedure Deltag (The_Tag : Tag);
    procedure Deletetag (The_Tag : Tag) renames Deltag;
    procedure Depthcue (On : Boolean);
    function Dopup (Menu : Menu_Id_Type) return Menu_Item_Type;
    function Dopopup (Menu : Menu_Id_Type) return Menu_Item_Type renames Dopup;
    procedure Doublebuffer;
    procedure Draw (X, Y, Z : Coord);
    procedure Drawi (X, Y, Z : Icoord);
    procedure Draw (X, Y, Z : Icoord) renames Drawi;
    procedure Draws (X, Y, Z : Scoord);
    procedure Draw (X, Y, Z : Scoord) renames Draws;
    procedure Draw2 (X, Y : Coord);
    procedure Draw (X, Y : Coord) renames Draw2;
    procedure Draw2i (X, Y : Icoord);
    procedure Draw (X, Y : Icoord) renames Draw2i;
    procedure Draw2s (X, Y : Scoord);
    procedure Draw (X, Y : Scoord) renames Draw2s;
    procedure Drawmode (Mode : Draw_Mode_Type);
    procedure Editobj (The_Object : Object);
    procedure Editobject (The_Object : Object) renames Editobj;
    procedure Endclosedline;
    procedure Endfullscrn;
    procedure Endfullscreen renames Endfullscrn;
    procedure Endline;
    procedure Endsurface;
    procedure Endtrim;
    procedure Endpick (Names : out Names_Type; Hits : out Integer);
    procedure Endpoint;
    procedure Endpolygon;
    procedure Endselect (Names : in out Names_Type; Hits : out Integer);
    procedure Endtmesh;
    procedure Endtrianglemesh renames Endtmesh;
    procedure Finish;
    procedure Font (Font : Font_Id_Type);
    procedure Foreground;
    procedure Freepup (Menu : Menu_Id_Type);
    procedure Freepopup (Menu : Menu_Id_Type) renames Freepup;
    procedure Frontbuffer (Enable_Drawing_In_Front_Buffer : Boolean);
    procedure Frontface (Enable_Frontfacing_Polygon_Removal : Boolean);
    procedure Fudge (X, Y : Pixels);
    procedure Fullscrn;
    procedure Fullscreen renames Fullscrn;
    procedure Gammaramp (Red, Green, Blue : Gammaramp_Values_Type);
    procedure Gbegin;
    procedure Gconfig;
    procedure Configure renames Gconfig;
    function Genobj return Object;
    function Generateobject return Object renames Genobj;
    function Gentag return Tag;
    function Generatetag return Tag renames Gentag;
    function Getbackface return Boolean;
    function Getbuffer return Buffer_Mode_Type;
    function Getbutton (The_Device : Device.Device) return Button_State_Type;
    function Getcmmode return Boolean;
    function Getcolormapmode return Boolean renames Getcmmode;
    function Getcolor return Colorindex;
    procedure Getcpos (X, Y : out Screencoord);
    procedure Getcharacterposition (X, Y : out Screencoord) renames Getcpos;
    procedure Getcursor (Cursor : out Cursor_Id_Type; Visible : out Boolean);
    function Getdcm return Boolean;
    function Getdepthcuemode return Boolean renames Getdcm;
    function Getdescender return Pixels;
    subtype Device_Count_Type is Natural range 0 .. 128;
    procedure Getdev (Number_Of_Devices : Device_Count_Type;
                      Devices : out Device.Devices_Type;
                      Values : out Device.Device_Values_Type);
    procedure Getdevices (Number_Of_Devices : Device_Count_Type;
                          Devices : out Device.Devices_Type;
                          Values : out Device.Device_Values_Type)
        renames Getdev;
    procedure Getdev (Devices : out Device.Devices_Type;
                      Values : out Device.Device_Values_Type);
    procedure Getdevices (Devices : out Device.Devices_Type;
                          Values : out Device.Device_Values_Type)
        renames Getdev;
    function Getdisplaymode return Display_Mode_Type;
    function Getdrawmode return Draw_Mode_Type;
    function Getfont return Font_Id_Type;
    function Getfontencoding return String;
    function Getfonttype return Font_Type;
    function Getgdesc (Inquiry : Getgdesc_Inquiry_Type) return Integer;
    function Getgdesc (Inquiry : Getgdesc_Inquiry_Type) return Boolean;
    procedure Getgpos (X, Y, Z, W : out Coord);
    procedure Getgraphicsposition (X, Y, Z, W : out Coord) renames Getgpos;
    function Getheight return Pixels;
    function Getlsrepeat return Linestyle_Repeat_Type;
    function Getlinestylerepeat return Linestyle_Repeat_Type
        renames Getlsrepeat;
    function Getlstyle return Linestyle_Id_Type;
    function Getlinestyle return Linestyle_Id_Type renames Getlstyle;
    function Getlwidth return Pixels;
    function Getlinewidth return Pixels renames Getlwidth;
    function Getmap return Map_Id_Type;
    procedure Getmatrix (M : out Matrix);
    procedure Getmcolor (Color : Colorindex; Red, Green, Blue : out Rgb_Value);
    procedure Getmcolors (Starting, Ending : Colorindex;
                          Red, Green, Blue : out Rgb_Values);
    function Getmmode return Matrix_Mode_Type;
    function Getmatrixmode return Matrix_Mode_Type renames Getmmode;
    procedure Getnurbsproperty (Property : Nurbs_Property_Type;
                                Value : out Nurbs_Property_Value);
    function Getopenobj return Object;
    function Getopenobject return Object renames Getopenobj;
    procedure Getorigin (X, Y : out Pixels);
    function Getpattern return Pattern_Id_Type;
    function Getplanes return Bitplanes_Type;
    procedure Getscrmask (Left, Right, Bottom, Top : out Screencoord);
    procedure Getscreenmask (Left, Right, Bottom, Top : out Screencoord)
        renames Getscrmask;
    procedure Getsize (X, Y : out Pixels);
    function Getsm return Shade_Model_Type;
    function Getshademodel return Shade_Model_Type renames Getsm;
    function Getvaluator (From : Device.Device)
                         return Device.Valuator_Value_Type;
    procedure Getviewport (Left, Right, Bottom, Top : out Screencoord);
    function Getwritemask return Write_Mask_Type;
    function Getxdpy return X_Display_Pointer;
    function Getxwid return X_Window;
    function Getzbuffer return Boolean;
    procedure Gexit;
    procedure Ginit;
    procedure Initialize renames Ginit;
    procedure Greset;
    procedure Reset renames Greset;
    procedure Grgbcolor (Red, Green, Blue : out Rgb_Value);
    procedure Getrgbcolor (Red, Green, Blue : out Rgb_Value) renames Grgbcolor;
    procedure Grgbmask (Red, Green, Blue : out Rgb_Write_Mask_Type);
    procedure Getrgbmask (Red, Green, Blue : out Rgb_Write_Mask_Type)
        renames Grgbmask;
    procedure Gselect (Names : out Names_Type; Maximum_Names : Positive);
    procedure Gselect (Names : out Names_Type);
    procedure Gsync;
    procedure Sync renames Gsync;
    function Gversion return String;
    function Version return String renames Gversion;
    procedure Iconsize (X, Y : Pixels);
    procedure Icontitle (Title : String);
    procedure Initnames;
    procedure Initializenames renames Initnames;
    function Isobj (This : Object) return Boolean;
    function Isobject (This : Object) return Boolean renames Isobj;
    function Isqueued (This_Device : Device.Device) return Boolean;
    function Istag (This_Tag : Tag) return Boolean;
    procedure Keepaspect (X, Y : Integer);
    procedure Lampon (Lamps : Lamps_Type);
    procedure Lampoff (Lamps : Lamps_Type);
    procedure Lgetdepth (Near, Far : out Z_Value_Type);
    procedure Getdepth (Near, Far : out Z_Value_Type) renames Lgetdepth;
    procedure Linesmooth (Enable_Smooth_Lines : Boolean);
    procedure Linewidth (Width : Short_Pixels);
    procedure Lmbind (Target : Lm_Target_Type; Id : Lm_Id_Type);
    procedure Lmcolor (Mode : Lm_Color_Type);
    procedure Lmdef (Lm_Definition : Lm_Definition_Type;
                     Lm_Id : Lm_Id_Type;
                     Count : Short_Positive;
                     Properties : Lm_Property_List_Type);
    procedure Lmdef (Lm_Definition : Lm_Definition_Type;
                     Lm_Id : Lm_Id_Type;
                     Properties : Lm_Property_List_Type);
    procedure Loadmatrix (M : in Matrix);
    procedure Loadname (Name : Name_Type);
    procedure Loadxfont (Font : Font_Id_Type; Font_Name : String);
    procedure Logicop (Operation : Logical_Operation_Type);
    procedure Logicaloperation (Operation : Logical_Operation_Type)
        renames Logicop;
    procedure Lookat (View_X, View_Y, View_Z : Coord;
                      Point_X, Point_Y, Point_Z : Coord;
                      Twist : Angle);
    procedure Lrectread (Lower_Left_X, Lower_Left_Y : Screencoord;
                         Upper_Right_X, Upper_Right_Y : Screencoord;
                         Number_Of_Pixels : out Pixels;
                         Colors : out Packed_Rgbs_Type);
    procedure Rectangleread (Lower_Left_X, Lower_Left_Y : Screencoord;
                             Upper_Right_X, Upper_Right_Y : Screencoord;
                             Number_Of_Pixels : out Pixels;
                             Colors : out Packed_Rgbs_Type) renames Lrectread;
    procedure Lrectread (Lower_Left_X, Lower_Left_Y : Screencoord;
                         Upper_Right_X, Upper_Right_Y : Screencoord;
                         Number_Of_Pixels : out Pixels;
                         Colors : out Packed_Rgbas_Type);
    procedure Rectangleread (Lower_Left_X, Lower_Left_Y : Screencoord;
                             Upper_Right_X, Upper_Right_Y : Screencoord;
                             Number_Of_Pixels : out Pixels;
                             Colors : out Packed_Rgbas_Type) renames Lrectread;
    procedure Lrectread (Lower_Left_X, Lower_Left_Y : Screencoord;
                         Upper_Right_X, Upper_Right_Y : Screencoord;
                         Number_Of_Pixels : out Pixels;
                         Z_Values : out Z_Values_Type);
    procedure Rectangleread (Lower_Left_X, Lower_Left_Y : Screencoord;
                             Upper_Right_X, Upper_Right_Y : Screencoord;
                             Number_Of_Pixels : out Pixels;
                             Z_Values : out Z_Values_Type) renames Lrectread;
    procedure Lrectwrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                          Upper_Right_X, Upper_Right_Y : Screencoord;
                          Colors : Packed_Rgbs_Type);
    procedure Rectanglewrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                              Upper_Right_X, Upper_Right_Y : Screencoord;
                              Colors : Packed_Rgbs_Type) renames Lrectwrite;
    procedure Lrectwrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                          Upper_Right_X, Upper_Right_Y : Screencoord;
                          Colors : Packed_Rgbas_Type);
    procedure Rectanglewrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                              Upper_Right_X, Upper_Right_Y : Screencoord;
                              Colors : Packed_Rgbas_Type) renames Lrectwrite;
    procedure Lrectwrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                          Upper_Right_X, Upper_Right_Y : Screencoord;
                          Z_Values : Z_Values_Type);
    procedure Rectanglewrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                              Upper_Right_X, Upper_Right_Y : Screencoord;
                              Z_Values : Z_Values_Type) renames Lrectwrite;
    procedure Lrgbrange (Red_Min, Green_Min, Blue_Min : Rgb_Value;
                         Red_Max, Green_Max, Blue_Max : Rgb_Value;
                         Z_Near, Z_Far : Z_Value_Type);
    procedure Lsetdepth (Near, Far : in Z_Value_Type);
    procedure Lshaderange (Low, High : Colorindex; Near, Far : Z_Value_Type);
    procedure Lsrepeat (Factor : Linestyle_Repeat_Type);
    procedure Linestylerepeat (Factor : Linestyle_Repeat_Type) renames Lsrepeat;
    procedure Makeobj (The_Object : Object);
    procedure Makeobject (The_Object : Object) renames Makeobj;
    procedure Maketag (The_Tag : Tag);
    procedure Mapcolor (Color : Colorindex; Red, Green, Blue : Rgb_Value);
    procedure Mapcolors (Starting, Ending : Colorindex;
                         Red, Green, Blue : Rgb_Values);
    procedure Mapw (Viewing_Object : Object;
                    Screen_X, Screen_Y : Screencoord;
                    X1, Y1, Z1 : out Coord;
                    X2, Y2, Z2 : out Coord);
    procedure Mapw2 (Viewing_Object : Object;
                     Screen_X, Screen_Y : Screencoord;
                     X, Y : out Coord);
    procedure Maxsize (X, Y : Pixels);
    procedure Minsize (X, Y : Pixels);
    procedure Mmode (Mode : Matrix_Mode_Type);
    procedure Matrixmode (Mode : Matrix_Mode_Type) renames Mmode;
    procedure Move (X, Y, Z : Coord);
    procedure Movei (X, Y, Z : Icoord);
    procedure Move (X, Y, Z : Icoord) renames Movei;
    procedure Moves (X, Y, Z : Scoord);
    procedure Move (X, Y, Z : Scoord) renames Moves;
    procedure Move2 (X, Y : Coord);
    procedure Move (X, Y : Coord) renames Move2;
    procedure Move2i (X, Y : Icoord);
    procedure Move (X, Y : Icoord) renames Move2i;
    procedure Move2s (X, Y : Scoord);
    procedure Move (X, Y : Scoord) renames Move2s;
    procedure Multimap;
    procedure Multmatrix (M : in Matrix);
    procedure N3f (Normal : Vector_3d);
    function Newpup return Menu_Id_Type;
    function Newpopup return Menu_Id_Type renames Newpup;
    procedure Newtag (New_Tag : Tag; Old_Tag : Tag; The_Offset : Offset);
    procedure Noborder;
    procedure Noise (Valuator : Device.Device; Noise_Delta : Noise_Delta_Type);
    procedure Noport;
    procedure Normal (Normal : Vector_3d);
    procedure Nurbscurve (Knot_Count : Natural;
                          Knots : Knots_Type;
                          Control_Points : Nurbs_Control_Points_2d;
                          Order : Natural);
    procedure Nurbscurve (Knots : Knots_Type;
                          Control_Points : Nurbs_Control_Points_2d;
                          Order : Natural);
    procedure Nurbscurve (Knot_Count : Natural;
                          Knots : Knots_Type;
                          Control_Points : Nurbs_Control_Points_3d;
                          Order : Natural);
    procedure Nurbscurve (Knots : Knots_Type;
                          Control_Points : Nurbs_Control_Points_3d;
                          Order : Natural);
    procedure Nurbssurface (S_Knot_Count : Positive;
                            S_Knots : Knots_Type;
                            T_Knot_Count : Positive;
                            T_Knots : Knots_Type;
                            Control_Points : Nurbs_Control_Matrix_3d;
                            S_Order : Natural;
                            T_Order : Natural);
    procedure Nurbssurface (S_Knots : Knots_Type;
                            T_Knots : Knots_Type;
                            Control_Points : Nurbs_Control_Matrix_3d;
                            S_Order : Natural;
                            T_Order : Natural);
    procedure Nurbssurface (S_Knot_Count : Positive;
                            S_Knots : Knots_Type;
                            T_Knot_Count : Positive;
                            T_Knots : Knots_Type;
                            Control_Points : Nurbs_Control_Matrix_4d;
                            S_Order : Natural;
                            T_Order : Natural);
    procedure Nurbssurface (S_Knots : Knots_Type;
                            T_Knots : Knots_Type;
                            Control_Points : Nurbs_Control_Matrix_4d;
                            S_Order : Natural;
                            T_Order : Natural);
    procedure Objdelete (Tag1, Tag2 : Tag);
    procedure Objectdelete (Tag1, Tag2 : Tag) renames Objdelete;
    procedure Objinsert (The_Tag : Tag);
    procedure Objectinsert (The_Tag : Tag) renames Objinsert;
    procedure Objreplace (The_Tag : Tag);
    procedure Objectreplace (The_Tag : Tag) renames Objreplace;
    procedure Onemap;
    procedure Ortho (Left, Right, Bottom, Top, Near, Far : Coord);
    procedure Coordinatesystem (Left, Right, Bottom, Top, Near, Far : Coord)
        renames Ortho;
    procedure Ortho2 (Left, Right, Bottom, Top : Coord);
    procedure Coordinatesystem (Left, Right, Bottom, Top : Coord)
        renames Ortho2;
    procedure Overlay (Planes : Bitplanes_Type);
    procedure Patch (X, Y, Z : Matrix);
    procedure Patchbasis (U_Basis, V_Basis : Basis_Id_Type);
    procedure Patchcurves (U_Curves, V_Curves : Natural);
    procedure Patchprecision (U_Segments, V_Segments : Natural);
    procedure Pclos;
    procedure Polygonclose renames Pclos;
    procedure Pdr (X, Y, Z : Coord);
    procedure Polygondraw (X, Y, Z : Coord) renames Pdr;
    procedure Pdri (X, Y, Z : Icoord);
    procedure Polygondraw (X, Y, Z : Icoord) renames Pdri;
    procedure Pdrs (X, Y, Z : Scoord);
    procedure Polygondraw (X, Y, Z : Scoord) renames Pdrs;
    procedure Pdr2 (X, Y : Coord);
    procedure Polygondraw (X, Y : Coord) renames Pdr2;
    procedure Pdr2i (X, Y : Icoord);
    procedure Polygondraw (X, Y : Icoord) renames Pdr2i;
    procedure Pdr2s (X, Y : Scoord);
    procedure Polygondraw (X, Y : Scoord) renames Pdr2s;
    procedure Perspective (Field_Of_View : Angle;
                           Aspect : Aspect_Ratio_Type;
                           Near, Far : Coord);
    procedure Pick (Names : in out Names_Type);
    procedure Picksize (X, Y : Short_Pixels);
    procedure Pixmode (Mode : Pixmode_Mode_Type; Value : Integer);
    procedure Pixmode (Mode : Pixmode_Mode_Type; Value : Boolean);
    procedure Pmv (X, Y, Z : Coord);
    procedure Polygonmove (X, Y, Z : Coord) renames Pmv;
    procedure Pmvi (X, Y, Z : Icoord);
    procedure Polygonmove (X, Y, Z : Icoord) renames Pmvi;
    procedure Pmvs (X, Y, Z : Scoord);
    procedure Polygonmove (X, Y, Z : Scoord) renames Pmvs;
    procedure Pmv2 (X, Y : Coord);
    procedure Polygonmove (X, Y : Coord) renames Pmv2;
    procedure Pmv2i (X, Y : Icoord);
    procedure Polygonmove (X, Y : Icoord) renames Pmv2i;
    procedure Pmv2s (X, Y : Scoord);
    procedure Polygonmove (X, Y : Scoord) renames Pmv2s;
    procedure Pnt (X, Y, Z : Coord);
    procedure Point (X, Y, Z : Coord) renames Pnt;
    procedure Pnti (X, Y, Z : Icoord);
    procedure Point (X, Y, Z : Icoord) renames Pnti;
    procedure Pnts (X, Y, Z : Scoord);
    procedure Point (X, Y, Z : Scoord) renames Pnts;
    procedure Pnt2 (X, Y : Coord);
    procedure Point (X, Y : Coord) renames Pnt2;
    procedure Pnt2i (X, Y : Icoord);
    procedure Point (X, Y : Icoord) renames Pnt2i;
    procedure Pnt2s (X, Y : Scoord);
    procedure Point (X, Y : Scoord) renames Pnt2s;
    procedure Pntsmooth (Turn_On_Antialiasing : Boolean);
    procedure Pointsmooth (Turn_On_Antialiasing : Boolean) renames Pntsmooth;
    procedure Polarview (Distance : Coord;
                         Azimuth : Angle;
                         Incidence : Angle;
                         Twist : Angle);
    procedure Polf (N : Natural; Vertices : Vectors_3d);
    procedure Polf (Vertices : Vectors_3d);
    procedure Filledpolygon (N : Natural; Vertices : Vectors_3d) renames Polf;
    procedure Filledpolygon (Vertices : Vectors_3d) renames Polf;
    procedure Polfs (N : Natural; Vertices : Svectors_3d);
    procedure Polfs (Vertices : Svectors_3d);
    procedure Filledpolygon (N : Natural; Vertices : Svectors_3d) renames Polfs;
    procedure Filledpolygon (Vertices : Svectors_3d) renames Polfs;
    procedure Polfi (N : Natural; Vertices : Ivectors_3d);
    procedure Polfi (Vertices : Ivectors_3d);
    procedure Filledpolygon (N : Natural; Vertices : Ivectors_3d) renames Polfi;
    procedure Filledpolygon (Vertices : Ivectors_3d) renames Polfi;
    procedure Polf2 (N : Natural; Vertices : Vectors_2d);
    procedure Polf2 (Vertices : Vectors_2d);
    procedure Filledpolygon (N : Natural; Vertices : Vectors_2d) renames Polf2;
    procedure Filledpolygon (Vertices : Vectors_2d) renames Polf2;
    procedure Polf2s (N : Natural; Vertices : Svectors_2d);
    procedure Polf2s (Vertices : Svectors_2d);
    procedure Filledpolygon (N : Natural; Vertices : Svectors_2d)
        renames Polf2s;
    procedure Filledpolygon (Vertices : Svectors_2d) renames Polf2s;
    procedure Polf2i (N : Natural; Vertices : Ivectors_2d);
    procedure Polf2i (Vertices : Ivectors_2d);
    procedure Filledpolygon (N : Natural; Vertices : Ivectors_2d)
        renames Polf2i;
    procedure Filledpolygon (Vertices : Ivectors_2d) renames Polf2i;
    procedure Poly (N : Natural; Vertices : Vectors_3d);
    procedure Poly (Vertices : Vectors_3d);
    procedure Polygon (N : Natural; Vertices : Vectors_3d) renames Poly;
    procedure Polygon (Vertices : Vectors_3d) renames Poly;
    procedure Polys (N : Natural; Vertices : Svectors_3d);
    procedure Polys (Vertices : Svectors_3d);
    procedure Polygon (N : Natural; Vertices : Svectors_3d) renames Polys;
    procedure Polygon (Vertices : Svectors_3d) renames Polys;
    procedure Polyi (N : Natural; Vertices : Ivectors_3d);
    procedure Polyi (Vertices : Ivectors_3d);
    procedure Polygon (N : Natural; Vertices : Ivectors_3d) renames Polyi;
    procedure Polygon (Vertices : Ivectors_3d) renames Polyi;
    procedure Poly2 (N : Natural; Vertices : Vectors_2d);
    procedure Poly2 (Vertices : Vectors_2d);
    procedure Polygon (N : Natural; Vertices : Vectors_2d) renames Poly2;
    procedure Polygon (Vertices : Vectors_2d) renames Poly2;
    procedure Poly2s (N : Natural; Vertices : Svectors_2d);
    procedure Poly2s (Vertices : Svectors_2d);
    procedure Polygon (N : Natural; Vertices : Svectors_2d) renames Poly2s;
    procedure Polygon (Vertices : Svectors_2d) renames Poly2s;
    procedure Poly2i (N : Natural; Vertices : Ivectors_2d);
    procedure Poly2i (Vertices : Ivectors_2d);
    procedure Polygon (N : Natural; Vertices : Ivectors_2d) renames Poly2i;
    procedure Polygon (Vertices : Ivectors_2d) renames Poly2i;
    procedure Popattributes;
    procedure Popmatrix;
    procedure Popname;
    procedure Popviewport;
    procedure Prefposition (X1, X2, Y1, Y2 : Pixels);
    procedure Preferredposition (X1, X2, Y1, Y2 : Pixels) renames Prefposition;
    procedure Prefsize (X, Y : Pixels);
    procedure Preferredsize (X, Y : Pixels) renames Prefsize;
    procedure Pushattributes;
    procedure Pushmatrix;
    procedure Pushname (Name : Name_Type);
    procedure Pushviewport;
    procedure Pwlcurve (Number_Of_Points : Positive;
                        Points : Nurbs_Control_Points_2d);
    procedure Piecewiselinearcurve
                 (Number_Of_Points : Positive; Points : Nurbs_Control_Points_2d)
        renames Pwlcurve;
    procedure Pwlcurve (Points : Nurbs_Control_Points_2d);
    procedure Piecewiselinearcurve (Points : Nurbs_Control_Points_2d)
        renames Pwlcurve;
    procedure Qdevice (The_Device : Device.Device);
    procedure Queuedevice (The_Device : Device.Device) renames Qdevice;
    procedure Qenter (The_Device : Device.Device;
                      Value : Device.Device_Value_Type);
    procedure Queueenter
                 (The_Device : Device.Device; Value : Device.Device_Value_Type)
        renames Qenter;
    procedure Qread (The_Device : out Device.Device;
                     Value : out Device.Device_Value_Type);
    procedure Queueread (The_Device : out Device.Device;
                         Value : out Device.Device_Value_Type) renames Qread;
    procedure Qreset;
    procedure Queuereset renames Qreset;
    function Qtest return Device.Device;
    function Queuetest return Device.Device renames Qtest;
    procedure Rcrv (Control_Points : Rationalcurvecontrol4_Type);
    procedure Rcrvn (N : Natural; Control_Points : Rationalcurvecontrol_Type);
    procedure Rationalcurve
                 (N : Natural; Control_Points : Rationalcurvecontrol_Type)
        renames Rcrvn;
    procedure Rationalcurve (Control_Points : Rationalcurvecontrol_Type);
    procedure Rdr (X, Y, Z : Coord);
    procedure Relativedraw (X, Y, Z : Coord) renames Rdr;
    procedure Rdri (X, Y, Z : Icoord);
    procedure Relativedraw (X, Y, Z : Icoord) renames Rdri;
    procedure Rdrs (X, Y, Z : Scoord);
    procedure Relativedraw (X, Y, Z : Scoord) renames Rdrs;
    procedure Rdr2 (X, Y : Coord);
    procedure Relativedraw (X, Y : Coord) renames Rdr2;
    procedure Rdr2i (X, Y : Icoord);
    procedure Relativedraw (X, Y : Icoord) renames Rdr2i;
    procedure Rdr2s (X, Y : Scoord);
    procedure Relativedraw (X, Y : Scoord) renames Rdr2s;
    procedure Readpixels (Read_This_Many : Short_Natural;
                          Colors : out Colorindices;
                          Number_Of_Pixels : out Integer);
    procedure Readpixels (Colors : out Colorindices;
                          Number_Of_Pixels : out Integer);
    procedure Readrgb (Read_This_Many : Short_Natural;
                       Red, Green, Blue : out Rgbvalues;
                       Number_Of_Pixels : out Integer);
    procedure Readrgb (Red, Green, Blue : out Rgbvalues;
                       Number_Of_Pixels : out Integer);
    procedure Readsource (Source : Readsource_Type);
    procedure Rect (X1, Y1, X2, Y2 : Coord);
    procedure Rectangle (X1, Y1, X2, Y2 : Coord) renames Rect;
    procedure Recti (X1, Y1, X2, Y2 : Icoord);
    procedure Rectangle (X1, Y1, X2, Y2 : Icoord) renames Recti;
    procedure Rects (X1, Y1, X2, Y2 : Scoord);
    procedure Rectangle (X1, Y1, X2, Y2 : Scoord) renames Rects;
    procedure Rectf (X1, Y1, X2, Y2 : Coord);
    procedure Filledrectangle (X1, Y1, X2, Y2 : Coord) renames Rectf;
    procedure Rectfi (X1, Y1, X2, Y2 : Icoord);
    procedure Filledrectangle (X1, Y1, X2, Y2 : Icoord) renames Rectfi;
    procedure Rectfs (X1, Y1, X2, Y2 : Scoord);
    procedure Filledrectangle (X1, Y1, X2, Y2 : Scoord) renames Rectfs;
    procedure Rectcopy (Lower_Left_X, Lower_Left_Y : Screencoord;
                        Upper_Right_X, Upper_Right_Y : Screencoord;
                        X, Y : Screencoord);
    procedure Rectanglecopy (Lower_Left_X, Lower_Left_Y : Screencoord;
                             Upper_Right_X, Upper_Right_Y : Screencoord;
                             X, Y : Screencoord) renames Rectcopy;
    procedure Rectread (Lower_Left_X, Lower_Left_Y : Screencoord;
                        Upper_Right_X, Upper_Right_Y : Screencoord;
                        Number_Of_Pixels : out Pixels;
                        Colors : out Colorindices);
    procedure Rectangleread (Lower_Left_X, Lower_Left_Y : Screencoord;
                             Upper_Right_X, Upper_Right_Y : Screencoord;
                             Number_Of_Pixels : out Pixels;
                             Colors : out Colorindices) renames Rectread;
    procedure Rectwrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                         Upper_Right_X, Upper_Right_Y : Screencoord;
                         Colors : Colorindices);
    procedure Rectanglewrite (Lower_Left_X, Lower_Left_Y : Screencoord;
                              Upper_Right_X, Upper_Right_Y : Screencoord;
                              Colors : Colorindices) renames Rectwrite;
    procedure Rectzoom (X_Factor, Y_Factor : Zoom_Factor_Type);
    procedure Rectanglezoom (X_Factor, Y_Factor : Zoom_Factor_Type)
        renames Rectzoom;
    procedure Reshapeviewport;
    procedure Rgbcolor (Red, Green, Blue : Rgb_Value);
    pragma Interface (C, Rgbcolor);
    pragma Interface_Information (Rgbcolor, ".RGBcolor");
    procedure Rgbcolor (Color : Rgb_Color_Type);
    procedure Rgbmode;
    procedure Rgbwritemask (Red, Green, Blue : Rgb_Write_Mask_Type);
    procedure Ringbell;
    procedure Rmv (X, Y, Z : Coord);
    procedure Relativemove (X, Y, Z : Coord) renames Rmv;
    procedure Rmvi (X, Y, Z : Icoord);
    procedure Relativemove (X, Y, Z : Icoord) renames Rmvi;
    procedure Rmvs (X, Y, Z : Scoord);
    procedure Relativemove (X, Y, Z : Scoord) renames Rmvs;
    procedure Rmv2 (X, Y : Coord);
    procedure Relativemove (X, Y : Coord) renames Rmv2;
    procedure Rmv2i (X, Y : Icoord);
    procedure Relativemove (X, Y : Icoord) renames Rmv2i;
    procedure Rmv2s (X, Y : Scoord);
    procedure Relativemove (X, Y : Scoord) renames Rmv2s;
    procedure Rot (Amount : Floatangle; Axis : Axis_Type);
    procedure Rotate (Amount : Floatangle; Axis : Axis_Type) renames Rot;
    procedure Rotate (Amount : Angle; Axis : Axis_Type);
    procedure Rpatch (X, Y, Z, W : Matrix);
    procedure Rationalpatch (X, Y, Z, W : Matrix) renames Rpatch;
    procedure Rpdr (X, Y, Z : Coord);
    procedure Relativepolygondraw (X, Y, Z : Coord) renames Rpdr;
    procedure Rpdri (X, Y, Z : Icoord);
    procedure Relativepolygondraw (X, Y, Z : Icoord) renames Rpdri;
    procedure Rpdrs (X, Y, Z : Scoord);
    procedure Relativepolygondraw (X, Y, Z : Scoord) renames Rpdrs;
    procedure Rpdr2 (X, Y : Coord);
    procedure Relativepolygondraw (X, Y : Coord) renames Rpdr2;
    procedure Rpdr2i (X, Y : Icoord);
    procedure Relativepolygondraw (X, Y : Icoord) renames Rpdr2i;
    procedure Rpdr2s (X, Y : Scoord);
    procedure Relativepolygondraw (X, Y : Scoord) renames Rpdr2s;
    procedure Rpmv (X, Y, Z : Coord);
    procedure Relativepolygonmove (X, Y, Z : Coord) renames Rpmv;
    procedure Rpmvi (X, Y, Z : Icoord);
    procedure Relativepolygonmove (X, Y, Z : Icoord) renames Rpmvi;
    procedure Rpmvs (X, Y, Z : Scoord);
    procedure Relativepolygonmove (X, Y, Z : Scoord) renames Rpmvs;
    procedure Rpmv2 (X, Y : Coord);
    procedure Relativepolygonmove (X, Y : Coord) renames Rpmv2;
    procedure Rpmv2i (X, Y : Icoord);
    procedure Relativepolygonmove (X, Y : Icoord) renames Rpmv2i;
    procedure Rpmv2s (X, Y : Scoord);
    procedure Relativepolygonmove (X, Y : Scoord) renames Rpmv2s;
    procedure Sbox (X1, Y1, X2, Y2 : Coord);
    procedure Screenbox (X1, Y1, X2, Y2 : Coord) renames Sbox;
    procedure Sboxi (X1, Y1, X2, Y2 : Icoord);
    procedure Screenbox (X1, Y1, X2, Y2 : Icoord) renames Sboxi;
    procedure Sboxs (X1, Y1, X2, Y2 : Scoord);
    procedure Screenbox (X1, Y1, X2, Y2 : Scoord) renames Sboxs;
    procedure Sboxf (X1, Y1, X2, Y2 : Coord);
    procedure Filledscreenbox (X1, Y1, X2, Y2 : Coord) renames Sboxf;
    procedure Sboxfi (X1, Y1, X2, Y2 : Icoord);
    procedure Filledscreenbox (X1, Y1, X2, Y2 : Icoord) renames Sboxfi;
    procedure Sboxfs (X1, Y1, X2, Y2 : Scoord);
    procedure Filledscreenbox (X1, Y1, X2, Y2 : Scoord) renames Sboxfs;
    procedure Scale (X, Y, Z : Scale_Factor);
    procedure Screenspace;
    procedure Scrmask (Left, Right, Bottom, Top : Screencoord);
    procedure Screenmask (Left, Right, Bottom, Top : Screencoord)
        renames Scrmask;
    procedure Setbell (Bell_Sound : Bell_Sound_Type);
    procedure Setcursor (Cursor : Cursor_Id_Type;
                         Color : Colorindex;  
                         Writemask : Colorindex  
                         );
    pragma Interface (C, Setcursor);
    procedure Setcursor (Cursor : Cursor_Id_Type);
    procedure Setdblights (Lights : Dial_And_Box_Lights_Type);
    procedure Setdialandboxlights (Lights : Dial_And_Box_Lights_Type)
        renames Setdblights;
    procedure Setlinestyle (Linestyle : Linestyle_Id_Type);
    procedure Setmap (Map : Map_Id_Type);
    procedure Setnurbsproperty (Property : Nurbs_Property_Type;
                                Value : Nurbs_Property_Value);
    procedure Setpattern (Pattern : Pattern_Id_Type);
    procedure Setpup (Menu : Menu_Id_Type;
                      Item : Menu_Item_Type;
                      Mode : Pop_Up_Enable_Type);
    procedure Setpopup (Menu : Menu_Id_Type;
                        Item : Menu_Item_Type;
                        Mode : Pop_Up_Enable_Type) renames Setpup;
    procedure Setvaluator (The_Device : Device.Device;
                           Initial, Minimum, Maximum :
                              Device.Valuator_Value_Type);
    procedure Shademodel (Model : Shade_Model_Type);
    procedure Singlebuffer;
    procedure Splf (N : Natural; Vertices : Vectors_3d; Colors : Colorindices);
    procedure Splf (Vertices : Vectors_3d; Colors : Colorindices);
    procedure Shadedfilledpolygon
                 (N : Natural; Vertices : Vectors_3d; Colors : Colorindices)
        renames Splf;
    procedure Shadedfilledpolygon (Vertices : Vectors_3d; Colors : Colorindices)
        renames Splf;
    procedure Splfs (N : Natural;
                     Vertices : Svectors_3d;
                     Colors : Colorindices);
    procedure Splfs (Vertices : Svectors_3d; Colors : Colorindices);
    procedure Shadedfilledpolygon
                 (N : Natural; Vertices : Svectors_3d; Colors : Colorindices)
        renames Splfs;
    procedure Shadedfilledpolygon
                 (Vertices : Svectors_3d; Colors : Colorindices) renames Splfs;
    procedure Splfi (N : Natural;
                     Vertices : Ivectors_3d;
                     Colors : Colorindices);
    procedure Splfi (Vertices : Ivectors_3d; Colors : Colorindices);
    procedure Shadedfilledpolygon
                 (N : Natural; Vertices : Ivectors_3d; Colors : Colorindices)
        renames Splfi;
    procedure Shadedfilledpolygon
                 (Vertices : Ivectors_3d; Colors : Colorindices) renames Splfi;
    procedure Splf2 (N : Natural; Vertices : Vectors_2d; Colors : Colorindices);
    procedure Splf2 (Vertices : Vectors_2d; Colors : Colorindices);
    procedure Shadedfilledpolygon
                 (N : Natural; Vertices : Vectors_2d; Colors : Colorindices)
        renames Splf2;
    procedure Shadedfilledpolygon (Vertices : Vectors_2d; Colors : Colorindices)
        renames Splf2;
    procedure Splf2s (N : Natural;
                      Vertices : Svectors_2d;
                      Colors : Colorindices);
    procedure Splf2s (Vertices : Svectors_2d; Colors : Colorindices);
    procedure Shadedfilledpolygon
                 (N : Natural; Vertices : Svectors_2d; Colors : Colorindices)
        renames Splf2s;
    procedure Shadedfilledpolygon
                 (Vertices : Svectors_2d; Colors : Colorindices) renames Splf2s;
    procedure Splf2i (N : Natural;
                      Vertices : Ivectors_2d;
                      Colors : Colorindices);
    procedure Splf2i (Vertices : Ivectors_2d; Colors : Colorindices);
    procedure Shadedfilledpolygon
                 (N : Natural; Vertices : Ivectors_2d; Colors : Colorindices)
        renames Splf2i;
    procedure Shadedfilledpolygon
                 (Vertices : Ivectors_2d; Colors : Colorindices) renames Splf2i;
    procedure Stepunit (X, Y : Pixels);
    function Strwidth (S : String) return Pixels;
    function Stringwidth (S : String) return Pixels renames Strwidth;
    procedure Subpixel (Smooth : Boolean);
    procedure Swapbuffers;
    procedure Swapinterval (Count : Vertical_Retraces_Type);
    procedure Swaptmesh;
    procedure Swaptrianglemesh renames Swaptmesh;
    function Swinopen (Parent : Window_Id_Type) return Window_Id_Type;
    function Subwindowopen (Parent : Window_Id_Type) return Window_Id_Type
        renames Swinopen;
    procedure Textport (Left, Right, Bottom, Top : Screencoord);
    procedure Tie (Button : Device.Device;
                   Valuator1, Valuator2 : Device.Device := Device.Nulldev);
    procedure Tpoff;
    procedure Textportoff renames Tpoff;
    procedure Tpon;
    procedure Textporton renames Tpon;
    procedure Translate (X, Y, Z : Coord);
    procedure Underlay (Planes : Bitplanes_Type);
    procedure Unqdevice (The_Device : Device.Device);
    procedure Unqueuedevice (The_Device : Device.Device) renames Unqdevice;
    procedure V2s (Vertex : Svector_2d);
    procedure Vertex (Vertex : Svector_2d) renames V2s;
    procedure V2i (Vertex : Ivector_2d);
    procedure Vertex (Vertex : Ivector_2d) renames V2i;
    procedure V2f (Vertex : Vector_2d);
    procedure Vertex (Vertex : Vector_2d) renames V2f;
    procedure V2d (Vertex : Dvector_2d);
    procedure Vertex (Vertex : Dvector_2d) renames V2d;
    procedure V3s (Vertex : Svector_3d);
    procedure Vertex (Vertex : Svector_3d) renames V3s;
    procedure V3i (Vertex : Ivector_3d);
    procedure Vertex (Vertex : Ivector_3d) renames V3i;
    procedure V3f (Vertex : Vector_3d);
    procedure Vertex (Vertex : Vector_3d) renames V3f;
    procedure V3d (Vertex : Dvector_3d);
    procedure Vertex (Vertex : Dvector_3d) renames V3d;
    procedure V4s (Vertex : Svector_4d);
    procedure Vertex (Vertex : Svector_4d) renames V4s;
    procedure V4i (Vertex : Ivector_4d);
    procedure Vertex (Vertex : Ivector_4d) renames V4i;
    procedure V4f (Vertex : Vector_4d);
    procedure Vertex (Vertex : Vector_4d) renames V4f;
    procedure V4d (Vertex : Dvector_4d);
    procedure Vertex (Vertex : Dvector_4d) renames V4d;
    procedure Viewport (Left, Right, Bottom, Top : Screencoord);
    procedure Winclose (Window : Window_Id_Type);
    procedure Windowclose (Window : Window_Id_Type) renames Winclose;
    procedure Winconstraints;
    procedure Windowconstraints renames Winconstraints;
    function Windepth (Window : Window_Id_Type) return Integer;
    function Windowdepth (Window : Window_Id_Type) return Integer
        renames Windepth;
    procedure Window (Left, Right, Bottom, Top, Near, Far : Coord);
    function Winget return Window_Id_Type;
    function Windowget return Window_Id_Type renames Winget;
    procedure Winmove (X, Y : Pixels);
    procedure Windowmove (X, Y : Pixels) renames Winmove;
    function Winopen (Name : String) return Window_Id_Type;
    function Windowopen (Name : String) return Window_Id_Type renames Winopen;
    procedure Winpop;
    procedure Windowpop renames Winpop;
    procedure Winposition (X1, X2, Y1, Y2 : Pixels);
    procedure Windowposition (X1, X2, Y1, Y2 : Pixels) renames Winposition;
    procedure Winpush;
    procedure Windowpush renames Winpush;
    procedure Winset (Window : Window_Id_Type);
    procedure Windowset (Window : Window_Id_Type) renames Winset;
    procedure Wintitle (Title : String);
    procedure Windowtitle (Title : String) renames Wintitle;
    function Winx (Dpy : X_Display_Pointer; Xid : X_Window)
                  return Window_Id_Type;
    procedure Writemask (Mask : Write_Mask_Type);
    pragma Interface (C, Writemask);
    procedure Wmpack (Mask : Packed_Rgba_Write_Masks_Type);
    procedure Writemask (Mask : Packed_Rgba_Write_Masks_Type) renames Wmpack;
    procedure Writepixels (Write_This_Many : Short_Natural;
                           Colors : Colorindices);
    procedure Writepixels (Colors : Colorindices);
    procedure Writergb (Write_This_Many : Short_Natural;
                        Red, Green, Blue : Rgbvalues);
    procedure Writergb (Red, Green, Blue : Rgbvalues);
    procedure Zbuffer (Enable_Z_Buffer : Boolean);
    procedure Zclear;
    procedure Zdraw (Enable_Z_Buffer_Drawing : Boolean);
    procedure Zfunction (F : Z_Function_Type);
    procedure Zsource (F : Z_Source_Type);
    procedure Zwritemask (Mask : Z_Write_Mask_Type);
private
    pragma Interface (C, Arc);
    pragma Interface (C, Attachcursor);
    pragma Interface (C, Backbuffer);
    pragma Interface (C, Backface);
    pragma Interface (C, Bgnclosedline);
    pragma Interface (C, Bgnline);
    pragma Interface (C, Bgnpoint);
    pragma Interface (C, Bgnpolygon);
    pragma Interface (C, Bgnsurface);
    pragma Interface (C, Bgntmesh);
    pragma Interface (C, Bgntrim);
    pragma Interface (C, Blankscreen);
    pragma Interface (C, Blanktime);
    pragma Interface (C, Blendfunction);
    pragma Interface (C, Blink);
    pragma Interface (C, Boundingbox);
    pragma Interface (C, Callobj);
    pragma Interface (C, Chunksize);
    pragma Interface (C, Circle);
    pragma Interface (C, Clkoff);
    pragma Interface (C, Clkon);
    pragma Interface (C, Closeobj);
    pragma Interface (C, Cmode);
    pragma Interface (C, Compactify);
    pragma Interface (C, Concave);
    pragma Interface (C, Curorigin);
    pragma Interface (C, Cursoff);
    pragma Interface (C, Curson);
    pragma Interface (C, Curstype);
    pragma Interface (C, Curvebasis);
    pragma Interface (C, Curveit);
    pragma Interface (C, Curveprecision);
    pragma Interface (C, Cyclemap);
    pragma Interface (C, Defbasis);
    pragma Interface (C, Deflinestyle);
    pragma Interface (C, Delobj);
    pragma Interface (C, Deltag);
    pragma Interface (C, Depthcue);
    pragma Interface (C, Dopup);
    pragma Interface (C, Doublebuffer);
    pragma Interface (C, Draw);
    pragma Interface (C, Drawmode);
    pragma Interface (C, Editobj);
    pragma Interface (C, Endclosedline);
    pragma Interface (C, Endfullscreen);
    pragma Interface (C, Endline);
    pragma Interface (C, Endpoint);
    pragma Interface (C, Endpolygon);
    pragma Interface (C, Endsurface);
    pragma Interface (C, Endtmesh);
    pragma Interface (C, Endtrim);
    pragma Interface (C, Finish);
    pragma Interface (C, Filledarc);
    pragma Interface (C, Font);
    pragma Interface (C, Filledcircle);
    pragma Interface (C, Foreground);
    pragma Interface (C, Freepup);
    pragma Interface (C, Frontbuffer);
    pragma Interface (C, Frontface);
    pragma Interface (C, Fudge);
    pragma Interface (C, Fullscrn);
    pragma Interface (C, Gbegin);
    pragma Interface (C, Gconfig);
    pragma Interface (C, Genobj);
    pragma Interface (C, Gentag);
    pragma Interface (C, Getbackface);
    pragma Interface (C, Getbuffer);
    pragma Interface (C, Getbutton);
    pragma Interface (C, Getcmmode);
    pragma Interface (C, Getcolor);
    pragma Interface (C, Getdcm);
    pragma Interface (C, Getdescender);
    pragma Interface (C, Getdisplaymode);
    pragma Interface (C, Getdrawmode);
    pragma Interface (C, Getfont);
    pragma Interface (C, Getfonttype);
    function Integer_Getgdesc (Inquiry : Getgdesc_Inquiry_Type) return Integer
        renames Getgdesc;
    pragma Interface (C, Integer_Getgdesc);
    pragma Interface_Information (Integer_Getgdesc, ".getgdesc");
    function Boolean_Getgdesc (Inquiry : Getgdesc_Inquiry_Type) return Boolean
        renames Getgdesc;
    pragma Interface (C, Boolean_Getgdesc);
    pragma Interface_Information (Boolean_Getgdesc, ".getgdesc");
    pragma Interface (C, Getheight);
    pragma Interface (C, Getlsrepeat);
    pragma Interface (C, Getlstyle);
    pragma Interface (C, Getlwidth);
    pragma Interface (C, Getmap);
    pragma Interface (C, Getmmode);
    pragma Interface (C, Getopenobj);
    pragma Interface (C, Getpattern);
    pragma Interface (C, Getplanes);
    pragma Interface (C, Getsm);
    pragma Interface (C, Getvaluator);
    pragma Interface (C, Getwritemask);
    pragma Interface (C, Getxdpy);
    pragma Interface_Information (Getxdpy, ".getXdpy");
    pragma Interface (C, Getxwid);
    pragma Interface_Information (Getxwid, ".getXwid");
    pragma Interface (C, Getzbuffer);
    pragma Interface (C, Gexit);
    pragma Interface (C, Ginit);
    pragma Interface (C, Greset);
    pragma Interface (C, Gsync);
    pragma Interface (C, Iconsize);
    pragma Interface (C, Initnames);
    pragma Interface (C, Isobj);
    pragma Interface (C, Isqueued);
    pragma Interface (C, Istag);
    pragma Interface (C, Keepaspect);
    pragma Interface (C, Lrgbrange);
    pragma Interface_Information (Lrgbrange, ".lRGBrange");
    pragma Interface (C, Lampoff);
    pragma Interface (C, Lampon);
    pragma Interface (C, Lsetdepth);
    pragma Interface (C, Linesmooth);
    pragma Interface (C, Linewidth);
    pragma Interface (C, Lmbind);
    pragma Interface (C, Lmcolor);
    pragma Interface (C, Logicop);
    pragma Interface (C, Loadname);
    pragma Interface (C, Lookat);
    pragma Interface (C, Lshaderange);
    pragma Interface (C, Lsrepeat);
    pragma Interface (C, Makeobj);
    pragma Interface (C, Maketag);
    pragma Interface (C, Mapcolor);
    pragma Interface (C, Maxsize);
    pragma Interface (C, Minsize);
    pragma Interface (C, Mmode);
    pragma Interface (C, Move);
    pragma Interface (C, Multimap);
    pragma Interface (C, Newpup);
    pragma Interface (C, Newtag);
    pragma Interface (C, Noborder);
    pragma Interface (C, Noise);
    pragma Interface (C, Noport);
    pragma Interface (C, Objdelete);
    pragma Interface (C, Objinsert);
    pragma Interface (C, Objreplace);
    pragma Interface (C, Onemap);
    pragma Interface (C, Ortho);
    pragma Interface (C, Ortho2);
    pragma Interface (C, Overlay);
    pragma Interface (C, Patchbasis);
    pragma Interface (C, Patchcurves);
    pragma Interface (C, Patchprecision);
    pragma Interface (C, Pclos);
    pragma Interface (C, Popattributes);
    pragma Interface (C, Polygondraw);
    pragma Interface (C, Pmv);
    pragma Interface (C, Pmvi);
    pragma Interface (C, Pmvs);
    pragma Interface (C, Pmv2);
    pragma Interface (C, Pmv2i);
    pragma Interface (C, Pmv2s);
    pragma Interface (C, Point);
    pragma Interface (C, Popmatrix);
    pragma Interface (C, Popname);
    pragma Interface (C, Popviewport);
    pragma Interface (C, Prefposition);
    pragma Interface (C, Prefsize);
    pragma Interface (C, Pushattributes);
    pragma Interface (C, Pushmatrix);
    pragma Interface (C, Pushviewport);
    pragma Interface (C, Qreset);
    pragma Interface (C, Rect);
    pragma Interface (C, Recti);
    pragma Interface (C, Rects);
    pragma Interface (C, Rectf);
    pragma Interface (C, Rectfi);
    pragma Interface (C, Rectfs);
    pragma Interface (C, Relativedraw);
    pragma Interface (C, Relativemove);
    pragma Interface (C, Relativepolygondraw);
    pragma Interface (C, Relativepolygonmove);
    pragma Interface (C, Reshapeviewport);
    pragma Interface (C, Rgbmode);
    pragma Interface_Information (Rgbmode, ".RGBmode");
    pragma Interface (C, Rgbwritemask);
    pragma Interface_Information (Rgbwritemask, ".RGBwritemask");
    pragma Interface (C, Ringbell);
    pragma Interface (C, Rotate);
    pragma Interface (C, Rot);
    pragma Interface (C, Setdblights);
    pragma Interface (C, Settextposition);
    pragma Interface (C, Screenspace);
    pragma Interface (C, Scale);
    pragma Interface (C, Setbell);
    pragma Interface (C, Singlebuffer);
    pragma Interface (C, Swapbuffers);
    pragma Interface (C, Swaptmesh);
    pragma Interface (C, Tpoff);
    pragma Interface (C, Tpon);
    pragma Interface (C, Translate);
    pragma Interface (C, Winpop);
    pragma Interface (C, Winconstraints);
    pragma Interface (C, Winpush);
    pragma Interface (C, Zbuffer);
    pragma Interface (C, Zclear);
    pragma Interface (C, Perspective);
    pragma Interface (C, Picksize);
    procedure Integer_Pixmode (Mode : Pixmode_Mode_Type; Value : Integer)
        renames Pixmode;
    pragma Interface (C, Integer_Pixmode);
    pragma Interface_Information (Integer_Pixmode, ".pixmode");
    procedure Boolean_Pixmode (Mode : Pixmode_Mode_Type; Value : Boolean)
        renames Pixmode;
    pragma Interface (C, Boolean_Pixmode);
    pragma Interface_Information (Boolean_Pixmode, ".pixmode");
    pragma Interface (C, Pntsmooth);
    pragma Interface (C, Polarview);
    pragma Interface (C, Pushname);
    pragma Interface (C, Qdevice);
    pragma Interface (C, Qenter);
    pragma Interface (C, Qtest);
    pragma Interface (C, Readsource);
    pragma Interface (C, Rectcopy);
    pragma Interface (C, Rectzoom);
    pragma Interface (C, Sbox);
    pragma Interface (C, Sboxi);
    pragma Interface (C, Sboxs);
    pragma Interface (C, Sboxf);
    pragma Interface (C, Sboxfi);
    pragma Interface (C, Sboxfs);
    pragma Interface (C, Setlinestyle);
    pragma Interface (C, Setmap);
    pragma Interface (C, Setpup);
    pragma Interface (C, Setvaluator);
    pragma Interface (C, Shademodel);
    pragma Interface (C, Scrmask);
    pragma Interface (C, Setpattern);
    pragma Interface (C, Subpixel);
    pragma Interface (C, Stepunit);
    pragma Interface (C, Swinopen);
    pragma Interface (C, Textport);
    pragma Interface (C, Tie);
    pragma Interface (C, Underlay);
    pragma Interface (C, Unqdevice);
    pragma Interface (C, Swapinterval);
    pragma Interface (C, Winclose);
    pragma Interface (C, Winx);
    pragma Interface (C, Viewport);
    pragma Interface (C, Windepth);
    pragma Interface (C, Window);
    pragma Interface (C, Winget);
    pragma Interface (C, Winmove);
    pragma Interface (C, Winset);
    pragma Interface (C, Winposition);
    pragma Interface (C, Zdraw);
    pragma Interface (C, Zfunction);
    pragma Interface (C, Zsource);
    pragma Interface (C, Setnurbsproperty);
    pragma Interface (C, Zwritemask);
end Gl;generic
    type Base_Type is range <>;  
    type Numbering is range <>;  
package Gl_Flags is
    type Flags_Type is new Base_Type;
    function Set (Flags : Flags_Type; Flag : Numbering; Value : Boolean := True)
                 return Flags_Type;
    pragma Inline (Set);
    function Is_Set (Flags : Flags_Type; Flag : Numbering) return Boolean;
    pragma Inline (Is_Set);
end Gl_Flags;package Gl_System_Types is
    type Float32 is new Float;
    for Float32'Size use 32;
    type Float64 is new Long_Float;
    for Float64'Size use 64;
    type Int16 is range -2 ** 15 .. 2 ** 15 - 1;
    for Int16'Size use 16;
    type Int32 is range -2 ** 31 .. 2 ** 31 - 1;
    for Int32'Size use 32;
    type Int8 is range -2 ** 7 .. 2 ** 7 - 1;
    for Int8'Size use 8;
    type Long is range -2 ** 31 .. 2 ** 31 - 1;
    for Long'Size use 32;
    type Uint16 is range 0 .. 2 ** 16 - 1;
    for Uint16'Size use 16;
    type Uint32 is range -2 ** 31 .. 2 ** 31 - 1;
    for Uint32'Size use 32;
    type Uint8 is range 0 .. 2 ** 8 - 1;
    for Uint8'Size use 8;
    type Ushort is range 0 .. 2 ** 16 - 1;
    for Ushort'Size use 16;
end Gl_System_Types;package Interrupt is
    type Signal_Type is
       (Sigprof,  
        Sigusr2,  
        Sigusr1,  
        Sigpwr,  
        Sigwinch,  
        Sigmsg,  
        Res26, Sigxfsz,  
        Sigxcpu,  
        Sigio,  
        Sigttou,  
        Sigttin,  
        Sigchld,  
        Sigcont,  
        Sigtstp,  
        Sigstop,  
        Sigurg,  
        Sigterm,  
        Sigalrm,  
        Sigpipe,  
        Sigsys,  
        Sigsegv,  
        Sigbus,  
        Sigkill,  
        Sigfpe,  
        Sigemt,  
        Sigiot,  
        Sigtrap,  
        Sigill,  
        Sigquit,  
        Sigint,  
        Sighup,  
        Res0, Res63, Sigsound,  
        Sigretract, Siggrant,  
        Sig_59, Res58, Res57, Res56, Res55, Res54, Res53, Res52, Res51,
        Res50, Res49, Res48, Res47, Res46, Res45, Res44, Res43, Res42, Res41,
        Res40, Res39, Res38, Res37, Res36, Res35, Sigvtalrm, Sigdanger);
    type Signal_Mask_Type is array (Signal_Type) of Boolean;
    pragma Pack (Signal_Mask_Type);
    function Get_Signal_Mask return Signal_Mask_Type;
    procedure Set_Signal_Mask (Signal_Mask : Signal_Mask_Type);
    function Get_Signal return Signal_Type;
    type Descriptor is private;
    function Source return Descriptor;
    package Preemption_Control is
        procedure Disable_Preemption;
        procedure Enable_Preemption;
    end Preemption_Control;
private
    pragma List (Off);
    type Descriptor is
        record
            null;
        end record;
end Interrupt;with X_Windows;
package Key_Syms is
    Xk_No_Symbol : constant X_Windows.Keyboard.Key_Sym := 0;
    Xk_Backspace : constant X_Windows.Keyboard.Key_Sym := 16#FF08#;
    Xk_Tab : constant X_Windows.Keyboard.Key_Sym := 16#FF09#;
    Xk_Clear : constant X_Windows.Keyboard.Key_Sym := 16#FF0B#;
    Xk_Linefeed : constant X_Windows.Keyboard.Key_Sym := 16#FF0A#;
    Xk_Return : constant X_Windows.Keyboard.Key_Sym := 16#FF0D#;
    Xk_Pause : constant X_Windows.Keyboard.Key_Sym := 16#FF13#;
    Xk_Escape : constant X_Windows.Keyboard.Key_Sym := 16#FF1B#;
    Xk_Delete : constant X_Windows.Keyboard.Key_Sym := 16#FFFF#;
    Xk_Compose : constant X_Windows.Keyboard.Key_Sym := 16#FF20#;
    Xk_Kanji : constant X_Windows.Keyboard.Key_Sym := 16#FF21#;
    Xk_Home : constant X_Windows.Keyboard.Key_Sym := 16#FF50#;
    Xk_Left : constant X_Windows.Keyboard.Key_Sym := 16#FF51#;
    Xk_Up : constant X_Windows.Keyboard.Key_Sym := 16#FF52#;
    Xk_Right : constant X_Windows.Keyboard.Key_Sym := 16#FF53#;
    Xk_Down : constant X_Windows.Keyboard.Key_Sym := 16#FF54#;
    Xk_Prior : constant X_Windows.Keyboard.Key_Sym := 16#FF55#;
    Xk_Next : constant X_Windows.Keyboard.Key_Sym := 16#FF56#;
    Xk_End : constant X_Windows.Keyboard.Key_Sym := 16#FF57#;
    Xk_Begin : constant X_Windows.Keyboard.Key_Sym := 16#FF58#;
    Xk_Select : constant X_Windows.Keyboard.Key_Sym := 16#FF60#;
    Xk_Print : constant X_Windows.Keyboard.Key_Sym := 16#FF61#;
    Xk_Execute : constant X_Windows.Keyboard.Key_Sym := 16#FF62#;
    Xk_Insert : constant X_Windows.Keyboard.Key_Sym := 16#FF63#;
    Xk_Undo : constant X_Windows.Keyboard.Key_Sym := 16#FF65#;
    Xk_Redo : constant X_Windows.Keyboard.Key_Sym := 16#FF66#;
    Xk_Menu : constant X_Windows.Keyboard.Key_Sym := 16#FF67#;
    Xk_Find : constant X_Windows.Keyboard.Key_Sym := 16#FF68#;
    Xk_Cancel : constant X_Windows.Keyboard.Key_Sym := 16#FF69#;
    Xk_Help : constant X_Windows.Keyboard.Key_Sym := 16#FF6A#;
    Xk_Break : constant X_Windows.Keyboard.Key_Sym := 16#FF6B#;
    Xk_Mode_Switch : constant X_Windows.Keyboard.Key_Sym := 16#FF7E#;
    Xk_Script_Switch : constant X_Windows.Keyboard.Key_Sym := 16#FF7E#;
    Xk_Num_Lock : constant X_Windows.Keyboard.Key_Sym := 16#FF7F#;
    Xk_Kp_Space : constant X_Windows.Keyboard.Key_Sym := 16#FF80#;
    Xk_Kp_Tab : constant X_Windows.Keyboard.Key_Sym := 16#FF89#;
    Xk_Kp_Enter : constant X_Windows.Keyboard.Key_Sym := 16#FF8D#;
    Xk_Kp_F1 : constant X_Windows.Keyboard.Key_Sym := 16#FF91#;
    Xk_Kp_F2 : constant X_Windows.Keyboard.Key_Sym := 16#FF92#;
    Xk_Kp_F3 : constant X_Windows.Keyboard.Key_Sym := 16#FF93#;
    Xk_Kp_F4 : constant X_Windows.Keyboard.Key_Sym := 16#FF94#;
    Xk_Kp_Equal : constant X_Windows.Keyboard.Key_Sym := 16#FFBD#;
    Xk_Kp_Multiply : constant X_Windows.Keyboard.Key_Sym := 16#FFAA#;
    Xk_Kp_Add : constant X_Windows.Keyboard.Key_Sym := 16#FFAB#;
    Xk_Kp_Separator : constant X_Windows.Keyboard.Key_Sym := 16#FFAC#;
    Xk_Kp_Subtract : constant X_Windows.Keyboard.Key_Sym := 16#FFAD#;
    Xk_Kp_Decimal : constant X_Windows.Keyboard.Key_Sym := 16#FFAE#;
    Xk_Kp_Divide : constant X_Windows.Keyboard.Key_Sym := 16#FFAF#;
    Xk_Kp_0 : constant X_Windows.Keyboard.Key_Sym := 16#FFB0#;
    Xk_Kp_1 : constant X_Windows.Keyboard.Key_Sym := 16#FFB1#;
    Xk_Kp_2 : constant X_Windows.Keyboard.Key_Sym := 16#FFB2#;
    Xk_Kp_3 : constant X_Windows.Keyboard.Key_Sym := 16#FFB3#;
    Xk_Kp_4 : constant X_Windows.Keyboard.Key_Sym := 16#FFB4#;
    Xk_Kp_5 : constant X_Windows.Keyboard.Key_Sym := 16#FFB5#;
    Xk_Kp_6 : constant X_Windows.Keyboard.Key_Sym := 16#FFB6#;
    Xk_Kp_7 : constant X_Windows.Keyboard.Key_Sym := 16#FFB7#;
    Xk_Kp_8 : constant X_Windows.Keyboard.Key_Sym := 16#FFB8#;
    Xk_Kp_9 : constant X_Windows.Keyboard.Key_Sym := 16#FFB9#;
    Xk_F1 : constant X_Windows.Keyboard.Key_Sym := 16#FFBE#;
    Xk_F2 : constant X_Windows.Keyboard.Key_Sym := 16#FFBF#;
    Xk_F3 : constant X_Windows.Keyboard.Key_Sym := 16#FFC0#;
    Xk_F4 : constant X_Windows.Keyboard.Key_Sym := 16#FFC1#;
    Xk_F5 : constant X_Windows.Keyboard.Key_Sym := 16#FFC2#;
    Xk_F6 : constant X_Windows.Keyboard.Key_Sym := 16#FFC3#;
    Xk_F7 : constant X_Windows.Keyboard.Key_Sym := 16#FFC4#;
    Xk_F8 : constant X_Windows.Keyboard.Key_Sym := 16#FFC5#;
    Xk_F9 : constant X_Windows.Keyboard.Key_Sym := 16#FFC6#;
    Xk_F10 : constant X_Windows.Keyboard.Key_Sym := 16#FFC7#;
    Xk_F11 : constant X_Windows.Keyboard.Key_Sym := 16#FFC8#;
    Xk_F12 : constant X_Windows.Keyboard.Key_Sym := 16#FFC9#;
    Xk_F13 : constant X_Windows.Keyboard.Key_Sym := 16#FFCA#;
    Xk_F14 : constant X_Windows.Keyboard.Key_Sym := 16#FFCB#;
    Xk_F15 : constant X_Windows.Keyboard.Key_Sym := 16#FFCC#;
    Xk_F16 : constant X_Windows.Keyboard.Key_Sym := 16#FFCD#;
    Xk_F17 : constant X_Windows.Keyboard.Key_Sym := 16#FFCE#;
    Xk_F18 : constant X_Windows.Keyboard.Key_Sym := 16#FFCF#;
    Xk_F19 : constant X_Windows.Keyboard.Key_Sym := 16#FFD0#;
    Xk_F20 : constant X_Windows.Keyboard.Key_Sym := 16#FFD1#;
    Xk_F21 : constant X_Windows.Keyboard.Key_Sym := 16#FFD2#;
    Xk_F22 : constant X_Windows.Keyboard.Key_Sym := 16#FFD3#;
    Xk_F23 : constant X_Windows.Keyboard.Key_Sym := 16#FFD4#;
    Xk_F24 : constant X_Windows.Keyboard.Key_Sym := 16#FFD5#;
    Xk_F25 : constant X_Windows.Keyboard.Key_Sym := 16#FFD6#;
    Xk_F26 : constant X_Windows.Keyboard.Key_Sym := 16#FFD7#;
    Xk_F27 : constant X_Windows.Keyboard.Key_Sym := 16#FFD8#;
    Xk_F28 : constant X_Windows.Keyboard.Key_Sym := 16#FFD9#;
    Xk_F29 : constant X_Windows.Keyboard.Key_Sym := 16#FFDA#;
    Xk_F30 : constant X_Windows.Keyboard.Key_Sym := 16#FFDB#;
    Xk_F31 : constant X_Windows.Keyboard.Key_Sym := 16#FFDC#;
    Xk_F32 : constant X_Windows.Keyboard.Key_Sym := 16#FFDD#;
    Xk_F33 : constant X_Windows.Keyboard.Key_Sym := 16#FFDE#;
    Xk_F34 : constant X_Windows.Keyboard.Key_Sym := 16#FFDF#;
    Xk_F35 : constant X_Windows.Keyboard.Key_Sym := 16#FFE0#;
    Xk_L1 : constant X_Windows.Keyboard.Key_Sym := Xk_F11;
    Xk_L2 : constant X_Windows.Keyboard.Key_Sym := Xk_F12;
    Xk_L3 : constant X_Windows.Keyboard.Key_Sym := Xk_F13;
    Xk_L4 : constant X_Windows.Keyboard.Key_Sym := Xk_F14;
    Xk_L5 : constant X_Windows.Keyboard.Key_Sym := Xk_F15;
    Xk_L6 : constant X_Windows.Keyboard.Key_Sym := Xk_F16;
    Xk_L7 : constant X_Windows.Keyboard.Key_Sym := Xk_F17;
    Xk_L8 : constant X_Windows.Keyboard.Key_Sym := Xk_F18;
    Xk_L9 : constant X_Windows.Keyboard.Key_Sym := Xk_F19;
    Xk_L10 : constant X_Windows.Keyboard.Key_Sym := Xk_F20;
    Xk_R1 : constant X_Windows.Keyboard.Key_Sym := Xk_F21;
    Xk_R2 : constant X_Windows.Keyboard.Key_Sym := Xk_F22;
    Xk_R3 : constant X_Windows.Keyboard.Key_Sym := Xk_F23;
    Xk_R4 : constant X_Windows.Keyboard.Key_Sym := Xk_F24;
    Xk_R5 : constant X_Windows.Keyboard.Key_Sym := Xk_F25;
    Xk_R6 : constant X_Windows.Keyboard.Key_Sym := Xk_F26;
    Xk_R7 : constant X_Windows.Keyboard.Key_Sym := Xk_F27;
    Xk_R8 : constant X_Windows.Keyboard.Key_Sym := Xk_F28;
    Xk_R9 : constant X_Windows.Keyboard.Key_Sym := Xk_F29;
    Xk_R10 : constant X_Windows.Keyboard.Key_Sym := Xk_F30;
    Xk_R11 : constant X_Windows.Keyboard.Key_Sym := Xk_F31;
    Xk_R12 : constant X_Windows.Keyboard.Key_Sym := Xk_F32;
    Xk_R13 : constant X_Windows.Keyboard.Key_Sym := Xk_F33;
    Xk_R14 : constant X_Windows.Keyboard.Key_Sym := Xk_F34;
    Xk_R15 : constant X_Windows.Keyboard.Key_Sym := Xk_F35;
    Xk_Shift_L : constant X_Windows.Keyboard.Key_Sym := 16#FFE1#;
    Xk_Shift_R : constant X_Windows.Keyboard.Key_Sym := 16#FFE2#;
    Xk_Control_L : constant X_Windows.Keyboard.Key_Sym := 16#FFE3#;
    Xk_Control_R : constant X_Windows.Keyboard.Key_Sym := 16#FFE4#;
    Xk_Caps_Lock : constant X_Windows.Keyboard.Key_Sym := 16#FFE5#;
    Xk_Shift_Lock : constant X_Windows.Keyboard.Key_Sym := 16#FFE6#;
    Xk_Meta_L : constant X_Windows.Keyboard.Key_Sym := 16#FFE7#;
    Xk_Meta_R : constant X_Windows.Keyboard.Key_Sym := 16#FFE8#;
    Xk_Alt_L : constant X_Windows.Keyboard.Key_Sym := 16#FFE9#;
    Xk_Alt_R : constant X_Windows.Keyboard.Key_Sym := 16#FFEA#;
    Xk_Super_L : constant X_Windows.Keyboard.Key_Sym := 16#FFEB#;
    Xk_Super_R : constant X_Windows.Keyboard.Key_Sym := 16#FFEC#;
    Xk_Hyper_L : constant X_Windows.Keyboard.Key_Sym := 16#FFED#;
    Xk_Hyper_R : constant X_Windows.Keyboard.Key_Sym := 16#FFEE#;
    Xk_Space : constant X_Windows.Keyboard.Key_Sym := 16#020#;
    Xk_Exclam : constant X_Windows.Keyboard.Key_Sym := 16#021#;
    Xk_Quote_Dbl : constant X_Windows.Keyboard.Key_Sym := 16#022#;
    Xk_Number_Sign : constant X_Windows.Keyboard.Key_Sym := 16#023#;
    Xk_Dollar : constant X_Windows.Keyboard.Key_Sym := 16#024#;
    Xk_Percent : constant X_Windows.Keyboard.Key_Sym := 16#025#;
    Xk_Ampersand : constant X_Windows.Keyboard.Key_Sym := 16#026#;
    Xk_Quote_Right : constant X_Windows.Keyboard.Key_Sym := 16#027#;
    Xk_Paren_Left : constant X_Windows.Keyboard.Key_Sym := 16#028#;
    Xk_Paren_Right : constant X_Windows.Keyboard.Key_Sym := 16#029#;
    Xk_Asterisk : constant X_Windows.Keyboard.Key_Sym := 16#02A#;
    Xk_Plus : constant X_Windows.Keyboard.Key_Sym := 16#02B#;
    Xk_Comma : constant X_Windows.Keyboard.Key_Sym := 16#02C#;
    Xk_Minus : constant X_Windows.Keyboard.Key_Sym := 16#02D#;
    Xk_Period : constant X_Windows.Keyboard.Key_Sym := 16#02E#;
    Xk_Slash : constant X_Windows.Keyboard.Key_Sym := 16#02F#;
    Xk_0 : constant X_Windows.Keyboard.Key_Sym := 16#030#;
    Xk_1 : constant X_Windows.Keyboard.Key_Sym := 16#031#;
    Xk_2 : constant X_Windows.Keyboard.Key_Sym := 16#032#;
    Xk_3 : constant X_Windows.Keyboard.Key_Sym := 16#033#;
    Xk_4 : constant X_Windows.Keyboard.Key_Sym := 16#034#;
    Xk_5 : constant X_Windows.Keyboard.Key_Sym := 16#035#;
    Xk_6 : constant X_Windows.Keyboard.Key_Sym := 16#036#;
    Xk_7 : constant X_Windows.Keyboard.Key_Sym := 16#037#;
    Xk_8 : constant X_Windows.Keyboard.Key_Sym := 16#038#;
    Xk_9 : constant X_Windows.Keyboard.Key_Sym := 16#039#;
    Xk_Colon : constant X_Windows.Keyboard.Key_Sym := 16#03A#;
    Xk_Semicolon : constant X_Windows.Keyboard.Key_Sym := 16#03B#;
    Xk_Less : constant X_Windows.Keyboard.Key_Sym := 16#03C#;
    Xk_Equal : constant X_Windows.Keyboard.Key_Sym := 16#03D#;
    Xk_Greater : constant X_Windows.Keyboard.Key_Sym := 16#03E#;
    Xk_Question : constant X_Windows.Keyboard.Key_Sym := 16#03F#;
    Xk_At : constant X_Windows.Keyboard.Key_Sym := 16#040#;
    Xk_A : constant X_Windows.Keyboard.Key_Sym := 16#041#;
    Xk_B : constant X_Windows.Keyboard.Key_Sym := 16#042#;
    Xk_C : constant X_Windows.Keyboard.Key_Sym := 16#043#;
    Xk_D : constant X_Windows.Keyboard.Key_Sym := 16#044#;
    Xk_E : constant X_Windows.Keyboard.Key_Sym := 16#045#;
    Xk_F : constant X_Windows.Keyboard.Key_Sym := 16#046#;
    Xk_G : constant X_Windows.Keyboard.Key_Sym := 16#047#;
    Xk_H : constant X_Windows.Keyboard.Key_Sym := 16#048#;
    Xk_I : constant X_Windows.Keyboard.Key_Sym := 16#049#;
    Xk_J : constant X_Windows.Keyboard.Key_Sym := 16#04A#;
    Xk_K : constant X_Windows.Keyboard.Key_Sym := 16#04B#;
    Xk_L : constant X_Windows.Keyboard.Key_Sym := 16#04C#;
    Xk_M : constant X_Windows.Keyboard.Key_Sym := 16#04D#;
    Xk_N : constant X_Windows.Keyboard.Key_Sym := 16#04E#;
    Xk_O : constant X_Windows.Keyboard.Key_Sym := 16#04F#;
    Xk_P : constant X_Windows.Keyboard.Key_Sym := 16#050#;
    Xk_Q : constant X_Windows.Keyboard.Key_Sym := 16#051#;
    Xk_R : constant X_Windows.Keyboard.Key_Sym := 16#052#;
    Xk_S : constant X_Windows.Keyboard.Key_Sym := 16#053#;
    Xk_T : constant X_Windows.Keyboard.Key_Sym := 16#054#;
    Xk_U : constant X_Windows.Keyboard.Key_Sym := 16#055#;
    Xk_V : constant X_Windows.Keyboard.Key_Sym := 16#056#;
    Xk_W : constant X_Windows.Keyboard.Key_Sym := 16#057#;
    Xk_X : constant X_Windows.Keyboard.Key_Sym := 16#058#;
    Xk_Y : constant X_Windows.Keyboard.Key_Sym := 16#059#;
    Xk_Z : constant X_Windows.Keyboard.Key_Sym := 16#05A#;
    Xk_Bracket_Left : constant X_Windows.Keyboard.Key_Sym := 16#05B#;
    Xk_Back_Slash : constant X_Windows.Keyboard.Key_Sym := 16#05C#;
    Xk_Bracket_Right : constant X_Windows.Keyboard.Key_Sym := 16#05D#;
    Xk_Ascii_Circum : constant X_Windows.Keyboard.Key_Sym := 16#05E#;
    Xk_Underscore : constant X_Windows.Keyboard.Key_Sym := 16#05F#;
    Xk_Quote_Left : constant X_Windows.Keyboard.Key_Sym := 16#060#;
    Xk_Lc_A : constant X_Windows.Keyboard.Key_Sym := 16#061#;
    Xk_Lc_B : constant X_Windows.Keyboard.Key_Sym := 16#062#;
    Xk_Lc_C : constant X_Windows.Keyboard.Key_Sym := 16#063#;
    Xk_Lc_D : constant X_Windows.Keyboard.Key_Sym := 16#064#;
    Xk_Lc_E : constant X_Windows.Keyboard.Key_Sym := 16#065#;
    Xk_Lc_F : constant X_Windows.Keyboard.Key_Sym := 16#066#;
    Xk_Lc_G : constant X_Windows.Keyboard.Key_Sym := 16#067#;
    Xk_Lc_H : constant X_Windows.Keyboard.Key_Sym := 16#068#;
    Xk_Lc_I : constant X_Windows.Keyboard.Key_Sym := 16#069#;
    Xk_Lc_J : constant X_Windows.Keyboard.Key_Sym := 16#06A#;
    Xk_Lc_K : constant X_Windows.Keyboard.Key_Sym := 16#06B#;
    Xk_Lc_L : constant X_Windows.Keyboard.Key_Sym := 16#06C#;
    Xk_Lc_M : constant X_Windows.Keyboard.Key_Sym := 16#06D#;
    Xk_Lc_N : constant X_Windows.Keyboard.Key_Sym := 16#06E#;
    Xk_Lc_O : constant X_Windows.Keyboard.Key_Sym := 16#06F#;
    Xk_Lc_P : constant X_Windows.Keyboard.Key_Sym := 16#070#;
    Xk_Lc_Q : constant X_Windows.Keyboard.Key_Sym := 16#071#;
    Xk_Lc_R : constant X_Windows.Keyboard.Key_Sym := 16#072#;
    Xk_Lc_S : constant X_Windows.Keyboard.Key_Sym := 16#073#;
    Xk_Lc_T : constant X_Windows.Keyboard.Key_Sym := 16#074#;
    Xk_Lc_U : constant X_Windows.Keyboard.Key_Sym := 16#075#;
    Xk_Lc_V : constant X_Windows.Keyboard.Key_Sym := 16#076#;
    Xk_Lc_W : constant X_Windows.Keyboard.Key_Sym := 16#077#;
    Xk_Lc_X : constant X_Windows.Keyboard.Key_Sym := 16#078#;
    Xk_Lc_Y : constant X_Windows.Keyboard.Key_Sym := 16#079#;
    Xk_Lc_Z : constant X_Windows.Keyboard.Key_Sym := 16#07A#;
    Xk_Brace_Left : constant X_Windows.Keyboard.Key_Sym := 16#07B#;
    Xk_Bar : constant X_Windows.Keyboard.Key_Sym := 16#07C#;
    Xk_Brace_Right : constant X_Windows.Keyboard.Key_Sym := 16#07D#;
    Xk_Ascii_Tilde : constant X_Windows.Keyboard.Key_Sym := 16#07E#;
    Xk_No_Break_Space : constant X_Windows.Keyboard.Key_Sym := 16#0A0#;
    Xk_Exclam_Down : constant X_Windows.Keyboard.Key_Sym := 16#0A1#;
    Xk_Cent : constant X_Windows.Keyboard.Key_Sym := 16#0A2#;
    Xk_Sterling : constant X_Windows.Keyboard.Key_Sym := 16#0A3#;
    Xk_Currency : constant X_Windows.Keyboard.Key_Sym := 16#0A4#;
    Xk_Yen : constant X_Windows.Keyboard.Key_Sym := 16#0A5#;
    Xk_Broken_Bar : constant X_Windows.Keyboard.Key_Sym := 16#0A6#;
    Xk_Section : constant X_Windows.Keyboard.Key_Sym := 16#0A7#;
    Xk_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0A8#;
    Xk_Copyright : constant X_Windows.Keyboard.Key_Sym := 16#0A9#;
    Xk_Ord_Feminine : constant X_Windows.Keyboard.Key_Sym := 16#0AA#;
    Xk_Guillemot_Left : constant X_Windows.Keyboard.Key_Sym := 16#0AB#;
    Xk_Logical_Not : constant X_Windows.Keyboard.Key_Sym := 16#0AC#;
    Xk_Hyphen : constant X_Windows.Keyboard.Key_Sym := 16#0AD#;
    Xk_Registered : constant X_Windows.Keyboard.Key_Sym := 16#0AE#;
    Xk_Macron : constant X_Windows.Keyboard.Key_Sym := 16#0AF#;
    Xk_Degree : constant X_Windows.Keyboard.Key_Sym := 16#0B0#;
    Xk_Plus_Minus : constant X_Windows.Keyboard.Key_Sym := 16#0B1#;
    Xk_Two_Superior : constant X_Windows.Keyboard.Key_Sym := 16#0B2#;
    Xk_Three_Superior : constant X_Windows.Keyboard.Key_Sym := 16#0B3#;
    Xk_Acute : constant X_Windows.Keyboard.Key_Sym := 16#0B4#;
    Xk_Mu : constant X_Windows.Keyboard.Key_Sym := 16#0B5#;
    Xk_Paragraph : constant X_Windows.Keyboard.Key_Sym := 16#0B6#;
    Xk_Period_Centered : constant X_Windows.Keyboard.Key_Sym := 16#0B7#;
    Xk_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#0B8#;
    Xk_One_Superior : constant X_Windows.Keyboard.Key_Sym := 16#0B9#;
    Xk_Masculine : constant X_Windows.Keyboard.Key_Sym := 16#0BA#;
    Xk_Guillemot_Right : constant X_Windows.Keyboard.Key_Sym := 16#0BB#;
    Xk_One_Quarter : constant X_Windows.Keyboard.Key_Sym := 16#0BC#;
    Xk_One_Half : constant X_Windows.Keyboard.Key_Sym := 16#0BD#;
    Xk_Three_Quarters : constant X_Windows.Keyboard.Key_Sym := 16#0BE#;
    Xk_Question_Down : constant X_Windows.Keyboard.Key_Sym := 16#0BF#;
    Xk_Agrave : constant X_Windows.Keyboard.Key_Sym := 16#0C0#;
    Xk_Aacute : constant X_Windows.Keyboard.Key_Sym := 16#0C1#;
    Xk_Acircumflex : constant X_Windows.Keyboard.Key_Sym := 16#0C2#;
    Xk_Atilde : constant X_Windows.Keyboard.Key_Sym := 16#0C3#;
    Xk_Adiaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0C4#;
    Xk_Aring : constant X_Windows.Keyboard.Key_Sym := 16#0C5#;
    Xk_Ae : constant X_Windows.Keyboard.Key_Sym := 16#0C6#;
    Xk_Ccedilla : constant X_Windows.Keyboard.Key_Sym := 16#0C7#;
    Xk_Egrave : constant X_Windows.Keyboard.Key_Sym := 16#0C8#;
    Xk_Eacute : constant X_Windows.Keyboard.Key_Sym := 16#0C9#;
    Xk_Ecircumflex : constant X_Windows.Keyboard.Key_Sym := 16#0CA#;
    Xk_Ediaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0CB#;
    Xk_Igrave : constant X_Windows.Keyboard.Key_Sym := 16#0CC#;
    Xk_Iacute : constant X_Windows.Keyboard.Key_Sym := 16#0CD#;
    Xk_Icircumflex : constant X_Windows.Keyboard.Key_Sym := 16#0CE#;
    Xk_Idiaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0CF#;
    Xk_Eth : constant X_Windows.Keyboard.Key_Sym := 16#0D0#;
    Xk_Ntilde : constant X_Windows.Keyboard.Key_Sym := 16#0D1#;
    Xk_Ograve : constant X_Windows.Keyboard.Key_Sym := 16#0D2#;
    Xk_Oacute : constant X_Windows.Keyboard.Key_Sym := 16#0D3#;
    Xk_Ocircumflex : constant X_Windows.Keyboard.Key_Sym := 16#0D4#;
    Xk_Otilde : constant X_Windows.Keyboard.Key_Sym := 16#0D5#;
    Xk_Odiaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0D6#;
    Xk_Multiply : constant X_Windows.Keyboard.Key_Sym := 16#0D7#;
    Xk_Ooblique : constant X_Windows.Keyboard.Key_Sym := 16#0D8#;
    Xk_Ugrave : constant X_Windows.Keyboard.Key_Sym := 16#0D9#;
    Xk_Uacute : constant X_Windows.Keyboard.Key_Sym := 16#0DA#;
    Xk_Ucircumflex : constant X_Windows.Keyboard.Key_Sym := 16#0DB#;
    Xk_Udiaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0DC#;
    Xk_Yacute : constant X_Windows.Keyboard.Key_Sym := 16#0DD#;
    Xk_Thorn_1 : constant X_Windows.Keyboard.Key_Sym := 16#0DE#;
    Xk_German_Dbl_S : constant X_Windows.Keyboard.Key_Sym := 16#0DF#;
    Xk_A_Grave : constant X_Windows.Keyboard.Key_Sym := 16#0E0#;
    Xk_A_Acute : constant X_Windows.Keyboard.Key_Sym := 16#0E1#;
    Xk_A_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#0E2#;
    Xk_Wtilde : constant X_Windows.Keyboard.Key_Sym := 16#0E3#;
    Xk_A_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0E4#;
    Xk_A_Ring : constant X_Windows.Keyboard.Key_Sym := 16#0E5#;
    Xk_A_E : constant X_Windows.Keyboard.Key_Sym := 16#0E6#;
    Xk_C_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#0E7#;
    Xk_E_Grave : constant X_Windows.Keyboard.Key_Sym := 16#0E8#;
    Xk_E_Acute : constant X_Windows.Keyboard.Key_Sym := 16#0E9#;
    Xk_E_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#0EA#;
    Xk_E_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0EB#;
    Xk_I_Grave : constant X_Windows.Keyboard.Key_Sym := 16#0EC#;
    Xk_I_Acute : constant X_Windows.Keyboard.Key_Sym := 16#0ED#;
    Xk_I_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#0EE#;
    Xk_I_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0EF#;
    Xk_E_Th : constant X_Windows.Keyboard.Key_Sym := 16#0F0#;
    Xk_N_Tilde : constant X_Windows.Keyboard.Key_Sym := 16#0F1#;
    Xk_O_Grave : constant X_Windows.Keyboard.Key_Sym := 16#0F2#;
    Xk_O_Acute : constant X_Windows.Keyboard.Key_Sym := 16#0F3#;
    Xk_O_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#0F4#;
    Xk_O_Tilde : constant X_Windows.Keyboard.Key_Sym := 16#0F5#;
    Xk_O_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0F6#;
    Xk_Division : constant X_Windows.Keyboard.Key_Sym := 16#0F7#;
    Xk_O_Slash : constant X_Windows.Keyboard.Key_Sym := 16#0F8#;
    Xk_U_Grave : constant X_Windows.Keyboard.Key_Sym := 16#0F9#;
    Xk_U_Acute : constant X_Windows.Keyboard.Key_Sym := 16#0FA#;
    Xk_U_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#0FB#;
    Xk_U_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0FC#;
    Xk_Y_Acute : constant X_Windows.Keyboard.Key_Sym := 16#0FD#;
    Xk_Thorn_2 : constant X_Windows.Keyboard.Key_Sym := 16#0FE#;
    Xk_Y_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#0FF#;
    Xk_Aogonek : constant X_Windows.Keyboard.Key_Sym := 16#1A1#;
    Xk_Breve : constant X_Windows.Keyboard.Key_Sym := 16#1A2#;
    Xk_Lstroke : constant X_Windows.Keyboard.Key_Sym := 16#1A3#;
    Xk_Lcaron : constant X_Windows.Keyboard.Key_Sym := 16#1A5#;
    Xk_Sacute : constant X_Windows.Keyboard.Key_Sym := 16#1A6#;
    Xk_Scaron : constant X_Windows.Keyboard.Key_Sym := 16#1A9#;
    Xk_Scedilla : constant X_Windows.Keyboard.Key_Sym := 16#1AA#;
    Xk_Tcaron : constant X_Windows.Keyboard.Key_Sym := 16#1AB#;
    Xk_Zacute : constant X_Windows.Keyboard.Key_Sym := 16#1AC#;
    Xk_Zcaron : constant X_Windows.Keyboard.Key_Sym := 16#1AE#;
    Xk_Zabovedot : constant X_Windows.Keyboard.Key_Sym := 16#1AF#;
    Xk_A_Ogonek : constant X_Windows.Keyboard.Key_Sym := 16#1B1#;
    Xk_Ogonek : constant X_Windows.Keyboard.Key_Sym := 16#1B2#;
    Xk_L_Stroke : constant X_Windows.Keyboard.Key_Sym := 16#1B3#;
    Xk_L_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1B5#;
    Xk_S_Acute : constant X_Windows.Keyboard.Key_Sym := 16#1B6#;
    Xk_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1B7#;
    Xk_S_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1B9#;
    Xk_S_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#1BA#;
    Xk_T_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1BB#;
    Xk_Z_Acute : constant X_Windows.Keyboard.Key_Sym := 16#1BC#;
    Xk_Double_Acute : constant X_Windows.Keyboard.Key_Sym := 16#1BD#;
    Xk_Z_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1BE#;
    Xk_Z_Abovedot : constant X_Windows.Keyboard.Key_Sym := 16#1BF#;
    Xk_Racute : constant X_Windows.Keyboard.Key_Sym := 16#1C0#;
    Xk_Abreve : constant X_Windows.Keyboard.Key_Sym := 16#1C3#;
    Xk_Cacute : constant X_Windows.Keyboard.Key_Sym := 16#1C6#;
    Xk_Ccaron : constant X_Windows.Keyboard.Key_Sym := 16#1C8#;
    Xk_Eogonek : constant X_Windows.Keyboard.Key_Sym := 16#1CA#;
    Xk_Ecaron : constant X_Windows.Keyboard.Key_Sym := 16#1CC#;
    Xk_Dcaron : constant X_Windows.Keyboard.Key_Sym := 16#1CF#;
    Xk_Nacute : constant X_Windows.Keyboard.Key_Sym := 16#1D1#;
    Xk_Ncaron : constant X_Windows.Keyboard.Key_Sym := 16#1D2#;
    Xk_Odoubleacute : constant X_Windows.Keyboard.Key_Sym := 16#1D5#;
    Xk_Rcaron : constant X_Windows.Keyboard.Key_Sym := 16#1D8#;
    Xk_Uring : constant X_Windows.Keyboard.Key_Sym := 16#1D9#;
    Xk_Udoubleacute : constant X_Windows.Keyboard.Key_Sym := 16#1DA#;
    Xk_Tcedilla : constant X_Windows.Keyboard.Key_Sym := 16#1DE#;
    Xk_R_Acute : constant X_Windows.Keyboard.Key_Sym := 16#1E0#;
    Xk_A_Breve : constant X_Windows.Keyboard.Key_Sym := 16#1E3#;
    Xk_C_Acute : constant X_Windows.Keyboard.Key_Sym := 16#1E6#;
    Xk_C_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1E8#;
    Xk_E_Ogonek : constant X_Windows.Keyboard.Key_Sym := 16#1EA#;
    Xk_E_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1EC#;
    Xk_D_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1EF#;
    Xk_N_Acute : constant X_Windows.Keyboard.Key_Sym := 16#1F1#;
    Xk_N_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1F2#;
    Xk_R_Caron : constant X_Windows.Keyboard.Key_Sym := 16#1F8#;
    Xk_U_Ring : constant X_Windows.Keyboard.Key_Sym := 16#1F9#;
    Xk_T_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#1FE#;
    Xk_Above_Dot : constant X_Windows.Keyboard.Key_Sym := 16#1FF#;
    Xk_Hstroke : constant X_Windows.Keyboard.Key_Sym := 16#2A1#;
    Xk_Hcircumflex : constant X_Windows.Keyboard.Key_Sym := 16#2A6#;
    Xk_Iabovedot : constant X_Windows.Keyboard.Key_Sym := 16#2A9#;
    Xk_Gbreve : constant X_Windows.Keyboard.Key_Sym := 16#2AB#;
    Xk_Jcircumflex : constant X_Windows.Keyboard.Key_Sym := 16#2AC#;
    Xk_H_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#2B1#;
    Xk_Hslash : constant X_Windows.Keyboard.Key_Sym := 16#2B6#;
    Xk_Idotless : constant X_Windows.Keyboard.Key_Sym := 16#2B9#;
    Xk_G_Breve : constant X_Windows.Keyboard.Key_Sym := 16#2BB#;
    Xk_J_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#2BC#;
    Xk_Cabovedot : constant X_Windows.Keyboard.Key_Sym := 16#2C5#;
    Xk_Ccircumflex : constant X_Windows.Keyboard.Key_Sym := 16#2C6#;
    Xk_Gabovedot : constant X_Windows.Keyboard.Key_Sym := 16#2D5#;
    Xk_Gcircumflex : constant X_Windows.Keyboard.Key_Sym := 16#2D8#;
    Xk_Ubreve : constant X_Windows.Keyboard.Key_Sym := 16#2DD#;
    Xk_Wcircumflex : constant X_Windows.Keyboard.Key_Sym := 16#2DE#;
    Xk_Sgernamsharp : constant X_Windows.Keyboard.Key_Sym := 16#2DF#;
    Xk_C_Abovedot : constant X_Windows.Keyboard.Key_Sym := 16#2E5#;
    Xk_C_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#2E6#;
    Xk_G_Abovedot : constant X_Windows.Keyboard.Key_Sym := 16#2F5#;
    Xk_G_Circumflex : constant X_Windows.Keyboard.Key_Sym := 16#2F8#;
    Xk_U_Breve : constant X_Windows.Keyboard.Key_Sym := 16#2FD#;
    Xk_Scircumflex : constant X_Windows.Keyboard.Key_Sym := 16#2FE#;
    Xk_Kappa : constant X_Windows.Keyboard.Key_Sym := 16#3A2#;
    Xk_Rcedilla : constant X_Windows.Keyboard.Key_Sym := 16#3A3#;
    Xk_Itilde : constant X_Windows.Keyboard.Key_Sym := 16#3A5#;
    Xk_Lcedilla : constant X_Windows.Keyboard.Key_Sym := 16#3A6#;
    Xk_Emacron : constant X_Windows.Keyboard.Key_Sym := 16#3AA#;
    Xk_Gcedilla : constant X_Windows.Keyboard.Key_Sym := 16#3AB#;
    Xk_Tslash : constant X_Windows.Keyboard.Key_Sym := 16#3AC#;
    Xk_R_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#3B3#;
    Xk_I_Tilde : constant X_Windows.Keyboard.Key_Sym := 16#3B5#;
    Xk_L_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#3B6#;
    Xk_E_Macron : constant X_Windows.Keyboard.Key_Sym := 16#3BA#;
    Xk_Gacute : constant X_Windows.Keyboard.Key_Sym := 16#3BB#;
    Xk_T_Slash : constant X_Windows.Keyboard.Key_Sym := 16#3BC#;
    Xk_Eng : constant X_Windows.Keyboard.Key_Sym := 16#3BD#;
    Xk_E_Ng : constant X_Windows.Keyboard.Key_Sym := 16#3BF#;
    Xk_Amacron : constant X_Windows.Keyboard.Key_Sym := 16#3C0#;
    Xk_Iogonek : constant X_Windows.Keyboard.Key_Sym := 16#3C7#;
    Xk_Eabovedot : constant X_Windows.Keyboard.Key_Sym := 16#3CC#;
    Xk_Imacron : constant X_Windows.Keyboard.Key_Sym := 16#3CF#;
    Xk_Ncedilla : constant X_Windows.Keyboard.Key_Sym := 16#3D1#;
    Xk_Omacron : constant X_Windows.Keyboard.Key_Sym := 16#3D2#;
    Xk_Kcedilla : constant X_Windows.Keyboard.Key_Sym := 16#3D3#;
    Xk_Uogonek : constant X_Windows.Keyboard.Key_Sym := 16#3D9#;
    Xk_Utilde : constant X_Windows.Keyboard.Key_Sym := 16#3DD#;
    Xk_Umacron : constant X_Windows.Keyboard.Key_Sym := 16#3DE#;
    Xk_A_Macron : constant X_Windows.Keyboard.Key_Sym := 16#3E0#;
    Xk_I_Ogonek : constant X_Windows.Keyboard.Key_Sym := 16#3E7#;
    Xk_E_Abovedot : constant X_Windows.Keyboard.Key_Sym := 16#3EC#;
    Xk_I_Macron : constant X_Windows.Keyboard.Key_Sym := 16#3EF#;
    Xk_N_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#3F1#;
    Xk_O_Macron : constant X_Windows.Keyboard.Key_Sym := 16#3F2#;
    Xk_K_Cedilla : constant X_Windows.Keyboard.Key_Sym := 16#3F3#;
    Xk_U_Ogonek : constant X_Windows.Keyboard.Key_Sym := 16#3F9#;
    Xk_U_Tilde : constant X_Windows.Keyboard.Key_Sym := 16#3FD#;
    Xk_U_Macron : constant X_Windows.Keyboard.Key_Sym := 16#3FE#;
    Xk_Overline : constant X_Windows.Keyboard.Key_Sym := 16#47E#;
    Xk_Kana_Fullstop : constant X_Windows.Keyboard.Key_Sym := 16#4A1#;
    Xk_Kana_Opening_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#4A2#;
    Xk_Kana_Closing_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#4A3#;
    Xk_Kana_Comma : constant X_Windows.Keyboard.Key_Sym := 16#4A4#;
    Xk_Kana_Middle_Dot : constant X_Windows.Keyboard.Key_Sym := 16#4A5#;
    Xk_Katakana_Wo : constant X_Windows.Keyboard.Key_Sym := 16#4A6#;
    Xk_Katakana_A : constant X_Windows.Keyboard.Key_Sym := 16#4A7#;
    Xk_Katakana_I : constant X_Windows.Keyboard.Key_Sym := 16#4A8#;
    Xk_Katakana_U : constant X_Windows.Keyboard.Key_Sym := 16#4A9#;
    Xk_Katakana_E : constant X_Windows.Keyboard.Key_Sym := 16#4AA#;
    Xk_Katakana_O : constant X_Windows.Keyboard.Key_Sym := 16#4AB#;
    Xk_Ya : constant X_Windows.Keyboard.Key_Sym := 16#4AC#;
    Xk_Yu : constant X_Windows.Keyboard.Key_Sym := 16#4AD#;
    Xk_Yo : constant X_Windows.Keyboard.Key_Sym := 16#4AE#;
    Xk_Tu : constant X_Windows.Keyboard.Key_Sym := 16#4AF#;
    Xk_Prolonged_Sound : constant X_Windows.Keyboard.Key_Sym := 16#4B0#;
    Xk_Uc_A : constant X_Windows.Keyboard.Key_Sym := 16#4B1#;
    Xk_Uc_I : constant X_Windows.Keyboard.Key_Sym := 16#4B2#;
    Xk_Uc_U : constant X_Windows.Keyboard.Key_Sym := 16#4B3#;
    Xk_Uc_E : constant X_Windows.Keyboard.Key_Sym := 16#4B4#;
    Xk_Uc_O : constant X_Windows.Keyboard.Key_Sym := 16#4B5#;
    Xk_Kana_Ka : constant X_Windows.Keyboard.Key_Sym := 16#4B6#;
    Xk_Kana_Ki : constant X_Windows.Keyboard.Key_Sym := 16#4B7#;
    Xk_Kana_Ku : constant X_Windows.Keyboard.Key_Sym := 16#4B8#;
    Xk_Kana_Ke : constant X_Windows.Keyboard.Key_Sym := 16#4B9#;
    Xk_Kana_Ko : constant X_Windows.Keyboard.Key_Sym := 16#4BA#;
    Xk_Kana_Sa : constant X_Windows.Keyboard.Key_Sym := 16#4BB#;
    Xk_Kana_Shi : constant X_Windows.Keyboard.Key_Sym := 16#4BC#;
    Xk_Kana_Su : constant X_Windows.Keyboard.Key_Sym := 16#4BD#;
    Xk_Kana_Se : constant X_Windows.Keyboard.Key_Sym := 16#4BE#;
    Xk_Kana_So : constant X_Windows.Keyboard.Key_Sym := 16#4BF#;
    Xk_Kana_Ta : constant X_Windows.Keyboard.Key_Sym := 16#4C0#;
    Xk_Kana_Ti : constant X_Windows.Keyboard.Key_Sym := 16#4C1#;
    Xk_Kana_Tu : constant X_Windows.Keyboard.Key_Sym := 16#4C2#;
    Xk_Kana_Te : constant X_Windows.Keyboard.Key_Sym := 16#4C3#;
    Xk_Kana_To : constant X_Windows.Keyboard.Key_Sym := 16#4C4#;
    Xk_Kana_Na : constant X_Windows.Keyboard.Key_Sym := 16#4C5#;
    Xk_Kana_Ni : constant X_Windows.Keyboard.Key_Sym := 16#4C6#;
    Xk_Kana_Nu : constant X_Windows.Keyboard.Key_Sym := 16#4C7#;
    Xk_Kana_Ne : constant X_Windows.Keyboard.Key_Sym := 16#4C8#;
    Xk_Kana_No : constant X_Windows.Keyboard.Key_Sym := 16#4C9#;
    Xk_Kana_Ha : constant X_Windows.Keyboard.Key_Sym := 16#4CA#;
    Xk_Kana_Hi : constant X_Windows.Keyboard.Key_Sym := 16#4CB#;
    Xk_Kana_Hu : constant X_Windows.Keyboard.Key_Sym := 16#4CC#;
    Xk_Kana_He : constant X_Windows.Keyboard.Key_Sym := 16#4CD#;
    Xk_Kana_Ho : constant X_Windows.Keyboard.Key_Sym := 16#4CE#;
    Xk_Kana_Ma : constant X_Windows.Keyboard.Key_Sym := 16#4CF#;
    Xk_Kana_Mi : constant X_Windows.Keyboard.Key_Sym := 16#4D0#;
    Xk_Kana_Mu : constant X_Windows.Keyboard.Key_Sym := 16#4D1#;
    Xk_Kana_Me : constant X_Windows.Keyboard.Key_Sym := 16#4D2#;
    Xk_Kana_Mo : constant X_Windows.Keyboard.Key_Sym := 16#4D3#;
    Xk_Kana_Ya : constant X_Windows.Keyboard.Key_Sym := 16#4D4#;
    Xk_Kana_Yu : constant X_Windows.Keyboard.Key_Sym := 16#4D5#;
    Xk_Kana_Yo : constant X_Windows.Keyboard.Key_Sym := 16#4D6#;
    Xk_Kana_Ra : constant X_Windows.Keyboard.Key_Sym := 16#4D7#;
    Xk_Kana_Ri : constant X_Windows.Keyboard.Key_Sym := 16#4D8#;
    Xk_Kana_Ru : constant X_Windows.Keyboard.Key_Sym := 16#4D9#;
    Xk_Kana_Re : constant X_Windows.Keyboard.Key_Sym := 16#4DA#;
    Xk_Kana_Ro : constant X_Windows.Keyboard.Key_Sym := 16#4DB#;
    Xk_Kana_Wa : constant X_Windows.Keyboard.Key_Sym := 16#4DC#;
    Xk_Kana_N : constant X_Windows.Keyboard.Key_Sym := 16#4DD#;
    Xk_Voiced_Sound : constant X_Windows.Keyboard.Key_Sym := 16#4DE#;
    Xk_Semivoiced_Sound : constant X_Windows.Keyboard.Key_Sym := 16#4DF#;
    Xk_Kana_Switch : constant X_Windows.Keyboard.Key_Sym := Xk_Mode_Switch;
    Xk_Arabic_Comma : constant X_Windows.Keyboard.Key_Sym := 16#5AC#;
    Xk_Arabic_Semicolon : constant X_Windows.Keyboard.Key_Sym := 16#5BB#;
    Xk_Arabic_Question_Mark : constant X_Windows.Keyboard.Key_Sym := 16#5BF#;
    Xk_Arabic_Hamza : constant X_Windows.Keyboard.Key_Sym := 16#5C1#;
    Xk_Arabic_Madda_On_Alef : constant X_Windows.Keyboard.Key_Sym := 16#5C2#;
    Xk_Arabic_Hamza_On_Alef : constant X_Windows.Keyboard.Key_Sym := 16#5C3#;
    Xk_Arabic_Hamza_On_Waw : constant X_Windows.Keyboard.Key_Sym := 16#5C4#;
    Xk_Arabic_Hamza_Under_Alef : constant X_Windows.Keyboard.Key_Sym := 16#5C5#;
    Xk_Arabic_Hamza_On_Yeh : constant X_Windows.Keyboard.Key_Sym := 16#5C6#;
    Xk_Arabic_Alef : constant X_Windows.Keyboard.Key_Sym := 16#5C7#;
    Xk_Arabic_Beh : constant X_Windows.Keyboard.Key_Sym := 16#5C8#;
    Xk_Arabic_Tehmarbuta : constant X_Windows.Keyboard.Key_Sym := 16#5C9#;
    Xk_Arabic_Teh : constant X_Windows.Keyboard.Key_Sym := 16#5CA#;
    Xk_Arabic_Theh : constant X_Windows.Keyboard.Key_Sym := 16#5CB#;
    Xk_Arabic_Jeem : constant X_Windows.Keyboard.Key_Sym := 16#5CC#;
    Xk_Arabic_Hah : constant X_Windows.Keyboard.Key_Sym := 16#5CD#;
    Xk_Arabic_Khah : constant X_Windows.Keyboard.Key_Sym := 16#5CE#;
    Xk_Arabic_Dal : constant X_Windows.Keyboard.Key_Sym := 16#5CF#;
    Xk_Arabic_Thal : constant X_Windows.Keyboard.Key_Sym := 16#5D0#;
    Xk_Arabic_Ra : constant X_Windows.Keyboard.Key_Sym := 16#5D1#;
    Xk_Arabic_Zain : constant X_Windows.Keyboard.Key_Sym := 16#5D2#;
    Xk_Arabic_Seen : constant X_Windows.Keyboard.Key_Sym := 16#5D3#;
    Xk_Arabic_Sheen : constant X_Windows.Keyboard.Key_Sym := 16#5D4#;
    Xk_Arabic_Sad : constant X_Windows.Keyboard.Key_Sym := 16#5D5#;
    Xk_Arabic_Dad : constant X_Windows.Keyboard.Key_Sym := 16#5D6#;
    Xk_Arabic_Tah : constant X_Windows.Keyboard.Key_Sym := 16#5D7#;
    Xk_Arabic_Zah : constant X_Windows.Keyboard.Key_Sym := 16#5D8#;
    Xk_Arabic_Ain : constant X_Windows.Keyboard.Key_Sym := 16#5D9#;
    Xk_Arabic_Ghain : constant X_Windows.Keyboard.Key_Sym := 16#5DA#;
    Xk_Arabic_Tatweel : constant X_Windows.Keyboard.Key_Sym := 16#5E0#;
    Xk_Arabic_Feh : constant X_Windows.Keyboard.Key_Sym := 16#5E1#;
    Xk_Arabic_Qaf : constant X_Windows.Keyboard.Key_Sym := 16#5E2#;
    Xk_Arabic_Kaf : constant X_Windows.Keyboard.Key_Sym := 16#5E3#;
    Xk_Arabic_Lam : constant X_Windows.Keyboard.Key_Sym := 16#5E4#;
    Xk_Arabic_Meem : constant X_Windows.Keyboard.Key_Sym := 16#5E5#;
    Xk_Arabic_Noon : constant X_Windows.Keyboard.Key_Sym := 16#5E6#;
    Xk_Arabic_Heh : constant X_Windows.Keyboard.Key_Sym := 16#5E7#;
    Xk_Arabic_Waw : constant X_Windows.Keyboard.Key_Sym := 16#5E8#;
    Xk_Arabic_Alef_Maksura : constant X_Windows.Keyboard.Key_Sym := 16#5E9#;
    Xk_Arabic_Yeh : constant X_Windows.Keyboard.Key_Sym := 16#5EA#;
    Xk_Arabic_Fatha_Tan : constant X_Windows.Keyboard.Key_Sym := 16#5EB#;
    Xk_Arabic_Damma_Tan : constant X_Windows.Keyboard.Key_Sym := 16#5EC#;
    Xk_Arabic_Kasra_Tan : constant X_Windows.Keyboard.Key_Sym := 16#5ED#;
    Xk_Arabic_Fatha : constant X_Windows.Keyboard.Key_Sym := 16#5EE#;
    Xk_Arabic_Damma : constant X_Windows.Keyboard.Key_Sym := 16#5EF#;
    Xk_Arabic_Kasra : constant X_Windows.Keyboard.Key_Sym := 16#5F0#;
    Xk_Arabic_Shadda : constant X_Windows.Keyboard.Key_Sym := 16#5F1#;
    Xk_Arabic_Sukun : constant X_Windows.Keyboard.Key_Sym := 16#5F2#;
    Xk_Arabic_Switch : constant X_Windows.Keyboard.Key_Sym := Xk_Mode_Switch;
    Xk_Serbian_Dje : constant X_Windows.Keyboard.Key_Sym := 16#6A1#;
    Xk_Macedonia_Gje : constant X_Windows.Keyboard.Key_Sym := 16#6A2#;
    Xk_Cyrillic_Io : constant X_Windows.Keyboard.Key_Sym := 16#6A3#;
    Xk_Ukranian_Je : constant X_Windows.Keyboard.Key_Sym := 16#6A4#;
    Xk_Macedonia_Dse : constant X_Windows.Keyboard.Key_Sym := 16#6A5#;
    Xk_Ukranian_I : constant X_Windows.Keyboard.Key_Sym := 16#6A6#;
    Xk_Ukranian_Yi : constant X_Windows.Keyboard.Key_Sym := 16#6A7#;
    Xk_Serbian_Je : constant X_Windows.Keyboard.Key_Sym := 16#6A8#;
    Xk_Serbian_Lje : constant X_Windows.Keyboard.Key_Sym := 16#6A9#;
    Xk_Serbian_Nje : constant X_Windows.Keyboard.Key_Sym := 16#6AA#;
    Xk_Serbian_Tshe : constant X_Windows.Keyboard.Key_Sym := 16#6AB#;
    Xk_Macedonia_Kje : constant X_Windows.Keyboard.Key_Sym := 16#6AC#;
    Xk_Byelorussian_Shortu : constant X_Windows.Keyboard.Key_Sym := 16#6AE#;
    Xk_Serbian_Dze : constant X_Windows.Keyboard.Key_Sym := 16#6AF#;
    Xk_Numerosign : constant X_Windows.Keyboard.Key_Sym := 16#6B0#;
    Xk_Serbian_Uc_Dje : constant X_Windows.Keyboard.Key_Sym := 16#6B1#;
    Xk_Macedonia_Uc_Gje : constant X_Windows.Keyboard.Key_Sym := 16#6B2#;
    Xk_Cyrillic_Uc_Io : constant X_Windows.Keyboard.Key_Sym := 16#6B3#;
    Xk_Ukranian_Uc_Je : constant X_Windows.Keyboard.Key_Sym := 16#6B4#;
    Xk_Macedonia_Uc_Dse : constant X_Windows.Keyboard.Key_Sym := 16#6B5#;
    Xk_Ukranian_Uc_I : constant X_Windows.Keyboard.Key_Sym := 16#6B6#;
    Xk_Ukranian_Uc_Yi : constant X_Windows.Keyboard.Key_Sym := 16#6B7#;
    Xk_Serbian_Uc_Je : constant X_Windows.Keyboard.Key_Sym := 16#6B8#;
    Xk_Serbian_Uc_Lje : constant X_Windows.Keyboard.Key_Sym := 16#6B9#;
    Xk_Serbian_Uc_Nje : constant X_Windows.Keyboard.Key_Sym := 16#6BA#;
    Xk_Serbian_Uc_Tshe : constant X_Windows.Keyboard.Key_Sym := 16#6BB#;
    Xk_Macedonia_Uc_Kje : constant X_Windows.Keyboard.Key_Sym := 16#6BC#;
    Xk_Byelorussian_Uc_Shortu : constant X_Windows.Keyboard.Key_Sym := 16#6BE#;
    Xk_Serbian_Uc_Dze : constant X_Windows.Keyboard.Key_Sym := 16#6BF#;
    Xk_Cyrillic_Yu : constant X_Windows.Keyboard.Key_Sym := 16#6C0#;
    Xk_Cyrillic_A : constant X_Windows.Keyboard.Key_Sym := 16#6C1#;
    Xk_Cyrillic_Be : constant X_Windows.Keyboard.Key_Sym := 16#6C2#;
    Xk_Cyrillic_Tse : constant X_Windows.Keyboard.Key_Sym := 16#6C3#;
    Xk_Cyrillic_De : constant X_Windows.Keyboard.Key_Sym := 16#6C4#;
    Xk_Cyrillic_Ie : constant X_Windows.Keyboard.Key_Sym := 16#6C5#;
    Xk_Cyrillic_Ef : constant X_Windows.Keyboard.Key_Sym := 16#6C6#;
    Xk_Cyrillic_Ghe : constant X_Windows.Keyboard.Key_Sym := 16#6C7#;
    Xk_Cyrillic_Ha : constant X_Windows.Keyboard.Key_Sym := 16#6C8#;
    Xk_Cyrillic_I : constant X_Windows.Keyboard.Key_Sym := 16#6C9#;
    Xk_Cyrillic_Shorti : constant X_Windows.Keyboard.Key_Sym := 16#6CA#;
    Xk_Cyrillic_Ka : constant X_Windows.Keyboard.Key_Sym := 16#6CB#;
    Xk_Cyrillic_El : constant X_Windows.Keyboard.Key_Sym := 16#6CC#;
    Xk_Cyrillic_Em : constant X_Windows.Keyboard.Key_Sym := 16#6CD#;
    Xk_Cyrillic_En : constant X_Windows.Keyboard.Key_Sym := 16#6CE#;
    Xk_Cyrillic_O : constant X_Windows.Keyboard.Key_Sym := 16#6CF#;
    Xk_Cyrillic_Pe : constant X_Windows.Keyboard.Key_Sym := 16#6D0#;
    Xk_Cyrillic_Ya : constant X_Windows.Keyboard.Key_Sym := 16#6D1#;
    Xk_Cyrillic_Er : constant X_Windows.Keyboard.Key_Sym := 16#6D2#;
    Xk_Cyrillic_Es : constant X_Windows.Keyboard.Key_Sym := 16#6D3#;
    Xk_Cyrillic_Te : constant X_Windows.Keyboard.Key_Sym := 16#6D4#;
    Xk_Cyrillic_U : constant X_Windows.Keyboard.Key_Sym := 16#6D5#;
    Xk_Cyrillic_Zhe : constant X_Windows.Keyboard.Key_Sym := 16#6D6#;
    Xk_Cyrillic_Ve : constant X_Windows.Keyboard.Key_Sym := 16#6D7#;
    Xk_Cyrillic_Softsign : constant X_Windows.Keyboard.Key_Sym := 16#6D8#;
    Xk_Cyrillic_Yeru : constant X_Windows.Keyboard.Key_Sym := 16#6D9#;
    Xk_Cyrillic_Ze : constant X_Windows.Keyboard.Key_Sym := 16#6DA#;
    Xk_Cyrillic_Sha : constant X_Windows.Keyboard.Key_Sym := 16#6DB#;
    Xk_Cyrillic_E : constant X_Windows.Keyboard.Key_Sym := 16#6DC#;
    Xk_Cyrillic_Shcha : constant X_Windows.Keyboard.Key_Sym := 16#6DD#;
    Xk_Cyrillic_Che : constant X_Windows.Keyboard.Key_Sym := 16#6DE#;
    Xk_Cyrillic_Hardsign : constant X_Windows.Keyboard.Key_Sym := 16#6DF#;
    Xk_Cyrillic_Uc_Yu : constant X_Windows.Keyboard.Key_Sym := 16#6E0#;
    Xk_Cyrillic_Uc_A : constant X_Windows.Keyboard.Key_Sym := 16#6E1#;
    Xk_Cyrillic_Uc_Be : constant X_Windows.Keyboard.Key_Sym := 16#6E2#;
    Xk_Cyrillic_Uc_Tse : constant X_Windows.Keyboard.Key_Sym := 16#6E3#;
    Xk_Cyrillic_Uc_De : constant X_Windows.Keyboard.Key_Sym := 16#6E4#;
    Xk_Cyrillic_Uc_Ie : constant X_Windows.Keyboard.Key_Sym := 16#6E5#;
    Xk_Cyrillic_Uc_Ef : constant X_Windows.Keyboard.Key_Sym := 16#6E6#;
    Xk_Cyrillic_Uc_Ghe : constant X_Windows.Keyboard.Key_Sym := 16#6E7#;
    Xk_Cyrillic_Uc_Ha : constant X_Windows.Keyboard.Key_Sym := 16#6E8#;
    Xk_Cyrillic_Uc_I : constant X_Windows.Keyboard.Key_Sym := 16#6E9#;
    Xk_Cyrillic_Uc_Shorti : constant X_Windows.Keyboard.Key_Sym := 16#6EA#;
    Xk_Cyrillic_Uc_Ka : constant X_Windows.Keyboard.Key_Sym := 16#6EB#;
    Xk_Cyrillic_Uc_El : constant X_Windows.Keyboard.Key_Sym := 16#6EC#;
    Xk_Cyrillic_Uc_Em : constant X_Windows.Keyboard.Key_Sym := 16#6ED#;
    Xk_Cyrillic_Uc_En : constant X_Windows.Keyboard.Key_Sym := 16#6EE#;
    Xk_Cyrillic_Uc_O : constant X_Windows.Keyboard.Key_Sym := 16#6EF#;
    Xk_Cyrillic_Uc_Pe : constant X_Windows.Keyboard.Key_Sym := 16#6F0#;
    Xk_Cyrillic_Uc_Ya : constant X_Windows.Keyboard.Key_Sym := 16#6F1#;
    Xk_Cyrillic_Uc_Er : constant X_Windows.Keyboard.Key_Sym := 16#6F2#;
    Xk_Cyrillic_Uc_Es : constant X_Windows.Keyboard.Key_Sym := 16#6F3#;
    Xk_Cyrillic_Uc_Te : constant X_Windows.Keyboard.Key_Sym := 16#6F4#;
    Xk_Cyrillic_Uc_U : constant X_Windows.Keyboard.Key_Sym := 16#6F5#;
    Xk_Cyrillic_Uc_Zhe : constant X_Windows.Keyboard.Key_Sym := 16#6F6#;
    Xk_Cyrillic_Uc_Ve : constant X_Windows.Keyboard.Key_Sym := 16#6F7#;
    Xk_Cyrillic_Uc_Softsign : constant X_Windows.Keyboard.Key_Sym := 16#6F8#;
    Xk_Cyrillic_Uc_Yeru : constant X_Windows.Keyboard.Key_Sym := 16#6F9#;
    Xk_Cyrillic_Uc_Ze : constant X_Windows.Keyboard.Key_Sym := 16#6FA#;
    Xk_Cyrillic_Uc_Sha : constant X_Windows.Keyboard.Key_Sym := 16#6FB#;
    Xk_Cyrillic_Uc_E : constant X_Windows.Keyboard.Key_Sym := 16#6FC#;
    Xk_Cyrillic_Uc_Shcha : constant X_Windows.Keyboard.Key_Sym := 16#6FD#;
    Xk_Cyrillic_Uc_Che : constant X_Windows.Keyboard.Key_Sym := 16#6FE#;
    Xk_Cyrillic_Uc_Hardsign : constant X_Windows.Keyboard.Key_Sym := 16#6FF#;
    Xk_Greek_Uc_Alpha_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7A1#;
    Xk_Greek_Uc_Epsilon_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7A2#;
    Xk_Greek_Uc_Eta_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7A3#;
    Xk_Greek_Uc_Iota_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7A4#;
    Xk_Greek_Uc_Iota_Diaeresis : constant X_Windows.Keyboard.Key_Sym := 16#7A5#;
    Xk_Greek_Uc_Iota_Accent_Diaeresis :
       constant X_Windows.Keyboard.Key_Sym := 16#7A6#;
    Xk_Greek_Uc_Omicron_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7A7#;
    Xk_Greek_Uc_Upsilon_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7A8#;
    Xk_Greek_Uc_Upsilon_Dieresis :
       constant X_Windows.Keyboard.Key_Sym := 16#7A9#;
    Xk_Greek_Uc_Upsilon_Accent_Dieresis :
       constant X_Windows.Keyboard.Key_Sym := 16#7AA#;
    Xk_Greek_Uc_Omega_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7AB#;
    Xk_Greek_Alpha_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7B1#;
    Xk_Greek_Epsilon_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7B2#;
    Xk_Greek_Eta_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7B3#;
    Xk_Greek_Iota_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7B4#;
    Xk_Greek_Iota_Dieresis : constant X_Windows.Keyboard.Key_Sym := 16#7B5#;
    Xk_Greek_Iota_Accent_Dieresis :
       constant X_Windows.Keyboard.Key_Sym := 16#7B6#;
    Xk_Greek_Omicron_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7B7#;
    Xk_Greek_Upsilon_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7B8#;
    Xk_Greek_Upsilon_Dieresis : constant X_Windows.Keyboard.Key_Sym := 16#7B9#;
    Xk_Greek_Upsilon_Accent_Dieresis :
       constant X_Windows.Keyboard.Key_Sym := 16#7BA#;
    Xk_Greek_Omega_Accent : constant X_Windows.Keyboard.Key_Sym := 16#7BB#;
    Xk_Greek_Uc_Alpha : constant X_Windows.Keyboard.Key_Sym := 16#7C1#;
    Xk_Greek_Uc_Beta : constant X_Windows.Keyboard.Key_Sym := 16#7C2#;
    Xk_Greek_Uc_Gamma : constant X_Windows.Keyboard.Key_Sym := 16#7C3#;
    Xk_Greek_Uc_Delta : constant X_Windows.Keyboard.Key_Sym := 16#7C4#;
    Xk_Greek_Uc_Epsilon : constant X_Windows.Keyboard.Key_Sym := 16#7C5#;
    Xk_Greek_Uc_Zeta : constant X_Windows.Keyboard.Key_Sym := 16#7C6#;
    Xk_Greek_Uc_Eta : constant X_Windows.Keyboard.Key_Sym := 16#7C7#;
    Xk_Greek_Uc_Theta : constant X_Windows.Keyboard.Key_Sym := 16#7C8#;
    Xk_Greek_Uc_Iota : constant X_Windows.Keyboard.Key_Sym := 16#7C9#;
    Xk_Greek_Uc_Kappa : constant X_Windows.Keyboard.Key_Sym := 16#7CA#;
    Xk_Greek_Uc_Lambda : constant X_Windows.Keyboard.Key_Sym := 16#7CB#;
    Xk_Greek_Uc_Mu : constant X_Windows.Keyboard.Key_Sym := 16#7CC#;
    Xk_Greek_Uc_Nu : constant X_Windows.Keyboard.Key_Sym := 16#7CD#;
    Xk_Greek_Uc_Xi : constant X_Windows.Keyboard.Key_Sym := 16#7CE#;
    Xk_Greek_Uc_Omicron : constant X_Windows.Keyboard.Key_Sym := 16#7CF#;
    Xk_Greek_Uc_Pi : constant X_Windows.Keyboard.Key_Sym := 16#7D0#;
    Xk_Greek_Uc_Rho : constant X_Windows.Keyboard.Key_Sym := 16#7D1#;
    Xk_Greek_Uc_Sigma : constant X_Windows.Keyboard.Key_Sym := 16#7D2#;
    Xk_Greek_Uc_Tau : constant X_Windows.Keyboard.Key_Sym := 16#7D4#;
    Xk_Greek_Uc_Upsilon : constant X_Windows.Keyboard.Key_Sym := 16#7D5#;
    Xk_Greek_Uc_Phi : constant X_Windows.Keyboard.Key_Sym := 16#7D6#;
    Xk_Greek_Uc_Chi : constant X_Windows.Keyboard.Key_Sym := 16#7D7#;
    Xk_Greek_Uc_Psi : constant X_Windows.Keyboard.Key_Sym := 16#7D8#;
    Xk_Greek_Uc_Omega : constant X_Windows.Keyboard.Key_Sym := 16#7D9#;
    Xk_Greek_Alpha : constant X_Windows.Keyboard.Key_Sym := 16#7E1#;
    Xk_Greek_Beta : constant X_Windows.Keyboard.Key_Sym := 16#7E2#;
    Xk_Greek_Gamma : constant X_Windows.Keyboard.Key_Sym := 16#7E3#;
    Xk_Greek_Delta : constant X_Windows.Keyboard.Key_Sym := 16#7E4#;
    Xk_Greek_Epsilon : constant X_Windows.Keyboard.Key_Sym := 16#7E5#;
    Xk_Greek_Zeta : constant X_Windows.Keyboard.Key_Sym := 16#7E6#;
    Xk_Greek_Eta : constant X_Windows.Keyboard.Key_Sym := 16#7E7#;
    Xk_Greek_Theta : constant X_Windows.Keyboard.Key_Sym := 16#7E8#;
    Xk_Greek_Iota : constant X_Windows.Keyboard.Key_Sym := 16#7E9#;
    Xk_Greek_Kappa : constant X_Windows.Keyboard.Key_Sym := 16#7EA#;
    Xk_Greek_Lambda : constant X_Windows.Keyboard.Key_Sym := 16#7EB#;
    Xk_Greek_Mu : constant X_Windows.Keyboard.Key_Sym := 16#7EC#;
    Xk_Greek_Nu : constant X_Windows.Keyboard.Key_Sym := 16#7ED#;
    Xk_Greek_Xi : constant X_Windows.Keyboard.Key_Sym := 16#7EE#;
    Xk_Greek_Omicron : constant X_Windows.Keyboard.Key_Sym := 16#7EF#;
    Xk_Greek_Pi : constant X_Windows.Keyboard.Key_Sym := 16#7F0#;
    Xk_Greek_Rho : constant X_Windows.Keyboard.Key_Sym := 16#7F1#;
    Xk_Greek_Sigma : constant X_Windows.Keyboard.Key_Sym := 16#7F2#;
    Xk_Greek_Final_Small_Sigma : constant X_Windows.Keyboard.Key_Sym := 16#7F3#;
    Xk_Greek_Tau : constant X_Windows.Keyboard.Key_Sym := 16#7F4#;
    Xk_Greek_Upsilon : constant X_Windows.Keyboard.Key_Sym := 16#7F5#;
    Xk_Greek_Phi : constant X_Windows.Keyboard.Key_Sym := 16#7F6#;
    Xk_Greek_Chi : constant X_Windows.Keyboard.Key_Sym := 16#7F7#;
    Xk_Greek_Psi : constant X_Windows.Keyboard.Key_Sym := 16#7F8#;
    Xk_Greek_Omega : constant X_Windows.Keyboard.Key_Sym := 16#7F9#;
    Xk_Greek_Switch : constant X_Windows.Keyboard.Key_Sym := Xk_Mode_Switch;
    Xk_Left_Radical : constant X_Windows.Keyboard.Key_Sym := 16#8A1#;
    Xk_Top_Left_Radical : constant X_Windows.Keyboard.Key_Sym := 16#8A2#;
    Xk_Horiz_Connector : constant X_Windows.Keyboard.Key_Sym := 16#8A3#;
    Xk_Top_Integral : constant X_Windows.Keyboard.Key_Sym := 16#8A4#;
    Xk_Bot_Integral : constant X_Windows.Keyboard.Key_Sym := 16#8A5#;
    Xk_Vert_Connector : constant X_Windows.Keyboard.Key_Sym := 16#8A6#;
    Xk_Top_Left_Sq_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#8A7#;
    Xk_Bot_Left_Sq_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#8A8#;
    Xk_Top_Right_Sq_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#8A9#;
    Xk_Bot_Right_Sq_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#8AA#;
    Xk_Top_Left_Parens : constant X_Windows.Keyboard.Key_Sym := 16#8AB#;
    Xk_Bot_Left_Parens : constant X_Windows.Keyboard.Key_Sym := 16#8AC#;
    Xk_Top_Right_Parens : constant X_Windows.Keyboard.Key_Sym := 16#8AD#;
    Xk_Bot_Right_Parens : constant X_Windows.Keyboard.Key_Sym := 16#8AE#;
    Xk_Left_Middle_Curly_Brace : constant X_Windows.Keyboard.Key_Sym := 16#8AF#;
    Xk_Right_Middle_Curly_Brace :
       constant X_Windows.Keyboard.Key_Sym := 16#8B0#;
    Xk_Top_Left_Summation : constant X_Windows.Keyboard.Key_Sym := 16#8B1#;
    Xk_Bot_Left_Summation : constant X_Windows.Keyboard.Key_Sym := 16#8B2#;
    Xk_Top_Vert_Summation_Connector :
       constant X_Windows.Keyboard.Key_Sym := 16#8B3#;
    Xk_Bot_Vert_Summation_Connector :
       constant X_Windows.Keyboard.Key_Sym := 16#8B4#;
    Xk_Top_Right_Summation : constant X_Windows.Keyboard.Key_Sym := 16#8B5#;
    Xk_Bot_Right_Summation : constant X_Windows.Keyboard.Key_Sym := 16#8B6#;
    Xk_Right_Middle_Summation : constant X_Windows.Keyboard.Key_Sym := 16#8B7#;
    Xk_Less_Than_Equal : constant X_Windows.Keyboard.Key_Sym := 16#8BC#;
    Xk_Not_Equal : constant X_Windows.Keyboard.Key_Sym := 16#8BD#;
    Xk_Greater_Than_Equal : constant X_Windows.Keyboard.Key_Sym := 16#8BE#;
    Xk_Integral : constant X_Windows.Keyboard.Key_Sym := 16#8BF#;
    Xk_Therefore : constant X_Windows.Keyboard.Key_Sym := 16#8C0#;
    Xk_Variation : constant X_Windows.Keyboard.Key_Sym := 16#8C1#;
    Xk_Infinity : constant X_Windows.Keyboard.Key_Sym := 16#8C2#;
    Xk_Nabla : constant X_Windows.Keyboard.Key_Sym := 16#8C5#;
    Xk_Approximate : constant X_Windows.Keyboard.Key_Sym := 16#8C8#;
    Xk_Similar_Equal : constant X_Windows.Keyboard.Key_Sym := 16#8C9#;
    Xk_If_Only_If : constant X_Windows.Keyboard.Key_Sym := 16#8CD#;
    Xk_Implies : constant X_Windows.Keyboard.Key_Sym := 16#8CE#;
    Xk_Identical : constant X_Windows.Keyboard.Key_Sym := 16#8CF#;
    Xk_Radical : constant X_Windows.Keyboard.Key_Sym := 16#8D6#;
    Xk_Included_In : constant X_Windows.Keyboard.Key_Sym := 16#8DA#;
    Xk_Includes : constant X_Windows.Keyboard.Key_Sym := 16#8DB#;
    Xk_Intersection : constant X_Windows.Keyboard.Key_Sym := 16#8DC#;
    Xk_Union : constant X_Windows.Keyboard.Key_Sym := 16#8DD#;
    Xk_Logical_And : constant X_Windows.Keyboard.Key_Sym := 16#8DE#;
    Xk_Logical_Or : constant X_Windows.Keyboard.Key_Sym := 16#8DF#;
    Xk_Partial_Derivative : constant X_Windows.Keyboard.Key_Sym := 16#8EF#;
    Xk_Function : constant X_Windows.Keyboard.Key_Sym := 16#8F6#;
    Xk_Left_Arrow : constant X_Windows.Keyboard.Key_Sym := 16#8FB#;
    Xk_Up_Arrow : constant X_Windows.Keyboard.Key_Sym := 16#8FC#;
    Xk_Right_Arrow : constant X_Windows.Keyboard.Key_Sym := 16#8FD#;
    Xk_Down_Arrow : constant X_Windows.Keyboard.Key_Sym := 16#8FE#;
    Xk_Blank : constant X_Windows.Keyboard.Key_Sym := 16#9DF#;
    Xk_Solid_Diamond : constant X_Windows.Keyboard.Key_Sym := 16#9E0#;
    Xk_Checker_Board : constant X_Windows.Keyboard.Key_Sym := 16#9E1#;
    Xk_Ht : constant X_Windows.Keyboard.Key_Sym := 16#9E2#;
    Xk_Ff : constant X_Windows.Keyboard.Key_Sym := 16#9E3#;
    Xk_Cr : constant X_Windows.Keyboard.Key_Sym := 16#9E4#;
    Xk_Lf : constant X_Windows.Keyboard.Key_Sym := 16#9E5#;
    Xk_Nl : constant X_Windows.Keyboard.Key_Sym := 16#9E8#;
    Xk_Vt : constant X_Windows.Keyboard.Key_Sym := 16#9E9#;
    Xk_Low_Right_Corner : constant X_Windows.Keyboard.Key_Sym := 16#9EA#;
    Xk_Up_Right_Corner : constant X_Windows.Keyboard.Key_Sym := 16#9EB#;
    Xk_Up_Left_Corner : constant X_Windows.Keyboard.Key_Sym := 16#9EC#;
    Xk_Low_Left_Corner : constant X_Windows.Keyboard.Key_Sym := 16#9ED#;
    Xk_Crossing_Lines : constant X_Windows.Keyboard.Key_Sym := 16#9EE#;
    Xk_Horiz_Line_Scan_1 : constant X_Windows.Keyboard.Key_Sym := 16#9EF#;
    Xk_Horiz_Line_Scan_3 : constant X_Windows.Keyboard.Key_Sym := 16#9F0#;
    Xk_Horiz_Line_Scan_5 : constant X_Windows.Keyboard.Key_Sym := 16#9F1#;
    Xk_Horiz_Line_Scan_7 : constant X_Windows.Keyboard.Key_Sym := 16#9F2#;
    Xk_Horiz_Line_Scan_9 : constant X_Windows.Keyboard.Key_Sym := 16#9F3#;
    Xk_Left_T : constant X_Windows.Keyboard.Key_Sym := 16#9F4#;
    Xk_Right_T : constant X_Windows.Keyboard.Key_Sym := 16#9F5#;
    Xk_Bot_T : constant X_Windows.Keyboard.Key_Sym := 16#9F6#;
    Xk_Top_T : constant X_Windows.Keyboard.Key_Sym := 16#9F7#;
    Xk_Vert_Bar : constant X_Windows.Keyboard.Key_Sym := 16#9F8#;
    Xk_Em_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA1#;
    Xk_En_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA2#;
    Xk_Em_3_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA3#;
    Xk_Em_4_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA4#;
    Xk_Digit_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA5#;
    Xk_Punct_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA6#;
    Xk_Thin_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA7#;
    Xk_Hair_Space : constant X_Windows.Keyboard.Key_Sym := 16#AA8#;
    Xk_Em_Dash : constant X_Windows.Keyboard.Key_Sym := 16#AA9#;
    Xk_En_Dash : constant X_Windows.Keyboard.Key_Sym := 16#AAA#;
    Xk_Sign_If_Blank : constant X_Windows.Keyboard.Key_Sym := 16#AAC#;
    Xk_Ellipsis : constant X_Windows.Keyboard.Key_Sym := 16#AAE#;
    Xk_Doub_Baseline_Dot : constant X_Windows.Keyboard.Key_Sym := 16#AAF#;
    Xk_One_Third : constant X_Windows.Keyboard.Key_Sym := 16#AB0#;
    Xk_Two_Thirds : constant X_Windows.Keyboard.Key_Sym := 16#AB1#;
    Xk_One_Fifth : constant X_Windows.Keyboard.Key_Sym := 16#AB2#;
    Xk_Two_Fifths : constant X_Windows.Keyboard.Key_Sym := 16#AB3#;
    Xk_Three_Fifths : constant X_Windows.Keyboard.Key_Sym := 16#AB4#;
    Xk_Four_Fifths : constant X_Windows.Keyboard.Key_Sym := 16#AB5#;
    Xk_One_Sixth : constant X_Windows.Keyboard.Key_Sym := 16#AB6#;
    Xk_Five_Sixths : constant X_Windows.Keyboard.Key_Sym := 16#AB7#;
    Xk_Care_Of : constant X_Windows.Keyboard.Key_Sym := 16#AB8#;
    Xk_Fig_Dash : constant X_Windows.Keyboard.Key_Sym := 16#ABB#;
    Xk_Left_Angle_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#ABC#;
    Xk_Decimal_Point : constant X_Windows.Keyboard.Key_Sym := 16#ABD#;
    Xk_Right_Angle_Bracket : constant X_Windows.Keyboard.Key_Sym := 16#ABE#;
    Xk_Marker : constant X_Windows.Keyboard.Key_Sym := 16#ABF#;
    Xk_One_Eighth : constant X_Windows.Keyboard.Key_Sym := 16#AC3#;
    Xk_Three_Eighths : constant X_Windows.Keyboard.Key_Sym := 16#AC4#;
    Xk_Five_Eighths : constant X_Windows.Keyboard.Key_Sym := 16#AC5#;
    Xk_Seven_Eighths : constant X_Windows.Keyboard.Key_Sym := 16#AC6#;
    Xk_Trade_Mark : constant X_Windows.Keyboard.Key_Sym := 16#AC9#;
    Xk_Signature_Mark : constant X_Windows.Keyboard.Key_Sym := 16#ACA#;
    Xk_Trademark_In_Circle : constant X_Windows.Keyboard.Key_Sym := 16#ACB#;
    Xk_Left_Open_Triangle : constant X_Windows.Keyboard.Key_Sym := 16#ACC#;
    Xk_Right_Open_Triangle : constant X_Windows.Keyboard.Key_Sym := 16#ACD#;
    Xk_Em_Open_Circle : constant X_Windows.Keyboard.Key_Sym := 16#ACE#;
    Xk_Em_Open_Rectangle : constant X_Windows.Keyboard.Key_Sym := 16#ACF#;
    Xk_Left_Single_Quotemark : constant X_Windows.Keyboard.Key_Sym := 16#AD0#;
    Xk_Right_Single_Quotemark : constant X_Windows.Keyboard.Key_Sym := 16#AD1#;
    Xk_Left_Double_Quotemark : constant X_Windows.Keyboard.Key_Sym := 16#AD2#;
    Xk_Right_Double_Quotemark : constant X_Windows.Keyboard.Key_Sym := 16#AD3#;
    Xk_Prescription : constant X_Windows.Keyboard.Key_Sym := 16#AD4#;
    Xk_Minutes : constant X_Windows.Keyboard.Key_Sym := 16#AD6#;
    Xk_Seconds : constant X_Windows.Keyboard.Key_Sym := 16#AD7#;
    Xk_Latin_Cross : constant X_Windows.Keyboard.Key_Sym := 16#AD9#;
    Xk_Hexagram : constant X_Windows.Keyboard.Key_Sym := 16#ADA#;
    Xk_Filled_Rect_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#ADB#;
    Xk_Filled_Left_Tri_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#ADC#;
    Xk_Filled_Right_Tri_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#ADD#;
    Xk_Em_Filled_Circle : constant X_Windows.Keyboard.Key_Sym := 16#ADE#;
    Xk_Em_Filled_Rect : constant X_Windows.Keyboard.Key_Sym := 16#ADF#;
    Xk_En_Open_Circ_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#AE0#;
    Xk_En_Open_Square_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#AE1#;
    Xk_Open_Rect_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#AE2#;
    Xk_Open_Tri_Bullet_Up : constant X_Windows.Keyboard.Key_Sym := 16#AE3#;
    Xk_Open_Tri_Bullet_Down : constant X_Windows.Keyboard.Key_Sym := 16#AE4#;
    Xk_Open_Star : constant X_Windows.Keyboard.Key_Sym := 16#AE5#;
    Xk_En_Filled_Circ_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#AE6#;
    Xk_En_Filled_Sq_Bullet : constant X_Windows.Keyboard.Key_Sym := 16#AE7#;
    Xk_Filled_Tri_Bullet_Up : constant X_Windows.Keyboard.Key_Sym := 16#AE8#;
    Xk_Filled_Tri_Bullet_Down : constant X_Windows.Keyboard.Key_Sym := 16#AE9#;
    Xk_Left_Pointer : constant X_Windows.Keyboard.Key_Sym := 16#AEA#;
    Xk_Right_Pointer : constant X_Windows.Keyboard.Key_Sym := 16#AEB#;
    Xk_Club : constant X_Windows.Keyboard.Key_Sym := 16#AEC#;
    Xk_Diamond : constant X_Windows.Keyboard.Key_Sym := 16#AED#;
    Xk_Heart : constant X_Windows.Keyboard.Key_Sym := 16#AEE#;
    Xk_Maltese_Cross : constant X_Windows.Keyboard.Key_Sym := 16#AF0#;
    Xk_Dagger : constant X_Windows.Keyboard.Key_Sym := 16#AF1#;
    Xk_Double_Dagger : constant X_Windows.Keyboard.Key_Sym := 16#AF2#;
    Xk_Checkmark : constant X_Windows.Keyboard.Key_Sym := 16#AF3#;
    Xk_Ballot_Cross : constant X_Windows.Keyboard.Key_Sym := 16#AF4#;
    Xk_Musical_Sharp : constant X_Windows.Keyboard.Key_Sym := 16#AF5#;
    Xk_Musical_Flat : constant X_Windows.Keyboard.Key_Sym := 16#AF6#;
    Xk_Male_Symbol : constant X_Windows.Keyboard.Key_Sym := 16#AF7#;
    Xk_Female_Symbol : constant X_Windows.Keyboard.Key_Sym := 16#AF8#;
    Xk_Telephone : constant X_Windows.Keyboard.Key_Sym := 16#AF9#;
    Xk_Telephone_Recorder : constant X_Windows.Keyboard.Key_Sym := 16#AFA#;
    Xk_Phonograph_Copyright : constant X_Windows.Keyboard.Key_Sym := 16#AFB#;
    Xk_Caret : constant X_Windows.Keyboard.Key_Sym := 16#AFC#;
    Xk_Single_Low_Quote_Mark : constant X_Windows.Keyboard.Key_Sym := 16#AFD#;
    Xk_Double_Low_Quote_Mark : constant X_Windows.Keyboard.Key_Sym := 16#AFE#;
    Xk_Cursor : constant X_Windows.Keyboard.Key_Sym := 16#AFF#;
    Xk_Left_Caret : constant X_Windows.Keyboard.Key_Sym := 16#BA3#;
    Xk_Right_Caret : constant X_Windows.Keyboard.Key_Sym := 16#BA6#;
    Xk_Down_Caret : constant X_Windows.Keyboard.Key_Sym := 16#BA8#;
    Xk_Up_Caret : constant X_Windows.Keyboard.Key_Sym := 16#BA9#;
    Xk_Over_Bar : constant X_Windows.Keyboard.Key_Sym := 16#BC0#;
    Xk_Down_Tack : constant X_Windows.Keyboard.Key_Sym := 16#BC2#;
    Xk_Up_Shoe : constant X_Windows.Keyboard.Key_Sym := 16#BC3#;
    Xk_Down_Stile : constant X_Windows.Keyboard.Key_Sym := 16#BC4#;
    Xk_Under_Bar : constant X_Windows.Keyboard.Key_Sym := 16#BC6#;
    Xk_Jot : constant X_Windows.Keyboard.Key_Sym := 16#BCA#;
    Xk_Quad : constant X_Windows.Keyboard.Key_Sym := 16#BCC#;
    Xk_Up_Tack : constant X_Windows.Keyboard.Key_Sym := 16#BCE#;
    Xk_Circle : constant X_Windows.Keyboard.Key_Sym := 16#BCF#;
    Xk_Up_Stile : constant X_Windows.Keyboard.Key_Sym := 16#BD3#;
    Xk_Down_Shoe : constant X_Windows.Keyboard.Key_Sym := 16#BD6#;
    Xk_Right_Shoe : constant X_Windows.Keyboard.Key_Sym := 16#BD8#;
    Xk_Left_Shoe : constant X_Windows.Keyboard.Key_Sym := 16#BDA#;
    Xk_Left_Tack : constant X_Windows.Keyboard.Key_Sym := 16#BDC#;
    Xk_Right_Tack : constant X_Windows.Keyboard.Key_Sym := 16#BFC#;
    Xk_Hebrew_Aleph : constant X_Windows.Keyboard.Key_Sym := 16#CE0#;
    Xk_Hebrew_Beth : constant X_Windows.Keyboard.Key_Sym := 16#CE1#;
    Xk_Hebrew_Gimmel : constant X_Windows.Keyboard.Key_Sym := 16#CE2#;
    Xk_Hebrew_Daleth : constant X_Windows.Keyboard.Key_Sym := 16#CE3#;
    Xk_Hebrew_He : constant X_Windows.Keyboard.Key_Sym := 16#CE4#;
    Xk_Hebrew_Waw : constant X_Windows.Keyboard.Key_Sym := 16#CE5#;
    Xk_Hebrew_Zayin : constant X_Windows.Keyboard.Key_Sym := 16#CE6#;
    Xk_Hebrew_Het : constant X_Windows.Keyboard.Key_Sym := 16#CE7#;
    Xk_Hebrew_Teth : constant X_Windows.Keyboard.Key_Sym := 16#CE8#;
    Xk_Hebrew_Yod : constant X_Windows.Keyboard.Key_Sym := 16#CE9#;
    Xk_Hebrew_Final_Kaph : constant X_Windows.Keyboard.Key_Sym := 16#CEA#;
    Xk_Hebrew_Kaph : constant X_Windows.Keyboard.Key_Sym := 16#CEB#;
    Xk_Hebrew_Lamed : constant X_Windows.Keyboard.Key_Sym := 16#CEC#;
    Xk_Hebrew_Final_Mem : constant X_Windows.Keyboard.Key_Sym := 16#CED#;
    Xk_Hebrew_Mem : constant X_Windows.Keyboard.Key_Sym := 16#CEE#;
    Xk_Hebrew_Final_Nun : constant X_Windows.Keyboard.Key_Sym := 16#CEF#;
    Xk_Hebrew_Nun : constant X_Windows.Keyboard.Key_Sym := 16#CF0#;
    Xk_Hebrew_Samekh : constant X_Windows.Keyboard.Key_Sym := 16#CF1#;
    Xk_Hebrew_Ayin : constant X_Windows.Keyboard.Key_Sym := 16#CF2#;
    Xk_Hebrew_Final_Pe : constant X_Windows.Keyboard.Key_Sym := 16#CF3#;
    Xk_Hebrew_Pe : constant X_Windows.Keyboard.Key_Sym := 16#CF4#;
    Xk_Hebrew_Final_Zadi : constant X_Windows.Keyboard.Key_Sym := 16#CF5#;
    Xk_Hebrew_Zadi : constant X_Windows.Keyboard.Key_Sym := 16#CF6#;
    Xk_Hebrew_Kuf : constant X_Windows.Keyboard.Key_Sym := 16#CF7#;
    Xk_Hebrew_Resh : constant X_Windows.Keyboard.Key_Sym := 16#CF8#;
    Xk_Hebrew_Shin : constant X_Windows.Keyboard.Key_Sym := 16#CF9#;
    Xk_Hebrew_Taf : constant X_Windows.Keyboard.Key_Sym := 16#CFA#;
    Xk_Hebrew_Switch : constant X_Windows.Keyboard.Key_Sym := Xk_Mode_Switch;
end Key_Syms;with Generic_Elementary_Functions;  
package Long_Elementary_Functions is  
   new Generic_Elementary_Functions (Long_Float);  with Generic_Math;
package Math is new Generic_Math (False);with System;
package X_Windows is
    Bad_Request : exception;
    Bad_Value : exception;
    Bad_Window : exception;
    Bad_Pixmap : exception;
    Bad_Atom : exception;
    Bad_Cursor : exception;
    Bad_Font : exception;
    Bad_Match : exception;
    Bad_Drawable : exception;
    Bad_Access : exception;
    Bad_Alloc : exception;
    Bad_Color : exception;
    Bad_Gc : exception;
    Bad_Id_Choice : exception;
    Bad_Name : exception;
    Bad_Length : exception;
    Bad_Implementation : exception;
    First_Extension_Error : exception;
    Last_Extension_Error : exception;
    type Display is private;
    type Context is private;
    type Screen is private;
    type Visual is private;
    type Drawable is private;
    subtype Window is Drawable;
    subtype Pixmap is Drawable;
    type X_Id is private;
    Null_Display : constant Display;
    Null_Context : constant Context;
    Null_Drawable : constant Drawable;
    None : constant Drawable;
    Copy_Drawable_From_Parent : constant Drawable;
    Null_Window : constant Window;
    Pointer_Window : constant Window;
    Input_Focus_Window : constant Window;
    Pointer_Root_Window : constant Window;
    Null_Pixmap : constant Pixmap;
    Parent_Relative : constant Pixmap;
    Copy_Visual_From_Parent : constant Visual;
    Null_X_Id : constant X_Id;
    type Property_Format_Type is (Format_8, Format_16, Format_32);
    type X_Short_Integer is range -2 ** 7 .. (2 ** 7) - 1;
    type X_Integer is range -2 ** 15 .. (2 ** 15) - 1;
    type X_Long_Integer is range -2 ** 31 .. (2 ** 31) - 1;
    type Boolean_Array is array (Natural range <>) of Boolean;
    type Byte is range 0 .. 255;
    type Byte_Array is array (Natural range <>) of Byte;
    type Bytes is access Byte_Array;
    type Bit_Data is range 0 .. (2 ** 8) - 1;
    for Bit_Data'Size use 8;
    type Bit_Data_Array is array (Natural range <>) of Bit_Data;
    type Bits is access Bit_Data_Array;
    type Word is range 0 .. 65_535;
    type Word_Array is array (Natural range <>) of Word;
    type Words is access Word_Array;
    type String_Pointer is access String;
    type String_Pointer_Array is array (Natural range <>) of String_Pointer;
    type String_List is access String_Pointer_Array;
    type Long_Array is array (Natural range <>) of X_Long_Integer;
    type X_Character is range 0 .. 255;
    type String_8 is array (Positive range <>) of X_Character;
    type String_Pointer_8 is access String_8;
    type Time is range -2 ** 31 .. (2 ** 31) - 1;
    type Angle is range 0 .. (360 * 64);
    type Pixels is range -2 ** 31 .. (2 ** 31) - 1;
    type Millimeters is range -2 ** 15 .. (2 ** 15) - 1;
    subtype Coordinate is Pixels;
    type Depth_Type is range 0 .. (2 ** 15) - 1;
    type Screen_Number is range 0 .. (2 ** 15) - 1;
    type Segment is
        record
            X_1, Y_1 : Coordinate := 0;
            X_2, Y_2 : Coordinate := 0;
        end record;
    type Segment_Array is array (Natural range <>) of Segment;
    type Point is
        record
            X, Y : Coordinate := 0;
        end record;
    type Point_Array is array (Natural range <>) of Point;
    type Rectangle is
        record
            X, Y : Coordinate := 0;
            Width : Pixels := 0;
            Height : Pixels := 0;
        end record;
    type Rectangle_Array is array (Natural range <>) of Rectangle;
    type Arc is
        record
            X, Y : Coordinate := 0;
            Width : Pixels := 0;
            Height : Pixels := 0;
            Angle_1 : Angle := 0;
            Angle_2 : Angle := 0;
        end record;
    type Arc_Array is array (Natural range <>) of Arc;
    subtype Plane_Mask is Boolean_Array (0 .. 24);
    type Plane_Mask_Array is array (Natural range <>) of Plane_Mask;
    All_Planes : constant Plane_Mask := (0 .. 24 => False);
    type Depth_Record is
        record
            Depth : Depth_Type;
            Number_Of_Visuals : Natural;
            Visuals : Visual;
        end record;
    type Pixmap_Format is (Xy_Bitmap, Xy_Pixmap, Z_Pixmap);
    type Order_Type is (Lsb_First, Msb_First);
    type Backing_Store_Type is (Not_Useful, When_Mapped, Always);
    type Stack_Mode_Type is (Above, Below, Top_If, Bottom_If, Opposite);
    package Atoms is
        type Atom is private;
        type Atom_Array is array (Natural range <>) of Atom;
        type Atom_List is access Atom_Array;
        Xa_Primary : constant Atom;
        Xa_Secondary : constant Atom;
        Xa_Arc : constant Atom;
        Xa_Atom : constant Atom;
        Xa_Bitmap : constant Atom;
        Xa_Cardinal : constant Atom;
        Xa_Colormap : constant Atom;
        Xa_Cursor : constant Atom;
        Xa_Cut_Buffer_0 : constant Atom;
        Xa_Cut_Buffer_1 : constant Atom;
        Xa_Cut_Buffer_2 : constant Atom;
        Xa_Cut_Buffer_3 : constant Atom;
        Xa_Cut_Buffer_4 : constant Atom;
        Xa_Cut_Buffer_5 : constant Atom;
        Xa_Cut_Buffer_6 : constant Atom;
        Xa_Cut_Buffer_7 : constant Atom;
        Xa_Drawable : constant Atom;
        Xa_Font : constant Atom;
        Xa_Integer : constant Atom;
        Xa_Pixmap : constant Atom;
        Xa_Point : constant Atom;
        Xa_Rectangle : constant Atom;
        Xa_Resource_Manager : constant Atom;
        Xa_Rgb_Color_Map : constant Atom;
        Xa_Rgb_Best_Map : constant Atom;
        Xa_Rgb_Blue_Map : constant Atom;
        Xa_Rgb_Default_Map : constant Atom;
        Xa_Rgb_Gray_Map : constant Atom;
        Xa_Rgb_Green_Map : constant Atom;
        Xa_Rgb_Red_Map : constant Atom;
        Xa_String : constant Atom;
        Xa_Visual_Id : constant Atom;
        Xa_Window : constant Atom;
        Xa_Wm_Command : constant Atom;
        Xa_Wm_Hints : constant Atom;
        Xa_Wm_Client_Machine : constant Atom;
        Xa_Wm_Icon_Name : constant Atom;
        Xa_Wm_Icon_Size : constant Atom;
        Xa_Wm_Name : constant Atom;
        Xa_Wm_Normal_Hints : constant Atom;
        Xa_Wm_Size_Hints : constant Atom;
        Xa_Wm_Zoom_Hints : constant Atom;
        Xa_Wm_Class : constant Atom;
        Xa_Wm_Transient_Height : constant Atom;
        Xa_Min_Space : constant Atom;
        Xa_Norm_Space : constant Atom;
        Xa_Max_Space : constant Atom;
        Xa_End_Space : constant Atom;
        Xa_Superscript_X : constant Atom;
        Xa_Superscript_Y : constant Atom;
        Xa_Subscript_X : constant Atom;
        Xa_Subscript_Y : constant Atom;
        Xa_Underline_Position : constant Atom;
        Xa_Underline_Thickness : constant Atom;
        Xa_Strikeout_Ascent : constant Atom;
        Xa_Strikeout_Descent : constant Atom;
        Xa_Italic_Angle : constant Atom;
        Xa_X_Height : constant Atom;
        Xa_Quad_Width : constant Atom;
        Xa_Weight : constant Atom;
        Xa_Point_Size : constant Atom;
        Xa_Resolution : constant Atom;
        Xa_Copyright : constant Atom;
        Xa_Notice : constant Atom;
        Xa_Font_Name : constant Atom;
        Xa_Family_Name : constant Atom;
        Xa_Full_Name : constant Atom;
        Xa_Cap_Height : constant Atom;
        Xa_Last_Predefined : constant Atom;
        function Visual_Id_From_Visual (Visual_Id : in Visual) return X_Id;
        function Intern_Atom (Display_Id : in Display;
                              Atom_Name : in String;
                              Only_If_Exists : in Boolean := True) return Atom;
        function Get_Atom_Name
                    (Display_Id : in Display; Atom_Id : in Atom) return String;
    private
        type Atom is range 0 .. (2 ** 28) - 1;
        Xa_Primary : constant Atom := 1;
        Xa_Secondary : constant Atom := 2;
        Xa_Arc : constant Atom := 3;
        Xa_Atom : constant Atom := 4;
        Xa_Bitmap : constant Atom := 5;
        Xa_Cardinal : constant Atom := 6;
        Xa_Colormap : constant Atom := 7;
        Xa_Cursor : constant Atom := 8;
        Xa_Cut_Buffer_0 : constant Atom := 9;
        Xa_Cut_Buffer_1 : constant Atom := 10;
        Xa_Cut_Buffer_2 : constant Atom := 11;
        Xa_Cut_Buffer_3 : constant Atom := 12;
        Xa_Cut_Buffer_4 : constant Atom := 13;
        Xa_Cut_Buffer_5 : constant Atom := 14;
        Xa_Cut_Buffer_6 : constant Atom := 15;
        Xa_Cut_Buffer_7 : constant Atom := 16;
        Xa_Drawable : constant Atom := 17;
        Xa_Font : constant Atom := 18;
        Xa_Integer : constant Atom := 19;
        Xa_Pixmap : constant Atom := 20;
        Xa_Point : constant Atom := 21;
        Xa_Rectangle : constant Atom := 22;
        Xa_Resource_Manager : constant Atom := 23;
        Xa_Rgb_Color_Map : constant Atom := 24;
        Xa_Rgb_Best_Map : constant Atom := 25;
        Xa_Rgb_Blue_Map : constant Atom := 26;
        Xa_Rgb_Default_Map : constant Atom := 27;
        Xa_Rgb_Gray_Map : constant Atom := 28;
        Xa_Rgb_Green_Map : constant Atom := 29;
        Xa_Rgb_Red_Map : constant Atom := 30;
        Xa_String : constant Atom := 31;
        Xa_Visual_Id : constant Atom := 32;
        Xa_Window : constant Atom := 33;
        Xa_Wm_Command : constant Atom := 34;
        Xa_Wm_Hints : constant Atom := 35;
        Xa_Wm_Client_Machine : constant Atom := 36;
        Xa_Wm_Icon_Name : constant Atom := 37;
        Xa_Wm_Icon_Size : constant Atom := 38;
        Xa_Wm_Name : constant Atom := 39;
        Xa_Wm_Normal_Hints : constant Atom := 40;
        Xa_Wm_Size_Hints : constant Atom := 41;
        Xa_Wm_Zoom_Hints : constant Atom := 42;
        Xa_Wm_Class : constant Atom := 67;
        Xa_Wm_Transient_Height : constant Atom := 68;
        Xa_Min_Space : constant Atom := 43;
        Xa_Norm_Space : constant Atom := 44;
        Xa_Max_Space : constant Atom := 45;
        Xa_End_Space : constant Atom := 46;
        Xa_Superscript_X : constant Atom := 47;
        Xa_Superscript_Y : constant Atom := 48;
        Xa_Subscript_X : constant Atom := 49;
        Xa_Subscript_Y : constant Atom := 50;
        Xa_Underline_Position : constant Atom := 51;
        Xa_Underline_Thickness : constant Atom := 52;
        Xa_Strikeout_Ascent : constant Atom := 53;
        Xa_Strikeout_Descent : constant Atom := 54;
        Xa_Italic_Angle : constant Atom := 55;
        Xa_X_Height : constant Atom := 56;
        Xa_Quad_Width : constant Atom := 57;
        Xa_Weight : constant Atom := 58;
        Xa_Point_Size : constant Atom := 59;
        Xa_Resolution : constant Atom := 60;
        Xa_Copyright : constant Atom := 61;
        Xa_Notice : constant Atom := 62;
        Xa_Font_Name : constant Atom := 63;
        Xa_Family_Name : constant Atom := 64;
        Xa_Full_Name : constant Atom := 65;
        Xa_Cap_Height : constant Atom := 66;
        Xa_Last_Predefined : constant Atom := Xa_Wm_Transient_Height;
    end Atoms;
    package Fonts is
        type Font is private;
        type Font_Direction is (Left_To_Right, Right_To_Left);
        type Character_Record is
            record
                Left_Bearing : Pixels;
                Right_Bearing : Pixels;
                Width : Pixels;
                Ascent : Pixels;
                Descent : Pixels;
                Attributes : Pixels;
            end record;
        type Character_Array is array (Natural range <>) of Character_Record;
        type Character_List is access Character_Array;
        type Font_Property_Record is
            record
                Name : Atoms.Atom;
                Card_32 : X_Long_Integer;
            end record;
        type Font_Property_Array is
           array (Natural range <>) of Font_Property_Record;
        type Font_Property_List is access Font_Property_Array;
        Null_Font_Id : constant Font;
        type Font_Record is
            record
                Ext_Data : System.Address;
                Font_Id : Font;
                Direction : Font_Direction;
                First_Char : X_Character;
                Last_Char : X_Character;
                First_Row : X_Character;
                Last_Row : X_Character;
                All_Exist : Boolean;
                Default_Char : X_Character;
                Properties : Font_Property_List;
                Min_Bounds : Character_Record;
                Max_Bounds : Character_Record;
                Per_Char : Character_List;
                Ascent : Pixels;
                Descent : Pixels;
            end record;
        type Font_Record_Pointer is access Font_Record;
        type Font_Record_Array is array (Natural range <>) of Font_Record;
        type Font_Record_List is access Font_Record_Array;
        type Character_2b is
            record
                Byte_1 : Byte;
                Byte_2 : Byte;
            end record;
        type String_16 is array (Natural range <>) of Character_2b;
        type String_Pointer_16 is access String_16;
        function Load_Font (Display_Id : in Display; Font_Name : in String)
                           return Font;
        function Query_Font (Display_Id : in Display; Font_Id : in Font)
                            return Font_Record;
        procedure List_Fonts_With_Info
                     (Display_Id : in Display;
                      Pattern : in String;
                      Font_Info_List : in out Font_Record_List;
                      Names_List : in out String_List);
        procedure Free_Font_Info (Names_List : in out String_List;
                                  Font_Info_List : in out Font_Record_List);
        function Load_Query_Font
                    (Display_Id : in Display; Font_Name : in String)
                    return Font_Record;
        procedure Free_Font (Display_Id : in Display;
                             Font_Info : in out Font_Record);
        procedure Get_Font_Property (Font_Info : in Font_Record;
                                     Property : in Atoms.Atom;
                                     Value : out X_Long_Integer;
                                     Defined : out Boolean);
        procedure Unload_Font (Display_Id : in Display; Font_Id : in Font);
        procedure List_Fonts (Display_Id : in Display;
                              Pattern : in String;
                              Names : in out String_List);
        procedure Free_Font_Names (Display_Id : in Display;
                                   Directories : in out String_List);
        procedure Set_Font_Path (Display_Id : in Display;
                                 Directories : in String_List);
        function Get_Font_Path (Display_Id : in Display) return String_List;
        procedure Free_Font_Path (Directories : in out String_List);
        function Text_Width (Font_Info : in Font_Record; Text : in String)
                            return Pixels;
        function Text_Width (Font_Info : in Font_Record; Text : in String_8)
                            return Pixels;
        function Text_Width_16 (Font_Info : in Font_Record; Text : in String_16)
                               return Pixels;
        procedure Text_Extents (Font_Info : in Font_Record;
                                Text : in String;
                                Direction : out Font_Direction;
                                Ascent : out Pixels;
                                Descent : out Pixels;
                                Overall : out Character_Record);
        procedure Text_Extents (Font_Info : in Font_Record;
                                Text : in String_8;
                                Direction : out Font_Direction;
                                Ascent : out Pixels;
                                Descent : out Pixels;
                                Overall : out Character_Record);
        procedure Text_Extents_16 (Font_Info : in Font_Record;
                                   Text : in String_16;
                                   Direction : out Font_Direction;
                                   Ascent : out Pixels;
                                   Descent : out Pixels;
                                   Overall : out Character_Record);
        procedure Query_Text_Extents (Display_Id : in Display;
                                      Font_Id : in Font;
                                      Text : in String;
                                      Direction : out Font_Direction;
                                      Ascent : out Pixels;
                                      Descent : out Pixels;
                                      Overall : out Character_Record);
        procedure Query_Text_Extents (Display_Id : in Display;
                                      Font_Id : in Font;
                                      Text : in String_8;
                                      Direction : out Font_Direction;
                                      Ascent : out Pixels;
                                      Descent : out Pixels;
                                      Overall : out Character_Record);
        procedure Query_Text_Extents_16 (Display_Id : in Display;
                                         Font_Id : in Font;
                                         Text : in String_16;
                                         Direction : out Font_Direction;
                                         Ascent : out Pixels;
                                         Descent : out Pixels;
                                         Overall : out Character_Record);
    private
        type Font is range 0 .. (2 ** 28) - 1;
        Null_Font_Id : constant Font := Font (0);
    end Fonts;
    package Colors is
        type Color_Map is private;
        type Color_Map_Array is array (Natural range <>) of Color_Map;
        type Color_Map_List is access Color_Map_Array;
        Null_Color_Map : constant Color_Map;
        Copy_Colormap_From_Parent : constant Color_Map;
        type Color_Flag is array (Natural range 0 .. 2) of Boolean;
        Do_Red : constant Color_Flag := Color_Flag'(0 => True, others => False);
        Do_Green : constant Color_Flag :=
           Color_Flag'(1 => True, others => False);
        Do_Blue : constant Color_Flag :=
           Color_Flag'(2 => True, others => False);
        type Rgb_Value_Type is range 0 .. 65_535;
        Full_Color : constant Rgb_Value_Type := Rgb_Value_Type'Last;
        Half_Color : constant Rgb_Value_Type := Rgb_Value_Type'Last / 2;
        Color_Off : constant Rgb_Value_Type := 0;
        type Color_Record is
            record
                Value : X_Long_Integer := 0;  
                Red : Rgb_Value_Type := 0;  
                Green : Rgb_Value_Type := 0;
                Blue : Rgb_Value_Type := 0;
                Flags : Color_Flag;
            end record;
        type Color_Array is array (Natural range <>) of Color_Record;
        type Pixel_Array is array (Natural range <>) of Pixels;
        type Pixel_List is access Pixel_Array;
        type Color_Map_Allocator is (Allocate_None, Allocate_All);
        type Standard_Colormap_Record is
            record
                Map_Id : Colors.Color_Map;
                Red_Max : Pixels;
                Red_Mult : Pixels;
                Green_Max : Pixels;
                Green_Mult : Pixels;
                Blue_Max : Pixels;
                Blue_Mult : Pixels;
                Base_Pixel : Pixels;
            end record;
        function Create_Colormap
                    (Display_Id : in Display;
                     Window_Id : in Window;
                     Visual_Id : in Visual;
                     Allocate : in Color_Map_Allocator) return Color_Map;
        procedure Copy_Colormap_And_Free (Display_Id : in Display;
                                          Source : in out Color_Map;
                                          Target : out Color_Map);
        procedure Free_Colormap (Display_Id : in Display;
                                 Map_Id : in out Color_Map);
        procedure Set_Window_Colormap (Display_Id : in Display;
                                       Window_Id : in Window;
                                       Map_Id : in Color_Map);
        procedure Allocate_Color (Display_Id : in Display;
                                  Map_Id : in Color_Map;
                                  Definition : in out Color_Record;
                                  Success : out Boolean);
        procedure Allocate_Named_Color (Display_Id : in Display;
                                        Map_Id : in Color_Map;
                                        Color_Name : in String;
                                        Screen_Def : out Color_Record;
                                        Exact_Def : out Color_Record;
                                        Success : out Boolean);
        procedure Lookup_Color (Display_Id : in Display;
                                Map_Id : in Color_Map;
                                Color_Name : in String;
                                Screen_Def : out Color_Record;
                                Exact_Def : out Color_Record;
                                Success : out Boolean);
        procedure Store_Colors (Display_Id : in Display;
                                Map_Id : in Color_Map;
                                Colors : in out Color_Array);
        procedure Store_Color (Display_Id : in Display;
                               Map_Id : in Color_Map;
                               Screen_Def : in out Color_Record);
        procedure Allocate_Color_Cells (Display_Id : in Display;
                                        Map_Id : in Color_Map;
                                        Contiguous : in Boolean;
                                        Planes : in out Plane_Mask_Array;
                                        Pixel_Values : in out Pixel_Array;
                                        Success : out Boolean);
        procedure Allocate_Color_Planes (Display_Id : in Display;
                                         Map_Id : in Color_Map;
                                         Contiguous : in Boolean;
                                         Red_Shades : in Natural;
                                         Green_Shades : in Natural;
                                         Blue_Shades : in Natural;
                                         Pixel_Values : in out Pixel_List;
                                         Red_Mask : out Plane_Mask;
                                         Green_Mask : out Plane_Mask;
                                         Blue_Mask : out Plane_Mask;
                                         Success : out Boolean);
        procedure Store_Named_Color (Display_Id : in Display;
                                     Map_Id : in Color_Map;
                                     Color_Name : in String;
                                     Map_Entry : in Pixels;
                                     Flags : in Color_Flag);
        procedure Free_Colors (Display_Id : in Display;
                               Map_Id : in Color_Map;
                               Pixels_To_Free : in Pixel_Array;
                               Planes : in Plane_Mask);
        procedure Query_Color (Display_Id : in Display;
                               Map_Id : in Color_Map;
                               The_Color : in out Color_Record);
        procedure Query_Colors (Display_Id : in Display;
                                Map_Id : in Color_Map;
                                The_Colors : in out Color_Array);
        procedure Install_Colormap
                     (Display_Id : in Display; Map_Id : in Color_Map);
        procedure Uninstall_Colormap
                     (Display_Id : in Display; Map_Id : in Color_Map);
        function List_Installed_Colormaps
                    (Display_Id : in Display; Window_Id : in Window)
                    return Color_Map_List;
        procedure Parse_Color (Display_Id : in Display;
                               Map_Id : in Color_Map;
                               Color_Name : in String;
                               Screen_Def : out Color_Record;
                               Success : out Boolean);
        procedure Get_Standard_Colormap
                     (Display_Id : in Display;
                      Window_Id : in Window;
                      Property : in Atoms.Atom;
                      Cmap_Return : out Standard_Colormap_Record;
                      Success : out Boolean);
        procedure Set_Standard_Colormap (Display_Id : in Display;
                                         Window_Id : in Window;
                                         Cmap : in Standard_Colormap_Record;
                                         Property : in Atoms.Atom);
    private
        type Color_Map is range 0 .. (2 ** 28) - 1;
        for Color_Map'Size use 32;
        Null_Color_Map : constant Color_Map := Color_Map (0);
        Copy_Colormap_From_Parent : constant Color_Map := Color_Map (0);
    end Colors;
    package Graphic_Output is
        type Graphic_Context is private;
        type Image is private;
        type Resource_Gc is private;
        Image_Context : constant Image;
        Null_Graphic_Context : constant Graphic_Context;
        type Bitmap_Status_Type is (Bitmap_Success, Bitmap_Open_Failed,
                                    Bitmap_File_Invalid, Bitmap_No_Memory);
        type Gx_Function_Code is (Gx_Clear, Gx_And, Gx_And_Reverse, Gx_Copy,
                                  Gx_And_Inverted, Gx_Noop, Gx_Xor,
                                  Gx_Or, Gx_Nor, Gx_Equiv, Gx_Invert,
                                  Gx_Or_Reverse, Gx_Copy_Inverted,
                                  Gx_Or_Inverted, Gx_Nand, Gx_Set);
        type Text_Item is
            record
                Characters : String_Pointer;
                String_Delta : Pixels;
                Font_Id : Fonts.Font;
            end record;
        type Text_Item_Array is array (Natural range <>) of Text_Item;
        type Text_Item_List is access Text_Item_Array;
        type Text_Item_8 is
            record
                Characters : String_Pointer_8;
                String_Delta : Pixels;
                Font_Id : Fonts.Font;
            end record;
        type Text_Item_8_Array is array (Natural range <>) of Text_Item_8;
        type Text_Item_8_List is access Text_Item_8_Array;
        type Text_Item_16 is
            record
                Characters : Fonts.String_Pointer_16;
                String_Delta : Pixels;
                Font_Id : Fonts.Font;
            end record;
        type Text_Item_16_Array is array (Natural range <>) of Text_Item_16;
        type Text_Item_16_List is access Text_Item_16_Array;
        type Line_Style_Type is
           (Line_Solid, Line_On_Off_Dash, Line_Double_Dash);
        type Cap_Style_Type is (Cap_Not_Last, Cap_Butt,
                                Cap_Round, Cap_Projecting);
        type Join_Style_Type is (Join_Miter, Join_Round, Join_Bevel);
        type Fill_Style_Type is (Fill_Solid, Fill_Tiled,
                                 Fill_Stippled, Fill_Opaque_Stippled);
        type Fill_Rule_Type is (Even_Odd_Rule, Winding_Rule);
        type Shape_Class_Type is
           (Tile_Shape_Class, Cursor_Shape_Class, Stipple_Shape_Class);
        type Ordering_Type is (Unsorted, Y_Sorted, Yx_Sorted, Yx_Banded);
        type Arc_Mode_Type is (Arc_Chord, Arc_Pie_Slice);
        type Subwindow_Mode_Type is (Clip_By_Children, Include_Inferiors);
        type Coordinate_Mode_Type is (Origin, Previous);
        type Shape_Type is (Complex, Convex, Nonconvex);
        subtype Gc_Mask_Type is Boolean_Array (0 .. 22);
        Gc_Function : constant Gc_Mask_Type :=
           Gc_Mask_Type'(0 => True, others => False);
        Gc_Plane_Mask : constant Gc_Mask_Type :=
           Gc_Mask_Type'(1 => True, others => False);
        Gc_Foreground : constant Gc_Mask_Type :=
           Gc_Mask_Type'(2 => True, others => False);
        Gc_Background : constant Gc_Mask_Type :=
           Gc_Mask_Type'(3 => True, others => False);
        Gc_Line_Width : constant Gc_Mask_Type :=
           Gc_Mask_Type'(4 => True, others => False);
        Gc_Line_Style : constant Gc_Mask_Type :=
           Gc_Mask_Type'(5 => True, others => False);
        Gc_Cap_Style : constant Gc_Mask_Type :=
           Gc_Mask_Type'(6 => True, others => False);
        Gc_Join_Style : constant Gc_Mask_Type :=
           Gc_Mask_Type'(7 => True, others => False);
        Gc_Fill_Style : constant Gc_Mask_Type :=
           Gc_Mask_Type'(8 => True, others => False);
        Gc_Fill_Rule : constant Gc_Mask_Type :=
           Gc_Mask_Type'(9 => True, others => False);
        Gc_Tile : constant Gc_Mask_Type :=
           Gc_Mask_Type'(10 => True, others => False);
        Gc_Stipple : constant Gc_Mask_Type :=
           Gc_Mask_Type'(11 => True, others => False);
        Gc_Ts_X_Origin : constant Gc_Mask_Type :=
           Gc_Mask_Type'(12 => True, others => False);
        Gc_Ts_Y_Origin : constant Gc_Mask_Type :=
           Gc_Mask_Type'(13 => True, others => False);
        Gc_Font : constant Gc_Mask_Type :=
           Gc_Mask_Type'(14 => True, others => False);
        Gc_Subwindow_Mode : constant Gc_Mask_Type :=
           Gc_Mask_Type'(15 => True, others => False);
        Gc_Graphics_Exposure : constant Gc_Mask_Type :=
           Gc_Mask_Type'(16 => True, others => False);
        Gc_Clip_X_Origin : constant Gc_Mask_Type :=
           Gc_Mask_Type'(17 => True, others => False);
        Gc_Clip_Y_Origin : constant Gc_Mask_Type :=
           Gc_Mask_Type'(18 => True, others => False);
        Gc_Clip_Mask : constant Gc_Mask_Type :=
           Gc_Mask_Type'(19 => True, others => False);
        Cg_Dash_Offset : constant Gc_Mask_Type :=
           Gc_Mask_Type'(20 => True, others => False);
        Gc_Dash_List : constant Gc_Mask_Type :=
           Gc_Mask_Type'(21 => True, others => False);
        Gc_Arc_Mode : constant Gc_Mask_Type :=
           Gc_Mask_Type'(22 => True, others => False);
        type Gc_Value_Record is
            record
                Logical_Operation : Gx_Function_Code := Gx_Copy;
                Plane : Plane_Mask := All_Planes;
                Foreground : Pixels := 0;
                Background : Pixels := 1;
                Line_Width : Pixels := 0;
                Line_Style : Line_Style_Type := Line_Solid;
                Cap_Style : Cap_Style_Type := Cap_Butt;
                Join_Style : Join_Style_Type := Join_Miter;
                Fill_Style : Fill_Style_Type := Fill_Solid;
                Fill_Rule : Fill_Rule_Type := Even_Odd_Rule;
                Arc_Mode : Arc_Mode_Type := Arc_Pie_Slice;
                Tile : Pixmap;
                Stipple : Pixmap;
                Ts_X_Origin : Coordinate := 0;
                Ts_Y_Origin : Coordinate := 0;
                Font_Id : Fonts.Font;
                Subwindow_Mode : Subwindow_Mode_Type := Clip_By_Children;
                Graphics_Exposures : Boolean := True;
                Clip_X_Origin : Coordinate := 0;
                Clip_Y_Origin : Coordinate := 0;
                Clip_Mask : Pixmap;
                Dash_Offset : Pixels := 0;
                Dashes : X_Short_Integer := 4;
            end record;
        function Create_Gc (Display_Id : in Display;
                            Drawable_Id : in Drawable;
                            Value_Mask : in Gc_Mask_Type;
                            Values : in Gc_Value_Record) return Graphic_Context;
        procedure Copy_Gc (Display_Id : in Display;
                           Value_Mask : in Gc_Mask_Type;
                           Source : in Graphic_Context;
                           Destination : in Graphic_Context);
        procedure Change_Gc (Display_Id : in Display;
                             Gc : in Graphic_Context;
                             Value_Mask : in Gc_Mask_Type;
                             Values : in Gc_Value_Record);
        procedure Free_Gc (Display_Id : in Display;
                           Gc : in out Graphic_Context);
        procedure Set_State (Display_Id : in Display;
                             Gc : in Graphic_Context;
                             Foreground : in Pixels;
                             Background : in Pixels;
                             Gx_Function : in Gx_Function_Code;
                             Plane : in Plane_Mask);
        procedure Set_Function (Display_Id : in Display;
                                Gc : in Graphic_Context;
                                Gx_Function : in Gx_Function_Code);
        procedure Set_Plane_Mask (Display_Id : in Display;
                                  Gc : in Graphic_Context;
                                  Plane : in Plane_Mask);
        procedure Set_Foreground (Display_Id : in Display;
                                  Gc : in Graphic_Context;
                                  Foreground : in Pixels);
        procedure Set_Background (Display_Id : in Display;
                                  Gc : in Graphic_Context;
                                  Background : in Pixels);
        procedure Set_Line_Attributes (Display_Id : in Display;
                                       Gc : in Graphic_Context;
                                       Line_Width : in Pixels;
                                       Line_Style : in Line_Style_Type;
                                       Cap_Style : in Cap_Style_Type;
                                       Join_Style : in Join_Style_Type);
        procedure Set_Dashes (Display_Id : in Display;
                              Gc : in Graphic_Context;
                              Dash_Offset : in Pixels;
                              Dash_List : in Bits);  
        procedure Set_Fill_Style (Display_Id : in Display;
                                  Gc : in Graphic_Context;
                                  Fill_Style : in Fill_Style_Type);
        procedure Set_Fill_Rule (Display_Id : in Display;
                                 Gc : in Graphic_Context;
                                 Fill_Rule : in Fill_Rule_Type);
        procedure Query_Best_Size (Display_Id : in Display;
                                   Shape_Class : in Shape_Class_Type;
                                   Which_Screen : in Drawable;
                                   Width : in out Pixels;
                                   Height : in out Pixels);
        procedure Query_Best_Tile (Display_Id : in Display;
                                   Which_Screen : in Drawable;
                                   Width : in out Pixels;
                                   Height : in out Pixels);
        procedure Query_Best_Stipple (Display_Id : in Display;
                                      Which_Screen : in Drawable;
                                      Width : in out Pixels;
                                      Height : in out Pixels);
        procedure Set_Tile (Display_Id : in Display;
                            Gc : in Graphic_Context;
                            Tile : in Pixmap);
        procedure Set_Stipple (Display_Id : in Display;
                               Gc : in Graphic_Context;
                               Stipple : in Pixmap);
        procedure Set_Ts_Origin (Display_Id : in Display;
                                 Gc : in Graphic_Context;
                                 Origin : in Point);
        procedure Set_Font (Display_Id : in Display;
                            Gc : in Graphic_Context;
                            Font_Id : in Fonts.Font);
        procedure Set_Clip_Origin (Display_Id : in Display;
                                   Gc : in Graphic_Context;
                                   Origin : in Point);
        procedure Set_Clip_Mask (Display_Id : in Display;
                                 Gc : in Graphic_Context;
                                 Clip_Mask : in Pixmap);
        procedure Set_Clip_Rectangle (Display_Id : in Display;
                                      Gc : in Graphic_Context;
                                      Origin : in Point;
                                      Rectangles : in Rectangle_Array;
                                      Ordering : in Ordering_Type);
        procedure Set_Arc_Mode (Display_Id : in Display;
                                Gc : in Graphic_Context;
                                Arc_Mode : in Arc_Mode_Type);
        procedure Set_Subwindow_Mode (Display_Id : in Display;
                                      Gc : in Graphic_Context;
                                      Subwindow_Mode : in Subwindow_Mode_Type);
        procedure Set_Graphics_Exposures (Display_Id : in Display;
                                          Gc : in Graphic_Context;
                                          Graphics_Exposures : in Boolean);
        procedure Clear_Area (Display_Id : in Display;
                              Window_Id : in Window;
                              Bounds : in Rectangle;
                              Exposures : in Boolean);
        procedure Clear_Window (Display_Id : in Display; Window_Id : in Window);
        procedure Copy_Area (Display_Id : in Display;
                             Source : in Drawable;
                             Destination : in Drawable;
                             Gc : in Graphic_Context;
                             Source_Area : in Rectangle;
                             Dest_Origin : in Point);
        procedure Copy_Plane (Display_Id : in Display;
                              Source : in Drawable;
                              Destination : in Drawable;
                              Gc : in Graphic_Context;
                              Source_Area : in Rectangle;
                              Dest_Origin : in Point;
                              Plane : in Plane_Mask);
        procedure Draw_Point (Display_Id : in Display;
                              Drawable_Id : in Drawable;
                              Gc : in Graphic_Context;
                              Xy : in Point);
        procedure Draw_Points (Display_Id : in Display;
                               Drawable_Id : in Drawable;
                               Gc : in Graphic_Context;
                               Points : in Point_Array;
                               Coordinate_Mode : in Coordinate_Mode_Type);
        procedure Draw_Line (Display_Id : in Display;
                             Drawable_Id : in Drawable;
                             Gc : in Graphic_Context;
                             Point_1 : in Point;
                             Point_2 : in Point);
        procedure Draw_Lines (Display_Id : in Display;
                              Drawable_Id : in Drawable;
                              Gc : in Graphic_Context;
                              Points : in Point_Array;
                              Coordinate_Mode : in Coordinate_Mode_Type);
        procedure Draw_Segments (Display_Id : in Display;
                                 Drawable_Id : in Drawable;
                                 Gc : in Graphic_Context;
                                 Segments : in Segment_Array);
        procedure Draw_Rectangle (Display_Id : in Display;
                                  Drawable_Id : in Drawable;
                                  Gc : in Graphic_Context;
                                  Bounds : in Rectangle);
        procedure Draw_Rectangles (Display_Id : in Display;
                                   Drawable_Id : in Drawable;
                                   Gc : in Graphic_Context;
                                   Bounds : in Rectangle_Array);
        procedure Draw_Arc (Display_Id : in Display;
                            Drawable_Id : in Drawable;
                            Gc : in Graphic_Context;
                            Bounds : in Arc);
        procedure Draw_Arcs (Display_Id : in Display;
                             Drawable_Id : in Drawable;
                             Gc : in Graphic_Context;
                             Bounds : in Arc_Array);
        procedure Fill_Rectangle (Display_Id : in Display;
                                  Drawable_Id : in Drawable;
                                  Gc : in Graphic_Context;
                                  Bounds : in Rectangle);
        procedure Fill_Rectangles (Display_Id : in Display;
                                   Drawable_Id : in Drawable;
                                   Gc : in Graphic_Context;
                                   Rectangles : in Rectangle_Array);
        procedure Fill_Polygon (Display_Id : in Display;
                                Drawable_Id : in Drawable;
                                Gc : in Graphic_Context;
                                Points : in Point_Array;
                                Shape : in Shape_Type;
                                Coordinate_Mode : in Coordinate_Mode_Type);
        procedure Fill_Arc (Display_Id : in Display;
                            Drawable_Id : in Drawable;
                            Gc : in Graphic_Context;
                            Bounds : in Rectangle;
                            Angle_1 : in Angle;
                            Angle_2 : in Angle);
        procedure Fill_Arcs (Display_Id : in Display;
                             Drawable_Id : in Drawable;
                             Gc : in Graphic_Context;
                             Arcs : in Arc_Array);
        procedure Draw_Text (Display_Id : in Display;
                             Drawable_Id : in Drawable;
                             Gc : in Graphic_Context;
                             Baseline : in Point;
                             Text_Items : in Text_Item_Array);
        procedure Draw_Text (Display_Id : in Display;
                             Drawable_Id : in Drawable;
                             Gc : in Graphic_Context;
                             Baseline : in Point;
                             Text_Items : in Text_Item_8_Array);
        procedure Draw_Text_16 (Display_Id : in Display;
                                Drawable_Id : in Drawable;
                                Gc : in Graphic_Context;
                                Baseline : in Point;
                                Text_Items : in Text_Item_16_Array);
        procedure Draw_String (Display_Id : in Display;
                               Drawable_Id : in Drawable;
                               Gc : in Graphic_Context;
                               Baseline : in Point;
                               Text : in String);
        procedure Draw_String (Display_Id : in Display;
                               Drawable_Id : in Drawable;
                               Gc : in Graphic_Context;
                               Baseline : in Point;
                               Text : in String_8);
        procedure Draw_String_16 (Display_Id : in Display;
                                  Drawable_Id : in Drawable;
                                  Gc : in Graphic_Context;
                                  Baseline : in Point;
                                  Text : in Fonts.String_16);
        procedure Draw_Image_String (Display_Id : in Display;
                                     Drawable_Id : in Drawable;
                                     Gc : in Graphic_Context;
                                     Baseline : in Point;
                                     Text : in String);
        procedure Draw_Image_String (Display_Id : in Display;
                                     Drawable_Id : in Drawable;
                                     Gc : in Graphic_Context;
                                     Baseline : in Point;
                                     Text : in String_8);
        procedure Draw_Image_String_16 (Display_Id : in Display;
                                        Drawable_Id : in Drawable;
                                        Gc : in Graphic_Context;
                                        Baseline : in Point;
                                        Text : in Fonts.String_16);
        procedure Put_Image (Display_Id : in Display;
                             Drawable_Id : in Drawable;
                             Gc : in Graphic_Context;
                             X_Image : in Image;
                             Source_Xy : in Point;
                             Destination : in Rectangle);
        function Get_Image (Display_Id : in Display;
                            Drawable_Id : in Drawable;
                            Source : in Rectangle;
                            Planes : in Plane_Mask;
                            Format : in Pixmap_Format) return Image;
        function Get_Subimage (Display_Id : in Display;
                               Drawable_Id : in Drawable;
                               Source : in Rectangle;
                               Planes : in Plane_Mask;
                               Format : in Pixmap_Format;
                               Dest_Origin : in Point;
                               Destination : in Image) return Image;
        function Create_Image (Display_Id : in Display;
                               Visual_Id : in Visual;
                               Depth : in Depth_Type;
                               Format : in Pixmap_Format;
                               Offset : in Pixels;
                               Data : in Bits;  
                               Width : in Pixels;
                               Height : in Pixels;
                               Scanline_Pad : in Pixels;
                               Scanline_Length : in Pixels) return Image;
        function Get_Pixel (X_Image : in Image; Xy : in Point) return Pixels;
        procedure Put_Pixel
                     (X_Image : in Image; Xy : in Point; Pixel : in Pixels);
        function Sub_Image
                    (X_Image : in Image; Bounds : in Rectangle) return Image;
        procedure Add_Pixel (X_Image : in Image; Value : in Pixels);
        procedure Destroy_Image (X_Image : in out Image);
        procedure Read_Bitmap_File (Display_Id : in Display;
                                    Drawable_Id : in Drawable;
                                    Filename : in String;
                                    Width : out Pixels;
                                    Height : out Pixels;
                                    Hot_Spot : out Point;
                                    Bitmap : out Pixmap;
                                    Status : out Bitmap_Status_Type);
        function Write_Bitmap_File
                    (Display_Id : in Display;
                     Filename : in String;
                     Bitmap : in Pixmap;
                     Width : in Pixels;
                     Height : in Pixels;
                     Hot_Spot : in Point) return Bitmap_Status_Type;
        function Create_Bitmap_From_Data (Display_Id : in Display;
                                          Drawable_Id : in Drawable;
                                          Data : in Bits;  
                                          Width : in Pixels;
                                          Height : in Pixels) return Pixmap;
        function Create_Pixmap_From_Bitmap_Data
                    (Display_Id : in Display;
                     Drawable_Id : in Drawable;
                     Data : in Bits;  
                     Width : in Pixels;
                     Height : in Pixels;
                     Foreground : in Pixels;
                     Background : in Pixels;
                     Depth : in Depth_Type) return Pixmap;
        function Resource_Gc_From_Graphic_Context
                    (Gc : in Graphic_Context) return Resource_Gc;
    private
        type Gc_Record;
        type Graphic_Context is access Gc_Record;
        Null_Graphic_Context : constant Graphic_Context := null;
        type Image_Record;
        type Image is access Image_Record;
        Image_Context : constant Image := null;
        type Resource_Gc is range 0 .. (2 ** 28) - 1;
    end Graphic_Output;
    package Cursors is
        type Cursor is private;
        Null_Cursor : constant Cursor;
        subtype Cursor_Shape is X_Character;
        X_Cursor : constant Cursor_Shape := 0;
        Arrow : constant Cursor_Shape := 2;
        Based_Arrow_Down : constant Cursor_Shape := 4;
        Based_Arrow_Up : constant Cursor_Shape := 6;
        Boat : constant Cursor_Shape := 8;
        Bogosity : constant Cursor_Shape := 10;
        Bottom_Left_Corner : constant Cursor_Shape := 12;
        Bottom_Right_Corner : constant Cursor_Shape := 14;
        Bottom_Side : constant Cursor_Shape := 16;
        Bottom_Tee : constant Cursor_Shape := 18;
        Box_Spiral : constant Cursor_Shape := 20;
        Center_Ptr : constant Cursor_Shape := 22;
        Circle : constant Cursor_Shape := 24;
        Clock : constant Cursor_Shape := 26;
        Coffee_Mug : constant Cursor_Shape := 28;
        Cross : constant Cursor_Shape := 30;
        Cross_Reverse : constant Cursor_Shape := 32;
        Crosshair : constant Cursor_Shape := 34;
        Diamond_Cross : constant Cursor_Shape := 36;
        Dot : constant Cursor_Shape := 38;
        Dot_Box_Mask : constant Cursor_Shape := 40;
        Double_Arrow : constant Cursor_Shape := 42;
        Draft_Large : constant Cursor_Shape := 44;
        Draft_Small : constant Cursor_Shape := 46;
        Draped_Box : constant Cursor_Shape := 48;
        Exchange : constant Cursor_Shape := 50;
        Fleur : constant Cursor_Shape := 52;
        Gobbler : constant Cursor_Shape := 54;
        Gumby : constant Cursor_Shape := 56;
        Hand : constant Cursor_Shape := 58;
        Handl_Mask : constant Cursor_Shape := 60;
        Heart : constant Cursor_Shape := 62;
        Icon : constant Cursor_Shape := 64;
        Iron_Cross : constant Cursor_Shape := 66;
        Left_Ptr : constant Cursor_Shape := 68;
        Left_Side : constant Cursor_Shape := 70;
        Left_Tee : constant Cursor_Shape := 72;
        Leftbutton : constant Cursor_Shape := 74;
        Ll_Angle : constant Cursor_Shape := 76;
        Lr_Angle : constant Cursor_Shape := 78;
        Man : constant Cursor_Shape := 80;
        Middlebutton : constant Cursor_Shape := 82;
        Mouse : constant Cursor_Shape := 84;
        Pencil : constant Cursor_Shape := 86;
        Pirate : constant Cursor_Shape := 88;
        Plus : constant Cursor_Shape := 90;
        Question_Arrow : constant Cursor_Shape := 92;
        Right_Ptr : constant Cursor_Shape := 94;
        Right_Side : constant Cursor_Shape := 96;
        Right_Tee : constant Cursor_Shape := 98;
        Rightbutton : constant Cursor_Shape := 100;
        Rtl_Logo : constant Cursor_Shape := 102;
        Sailboat : constant Cursor_Shape := 104;
        Sb_Down_Arrow : constant Cursor_Shape := 106;
        Sb_H_Double_Arrow : constant Cursor_Shape := 108;
        Sb_Left_Arrow : constant Cursor_Shape := 110;
        Sb_Right_Arrow : constant Cursor_Shape := 112;
        Sb_Up_Arrow : constant Cursor_Shape := 114;
        Sb_V_Double_Arrow : constant Cursor_Shape := 116;
        Shuttle : constant Cursor_Shape := 118;
        Sizing : constant Cursor_Shape := 120;
        Spider : constant Cursor_Shape := 122;
        Spraycan : constant Cursor_Shape := 124;
        Star : constant Cursor_Shape := 126;
        Target : constant Cursor_Shape := 128;
        Tcross : constant Cursor_Shape := 130;
        Top_Left_Arrow : constant Cursor_Shape := 132;
        Top_Left_Corner : constant Cursor_Shape := 134;
        Top_Right_Corner : constant Cursor_Shape := 136;
        Top_Side : constant Cursor_Shape := 138;
        Top_Tee : constant Cursor_Shape := 140;
        Trek : constant Cursor_Shape := 142;
        Ul_Angle : constant Cursor_Shape := 144;
        Umbrella : constant Cursor_Shape := 146;
        Ur_Angle : constant Cursor_Shape := 148;
        Watch : constant Cursor_Shape := 150;
        Xterm : constant Cursor_Shape := 152;
        Num_Glyphs : constant Cursor_Shape := 154;
        function Create_Font_Cursor
                    (Display_Id : in Display; Shape : in Cursor_Shape)
                    return Cursor;
        function Create_Pixmap_Cursor (Display_Id : in Display;
                                       Source : in Pixmap;
                                       Mask : in Pixmap;
                                       Foreground : in Colors.Color_Record;
                                       Background : in Colors.Color_Record;
                                       Hot_Spot : in Point) return Cursor;
        function Create_Glyph_Cursor
                    (Display_Id : in Display;
                     Source_Font : in Fonts.Font;
                     Mask_Font : in Fonts.Font;
                     Source_Glyph : in X_Character;
                     Mask_Glyph : in X_Character;
                     Foreground : in Colors.Color_Record;
                     Background : in Colors.Color_Record) return Cursor;
        procedure Recolor_Cursor (Display_Id : in Display;
                                  Cursor_Id : in Cursor;
                                  Foreground : in Colors.Color_Record;
                                  Background : in Colors.Color_Record);
        procedure Free_Cursor (Display_Id : in Display;
                               Cursor_Id : in out Cursor);
        procedure Query_Best_Cursor (Display_Id : in Display;
                                     Drawable_Id : in Drawable;
                                     Width : in out Pixels;
                                     Height : in out Pixels);
        procedure Define_Cursor (Display_Id : in Display;
                                 Window_Id : in Window;
                                 Cursor_Id : in Cursor);
        procedure Undefine_Cursor
                     (Display_Id : in Display; Window_Id : in Window);
    private
        type Cursor is range 0 .. (2 ** 28) - 1;
        Null_Cursor : constant Cursor := Cursor (0);
    end Cursors;
    package Cut_And_Paste is
        procedure Store_Buffer (Display_Id : in Display;
                                Data : in Bytes;
                                Number_Of_Bytes : in Positive;
                                To_Buffer : in Natural := 0);
        function Fetch_Buffer
                    (Display_Id : in Display; From_Buffer : in Natural := 0)
                    return Bytes;
        procedure Rotate_Buffers (Display_Id : in Display; By : in Integer);
    end Cut_And_Paste;
    package Regions is
        type Region is private;
        Null_Region : constant Region;
        function Polygon_Region
                    (Points : in Point_Array;
                     Rule : in Graphic_Output.Fill_Rule_Type) return Region;
        procedure Clip_Box (Region_Id : in Region; Bounds : in out Rectangle);
        function Create_Region return Region;
        procedure Set_Region (Display_Id : in Display;
                              Gc : in Graphic_Output.Graphic_Context;
                              Region_Id : in Region);
        procedure Destroy_Region (Region_Id : in out Region);
        procedure Offset_Region (Region_Id : in Region; Delta_Xy : in Point);
        procedure Shrink_Region (Region_Id : in Region; Delta_Xy : in Point);
        procedure Intersect_Region (Source_A : in Region;
                                    Source_B : in Region;
                                    Destination : in Region);
        procedure Union_Region (Source_A : in Region;
                                Source_B : in Region;
                                Destination : in Region);
        procedure Union_Rectangle_With_Region (Source_A : in Region;
                                               Source_B : in Region;
                                               Destination : in Region);
        procedure Subtract_Region (Source_A : in Region;
                                   Source_B : in Region;
                                   Destination : in Region);
        procedure Xor_Region (Source_A : in Region;
                              Source_B : in Region;
                              Destination : in Region);
        function Empty_Region (Region_Id : in Region) return Boolean;
        function Equal_Region (Region_1, Region_2 : in Region) return Boolean;
        function Point_In_Region
                    (Region_Id : in Region; Xy : in Point) return Boolean;
        function Rectangle_In_Region
                    (Region_Id : in Region; Bounds : in Rectangle)
                    return Boolean;
    private
        type Region is range 0 .. (2 ** 28) - 1;
        Null_Region : constant Region := Region (0);
    end Regions;
    package Keyboard is
        type Keycode is range 8 .. 255;
        type Keycode_Array is array (Natural range <>) of Keycode;
        type Key_Sym is range 0 .. (2 ** 28) - 1;
        type Key_Sym_Array is array (Natural range <>) of Key_Sym;
        type Key_Sym_List is access Key_Sym_Array;
        type Keyboard_Encoding_Array is
           array (Keycode range <>) of Key_Sym_List;
        type Key_Vector_Mask_Type is
           array (Keycode range Keycode'First .. Keycode'Last) of Boolean;
        type Milliseconds_Type is range -1 .. 5_000;
        type Bell_Volume_Type is range -100 .. 100;
        type Percent_Type is range -1 .. 100;
        type Hertz_Type is range -1 .. 1000;
        type Led_Mode_Type is (Led_Mode_Off, Led_Mode_On);
        type Led_Type is range 1 .. 32;
        subtype Led_Mask_Type is Boolean_Array (0 .. 31);
        type Auto_Repeat_Mode_Type is
           (Auto_Repeat_Off, Auto_Repeat_On, Auto_Repeat_Default);
        type Keyboard_Control_Record is
            record
                Key_Click_Percent : Percent_Type;
                Bell_Volume : Bell_Volume_Type;
                Bell_Pitch : Hertz_Type;
                Bell_Duration : Milliseconds_Type;
                Led : Led_Type;
                Led_Mode : Led_Mode_Type;
                Key : Keycode;
                Auto_Repeat_Mode : Auto_Repeat_Mode_Type;
            end record;
        subtype Keyboard_Control_Mask is Boolean_Array (0 .. 7);
        Key_Click_Percent_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(0 => True, others => False);
        Bell_Volume_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(1 => True, others => False);
        Bell_Pitch_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(2 => True, others => False);
        Bell_Duration_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(3 => True, others => False);
        Led_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(4 => True, others => False);
        Led_Mode_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(5 => True, others => False);
        Keycode_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(6 => True, others => False);
        Auto_Repeat_Mode_Mask : constant Keyboard_Control_Mask :=
           Keyboard_Control_Mask'(7 => True, others => False);
        type Keyboard_State_Record is
            record
                Key_Click_Percent : Percent_Type;
                Bell_Volume : Bell_Volume_Type;
                Bell_Pitch : Hertz_Type;
                Bell_Duration : Milliseconds_Type;
                Led_Mask : Led_Mask_Type;
                Global_Auto_Repeat : Auto_Repeat_Mode_Type;
                Auto_Repeats : Key_Vector_Mask_Type;
            end record;
        type Modifier_Type is (Lock, Shift, Control, Mod_1,
                               Mod_2, Mod_3, Mod_4, Mod_5);
        type Modifier_Key_Record (Max_Keys_Per_Mod : Natural) is
            record
                Modifier_Map : Keycode_Array (0 .. Max_Keys_Per_Mod);
            end record;
        type Modifier_Keymap is access Modifier_Key_Record;
        procedure Display_Keycodes (Display_Id : in Display;
                                    Min_Keycodes : out Keycode;
                                    Max_Keycodes : out Keycode);
        procedure Rebind_Keysym (Display_Id : in X_Windows.Display;
                                 The_Symbol : in Key_Sym;
                                 Modifiers : in Key_Sym_List;
                                 Text : in String);
        function String_To_Keysym (Name : in String) return Key_Sym;
        function Keysym_To_String (The_Symbol : in Key_Sym) return String;
        procedure Keycode_To_Keysym (Display_Id : in Display;
                                     Key_Code : in Keycode;
                                     Key : out Keycode;
                                     The_Symbol : out Key_Sym);
        function Keysym_To_Keycode
                    (Display_Id : in Display; The_Symbol : in Key_Sym)
                    return Keycode;
        procedure Change_Keyboard_Control
                     (Display_Id : in Display;
                      Value_Mask : in Keyboard_Control_Mask;
                      Values : in Keyboard_Control_Record);
        function Get_Keyboard_Control
                    (Display_Id : in Display) return Keyboard_State_Record;
        procedure Auto_Repeat_On (Display_Id : in Display);
        procedure Auto_Repeat_Off (Display_Id : in Display);
        procedure Bell (Display_Id : in Display; Volume : in Bell_Volume_Type);
        function Query_Keymap (Display_Id : in Display)
                              return Keyboard.Key_Vector_Mask_Type;
        procedure Get_Keyboard_Mapping (Display_Id : in Display;
                                        Syms : in out Keyboard_Encoding_Array);
        procedure Change_Keyboard_Mapping (Display_Id : in Display;
                                           Syms : in Keyboard_Encoding_Array);
        function Set_Modifier_Mapping
                    (Display_Id : in Display; Modifiers : in Modifier_Keymap)
                    return Boolean;
        procedure Insert_Modifier_Map_Entry (Map : in out Modifier_Keymap;
                                             Key : in Keycode;
                                             Modifier : in Modifier_Type);
        procedure Delete_Modifier_Map_Entry (Map : in out Modifier_Keymap;
                                             Key : in Keycode;
                                             Modifier : in Modifier_Type);
        function Get_Modifier_Mapping
                    (Display_Id : in Display) return Modifier_Keymap;
        function Is_Keypad_Key (Sym : in Key_Sym) return Boolean;
        function Is_Cursor_Key (Sym : in Key_Sym) return Boolean;
        function Is_Pf_Key (Sym : in Key_Sym) return Boolean;
        function Is_Function_Key (Sym : in Key_Sym) return Boolean;
        function Is_Misc_Function_Key (Sym : in Key_Sym) return Boolean;
        function Is_Modifier_Key (Sym : in Key_Sym) return Boolean;
        pragma Inline (Is_Keypad_Key, Is_Cursor_Key, Is_Pf_Key,
                       Is_Function_Key, Is_Misc_Function_Key, Is_Modifier_Key);
    end Keyboard;
    package Events is
        type Event_Queue_Mode_Type is
           (Queued_Already, Queued_After_Flush, Queued_After_Reading);
        type Event_Type is (Unused_Event_1, Unused_Event_2, Key_Press,
                            Key_Release, Button_Press, Button_Release,
                            Motion_Notify, Enter_Notify, Leave_Notify,
                            Focus_In, Focus_Out, Keymap_Notify, Expose,
                            Graphics_Expose, No_Expose, Visibility_Notify,
                            Create_Notify, Destroy_Notify, Unmap_Notify,
                            Map_Notify, Map_Request, Reparent_Notify,
                            Configure_Notify, Configure_Request, Gravity_Notify,
                            Resize_Request, Circulate_Notify, Circulate_Request,
                            Property_Notify, Selection_Clear, Selection_Request,
                            Selection_Notify, Colormap_Notify,
                            Client_Message, Mapping_Notify, Last_Event);
        subtype Event_Mask_Type is Boolean_Array (0 .. 31);
        No_Event_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(others => False);
        Key_Press_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(0 => True, others => False);
        Key_Release_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(1 => True, others => False);
        Button_Press_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(2 => True, others => False);
        Button_Release_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(3 => True, others => False);
        Enter_Window_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(4 => True, others => False);
        Leave_Window_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(5 => True, others => False);
        Pointer_Motion_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(6 => True, others => False);
        Pointer_Motion_Hint_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(7 => True, others => False);
        Button_1_Motion_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(8 => True, others => False);
        Button_2_Motion_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(9 => True, others => False);
        Button_3_Motion_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(10 => True, others => False);
        Button_4_Motion_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(11 => True, others => False);
        Button_5_Motion_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(12 => True, others => False);
        Button_Motion_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(13 => True, others => False);
        Keymap_State_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(14 => True, others => False);
        Exposure_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(15 => True, others => False);
        Visibility_Change_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(16 => True, others => False);
        Structure_Change_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(17 => True, others => False);
        Resize_Redirect_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(18 => True, others => False);
        Substructure_Notify_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(19 => True, others => False);
        Substructure_Redirect_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(20 => True, others => False);
        Focus_Change_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(21 => True, others => False);
        Property_Change_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(22 => True, others => False);
        Colormap_Change_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(23 => True, others => False);
        Owner_Grab_Button_Mask : constant Event_Mask_Type :=
           Event_Mask_Type'(24 => True, others => False);
        subtype Key_And_Button_Mask is Boolean_Array (0 .. 15);
        Shift_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(0 => True, others => False);
        Lock_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(1 => True, others => False);
        Control_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(2 => True, others => False);
        Mod_1_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(3 => True, others => False);
        Mod_2_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(4 => True, others => False);
        Mod_3_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(5 => True, others => False);
        Mod_4_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(6 => True, others => False);
        Mod_5_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(7 => True, others => False);
        Button_1_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(8 => True, others => False);
        Button_2_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(9 => True, others => False);
        Button_3_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(10 => True, others => False);
        Button_4_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(11 => True, others => False);
        Button_5_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(12 => True, others => False);
        Any_Modifier_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(15 => True, others => False);
        Any_Button_Mask : constant Key_And_Button_Mask :=
           Key_And_Button_Mask'(others => False);
        type Button_Name_Type is (Any_Button, Button_1, Button_2,
                                  Button_3, Button_4, Button_5);
        type Notify_Mode_Type is (Notify_Normal, Notify_Grab,
                                  Notify_Ungrab, Notify_While_Grabbed);
        Notify_Hint : constant Notify_Mode_Type := Notify_Grab;
        type Notify_Detail_Type is (Notify_Ancestor, Notify_Virtual,
                                    Notify_Inferior, Notify_Nonlinear,
                                    Notify_Nonlinear_Virtual, Notify_Pointer,
                                    Notify_Pointer_Root, Notify_Detail_None);
        type Mapping_Request_Type is
           (Mapping_Modifier, Mapping_Keyboard, Mapping_Pointer);
        type Colormap_State_Type is (Uninstalled, Installed);
        type Property_State_Type is (New_Value, Delete);
        type Placement_Type is (Place_On_Top, Place_On_Bottom);
        subtype Configure_Request_Mask_Type is Boolean_Array (0 .. 8);
        type Visibility_Type is (Visibility_Unobscured,
                                 Visibility_Partially_Obscured,
                                 Visibility_Full_Obscured);
        type Graphic_Expose_Code_Type is range 0 .. (2 ** 16 - 1);
        X_Copy_Area : constant Graphic_Expose_Code_Type := 62;
        X_Copy_Plane : constant Graphic_Expose_Code_Type := 63;
        type Event_Record (Kind : Event_Type := Enter_Notify);
        type Event is access Event_Record;
        type Any_Event_Record is
            record
                Window_Id : Window;
            end record;
        type Any_Event is access Any_Event_Record;
        type Key_Event_Record is
            record
                Window_Id : Window;
                Root : Window;
                Subwindow : Window;
                Event_Time : Time;
                X : Coordinate;
                Y : Coordinate;
                X_Root : Coordinate;
                Y_Root : Coordinate;
                State : Key_And_Button_Mask;
                Key_Code : Keyboard.Keycode;
                Same_Screen : Boolean;
            end record;
        type Key_Event is access Key_Event_Record;
        type Button_Event_Record is
            record
                Window_Id : Window;
                Root : Window;
                Subwindow : Window;
                Event_Time : Time;
                X : Coordinate;
                Y : Coordinate;
                X_Root : Coordinate;
                Y_Root : Coordinate;
                State : Key_And_Button_Mask;
                Button : Button_Name_Type;
                Same_Screen : Boolean;
            end record;
        type Button_Event is access Button_Event_Record;
        type Motion_Event_Record is
            record
                Window_Id : Window;
                Root : Window;
                Subwindow : Window;
                Event_Time : Time;
                X : Coordinate;
                Y : Coordinate;
                X_Root : Coordinate;
                Y_Root : Coordinate;
                State : Key_And_Button_Mask;
                Is_Hint : Notify_Mode_Type;
                Same_Screen : Boolean;
            end record;
        type Motion_Event is access Motion_Event_Record;
        type Crossing_Event_Record is
            record
                Window_Id : Window;
                Root : Window;
                Subwindow : Window;
                Event_Time : Time;
                X : Coordinate;
                Y : Coordinate;
                X_Root : Coordinate;
                Y_Root : Coordinate;
                Mode : Notify_Mode_Type;
                Detail : Notify_Detail_Type;
                Same_Screen : Boolean;
                Focus : Boolean;
                State : Key_And_Button_Mask;
            end record;
        type Crossing_Event is access Crossing_Event_Record;
        type Focus_Change_Event_Record is
            record
                Window_Id : Window;
                Mode : Notify_Mode_Type;
                Detail : Notify_Detail_Type;
            end record;
        type Focus_Change_Event is access Focus_Change_Event_Record;
        type Keymap_Event_Record is
            record
                Window_Id : Window;
                Key_Vector : Keyboard.Key_Vector_Mask_Type;
            end record;
        type Keymap_Event is access Keymap_Event_Record;
        type Expose_Event_Record is
            record
                Window_Id : Window;
                X : Coordinate;
                Y : Coordinate;
                Width : Pixels;
                Height : Pixels;
                Count : Natural;
            end record;
        type Expose_Event is access Expose_Event_Record;
        type Graphics_Expose_Event_Record is
            record
                D : Drawable;
                X : Coordinate;
                Y : Coordinate;
                Width : Pixels;
                Height : Pixels;
                Count : Natural;
                Major_Code : Graphic_Expose_Code_Type;
                Minor_Code : Graphic_Expose_Code_Type;
            end record;
        type Graphics_Expose_Event is access Graphics_Expose_Event_Record;
        type No_Expose_Event_Record is
            record
                D : Drawable;
                Major_Code : Graphic_Expose_Code_Type;
                Minor_Code : Graphic_Expose_Code_Type;
            end record;
        type No_Expose_Event is access No_Expose_Event_Record;
        type Visibility_Event_Record is
            record
                Window_Id : Window;
                State : Visibility_Type;
            end record;
        type Visibility_Event is access Visibility_Event_Record;
        type Create_Window_Event_Record is
            record
                Parent : Window;
                Window_Id : Window;
                X : Coordinate;
                Y : Coordinate;
                Width : Pixels;
                Height : Pixels;
                Border_Width : Pixels;
                Override_Redirect : Boolean;
            end record;
        type Create_Window_Event is access Create_Window_Event_Record;
        type Destroy_Window_Event_Record is
            record
                Event_Window : Window;
                Window_Id : Window;
            end record;
        type Destroy_Window_Event is access Destroy_Window_Event_Record;
        type Unmap_Event_Record is
            record
                Event_Window : Window;
                Window_Id : Window;
                From_Configure : Boolean;
            end record;
        type Unmap_Event is access Unmap_Event_Record;
        type Map_Event_Record is
            record
                Event_Window : Window;
                Window_Id : Window;
                Override_Redirect : Boolean;
            end record;
        type Map_Event is access Map_Event_Record;
        type Map_Request_Event_Record is
            record
                Parent : Window;
                Window_Id : Window;
            end record;
        type Map_Request_Event is access Map_Request_Event_Record;
        type Reparent_Event_Record is
            record
                Event_Window : Window;
                Window_Id : Window;
                Parent : Window;
                X : Coordinate;
                Y : Coordinate;
                Override_Redirect : Boolean;
            end record;
        type Reparent_Event is access Reparent_Event_Record;
        type Resize_Request_Event_Record is
            record
                Window_Id : Window;
                Width : Pixels;
                Height : Pixels;
            end record;
        type Resize_Request_Event is access Resize_Request_Event_Record;
        type Gravity_Event_Record is
            record
                Event_Window : Window;
                Window_Id : Window;
                X : Coordinate;
                Y : Coordinate;
            end record;
        type Gravity_Event is access Gravity_Event_Record;
        type Configure_Event_Record is
            record
                Event_Window : Window;
                Window_Id : Window;
                X : Coordinate;
                Y : Coordinate;
                Width : Pixels;
                Height : Pixels;
                Border_Width : Pixels;
                Above : Window;
                Override_Redirect : Boolean;
            end record;
        type Configure_Event is access Configure_Event_Record;
        type Configure_Request_Event_Record is
            record
                Parent : Window;
                Window_Id : Window;
                X : Coordinate;
                Y : Coordinate;
                Width : Pixels;
                Height : Pixels;
                Border_Width : Pixels;
                Above : Window;
                Detail : Stack_Mode_Type;
                Value_Mask : Configure_Request_Mask_Type;
            end record;
        type Configure_Request_Event is access Configure_Request_Event_Record;
        type Circulate_Event_Record is
            record
                Parent : Window;
                Window_Id : Window;
                Place : Placement_Type;
            end record;
        type Circulate_Event is access Circulate_Event_Record;
        type Circulate_Request_Event_Record is
            record
                Parent : Window;
                Window_Id : Window;
                Place : Placement_Type;
            end record;
        type Circulate_Request_Event is access Circulate_Request_Event_Record;
        type Property_Event_Record is
            record
                Window_Id : Window;
                Atom_Id : Atoms.Atom;
                Time_Stamp : Time;
                State : Property_State_Type;
            end record;
        type Property_Event is access Property_Event_Record;
        type Selection_Clear_Event_Record is
            record
                Owner : Window;
                Selection : Atoms.Atom;
                Time_Stamp : Time;
            end record;
        type Selection_Clear_Event is access Selection_Clear_Event_Record;
        type Selection_Request_Event_Record is
            record
                Owner : Window;
                Requestor : Window;
                Selection : Atoms.Atom;
                Target : Atoms.Atom;
                Property : Atoms.Atom;
                Time_Stamp : Time;
            end record;
        type Selection_Request_Event is access Selection_Request_Event_Record;
        type Selection_Event_Record is
            record
                Requestor : Window;
                Selection : Atoms.Atom;
                Target : Atoms.Atom;
                Property : Atoms.Atom;
                Time_Stamp : Time;
            end record;
        type Selection_Event is access Selection_Event_Record;
        type Colormap_Event_Record is
            record
                Window_Id : Window;
                Colormap : Colors.Color_Map;
                New_Map : Boolean;
                State : Colormap_State_Type;
            end record;
        type Colormap_Event is access Colormap_Event_Record;
        type Client_Message_Event_Record is
            record
                Window_Id : Window;
                Message_Type : Atoms.Atom;
                Format : Property_Format_Type;
                Data : Long_Array (1 .. 5);
            end record;
        type Client_Message_Event is access Client_Message_Event_Record;
        type Mapping_Event_Record is
            record
                Window_Id : Window;
                Request : Mapping_Request_Type;
                First_Keycode : Keyboard.Keycode;
                Count : Keyboard.Keycode;
            end record;
        type Mapping_Event is access Mapping_Event_Record;
        type Event_Record (Kind : Event_Type := Enter_Notify) is
            record
                Serial : X_Long_Integer;
                Send_Event : Boolean;
                Display_Id : Display;
                case Kind is
                    when Button_Press | Button_Release =>
                        Button : Button_Event_Record;
                    when Circulate_Notify =>
                        Circulate : Circulate_Event_Record;
                    when Circulate_Request =>
                        Circulate_Reqst : Circulate_Request_Event_Record;
                    when Client_Message =>
                        Client : Client_Message_Event_Record;
                    when Colormap_Notify =>
                        Colormap : Colormap_Event_Record;
                    when Configure_Notify =>
                        Configure : Configure_Event_Record;
                    when Configure_Request =>
                        Configure_Reqst : Configure_Request_Event_Record;
                    when Create_Notify =>
                        Create_Window : Create_Window_Event_Record;
                    when Destroy_Notify =>
                        Destroy_Window : Destroy_Window_Event_Record;
                    when Enter_Notify | Leave_Notify =>
                        Crossing : Crossing_Event_Record;
                    when Expose =>
                        Expose_Notify : Expose_Event_Record;
                    when Focus_In | Focus_Out =>
                        Focus : Focus_Change_Event_Record;
                    when Graphics_Expose =>
                        Graphics : Graphics_Expose_Event_Record;
                    when Gravity_Notify =>
                        Gravity : Gravity_Event_Record;
                    when Key_Press | Key_Release =>
                        Key : Key_Event_Record;
                    when Keymap_Notify =>
                        Keymap : Keymap_Event_Record;
                    when Map_Notify | Mapping_Notify =>
                        Map : Map_Event_Record;
                    when Map_Request =>
                        Map_Reqst : Map_Request_Event_Record;
                    when Motion_Notify =>
                        Motion : Motion_Event_Record;
                    when No_Expose =>
                        Noexpose : No_Expose_Event_Record;
                    when Property_Notify =>
                        Property : Property_Event_Record;
                    when Reparent_Notify =>
                        Reparent : Reparent_Event_Record;
                    when Resize_Request =>
                        Resize_Reqst : Resize_Request_Event_Record;
                    when Selection_Clear =>
                        Selection_Clr : Selection_Clear_Event_Record;
                    when Selection_Notify =>
                        Selection : Selection_Event_Record;
                    when Selection_Request =>
                        Selection_Reqst : Selection_Request_Event_Record;
                    when Unmap_Notify =>
                        Unmap : Unmap_Event_Record;
                    when Visibility_Notify =>
                        Visibility : Visibility_Event_Record;
                    when others =>
                        Any : Any_Event_Record;
                end case;
            end record;
        type Time_Coord_Record is
            record
                X, Y : Coordinate;
                Timestamp : Time;
            end record;
        type Time_Coord_Array is array (Natural range <>) of Time_Coord_Record;
        type Time_Coord_List is access Time_Coord_Array;
        type Compose_Status_Record is
            record
                Compose_Pointer : String_Pointer;
                Chars_Matched : X_Long_Integer;
            end record;
        function Display_Motion_Buffer_Size
                    (Display_Id : in Display) return X_Long_Integer;
        procedure Select_Input (Display_Id : in Display;
                                Window_Id : in Window;
                                Mask : in Event_Mask_Type);
        procedure Flush (Display_Id : in Display);
        procedure Sync (Display_Id : in Display; Discard : in Boolean := False);
        function Events_Queued
                    (Display_Id : in Display; Mode : in Event_Queue_Mode_Type)
                    return Natural;
        function Pending (Display_Id : in Display) return Natural;
        procedure Next_Event (Display_Id : in Display;
                              The_Event : in out Event);
        procedure Free_Event (The_Event : in out Event);
        procedure Peek_Event (Display_Id : in Display;
                              The_Event : in out Event);
        procedure Put_Back_Event
                     (Display_Id : in Display; The_Event : in Event);
        procedure Window_Event (Display_Id : in Display;
                                Window_Id : in Window;
                                Mask : in Event_Mask_Type;
                                The_Event : in out Event);
        procedure Check_Window_Event (Display_Id : in Display;
                                      Window_Id : in Window;
                                      Mask : in Event_Mask_Type;
                                      The_Event : in out Event;
                                      Event_Found : in out Boolean);
        procedure Check_Typed_Event (Display_Id : in Display;
                                     Event_Kind : in Event_Type;
                                     Event_Return : in out Event;
                                     Event_Found : in out Boolean);
        procedure Check_Typed_Window_Event (Display_Id : in Display;
                                            Window_Id : in Window;
                                            Event_Kind : in Event_Type;
                                            Event_Return : in out Event;
                                            Event_Found : in out Boolean);
        procedure Mask_Event (Display_Id : in Display;
                              Mask : in Event_Mask_Type;
                              The_Event : in out Event);
        procedure Check_Mask_Event (Display_Id : in Display;
                                    Mask : in Event_Mask_Type;
                                    The_Event : in out Event;
                                    Event_Found : in out Boolean);
        function Get_Motion_Events (Display_Id : in Display;
                                    Window_Id : in Window;
                                    Start : in Time;
                                    Stop : in Time) return Time_Coord_List;
        procedure Send_Event (Display_Id : in Display;
                              Window_Id : in Window;
                              Propagate : in Boolean;
                              Mask : in Event_Mask_Type;
                              The_Event : in Event);
        function Lookup_Keysym (The_Event : in Event; Index : in Natural)
                               return Keyboard.Key_Sym;
        procedure Refresh_Keyboard_Mapping (The_Event : in Event);
        procedure Lookup_String (The_Event : in Event;
                                 Buffer : in out String_Pointer;
                                 The_Symbol : out Keyboard.Key_Sym;
                                 Status : out Compose_Status_Record);
    end Events;
    package Window_Manager is
        type Resource is private;
        type Grab_Mode is (Sync, Async);
        type Grab_Reply_Status is
           (Grab_Success, Already_Grabbed, Grab_Invalid_Time,
            Grab_Not_Viewable, Grab_Frozen);
        type Notify_Modes is (Normal, Grab, Ungrab, While_Grabbed);
        type Notify_Detail is (Ancestor, Virtual, Inferior,
                               Nonlinear, Nonlinear_Virtual,
                               Pointer, Pointer_Root, Detail_None);
        type Visibility_Notify_Type is
           (Unobscured, Partially_Obscured, Fully_Obscured);
        type Circulation_Request is (Place_On_Top, Place_On_Bottom);
        type Protocol_Family is (Internet, Decnet, Chaos);
        type Property_Notification is (New_Value, Delete);
        type Colormap_Notification is (Uninstalled, Installed);
        type Map_Status is (Success, Busy, Failed);
        type Allow_Event_Mode is (Async_Pointer, Sync_Pointer, Replay_Pointer,
                                  Async_Keyboard, Sync_Keyboard,
                                  Replay_Keyboard, Async_Both, Sync_Both);
        type Revert_Mode is
           (Revert_To_None, Revert_To_Pointer_Root, Revert_To_Parent);
        type Close_Mode is (Destroy_All, Retain_Permanent, Retain_Temporary);
        type Map_Array is array (Natural range <>) of X_Short_Integer;
        type Screen_Saver_Mode is (Active, Reset);
        type Exposure_Type is (Dont_Allow_Exposures,
                               Allow_Exposures, Default_Exposures);
        type Blanking_Type is (Dont_Prefer_Blanking,
                               Prefer_Blanking, Default_Blanking);
        type Host_Address_Record is
            record
                Family : X_Id;
                Length : X_Id;
                The_Address : System.Address;
            end record;
        type Host_Array is array (Natural range <>) of Host_Address_Record;
        type Host_List is access Host_Array;
        type Access_Control_Mode is (Enable, Disable);
        procedure Grab_Button (Display_Id : in Display;
                               Button : in Events.Button_Name_Type;
                               Modifiers : in Events.Key_And_Button_Mask;
                               Window_Id : in Window;
                               Owner_Events : in Boolean;
                               Grab_Events : in Events.Event_Mask_Type;
                               Pointer_Mode : in Grab_Mode;
                               Keyboard_Mode : in Grab_Mode;
                               Confine_To : in Window;
                               Cursor_Id : in Cursors.Cursor);
        procedure Ungrab_Button (Display_Id : in Display;
                                 Button : in Events.Button_Name_Type;
                                 Modifiers : in Events.Key_And_Button_Mask;
                                 Window_Id : in Window);
        function Grab_Pointer (Display_Id : in Display;
                               Window_Id : in Window;
                               Owner_Events : in Boolean;
                               Grab_Events : in Events.Event_Mask_Type;
                               Pointer_Mode : in Grab_Mode;
                               Keyboard_Mode : in Grab_Mode;
                               Confine_To : in Window;
                               Cursor_Id : in Cursors.Cursor;
                               Grab_Time : in Time) return Grab_Reply_Status;
        procedure Ungrab_Pointer
                     (Display_Id : in Display; Ungrab_Time : in Time);
        procedure Change_Active_Pointer_Grab
                     (Display_Id : in Display;
                      Grab_Events : in Events.Event_Mask_Type;
                      Cursor_Id : in Cursors.Cursor;
                      Grab_Time : in Time);
        function Grab_Keyboard (Display_Id : in Display;
                                Window_Id : in Window;
                                Owner_Events : in Boolean;
                                Pointer_Mode : in Grab_Mode;
                                Keyboard_Mode : in Grab_Mode;
                                Grab_Time : in Time) return Grab_Reply_Status;
        procedure Ungrab_Keyboard
                     (Display_Id : in Display; Ungrab_Time : in Time);
        procedure Grab_Key (Display_Id : in Display;
                            Key : in Keyboard.Keycode;
                            Modifiers : in Events.Key_And_Button_Mask;
                            Owner_Events : in Boolean;
                            Window_Id : in Window;
                            Pointer_Mode : in Grab_Mode;
                            Keyboard_Mode : in Grab_Mode);
        procedure Ungrab_Key (Display_Id : in Display;
                              Key : in Keyboard.Keycode;
                              Modifiers : in Events.Key_And_Button_Mask;
                              Window_Id : in Window);
        procedure Allow_Events (Display_Id : in Display;
                                Mode : in Allow_Event_Mode;
                                Event_Time : in Time);
        procedure Grab_Server (Display_Id : in Display);
        procedure Ungrab_Server (Display_Id : in Display);
        procedure Warp_Pointer (Display_Id : in Display;
                                Source : in Window;
                                Destination : in Window;
                                Source_Bounds : in Rectangle;
                                Dest_Xy : in Point);
        procedure Set_Input_Focus (Display_Id : in Display;
                                   Focus : in Window;
                                   Mode : in Revert_Mode;
                                   Grab_Time : in Time);
        procedure Get_Input_Focus (Display_Id : in Display;
                                   Focus : in out Window;
                                   Mode : in out Revert_Mode);
        procedure Change_Pointer_Control (Display_Id : in Display;
                                          Do_Accel : in Boolean;
                                          Do_Threshold : in Boolean;
                                          Numerator : in Integer;
                                          Denominator : in Integer;
                                          Threshold : in Integer);
        procedure Get_Pointer_Control (Display_Id : in Display;
                                       Numerator : out Integer;
                                       Denominator : out Integer;
                                       Threshold : out Integer);
        procedure Set_Pointer_Mapping (Display_Id : in Display;
                                       Map : in Map_Array;
                                       Status : out Map_Status);
        procedure Get_Pointer_Mapping (Display_Id : in Display;
                                       Map : in out Map_Array;
                                       Status : out Map_Status);
        procedure Set_Close_Down_Mode
                     (Display_Id : in Display; Mode : in Close_Mode);
        procedure Kill_Client (Display_Id : in Display;
                               Resource_Id : in Resource);
        procedure Set_Screen_Saver (Display_Id : in Display;
                                    Time_Out : in Time;
                                    Interval : in Time;
                                    Blanking : in Blanking_Type;
                                    Exposures : in Exposure_Type);
        procedure Force_Screen_Saver (Display_Id : in Display;
                                      Mode : in Screen_Saver_Mode);
        procedure Activate_Screen_Saver (Display_Id : in Display);
        procedure Reset_Screen_Saver (Display_Id : in Display);
        procedure Get_Screen_Saver (Display_Id : in Display;
                                    Time_Out : out Time;
                                    Interval : out Time;
                                    Blanking : out Blanking_Type;
                                    Exposures : out Exposure_Type);
        procedure Add_Host (Display_Id : in Display;
                            Host : in Host_Address_Record);
        procedure Add_Hosts (Display_Id : in Display; Hosts : in Host_Array);
        procedure List_Hosts (Display_Id : in Display;
                              States : in out Boolean_Array;
                              Hosts : out Host_List);
        procedure Remove_Host (Display_Id : in Display;
                               Host : in Host_Address_Record);
        procedure Remove_Hosts (Display_Id : in Display; Hosts : in Host_Array);
        procedure Set_Access_Control (Display_Id : in Display;
                                      Mode : in Access_Control_Mode);
        procedure Enable_Access_Control (Display_Id : in Display);
        procedure Disable_Access_Control (Display_Id : in Display);
        function Get_Default (Display_Id : in Display;
                              Program : in String;
                              Option : in String) return String;
    private
        type Resource is range 0 .. (2 ** 28) - 1;
    end Window_Manager;
    function Get_Command_Line_Arguments return String_List;
    function Open_Display (Name : in String) return Display;
    procedure No_Operation (Display_Id : in Display);
    procedure Close_Display (The_Display : in Display);
    function Bitmap_Bit_Order (Display_Id : in Display) return Order_Type;
    function Bitmap_Pad (Display_Id : in Display) return Pixels;
    function Bitmap_Unit (Display_Id : in Display) return Pixels;
    function Black_Pixel (Display_Id : in Display; Screen_Id : in Screen_Number)
                         return Pixels;
    function Connection_Number (Display_Id : in Display) return X_Long_Integer;
    function Default_Colormap
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Colors.Color_Map;
    function Default_Depth
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Depth_Type;
    function Default_Graphic_Context
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Graphic_Output.Graphic_Context;
    function Default_Root_Window (Display_Id : in Display) return Window;
    function Default_Screen (Display_Id : in Display) return Screen_Number;
    function Default_Visual
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Visual;
    function Display_Cells
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Natural;
    function Display_Height
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Pixels;
    function Display_Height
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Millimeters;
    function Display_Name (Name : in String) return String;
    function Display_Planes
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Depth_Type;
    function Display_String (Display_Id : in Display) return String;
    function Display_Width
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Pixels;
    function Display_Width
                (Display_Id : in Display; Screen_Id : in Screen_Number)
                return Millimeters;
    function Image_Byte_Order (Display_Id : in Display) return Order_Type;
    function Last_Known_Request_Processed
                (Display_Id : in Display) return X_Long_Integer;
    function Next_Request (Display_Id : in Display) return X_Long_Integer;
    function Protocol_Version (Display_Id : in Display) return Natural;
    function Protocol_Revision (Display_Id : in Display) return Natural;
    function Q_Length (Display_Id : in Display) return Natural;
    function Root_Window (Display_Id : in Display; Screen_Id : in Screen_Number)
                         return Window;
    function Screen_Count (Display_Id : in Display) return Screen_Number;
    function Server_Vendor (Display_Id : in Display) return String;
    function Vendor_Release (Display_Id : in Display) return Natural;
    function White_Pixel (Display_Id : in Display; Screen_Id : in Screen_Number)
                         return Pixels;
    function Screen_Of_Display
                (Display_Id : in Display; Screen_Num : in Screen_Number)
                return Screen;
    function Default_Screen_Of_Display (Display_Id : in Display) return Screen;
    function Display_Of_Screen (Screen_Id : in Screen) return Display;
    function Root_Window_Of_Screen (Screen_Id : in Screen) return Window;
    function Black_Pixel_Of_Screen (Screen_Id : in Screen) return Pixels;
    function White_Pixel_Of_Screen (Screen_Id : in Screen) return Pixels;
    function Default_Colormap_Of_Screen
                (Screen_Id : in Screen) return Colors.Color_Map;
    function Default_Depth_Of_Screen (Screen_Id : in Screen) return Depth_Type;
    function Default_Gc_Of_Screen (Screen_Id : in Screen)
                                  return Graphic_Output.Graphic_Context;
    function Default_Visual_Of_Screen (Screen_Id : in Screen) return Visual;
    function Width_Of_Screen (Screen_Id : in Screen) return Pixels;
    function Height_Of_Screen (Screen_Id : in Screen) return Pixels;
    function Width_Mm_Of_Screen (Screen_Id : in Screen) return Millimeters;
    function Height_Mm_Of_Screen (Screen_Id : in Screen) return Millimeters;
    function Planes_Of_Screen (Screen_Id : in Screen) return Natural;
    function Cells_Of_Screen (Screen_Id : in Screen) return Natural;
    function Min_Cmaps_Of_Screen (Screen_Id : in Screen) return Natural;
    function Max_Cmaps_Of_Screen (Screen_Id : in Screen) return Natural;
    function Does_Save_Unders (Screen_Id : in Screen) return Boolean;
    function Does_Backing_Store
                (Screen_Id : in Screen) return Backing_Store_Type;
    function Event_Mask_Of_Screen (Screen_Id : in Screen)
                                  return Events.Event_Mask_Type;
    function Min_Keycode (Display_Id : in Display) return Keyboard.Keycode;
    function Max_Keycode (Display_Id : in Display) return Keyboard.Keycode;
    pragma Inline (Bitmap_Bit_Order, Bitmap_Pad, Bitmap_Unit, Black_Pixel,
                   Connection_Number, Default_Colormap, Default_Root_Window,
                   Default_Depth, Default_Graphic_Context, Default_Screen,
                   Default_Visual, Display_Cells, Display_Height,
                   Display_Name, Display_Planes, Display_String,
                   Display_Width, Image_Byte_Order, Protocol_Version,
                   Protocol_Revision, Q_Length, Root_Window, Screen_Count,
                   Server_Vendor, White_Pixel, Screen_Of_Display,
                   Default_Screen_Of_Display, Display_Of_Screen,
                   Root_Window_Of_Screen, Black_Pixel_Of_Screen,
                   White_Pixel_Of_Screen, Default_Colormap_Of_Screen,
                   Default_Depth_Of_Screen, Default_Gc_Of_Screen,
                   Default_Visual_Of_Screen, Width_Of_Screen,
                   Height_Of_Screen, Width_Mm_Of_Screen, Height_Mm_Of_Screen,
                   Planes_Of_Screen, Cells_Of_Screen, Min_Cmaps_Of_Screen,
                   Max_Cmaps_Of_Screen, Does_Save_Unders, Does_Backing_Store,
                   Event_Mask_Of_Screen, Min_Keycode, Max_Keycode);
    type Visual_Class_Type is (Static_Gray, Gray_Scale, Static_Color,
                               Pseudo_Color, True_Color, Direct_Color);
    type Visual_Info_Record is
        record
            Visual_Record : Visual;
            Visual_Id : X_Id;
            Screen_Id : Screen_Number;
            Depth : Depth_Type;
            Class : Visual_Class_Type;
            Red_Mask : Pixels;
            Green_Mask : Pixels;
            Blue_Mask : Pixels;
            Colormap_Size : Integer;
            Bits_Per_Rgb : Pixels;
        end record;
    type Visual_Info_Array is array (Natural range <>) of Visual_Info_Record;
    type Visual_Info_List is access Visual_Info_Array;
    subtype Visual_Mask_Type is Boolean_Array (0 .. 8);
    Visual_No_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(others => False);
    Visual_Id_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(0 => True, others => False);
    Visual_Screen_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(1 => True, others => False);
    Visual_Depth_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(2 => True, others => False);
    Visual_Class_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(3 => True, others => False);
    Visual_Red_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(4 => True, others => False);
    Visual_Green_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(5 => True, others => False);
    Visual_Blue_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(6 => True, others => False);
    Visual_Colormap_Size_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(7 => True, others => False);
    Visual_Bits_Per_Rgb_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(8 => True, others => False);
    Visual_All_Mask : constant Visual_Mask_Type :=
       Visual_Mask_Type'(others => True);
    function Get_Visual_Info
                (Display_Id : in Display;
                 Info_Mask : in Visual_Mask_Type;
                 Info_Template : in Visual_Info_Record) return Visual_Info_List;
    procedure Match_Visual_Info (Display_Id : in Display;
                                 Screen_Id : in Screen;
                                 Depth_Of_Screen : in Depth_Type;
                                 Class_Of_Screen : in Visual_Class_Type;
                                 Visual_Info : out Visual_Info_Record;
                                 Success : out Boolean);
    type Window_Array is array (Natural range <>) of Window;
    type Window_List is access Window_Array;
    type Window_Class is (Copy_Class_From_Parent, Input_Output, Input_Only);
    type Direction_Type is (Raise_Lowest, Lower_Highest);
    type Property_Mode is (Replace, Prepend, Append);
    type Change_Mode is (Insert, Delete);
    type Gravity_Type is (Forget_Gravity, Northwest_Gravity, North_Gravity,
                          Northeast_Gravity, West_Gravity, Center_Gravity,
                          East_Gravity, Southwest_Gravity, South_Gravity,
                          Southeast_Gravity, Static_Gravity);
    Unmap_Gravity : constant Gravity_Type := Forget_Gravity;
    type Map_State_Type is (Is_Unmapped, Is_Unviewable, Is_Viewable);
    subtype Geometry_Mask_Type is Boolean_Array (0 .. 6);
    X_Value : constant Geometry_Mask_Type :=
       Geometry_Mask_Type'(0 => True, others => False);
    Y_Value : constant Geometry_Mask_Type :=
       Geometry_Mask_Type'(1 => True, others => False);
    Width_Value : constant Geometry_Mask_Type :=
       Geometry_Mask_Type'(2 => True, others => False);
    Height_Value : constant Geometry_Mask_Type :=
       Geometry_Mask_Type'(3 => True, others => False);
    All_Values : constant Geometry_Mask_Type :=
       Geometry_Mask_Type'(4 => True, others => False);
    X_Negative : constant Geometry_Mask_Type :=
       Geometry_Mask_Type'(5 => True, others => False);
    Y_Negative : constant Geometry_Mask_Type :=
       Geometry_Mask_Type'(6 => True, others => False);
    type Set_Window_Attributes_Record is
        record
            Background_Pixmap : Pixmap;
            Background_Pixel : Pixels := 0;
            Border_Pixmap : Pixmap;
            Border_Pixel : Pixels := 1;
            Bit_Gravity : Gravity_Type := Forget_Gravity;
            Window_Gravity : Gravity_Type := Northwest_Gravity;
            Backing_Store : Backing_Store_Type := Not_Useful;
            Backing_Planes : Plane_Mask := All_Planes;
            Backing_Pixel : Pixels := 0;
            Save_Under : Boolean := False;
            Event_Mask : Events.Event_Mask_Type :=
               Events.Event_Mask_Type'(others => False);
            Do_Not_Propagate : Events.Event_Mask_Type :=
               Events.Event_Mask_Type'(others => False);
            Override_Redirect : Boolean := False;
            Current_Color_Map : Colors.Color_Map;
            Current_Cursor : Cursors.Cursor;
        end record;
    type Window_Attributes_Record is
        record
            X : Coordinate;
            Y : Coordinate;
            Width : Pixels;
            Height : Pixels;
            Border_Width : Pixels;
            Depth : Depth_Type;
            Visuals : Visual;
            Root : Window;
            Class : Window_Class;
            Bit_Gravity : Gravity_Type;
            Window_Gravity : Gravity_Type;
            Backing_Store : Backing_Store_Type;
            Backing_Planes : Plane_Mask;
            Backing_Pixel : Pixels;
            Save_Under : Boolean;
            Colormap : Colors.Color_Map;
            Map_Installed : Boolean;
            Map_State : Map_State_Type;
            All_Event_Masks : Events.Event_Mask_Type;
            Your_Event_Mask : Events.Event_Mask_Type;
            Do_Not_Propagate : Events.Event_Mask_Type;
            Override_Redirect : Boolean;
            Screen_Id : Screen;
        end record;
    subtype Wa_Mask_Type is Boolean_Array (0 .. 14);
    Wa_Background_Pixmap : constant Wa_Mask_Type :=
       Wa_Mask_Type'(0 => True, others => False);
    Wa_Background_Pixel : constant Wa_Mask_Type :=
       Wa_Mask_Type'(1 => True, others => False);
    Wa_Border_Pixmap : constant Wa_Mask_Type :=
       Wa_Mask_Type'(2 => True, others => False);
    Wa_Border_Pixel : constant Wa_Mask_Type :=
       Wa_Mask_Type'(3 => True, others => False);
    Wa_Bit_Gravity : constant Wa_Mask_Type :=
       Wa_Mask_Type'(4 => True, others => False);
    Wa_Win_Gravity : constant Wa_Mask_Type :=
       Wa_Mask_Type'(5 => True, others => False);
    Wa_Backing_Store : constant Wa_Mask_Type :=
       Wa_Mask_Type'(6 => True, others => False);
    Wa_Backing_Planes : constant Wa_Mask_Type :=
       Wa_Mask_Type'(7 => True, others => False);
    Wa_Backing_Pixel : constant Wa_Mask_Type :=
       Wa_Mask_Type'(8 => True, others => False);
    Wa_Override_Redirect : constant Wa_Mask_Type :=
       Wa_Mask_Type'(9 => True, others => False);
    Wa_Save_Under : constant Wa_Mask_Type :=
       Wa_Mask_Type'(10 => True, others => False);
    Wa_Event_Mask : constant Wa_Mask_Type :=
       Wa_Mask_Type'(11 => True, others => False);
    Wa_Dont_Propagate : constant Wa_Mask_Type :=
       Wa_Mask_Type'(12 => True, others => False);
    Wa_Colormap : constant Wa_Mask_Type :=
       Wa_Mask_Type'(13 => True, others => False);
    Wa_Cursor : constant Wa_Mask_Type :=
       Wa_Mask_Type'(14 => True, others => False);
    subtype Cw_Mask_Type is Boolean_Array (0 .. 31);  
    Cw_X : constant Cw_Mask_Type := Cw_Mask_Type'(0 => True, others => False);
    Cw_Y : constant Cw_Mask_Type := Cw_Mask_Type'(1 => True, others => False);
    Cw_Width : constant Cw_Mask_Type :=
       Cw_Mask_Type'(2 => True, others => False);
    Cw_Height : constant Cw_Mask_Type :=
       Cw_Mask_Type'(3 => True, others => False);
    Cw_Border_Width : constant Cw_Mask_Type :=
       Cw_Mask_Type'(4 => True, others => False);
    Cw_Sibling : constant Cw_Mask_Type :=
       Cw_Mask_Type'(5 => True, others => False);
    Cw_Stack_Mode : constant Cw_Mask_Type :=
       Cw_Mask_Type'(6 => True, others => False);
    type Window_Changes_Record is
        record
            Bounds : Rectangle;
            Border_Width : Pixels;
            Sibling : Window;
            Stack_Mode : Stack_Mode_Type;
        end record;
    subtype Size_Hint_Mask_Type is Boolean_Array (0 .. 7);
    User_Specified_Position : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(0 => True, others => False);
    User_Specified_Size : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(1 => True, others => False);
    Program_Specified_Position : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(2 => True, others => False);
    Program_Specified_Size : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(3 => True, others => False);
    Program_Specified_Min_Size : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(4 => True, others => False);
    Program_Specified_Max_Size : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(5 => True, others => False);
    Program_Specified_Resize_Inc : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(6 => True, others => False);
    Program_Specified_Aspect : constant Size_Hint_Mask_Type :=
       Size_Hint_Mask_Type'(7 => True, others => False);
    Program_Specified_All_Hints : constant Size_Hint_Mask_Type :=
       (Program_Specified_Position or Program_Specified_Size or
        Program_Specified_Min_Size or Program_Specified_Max_Size or
        Program_Specified_Resize_Inc or Program_Specified_Aspect);
    type Size_Hint_Record is
        record
            Flags : Size_Hint_Mask_Type;
            Bounds : Rectangle;
            Min_Width : Pixels;
            Min_Height : Pixels;
            Max_Width : Pixels;
            Max_Height : Pixels;
            Width_Inc : Pixels;
            Height_Inc : Pixels;
            Min_Aspect : Point;
            Max_Aspect : Point;
        end record;
    procedure Set_Standard_Properties (Display_Id : in Display;
                                       Window_Id : in Window;
                                       W_Name : in String;
                                       Icon_Name : in String;
                                       Icon : in Pixmap;
                                       Command : in String_List;
                                       Hints : in Size_Hint_Record);
    procedure Store_Name (Display_Id : in Display;
                          Window_Id : in Window;
                          Name : in String);
    function Fetch_Name
                (Display_Id : in Display; Window_Id : in Window) return String;
    procedure Set_Icon_Name (Display_Id : in Display;
                             Window_Id : in Window;
                             Name : in String);
    function Get_Icon_Name
                (Display_Id : in Display; Window_Id : in Window) return String;
    procedure Set_Command (Display_Id : in Display;
                           Window_Id : in Window;
                           Command : in String_List);
    type Initial_State_Type is (Dont_Care_State, Normal_State, Zoom_State,
                                Iconic_State, Inactive_State);
    subtype Wm_Hint_Mask_Type is Boolean_Array (0 .. 6);
    Input_Hint : constant Wm_Hint_Mask_Type :=
       Wm_Hint_Mask_Type'(0 => True, others => False);
    Initial_State_Hint : constant Wm_Hint_Mask_Type :=
       Wm_Hint_Mask_Type'(1 => True, others => False);
    Icon_Pixmap_Hint : constant Wm_Hint_Mask_Type :=
       Wm_Hint_Mask_Type'(2 => True, others => False);
    Icon_Window_Hint : constant Wm_Hint_Mask_Type :=
       Wm_Hint_Mask_Type'(3 => True, others => False);
    Icon_Position_Hint : constant Wm_Hint_Mask_Type :=
       Wm_Hint_Mask_Type'(4 => True, others => False);
    Icon_Mask_Hint : constant Wm_Hint_Mask_Type :=
       Wm_Hint_Mask_Type'(5 => True, others => False);
    Window_Group_Hint : constant Wm_Hint_Mask_Type :=
       Wm_Hint_Mask_Type'(6 => True, others => False);
    All_Hints : constant Wm_Hint_Mask_Type :=
       (Input_Hint or Icon_Pixmap_Hint or Icon_Window_Hint or
        Icon_Position_Hint or Icon_Mask_Hint);
    type Wm_Hint_Record is
        record
            Flags : Wm_Hint_Mask_Type;
            Input : Boolean;
            Initial_State : Initial_State_Type;
            Icon_Pixmap : Pixmap;
            Icon_Window : Window;
            Icon_Position : Point;
            Icon_Mask : Pixmap;
            Window_Group : X_Id;
        end record;
    type Wm_Class_Hint_Record is
        record
            Res_Name : String_Pointer;
            Res_Class : String_Pointer;
        end record;
    type Icon_Size_Record is
        record
            Min_Width : Pixels;
            Min_Height : Pixels;
            Max_Width : Pixels;
            Max_Height : Pixels;
            Width_Inc : Pixels;
            Height_Inc : Pixels;
        end record;
    type Icon_Size_Array is array (Natural range <>) of Icon_Size_Record;
    type Icon_Size_List is access Icon_Size_Array;
    function Resource_Manager_String
                (Display_Id : in Display) return String_Pointer;
    procedure Set_Wm_Hints (Display_Id : in Display;
                            Window_Id : in Window;
                            Hints : in Wm_Hint_Record);
    function Get_Wm_Hints (Display_Id : in Display; Window_Id : in Window)
                          return Wm_Hint_Record;
    procedure Set_Normal_Hints (Display_Id : in Display;
                                Window_Id : in Window;
                                Hints : in Size_Hint_Record);
    procedure Get_Normal_Hints (Display_Id : in Display;
                                Window_Id : in Window;
                                Hints : in out Size_Hint_Record;
                                Hints_Found : out Boolean);
    procedure Set_Zoom_Hints (Display_Id : in Display;
                              Window_Id : in Window;
                              Hints : in Size_Hint_Record);
    procedure Get_Zoom_Hints (Display_Id : in Display;
                              Window_Id : in Window;
                              Hints : in out Size_Hint_Record;
                              Hints_Found : out Boolean);
    procedure Set_Size_Hints (Display_Id : in Display;
                              Window_Id : in Window;
                              Hints : in Size_Hint_Record;
                              Property : in Atoms.Atom);
    procedure Get_Size_Hints (Display_Id : in Display;
                              Window_Id : in Window;
                              Property : in Atoms.Atom;
                              Hints : in out Size_Hint_Record;
                              Hints_Found : out Boolean);
    procedure Set_Icon_Sizes (Display_Id : in Display;
                              Window_Id : in Window;
                              Size_List : in Icon_Size_List);
    function Get_Icon_Sizes (Display_Id : in Display; Window_Id : in Window)
                            return Icon_Size_List;
    procedure Set_Class_Hint (Display_Id : in Display;
                              Window_Id : in Window;
                              Class_Hints : in Wm_Class_Hint_Record);
    procedure Get_Class_Hint (Display_Id : in Display;
                              Window_Id : in Window;
                              Class_Hints_Return : in out Wm_Class_Hint_Record;
                              Success : out Boolean);
    procedure Set_Transient_For_Hint (Display_Id : in Display;
                                      Window_Id : in Window;
                                      Prop_Window : in Window);
    procedure Get_Transient_For_Hint (Display_Id : in Display;
                                      Window_Id : in Window;
                                      Prop_Window_Return : in out Window;
                                      Success : out Boolean);
    function Create_Pixmap (Display_Id : in Display;
                            Drawable_Id : in Drawable;
                            Width : in Pixels;
                            Height : in Pixels;
                            Depth : in Depth_Type) return Pixmap;
    procedure Free_Pixmap (Display_Id : in Display; Pixmap_Id : in out Pixmap);
    function Create_Window
                (Display_Id : in Display;
                 Parent : in Window;
                 Bounds : in Rectangle;
                 Border_Width : in Pixels;
                 Depth : in Depth_Type;
                 Class : in Window_Class;
                 Visuals : in Visual;
                 Value_Mask : in Wa_Mask_Type;
                 Attributes : in Set_Window_Attributes_Record) return Window;
    function Create_Simple_Window (Display_Id : in Display;
                                   Parent : in Window;
                                   Bounds : in Rectangle;
                                   Border_Width : in Pixels;
                                   Border : in Pixels;
                                   Background : in Pixels) return Window;
    procedure Destroy_Window (Display_Id : in Display; Window_Id : in Window);
    procedure Destroy_Subwindows
                 (Display_Id : in Display; Window_Id : in Window);
    procedure Map_Window (Display_Id : in Display; Window_Id : in Window);
    procedure Map_Raised (Display_Id : in Display; Window_Id : in Window);
    procedure Map_Subwindows (Display_Id : in Display; Window_Id : in Window);
    procedure Unmap_Window (Display_Id : in Display; Window_Id : in Window);
    procedure Unmap_Subwindows (Display_Id : in Display; Window_Id : in Window);
    procedure Configure_Window (Display_Id : in Display;
                                Window_Id : in Window;
                                Value_Mask : in Cw_Mask_Type;
                                Changes : in Window_Changes_Record);
    procedure Move_Window (Display_Id : in Display;
                           Window_Id : in Window;
                           Xy : in Point);
    procedure Resize_Window (Display_Id : in Display;
                             Window_Id : in Window;
                             Width : in Pixels;
                             Height : in Pixels);
    procedure Move_Resize_Window (Display_Id : in Display;
                                  Window_Id : in Window;
                                  Bounds : in Rectangle);
    procedure Set_Window_Border_Width (Display_Id : in Display;
                                       Window_Id : in Window;
                                       Width : in Pixels);
    procedure Raise_Window (Display_Id : in Display; Window_Id : in Window);
    procedure Lower_Window (Display_Id : in Display; Window_Id : in Window);
    procedure Circulate_Subwindows (Display_Id : in Display;
                                    Window_Id : in Window;
                                    Direction : in Direction_Type);
    procedure Circulate_Subwindows_Up
                 (Display_Id : in Display; Window_Id : in Window);
    procedure Circulate_Subwindows_Down
                 (Display_Id : in Display; Window_Id : in Window);
    procedure Restack_Windows (Display_Id : in Display;
                               Windows : in Window_List);
    procedure Change_Window_Attributes
                 (Display_Id : in Display;
                  Window_Id : in Window;
                  Value_Mask : in Wa_Mask_Type;
                  Attributes : in Set_Window_Attributes_Record);
    procedure Set_Window_Background (Display_Id : in Display;
                                     Window_Id : in Window;
                                     Background : in Pixels);
    procedure Set_Window_Background_Pixmap (Display_Id : in Display;
                                            Window_Id : in Window;
                                            Tile : in Pixmap);
    procedure Set_Window_Border (Display_Id : in Display;
                                 Window_Id : in Window;
                                 Border : in Pixels);
    procedure Set_Window_Border_Pixmap (Display_Id : in Display;
                                        Window_Id : in Window;
                                        Tile : in Pixmap);
    procedure Translate_Coordinates (Display_Id : in Display;
                                     Source : in Window;
                                     Destination : in Window;
                                     From : in Point;
                                     To : out Point;
                                     Child : in out Window;
                                     Same_Screen : out Boolean);
    procedure Query_Tree (Display_Id : in Display;
                          Window_Id : in Window;
                          Root : in out Window;
                          Parent : in out Window;
                          Children : in out Window_List;
                          Status : out Boolean);
    procedure Get_Window_Attributes
                 (Display_Id : in Display;
                  Window_Id : in Window;
                  Attributes : in out Window_Attributes_Record;
                  Status : out Boolean);
    procedure Get_Geometry (Display_Id : in Display;
                            Drawable_Id : in Drawable;
                            Root : in out Window;
                            Bounds : out Rectangle;
                            Border_Width : out Pixels;
                            Depths : out Depth_Type;
                            Status : out Boolean);
    procedure Parse_Geometry (Parse_String : in String;
                              Geometry : out Rectangle;
                              Values_Found : out Geometry_Mask_Type);
    procedure Geometry (Display_Id : in Display;
                        Screen_Id : in Screen;
                        Position : in String;
                        Default : in String;
                        Border_Width : in Pixels;
                        Font_Height : in Pixels;
                        Font_Width : in Pixels;
                        Xy_Padding : in Point;
                        Geometry : out Rectangle;
                        Values_Found : out Geometry_Mask_Type);
    procedure Query_Pointer (Display_Id : in Display;
                             Window_Id : in Window;
                             Root : in out Window;
                             Child : in out Window;
                             Root_Xy : out Point;
                             Window_Xy : out Point;
                             Keys_And_Buttons : out Events.Key_And_Button_Mask;
                             Same_Screen : out Boolean);
    procedure Get_Window_Property (Display_Id : in Display;
                                   Window_Id : in Window;
                                   Property : in Atoms.Atom;
                                   Long_Offset : in X_Long_Integer;
                                   Long_Length : in X_Long_Integer;
                                   Delete : in Boolean;
                                   Req_Type : in Atoms.Atom;
                                   Actual_Type : out Atoms.Atom;
                                   Actual_Form : out X_Long_Integer;
                                   Bytes_After : out X_Long_Integer;
                                   Data : out Bytes);
    function List_Properties (Display_Id : in Display; Window_Id : in Window)
                             return Atoms.Atom_List;
    procedure Change_Property (Display_Id : in Display;
                               Window_Id : in Window;
                               Property : in Atoms.Atom;
                               Kind : in Atoms.Atom;
                               Format : in Property_Format_Type;
                               Mode : in Property_Mode;
                               Data : in Bytes;
                               N_Items : in Natural);
    procedure Rotate_Window_Properties (Display_Id : in Display;
                                        Window_Id : in Window;
                                        Properties : in Atoms.Atom_List;
                                        N_Positions : in Natural);
    procedure Delete_Property (Display_Id : in Display;
                               Window_Id : in Window;
                               Property : in Atoms.Atom);
    procedure Set_Selection_Owner (Display_Id : in Display;
                                   Selection : in Atoms.Atom;
                                   Owner : in Window;
                                   Time_Stamp : in Time);
    function Get_Selection_Owner
                (Display_Id : in Display; Selection : in Atoms.Atom)
                return Window;
    procedure Convert_Selection (Display_Id : in Display;
                                 Selection : in Atoms.Atom;
                                 Target : in Atoms.Atom;
                                 Property : in Atoms.Atom;
                                 Requestor : in Window;
                                 Time_Stamp : in Time);
    procedure Reparent_Window (Display_Id : in Display;
                               Window_Id : in Window;
                               Parent : in Window;
                               Upper_Left : in Point);
    procedure Change_Save_Set (Display_Id : in Display;
                               Window_Id : in Window;
                               Mode : in Change_Mode);
    procedure Add_To_Save_Set (Display_Id : in Display; Window_Id : in Window);
    procedure Remove_From_Save_Set
                 (Display_Id : in Display; Window_Id : in Window);
    procedure Save_Context (Display_Id : in Display;
                            Window_Id : in Window;
                            The_Context : in Context;
                            Data : in System.Address);
    function Find_Context (Display_Id : in Display;
                           Window_Id : in Window;
                           The_Context : in Context) return System.Address;
    procedure Delete_Context (Display_Id : in Display;
                              Window_Id : in Window;
                              The_Context : in Context);
    function Unique_Context return Context;
    type Synchronize_Mode is (Off, On);
    procedure Synchronize (Display_Id : in Display;
                           Mode : in Synchronize_Mode := On);
    function Max_Request_Size (Display_Id : in Display) return X_Long_Integer;
private
    type Context is range 0 .. (2 ** 28) - 1;
    type Drawable is range 0 .. (2 ** 28) - 1;
    type X_Id is range 0 .. (2 ** 28) - 1;
    type Visual_Record;
    type Visual is access Visual_Record;
    type Screen_Record;
    type Screen is access Screen_Record;
    type Display_Record;
    type Display is access Display_Record;
    Null_Display : constant Display := null;
    Null_Context : constant Context := Context (0);
    Null_Drawable : constant Drawable := Drawable (0);
    Null_Window : constant Window := Null_Drawable;
    Null_Pixmap : constant Pixmap := Null_Drawable;
    Pointer_Window : constant Window := Null_Drawable;
    Input_Focus_Window : constant Window := Window (1);
    Pointer_Root_Window : constant Window := Window (1);
    None : constant Drawable := Drawable (1);
    Parent_Relative : constant Pixmap := Drawable (0);
    Copy_Drawable_From_Parent : constant Drawable := Drawable (0);
    Copy_Visual_From_Parent : constant Visual := null;
    Null_X_Id : constant X_Id := X_Id (0);
end X_Windows