|
|
DataMuseum.dkPresents historical artifacts from the history of: Rational R1000/400 |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about Rational R1000/400 Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - metrics - download
Length: 141702 (0x22986)
Types: TextFile
Notes: R1k Text-file segment
└─⟦8527c1e9b⟧ Bits:30000544 8mm tape, Rational 1000, Arrival backup of disks in PAM's R1000
└─⟦cfc2e13cd⟧ »Space Info Vol 2«
└─⟦6261e4b0d⟧
└─⟦this⟧
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 .. 2147483647;
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 .. 255;
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
-- The order of the elements of this type is not significant.
type Name is (S370, I80x86, I80386, Mc680x0, Vax, Transputer);
System_Name : constant Name := I80386;
Storage_Unit : constant := 8;
Max_Int : constant := 2 ** 31 - 1;
Min_Int : constant := -(2 ** 31);
Max_Mantissa : constant := 31;
Fine_Delta : constant := 2#1.0#E-31;
Max_Digits : constant := 15;
Memory_Size : constant := 2 ** 32;
Tick : constant := 0.02;
subtype Priority is Integer range 1 .. 28;
type Address is private;
Null_Address : constant Address;
-- Converts a string to an address. The syntax of the string and its
-- meaning are target dependent.
--
-- For the 80386 the syntax is:
-- "OOOOOOOO" where OOOOOOOO is an 8 digit or less hexadecimal number
-- representing an offset either in the data segment or in the
-- code segment.
-- Example:
-- "00000008"
--
-- The exception CONSTRAINT_ERROR is raised if the string has not the
-- proper syntax.
function Value (Left : in String) return Address;
-- Converts an address to a string. The syntax of the returned string
-- is described in the VALUE function.
subtype Address_String is String (1 .. 8);
function Image (Left : in Address) return Address_String;
-- The following routines provide support to perform address
-- computation. The meaning of the "+" and "-" operators is
-- architecture dependent. For example on a segmented machine
-- the OFFSET parameter is added to, or subtracted from the offset
-- part of the address, the segment remaining untouched.
type Offset is range 0 .. 2 ** 31 - 1;
-- The exeception ADDRESS_ERROR is raised by "<", "<=", ">", ">=", "-"
-- if the two addresses do not have the same segment value. This
-- exception is never raised on a non segmented machine.
-- The exception CONSTRAINT_ERROR can be raised by "+" and "-".
Address_Error : exception;
function "+" (Left : in Address; Right : in Offset) return Address;
function "+" (Left : in Offset; Right : in Address) return Address;
function "-" (Left : in Address; Right : in Offset) return Address;
-- The exception ADDRESS_ERROR is raised on a segmented architecture
-- if the two addresses do not have the same segment value.
function "-" (Left : in Address; Right : in Address) return Offset;
-- Perform an unsigned comparison on addresses or offset part of
-- addresses on a segmented machine.
function "<=" (Left, Right : in Address) return Boolean;
function "<" (Left, Right : in Address) return Boolean;
function ">=" (Left, Right : in Address) return Boolean;
function ">" (Left, Right : in Address) return Boolean;
function "mod" (Left : in Address; Right : in Positive) return Natural;
-- Returns the given address rounded to a specific value.
type Round_Direction is (Down, Up);
function Round (Value : in Address;
Direction : in Round_Direction;
Modulus : in Positive) return Address;
-- These routines are provided to perform READ/WRITE operation
-- in memory.
-- Warning: These routines will give unexpected results if used with
-- unconstrained types.
generic
type Target is private;
function Fetch_From_Address (A : in Address) return Target;
generic
type Target is private;
procedure Assign_To_Address (A : in Address; T : in Target);
-- Procedure to copy LENGTH storage unit starting at the address
-- FROM to the address TO. The source and destination may overlap.
-- OBJECT_LENGTH designates the size of an object in storage units.
type Object_Length is range 0 .. 2 ** 31 - 1;
procedure Move (To : in Address;
From : in Address;
Length : in Object_Length);
private
pragma Inline ("+", "-", Same_Segment);
type Address is access String;
Null_Address : constant Address := null;
pragma Interface (Assembler, Move);
pragma Interface_Name (Move, "ADA@BLOCK_MOVE");
end System;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);-- -------------------------------------------------------------------------
-- CIFO package that suspends and resumes a task.
-- See CIFO section titled "Controlling when a task executes".
-- -------------------------------------------------------------------------
with TASK_IDS;
package DISPATCHING_CONTROL is
type TASK_SUSPENSION_STATUS is (PROTECTED, SUSPENDED, UNTOUCHED);
procedure SUSPEND (I : in TASK_IDS.TASK_ID);
function SUSPEND (I : in TASK_IDS.TASK_ID)
return TASK_SUSPENSION_STATUS;
procedure RESUME (I : in TASK_IDS.TASK_ID);
function RESUME (I : in TASK_IDS.TASK_ID)
return TASK_SUSPENSION_STATUS;
procedure PROTECT (I : in TASK_IDS.TASK_ID);
function PROTECT (I : in TASK_IDS.TASK_ID)
return TASK_SUSPENSION_STATUS;
procedure UNPROTECT (I : in TASK_IDS.TASK_ID);
function UNPROTECT (I : in TASK_IDS.TASK_ID)
return TASK_SUSPENSION_STATUS;
function STATUS (I : in TASK_IDS.TASK_ID)
return TASK_SUSPENSION_STATUS;
end DISPATCHING_CONTROL;-- -------------------------------------------------------------------------
-- CIFO "dynamic priorities" section.
-- -------------------------------------------------------------------------
with TASK_IDS;
package DYNAMIC_PRIORITIES is
type PRIORITY is range 0 .. 28;
type URGENCY is (NOW, LATER);
procedure SET_PRIORITY (OF_TASK : in TASK_IDS.TASK_ID;
TO : in PRIORITY;
HOW_SOON : in URGENCY := NOW);
function PRIORITY_OF (THE_TASK : TASK_IDS.TASK_ID) return PRIORITY;
end DYNAMIC_PRIORITIES;-- "This unpublished work is protected both as a proprietary work and
-- under the Universal Copyright Convention and the US Copyright Act of
-- 1976. Its distribution and access are limited only to authorized
-- persons. Copr. (c) Alsys. Created 1990, initially licensed 1990.
-- All rights reserved.
-- Unauthorized use (including use to prepare other works), disclosure,
-- reproduction, or distribution may violate national criminal law."
------------------------------------------------------------------------------
-- This module is a generic template for the EVENT_MANAGEMENT package --
-- required by CIFO 3.0, which is obtained by instantiating this generic. --
------------------------------------------------------------------------------
-- *********************
-- * TABLE OF CONTENTS *
-- *********************
-- 1. Generic Parameters
-- 2. User Visible Types
-- 3. Event Testing
-- 4. Signal Operations
-- 5. Event Construction
-- 6. Wait Operations
-- 7. IBM SOW Declarations
-- 13. Instantiations
generic
-- *************************
-- * 1. GENERIC PARAMETERS *
-- *************************
MAX_EVENTS : INTEGER;
-- This parameter controls the maximum number of events which can be
-- handled as part of a single COMPLEX_EVENT value, avoiding additional
-- heap allocations. The size of a COMPLEX_EVENT depends on this value
-- since enough space is allocated to hold an expression of this size.
SIGNAL_MAX_EXCEEDED : BOOLEAN := FALSE;
-- This parameter controls the behaviour of the system if a complex
-- expression exceeds the threshhold specified by the MAX_EVENTS value.
-- If the value of the parameter is FALSE, then storage for at least
-- part of the complex event structure may be obtained from the heap.
-- This avoids any limits on the complexity of event expressions, but
-- can result in storage leaks. If the parameter is TRUE, then an attempt
-- to build a complex expression exceeding the limit causes the exception
-- MAX_EVENTS_EXCEEDED to be raised, warning the programmer that the
-- attempted event construction may lead to storage leaks.
package CIFO_EVENT_MANAGEMENT is
-- The library contains a standard instantiations of this package:
-- package EVENT_MANAGEMENT
-- is new CIFO_EVENT_MANAGEMENT (MAX_EVENTS => 6,
-- SIGNAL_MAX_EXCEEDED => FALSE);
-- This generates a package which has no limit on the complexity of
-- complex events, but which uses the heap if the number of events
-- exceeds 6, and may thus cause storage leaks in these cases.
-- *************************
-- * 2. USER VISIBLE TYPES *
-- *************************
type EVENT is limited private;
-- Note: we have deliberately changed this to limited private, since the
-- semantics of both assignment and comparison of EVENTs is obscure.
type COMPLEX_EVENT is private;
-- ********************
-- * 3. EVENT TESTING *
-- ********************
function IS_SET (AN_EVENT : in EVENT) return BOOLEAN;
function IS_SET (EXPRESSION : in COMPLEX_EVENT) return BOOLEAN;
pragma INLINE (IS_SET);
-- ************************
-- * 4. SIGNAL OPERATIONS *
-- ************************
procedure SET (TARGET_EVENT : in out EVENT);
procedure RESET (TARGET_EVENT : in out EVENT);
procedure TOGGLE (TARGET_EVENT : in out EVENT);
procedure PULSE (TARGET_EVENT : in out EVENT);
-- *************************
-- * 5. EVENT CONSTRUCTION *
-- *************************
function COMPLEX_EVENT_OF (SIMPLE_EVENT : EVENT) return COMPLEX_EVENT;
function "and" (LEFT, RIGHT : EVENT) return COMPLEX_EVENT;
function "and" (LEFT : COMPLEX_EVENT; RIGHT : EVENT) return COMPLEX_EVENT;
function "and" (LEFT : EVENT; RIGHT : COMPLEX_EVENT) return COMPLEX_EVENT;
function "and" (LEFT, RIGHT : COMPLEX_EVENT) return COMPLEX_EVENT;
function "or" (LEFT, RIGHT : EVENT) return COMPLEX_EVENT;
function "or" (LEFT : COMPLEX_EVENT; RIGHT : EVENT) return COMPLEX_EVENT;
function "or" (LEFT : EVENT; RIGHT : COMPLEX_EVENT) return COMPLEX_EVENT;
function "or" (LEFT, RIGHT : COMPLEX_EVENT) return COMPLEX_EVENT;
function "xor" (LEFT, RIGHT : EVENT) return COMPLEX_EVENT;
function "xor" (LEFT : COMPLEX_EVENT; RIGHT : EVENT) return COMPLEX_EVENT;
function "xor" (LEFT : EVENT; RIGHT : COMPLEX_EVENT) return COMPLEX_EVENT;
function "xor" (LEFT, RIGHT : COMPLEX_EVENT) return COMPLEX_EVENT;
function "not" (AN_EVENT : EVENT) return COMPLEX_EVENT;
function "not" (AN_EVENT : COMPLEX_EVENT) return COMPLEX_EVENT;
MAX_EVENTS_EXCEEDED : exception;
-- **********************
-- * 6. WAIT OPERATIONS *
-- **********************
procedure WAIT_ON (AN_EVENT : in COMPLEX_EVENT);
procedure CANCEL_WAIT_ON (TSK : in TASK_ID);
-- This procedure is used by the SCHEDULER. It removes a task from the
-- event structures (if it is currently chained). It is used for functions
-- such as task abort.
-- ***************************
-- * 7. IBM SOW DECLARATIONS *
-- ***************************
-- This section contains renamings and additional declarations required
-- by the IBM statement of work for the Lynx project. This SOW introduces
-- slightly different names, apparently taken from some intermediate
-- version of CIFO, between the 2.0 and 3.0 documents.
subtype EVENT_EXPRESSION is COMPLEX_EVENT;
function VALUE_OF (AN_EVENT : in COMPLEX_EVENT) return BOOLEAN
renames IS_SET;
function EXPRESSION_OF (SIMPLE_EVENT : EVENT) return COMPLEX_EVENT
renames COMPLEX_EVENT_OF;
procedure INITIALIZE (TARGET_EVENT : in out EVENT;
VALUE : in BOOLEAN := FALSE);
pragma INLINE (INITIALIZE);
end CIFO_EVENT_MANAGEMENT;
-- **********************
-- * 13. INSTANTIATIONS *
-- **********************
with CIFO_EVENT_MANAGEMENT;
package EVENT_MANAGEMENT is
new CIFO_EVENT_MANAGEMENT (MAX_EVENTS => 6,
SIGNAL_MAX_EXCEEDED => FALSE);-- -------------------------------------------------------------------------
-- CIFO section titled "Asynchronous Entry Call".
-- -------------------------------------------------------------------------
-- The CIFO documents ask for:
--
-- generic
-- type PARAMETER is limited private;
-- with procedure ENTRY_TO_BE_CALLED (PARAM : in PARAMETER);
-- procedure NON_WAITING_ENTRY_CALL (PARAM : in PARAMETER);
--
-- Instead we provide:
generic
type PARAMETER is private;
with procedure ENTRY_TO_BE_CALLED (PARAM : in PARAMETER);
package ENTRY_CALLER is
procedure NON_WAITING_ENTRY_CALL (PARAM : PARAMETER);
end;
-- It is used in much the same way as the one in the CIFO
-- document, but its instantiation is different. Instead of:
--
-- procedure MY_CALL(I:INTEGER)
-- is new NON_WAITING_ENTRY_CALL(INTEGER, T.E);
-- MY_CALL(100);
--
-- a program does
--
-- package CALLER is new ENTRY_CALLER(INTEGER, T.E);
-- procedure MY_CALL(I:INTEGER) renames CALLER.NON_WAITING_ENTRY_CALL;
-- MY_CALL(100);-- -------------------------------------------------------------------------
-- CIFO preemption control package.
-- See CIFO section titled "Nonpreemptible Sections".
-- -------------------------------------------------------------------------
package PREEMPTION_CONTROL is
procedure DISABLE_PREEMPTION;
procedure ENABLE_PREEMPTION;
function PREEMPTIBLE return BOOLEAN;
end PREEMPTION_CONTROL;
generic
with procedure NONPREEMPTIBLE_SECTION;
procedure CALL_NONPREEMPTIBLE_SECTION;-- -------------------------------------------------------------------------
-- CIFO HAL/S scheduling package.
-- See CIFO section titled "Synchronous and Asynchronous Task Scheduling",
-- or chapter 12 of "Programming in HAL/S" by Ryer.
-- -------------------------------------------------------------------------
with TASK_IDS, DYNAMIC_PRIORITIES, EVENT_MANAGEMENT, CALENDAR;
use TASK_IDS, DYNAMIC_PRIORITIES, EVENT_MANAGEMENT, CALENDAR;
package SCHEDULER is
TASK_OVERRUN : EVENT;
type TASK_INITIATIONS is (IMMEDIATELY, AT_TIME, AFTER_DELAY, ON_EVENT);
type TASK_REPETITIONS is (NONE, REPEAT_EVERY, REPEAT_AFTER);
type TASK_COMPLETIONS is (NONE, UNTIL_TIME, WHILE_EVENT, UNTIL_EVENT);
type INITIATION_INFO (INITIATION : TASK_INITIATIONS := IMMEDIATELY) is record
case INITIATION is
when IMMEDIATELY =>
null;
when AT_TIME =>
T : TIME;
when AFTER_DELAY =>
D : DURATION;
when ON_EVENT =>
E : EVENT_EXPRESSION;
end case;
end record;
type REPETITION_INFO (REPETITION : TASK_REPETITIONS := NONE) is record
case REPETITION is
when NONE =>
null;
when REPEAT_EVERY | REPEAT_AFTER =>
D : DURATION;
end case;
end record;
type COMPLETION_INFO (COMPLETION : TASK_COMPLETIONS := NONE) is record
case COMPLETION is
when NONE =>
null;
when UNTIL_TIME =>
T : TIME;
when WHILE_EVENT | UNTIL_EVENT =>
E : EVENT_EXPRESSION;
end case;
end record;
procedure SCHEDULE (SCHEDULED_TASK : in TASK_ID;
REPORT_OVERRUN : in BOOLEAN := FALSE;
PRIORITY : in DYNAMIC_PRIORITIES.PRIORITY;
INITIATION : in INITIATION_INFO;
REPETITION : in REPETITION_INFO;
COMPLETION : in COMPLETION_INFO;
OVERRUN : in EVENT := TASK_OVERRUN);
procedure WAIT_FOR_SCHEDULE (COMPLETED : out BOOLEAN);
procedure DESCHEDULE (SCHEDULED_TASK : in TASK_ID);
end SCHEDULER;-- -------------------------------------------------------------------------
-- POSIX 1003.4 semaphores
-- -------------------------------------------------------------------------
package SEMAPHORE is
type SEMAPHORE_VALUE is private;
procedure WAIT (SEMAPHORE : in SEMAPHORE_VALUE);
procedure POST (SEMAPHORE : in SEMAPHORE_VALUE);
procedure CONDITIONAL_WAIT (SEMAPHORE : in SEMAPHORE_VALUE;
SEMAPHORE_FREE : out BOOLEAN);
-- Semaphores are scarce system resources. One is allocated whenever
-- a program declares an object of type SEMAPHORE_VALUE. They can
-- run out, depending on the operating system limit. If one is declared
-- and there are no more left in the system, STORAGE_ERROR is raised.
-- CLOSE may be called to free one if it will no longer be used.
procedure CLOSE (SEMAPHORE : in out SEMAPHORE_VALUE);
end SEMAPHORE;-- -------------------------------------------------------------------------
-- CIFO shared data protection.
-- See CIFO section titled "Mutually Exclusive Access to Shared Data".
-- (CIFO V2 specification)
-- -------------------------------------------------------------------------
generic
type ITEM_TYPE is private;
package SHARED_DATA_GENERIC is
type SHARED_DATA is limited private;
procedure WRITE (TO_OBJECT : in out SHARED_DATA;
NEW_VALUE : in ITEM_TYPE);
function VALUE_OF (OBJECT : SHARED_DATA) return ITEM_TYPE;
function INITIALIZED (OBJECT : SHARED_DATA) return BOOLEAN;
end SHARED_DATA_GENERIC;-- -------------------------------------------------------------------------
-- CIFO Task identifiers. Used by all the other packages.
-- See CIFO section titled "Task Identifiers".
-- -------------------------------------------------------------------------
package TASK_IDS is
-----------------
-- CIFO V3 names:
-----------------
subtype TASK_ID is TID.TASK_ID;
TASK_ID_ERROR : exception;
function NULL_TASK return TASK_ID;
function SELF return TASK_ID;
function MASTER_TASK (I : TASK_ID := SELF) return TASK_ID;
function CALLER (I : TASK_ID := SELF) return TASK_ID;
function CALLABLE (I : TASK_ID := SELF) return BOOLEAN;
function TERMINATED (I : TASK_ID := SELF) return BOOLEAN;
-----------------
-- CIFO V2 names:
-----------------
generic
type TASK_TYPE is limited private;
function ID_OF (T : TASK_TYPE) return TASK_ID;
function PARENT (I : TASK_ID := SELF) return TASK_ID;
end TASK_IDS;generic
with procedure Nonpreemptible_Section;
procedure Call_Nonpreemptible_Section;-- "This unpublished work is protected both as a proprietary work and
-- under the Universal Copyright Convention and the US Copyright Act of
-- 1976. Its distribution and access are limited only to authorized
-- persons. Copr. (c) Alsys. Created 1990, initially licensed 1990.
-- All rights reserved.
-- Unauthorized use (including use to prepare other works), disclosure,
-- reproduction, or distribution may violate national criminal law."
------------------------------------------------------------------------------
-- This module is a generic template for the EVENT_MANAGEMENT package --
-- required by CIFO 3.0, which is obtained by instantiating this generic. --
------------------------------------------------------------------------------
-- *********************
-- * TABLE OF CONTENTS *
-- *********************
-- 1. Generic Parameters
-- 2. User Visible Types
-- 3. Event Testing
-- 4. Signal Operations
-- 5. Event Construction
-- 6. Wait Operations
-- 7. IBM SOW Declarations
-- 13. Instantiations
generic
-- *************************
-- * 1. GENERIC PARAMETERS *
-- *************************
Max_Events : Integer;
-- This parameter controls the maximum number of events which can be
-- handled as part of a single COMPLEX_EVENT value, avoiding additional
-- heap allocations. The size of a COMPLEX_EVENT depends on this value
-- since enough space is allocated to hold an expression of this size.
Signal_Max_Exceeded : Boolean := False;
-- This parameter controls the behaviour of the system if a complex
-- expression exceeds the threshhold specified by the MAX_EVENTS value.
-- If the value of the parameter is FALSE, then storage for at least
-- part of the complex event structure may be obtained from the heap.
-- This avoids any limits on the complexity of event expressions, but
-- can result in storage leaks. If the parameter is TRUE, then an attempt
-- to build a complex expression exceeding the limit causes the exception
-- MAX_EVENTS_EXCEEDED to be raised, warning the programmer that the
-- attempted event construction may lead to storage leaks.
package Cifo_Event_Management is
-- The library contains a standard instantiations of this package:
-- package EVENT_MANAGEMENT
-- is new CIFO_EVENT_MANAGEMENT (MAX_EVENTS => 6,
-- SIGNAL_MAX_EXCEEDED => FALSE);
-- This generates a package which has no limit on the complexity of
-- complex events, but which uses the heap if the number of events
-- exceeds 6, and may thus cause storage leaks in these cases.
-- *************************
-- * 2. USER VISIBLE TYPES *
-- *************************
type Event is limited private;
-- Note: we have deliberately changed this to limited private, since the
-- semantics of both assignment and comparison of EVENTs is obscure.
type Complex_Event is private;
-- ********************
-- * 3. EVENT TESTING *
-- ********************
function Is_Set (An_Event : in Event) return Boolean;
function Is_Set (Expression : in Complex_Event) return Boolean;
pragma Inline (Is_Set);
-- ************************
-- * 4. SIGNAL OPERATIONS *
-- ************************
procedure Set (Target_Event : in out Event);
procedure Reset (Target_Event : in out Event);
procedure Toggle (Target_Event : in out Event);
procedure Pulse (Target_Event : in out Event);
-- *************************
-- * 5. EVENT CONSTRUCTION *
-- *************************
function Complex_Event_Of (Simple_Event : Event) return Complex_Event;
function "and" (Left, Right : Event) return Complex_Event;
function "and" (Left : Complex_Event; Right : Event) return Complex_Event;
function "and" (Left : Event; Right : Complex_Event) return Complex_Event;
function "and" (Left, Right : Complex_Event) return Complex_Event;
function "or" (Left, Right : Event) return Complex_Event;
function "or" (Left : Complex_Event; Right : Event) return Complex_Event;
function "or" (Left : Event; Right : Complex_Event) return Complex_Event;
function "or" (Left, Right : Complex_Event) return Complex_Event;
function "xor" (Left, Right : Event) return Complex_Event;
function "xor" (Left : Complex_Event; Right : Event) return Complex_Event;
function "xor" (Left : Event; Right : Complex_Event) return Complex_Event;
function "xor" (Left, Right : Complex_Event) return Complex_Event;
function "not" (An_Event : Event) return Complex_Event;
function "not" (An_Event : Complex_Event) return Complex_Event;
Max_Events_Exceeded : exception;
-- **********************
-- * 6. WAIT OPERATIONS *
-- **********************
--
-- JRG Added this type for semantic consistency to allow
-- compilation on Rational. 9/20/91 Also added private
-- part.
--
type Task_Id is private; -- Bogus Declaration
procedure Wait_On (An_Event : in Complex_Event);
procedure Cancel_Wait_On (Tsk : in Task_Id);
-- This procedure is used by the SCHEDULER. It removes a task from the
-- event structures (if it is currently chained). It is used for functions
-- such as task abort.
-- ***************************
-- * 7. IBM SOW DECLARATIONS *
-- ***************************
-- This section contains renamings and additional declarations required
-- by the IBM statement of work for the Lynx project. This SOW introduces
-- slightly different names, apparently taken from some intermediate
-- version of CIFO, between the 2.0 and 3.0 documents.
subtype Event_Expression is Complex_Event;
function Value_Of (An_Event : in Complex_Event) return Boolean
renames Is_Set;
function Expression_Of (Simple_Event : Event) return Complex_Event
renames Complex_Event_Of;
procedure Initialize (Target_Event : in out Event;
Value : in Boolean := False);
pragma Inline (Initialize);
private
--
-- JRG Created Private Part for Compilation Closure
-- On Rational. Added the following three types to the
-- private part on 9/20/91.
--
type Event is new Boolean; -- Bogus Declaration
type Complex_Event is new Boolean; -- Bogus Declaration
type Task_Id is new Boolean; -- Bogus Declaration
end Cifo_Event_Management;
-- **********************
-- * 13. INSTANTIATIONS *
-- **********************-- -------------------------------------------------------------------------
-- CIFO package that suspends and resumes a task.
-- See CIFO section titled "Controlling when a task executes".
-- -------------------------------------------------------------------------
with Task_Ids;
package Dispatching_Control is
type Task_Suspension_Status is (Protected, Suspended, Untouched);
procedure Suspend (I : in Task_Ids.Task_Id);
function Suspend (I : in Task_Ids.Task_Id) return Task_Suspension_Status;
procedure Resume (I : in Task_Ids.Task_Id);
function Resume (I : in Task_Ids.Task_Id) return Task_Suspension_Status;
procedure Protect (I : in Task_Ids.Task_Id);
function Protect (I : in Task_Ids.Task_Id) return Task_Suspension_Status;
procedure Unprotect (I : in Task_Ids.Task_Id);
function Unprotect (I : in Task_Ids.Task_Id) return Task_Suspension_Status;
function Status (I : in Task_Ids.Task_Id) return Task_Suspension_Status;
end Dispatching_Control;-- -------------------------------------------------------------------------
-- CIFO "dynamic priorities" section.
-- -------------------------------------------------------------------------
with Task_Ids;
package Dynamic_Priorities is
type Priority is range 0 .. 28;
type Urgency is (Now, Later);
procedure Set_Priority (Of_Task : in Task_Ids.Task_Id;
To : in Priority;
How_Soon : in Urgency := Now);
function Priority_Of (The_Task : Task_Ids.Task_Id) return Priority;
end Dynamic_Priorities;-- -------------------------------------------------------------------------
-- CIFO section titled "Asynchronous Entry Call".
-- -------------------------------------------------------------------------
-- The CIFO documents ask for:
--
-- generic
-- type PARAMETER is limited private;
-- with procedure ENTRY_TO_BE_CALLED (PARAM : in PARAMETER);
-- procedure NON_WAITING_ENTRY_CALL (PARAM : in PARAMETER);
--
-- Instead we provide:
generic
type Parameter is private;
with procedure Entry_To_Be_Called (Param : in Parameter);
package Entry_Caller is
procedure Non_Waiting_Entry_Call (Param : Parameter);
end Entry_Caller;
-- It is used in much the same way as the one in the CIFO
-- document, but its instantiation is different. Instead of:
--
-- procedure MY_CALL(I:INTEGER)
-- is new NON_WAITING_ENTRY_CALL(INTEGER, T.E);
-- MY_CALL(100);
--
-- a program does
--
-- package CALLER is new ENTRY_CALLER(INTEGER, T.E);
-- procedure MY_CALL(I:INTEGER) renames CALLER.NON_WAITING_ENTRY_CALL;
-- MY_CALL(100);with Cifo_Event_Management;
package Event_Management is
new Cifo_Event_Management (Max_Events => 6, Signal_Max_Exceeded => False);-- -------------------------------------------------------------------------
-- CIFO preemption control package.
-- See CIFO section titled "Nonpreemptible Sections".
-- -------------------------------------------------------------------------
package Preemption_Control is
procedure Disable_Preemption;
procedure Enable_Preemption;
function Preemptible return Boolean;
end Preemption_Control;-- -------------------------------------------------------------------------
-- CIFO HAL/S scheduling package.
-- See CIFO section titled "Synchronous and Asynchronous Task Scheduling",
-- or chapter 12 of "Programming in HAL/S" by Ryer.
-- -------------------------------------------------------------------------
with Task_Ids, Dynamic_Priorities, Event_Management, Calendar;
use Task_Ids, Dynamic_Priorities, Event_Management, Calendar;
package Scheduler is
type Task_Id is new Boolean; -- Bogus Declaration
Task_Overrun : Event;
type Task_Initiations is (Immediately, At_Time, After_Delay, On_Event);
type Task_Repetitions is (None, Repeat_Every, Repeat_After);
type Task_Completions is (None, Until_Time, While_Event, Until_Event);
type Initiation_Info (Initiation : Task_Initiations := Immediately) is
record
case Initiation is
when Immediately =>
null;
when At_Time =>
T : Time;
when After_Delay =>
D : Duration;
when On_Event =>
E : Event_Expression;
end case;
end record;
type Repetition_Info (Repetition : Task_Repetitions := None) is
record
case Repetition is
when None =>
null;
when Repeat_Every | Repeat_After =>
D : Duration;
end case;
end record;
type Completion_Info (Completion : Task_Completions := None) is
record
case Completion is
when None =>
null;
when Until_Time =>
T : Time;
when While_Event | Until_Event =>
E : Event_Expression;
end case;
end record;
procedure Schedule (Scheduled_Task : in Task_Id;
Report_Overrun : in Boolean := False;
Priority : in Dynamic_Priorities.Priority;
Initiation : in Initiation_Info;
Repetition : in Repetition_Info;
Completion : in Completion_Info;
Overrun : in Event := Task_Overrun);
procedure Wait_For_Schedule (Completed : out Boolean);
procedure Deschedule (Scheduled_Task : in Task_Id);
end Scheduler;-- -------------------------------------------------------------------------
-- POSIX 1003.4 semaphores
-- -------------------------------------------------------------------------
package Semaphore is
type Semaphore_Value is private;
procedure Wait (Semaphore : in Semaphore_Value);
procedure Post (Semaphore : in Semaphore_Value);
procedure Conditional_Wait (Semaphore : in Semaphore_Value;
Semaphore_Free : out Boolean);
-- Semaphores are scarce system resources. One is allocated whenever
-- a program declares an object of type SEMAPHORE_VALUE. They can
-- run out, depending on the operating system limit. If one is declared
-- and there are no more left in the system, STORAGE_ERROR is raised.
-- CLOSE may be called to free one if it will no longer be used.
procedure Close (Semaphore : in out Semaphore_Value);
private
--
-- Private Part added by JRG for compilation on 9/20/91
--
type Semaphore_Value is new Boolean; -- Bogus implementation
end Semaphore;-- -------------------------------------------------------------------------
-- CIFO shared data protection.
-- See CIFO section titled "Mutually Exclusive Access to Shared Data".
-- (CIFO V2 specification)
-- -------------------------------------------------------------------------
generic
type Item_Type is private;
package Shared_Data_Generic is
type Shared_Data is limited private;
procedure Write (To_Object : in out Shared_Data; New_Value : in Item_Type);
function Value_Of (Object : Shared_Data) return Item_Type;
function Initialized (Object : Shared_Data) return Boolean;
private
type Shared_Data is new Boolean; -- Bogus Declaration
end Shared_Data_Generic;-- -------------------------------------------------------------------------
-- CIFO Task identifiers. Used by all the other packages.
-- See CIFO section titled "Task Identifiers".
-- -------------------------------------------------------------------------
package Task_Ids is
-----------------
-- CIFO V3 names:
-----------------
--subtype Task_Id is Tid.Task_Id;
-- Declaration above commented out by JRG on 9/19/91 for
-- Rational Compilation. Replaced with the following decl.
subtype Task_Id is Boolean; -- Bogus Declaration
Task_Id_Error : exception;
function Null_Task return Task_Id;
function Self return Task_Id;
function Master_Task (I : Task_Id := Self) return Task_Id;
function Caller (I : Task_Id := Self) return Task_Id;
function Callable (I : Task_Id := Self) return Boolean;
function Terminated (I : Task_Id := Self) return Boolean;
-----------------
-- CIFO V2 names:
-----------------
generic
type Task_Type is limited private;
function Id_Of (T : Task_Type) return Task_Id;
function Parent (I : Task_Id := Self) return Task_Id;
end Task_Ids;package Implem_Def is
Id_Job_Control : Boolean := True;
Id_Saved_Ids : Boolean := False;
Id_Change_Owner_Restricted : Boolean := True;
Id_No_Truncation : Boolean := True;
Id_Argument_Bytes : constant := 65536; -- EXECARGLEN
Id_Child_Processes : constant := 98; -- (NPROC-2)
Id_Groups : constant := 8; -- NGROUPS
Id_Open_Files : constant := 20; -- USR_NFDS
Id_Link_Limit_Range_Last : constant := 32767; -- LINK_MAX
Id_Input_Line_Limit_Range_Last : constant := 256; -- LINELEN
Id_Input_Queue_Limit_Range_Last : constant := 512; -- (LINELEN*2)
Id_Filename_Limit_Range_Last : constant := 255; -- NAME_MAX
Id_Pathname_Limit_Range_Last : constant := 1024; -- PATH_MAX
Id_Pipe_Limit_Range_Last : constant := 4096; -- PIPESIZE
end Implem_Def;with System;
package Local_Procs is
-- Convert a C string, which is a pointer to a null-terminated
-- character array, into an Ada string:
function C_String_To_Ada (C_String : in System.Address) return String;
end Local_Procs;with System;
with Implem_Def;
package Posix is
-- Symbolic constants
Job_Control : constant Boolean := Implem_Def.Id_Job_Control;
Saved_Ids : constant Boolean := Implem_Def.Id_Saved_Ids;
Change_Owner_Restricted : constant Boolean :=
Implem_Def.Id_Change_Owner_Restricted;
No_Truncation : constant Boolean := Implem_Def.Id_No_Truncation;
Portable_Argument_Bytes : constant := 4096;
Argument_Bytes : constant := Implem_Def.Id_Argument_Bytes;
Portable_Child_Processes : constant := 6;
Child_Processes : constant := Implem_Def.Id_Child_Processes;
Portable_Groups : constant := 0;
Groups : constant := Implem_Def.Id_Groups;
Portable_Open_Files : constant := 16;
Open_Files : constant := Implem_Def.Id_Open_Files;
Portable_Link_Limit : constant := 8;
subtype Link_Limit_Range is
Natural range 0 .. Implem_Def.Id_Link_Limit_Range_Last;
Portable_Input_Line_Limit : constant := 255;
subtype Input_Line_Limit_Range is
Natural range 0 .. Implem_Def.Id_Input_Line_Limit_Range_Last;
Portable_Input_Queue_Limit : constant := 255;
subtype Input_Queue_Limit_Range is
Natural range 0 .. Implem_Def.Id_Input_Queue_Limit_Range_Last;
Portable_Filename_Limit : constant := 14;
subtype Filename_Limit_Range is
Positive range 1 .. Implem_Def.Id_Filename_Limit_Range_Last;
Portable_Pathname_Limit : constant := 255;
subtype Pathname_Limit_Range is
Positive range 1 .. Implem_Def.Id_Pathname_Limit_Range_Last;
Portable_Pipe_Limit : constant := 512;
subtype Pipe_Limit_Range is
Natural -- why NATURAL ??
range 0 .. Implem_Def.Id_Pipe_Limit_Range_Last;
-- Characters and Strings
type Posix_Character is new Character;
-- (' ','0','1','2','3','4','5','6','7','8','9',
-- 'A','B','C','D','E','F','G','H','I','J','K','L','M',
-- 'N','O','P','Q','R','S','T','U','V','W','X','Y','Z',
-- 'a','b','c','d','e','f','g','h','i','j','k','l','m',
-- 'n','o','p','q','r','s','t','u','v','w','x','y','z',
-- '.','_','-','/'
-- @P<other characters are implementation defined>
-- );
type Posix_String is array (Positive range <>) of Posix_Character;
function To_String (Str : Posix_String) return String;
function To_Posix_String (Str : String) return Posix_String;
function To_Posix_String (Addr : System.Address) return Posix_String;
function "&" (L : String; R : Posix_String) return Posix_String;
function "&" (L : Character; R : Posix_String) return Posix_String;
function "&" (L : Posix_String; R : String) return Posix_String;
function "&" (L : Posix_String; R : Character) return Posix_String;
-- these should come for free
-- function "&" (l : POSIX_String; r : POSIX_Character)
-- return POSIX_STRING;
-- function "&" (l :POSIX_Character; r : POSIX_Character)
-- return POSIX_STRING;
function Is_Filename (Str : String) return Boolean;
function Is_Filename (Str : Posix_String) return Boolean;
function Is_Pathname (Str : String) return Boolean;
function Is_Pathname (Str : Posix_String) return Boolean;
function Is_Portable_Filename (Str : String) return Boolean;
function Is_Portable_Filename (Str : Posix_String) return Boolean;
function Is_Portable_Pathname (Str : String) return Boolean;
function Is_Portable_Pathname (Str : Posix_String) return Boolean;
-- String Lists
type Posix_String_List is limited private;
Empty_String_List : constant Posix_String_List;
procedure Make_Empty (List : in out Posix_String_List);
procedure Append (List : in out Posix_String_List;
String : in Posix_String);
generic
with procedure Action (S : in Posix_String);
procedure For_Every_Member (List : in Posix_String_List);
function Length (List : Posix_String_List) return Natural;
function Value (List : Posix_String_List; Index : Natural)
return Posix_String;
-- Exceptions C errno equivalent
Arg_List_Too_Long, -- E2BIG
Bad_Address, -- EFAULT
Bad_File_Descriptor, -- EBADF
Broken_Pipe, -- EPIPE
Directory_Not_Empty, -- ENOTEMPTY
Domain_Error, -- EDOM
Exec_Format_Error, -- ENOEXEC
File_Exists, -- EEXIST
File_Too_Big, -- EFBIG
Filename_Too_Long, -- ENAMETOOLONG
Function_Not_Implemented, -- ENOSYS
Improper_Link, -- EXDEV
Inappropriate_Io_Control_Operation, -- ENOTTY
Input_Output_Error, -- EIO
Interrupted_Operation, -- EINTR
Invalid_Argument, -- EINVAL
Invalid_Seek, -- ESPIPE
Is_A_Directory, -- EISDIR
No_Child_Process, -- ECHILD
No_Locks_Available, -- ENOLCK
No_Space_Left_On_Device, -- ENOSPC
No_Such_Device, -- ENODEV
No_Such_Device_Or_Address, -- ENXIO
No_Such_File_Or_Directory, -- ENOENT
No_Such_Process, -- ESRCH
Not_A_Directory, -- ENOTDIR
Not_Enough_Space, -- ENOMEM
Operation_Not_Permitted, -- EPERM
Permission_Denied, -- EACCES
Read_Only_File_System, -- EROFS
Resource_Busy, -- EBUSY
Resource_Deadlock_Avoided, -- EDEADLK
Resource_Temporarily_Unavailable, -- EAGAIN
Result_Too_Large, -- ERANGE
Too_Many_Links, -- EMLINK
Too_Many_Open_Files, -- EMFILE
Too_Many_Open_Files_In_System -- ENFILE
: exception;
private
type String_Ptr is access Posix_String;
type List_Elem is
record
Current : String_Ptr;
Next : Posix_String_List;
end record;
type Posix_String_List is access List_Elem;
Empty_String_List : constant Posix_String_List := null;
pragma Inline (To_String);
pragma Inline (To_Posix_String);
pragma Inline ("&");
end Posix;package Posix_Current_Exception is
-- The Lynx values for errno, see /usr/include/errno.h
No_Error : constant := 0;
Eperm : constant := 1;
Enoent : constant := 2;
Esrch : constant := 3;
Eintr : constant := 4;
Eio : constant := 5;
Enxio : constant := 6;
E2big : constant := 7;
Enoexec : constant := 8;
Ebadf : constant := 9;
Echild : constant := 10;
Eagain : constant := 11;
Enomem : constant := 12;
Eacces : constant := 13;
Efault : constant := 14;
Enotblk : constant := 15;
Ebusy : constant := 16;
Eexist : constant := 17;
Exdev : constant := 18;
Enodev : constant := 19;
Enotdir : constant := 20;
Eisdir : constant := 21;
Einval : constant := 22;
Enfile : constant := 23;
Emfile : constant := 24;
Enotty : constant := 25;
Etxtbsy : constant := 26;
Efbig : constant := 27;
Enospc : constant := 28;
Espipe : constant := 29;
Erofs : constant := 30;
Emlink : constant := 31;
Epipe : constant := 32;
Edom : constant := 33;
Erange : constant := 34;
Einprogress : constant := 36;
Ealready : constant := 37;
Enotsock : constant := 38;
Edestaddrreq : constant := 39;
Emsgsize : constant := 40;
Eprototype : constant := 41;
Enoprotoopt : constant := 42;
Eprotonosupport : constant := 43;
Esocktnosupport : constant := 44;
Eopnotsupp : constant := 45;
Epfnosupport : constant := 46;
Eafnosupport : constant := 47;
Eaddrinuse : constant := 48;
Eaddrnotavail : constant := 49;
Enetdown : constant := 50;
Enetunreach : constant := 51;
Enetreset : constant := 52;
Econnaborted : constant := 53;
Econnreset : constant := 54;
Enobufs : constant := 55;
Eisconn : constant := 56;
Enotconn : constant := 57;
Eshutdown : constant := 58;
Etoomanyrefs : constant := 59;
Etimedout : constant := 60;
Econnrefused : constant := 61;
Eloop : constant := 62;
Enametoolong : constant := 63;
Ehostdown : constant := 64;
Ehostunreach : constant := 65;
Enotempty : constant := 66;
Eproclim : constant := 67;
Eusers : constant := 68;
Ecanceled : constant := 69;
Edeadlk : constant := 72;
Enotchr : constant := 76;
Ehighb : constant := 80;
Enosys : constant := 99;
Eidrm : constant := 36;
Enomsg : constant := 35;
Enolck : constant := 46;
type Errno is
(No_Exception, Operation_Not_Permitted, -- EPERM
No_Such_File_Or_Directory, -- ENOENT
No_Such_Process, -- ESRCH
Interrupted_Operation, -- EINTR
Input_Output_Error, -- EIO
No_Such_Device_Or_Address, -- ENXIO
Arg_List_Too_Long, -- E2BIG
Exec_Format_Error, -- ENOEXEC
Bad_File_Descriptor, -- EBADF
No_Child_Process, -- ECHILD
Resource_Temporarily_Unavailable, -- EAGAIN or EWOULDBLOCK
Not_Enough_Space, -- ENOMEM
Permission_Denied, -- EACCES
Bad_Address, -- EFAULT
Block_Device_Required, -- ENOTBLK (not in POSIX)
Resource_Busy, -- EBUSY
File_Exists, -- EEXIST
Improper_Link, -- EXDEV
No_Such_Device, -- ENODEV
Not_A_Directory, -- ENOTDIR
Is_A_Directory, -- EISDIR
Invalid_Argument, -- EINVAL
Too_Many_Open_Files_In_System, -- ENFILE
Too_Many_Open_Files, -- EMFILE
Inappropriate_Io_Control_Operation, -- ENOTTY
Text_File_Busy, -- ETXTBSY (not in POSIX)
File_Too_Big, -- EFBIG
No_Space_Left_On_Device, -- ENOSPC
Invalid_Seek, -- ESPIPE
Read_Only_File_System, -- EROFS
Too_Many_Links, -- EMLINK
Broken_Pipe, -- EPIPE
Domain_Error, -- EDOM
Result_Too_Large, -- ERANGE
No_Such_Message, -- ENOMSG (Not in POSIX)
Operation_Now_In_Progress, -- EINPROGRESS (NOT_IN_POSIX)
Operation_Already_In_Progress, -- EALREADY (Not in POSIX)
Socket_Operation_On_Non_Socket, -- ENOTSOCK (Not in POSIX)
Destination_Address_Required, -- EDESTADDRREQ (Not in POSIX)
Message_Too_Long, -- EMSGSIZE (Not in POSIX)
Protocol_Wrong_Type_For_Socket, -- EPROTOTYPE (Not in POSIX)
Protocol_Not_Available, -- ENOPROTOOPT (Not in POSIX)
Protocol_Not_Supported, -- EPROTONOSUPPORT (Not in POSIX)
Socket_Type_Not_Supported, -- ESOCKTNOSUPPORT (Not in POSIX)
Operation_Not_Supported_On_Socket, -- EOPNOTSUPP (Not in POSIX)
No_Locks_Available, -- ENOLCK or EPFNOSUPPORT
Address_Family_Not_Supported_By_Protocol_Family,
-- EAFNOSUPPORT (Not in POSIX)
Address_Already_In_Use, -- EADDRINUSE (Not in POSIX)
Cant_Assign_Requested_Address, -- EADDRNOTAVAIL (Not in POSIX)
Network_Is_Down, -- ENETDOWN (Not in POSIX)
Network_Is_Unreachable, -- ENETUNREACH (Not in POSIX)
Network_Dropped_Connection_On_Reset, -- ENETRESET (Not in POSIX)
Software_Caused_Connection_Abort, -- ECONNABORTED (Not in POSIX)
Connection_Reset_By_Peer, -- ECONNRESET (Not in POSIX)
No_Buffer_Space_Available, -- ENOBUFS (Not in POSIX)
Socket_Is_Already_Connected, -- EISCONN (Not in POSIX)
Socket_Is_Not_Connected, -- ENOTCONN (Not in POSIX)
Cant_Send_After_Socket_Shutdown, -- ESHUTDOWN (Not in POSIX)
Too_Many_References_Cant_Splice, -- ETOOMANYREFS (Not in POSIX)
Connection_Timed_Out, -- ETIMEDOUT (Not in POSIX)
Connection_Refused, -- ECONNREFUSED (Not in POSIX)
Too_Many_Levels_Of_Symbolic_Links, -- ELOOP (Not in POSIX)
Filename_Too_Long, -- ENAMETOOLONG
Host_Is_Down, -- EHOSTDOWN (Not in POSIX)
No_Route_To_Host, -- EHOSTUNREACH (Not in POSIX)
Directory_Not_Empty, -- ENOTEMPTY
Too_Many_Processes, -- EPROCLIM (Not in POSIX)
Too_Many_Users, -- EUSERS (Not in POSIX)
Asynchronous_Operation_Canceled, -- ECANCELED (Not in POSIX)
Resource_Deadlock_Avoided, -- EDEADLK
High_Bit_In_File_Name, -- EHIGHB (Not in POSIX)
Function_Not_Implemented); -- ENOSYS
for Errno use
(No_Exception => No_Error,
Operation_Not_Permitted => Eperm,
No_Such_File_Or_Directory => Enoent,
No_Such_Process => Esrch,
Interrupted_Operation => Eintr,
Input_Output_Error => Eio,
No_Such_Device_Or_Address => Enxio,
Arg_List_Too_Long => E2big,
Exec_Format_Error => Enoexec,
Bad_File_Descriptor => Ebadf,
No_Child_Process => Echild,
Resource_Temporarily_Unavailable => Eagain,
Not_Enough_Space => Enomem,
Permission_Denied => Eacces,
Bad_Address => Efault,
Block_Device_Required => Enotblk,
Resource_Busy => Ebusy,
File_Exists => Eexist,
Improper_Link => Exdev,
No_Such_Device => Enodev,
Not_A_Directory => Enotdir,
Is_A_Directory => Eisdir,
Invalid_Argument => Einval,
Too_Many_Open_Files_In_System => Enfile,
Too_Many_Open_Files => Emfile,
Inappropriate_Io_Control_Operation => Enotty,
Text_File_Busy => Etxtbsy,
File_Too_Big => Efbig,
No_Space_Left_On_Device => Enospc,
Invalid_Seek => Espipe,
Read_Only_File_System => Erofs,
Too_Many_Links => Emlink,
Broken_Pipe => Epipe,
Domain_Error => Edom,
Result_Too_Large => Erange,
No_Such_Message => Enomsg,
Operation_Now_In_Progress => Einprogress,
Operation_Already_In_Progress => Ealready,
Socket_Operation_On_Non_Socket => Enotsock,
Destination_Address_Required => Edestaddrreq,
Message_Too_Long => Emsgsize,
Protocol_Wrong_Type_For_Socket => Eprototype,
Protocol_Not_Available => Enoprotoopt,
Protocol_Not_Supported => Eprotonosupport,
Socket_Type_Not_Supported => Esocktnosupport,
Operation_Not_Supported_On_Socket => Eopnotsupp,
No_Locks_Available => Enolck,
Address_Family_Not_Supported_By_Protocol_Family => Eafnosupport,
Address_Already_In_Use => Eaddrinuse,
Cant_Assign_Requested_Address => Eaddrnotavail,
Network_Is_Down => Enetdown,
Network_Is_Unreachable => Enetunreach,
Network_Dropped_Connection_On_Reset => Enetreset,
Software_Caused_Connection_Abort => Econnaborted,
Connection_Reset_By_Peer => Econnreset,
No_Buffer_Space_Available => Enobufs,
Socket_Is_Already_Connected => Eisconn,
Socket_Is_Not_Connected => Enotconn,
Cant_Send_After_Socket_Shutdown => Eshutdown,
Too_Many_References_Cant_Splice => Etoomanyrefs,
Connection_Timed_Out => Etimedout,
Connection_Refused => Econnrefused,
Too_Many_Levels_Of_Symbolic_Links => Eloop,
Filename_Too_Long => Enametoolong,
Host_Is_Down => Ehostdown,
No_Route_To_Host => Ehostunreach,
Directory_Not_Empty => Enotempty,
Too_Many_Processes => Eproclim,
Too_Many_Users => Eusers,
Asynchronous_Operation_Canceled => Ecanceled,
Resource_Deadlock_Avoided => Edeadlk,
High_Bit_In_File_Name => Ehighb,
Function_Not_Implemented => Enosys);
-- Returns the ERRNO value for the last POSIX call in the current task:
function Get_Errno return Errno;
-- To print it, use ERRNO'IMAGE
end Posix_Current_Exception;with Posix, Posix_Permissions, Posix_Process_Identification, Calendar;
package Posix_Files is
-- Operations to create files in the file system
procedure Create_File (Filename : in Posix.Posix_String;
Permission : in Posix_Permissions.Permission_Set);
procedure Create_Directory
(Directory_Name : in Posix.Posix_String;
Permission : in Posix_Permissions.Permission_Set);
procedure Create_Fifo_Special_File
(Filename : in Posix.Posix_String;
Permission : in Posix_Permissions.Permission_Set);
-- Operations to remove files from the file system
procedure Unlink (Filename : in Posix.Posix_String);
procedure Remove_Directory (Filename : in Posix.Posix_String);
-- Predicates on files in the file system
function Is_File (Filename : Posix.Posix_String) return Boolean;
function Is_Directory (Filename : Posix.Posix_String) return Boolean;
function Is_Fifo_Special_File
(Filename : Posix.Posix_String) return Boolean;
-- Operations to modify file pathnames
procedure Link (Filename : in Posix.Posix_String;
New_Filename : in Posix.Posix_String);
procedure Rename (Filename : in Posix.Posix_String;
New_Filename : in Posix.Posix_String);
-- Operation to iterate over files in a directory
generic
with procedure Action (Pathname : in Posix.Posix_String;
Quit : in out Boolean);
procedure For_Every_Directory_Entry (Dir : in Posix.Posix_String);
-- Operations to update file status information
procedure Change_Owner_And_Group
(Filename : in Posix.Posix_String;
Owner : in Posix_Process_Identification.User_Id;
Group : in Posix_Process_Identification.Group_Id);
procedure Change_Permissions
(Filename : in Posix.Posix_String;
Permission : in Posix_Permissions.Permission_Set);
type File_Times_Record is
record
Access_Time : Calendar.Time;
Modification_Time : Calendar.Time;
end record;
-- IMPORTANT NOTE : Due to the limits on the magnitude of a 32 bit
-- integer (i.e. -2**31 .. 2**31-1), the range of times that can be
-- specified for the time of a file is limited. More specifically, the
-- time should lie between 01:45:52, December 15, 1901 and 03:14:07,
-- January 17, 2038. Using times outside these limits may produce
-- unintended results (exceptions or wraparound dates). Staying within
-- the limits above will produce correct results in any time zone.
--
-- ALSO NOTE : The time set for the file is always local time.
procedure Set_File_Times (Filename : in Posix.Posix_String;
Time : in File_Times_Record);
procedure Set_File_Times_To_Current_Time (Filename : in Posix.Posix_String);
-- Operations to determine file accessibility
type Access_Modes is (Read_Ok, Write_Ok, Execute_Ok, File_Exists);
type Access_Mode_Set is array (Access_Modes) of Boolean;
-- In the two routines below, specifying FALSE for any of the access modes
-- means that you don't care about that permission, not that you want to
-- check if it is OFF. For example, if you call function ACCESSIBLE with
-- all of the ACCESS_MODES FALSE, the returned value will always be TRUE,
-- regardless of whether the file exists or what its permissions are. If
-- you wish to verify that a particular permission is OFF, check to see
-- if it is ON and then take the opposite of the returned value.
function Accessible (Filename : in Posix.Posix_String;
Permissions : in Access_Mode_Set) return Boolean;
procedure Accessible (Filename : in Posix.Posix_String;
Permissions : in Access_Mode_Set);
end Posix_Files;with System, Calendar;
with Posix, Posix_Permissions, Posix_Process_Identification, Posix_Io;
-- with Interface_Types; -- implementation defined
package Posix_File_Status is
type Status is private;
-- Operations to obtain file status
function File_Status (Filename : Posix.Posix_String) return Status;
function File_Status
(File_Descriptor : Posix_Io.File_Descriptor) return Status;
-- Operations to get information from status
type File_Serial_Number is range 0 .. 32767; -- 2**15-1
type Device_Serial_Number is range 0 .. 32767; -- 2**15-1
type Links is range 0 .. Posix.Link_Limit_Range'Last;
function Permission_Set_Of (File_Status : Status)
return Posix_Permissions.Permission_Set;
function File_Serial_Number_Of
(File_Status : Status) return File_Serial_Number;
function Device_Serial_Number_Of
(File_Status : Status) return Device_Serial_Number;
function Link_Count_Of (File_Status : Status) return Links;
function Owner_Of (File_Status : Status)
return Posix_Process_Identification.User_Id;
function Group_Of (File_Status : Status)
return Posix_Process_Identification.Group_Id;
function Io_Unit_Size_Of (File_Status : Status) return Posix_Io.Io_Count;
function Last_Access_Time_Of (File_Status : Status) return Calendar.Time;
function Last_Modification_Time_Of
(File_Status : Status) return Calendar.Time;
function Last_Status_Change_Time_Of
(File_Status : Status) return Calendar.Time;
function Is_Directory (File_Status : Status) return Boolean;
function Is_Character_Special_File (File_Status : Status) return Boolean;
function Is_Block_Special_File (File_Status : Status) return Boolean;
function Is_Regular_File (File_Status : Status) return Boolean;
function Is_Fifo (File_Status : Status) return Boolean;
private
type Status is new Boolean; -- RCF MOD
end Posix_File_Status;with Posix, Posix_Permissions, Posix_Process_Identification;
package Posix_Io is
-- common type declarations
type File_Descriptor is range 0 .. Posix.Open_Files;
Standard_Input : constant File_Descriptor := 0;
Standard_Output : constant File_Descriptor := 1;
Standard_Error : constant File_Descriptor := 2;
type Io_Offset is range -2 ** 31 .. 2 ** 31 - 1; -- implementation defined
type File_Mode is (Read_Only, Write_Only, Read_Write, Blocking, Append,
Close_On_Exec, Truncate, Exclusive, Control_Tty);
type File_Mode_Set is array (File_Mode range <>) of Boolean;
subtype File_Control_Mode is File_Mode range Read_Only .. Close_On_Exec;
subtype Settable_File_Control_Mode is
File_Control_Mode range Blocking .. Close_On_Exec;
subtype File_Control_Mode_Set is File_Mode_Set (File_Control_Mode);
subtype Settable_File_Control_Mode_Set is
File_Mode_Set (Settable_File_Control_Mode);
subtype Io_Count is Io_Offset range 0 .. Io_Offset'Last;
subtype Positive_Io_Count is Io_Count range 1 .. Io_Offset'Last;
subtype Open_Mode is File_Mode range Read_Only .. Read_Write;
type Position is (From_Beginning, From_Current_Position, From_End_Of_File);
-- File open, open_or_create, create, Close, duplicate and pipe
function Open (Name : Posix.Posix_String;
Mode : Open_Mode;
Blocking : Boolean := True;
Append : Boolean := False;
Truncate : Boolean := False;
Control_Tty : Boolean := True) return File_Descriptor;
function Open_Or_Create
(Name : Posix.Posix_String;
Mode : Open_Mode;
Permissions : Posix_Permissions.Permission_Set;
Blocking : Boolean := True;
Append : Boolean := False;
Truncate : Boolean := False;
Exclusive : Boolean := False;
Control_Tty : Boolean := True) return File_Descriptor;
procedure Close (File : in File_Descriptor);
function Duplicate (File : File_Descriptor) return File_Descriptor;
function Duplicate (File1 : File_Descriptor; File2 : File_Descriptor)
return File_Descriptor;
procedure Pipe (Read_End : out File_Descriptor;
Write_End : out File_Descriptor);
-- Read and Write
-------------------------------
-- in P1003.5 November 1989 :
-- PIPE_BUFFER_SIZE : constant := POSIX.Pipe_Limit_Range'FIRST;
-- but we must write:
-------------------------------
Pipe_Buffer_Size : constant Natural := Posix.Pipe_Limit_Range'Last;
type Io_Unit is range -128 .. 127; -- Implementation defined
for Io_Unit'Size use 8; -- Implementation defined
type Io_Buffer is array (Positive_Io_Count range <>) of Io_Unit;
procedure Read (File : in File_Descriptor;
Buffer : out Io_Buffer;
Last : out Io_Count);
procedure Write (File : in File_Descriptor;
Buffer : in Io_Buffer;
Last : out Io_Count);
generic
type T is private;
procedure Generic_Read ( -- compiler bug??
File : in File_Descriptor;
Item : out T);
generic
type T is private;
procedure Generic_Write ( -- compiler bug??
File : in File_Descriptor;
Item : in T);
-- Seek, File_size, File_Position
procedure Seek (File : in File_Descriptor;
Offset : in Io_Offset;
Whence : in Position := From_Beginning);
function File_Size (File : File_Descriptor) return Io_Count;
function File_Position (File : File_Descriptor) return Io_Count;
-- Terminal device operations
function Is_A_Terminal_Device (File : File_Descriptor) return Boolean;
function Get_Terminal_Device_Name
(File : File_Descriptor) return Posix.Posix_String;
-- File Control operations
function Get_File_Control (File : File_Descriptor)
return File_Control_Mode_Set;
procedure Set_File_Control (File : in File_Descriptor;
Modes : in Settable_File_Control_Mode_Set);
end Posix_Io;package Posix_Permissions is
type Permissions is (Owner_Read, Owner_Write, Owner_Execute, Group_Read,
Group_Write, Group_Execute, Others_Read, Others_Write,
Others_Execute, Set_Group_Id, Set_User_Id);
subtype Access_Permissions is Permissions
range Owner_Read .. Others_Execute;
subtype Owner_Permissions is Permissions range Owner_Read .. Owner_Execute;
subtype Group_Permissions is Permissions range Group_Read .. Group_Execute;
subtype Others_Permissions is Permissions
range Others_Read .. Others_Execute;
subtype Set_Id_Permissions is Permissions range Set_Group_Id .. Set_User_Id;
type Unconstrained_Permission_Set is
array (Permissions range <>) of Boolean;
subtype Permission_Set is Unconstrained_Permission_Set (Permissions);
subtype Access_Permission_Set is
Unconstrained_Permission_Set (Access_Permissions);
-- POSIX Permission-oriented operations --
function Allowed_Process_Permissions return Access_Permission_Set;
procedure Set_Allowed_Process_Permissions
(New_Permissions : in Access_Permission_Set;
Old_Permissions : out Access_Permission_Set);
end Posix_Permissions;with Posix;
package Posix_Process_Environment is
-- Process Arguments
function Command return Posix.Posix_String;
function Parameter_List return Posix.Posix_String_List;
-- Environment Variables
type Environment is limited private;
procedure Get_Current_Environment (Env : in out Environment);
function Environment_Value_Of
(Name : in Posix.Posix_String; Env : in Environment)
return Posix.Posix_String;
function Environment_Value_Of
(Name : in Posix.Posix_String) return Posix.Posix_String;
function Environment_Variable_Defined
(Name : in Posix.Posix_String; Env : in Environment)
return Boolean;
function Environment_Variable_Defined
(Name : in Posix.Posix_String) return Boolean;
procedure Clear_Environment (Env : in out Environment);
procedure Clear_Environment;
procedure Set_Environment_Value
(Name : in Posix.Posix_String; Value : in Posix.Posix_String);
procedure Set_Environment_Value (Name : in Posix.Posix_String;
Value : in Posix.Posix_String;
Env : in out Environment);
procedure Unset_Environment_Value (Name : in Posix.Posix_String);
procedure Unset_Environment_Value
(Name : in Posix.Posix_String; Env : in out Environment);
function Length (Env : Environment) return Natural;
function Length return Natural;
generic
with procedure Action (Name : in Posix.Posix_String;
Value : in Posix.Posix_String);
procedure For_Every_Environment_Variable (Env : in Environment);
generic
with procedure Action (Name : in Posix.Posix_String;
Value : in Posix.Posix_String);
procedure For_Every_Current_Environment_Variable;
Undefined_Environment_Variable : exception;
-- Process Working Directory
procedure Change_Working_Directory (Directory_Name : Posix.Posix_String);
function Get_Current_Working_Directory return Posix.Posix_String;
private
type Environment is new Boolean; -- RCF MOD
end Posix_Process_Environment;with Posix;
-- Commented out for RCI Customization
-- with Interface_Types; -- implementation defined
package Posix_Process_Identification is
-- Process Identification Operations
type Process_Id is private;
-- Null_Process_Id : constant Process_Id; -- RCF MOD
function Null_Process_Id return Process_Id; -- RCF MOD
function Get_Process_Id return Process_Id;
function Get_Parent_Process_Id return Process_Id;
function Image (Id : Process_Id) return String;
function Value (Str : String) return Process_Id;
-- Process Groups
function Get_Process_Group_Id return Process_Id;
procedure Create_Session (Session_Leader : out Process_Id);
procedure Set_Process_Group_Id
(Process : in Process_Id := Get_Process_Id;
Process_Group : in Process_Id := Get_Process_Group_Id);
-- User IDs
type User_Id is private;
function Get_Real_User_Id return User_Id;
function Get_Effective_User_Id return User_Id;
procedure Set_User_Id (Id : in User_Id);
function Get_Control_Terminal_Login_Name return Posix.Posix_String;
function Get_Effective_User_Login_Name return Posix.Posix_String;
function Image (Id : User_Id) return String;
function Value (Str : String) return User_Id;
-- Group IDs
type Group_Id is private;
function Get_Real_Group_Id return Group_Id;
function Get_Effective_Group_Id return Group_Id;
procedure Set_Group_Id (Id : in Group_Id);
type Group_Member_List is array (Positive range <>) of Group_Id;
function Get_Groups return Group_Member_List;
function Image (Id : Group_Id) return String;
function Value (Str : String) return Group_Id;
private
type Process_Id is new Boolean;
type User_Id is new Boolean;
type Group_Id is new Boolean;
end Posix_Process_Identification;with Posix_Process_Environment, Posix_Io, Posix_Permissions,
Posix_Process_Identification, Posix_Signals, Posix;
-- with Interface_Types; -- implementation defined
package Posix_Process_Primitives is
-- Process Template
type Process_Template is private;
function Current_Process_Template return Process_Template;
procedure Close_Template (Template : in out Process_Template);
procedure Set_Keep_Effective_Ids (Template : in out Process_Template);
procedure Set_Signal_Mask (Template : in out Process_Template;
Mask : in Posix_Signals.Signal_Set);
procedure Set_File_Action_To_Close (Template : in out Process_Template;
File : in Posix_Io.File_Descriptor);
procedure Set_File_Action_To_Open (Template : in out Process_Template;
File : in Posix_Io.File_Descriptor;
Name : in Posix.Posix_String;
Mode : in Posix_Io.Open_Mode;
Blocking : in Boolean := True;
Append : in Boolean := False;
Truncate : in Boolean := False;
Control_Tty : in Boolean := True);
procedure Set_File_Action_To_Duplicate
(Template : in out Process_Template;
File : in Posix_Io.File_Descriptor;
From_File : in Posix_Io.File_Descriptor);
-- Process Creation
function Start_Process (Pathname : in Posix.Posix_String;
Template : in Process_Template :=
Current_Process_Template;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List;
Env_List : in Posix_Process_Environment.Environment)
return Posix_Process_Identification.Process_Id;
function Start_Process (Pathname : in Posix.Posix_String;
Template : in Process_Template :=
Current_Process_Template;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List)
return Posix_Process_Identification.Process_Id;
function Start_Process_Search
(Filename : in Posix.Posix_String;
Template : in Process_Template := Current_Process_Template;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List;
Env_List : in Posix_Process_Environment.Environment)
return Posix_Process_Identification.Process_Id;
function Start_Process_Search
(Filename : in Posix.Posix_String;
Template : in Process_Template := Current_Process_Template;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List)
return Posix_Process_Identification.Process_Id;
-- Process Termination
type Exit_Status is range 0 .. 2 ** 8 - 1;
Normal_Exit : constant Exit_Status := 0;
Unhandled_Exception_Exit : constant Exit_Status := 42;
procedure Exit_Process (Status : in Exit_Status := Normal_Exit);
-- Wait for Process Termination
type Termination_Status is private;
function Process_Id_Of (Status : in Termination_Status)
return Posix_Process_Identification.Process_Id;
function Exit_Status_Of (Status : in Termination_Status) return Exit_Status;
function Terminate_Signal_Of
(Status : in Termination_Status) return Posix_Signals.Signal;
function Stop_Signal_Of (Status : in Termination_Status)
return Posix_Signals.Signal;
function Exited_Normally (Status : in Termination_Status) return Boolean;
function Terminated_By_Signal
(Status : in Termination_Status) return Boolean;
function Stopped_By_Signal (Status : in Termination_Status) return Boolean;
procedure Wait_For_Child
(Status : out Termination_Status;
Child : in Posix_Process_Identification.Process_Id :=
Posix_Process_Identification.Null_Process_Id;
Block : in Boolean := True;
Trace_Stopped : in Boolean := True);
procedure Wait_For_Process_Group
(Status : out Termination_Status;
Process_Group : in Posix_Process_Identification.Process_Id :=
Posix_Process_Identification.Null_Process_Id;
Block : in Boolean := True;
Trace_Stopped : in Boolean := True);
private
type Process_Template is new Boolean;
type Termination_Status is new Boolean;
end Posix_Process_Primitives;with Posix_Process_Identification, Unchecked_Conversion,
-- POSIX; in draft but not used
System;
--with Interface_Types;
--use Interface_Types;
package Posix_Signals is
-- Standard Signals
type Signal is
(Signal_Null,
-- required signals
Signal_Abort, Signal_Alarm, Signal_Floating_Point_Error, Signal_Hangup,
Signal_Illegal_Instruction, Signal_Interrupt, Signal_Kill,
Signal_Pipe_Write, Signal_Quit, Signal_Segment_Violation,
Signal_Terminate, Signal_User_1, Signal_User_2,
-- job control signals:
Signal_Child, Signal_Continue, Signal_Stop, Signal_Terminal_Stop,
Signal_Terminal_Input, Signal_Terminal_Output);
-- Signal Handler References
-- type LONG_INTEGER is new INTEGER; -- On 386
type Int is new Integer; -- BOGUS DECLARATION
function Convert_Signal is new Unchecked_Conversion (Int, System.Address);
Signal_Abort_Ref : constant System.Address := Convert_Signal (6);
-- Signal_Alarm intentionally omitted.
-- Signal_Floating_Point_Error intentionally omitted.
Signal_Hangup_Ref : constant System.Address := Convert_Signal (1);
-- Signal_Illegal_Instruction intentionally omitted.
Signal_Interrupt_Ref : constant System.Address := Convert_Signal (2);
-- Signal_Kill intentionally omitted.
Signal_Pipe_Write_Ref : constant System.Address := Convert_Signal (13);
Signal_Quit_Ref : constant System.Address := Convert_Signal (3);
-- Signal_Segment_Violation intentionally omitted.
Signal_Terminate_Ref : constant System.Address := Convert_Signal (15);
Signal_User_1_Ref : constant System.Address := Convert_Signal (30);
Signal_User_2_Ref : constant System.Address := Convert_Signal (31);
-- job control signals:
Signal_Child_Ref : constant System.Address := Convert_Signal (20);
Signal_Continue_Ref : constant System.Address := Convert_Signal (19);
-- Signal_Stop intentionally omitted.
Signal_Terminal_Stop_Ref : constant System.Address := Convert_Signal (18);
Signal_Terminal_Input_Ref : constant System.Address := Convert_Signal (21);
Signal_Terminal_Output_Ref : constant System.Address := Convert_Signal (22);
-- Send a Signal
procedure Send_Process
(Process : in Posix_Process_Identification.Process_Id;
Sig : in Signal);
procedure Send_Group (Group : in Posix_Process_Identification.Process_Id;
Sig : in Signal);
-- Signal Sets
type Signal_Set is private;
Empty_Set : constant Signal_Set;
Full_Set : constant Signal_Set;
procedure Add (Set : in out Signal_Set; Sig : in Signal);
procedure Delete (Set : in out Signal_Set; Sig : in Signal);
function Is_Member (Set : in Signal_Set; Sig : in Signal) return Boolean;
-- Examine and Change Signal Mask
procedure Get_And_Install (New_Mask : in Signal_Set;
Old_Mask : out Signal_Set);
procedure Get_And_Add (New_Mask : in Signal_Set; Old_Mask : out Signal_Set);
procedure Get_And_Subtract (New_Mask : in Signal_Set;
Old_Mask : out Signal_Set);
-- Ignore Signals
procedure Disable (Sig : in Signal);
procedure Enable (Sig : in Signal);
-- Control Delivery of Signal_Child Signal
procedure Send_Signal_Child_On_Stop (Enable : in Boolean := True);
-- Examine Pending Signals
function Pending_Signals return Signal_Set;
private
type Signal_Set is new Boolean;
Empty_Set : constant Signal_Set := True;
Full_Set : constant Signal_Set := True;
end Posix_Signals;with Posix;
with Posix_Process_Environment, Posix_Process_Identification;
package Posix_Unsafe_Process_Primitives is
-- Process Creation
function Fork return Posix_Process_Identification.Process_Id;
-- File Execution
procedure Exec (Pathname : in Posix.Posix_String;
Command : in Posix.Posix_String;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List;
Env_List : in Posix_Process_Environment.Environment);
procedure Exec (Pathname : in Posix.Posix_String;
Command : in Posix.Posix_String;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List);
procedure Exec_Search (Filename : in Posix.Posix_String;
Command : in Posix.Posix_String;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List;
Env_List : in Posix_Process_Environment.Environment);
procedure Exec_Search (Filename : in Posix.Posix_String;
Command : in Posix.Posix_String;
Parameter_List : in Posix.Posix_String_List :=
Posix.Empty_String_List);
end Posix_Unsafe_Process_Primitives;*** 535 ***
!RC.MAIN_PROGRAMS.REV6_WORKING.UNITS.RELEASES.[!TARGETS.I386_UNIX_ALS_XT,!TARGETS.IMPLEMENTATION.RELEASE_I386_UNIX_ALS_XT_2_0_2.INSTALL_ACTIVITY]
!TARGETS.I386_UNIX_ALS_XT
W||| 9/02/92 18:13:10|WORLD|||
ANETWORK_PUBLIC=>RCOD|DNETWORK_PUBLIC=>RW|TI386_UNIX_ALS_XT|
!TARGETS.I386_UNIX_ALS_XT.IO
N||| 9/02/92 18:16:16|DIRECTORY|||
!TARGETS.I386_UNIX_ALS_XT.IO.SWITCHES
H||| 3/02/92 18:50:08|SWITCH||1|
ANETWORK_PUBLIC=>RW|
Rci.Sparc_Sun_Xt_Elaborate
""
Semantics.Sm_Assign_Trace
FALSE
Rci.Sparc_Sun_Xt_Recompile_Instantiation
""
Format.Keyword_Case
LOWER
Rci.Vax_Vms_Dec_Xt_Noexecutable
FALSE
Rci.Vax_Vms_Dec_Xt_Nomain
FALSE
R1000_Cg.Epsilon_Code_Segments
FALSE
R1000_Cg.Elab_Order_Listing
FALSE
R1000_Cg.Seg_Listing
FALSE
R1000_Cg.Asm_Listing
FALSE
Rci.I386_Unix_Als_Xt_User_Set_Family_Name
""
Rci.I386_Unix_Als_Xt_Stack_Task_Size
""
Rci.I386_Unix_Als_Xt_Improve_Calls
""
Semantics.Subsystem_Interface
FALSE
Ftp.Auto_Login
FALSE
R1000_Cg.Disable_Class3_Assertions
FALSE
R1000_Cg.Disable_Class2_Assertions
FALSE
R1000_Cg.Disable_Class1_Assertions
FALSE
Rci.Sparc_Sun_Xt_Apply_Suppress
FALSE
Parser.Configuration
()
Rci.Vax_Vms_Dec_Xt_List
FALSE
Ftp.Account
""
Rci.I386_Unix_Als_Xt_Get_Lnk_File
FALSE
Rci.I386_Unix_Als_Xt_Stack_Object_Size
""
Semantics.Sm_Type_Eq
FALSE
Semantics.Flag_Inevitable_Exceptions
FALSE
R1000_Cg.Option_14
FALSE
Rci.Linker_Post_Options
""
Design.Phase
<None>
R1000_Cg.Option_15
FALSE
Ftp.Send_Port_Enabled
TRUE
Semantics.Drop_Minor_Errors
FALSE
Semantics.Ignore_Cdb
FALSE
Rci.Vax_Vms_Dec_Xt_Brief
FALSE
R1000_Cg.Enable_Kernel_Debugger
FALSE
R1000_Cg.Reclaim_Space
TRUE
Design.Options
""
Semantics.Sm_Attr_Trace
FALSE
Format.Wrap_Indentation
16
R1000_Cg.Ignore_Fixed_Module_Names
FALSE
Rci.Sparc_Sun_Xt_Invoke_Preprocessor
FALSE
Directory.Create_Subprogram_Specs
TRUE
Rci.Sparc_Sun_Xt_Timing
FALSE
Rci.Sparc_Sun_Xt_Dependencies_Only
FALSE
Rci.I386_Unix_Als_Xt_Stack_Main_Size
""
Rci.Sparc_Sun_Xt_Dependent_Files
FALSE
R1000_Cg.Option_13
FALSE
Rci.I386_Unix_Als_Xt_Heap_Initial_Size
""
Rci.I386_Unix_Als_Xt_Display_Show
"all"
Semantics.Reject_Inevitable_Exceptions
FALSE
Rci.Vax_Vms_Dec_Xt_Show
""
Rci.Vax_Vms_Dec_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Improve_Reduction
""
Rci.Vax_Vms_Dec_Xt_Full
FALSE
Rci.I386_Unix_Als_Xt_Heap_Increment_Size
""
Rci.Compiler_Pre_Options
""
Semantics.Sm_Agg_Trace
FALSE
R1000_Cg.Loader_46
FALSE
R1000_Cg.Epsilon_Mirrors
FALSE
Rci.Optimize_Download
TRUE
R1000_Cg.Loader_47
FALSE
Rci.I386_Unix_Als_Xt_Get_Binder_Listing
TRUE
R1000_Cg.Loader_44
FALSE
Directory.Require_Internal_Links
TRUE
Rci.Host_Only
FALSE
Format.Minor_Indentation
4
Format.Major_Indentation
4
R1000_Cg.Loader_45
FALSE
Rci.I386_Unix_Als_Xt_Default_Machine
""
Rci.Compiler_Post_Options
""
Ftp.Transfer_Mode
NIL
Semantics.Sm_Range_Trace
FALSE
Format.Statement_Indentation
3
R1000_Cg.Loader_42
FALSE
Rci.I386_Unix_Als_Xt_Keep_Debug
""
Rci.I386_Unix_Als_Xt_Run_Time_Checks
""
Format.Consistent_Breaking
1
Format.Alignment_Threshold
0
Ftp.Password
""
R1000_Cg.Debug_View_Level
0
R1000_Cg.Loader_43
FALSE
R1000_Cg.Check_Compatibility
TRUE
Rci.Sparc_Sun_Xt_Show_Tool_Name_Only
FALSE
Rci.Vax_Vms_Dec_Xt_Map
FALSE
Rci.Auto_Transfer
FALSE
Directory.Create_Internal_Links
TRUE
R1000_Cg.Module_Name_Bias
()
R1000_Cg.Loader_41
FALSE
Format.Comment_Column
1
Format.Id_Case
CAPITALIZED
Rci.Sparc_Sun_Xt_Main
""
Ftp.Username
""
Semantics.Ignore_Rep_Specs
FALSE
R1000_Cg.Integer_Option_07
0
R1000_Cg.Page_Limit
8000
R1000_Cg.Block_Inlining
FALSE
Rci.Sparc_Sun_Xt_Error_Listing
FALSE
Rci.I386_Unix_Als_Xt_Get_Executable_File
FALSE
Rci.I386_Unix_Als_Xt_Shared_Memory_Size
""
Rci.Operation_Mode
""
Rci.Vax_Vms_Dec_Xt_Optimize
"(NONE)"
Ftp.Remote_Machine
""
Rci.Sparc_Sun_Xt_Executable_Output
""
Rci.Sparc_Sun_Xt_Error_Output
FALSE
Rci.Sparc_Sun_Xt_Define_Preprocessor_Value
""
Semantics.Ignore_Unsupported_Rep_Specs
FALSE
R1000_Cg.Omit_Break_Optionals
FALSE
Format.Number_Case
UPPER
R1000_Cg.Branch_Table_Density
0
Rci.Sparc_Sun_Xt_Suppress_Warnings
FALSE
Rci.Vax_Vms_Dec_Xt_Default_Roof
""
R1000_Cg.Unfixed_Module_Name_Keys
()
R1000_Cg.Special_39
FALSE
R1000_Cg.Statistics
FALSE
Format.Statement_Length
35
Rci.Vax_Vms_Dec_Xt_Nocheck
FALSE
R1000_Cg.Spare_49
FALSE
R1000_Cg.Enable_Environment_Debugger
FALSE
Rci.Vax_Vms_Dec_Xt_Ldebug
FALSE
Rci.Vax_Vms_Dec_Xt_Nodebug
FALSE
Publisher.Options
""
R1000_Cg.Spare_48
FALSE
R1000_Cg.Vpids_Go_Native
FALSE
R1000_Cg.Retain_Delta1_Compatibility
TRUE
R1000_Cg.Debug_Option_21
FALSE
R1000_Cg.Full_Debugging
FALSE
Ftp.Prompt_For_Account
FALSE
R1000_Cg.Spare_55
FALSE
R1000_Cg.Suppress_Elaboration_Checks
FALSE
R1000_Cg.Debug_Option_22
FALSE
Rci.Sparc_Sun_Xt_Debug_Overflow
FALSE
Rci.I386_Unix_Als_Xt_Default_Roof
""
Ftp.Remote_Roof
""
R1000_Cg.Spare_54
FALSE
R1000_Cg.Wire_Code_Segments
FALSE
R1000_Cg.Debug_Option_23
FALSE
Rci.I386_Unix_Als_Xt_Display_Map_Data
""
Semantics.Ignore_Minor_Errors
FALSE
R1000_Cg.Package_Integration
FALSE
Rci.I386_Unix_Als_Xt_Display_Text
"yes"
Rci.Trace_Command_Output
FALSE
Rci.Linker_Pre_Options
""
Rci.Vax_Vms_Dec_Xt_Check
FALSE
Rci.Sparc_Sun_Xt_Default_Roof
""
R1000_Cg.Tos_Relative_Load_Limit
3
R1000_Cg.Debug_View_Layer
128
R1000_Cg.Epsilon_Debug_Tables
FALSE
Semantics.Closed_Private_Part
FALSE
Semantics.Sm_Match_Trace
FALSE
R1000_Cg.Auto_Integration
FALSE
R1000_Cg.Enable_Deallocation
FALSE
R1000_Cg.Output_06
FALSE
Rci.Remote_Library
""
R1000_Cg.Module_Name_Bias_Keys
()
R1000_Cg.Output_07
FALSE
Rci.I386_Unix_Als_Xt_Get_Cui_File
FALSE
Semantics.Reject_Bad_Lrm_Pragmas
FALSE
Semantics.Limit_Semantic_Messages
200
R1000_Cg.Optimization_31
FALSE
Rci.Sparc_Sun_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Stack_Trace_History
""
Ftp.Transfer_Type
NIL
Rci.Sparc_Sun_Xt_Optimization
""
Rci.Sparc_Sun_Xt_Keep_Intermediate
FALSE
Semantics.Reject_Statement_Prompts
FALSE
Semantics.Ignore_Invalid_Rep_Specs
FALSE
Rci.Vax_Vms_Dec_Xt_Cross_Ref
FALSE
R1000_Cg.Delta1_Code_View_Compatibility
FALSE
Rci.I386_Unix_Als_Xt_Get_Compiler_Listing
TRUE
Rci.I386_Unix_Als_Xt_Display_Assembly
""
Semantics.Sm_Exp_Trace
FALSE
R1000_Cg.Spare_51
FALSE
R1000_Cg.Spare_50
FALSE
R1000_Cg.Subprogram_Inlining
FALSE
R1000_Cg.Debug_Listing
FALSE
Rci.Sparc_Sun_Xt_Archive_File_Name
""
Semantics.Sm_Call_Trace
FALSE
Ftp.Prompt_For_Password
FALSE
R1000_Cg.Spare_53
FALSE
R1000_Cg.Suppress_Constraint_Checks
FALSE
Rci.Sparc_Sun_Xt_Verbose
FALSE
Semantics.Reject_Bad_Rational_Pragmas
FALSE
R1000_Cg.Spare_52
FALSE
Rci.I386_Unix_Als_Xt_Improve_Expressions
""
Semantics.Sm_Solve_Trace
FALSE
Ftp.Remote_Directory
""
Ftp.Remote_Type
""
Semantics.Ignore_Interface_Pragmas
FALSE
Semantics.Reject_Undefined_Pragmas
FALSE
Rci.Vax_Vms_Dec_Xt_Debug
""
R1000_Cg.Binary_Search_Size
0
R1000_Cg.Auto_Inlining
FALSE
Format.Line_Length
80
Rci.Sparc_Sun_Xt_Dependent_Units
FALSE
Ftp.Transfer_Structure
NIL
Rci.Vax_Vms_Dec_Xt_Upload_Exe
FALSE
R1000_Cg.Code_Segment_Size
0
R1000_Cg.Terminal_Echo
FALSE
!TARGETS.I386_UNIX_ALS_XT.IO
K
!TARGETS.I386_UNIX_ALS_XT.IO.SWITCHES
!TARGETS.I386_UNIX_ALS_XT.IO.BASIC_IO'SPEC
V|-3475|4| 5/10/90 12:39:57|PACKAGE_SPEC||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.IO.DIRECT_IO'SPEC
V3475|-2284|4| 8/21/90 13:00:24|GENERIC_PACKAGE||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.IO.IO_EXCEPTIONS'SPEC
V5759|-273|4| 5/07/90 14:57:13|PACKAGE_SPEC||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.IO.SEQUENTIAL_IO'SPEC
V6032|-1902|4| 5/07/90 15:51:22|GENERIC_PACKAGE||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.IO.TEXT_IO'SPEC
V7934|-9116|4|10/22/91 09:03:14|PACKAGE_SPEC||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.LRM
N||| 9/02/92 18:18:02|DIRECTORY|||
!TARGETS.I386_UNIX_ALS_XT.LRM.SWITCHES
H||| 8/13/92 17:21:44|SWITCH||1|
ANETWORK_PUBLIC=>RW|
Rci.Sparc_Sun_Xt_Elaborate
""
Semantics.Sm_Assign_Trace
FALSE
Rci.Sparc_Sun_Xt_Recompile_Instantiation
""
Format.Keyword_Case
LOWER
Rci.Vax_Vms_Dec_Xt_Noexecutable
FALSE
Rci.Vax_Vms_Dec_Xt_Nomain
FALSE
R1000_Cg.Epsilon_Code_Segments
FALSE
R1000_Cg.Elab_Order_Listing
FALSE
R1000_Cg.Seg_Listing
FALSE
R1000_Cg.Asm_Listing
FALSE
Rci.I386_Unix_Als_Xt_User_Set_Family_Name
""
Rci.I386_Unix_Als_Xt_Stack_Task_Size
""
Rci.I386_Unix_Als_Xt_Improve_Calls
""
Semantics.Subsystem_Interface
FALSE
Ftp.Auto_Login
FALSE
R1000_Cg.Disable_Class3_Assertions
FALSE
R1000_Cg.Disable_Class2_Assertions
FALSE
R1000_Cg.Disable_Class1_Assertions
FALSE
Rci.Sparc_Sun_Xt_Apply_Suppress
FALSE
Parser.Configuration
()
Rci.Vax_Vms_Dec_Xt_List
FALSE
Ftp.Account
""
Rci.I386_Unix_Als_Xt_Get_Lnk_File
FALSE
Rci.I386_Unix_Als_Xt_Stack_Object_Size
""
Semantics.Sm_Type_Eq
FALSE
Semantics.Flag_Inevitable_Exceptions
FALSE
R1000_Cg.Option_14
FALSE
Rci.Linker_Post_Options
""
Design.Phase
<None>
R1000_Cg.Option_15
FALSE
Ftp.Send_Port_Enabled
TRUE
Semantics.Drop_Minor_Errors
FALSE
Semantics.Ignore_Cdb
FALSE
Rci.Vax_Vms_Dec_Xt_Brief
FALSE
R1000_Cg.Enable_Kernel_Debugger
FALSE
R1000_Cg.Reclaim_Space
TRUE
Design.Options
""
Semantics.Sm_Attr_Trace
FALSE
Format.Wrap_Indentation
16
R1000_Cg.Ignore_Fixed_Module_Names
FALSE
Rci.Sparc_Sun_Xt_Invoke_Preprocessor
FALSE
Directory.Create_Subprogram_Specs
TRUE
Rci.Sparc_Sun_Xt_Timing
FALSE
Rci.Sparc_Sun_Xt_Dependencies_Only
FALSE
Rci.I386_Unix_Als_Xt_Stack_Main_Size
""
Rci.Sparc_Sun_Xt_Dependent_Files
FALSE
R1000_Cg.Option_13
FALSE
Rci.I386_Unix_Als_Xt_Heap_Initial_Size
""
Rci.I386_Unix_Als_Xt_Display_Show
"all"
Semantics.Reject_Inevitable_Exceptions
FALSE
Rci.Vax_Vms_Dec_Xt_Show
""
Rci.Vax_Vms_Dec_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Improve_Reduction
""
Rci.Vax_Vms_Dec_Xt_Full
FALSE
Rci.I386_Unix_Als_Xt_Heap_Increment_Size
""
Rci.Compiler_Pre_Options
""
Semantics.Sm_Agg_Trace
FALSE
R1000_Cg.Loader_46
FALSE
R1000_Cg.Epsilon_Mirrors
FALSE
Rci.Optimize_Download
TRUE
R1000_Cg.Loader_47
FALSE
Rci.I386_Unix_Als_Xt_Get_Binder_Listing
TRUE
R1000_Cg.Loader_44
FALSE
Directory.Require_Internal_Links
TRUE
Rci.Host_Only
FALSE
Format.Minor_Indentation
4
Format.Major_Indentation
4
R1000_Cg.Loader_45
FALSE
Rci.I386_Unix_Als_Xt_Default_Machine
""
Rci.Compiler_Post_Options
""
Ftp.Transfer_Mode
NIL
Semantics.Sm_Range_Trace
FALSE
Format.Statement_Indentation
3
R1000_Cg.Loader_42
FALSE
Rci.I386_Unix_Als_Xt_Keep_Debug
""
Rci.I386_Unix_Als_Xt_Run_Time_Checks
""
Format.Consistent_Breaking
1
Format.Alignment_Threshold
0
Ftp.Password
""
R1000_Cg.Debug_View_Level
0
R1000_Cg.Loader_43
FALSE
R1000_Cg.Check_Compatibility
TRUE
Rci.Sparc_Sun_Xt_Show_Tool_Name_Only
FALSE
Rci.Vax_Vms_Dec_Xt_Map
FALSE
Rci.Auto_Transfer
FALSE
Directory.Create_Internal_Links
TRUE
R1000_Cg.Module_Name_Bias
()
R1000_Cg.Loader_41
FALSE
Format.Comment_Column
1
Format.Id_Case
CAPITALIZED
Rci.Sparc_Sun_Xt_Main
""
Ftp.Username
""
Semantics.Ignore_Rep_Specs
FALSE
R1000_Cg.Integer_Option_07
0
R1000_Cg.Page_Limit
8000
R1000_Cg.Block_Inlining
FALSE
Rci.Sparc_Sun_Xt_Error_Listing
FALSE
Rci.I386_Unix_Als_Xt_Get_Executable_File
FALSE
Rci.I386_Unix_Als_Xt_Shared_Memory_Size
""
Rci.Operation_Mode
""
Rci.Vax_Vms_Dec_Xt_Optimize
"(NONE)"
Ftp.Remote_Machine
""
Rci.Sparc_Sun_Xt_Executable_Output
""
Rci.Sparc_Sun_Xt_Error_Output
FALSE
Rci.Sparc_Sun_Xt_Define_Preprocessor_Value
""
Semantics.Ignore_Unsupported_Rep_Specs
FALSE
R1000_Cg.Omit_Break_Optionals
FALSE
Format.Number_Case
UPPER
R1000_Cg.Branch_Table_Density
0
Rci.Sparc_Sun_Xt_Suppress_Warnings
FALSE
Rci.Vax_Vms_Dec_Xt_Default_Roof
""
R1000_Cg.Unfixed_Module_Name_Keys
()
R1000_Cg.Special_39
FALSE
R1000_Cg.Statistics
FALSE
Format.Statement_Length
35
Rci.Vax_Vms_Dec_Xt_Nocheck
FALSE
R1000_Cg.Spare_49
FALSE
R1000_Cg.Enable_Environment_Debugger
FALSE
Rci.Vax_Vms_Dec_Xt_Ldebug
FALSE
Rci.Vax_Vms_Dec_Xt_Nodebug
FALSE
Publisher.Options
""
R1000_Cg.Spare_48
FALSE
R1000_Cg.Vpids_Go_Native
FALSE
R1000_Cg.Retain_Delta1_Compatibility
FALSE
R1000_Cg.Debug_Option_21
FALSE
R1000_Cg.Full_Debugging
FALSE
Ftp.Prompt_For_Account
FALSE
R1000_Cg.Spare_55
FALSE
R1000_Cg.Suppress_Elaboration_Checks
FALSE
R1000_Cg.Debug_Option_22
FALSE
Rci.Sparc_Sun_Xt_Debug_Overflow
FALSE
Rci.I386_Unix_Als_Xt_Default_Roof
""
Ftp.Remote_Roof
""
R1000_Cg.Spare_54
FALSE
R1000_Cg.Wire_Code_Segments
FALSE
R1000_Cg.Debug_Option_23
FALSE
Rci.I386_Unix_Als_Xt_Display_Map_Data
""
Semantics.Ignore_Minor_Errors
FALSE
R1000_Cg.Package_Integration
FALSE
Rci.I386_Unix_Als_Xt_Display_Text
"yes"
Rci.Trace_Command_Output
FALSE
Rci.Linker_Pre_Options
""
Rci.Vax_Vms_Dec_Xt_Check
FALSE
Rci.Sparc_Sun_Xt_Default_Roof
""
R1000_Cg.Tos_Relative_Load_Limit
3
R1000_Cg.Debug_View_Layer
128
R1000_Cg.Epsilon_Debug_Tables
FALSE
Semantics.Closed_Private_Part
FALSE
Semantics.Sm_Match_Trace
FALSE
R1000_Cg.Auto_Integration
FALSE
R1000_Cg.Enable_Deallocation
FALSE
R1000_Cg.Output_06
FALSE
Rci.Remote_Library
""
R1000_Cg.Module_Name_Bias_Keys
()
R1000_Cg.Output_07
FALSE
Rci.I386_Unix_Als_Xt_Get_Cui_File
FALSE
Semantics.Reject_Bad_Lrm_Pragmas
FALSE
Semantics.Limit_Semantic_Messages
200
R1000_Cg.Optimization_31
FALSE
Rci.Sparc_Sun_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Stack_Trace_History
""
Ftp.Transfer_Type
NIL
Rci.Sparc_Sun_Xt_Optimization
""
Rci.Sparc_Sun_Xt_Keep_Intermediate
FALSE
Semantics.Reject_Statement_Prompts
FALSE
Semantics.Ignore_Invalid_Rep_Specs
FALSE
Rci.Vax_Vms_Dec_Xt_Cross_Ref
FALSE
R1000_Cg.Delta1_Code_View_Compatibility
FALSE
Rci.I386_Unix_Als_Xt_Get_Compiler_Listing
TRUE
Rci.I386_Unix_Als_Xt_Display_Assembly
""
Semantics.Sm_Exp_Trace
FALSE
R1000_Cg.Spare_51
FALSE
R1000_Cg.Spare_50
FALSE
R1000_Cg.Subprogram_Inlining
FALSE
R1000_Cg.Debug_Listing
FALSE
Rci.Sparc_Sun_Xt_Archive_File_Name
""
Semantics.Sm_Call_Trace
FALSE
Ftp.Prompt_For_Password
FALSE
R1000_Cg.Spare_53
FALSE
R1000_Cg.Suppress_Constraint_Checks
FALSE
Rci.Sparc_Sun_Xt_Verbose
FALSE
Semantics.Reject_Bad_Rational_Pragmas
FALSE
R1000_Cg.Spare_52
FALSE
Rci.I386_Unix_Als_Xt_Improve_Expressions
""
Semantics.Sm_Solve_Trace
FALSE
Ftp.Remote_Directory
""
Ftp.Remote_Type
""
Semantics.Ignore_Interface_Pragmas
FALSE
Semantics.Reject_Undefined_Pragmas
FALSE
Rci.Vax_Vms_Dec_Xt_Debug
""
R1000_Cg.Binary_Search_Size
0
R1000_Cg.Auto_Inlining
FALSE
Format.Line_Length
80
Rci.Sparc_Sun_Xt_Dependent_Units
FALSE
Ftp.Transfer_Structure
NIL
Rci.Vax_Vms_Dec_Xt_Upload_Exe
FALSE
R1000_Cg.Code_Segment_Size
0
R1000_Cg.Terminal_Echo
FALSE
!TARGETS.I386_UNIX_ALS_XT.LRM
K
!TARGETS.I386_UNIX_ALS_XT.LRM.SWITCHES
!TARGETS.I386_UNIX_ALS_XT.LRM.CALENDAR'SPEC
V17050|-1560|4| 7/26/90 11:14:32|PACKAGE_SPEC||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.LRM.MACHINE_CODE'SPEC
V18610|-41|4| 5/08/90 23:40:59|PACKAGE_SPEC||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.LRM.SYSTEM'SPEC
V18651|-4194|4|10/10/91 09:10:22|PACKAGE_SPEC||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.LRM.UNCHECKED_CONVERSION'SPEC
V22845|-137|4| 5/08/90 23:41:16|GENERIC_FUNCTION||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.LRM.UNCHECKED_DEALLOCATION'SPEC
V22982|-127|4| 5/08/90 23:41:28|GENERIC_PROCEDURE||1|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.REUSABLE_COMPONENTS
N||| 9/02/92 18:19:02|DIRECTORY|||
!TARGETS.I386_UNIX_ALS_XT.REUSABLE_COMPONENTS.SWITCHES
H||| 3/02/92 18:50:09|SWITCH||1|
ANETWORK_PUBLIC=>RW|
Rci.Sparc_Sun_Xt_Elaborate
""
Semantics.Sm_Assign_Trace
FALSE
Rci.Sparc_Sun_Xt_Recompile_Instantiation
""
Format.Keyword_Case
LOWER
Rci.Vax_Vms_Dec_Xt_Noexecutable
FALSE
Rci.Vax_Vms_Dec_Xt_Nomain
FALSE
R1000_Cg.Epsilon_Code_Segments
FALSE
R1000_Cg.Elab_Order_Listing
FALSE
R1000_Cg.Seg_Listing
FALSE
R1000_Cg.Asm_Listing
FALSE
Rci.I386_Unix_Als_Xt_User_Set_Family_Name
""
Rci.I386_Unix_Als_Xt_Stack_Task_Size
""
Rci.I386_Unix_Als_Xt_Improve_Calls
""
Semantics.Subsystem_Interface
FALSE
Ftp.Auto_Login
FALSE
R1000_Cg.Disable_Class3_Assertions
FALSE
R1000_Cg.Disable_Class2_Assertions
FALSE
R1000_Cg.Disable_Class1_Assertions
FALSE
Rci.Sparc_Sun_Xt_Apply_Suppress
FALSE
Parser.Configuration
()
Rci.Vax_Vms_Dec_Xt_List
FALSE
Ftp.Account
""
Rci.I386_Unix_Als_Xt_Get_Lnk_File
FALSE
Rci.I386_Unix_Als_Xt_Stack_Object_Size
""
Semantics.Sm_Type_Eq
FALSE
Semantics.Flag_Inevitable_Exceptions
FALSE
R1000_Cg.Option_14
FALSE
Rci.Linker_Post_Options
""
Design.Phase
<None>
R1000_Cg.Option_15
FALSE
Ftp.Send_Port_Enabled
TRUE
Semantics.Drop_Minor_Errors
FALSE
Semantics.Ignore_Cdb
FALSE
Rci.Vax_Vms_Dec_Xt_Brief
FALSE
R1000_Cg.Enable_Kernel_Debugger
FALSE
R1000_Cg.Reclaim_Space
TRUE
Design.Options
""
Semantics.Sm_Attr_Trace
FALSE
Format.Wrap_Indentation
16
R1000_Cg.Ignore_Fixed_Module_Names
FALSE
Rci.Sparc_Sun_Xt_Invoke_Preprocessor
FALSE
Directory.Create_Subprogram_Specs
TRUE
Rci.Sparc_Sun_Xt_Timing
FALSE
Rci.Sparc_Sun_Xt_Dependencies_Only
FALSE
Rci.I386_Unix_Als_Xt_Stack_Main_Size
""
Rci.Sparc_Sun_Xt_Dependent_Files
FALSE
R1000_Cg.Option_13
FALSE
Rci.I386_Unix_Als_Xt_Heap_Initial_Size
""
Rci.I386_Unix_Als_Xt_Display_Show
"all"
Semantics.Reject_Inevitable_Exceptions
FALSE
Rci.Vax_Vms_Dec_Xt_Show
""
Rci.Vax_Vms_Dec_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Improve_Reduction
""
Rci.Vax_Vms_Dec_Xt_Full
FALSE
Rci.I386_Unix_Als_Xt_Heap_Increment_Size
""
Rci.Compiler_Pre_Options
""
Semantics.Sm_Agg_Trace
FALSE
R1000_Cg.Loader_46
FALSE
R1000_Cg.Epsilon_Mirrors
FALSE
Rci.Optimize_Download
TRUE
R1000_Cg.Loader_47
FALSE
Rci.I386_Unix_Als_Xt_Get_Binder_Listing
TRUE
R1000_Cg.Loader_44
FALSE
Directory.Require_Internal_Links
TRUE
Rci.Host_Only
FALSE
Format.Minor_Indentation
4
Format.Major_Indentation
4
R1000_Cg.Loader_45
FALSE
Rci.I386_Unix_Als_Xt_Default_Machine
""
Rci.Compiler_Post_Options
""
Ftp.Transfer_Mode
NIL
Semantics.Sm_Range_Trace
FALSE
Format.Statement_Indentation
3
R1000_Cg.Loader_42
FALSE
Rci.I386_Unix_Als_Xt_Keep_Debug
""
Rci.I386_Unix_Als_Xt_Run_Time_Checks
""
Format.Consistent_Breaking
1
Format.Alignment_Threshold
0
Ftp.Password
""
R1000_Cg.Debug_View_Level
0
R1000_Cg.Loader_43
FALSE
R1000_Cg.Check_Compatibility
TRUE
Rci.Sparc_Sun_Xt_Show_Tool_Name_Only
FALSE
Rci.Vax_Vms_Dec_Xt_Map
FALSE
Rci.Auto_Transfer
FALSE
Directory.Create_Internal_Links
TRUE
R1000_Cg.Module_Name_Bias
()
R1000_Cg.Loader_41
FALSE
Format.Comment_Column
1
Format.Id_Case
CAPITALIZED
Rci.Sparc_Sun_Xt_Main
""
Ftp.Username
""
Semantics.Ignore_Rep_Specs
FALSE
R1000_Cg.Integer_Option_07
0
R1000_Cg.Page_Limit
8000
R1000_Cg.Block_Inlining
FALSE
Rci.Sparc_Sun_Xt_Error_Listing
FALSE
Rci.I386_Unix_Als_Xt_Get_Executable_File
FALSE
Rci.I386_Unix_Als_Xt_Shared_Memory_Size
""
Rci.Operation_Mode
""
Rci.Vax_Vms_Dec_Xt_Optimize
"(NONE)"
Ftp.Remote_Machine
""
Rci.Sparc_Sun_Xt_Executable_Output
""
Rci.Sparc_Sun_Xt_Error_Output
FALSE
Rci.Sparc_Sun_Xt_Define_Preprocessor_Value
""
Semantics.Ignore_Unsupported_Rep_Specs
FALSE
R1000_Cg.Omit_Break_Optionals
FALSE
Format.Number_Case
UPPER
R1000_Cg.Branch_Table_Density
0
Rci.Sparc_Sun_Xt_Suppress_Warnings
FALSE
Rci.Vax_Vms_Dec_Xt_Default_Roof
""
R1000_Cg.Unfixed_Module_Name_Keys
()
R1000_Cg.Special_39
FALSE
R1000_Cg.Statistics
FALSE
Format.Statement_Length
35
Rci.Vax_Vms_Dec_Xt_Nocheck
FALSE
R1000_Cg.Spare_49
FALSE
R1000_Cg.Enable_Environment_Debugger
FALSE
Rci.Vax_Vms_Dec_Xt_Ldebug
FALSE
Rci.Vax_Vms_Dec_Xt_Nodebug
FALSE
Publisher.Options
""
R1000_Cg.Spare_48
FALSE
R1000_Cg.Vpids_Go_Native
FALSE
R1000_Cg.Retain_Delta1_Compatibility
TRUE
R1000_Cg.Debug_Option_21
FALSE
R1000_Cg.Full_Debugging
FALSE
Ftp.Prompt_For_Account
FALSE
R1000_Cg.Spare_55
FALSE
R1000_Cg.Suppress_Elaboration_Checks
FALSE
R1000_Cg.Debug_Option_22
FALSE
Rci.Sparc_Sun_Xt_Debug_Overflow
FALSE
Rci.I386_Unix_Als_Xt_Default_Roof
""
Ftp.Remote_Roof
""
R1000_Cg.Spare_54
FALSE
R1000_Cg.Wire_Code_Segments
FALSE
R1000_Cg.Debug_Option_23
FALSE
Rci.I386_Unix_Als_Xt_Display_Map_Data
""
Semantics.Ignore_Minor_Errors
FALSE
R1000_Cg.Package_Integration
FALSE
Rci.I386_Unix_Als_Xt_Display_Text
"yes"
Rci.Trace_Command_Output
FALSE
Rci.Linker_Pre_Options
""
Rci.Vax_Vms_Dec_Xt_Check
FALSE
Rci.Sparc_Sun_Xt_Default_Roof
""
R1000_Cg.Tos_Relative_Load_Limit
3
R1000_Cg.Debug_View_Layer
128
R1000_Cg.Epsilon_Debug_Tables
FALSE
Semantics.Closed_Private_Part
FALSE
Semantics.Sm_Match_Trace
FALSE
R1000_Cg.Auto_Integration
FALSE
R1000_Cg.Enable_Deallocation
FALSE
R1000_Cg.Output_06
FALSE
Rci.Remote_Library
""
R1000_Cg.Module_Name_Bias_Keys
()
R1000_Cg.Output_07
FALSE
Rci.I386_Unix_Als_Xt_Get_Cui_File
FALSE
Semantics.Reject_Bad_Lrm_Pragmas
FALSE
Semantics.Limit_Semantic_Messages
200
R1000_Cg.Optimization_31
FALSE
Rci.Sparc_Sun_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Stack_Trace_History
""
Ftp.Transfer_Type
NIL
Rci.Sparc_Sun_Xt_Optimization
""
Rci.Sparc_Sun_Xt_Keep_Intermediate
FALSE
Semantics.Reject_Statement_Prompts
FALSE
Semantics.Ignore_Invalid_Rep_Specs
FALSE
Rci.Vax_Vms_Dec_Xt_Cross_Ref
FALSE
R1000_Cg.Delta1_Code_View_Compatibility
FALSE
Rci.I386_Unix_Als_Xt_Get_Compiler_Listing
TRUE
Rci.I386_Unix_Als_Xt_Display_Assembly
""
Semantics.Sm_Exp_Trace
FALSE
R1000_Cg.Spare_51
FALSE
R1000_Cg.Spare_50
FALSE
R1000_Cg.Subprogram_Inlining
FALSE
R1000_Cg.Debug_Listing
FALSE
Rci.Sparc_Sun_Xt_Archive_File_Name
""
Semantics.Sm_Call_Trace
FALSE
Ftp.Prompt_For_Password
FALSE
R1000_Cg.Spare_53
FALSE
R1000_Cg.Suppress_Constraint_Checks
FALSE
Rci.Sparc_Sun_Xt_Verbose
FALSE
Semantics.Reject_Bad_Rational_Pragmas
FALSE
R1000_Cg.Spare_52
FALSE
Rci.I386_Unix_Als_Xt_Improve_Expressions
""
Semantics.Sm_Solve_Trace
FALSE
Ftp.Remote_Directory
""
Ftp.Remote_Type
""
Semantics.Ignore_Interface_Pragmas
FALSE
Semantics.Reject_Undefined_Pragmas
FALSE
Rci.Vax_Vms_Dec_Xt_Debug
""
R1000_Cg.Binary_Search_Size
0
R1000_Cg.Auto_Inlining
FALSE
Format.Line_Length
80
Rci.Sparc_Sun_Xt_Dependent_Units
FALSE
Ftp.Transfer_Structure
NIL
Rci.Vax_Vms_Dec_Xt_Upload_Exe
FALSE
R1000_Cg.Code_Segment_Size
0
R1000_Cg.Terminal_Echo
FALSE
!TARGETS.I386_UNIX_ALS_XT.REUSABLE_COMPONENTS
K
!TARGETS.I386_UNIX_ALS_XT.REUSABLE_COMPONENTS.SWITCHES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE
N||| 4/17/92 16:30:04|DIRECTORY|||
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO
N||| 4/17/92 16:29:37|DIRECTORY||1|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT
N||| 4/17/92 16:29:40|DIRECTORY||3|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT
K
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.SWITCHES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.DISPATCH_TEXT
F23109|-1032|| 9/20/91 10:09:23|TEXT||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.DYN_PRI_TEXT
F24141|-574|| 9/20/91 10:09:08|TEXT||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.EVENTS_TEXT
F24715|-6262|| 9/20/91 10:08:49|||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.NON_WAIT_TEXT
F30977|-1055|| 9/20/91 10:08:35|TEXT||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.PREEMPT_TEXT
F32032|-497|| 9/20/91 10:08:19|||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.SCHEDULE_TEXT
F32529|-2002|| 9/20/91 10:07:19|TEXT||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.SEMAPHORE_TEXT
F34531|-914|| 9/20/91 10:06:59|TEXT||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.SHARED_TEXT
F35445|-649|| 9/20/91 10:06:37|TEXT||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_ADA_TEXT.TASK_IDS_TEXT
F36094|-977|| 9/20/91 10:05:10|TEXT||7|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO
K
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.SWITCHES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CALL_NONPREEMPTIBLE_SECTION'SPEC
V37071|-89|4| 9/20/91 13:47:27|GENERIC_PROCEDURE||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_EVENT_MANAGEMENT'SPEC
V37160|-6615|4| 9/20/91 13:47:30|GENERIC_PACKAGE||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.DISPATCHING_CONTROL'SPEC
V43775|-1003|4| 9/20/91 13:47:37|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.DYNAMIC_PRIORITIES'SPEC
V44778|-573|4| 9/20/91 13:47:43|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.ENTRY_CALLER'SPEC
V45351|-1067|4| 9/20/91 13:47:48|GENERIC_PACKAGE||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.EVENT_MANAGEMENT'SPEC
V46418|-134|4| 9/20/91 13:47:50|PACKAGE_INSTANTIATION||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.PREEMPTION_CONTROL'SPEC
V46552|-410|4| 9/20/91 13:47:54|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.SCHEDULER'SPEC
V46962|-2411|4| 9/20/91 13:49:42|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.SEMAPHORE'SPEC
V49373|-1066|4| 9/20/91 13:48:05|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.SHARED_DATA_GENERIC'SPEC
V50439|-701|4| 9/20/91 13:51:12|GENERIC_PACKAGE||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.TASK_IDS'SPEC
V51140|-1167|4| 9/20/91 13:47:38|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX
N||| 4/17/92 16:30:08|DIRECTORY||1|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX
K
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.SWITCHES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.IMPLEM_DEF'SPEC
V52307|-808|4|11/18/91 14:54:52|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.LOCAL_PROCS'SPEC
V53115|-241|4|11/18/91 14:55:05|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX'SPEC
V53356|-5903|4|11/18/91 14:54:55|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_CURRENT_EXCEPTION'SPEC
V59259|-9564|4|11/18/91 14:55:00|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_FILES'SPEC
V68823|-3992|4|11/18/91 14:55:02|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_FILE_STATUS'SPEC
V72815|-2083|4|11/18/91 15:53:24|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_IO'SPEC
V74898|-4373|4|11/18/91 14:54:57|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PERMISSIONS'SPEC
V79271|-1337|4|11/18/91 14:55:10|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PROCESS_ENVIRONMENT'SPEC
V80608|-2241|4|11/18/91 15:55:24|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PROCESS_IDENTIFICATION'SPEC
V82849|-1865|4|11/18/91 15:50:02|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PROCESS_PRIMITIVES'SPEC
V84714|-5015|4|11/18/91 16:48:22|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_SIGNALS'SPEC
V89729|-3671|4|11/18/91 16:45:50|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_UNSAFE_PROCESS_PRIMITIVES'SPEC
V93400|-1375|4|11/18/91 14:55:21|PACKAGE_SPEC||3|
ANETWORK_PUBLIC=>RW|
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.SWITCHES
H||| 3/02/92 18:50:09|SWITCH||1|
ANETWORK_PUBLIC=>RW|
Rci.Sparc_Sun_Xt_Elaborate
""
Semantics.Sm_Assign_Trace
FALSE
Rci.Sparc_Sun_Xt_Recompile_Instantiation
""
Format.Keyword_Case
LOWER
Rci.Vax_Vms_Dec_Xt_Noexecutable
FALSE
Rci.Vax_Vms_Dec_Xt_Nomain
FALSE
R1000_Cg.Epsilon_Code_Segments
FALSE
R1000_Cg.Elab_Order_Listing
FALSE
R1000_Cg.Seg_Listing
FALSE
R1000_Cg.Asm_Listing
FALSE
Rci.I386_Unix_Als_Xt_User_Set_Family_Name
""
Rci.I386_Unix_Als_Xt_Stack_Task_Size
""
Rci.I386_Unix_Als_Xt_Improve_Calls
""
Semantics.Subsystem_Interface
FALSE
Ftp.Auto_Login
FALSE
R1000_Cg.Disable_Class3_Assertions
FALSE
R1000_Cg.Disable_Class2_Assertions
FALSE
R1000_Cg.Disable_Class1_Assertions
FALSE
Rci.Sparc_Sun_Xt_Apply_Suppress
FALSE
Parser.Configuration
()
Rci.Vax_Vms_Dec_Xt_List
FALSE
Ftp.Account
""
Rci.I386_Unix_Als_Xt_Get_Lnk_File
FALSE
Rci.I386_Unix_Als_Xt_Stack_Object_Size
""
Semantics.Sm_Type_Eq
FALSE
Semantics.Flag_Inevitable_Exceptions
FALSE
R1000_Cg.Option_14
FALSE
Rci.Linker_Post_Options
""
Design.Phase
<None>
R1000_Cg.Option_15
FALSE
Ftp.Send_Port_Enabled
TRUE
Semantics.Drop_Minor_Errors
FALSE
Semantics.Ignore_Cdb
FALSE
Rci.Vax_Vms_Dec_Xt_Brief
FALSE
R1000_Cg.Enable_Kernel_Debugger
FALSE
R1000_Cg.Reclaim_Space
TRUE
Design.Options
""
Semantics.Sm_Attr_Trace
FALSE
Format.Wrap_Indentation
16
R1000_Cg.Ignore_Fixed_Module_Names
FALSE
Rci.Sparc_Sun_Xt_Invoke_Preprocessor
FALSE
Directory.Create_Subprogram_Specs
TRUE
Rci.Sparc_Sun_Xt_Timing
FALSE
Rci.Sparc_Sun_Xt_Dependencies_Only
FALSE
Rci.I386_Unix_Als_Xt_Stack_Main_Size
""
Rci.Sparc_Sun_Xt_Dependent_Files
FALSE
R1000_Cg.Option_13
FALSE
Rci.I386_Unix_Als_Xt_Heap_Initial_Size
""
Rci.I386_Unix_Als_Xt_Display_Show
"all"
Semantics.Reject_Inevitable_Exceptions
FALSE
Rci.Vax_Vms_Dec_Xt_Show
""
Rci.Vax_Vms_Dec_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Improve_Reduction
""
Rci.Vax_Vms_Dec_Xt_Full
FALSE
Rci.I386_Unix_Als_Xt_Heap_Increment_Size
""
Rci.Compiler_Pre_Options
""
Semantics.Sm_Agg_Trace
FALSE
R1000_Cg.Loader_46
FALSE
R1000_Cg.Epsilon_Mirrors
FALSE
Rci.Optimize_Download
TRUE
R1000_Cg.Loader_47
FALSE
Rci.I386_Unix_Als_Xt_Get_Binder_Listing
TRUE
R1000_Cg.Loader_44
FALSE
Directory.Require_Internal_Links
TRUE
Rci.Host_Only
FALSE
Format.Minor_Indentation
4
Format.Major_Indentation
4
R1000_Cg.Loader_45
FALSE
Rci.I386_Unix_Als_Xt_Default_Machine
""
Rci.Compiler_Post_Options
""
Ftp.Transfer_Mode
NIL
Semantics.Sm_Range_Trace
FALSE
Format.Statement_Indentation
3
R1000_Cg.Loader_42
FALSE
Rci.I386_Unix_Als_Xt_Keep_Debug
""
Rci.I386_Unix_Als_Xt_Run_Time_Checks
""
Format.Consistent_Breaking
1
Format.Alignment_Threshold
0
Ftp.Password
""
R1000_Cg.Debug_View_Level
0
R1000_Cg.Loader_43
FALSE
R1000_Cg.Check_Compatibility
TRUE
Rci.Sparc_Sun_Xt_Show_Tool_Name_Only
FALSE
Rci.Vax_Vms_Dec_Xt_Map
FALSE
Rci.Auto_Transfer
FALSE
Directory.Create_Internal_Links
TRUE
R1000_Cg.Module_Name_Bias
()
R1000_Cg.Loader_41
FALSE
Format.Comment_Column
1
Format.Id_Case
CAPITALIZED
Rci.Sparc_Sun_Xt_Main
""
Ftp.Username
""
Semantics.Ignore_Rep_Specs
FALSE
R1000_Cg.Integer_Option_07
0
R1000_Cg.Page_Limit
8000
R1000_Cg.Block_Inlining
FALSE
Rci.Sparc_Sun_Xt_Error_Listing
FALSE
Rci.I386_Unix_Als_Xt_Get_Executable_File
FALSE
Rci.I386_Unix_Als_Xt_Shared_Memory_Size
""
Rci.Operation_Mode
""
Rci.Vax_Vms_Dec_Xt_Optimize
"(NONE)"
Ftp.Remote_Machine
""
Rci.Sparc_Sun_Xt_Executable_Output
""
Rci.Sparc_Sun_Xt_Error_Output
FALSE
Rci.Sparc_Sun_Xt_Define_Preprocessor_Value
""
Semantics.Ignore_Unsupported_Rep_Specs
FALSE
R1000_Cg.Omit_Break_Optionals
FALSE
Format.Number_Case
UPPER
R1000_Cg.Branch_Table_Density
0
Rci.Sparc_Sun_Xt_Suppress_Warnings
FALSE
Rci.Vax_Vms_Dec_Xt_Default_Roof
""
R1000_Cg.Unfixed_Module_Name_Keys
()
R1000_Cg.Special_39
FALSE
R1000_Cg.Statistics
FALSE
Format.Statement_Length
35
Rci.Vax_Vms_Dec_Xt_Nocheck
FALSE
R1000_Cg.Spare_49
FALSE
R1000_Cg.Enable_Environment_Debugger
FALSE
Rci.Vax_Vms_Dec_Xt_Ldebug
FALSE
Rci.Vax_Vms_Dec_Xt_Nodebug
FALSE
Publisher.Options
""
R1000_Cg.Spare_48
FALSE
R1000_Cg.Vpids_Go_Native
FALSE
R1000_Cg.Retain_Delta1_Compatibility
TRUE
R1000_Cg.Debug_Option_21
FALSE
R1000_Cg.Full_Debugging
FALSE
Ftp.Prompt_For_Account
FALSE
R1000_Cg.Spare_55
FALSE
R1000_Cg.Suppress_Elaboration_Checks
FALSE
R1000_Cg.Debug_Option_22
FALSE
Rci.Sparc_Sun_Xt_Debug_Overflow
FALSE
Rci.I386_Unix_Als_Xt_Default_Roof
""
Ftp.Remote_Roof
""
R1000_Cg.Spare_54
FALSE
R1000_Cg.Wire_Code_Segments
FALSE
R1000_Cg.Debug_Option_23
FALSE
Rci.I386_Unix_Als_Xt_Display_Map_Data
""
Semantics.Ignore_Minor_Errors
FALSE
R1000_Cg.Package_Integration
FALSE
Rci.I386_Unix_Als_Xt_Display_Text
"yes"
Rci.Trace_Command_Output
FALSE
Rci.Linker_Pre_Options
""
Rci.Vax_Vms_Dec_Xt_Check
FALSE
Rci.Sparc_Sun_Xt_Default_Roof
""
R1000_Cg.Tos_Relative_Load_Limit
3
R1000_Cg.Debug_View_Layer
128
R1000_Cg.Epsilon_Debug_Tables
FALSE
Semantics.Closed_Private_Part
FALSE
Semantics.Sm_Match_Trace
FALSE
R1000_Cg.Auto_Integration
FALSE
R1000_Cg.Enable_Deallocation
FALSE
R1000_Cg.Output_06
FALSE
Rci.Remote_Library
""
R1000_Cg.Module_Name_Bias_Keys
()
R1000_Cg.Output_07
FALSE
Rci.I386_Unix_Als_Xt_Get_Cui_File
FALSE
Semantics.Reject_Bad_Lrm_Pragmas
FALSE
Semantics.Limit_Semantic_Messages
200
R1000_Cg.Optimization_31
FALSE
Rci.Sparc_Sun_Xt_Default_Machine
""
Rci.I386_Unix_Als_Xt_Stack_Trace_History
""
Ftp.Transfer_Type
NIL
Rci.Sparc_Sun_Xt_Optimization
""
Rci.Sparc_Sun_Xt_Keep_Intermediate
FALSE
Semantics.Reject_Statement_Prompts
FALSE
Semantics.Ignore_Invalid_Rep_Specs
FALSE
Rci.Vax_Vms_Dec_Xt_Cross_Ref
FALSE
R1000_Cg.Delta1_Code_View_Compatibility
FALSE
Rci.I386_Unix_Als_Xt_Get_Compiler_Listing
TRUE
Rci.I386_Unix_Als_Xt_Display_Assembly
""
Semantics.Sm_Exp_Trace
FALSE
R1000_Cg.Spare_51
FALSE
R1000_Cg.Spare_50
FALSE
R1000_Cg.Subprogram_Inlining
FALSE
R1000_Cg.Debug_Listing
FALSE
Rci.Sparc_Sun_Xt_Archive_File_Name
""
Semantics.Sm_Call_Trace
FALSE
Ftp.Prompt_For_Password
FALSE
R1000_Cg.Spare_53
FALSE
R1000_Cg.Suppress_Constraint_Checks
FALSE
Rci.Sparc_Sun_Xt_Verbose
FALSE
Semantics.Reject_Bad_Rational_Pragmas
FALSE
R1000_Cg.Spare_52
FALSE
Rci.I386_Unix_Als_Xt_Improve_Expressions
""
Semantics.Sm_Solve_Trace
FALSE
Ftp.Remote_Directory
""
Ftp.Remote_Type
""
Semantics.Ignore_Interface_Pragmas
FALSE
Semantics.Reject_Undefined_Pragmas
FALSE
Rci.Vax_Vms_Dec_Xt_Debug
""
R1000_Cg.Binary_Search_Size
0
R1000_Cg.Auto_Inlining
FALSE
Format.Line_Length
80
Rci.Sparc_Sun_Xt_Dependent_Units
FALSE
Ftp.Transfer_Structure
NIL
Rci.Vax_Vms_Dec_Xt_Upload_Exe
FALSE
R1000_Cg.Code_Segment_Size
0
R1000_Cg.Terminal_Echo
FALSE
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE
K
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.SWITCHES
!TARGETS.I386_UNIX_ALS_XT
Y
CIFO_EVENT_MANAGEMENT
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CIFO_EVENT_MANAGEMENT'SPEC
LOCAL_PROCS
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.LOCAL_PROCS'SPEC
SEQUENTIAL_IO
!TARGETS.I386_UNIX_ALS_XT.IO.SEQUENTIAL_IO'SPEC
POSIX_SIGNALS
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_SIGNALS'SPEC
POSIX_PERMISSIONS
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PERMISSIONS'SPEC
POSIX_UNSAFE_PROCESS_PRIMITIVES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_UNSAFE_PROCESS_PRIMITIVES'SPEC
POSIX_PROCESS_ENVIRONMENT
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PROCESS_ENVIRONMENT'SPEC
POSIX_FILES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_FILES'SPEC
POSIX
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX'SPEC
POSIX_PROCESS_PRIMITIVES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PROCESS_PRIMITIVES'SPEC
POSIX_FILE_STATUS
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_FILE_STATUS'SPEC
POSIX_CURRENT_EXCEPTION
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_CURRENT_EXCEPTION'SPEC
PREEMPTION_CONTROL
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.PREEMPTION_CONTROL'SPEC
DYNAMIC_PRIORITIES
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.DYNAMIC_PRIORITIES'SPEC
TASK_IDS
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.TASK_IDS'SPEC
POSIX_PROCESS_IDENTIFICATION
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_PROCESS_IDENTIFICATION'SPEC
IMPLEM_DEF
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.IMPLEM_DEF'SPEC
DISPATCHING_CONTROL
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.DISPATCHING_CONTROL'SPEC
DIRECT_IO
!TARGETS.I386_UNIX_ALS_XT.IO.DIRECT_IO'SPEC
TEXT_IO
!TARGETS.I386_UNIX_ALS_XT.IO.TEXT_IO'SPEC
SEMAPHORE
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.SEMAPHORE'SPEC
POSIX_IO
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.POSIX.POSIX_IO'SPEC
CALENDAR
!TARGETS.I386_UNIX_ALS_XT.LRM.CALENDAR'SPEC
UNCHECKED_CONVERSION
!TARGETS.I386_UNIX_ALS_XT.LRM.UNCHECKED_CONVERSION'SPEC
BASIC_IO
!TARGETS.I386_UNIX_ALS_XT.IO.BASIC_IO'SPEC
MACHINE_CODE
!TARGETS.I386_UNIX_ALS_XT.LRM.MACHINE_CODE'SPEC
UNCHECKED_DEALLOCATION
!TARGETS.I386_UNIX_ALS_XT.LRM.UNCHECKED_DEALLOCATION'SPEC
EVENT_MANAGEMENT
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.EVENT_MANAGEMENT'SPEC
ENTRY_CALLER
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.ENTRY_CALLER'SPEC
SHARED_DATA_GENERIC
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.SHARED_DATA_GENERIC'SPEC
IO_EXCEPTIONS
!TARGETS.I386_UNIX_ALS_XT.IO.IO_EXCEPTIONS'SPEC
CALL_NONPREEMPTIBLE_SECTION
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.CALL_NONPREEMPTIBLE_SECTION'SPEC
SYSTEM
!TARGETS.I386_UNIX_ALS_XT.LRM.SYSTEM'SPEC
SCHEDULER
!TARGETS.I386_UNIX_ALS_XT.TARGET_INTERFACE.CIFO.SCHEDULER'SPEC
!TARGETS.IMPLEMENTATION.RELEASE_I386_UNIX_ALS_XT_2_0_2.INSTALL_ACTIVITY
A|||12/03/92 13:14:02|ACTIVITY||2|
ANETWORK_PUBLIC=>RW|
!TARGETS.IMPLEMENTATION.RCI_CUSTOMIZATION.I386_UNIX_ALS_XT
!TARGETS.IMPLEMENTATION.RCI_CUSTOMIZATION.I386_UNIX_ALS_XT.REV2_0_SPEC
!TARGETS.IMPLEMENTATION.RCI_CUSTOMIZATION.I386_UNIX_ALS_XT.REV2_0_2
procedure Install_Customization (Target_Key : String := "<DEFAULT>";
Release_Number : String := "<DEFAULT>";
Version : String := "<DEFAULT>");with Activity;
with Archive;
with Debug_Tools;
with Directory_Tools;
with Log;
with Links;
with Profile;
with Program;
with Simple_Status;
with String_Utilities;
procedure Install_Customization (Target_Key : String := "<DEFAULT>";
Release_Number : String := "<DEFAULT>";
Version : String := "<DEFAULT>") is
Bad_Current_Context : exception;
Def_Con : constant String := Directory_Tools.Naming.Default_Context;
Install_World_Prefix : constant String := "!Targets.Implementation.Release";
Profile_Kind : array (Simple_Status.Condition_Class) of Profile.Msg_Kind :=
(Simple_Status.Normal => Profile.Note_Msg,
Simple_Status.Warning => Profile.Warning_Msg,
Simple_Status.Problem => Profile.Error_Msg,
Simple_Status.Fatal => Profile.Error_Msg);
function Default_Release_Suffix return String is
begin
if Install_World_Prefix'Length < Def_Con'Length and then
String_Utilities.Equal
(Install_World_Prefix,
Def_Con (Def_Con'First ..
Def_Con'First + Install_World_Prefix'Length - 1),
Ignore_Case => True) then
return Def_Con (Def_Con'First + Install_World_Prefix'Length ..
Def_Con'Last);
else
raise Bad_Current_Context;
end if;
end Default_Release_Suffix;
function Get_Target_Key return String is
begin
if String_Utilities.Equal
(Release_Number, "<DEFAULT>", Ignore_Case => True) then
declare
Release_Suffix : constant String := Default_Release_Suffix;
Last_Underscore : constant Integer :=
String_Utilities.Reverse_Locate
(Fragment => "_", Within => Release_Suffix);
Second_To_Last_Underscore : constant Integer :=
String_Utilities.Reverse_Locate
(Fragment => "_",
Within => Release_Suffix (Release_Suffix'First ..
Last_Underscore - 1));
Third_To_Last_Underscore : constant Integer :=
String_Utilities.Reverse_Locate
(Fragment => "_",
Within => Release_Suffix
(Release_Suffix'First ..
Second_To_Last_Underscore - 1));
begin
if Third_To_Last_Underscore > Release_Suffix'First then
return Release_Suffix (Release_Suffix'First + 1 ..
Third_To_Last_Underscore - 1);
else
raise Bad_Current_Context;
end if;
end;
else
return Release_Number;
end if;
end Get_Target_Key;
function Get_Release_Number return String is
begin
if String_Utilities.Equal
(Release_Number, "<DEFAULT>", Ignore_Case => True) then
declare
Release_Suffix : constant String := Default_Release_Suffix;
Last_Underscore : constant Integer :=
String_Utilities.Reverse_Locate
(Fragment => "_", Within => Release_Suffix);
Second_To_Last_Underscore : constant Integer :=
String_Utilities.Reverse_Locate
(Fragment => "_",
Within => Release_Suffix (Release_Suffix'First ..
Last_Underscore - 1));
Third_To_Last_Underscore : constant Integer :=
String_Utilities.Reverse_Locate
(Fragment => "_",
Within => Release_Suffix
(Release_Suffix'First ..
Second_To_Last_Underscore - 1));
begin
if Third_To_Last_Underscore > Release_Suffix'First then
return Release_Suffix (Third_To_Last_Underscore + 1 ..
Last_Underscore - 1);
else
raise Bad_Current_Context;
end if;
end;
else
return Release_Number;
end if;
end Get_Release_Number;
function Get_Version return String is
begin
if String_Utilities.Equal
(Version, "<DEFAULT>", Ignore_Case => True) then
declare
Release_Suffix : constant String := Default_Release_Suffix;
Last_Underscore : constant Integer :=
String_Utilities.Reverse_Locate
(Fragment => "_", Within => Release_Suffix);
begin
if Last_Underscore > Release_Suffix'First then
return Release_Suffix
(Last_Underscore .. Release_Suffix'Last);
else
raise Bad_Current_Context;
end if;
end;
else
return Version;
end if;
end Get_Version;
function Release_World return String is
begin
return "!targets.implementation.release_" & Get_Target_Key &
"_" & Get_Release_Number & Get_Version;
end Release_World;
procedure Register_Target is
Key : constant String := Get_Target_Key;
The_Job : Program.Job_Id;
Status : Program.Condition;
begin
Log.Put_Line ("Registering target " & Key);
Program.Create_Job (S => Key & ".register",
Job => The_Job,
Status => Status,
Debug => False,
Context => "$",
After => 0.0,
Options => "",
Response => "<PROFILE>");
if Simple_Status.">=" (Simple_Status.Severity (Status),
Simple_Status.Problem) then
Log.Put_Line (Simple_Status.Display_Message (Status),
Profile_Kind (Simple_Status.Severity (Status)));
Log.Put_Line ("Can't register " & Key, Profile.Error_Msg);
raise Program_Error;
else
Program.Wait_For (The_Job);
end if;
Log.Put_Line ("Successfully registered target " & Key);
exception
when others =>
Log.Put_Line (Debug_Tools.Get_Exception_Name &
" raised in Register_Target");
raise;
end Register_Target;
procedure Do_Restore_Predefined is
begin
Log.Put_Line ("Restoring predefined world");
Archive.Restore (Objects => "[?,~!Targets." & Get_Target_Key & "]",
Use_Prefix => "*",
For_Prefix => "*",
Options => "changed_objects replace",
Device => Release_World & ".predefined_archive",
Response => "<PROFILE>");
Log.Put_Line ("Successfully restored predefined world");
exception
when others =>
Log.Put_Line (Debug_Tools.Get_Exception_Name &
" raised in Restore_Predefined",
Kind => Profile.Error_Msg);
raise;
end Do_Restore_Predefined;
procedure Restore_Predefined is
Predefined_World : Directory_Tools.Object.Handle :=
Directory_Tools.Naming.Resolution ("!targets." & Get_Target_Key);
begin
if Directory_Tools.Object.Is_Ok (Predefined_World) then
Register_Target;
end if;
Do_Restore_Predefined;
end Restore_Predefined;
procedure Merge_Activities is
begin
Log.Put_Line
("Merging " & Release_World &
".install_activity into !machine.release.current.activity");
Activity.Merge (Source => Release_World & ".install_activity",
Subsystem => "?",
Spec_View => "?",
Load_View => "?",
Mode => Activity.Exact_Copy,
Target => "!machine.release.current.activity",
Response => "<PROFILE>");
Log.Put_Line ("Successfully merged activities");
exception
when others =>
Log.Put_Line (Debug_Tools.Get_Exception_Name &
" raised in Merge_Activities",
Kind => Profile.Error_Msg);
raise;
end Merge_Activities;
procedure Replace_Links is
Key : constant String := Get_Target_Key;
begin
Log.Put_Line ("Replacing link to " & Key);
Links.Replace (Source => "!targets.implementation.Rci_customization." &
Key & "'spec_view.units." & Key,
Link => "#",
World => "!machine.release.current.commands",
Response => "<PROFILE>");
Log.Put_Line ("Successfully replaced link");
exception
when others =>
Log.Put_Line (Message => "Unable to define link to " & Key,
Kind => Profile.Warning_Msg);
Log.Put_Line (Debug_Tools.Get_Exception_Name &
" raised in Replace_Links");
end Replace_Links;
begin
Merge_Activities;
Replace_Links;
Restore_Predefined;
-- May require registering target if predefined world preexists.
--Register_Target;
exception
when Bad_Current_Context =>
Log.Put_Line ("Unable to install " & Target_Key &
" due to unhandled exception " &
Debug_Tools.Get_Exception_Name, Profile.Negative_Msg);
when others =>
Log.Put_Line ("Unable to install " & Get_Target_Key &
" due to unhandled exception " &
Debug_Tools.Get_Exception_Name, Profile.Negative_Msg);
end Install_Customization;