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

⟦de5e66ca7⟧ Ada Source

    Length: 11264 (0x2c00)
    Types: Ada Source
    Notes: 03_class, FILE, R1k_Segment, e3_tag, package body Enp, seg_002fd9

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 Io;
with Log;
with Profile;
with Substrate;
with System;
with Time_Utilities;
--
package body Enp is

    package Iop_Defs renames Enp_Driver.Iop_Defs;
    package Machine_Time renames Enp_Driver.Machine_Time;

    subtype Byte is Enp_Driver.Byte;

    function "+" (L, R : Byte) return Byte renames System."+";
    function "/" (L, R : Byte) return Byte renames System."/";
    function "mod" (L, R : Byte) return Byte renames System."mod";

    function "=" (L, R : Enp_Driver.Status_Type) return Boolean
        renames Enp_Driver."=";

    function "+" (L, R : Address) return Address renames Enp_Driver."+";
    function "<=" (L, R : Address) return Boolean renames Enp_Driver."<=";

    Radix : constant := 16;
    subtype Nybble is Byte range 0 .. 15;

    Digit : constant array (Nybble) of Character :=
       ('0', '1', '2', '3', '4', '5', '6', '7',
        '8', '9', 'a', 'b', 'c', 'd', 'e', 'f');

    function Image (B : Byte_String) return String is
        S : String (1 .. B'Length * 2);
        Si : Positive := S'First;
    begin
        for Bi in B'Range loop
            S (Si .. Si + 1) := (Digit (B (Bi) / Radix),
                                 Digit (B (Bi) mod Radix));
            Si := Si + 2;
        end loop;
        return S;
    end Image;

    function Image (A : Address) return String is
        N : Natural := Natural (A);
        S : String (1 .. 5);
    begin
        for Si in reverse S'Range loop
            S (Si) := Digit (Nybble (N mod Radix));
            N := N / Radix;
        end loop;
        return S;
    end Image;

    procedure Check (Status : Enp_Driver.Status_Type; From : String) is
    begin
        if Status /= Enp_Driver.Ok then
            Log.Put_Line (From & ".Status = " &
                          Enp_Driver.Status_Type'Image (Status),
                          Profile.Error_Msg);
        end if;
    end Check;

    procedure Reset is
        Status : Enp_Driver.Status_Type;
    begin
        Enp_Driver.Reset (Status);
        Check (Status, "Enp_Driver.Reset");
        if Enp_Driver.Installed then
            Log.Put_Line ("Driver_Version =" &
                          Natural'Image (Enp_Driver.Driver_Version));
        else
            Log.Put_Line ("not Installed", Profile.Warning_Msg);
        end if;
    end Reset;

    procedure Read (First : Address; Length : Natural := 16) is
        Data : Enp_Driver.Byte_String (1 .. Length);
        Count : Natural;
        Status : Enp_Driver.Status_Type;
    begin
        Enp_Driver.Read (Status, First, Data, Count);
        Check (Status, "Enp_Driver.Read");
        if Count > 0 then
            Log.Put_Line (Image (First) & ": " &
                          Image (Data (Data'First .. Data'First + Count - 1)));
        end if;
        -- if Count < Length then
        --     Log.Put_Line ("actually read" & Natural'Image (Count) & " bytes",
        --                   Profile.Warning_Msg);
        -- end if;
    end Read;

    procedure Scan (First : Address := Address'First;
                    Last : Address := Address'Last;
                    Step : Positive := 2) is
        A : Address := First;
        Ok : Boolean := True;
        Data : Enp_Driver.Byte_String (1 .. Step);
        Count : Natural;
        Status : Enp_Driver.Status_Type;
    begin
        while A <= Last loop
            Enp_Driver.Read (Status, A, Data, Count);
            Check (Status, "Enp_Driver.Read");
            exit when Status /= Enp_Driver.Ok;
            if Count = Data'Length then
                if not Ok then
                    Log.Put_Line (Image (A), Profile.Positive_Msg);
                    Ok := True;
                end if;
            else
                if Ok then
                    Log.Put_Line (Image (A + Address (Count)),
                                  Profile.Negative_Msg);
                    Ok := False;
                end if;
            end if;
            if Count > 0 then
                A := A + Address (Count);
            else
                A := A + Address (Step);
            end if;
        end loop;
    end Scan;

    procedure Write (First : Address; Data : Byte_String) is
        Count : Natural;
        Status : Enp_Driver.Status_Type;
    begin
        Enp_Driver.Write (Status, First, Data, Count);
        Check (Status, "Enp_Driver.Write");
        if Count > 0 then
            Log.Put_Line (Image (First) & ":=" &
                          Image (Data (Data'First .. Data'First + Count - 1)));
        end if;
        -- if Count < Data'Length then
        --     Log.Put_Line ("actually wrote" & Natural'Image (Count) & " bytes",
        --                   Profile.Warning_Msg);
        -- end if;
    end Write;

    procedure Put_Timing (Entries : Natural := 16; Go_Back : Natural := 0) is
        T : constant Enp_Driver.Trace_String :=
           Enp_Driver.Get_Trace (Entries, Go_Back);
        procedure Put_Line (Line : String) is
        begin
            Io.Put_Line (Line);
        end Put_Line;
        procedure Put (E : Enp_Driver.Trace_Element;
                       Previous : Machine_Time.Duration := 0) is
            function Image (Command : Iop_Defs.Enp_Defs.Command_Type)
                           return String is
            begin
                case Command is
                    when Iop_Defs.Enp_Defs.Reset =>
                        return " RESET";
                    when Iop_Defs.Enp_Defs.Write =>
                        return " WRITE";
                    when Iop_Defs.Enp_Defs.Read =>
                        return " READ";
                    when Iop_Defs.Enp_Defs.Configure =>
                        return " CONFIGURE";
                    when Iop_Defs.Enp_Defs.Input =>
                        return " INPUT";
                    when Iop_Defs.Enp_Defs.Control =>
                        return " CONTROL";
                    when Iop_Defs.Enp_Defs.Immediate =>
                        return " IMMEDIATE";
                    when Iop_Defs.Enp_Defs.Transmit =>
                        return " TRANSMIT";
                    when Iop_Defs.Enp_Defs.Cancel =>
                        return " ABORT";
                    when others =>
                        return Iop_Defs.Enp_Defs.Command_Type'Image (Command);
                end case;
            end Image;
            function Image (Flag : Boolean; Name : String) return String is
            begin
                if Flag then
                    return ", " & Name;
                else
                    return "";
                end if;
            end Image;
            function Preface return String is
            begin
                return '+' & Time_Utilities.Image
                                (Machine_Time.Convert (Previous)) &
                          Machine_Time.Duration'Image (E.Timestamp) & ": ";
            end Preface;
        begin
            case E.Kind is
                when Enp_Driver.Nil =>
                    Put_Line ("<nil>");
                when Enp_Driver.Enp_Command =>
                    Put_Line (Preface & "command" &
                              Substrate.Packet_Id'Image (E.Packet) &
                              Image (E.Resume, "RESUME") & ':' &
                              Image (E.Command.Command) &  
                              Image (E.Command.Hld, "HLD") & ", unit" &
                              Iop_Defs.Unit_Number'Image (E.Command.Unit) &  
                              ',' & System.Byte'Image (E.Command.Byte_12) &
                              ',' & System.Byte'Image (E.Command.Byte_13) &
                              ',' & System.Byte'Image (E.Command.Byte_14) &
                              ',' & System.Byte'Image (E.Command.Byte_15) &
                              ';' & Natural'Image (E.Data_Bytes) & " bytes");  
                when Enp_Driver.Enp_Response =>
                    Put_Line (Preface & "response" &
                              Substrate.Packet_Id'Image (E.Packet) &
                              Image (not E.Success, "NOT SUCCESS") &  
                              ':' & System.Byte'Image (E.Response.Byte_13) &
                              ',' & System.Byte'Image (E.Response.Byte_14) &
                              ',' & System.Byte'Image (E.Response.Byte_15) &
                              Image (E.Dropsy, "DROPSY") & ';' &
                              Natural'Image (E.Data_Bytes) & " bytes");  
                when Enp_Driver.Enp_Output_Signal =>
                    Put_Line (Preface & "response" &
                              Substrate.Packet_Id'Image (E.Packet) &
                              ":         output signal" &
                              Iop_Defs.Filler.Filler_16'Image (E.Channel) &
                              ", max_bytes" & Natural'Image (E.Data_Bytes));  
            end case;
        end Put;
    begin
        if T'Length > 0 then
            Put (T (T'First));
            for I in T'First + 1 .. T'Last loop
                Put (T (I), Previous => T (I).Timestamp - T (I - 1).Timestamp);
            end loop;
        end if;
    end Put_Timing;

    procedure Trace (Entries : Natural := 8;
                     Go_Back : Natural := 0;
                     Raw : Boolean := False) is
        procedure Put_Raw is new Enp_Driver.Put_Trace (Io.Put_Line);
    begin
        if Raw then
            Put_Raw (Entries, Go_Back);
        else
            Put_Timing (Entries, Go_Back);
        end if;
    end Trace;

end Enp;

E3 Meta Data

    nblk1=a
    nid=0
    hdr6=14
        [0x00] rec0=21 rec1=00 rec2=01 rec3=04a
        [0x01] rec0=20 rec1=00 rec2=02 rec3=022
        [0x02] rec0=19 rec1=00 rec2=03 rec3=090
        [0x03] rec0=1a rec1=00 rec2=04 rec3=06c
        [0x04] rec0=1d rec1=00 rec2=05 rec3=008
        [0x05] rec0=16 rec1=00 rec2=06 rec3=014
        [0x06] rec0=17 rec1=00 rec2=07 rec3=066
        [0x07] rec0=11 rec1=00 rec2=08 rec3=094
        [0x08] rec0=0f rec1=00 rec2=09 rec3=07a
        [0x09] rec0=1a rec1=00 rec2=0a rec3=000
    tail 0x20f001326000806ab6b11 0x42a00088462060003