DataMuseum.dk

Presents historical artifacts from the history of:

Rational R1000/400

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

See our Wiki for more about Rational R1000/400

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - download

⟦8bcd2d1d6⟧ Ada Source

    Length: 25600 (0x6400)
    Types: Ada Source
    Notes: 03_class, FILE, R1k_Segment, e3_tag, generic, package Enp_Driver, pragma Module_Name Module_Names.Vpid_For_Kernel 449, pragma Subsystem Kernel, seg_002fd7

Derivation

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

E3 Source Code



with Module_Names;
with Processor_Manager;
with Substrate;
with System;
with Virt_Mem_Defs;
--
package Enp_Driver is

    -- Primitives to access an ENP-100 series Ethernet controller in the IOP.
    -- The ENP-100 is manufactured by Communication Machinery Corporation.

    pragma Subsystem (Kernel, Private_Part => Closed);
    pragma Module_Name (Module_Names.Vpid_For_Kernel, 449);
    -- pragma Assert (449 = Kernel_Module_Names.Segment_for_Enp_Driver);
    -- avoid compilation dependency on Kernel_Module_Names.

    subtype Byte is System.Byte;
    subtype Byte_String is System.Byte_String;
    Null_Byte_String : constant Byte_String (1 .. 0) := (others => 0);

    Forever : constant Duration := Duration'Last;

    type Status_Type is (Ok, No_Hardware, Not_Configured, Already_Open,
                         Not_Open, Not_Registered, Too_Many_Clients, Timed_Out);
    -- OK: operation succeeded.
    -- No_Hardware: Enp_Driver.Installed = False.
    -- Not_Configured: Configure has not been called since Reset.
    -- Not_Open: Channel is not open.
    -- Not_Registered: some task other than the caller is registered.
    -- Too_Many_Clients: another task is executing the same operation.
    -- Timed_Out: Max_Wait elapsed, and the operation was not performed.

    procedure Reset (Status : out Status_Type);
    -- Cause a hardware reset in the ENP controller board.
    -- The immediate outcome is returned by Installed and
    -- Driver_Version (below); in addition you should read
    -- Startup.Control_Status to see if self-test succeeds.
    -- A side-effect of Reset is to Close all open channels.
    -- If another task is presently executing Reset, return
    -- Status := Too_Many_Clients and do nothing.

    function Installed return Boolean;
    -- Return true iff the ENP hardware is installed in this machine,
    -- and responded correctly to Reset.

    function Driver_Version return Natural;
    -- If Installed = True, return the version of the ENP driver
    -- software that is presently running in the IOP; otherwise return
    Null_Driver_Version : constant Natural := 0;

    type Address is range 0 .. (2 ** 24) - 1;
    -- These are linear byte addresses: Address'(0) denotes the first
    -- byte of ENP RAM (controller memory), and consecutive values
    -- denote consecutive ENP RAM bytes.

    procedure Read (Status : out Status_Type;
                    First : Address;
                    Data : out Byte_String;
                    Count : out Natural);
    -- Read Data from controller memory, starting at First.
    -- Return Count = the number of bytes actually read.
    -- If another task is presently executing Read, return
    -- Status := Too_Many_Clients and do nothing.

    procedure Write (Status : out Status_Type;
                     First : Address;  
                     Data : Byte_String;  
                     Count : out Natural);
    -- Write Data into controller memory, starting at First.
    -- Return Count = the number of bytes actually written.
    -- If another other task executed Reset most recently,
    -- or another task is presently excecuting Write, return
    -- Status := Too_Many_Clients and do nothing.

    -- If Read or Write fails entirely, return Count = 0.
    -- Count may be less than Data'Length if there isn't
    -- that much ENP RAM, or Data won't fit into a page.

    type Channel_Number is range 0 .. 63;

    procedure Configure (Status : out Status_Type;
                         Max_Channel : Channel_Number;
                         Byte_12 : Byte := 0; -- reserved
                         Max_Small_Buffers : Byte;
                         Max_Medium_Buffers : Byte;
                         Max_Large_Buffers : Byte;
                         Max_Wait : Duration := Forever);
    -- Exchange a CONFIGURE command with the IOP.
    -- Max_Channel is the largest Channel_Number that may be used for I/O.
    -- Max_@_Buffers is the maximum number of @-sized buffers that may be
    -- allocated to a single channel.
    -- If another other task executed Reset most recently, or another task
    -- is presently executing Configure, return Status := Too_Many_Clients.
    -- Otherwise, write the correct value into SHARED.Hostbase, write zero
    -- into SHARED.Enpbase, and interrupt the ENP.  If any of this cannot
    -- be done, return Status := Not_Configured.  Wait for the ENP to pass
    -- a WAKE_BFRTYPE (and interrupt) to the IOP.  If Max_Wait elapses
    -- first, call Reset and then return Status := Timed_Out.  Otherwise,
    -- return Status := OK; the caller must read Shared.Status to see if
    -- the controller configuration succeeded, and if it did call

    procedure Configured;
    -- The controller has been successfully downloaded and configured.
    -- Until the controller crashes or is Reset, allow Open/Put/Get/etc.
    -- If another task executed Reset most recently, do nothing.

    subtype Unique_Id is Integer;
    Null_Unique_Id : constant Unique_Id := Unique_Id'First;

    type Channel_Id is
        record
            Number : Channel_Number;
            Unique : Unique_Id; -- to catch dangling (stale) Channel_Id's
        end record;

    Null_Channel_Id : constant Channel_Id :=
       (Channel_Number'First, Null_Unique_Id);

    procedure Open (Channel : Channel_Id;
                    Status : out Status_Type;
                    Type_Dependent_Bytes : Byte);
    -- If Is_Open (Channel.Number) then return Status := Already_Open;
    -- otherwise open Channel.
    -- Subsequent buffers delivered from the controller via e_tohost
    -- with b_type = BFRTYPE or TO_BFRTYPE will be returned from Get
    -- with Type_Dependent_Bytes following the BFR part of the header;
    -- Get.Header_Length will return 32 + Type_Dependent_Bytes for a
    -- verbose input buffer, or Type_Dependent_Bytes for a terse buffer.

    procedure Close (Channel : Channel_Id; Status : out Status_Type);
    -- If Is_Open (Channel) then close it;
    -- otherwise return Status := Not_Open.

    procedure Put (Channel : Channel_Id;
                   Status : out Status_Type;
                   Header, Data : Byte_String;
                   Immediate : Boolean := False;
                   Max_Wait : Duration := Forever);
    -- Pass one buffer, containing Header & Data, to the ENP controller.
    -- Header & Data contain a BCH, space for protocol headers, and a BDB.
    -- Data ordinarily contains the BDB, but this is NOT required: Header
    -- and Data are catentated before splitting them into their parts.
    -- If no buffer space is available, wait as long as Max_Wait for it.
    -- Immediate => this buffer should be passed to the ENP immediately,
    -- even if there is no buffer space available for non-Immediate buffers.
    -- Use Immediate = True only if the buffer will be returned promptly:
    -- an Immediate Put will block if there is another outstanding.

    procedure Put (Channel : Channel_Id;
                   Status : out Status_Type;
                   B_Msglen : Natural;
                   B_Type : Byte; -- BFRTYPE or TO_BFRTYPE only
                   Header_Bytes : Byte;
                   Header, Data : Byte_String;
                   Max_Wait : Duration := Forever);
    -- Pass one buffer, containing Header & Data, to the ENP controller.
    -- Header & Data contain the type-dependent part of a BCH and a BDB,
    -- but neither the type-independent BFR nor space for protocol headers.
    -- Although less flexible, this form of Put uses less time and space.
    -- It has the same effect as:
    -- Put (Channel, Status,
    --      Header & Data => BFR'(B_Device => Channel.Number,
    --                            B_Flags => 0,
    --                            B_Msglen => B_Msglen,
    --                            B_Type => B_Type)
    --                        & (Header & Data) (1..B_Type_Bytes)
    --                        & (1..Header_Bytes => <dont care>)
    --                        & (Header & Data) (B_Type_Bytes+1..Last),
    --      Max_Wait => Max_Wait);
    -- where B_Type_Bytes is a function of B_Type: 0 if B_Type=BFRTYPE,
    -- or 16 if B_Type=TO_BFRTYPE.  Other values of B_Type are not supported.
    -- Data ordinarily contains the BDB, but this is NOT required: Header
    -- and Data are catentated before splitting them into their parts.

    procedure Get (Channel : Channel_Id;
                   Status : out Status_Type;
                   Header, Data : out Byte_String;
                   Header_Length, Data_Length : out Natural;
                   Fragment : Boolean := False;
                   Max_Wait : Duration := Forever);
    -- Get (..., Preview => True, ...).
    -- See the more general form of Get, below.

    Get_Buffer_Ready : array (Channel_Number) of Boolean := (others => False);
    -- Get_Buffer_Ready (C) = true iff at least one input buffer is buffered,
    -- ready to be returned by Get.  Use this as a hint: it may change before
    -- you take action on it (call Get, for example).

    procedure Register_To_Put (Channel : Channel_Id;
                               Client : Processor_Manager.Task_Id);
    procedure Register_To_Get (Channel : Channel_Id;
                               Client : Processor_Manager.Task_Id);

    procedure Un_Register_To_Put (Channel : Channel_Id);
    procedure Un_Register_To_Get (Channel : Channel_Id);

    function Channel (Number : Channel_Number) return Channel_Id;
    -- Return a presently-open channel with the specified Number,
    -- or Null_Channel_Id if there is no such channel open.

    function Is_Open (Channel : Channel_Id) return Boolean;
    -- Return true iff Channel is presently open.
    -- Is_Open (Null_Channel_Id) = False.

    function Is_Open (Number : Channel_Number) return Boolean;
    -- Return Is_Open (Channel (Number));

    generic
        with procedure Put_Line (Data : String);
    procedure Put_Trace (Entries : Natural := 16; Go_Back : Natural := 0);
    -- Print out the most recent entries in the event trace.  The event
    -- trace contains a time sequence of various interesting events that
    -- occur in the Enp_Driver task.  It is useful mainly for debugging.

    procedure Scavenge (Status : out Status_Type);
    -- Un-wire surplus wired pages.  Check for stuck channels.
    -- This procedure should be called about once a minute,
    -- so long as Status := OK.

    package Machine_Time is

        subtype Duration is Long_Integer;

        function Convert (D : Duration) return Standard.Duration;
        pragma Inline (Convert);

        function Convert (D : Standard.Duration) return Duration;
        pragma Inline (Convert);

        function Time_Since_Ipl return Duration;
        pragma Inline (Time_Since_Ipl);

        type Deadline is private;

        function Start (Time_To_Go : Standard.Duration) return Deadline;

        function Time_To_Go (Timer : Deadline) return Standard.Duration;

        function Expired (Timer : Deadline) return Boolean;

    private
        type Deadline is new Duration; -- the Time_Since_IPL of expiration
    end Machine_Time;
    pragma Integrate (Machine_Time);

    type Iop_Address is new Long_Integer range 0 .. (2 ** 32) - 1;
    -- These are the addresses used by the IOP 680x0 CPU.

    type Iop_Quanta is (Bytes, Words, Longs);
    -- The IOP can read and write data in any of these quanta.
    -- Sometimes (depending on the IOP_Address) it matters.

    Quantum_Length : constant array (Iop_Quanta) of Positive := (1, 2, 4);
    -- The number of bytes in each quantum.

    procedure Read (First : Iop_Address;
                    Data : out Byte_String;
                    Count : out Natural;
                    Quantum : Iop_Quanta := Bytes);
    -- Read Data from IOP address space, starting at First.
    -- Return Count = the number of bytes actually read.

    procedure Write (First : Iop_Address;  
                     Data : Byte_String;  
                     Count : out Natural;
                     Quantum : Iop_Quanta := Bytes);
    -- Write Data into IOP address space, starting at First.
    -- Return Count = the number of bytes actually written.

    -- If Read or Write fails entirely, return Count = 0.
    -- Count may be less than Data'Length if Data'Length is
    -- not a multiple of Quantum, or Data cannot fit into an
    -- IOP command, or a nonexistent range of IOP_Addresses
    -- is referenced.

    package Iop_Defs is

        package Filler is
            subtype Filler is Long_Integer;
            subtype Filler_1 is Filler range 0 .. 2 ** 1 - 1;
            subtype Filler_2 is Filler range 0 .. 2 ** 2 - 1;
            subtype Filler_4 is Filler range 0 .. 2 ** 4 - 1;
            subtype Filler_5 is Filler range 0 .. 2 ** 5 - 1;
            subtype Filler_7 is Filler range 0 .. 2 ** 7 - 1;
            subtype Filler_8 is Filler range 0 .. 2 ** 8 - 1;
            subtype Filler_16 is Filler range 0 .. 2 ** 16 - 1;
        end Filler;
        pragma Integrate (Filler);

        type Unit_Number is new Filler.Filler_8;

        package Enp_Defs is

            type Command_Type is new Filler.Filler_7;
            Reset : constant Command_Type := 0;
            Write : constant Command_Type := 1;
            Read : constant Command_Type := 2;
            Configure : constant Command_Type := 3;
            Input : constant Command_Type := 4;
            Control : constant Command_Type := 5;
            Immediate : constant Command_Type := 6;
            Transmit : constant Command_Type := 7;
            Cancel : constant Command_Type := 8;

            type Enp_Command is
                record
                    Unit : Unit_Number;
                    Hld : Boolean;
                    Command : Command_Type;
                    Byte_12 : System.Byte;
                    Byte_13 : System.Byte;
                    Byte_14 : System.Byte;
                    Byte_15 : System.Byte;
                end record;

            type Enp_Response is
                record
                    Byte_13 : System.Byte;
                    Byte_14 : System.Byte;
                    Byte_15 : System.Byte;
                end record;

            -- Byte fields are numbered from byte 0 at the beginning of
            -- the entire Sysbus header (not just the Control_Part).

        end Enp_Defs;
        pragma Integrate (Enp_Defs);

        package Debug_Defs is

            type Command is
                record
                    Count : System.Byte;
                    Command : System.Byte;
                    Address : Iop_Address;
                end record;

            type Response is
                record
                    Byte_13 : Filler.Filler_8;
                    Count : Filler.Filler_16;
                end record;

        end Debug_Defs;
        pragma Integrate (Debug_Defs);

        --------------------------------------------------------------
        --
        --     Control portion of R1000 --> IOP packet
        --
        ---------------------------------------------------------------

        type Device_Kind is (Nil, Dh11, Rh11, Ts11, If11, Exos, Enp, Debug);

        type Sequence_Number is
           new Natural range 0 .. Substrate.Max_Ioa_Buffers - 1;

        type Virtual_Buffer_Number is new Natural range 0 .. 57;
        Null_Virtual_Buffer_Number : constant Virtual_Buffer_Number := 0;

        type Iop_Command (Slop_9_13 : Filler.Filler_4 := 0;
                          Device : Device_Kind := Nil) is
            record
                Slop_16_19 : Filler.Filler_4;
                Queue_Position : Sequence_Number;
                Slop_24_25 : Filler.Filler_2;
                Map_Location : Virtual_Buffer_Number;
                Slop_32_35 : Filler.Filler_4;
                Command_Packet : Substrate.Packet_Id;
                Is_Last_Part : Boolean;
                Slop_41_44 : Filler.Filler_4;
                Resume_Operation : Boolean;
                Slop_46_46 : Filler.Filler_1;
                Expects_Multi_Part_Response : Boolean;
                case Device is
                    when Enp | Debug =>
                        Enp : Enp_Defs.Enp_Command;
                        -- when Debug =>
                        --     Debug : Debug_Defs.Command;
                    when others =>
                        null;
                end case;
            end record;

        -- The UNIT, and device command are guaranteed to be the same
        -- in all parts of the same command.

        --------------------------------------------------------------
        --
        --     Control portion of IOP --> R1000 packet
        --
        ---------------------------------------------------------------

        type Iop_Response is
            record
                Slop_0_15 : Filler.Filler_16;
                Slop_16_31 : Filler.Filler_16;
                Slop_32_39 : Filler.Filler_8;
                Is_Last_Part : Boolean;
                Slop_41_45 : Filler.Filler_5;
                Success : Boolean;
                Slop_47 : Filler.Filler_1;
                Slop_48_63 : Filler.Filler_16;
                Slop_64_71 : Filler.Filler_8;
                Enp : Enp_Defs.Enp_Response;
            end record;

        -- Assume that a request enables the IOP to send packets for parts
        -- 0..n-1.  The IOP may choose to send fewer than n packets back.
        -- The R1000 knows how many packets are coming back because the last
        -- one has IS_LAST_PART set.  Thus, assuming IS_LAST_PART is set on
        -- part i, the R1000 will get packets for 0..i, and no packets for
        -- i+1..n-1.  Also beware that the actual arrival order of packets is
        -- unrelated to their logical ordering.

        function To_Control_Part (Cmd : Iop_Command)
                                 return Substrate.Control_Part;
        function To_Iop_Response
                    (Control : Substrate.Control_Part) return Iop_Response;

        -- Unchecked conversions.

    end Iop_Defs;
    pragma Integrate (Iop_Defs);

    Bits_Per_Page : constant Natural := Virt_Mem_Defs.Bits_Per_Page;
    Bytes_Per_Page : constant Natural := Bits_Per_Page / System.Byte'Size;

    subtype Byte_Count is Natural range 0 .. Bytes_Per_Page;

    type Trace_Element_Kind is
       (Nil, Enp_Command, Enp_Response, Enp_Output_Signal);

    type Trace_Element (Kind : Trace_Element_Kind := Nil) is
        record
            Timestamp : Machine_Time.Duration := 0;
            Packet : Substrate.Packet_Id := Substrate.Nil_Packet_Id;
            Data_Bytes : Byte_Count := 0;
            case Kind is
                when Enp_Command =>
                    Resume : Boolean;
                    Command : Iop_Defs.Enp_Defs.Enp_Command;
                when Enp_Response =>
                    Dropsy : Boolean;
                    Success : Boolean;
                    Response : Iop_Defs.Enp_Defs.Enp_Response;
                when Enp_Output_Signal =>
                    Channel : Iop_Defs.Filler.Filler_16;
                    -- Data_Bytes is Max_Bytes
                when others =>
                    null;
            end case;
        end record;

    type Trace_String is array (Natural range <>) of Trace_Element;

    function Get_Trace (Entries : Natural := 16; Go_Back : Natural := 0)
                       return Trace_String;
    -- Return the first Entries of the most recent (Entries + Go_Back).
    -- The returned Trace_String'Length may be less than Entries
    -- if fewer than Entries events have occurred since booting, or
    -- if the trace buffer is shorter than (Entries).

    procedure Put (Channel : Channel_Id;
                   Status : out Status_Type;
                   Bfr : out Iop_Address;
                   Header, Data : Byte_String;
                   Immediate : Boolean := False;
                   Max_Wait : Duration := Forever);
    -- Store one buffer, containing Header & Data, in ENP RAM, but do NOT
    -- pass it to the ENP.  Return Bfr := the address where it was stored.
    -- Header & Data contain a BCH, space for protocol headers, and a BDB.
    -- Data ordinarily contains the BDB, but this is NOT required: Header
    -- and Data are catentated before splitting them into their parts.
    -- If no buffer space is available, wait as long as Max_Wait for it.
    -- Immediate => allocate buffer space from the pool that is used for
    -- buffers to be passed to the controller immediately.
    -- Use Immediate = True only if the buffer will be returned promptly:
    -- an Immediate Put will block if there is another outstanding.

    procedure Get (Channel : Channel_Id;
                   Status : out Status_Type;
                   Header, Data : out Byte_String;
                   Header_Length, Data_Length : out Natural;
                   Preview : Boolean; -- := false
                   Fragment : Boolean := False;
                   Max_Wait : Duration := Forever);
    -- Return the contents of one buffer received from the ENP.
    -- If no buffer is waiting, wait as long as Max_Wait for one.
    -- If Preview, do not drop the returned buffer from the queue;
    -- a subsequent call to Get will return the same buffer again.
    -- If a verbose INPUT response was received then
    --     return the BCH to Header/Header_Length, and return the
    --     BDB to Data/Data_Length.  If the BCH is longer than
    --     Header'Length, return Header_Length > Header'Length;
    --     the excess bytes (not returned to Header) are lost.
    --     If the BDB is longer than Data'Length then
    --         return Data_Length > Data'Length.
    -- If a terse INPUT response was received then
    --     return the first Type_Dependent_Bytes (from Open)
    --     of the data pages to Header/Header_Length; and
    ---    return the remaining bytes to Data/Data_Length.
    --     If the number of remaining bytes > Data'Length then
    --         return Data_Length > Data'Length.
    -- If Data_Length > Data'Length then
    --     If Fragment and
    --     ((input was terse) or (input b_type = BFRTYPE or TO_BFRTYPE)) then
    --         subsequent Get operations will return fragments to
    --         Data with Header_Length = 0 and Data_Length = the
    --         number of remaining bytes (including Data'Length),
    --         until the last fragment is returned with
    --         Header_Length = 0 and Data_Length <= Data'Length;
    --     else
    --         the excess bytes (not returned to Data) are lost.

end Enp_Driver;

E3 Meta Data

    nblk1=18
    nid=0
    hdr6=30
        [0x00] rec0=1c rec1=00 rec2=01 rec3=006
        [0x01] rec0=14 rec1=00 rec2=02 rec3=014
        [0x02] rec0=16 rec1=00 rec2=03 rec3=006
        [0x03] rec0=14 rec1=00 rec2=04 rec3=05c
        [0x04] rec0=10 rec1=00 rec2=05 rec3=01c
        [0x05] rec0=17 rec1=00 rec2=06 rec3=056
        [0x06] rec0=12 rec1=00 rec2=07 rec3=054
        [0x07] rec0=13 rec1=00 rec2=08 rec3=032
        [0x08] rec0=13 rec1=00 rec2=09 rec3=03e
        [0x09] rec0=15 rec1=00 rec2=0a rec3=018
        [0x0a] rec0=19 rec1=00 rec2=0b rec3=04e
        [0x0b] rec0=1c rec1=00 rec2=0c rec3=024
        [0x0c] rec0=17 rec1=00 rec2=0d rec3=06e
        [0x0d] rec0=18 rec1=00 rec2=0e rec3=01e
        [0x0e] rec0=1e rec1=00 rec2=0f rec3=01e
        [0x0f] rec0=1c rec1=00 rec2=10 rec3=016
        [0x10] rec0=17 rec1=00 rec2=11 rec3=036
        [0x11] rec0=18 rec1=00 rec2=12 rec3=084
        [0x12] rec0=19 rec1=00 rec2=13 rec3=008
        [0x13] rec0=18 rec1=00 rec2=14 rec3=034
        [0x14] rec0=11 rec1=00 rec2=15 rec3=03e
        [0x15] rec0=12 rec1=00 rec2=16 rec3=00c
        [0x16] rec0=11 rec1=00 rec2=17 rec3=018
        [0x17] rec0=06 rec1=00 rec2=18 rec3=000
    tail 0x20f0012f2000806a63c27 0x42a00088462060003