Google
 

Trailing-Edge - PDP-10 Archives - BB-X117B-SB_1986 - 10,7/nml/knit10.b36
There are no other files named knit10.b36 in the archive.
%sbttl 'TOPS-10 Specific Ethernet Routines'


!
! Definitions needed for debugging
!

external
    %debug_data_base;


!
! Forward routines
!

forward routine
    BUILD_PARAMETER_DATA,
    POST_RECEIVE_BUFFER: vanilla_interrupt_linkage,
    ETHNT_PSI_INTERRUPT: vanilla_interrupt_linkage
			 novalue;


!
! Literals
!

literal
    FWORD = %O'777777777777',		! Full word mask
    LOAD_DUMP_PROTOCOL = %X'6001',	! LOAD-DUMP protocol
    MOP_BUFFER_LENGTH = 1504,		! MOP message buffer in bytes
    MOP_BUFFER_SIZE = ch$allocation (MOP_BUFFER_LENGTH, 8),
    MOP_BUFFER_ALLOCATION = MOP_BUFFER_SIZE * %upval;


!
! Macros
!

macro
    ETHNT_ARG_BLOCK = vector [4] volatile %,	! ETHNT UUO argument block
    UBD_ARG_BLOCK = vector [$UBLEN] volatile %,	! User buffer descriptor
    LLMOP_ARG_BLOCK = monblock [10] volatile %,	! LLMOP UUO argument block
    PSI_ARG_BLOCK = vector [3] volatile %;	! PISYS. UUO argument block
macro
    CH$HEX [ ] =
	uplit (X_CHAR(%explode(%remaining))) %;

macro
    X_CHAR [B1,B2,B3,B4,B5,B6,B7,B8] =
            ((%X B1 ^ (%bpval-4))
              %if not %null(B2)
              %then
                   or (%X B2 ^ (%bpval-8))
              %if not %null(B3)
              %then
                   or (%X B3 ^ (%bpval-12))
              %if not %null(B4)
              %then
                   or (%X B4 ^ (%bpval-16))
              %if not %null(B5)
              %then
                   or (%X B5 ^ (%bpval-20))
              %if not %null(B6)
              %then
                   or (%X B6 ^ (%bpval-24))
              %if not %null(B7)
              %then
                   or (%X B7 ^ (%bpval-28))
              %if not %null(B8)
              %then
                   or (%X B8 ^ (%bpval-32))
              %fi %fi %fi %fi %fi %fi %fi) %;


bind
    LDA_MULTICAST = CH$HEX ('AB0000010000');
%routine ('OPEN_KLNI_DEVICE', CD: ref CD_BLOCK, RSP_POINTER) =

!++
! Functional description:
!
!	This routine is called by NMU$KLNI_OPEN to perform
!	system specific operations for servicing a KLNI.
!
! Formal parameters:
!
!	.CD			Pointer to circuit data block
!	.RSP_POINTER		Pointer to NICE response buffer
!
! Routine value:
!
!	$true			System specific open succeeded
!	$false			Error opening KLNI
!
!--

begin

    builtin
	UUO;

    register
	T1;

    local
	ETHNT_BLOCK: ETHNT_ARG_BLOCK,
	PSI_BLOCK: PSI_ARG_BLOCK;

    !
    ! If not LOAD-DUMP ASSISTANCE, return now
    !

    if .CD [CD_USAGE] neq DLX_LDA
    then return $true;

    !
    ! Enable Ethernet PSI interrupts
    !

    CD [CD_KLNI_PSI] = ALLOCATE_INTERRUPT_CHANNEL (ETHNT_PSI_INTERRUPT, .CD);

    PSI_BLOCK [$PSECN] = $PCETH;
    PSI_BLOCK [$PSEOR] = (.CD [CD_KLNI_PSI]*4)^18;
    PSI_BLOCK [$PSEPR] = 0;

    T1 = PS$FAC + PSI_BLOCK;

    if not UUO (1, PISYS$ (T1))
    then
	begin
	    $RESPONSE (.RSP_POINTER, NICE$_OPF, 0,
		       'Enable PSI failed for %X.  PISYS. error %O',
		       (ch$ptr (CD [CD_NAME],,8)),
		       .T1);
	    CLOSE_KLNI_DEVICE (.CD);
	    return $false;
	end;

    CD [CD_KLNI_PSI_STS] = 0;

    !
    ! Initialize interrupt event blocks
    !

    NMU$SCHED_EVENT (CD [CD_KLNI_RCV_EVB], $true);
    NMU$SCHED_EVENT (CD [CD_KLNI_XMT_EVB], $true);

    !
    ! Open LOAD-DUMP Protocol
    !

    ETHNT_BLOCK [$ETFCN] = $ETOPN^18 or 4;
    ETHNT_BLOCK [$ETPSW] = 0;
    ETHNT_BLOCK [$ETCIW] = .CD [CD_KLNI_CHAN];
    ETHNT_BLOCK [$ETPIW] = ET$PAD+ LOAD_DUMP_PROTOCOL;

    T1 = ETHNT_BLOCK;

    INTERRUPT_OFF;

    if not UUO (1, ETHNT$ (T1))
    then
	begin
	    INTERRUPT_ON;
	    $RESPONSE (.RSP_POINTER, NICE$_OPF, 0,
		       'Protocol open failed for %X.  ETHNT. error %O',
		       ch$ptr (CD [CD_NAME],,8),
		       .T1);
	    return $false;
	end;

    !
    ! Remember portal id assigned by system for this protocol
    !

    CD [CD_KLNI_PRTLID] = (.ETHNT_BLOCK [$ETPSW]) and ET$PID;

    INTERRUPT_ON;

    $true

end;				! of OPEN_KLNI_DEVICE
%routine ('CLOSE_KLNI_DEVICE', CD: ref CD_BLOCK) =

!++
! Functional description:
!
!	This routine is called by NMU$KLNI_CLOSE to perform
!	system specific operations for releasing a KLNI.
!
! Formal parameters:
!
!	.CD			Pointer to circuit data block
!
! Routine value:
!
!	$true			System specific release succeeded
!	$false			Error releasing KLNI
!
!--

begin

    builtin
	UUO;

    register
	T1;

    local
	ETHNT_BLOCK: ETHNT_ARG_BLOCK,
	PSI_BLOCK: PSI_ARG_BLOCK;

    !
    ! Close LOAD-DUMP Portal
    !

    if .CD [CD_KLNI_PRTLID] neq 0
    then
	begin
	    ETHNT_BLOCK [$ETFCN] = $ETCLS^18 or 2;
	    ETHNT_BLOCK [$ETPSW] = .CD [CD_KLNI_PRTLID];
	    T1 = ETHNT_BLOCK;
	    UUO (1, ETHNT$ (T1));
	    CD [CD_KLNI_PRTLID] = 0;
	end;

    !
    ! Disable Ethernet PSI interrupts
    !

    if .CD [CD_KLNI_PSI] neq 0
    then
	begin
	    PSI_BLOCK [$PSECN] = $PCETH;
	    PSI_BLOCK [$PSEOR] = (.CD [CD_KLNI_PSI]*4)^18;
	    PSI_BLOCK [$PSEPR] = 0;
	    T1 = PS$FRC + PSI_BLOCK;
	    UUO (1, PISYS$ (T1));
	    RELEASE_INTERRUPT_CHANNEL (.CD [CD_KLNI_PSI]);
	    CD [CD_KLNI_PSI] = 0;
	end;

    $true

end;				! of CLOSE_KLNI_DEVICE
%routine ('READ_MOP_LOOP', CD: ref CD_BLOCK, PTR, LEN, RSP_POINTER) =

!++
! Functional description:
!
!	This routine is used by NMU$KLNI_READ to read a MOP loop
!	reply message from a remote node on an Ethernet.
!
! Formal parameters:
!
!	.CD			Pointer to circuit data block
!	.PTR			Pointer to message buffer
!	.LEN			Number of bytes in message buffer to write
!	.RSP_POINTER		Pointer to NICE response buffer
!
! Routine value:
!
!        Number of bytes read on circuit
!
!		or
!
!	-2 for read timeout
!	-1 for any other error
!
!--

begin


    builtin
	UUO;

    register
	T1 = 1,
	T2 = 2;

    local
	COUNT,
	LLMOP_BLOCK: LLMOP_ARG_BLOCK;

    LLMOP_BLOCK [$LMCID,FWORD] = 0;     ! Clear LLMOP Arg Block
    LLMOP_BLOCK [$LMDST,FWORD] = 0;
    LLMOP_BLOCK [$LMDST+1,FWORD] = 0;
    LLMOP_BLOCK [$LMREQ,FWORD] = 0;
    LLMOP_BLOCK [$LMRBL,FWORD] = 0;

    !
    ! First wait for reply message to arrive. Timeout after 'n' seconds
    !

    LLMOP_BLOCK [$LMCID,FWORD] = .CD[CD_KLNI_CHAN]; ! Pass channel id
    LLMOP_BLOCK [$LMREQ,LM$REQ] = .CD[CD_KLNI_REQNO]; ! Pass request number

    incr COUNT from 1 to 5 do
         begin
               T1 = $ELSTS;
               T2 = LLMOP_BLOCK;
              if not UUO (1, LLMOP$(T1))
              then
                  begin
                       RSP_POINTER = ch$plus (.RSP_POINTER,
                                              $RESPONSE (.RSP_POINTER,
                                                         NICE$_OPF,
                                                         0,
                                                         'LLMOP Failure',
                                                         ch$ptr (CD [CD_NAME],,
                                                                 8)));
                       return -1;
                  end;

              if .LLMOP_BLOCK [$LMSTF,LM$RTC] eql $LMSUC
              then
                  begin
                  !
                  ! Read MOP data message from KLNI
                  !

                  LLMOP_BLOCK [$LMRBL,LM$MBL] = .LEN; ! Pass length of reply buffer
                  LLMOP_BLOCK [$LMRBP,FWORD] = .PTR; ! Pass pointer to reply buffer

                   T1 = $ELRPY;
                   T2 = LLMOP_BLOCK;
                  if not UUO (1, LLMOP$(T1))
                  then
                      begin
                           RSP_POINTER = ch$plus (.RSP_POINTER,
                                                  $RESPONSE (.RSP_POINTER,
                                                             NICE$_OPF,
                                                             0,
                                                             'Failure reading MOP loop reply on %X.  Status = %O',
                                                             ch$ptr (CD [CD_NAME],,8),
                                                             .LLMOP_BLOCK [$LMSTF,LM$RTC]));
                           return -1;
                      end
                  else
                      begin
                           
                      local             ! Buffer for Ethernet reply address
                           RPYADR : vector [ch$allocation(7,8)*%upval];

%( Here put in the Data-Id and Data-Type bytes. See NMARCH and/or NMLPRM?)%

                      RSP_POINTER = ch$plus (.RSP_POINTER,
                                             $RESPONSE (.RSP_POINTER,
                                                        NICE$_SUC,
                                                        0));

                      ! Build ENTITY ID field in response message

                      RSP_POINTER = ch$move(ch$rchar(ch$ptr(CD[CD_NAME],,8))+1,
                                            ch$ptr (CD [CD_NAME],,8),
                                            .RSP_POINTER);

                      ! Build TEST DATA field in response message

                      PUTB (0, RSP_POINTER);
                      PUTB (0, RSP_POINTER);

                      ! Build DATA BLOCK field in response message

                      !
                      ! Conjure up an HI-6 parameter field.
                      !
                      ! Shuffle the 6 byte address forward to make room
                      ! for the I field, then store the I-6 field.
                      !

                      ch$move (6,
                               ch$ptr(LLMOP_BLOCK [$LMSRC,FWORD],,8),
                               ch$ptr(RPYADR,1,8));

                      ch$wchar (6,ch$ptr(RPYADR,0,8));

                      BUILD_PARAMETER_DATA (ENTITY_NODE, ! NODE Entity
                                            010, ! PHYSICAL ADDRESS Parameter
                                            RPYADR,
                                            12, ! Fake this for now
                                            RSP_POINTER);

                      return .LLMOP_BLOCK [$LMRBL,LM$RML];
                      end;
                  end
              else
                  NMU$SCHED_SLEEP(1);        ! Sleep a second before reading
         end;

     T1 = $ELABT;
     T2 = LLMOP_BLOCK;
    UUO (1, LLMOP$(T1));
    return -2                           ! Indicate timeout to caller

end;				! of READ_MOP_LOOP
%routine ('WRITE_MOP_LOOP', CD: ref CD_BLOCK, PTR, LEN, RSP_POINTER) =

!++
! Functional description:
!
!	This routine is used by NMU$KLNI_WRITE to send MOP data
!	messages on the Ethernet using a KLNI.
!
! Formal parameters:
!
!	.CD			Pointer to circuit data block
!	.PTR			Pointer to message buffer
!	.LEN			Number of bytes in message buffer to write
!	.RSP_POINTER		Pointer to NICE response buffer
!
! Routine value:
!
!	$true			If successful
!	$false			If error
!
!--

begin

    builtin
	UUO;

    register
	T1 = 1,
	T2 = 2;

    local
	LLMOP_BLOCK: LLMOP_ARG_BLOCK;

    !
    ! Set up the LLMOP JSYS argument block
    !

    LLMOP_BLOCK [$LMCID,FWORD] = 0;     ! Clear LLMOP Arg Block
    LLMOP_BLOCK [$LMDST,FWORD] = 0;
    LLMOP_BLOCK [$LMDST+1,FWORD] = 0;
    LLMOP_BLOCK [$LMREQ,FWORD] = 0;
    LLMOP_BLOCK [$LMRBL,FWORD] = 0;

    LLMOP_BLOCK [$LMCID,LM$CID] = .CD[CD_KLNI_CHAN]; ! Pass channel id
    LLMOP_BLOCK [$LMRBL,LM$MBL] = .LEN; ! Pass length of data message
    LLMOP_BLOCK [$LMRBP,FWORD] = .PTR;  ! Pass pointer to data message

    ch$move (6, .CD[CD_KLNI_PHYADR], ch$ptr(LLMOP_BLOCK[$LMDST,FWORD],,8));

    !
    ! Send MOP loop message
    !

     T1 = $ELDIR;
     T2 = LLMOP_BLOCK;
    if not UUO (1, LLMOP$(T1))
    then
	begin
	    $RESPONSE (.RSP_POINTER, NICE$_OPF, 0,
		       'Failure sending MOP loop data on %X.  Status = %O',
		       ch$ptr (CD [CD_NAME],,8),
		       .LLMOP_BLOCK [$LMSTF,LM$RTC]);
	    return $false;
	end;

    CD[CD_KLNI_REQNO] = .LLMOP_BLOCK [$LMREQ,LM$REQ]; ! Return request number

    $true

end;				! of WRITE_MOP_LOOP
%routine ('BOOT_REMOTE', CD: ref CD_BLOCK, PTR, LEN, RSP_POINTER) =

!++
! Functional description:
!
!	This routine is used by NMU$KLNI_WRITE to send a MOP BOOT
!	message on the Ethernet using a KLNI.
!
! Formal parameters:
!
!	.CD			Pointer to circuit data block
!	.PTR			Pointer to message buffer
!	.LEN			Number of bytes in message buffer to write
!	.RSP_POINTER		Pointer to NICE response buffer
!
! Routine value:
!
!	$true			If successful
!	$false			If error
!
!--

begin

    builtin
	UUO;

    register
	T1 = 1,
	T2 = 2;

    local
         L,
         LLMOP_BLOCK: LLMOP_ARG_BLOCK;	! LLMOP JSYS argument block

    if .LEN lss 12                      ! Is it a V3.0 style BOOT message?
    then
        begin
             $RESPONSE (.RSP_POINTER, NICE$_MPE, 0,
                        'Invalid BOOT message length');
             return $false;
        end;

    !
    ! Set up the LLMOP JSYS argument block
    !

    LLMOP_BLOCK [$LMCID,FWORD] = 0;     ! Clear Channel-Id
    LLMOP_BLOCK [$LMDST,FWORD] = 0;     ! Clear Destination Address
    LLMOP_BLOCK [$LMDST+1,FWORD] = 0;
    LLMOP_BLOCK [$LMPWD,FWORD] = 0;     ! Clear Password Verification
    LLMOP_BLOCK [$LMPWD+1,FWORD] = 0;
    LLMOP_BLOCK [$LMCIF,FWORD] = 0;     ! Clear Control Information
    LLMOP_BLOCK [$LMDID,FWORD] = 0;     ! Clear Device Id
    LLMOP_BLOCK [$LMSID,FWORD] = 0;     ! Clear Software Id

    LLMOP_BLOCK [$LMCID,LM$CID] = .CD[CD_KLNI_CHAN]; ! Pass channel id

    if GETB (PTR) neq ENTER_MOP_MODE    ! Is it a BOOT message
    then
        begin
             $RESPONSE (.RSP_POINTER, NICE$_MPE, 0,
                        'Invalid BOOT message function code');
             return $false;
        end;

    PTR = ch$move (8,                   ! Move Password Verification
                   .PTR,                !   From message
                   ch$ptr(LLMOP_BLOCK[$LMPWD,FWORD],,8)); !   To Arg Block

    ch$move (6,                         ! Move Ethernet Destination Address
             .CD[CD_KLNI_PHYADR],       !   From Circuit Data Block
             ch$ptr(LLMOP_BLOCK[$LMDST,FWORD],,8)); !   To Argument Block

    LLMOP_BLOCK [$LMCIF,LM$PRO] = GETB (PTR); ! Set Processor
    LLMOP_BLOCK [$LMCIF,(LM$BDV or LM$BSV)] = GETB (PTR); ! Set Control Info

    if .LLMOP_BLOCK [$LMCIF,LM$BDV]     ! Boot Device present?
    then
        begin
        if (L = GETB (PTR)) lss (12 - .LEN)
        then
            begin
                 $RESPONSE (.RSP_POINTER, NICE$_MPE, 0,
                            'Invalid BOOT message - length');
                 return $false;
            end;

        LLMOP_BLOCK [$LMDID,FWORD] = .PTR; ! Get Device Id pointer
        PTR = ch$plus (.PTR, .L);       ! Update pointer
        end
    else L = 0;

    if .LEN gtr .L + 11
    then
        LLMOP_BLOCK [$LMSID,FWORD] = .PTR; ! Set Software Id pointer

    !
    ! Send MOP BOOT message
    !

     T1 = $RCRBT;
     T2 = LLMOP_BLOCK;
    if not UUO (1, LLMOP$(T1))
    then
	begin
             $RESPONSE (.RSP_POINTER, NICE$_OPF, 0,
		       'Failure sending MOP message on %X.  Status = %O',
		       ch$ptr (CD [CD_NAME],,8),
		       .LLMOP_BLOCK [$LMSTF,LM$RTC]);
             return $false;
	end;

    $true

end;				! of BOOT_REMOTE
%routine ('WRITE_MOP_LOAD_DUMP', CD: ref CD_BLOCK, PTR, LEN, RSP_POINTER) =

!++
! Functional description:
!
!	This routine is used by NMU$KLNI_WRITE to send MOP data
!	messages on the Ethernet using a KLNI.
!
! Formal parameters:
!
!	.CD			Pointer to circuit data block
!	.PTR			Pointer to message buffer
!	.LEN			Number of bytes in message buffer to write
!	.RSP_POINTER		Pointer to NICE response buffer
!
! Routine value:
!
!	$true			If successful
!	$false			If error
!
!--

begin

    builtin
	UUO;

    register
	T1 = 1,
	T2 = 2;

    local
	UBD_BLOCK: UBD_ARG_BLOCK,
	ETHNT_BLOCK: ETHNT_ARG_BLOCK;

	%debug (NETWORK_TRACE,
		(begin
		 local COUNT, POINTER, OUTCNT;

                 TRACE_INFO (
                      'Writing MOP message to line %X, %D Bytes',
                      ch$ptr (CD[CD_NAME],,8),
                      .LEN);
                 TRACE_INFO ('address %6K', .CD [CD_KLNI_PHYADR]);

		 POINTER = .PTR;
		 COUNT = .LEN;

		 while .COUNT gtr 0 do
			begin
			OUTCNT = min (.COUNT, 8);
			TRACE_INFO (' %#B', .OUTCNT, .POINTER);
			POINTER = ch$plus (.POINTER, 8);
			COUNT = .COUNT - 8;
			end;

		 end));

    !
    ! Set up user buffer descriptor block
    !

    UBD_BLOCK [$UBNXT] = 0;
    UBD_BLOCK [$UBBID] = UBD_BLOCK;
    UBD_BLOCK [$UBSTS] = 0;
    UBD_BLOCK [$UBBSZ] = .LEN;
    UBD_BLOCK [$UBBFA] = .PTR;
    UBD_BLOCK [$UBBFA] + 1 = 0;
    UBD_BLOCK [$UBPTY] = 0;
    ch$move (6, .CD[CD_KLNI_PHYADR], ch$ptr(UBD_BLOCK [$UBDEA],,8));

    !
    ! Transmit the datagram
    !

    ETHNT_BLOCK [$ETFCN] = $ETQXB^18 + 3;
    ETHNT_BLOCK [$ETPSW] = .CD [CD_KLNI_PRTLID];
    ETHNT_BLOCK [$ETUBL] = UBD_BLOCK;

    T1 = ETHNT_BLOCK;

    if not UUO (1, ETHNT$ (T1))
    then
	begin
	    $RESPONSE (.RSP_POINTER, NICE$_OPF, 0,
		       'MOP transmit failure on %X.  ETHNT. error %O',
		       ch$ptr (CD [CD_NAME],,8),
		       .T1);
	    return $false;
	end;

    !
    ! Read the transmit queue
    !

    ETHNT_BLOCK [$ETFCN] = $ETRXQ^18 + 3;
    ETHNT_BLOCK [$ETPSW] = .CD [CD_KLNI_PRTLID];
    ETHNT_BLOCK [$ETUBL] = UBD_BLOCK;

    T1 = ETHNT_BLOCK;
    UUO (1, ETHNT$ (T1));

    while .ETHNT_BLOCK [$ETUBL] neq 0
    do
	begin
	    NMU$SCHED_WAIT (CD [CD_KLNI_XMT_EVB], 10);
	    T1 = ETHNT_BLOCK;
	    UUO (1, ETHNT$ (T1));
	end;

    $true

end;                         ! of WRITE_MOP_LOAD
%routine ('READ_MOP_LOAD_DUMP', CD: ref CD_BLOCK, PTR, LEN, RSP_POINTER) =

!++
! Functional description:
!
!	This routine is used by NMU$KLNI_READ to read MOP data
!	messages on the Ethernet using a KLNI.
!
! Formal parameters:
!
!	.CD			Pointer to circuit data block
!	.PTR			Pointer to message buffer
!	.LEN			Size of the receive buffer
!	.RSP_POINTER		Pointer to NICE response buffer
!
! Routine value:
!
!        Number of bytes read on circuit
!
!		or
!
!	-2 for read timeout
!	-1 for any other error
!
!--

begin

    builtin
	UUO;

    register
	T1;

    local
	UBD_BLOCK: UBD_ARG_BLOCK,
	ETHNT_BLOCK: ETHNT_ARG_BLOCK;

    !
    ! Read the received datagram
    !

    UBD_BLOCK [$UBNXT] = 0;

    ETHNT_BLOCK [$ETFCN] = $ETRRQ^18 + 3;
    ETHNT_BLOCK [$ETPSW] = .CD [CD_KLNI_PRTLID];
    ETHNT_BLOCK [$ETUBL] = UBD_BLOCK;

    T1 = ETHNT_BLOCK;
    UUO (1, ETHNT$ (T1));

    while .ETHNT_BLOCK [$ETUBL] neq 0
    do
	begin
	    if not NMU$SCHED_WAIT (CD [CD_KLNI_RCV_EVB], 4)
	    then
		return -2;
	    T1 = ETHNT_BLOCK;
	    UUO (1, ETHNT$ (T1));
	end;

    if .UBD_BLOCK [$UBBSZ] gtr .LEN
    then
	return -1;

    ch$move (.UBD_BLOCK [$UBBSZ], .UBD_BLOCK [$UBBFA], .PTR);
    ch$move (6, ch$ptr (UBD_BLOCK [$UBSEA],,8), .CD [CD_KLNI_HRDWADR]);
    CD [CD_KLNI_MULTICAST] = ch$eql (6, ch$ptr (LDA_MULTICAST,,8),
				     6, ch$ptr (UBD_BLOCK [$UBDEA],,8));

    %debug (NETWORK_TRACE,
	   (begin
		local COUNT, PTR, OUTCNT;

		TRACE_INFO ('Read MOP data on link %X, %D bytes read',
			    ch$ptr(CD[CD_NAME],,8),
			    .UBD_BLOCK [$UBBSZ]);
		TRACE_INFO ('address %6K, multicast: %D',
			    ch$ptr (UBD_BLOCK [$UBSEA],,8),
			    .CD [CD_KLNI_MULTICAST]);
		PTR = .UBD_BLOCK [$UBBFA];
		COUNT = .UBD_BLOCK [$UBBSZ];

		while .COUNT gtr 0
		do
		    begin
			OUTCNT = min (.COUNT, 8);
			TRACE_INFO (' %#B', .OUTCNT, .PTR);
			PTR = ch$plus (.PTR, 8);
			COUNT = .COUNT - 8;
		    end
	    end));

    NMU$MEMORY_RELEASE (.UBD_BLOCK [$UBBID], MOP_BUFFER_ALLOCATION);

    POST_RECEIVE_BUFFER (.CD);

    .UBD_BLOCK [$UBBSZ]

end;
%routine ('POST_RECEIVE_BUFFER', CD: ref CD_BLOCK): vanilla_interrupt_linkage =

begin

    builtin
	UUO;

    register
	T1;

    local
	BUFFER_ADDRESS,
	UBD_BLOCK: UBD_ARG_BLOCK,
	ETHNT_BLOCK: ETHNT_ARG_BLOCK;

    if (BUFFER_ADDRESS = NMU$MEMORY_GET (MOP_BUFFER_ALLOCATION)) eqla 0
    then
	return $false;

    UBD_BLOCK [$UBNXT] = 0;
    UBD_BLOCK [$UBBID] = .BUFFER_ADDRESS;
    UBD_BLOCK [$UBSTS] = 0;
    UBD_BLOCK [$UBBSZ] = MOP_BUFFER_LENGTH;
    UBD_BLOCK [$UBBFA] = ch$ptr (.BUFFER_ADDRESS,,8);
    UBD_BLOCK [$UBBFA] + 1 = 0;

    ETHNT_BLOCK [$ETFCN] = $ETQRB^18 + 3;
    ETHNT_BLOCK [$ETPSW] = .CD [CD_KLNI_PRTLID];
    ETHNT_BLOCK [$ETUBL] = UBD_BLOCK;

    T1 = ETHNT_BLOCK;

    if not UUO (1, ETHNT$ (T1))
    then
	begin
	    NMU$MEMORY_RELEASE (.BUFFER_ADDRESS, MOP_BUFFER_ALLOCATION);
	    return $false;
	end;

    $true

end;
%routine ('ENABLE_MULTICAST_ADDRESS', CD: ref CD_BLOCK, RSP_POINTER) =


begin

    builtin
	UUO;

    register
	T1;

    local
	MCA_POINTER,
	ETHNT_BLOCK: ETHNT_ARG_BLOCK;

    ETHNT_BLOCK [ $ETFCN] = $ETEMA^18 + 4;
    ETHNT_BLOCK [$ETPSW] = .CD [CD_KLNI_PRTLID];
    MCA_POINTER = ch$ptr (LDA_MULTICAST,,8);
    ch$move (6, .MCA_POINTER, ch$ptr (ETHNT_BLOCK [$ETMCA],,8));

    T1 = ETHNT_BLOCK;

    if not UUO (1, ETHNT$ (T1))
    then
	begin
	    $RESPONSE (.RSP_POINTER, NICE$_OPF, 0,
		       'Could not enable multi-cast address on %X.  ETHNT. error %O',
		       ch$ptr (CD [CD_NAME],,8),
		       .T1);
	    return $false;
	end;

    $true

end;
%routine ('ETHNT_PSI_INTERRUPT', CD: ref CD_BLOCK): vanilla_interrupt_linkage
						    novalue =

!++
! Functional description:
!
!	Routine called upon and ethernet PSI interrupt
!
!--

begin

    local
	STATUS;

    field
	PI_VECTOR_FIELDS =
	set
	    PI_VEC_NEWPC = [$PSVNP, 0, 36, 0],	! Interrupt vector
	    PI_VEC_OLDPC = [$PSVOP, 0, 36, 0],	! Address for DEBRK
	    PI_VEC_FLAGS = [$PSVFL, 0, 36, 0],	! Flags
	    PI_VEC_STATUS = [$PSVIS, 0, 36, 0]	! Status of this interrupt
	tes;

    external
	PIVEC: blockvector [8,4] field (PI_VECTOR_FIELDS);

    STATUS = .PIVEC [.CD [CD_KLNI_PSI], PI_VEC_STATUS];
    STATUS = .STATUS and (not .CD [CD_KLNI_PSI_STS]);

    if (.STATUS and ET$PON) neq 0
    then
	POST_RECEIVE_BUFFER (.CD);

    if (.STATUS and ET$PXB) neq 0
    then
	NMU$SCHED_FLAG (CD [CD_KLNI_XMT_EVB]);

    if (.STATUS and ET$PRB) neq 0
    then
	NMU$SCHED_FLAG (CD [CD_KLNI_RCV_EVB]);

    CD [CD_KLNI_PSI_STS] = .PIVEC [.CD [CD_KLNI_PSI], PI_VEC_STATUS];

end;				! of ETHNT_PSI_INTERRUPT
routine BUILD_PARAMETER_DATA (ENTITY_TYPE, PARMNO, PVALU, LENGTH, POINTER) =

%( Nota Bene:

%routine ('BUILD_PARAMETER_DATA', ENTITY_TYPE, PARMNO, PVALU, LENGTH, POINTER) =

   The code in this routine was lifted from NMLVDB 'READ_PARAMETER_DATA'.
   It is here only temporarily. It should be moved to NMLPRM and made
   to be a global routine. NMLEVD could be changed to make use of this.

)%

!++
! FUNCTIONAL DESCRIPTION:
!
!	Builds the DATA ID, DATA TYPE and PARAMETER DATA fields of the
!       NICE response message into the response message buffer.
!
! FORMAL PARAMETERS
!
!	ENTITY_TYPE     Entity type.
!	PARMNO          The architecturally defined parameter number
!                       for this parameter.
!       PVALU           The value for this parameter.
!       LENGTH          The length of the buffer remaining.
!       POINTER         The address of a character sequence pointer to the
!                       buffer.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	The number of bytes for this parameter excluding data id
!	and datatype bytes.
!
! SIDE EFFECTS:
!
!	If the parameter will fit in the buffer, it is copied into
!	the buffer.
!
!--

    begin

    external routine
             NML$DATA_TYPE;


    macro
         PUTN (VALUE, PTR_ADR, N) =
             begin
             local L, X;

             X = VALUE;
             ch$wchar_a (.X, PTR_ADR);
             incr L from 256 to ((N - 1) * 256) by 256
             do begin
                X = .X / .L;
                ch$wchar_a (.X, PTR_ADR);
                end;

             .L / 256
             end %;

    local
         BUF_PTR,
         BUF_LEN,
         DATA_ID: block [1] field (DATA_ID_FIELDS), ! Data ID
         DATA_TYPE: block [1] field (DATA_TYPE_FIELDS);

    BUF_PTR = ..POINTER;
    DATA_ID = 0;
    DATA_ID[DI_PARMNO] = .PARMNO;       ! Get parameter number
    DATA_ID[DI_TYPE] = 0;               ! This is a parameter
    DATA_TYPE = NML$DATA_TYPE (.ENTITY_TYPE, .PARMNO);

    if .DATA_TYPE[DT_CODED] eql 0       ! Not coded
    then begin
         PUTW (DATA_ID, BUF_PTR);       ! Write data id into buffer
         PUTB (.DATA_TYPE, BUF_PTR);    ! Write data type into buffer
         if .DATA_TYPE[DT_FTYPE] eql 0  ! Binary number
         then begin
              if .DATA_TYPE[DT_LENGTH] eql 0
              then begin                ! Binary image field
                   BUF_LEN = ch$rchar (ch$ptr (.PVALU,,8)) + 1;
                   if .LENGTH geq .BUF_LEN
                   then BUF_PTR = ch$move (.BUF_LEN,
                                           ch$ptr (.PVALU,,8),
                                           .BUF_PTR);
                   end
              else begin
                   BUF_LEN = .DATA_TYPE[DT_LENGTH];
                   if .DATA_TYPE[DT_LENGTH] leq %bpval/8
                   then begin           ! Data stored in value
                        if .LENGTH geq .BUF_LEN
                        then PUTN (.PVALU,
                                   BUF_PTR,
                                   .DATA_TYPE[DT_LENGTH]);
                        end
                   else begin           ! Data stored in buffer
                        BUF_LEN = .DATA_TYPE[DT_LENGTH];
                        if .LENGTH geq .BUF_LEN
                        then BUF_PTR = ch$move (.BUF_LEN,
                                                ch$ptr (.PVALU,,8),
                                                .BUF_PTR);
                        end;
                   end;
              end
         else begin                     ! ASCII image field
              BUF_LEN = ch$rchar (ch$ptr (.PVALU,,8)) + 1;
              if .LENGTH geq .BUF_LEN
              then BUF_PTR = ch$move (.BUF_LEN,
                                      ch$ptr (.PVALU,,8),
                                      .BUF_PTR);
              end;
         end
    else begin                          ! Coded

         %( N.B. - We have to do special casing here for multiple coded
            fields. )%

         if .DATA_TYPE[DT_FTYPE] eql 0  ! Single field
         then begin
              PUTW (DATA_ID, BUF_PTR);  ! Write data id into buffer
              PUTB (.DATA_TYPE, BUF_PTR); ! Write data type into buffer
              BUF_LEN = .DATA_TYPE[DT_NUMBER];
              if .LENGTH geq .BUF_LEN
              then PUTN (.PVALU, BUF_PTR, .DATA_TYPE[DT_NUMBER]);
              end
         else selectone .DATA_TYPE[DT_NUMBER] of
                  set                   ! Multiple field
                  [CMN] :               ! Node format
                      begin
                      local PTR;

                      PTR = ch$ptr (.PVALU,,8);
                      begin
                      literal DATA_TYPE = 1^7 + 1^6 + 2;
                      PUTW (DATA_ID, BUF_PTR); ! Write data id
                      PUTB (DATA_TYPE, BUF_PTR); ! Write data type
                      end;

                      BUF_LEN = 6 + 5;	! Assume node name of 6 chars
                      if .LENGTH geq .BUF_LEN
                      then
                        begin
                        !
                        ! Node address
                        !

                          begin
                          literal DATA_TYPE = 0^7 + 0^6 + 0^4 + 2;
                          local NODE_ADDRESS;

                          NODE_ADDRESS = GETW (PTR);
                          PUTB (DATA_TYPE, BUF_PTR); ! Write Data Type
                          PUTW (NODE_ADDRESS, BUF_PTR); ! Write address
                          end;

                        !
                        ! Node name
                        !

                          begin
                          literal DATA_TYPE = 0^7 + 1^6;
                          local NODE_NAME_LENGTH;

                          PUTB (DATA_TYPE, BUF_PTR); ! Write Data Type
                          NODE_NAME_LENGTH = GETB (PTR); ! Get I-length
                          PUTB (.NODE_NAME_LENGTH, BUF_PTR);
                          BUF_PTR = ch$move (.NODE_NAME_LENGTH,
                                             .PTR,
                                             .BUF_PTR);
                          BUF_LEN = .NODE_NAME_LENGTH + 5; ! Real length
                          end;
                        end;
                      end;

                  [CMV] :               ! Version format
                      begin
                      external          ! Version numbers defined in NMUSKD
                          NMLVER,       ! Major version
                          DECECO,       ! Minor version
                          USRECO;       ! Customer version

                      begin
                      literal DATA_TYPE = 1^7 + 1^6 + 3;
                      PUTW (DATA_ID, BUF_PTR); ! Write data id
                      PUTB (DATA_TYPE, BUF_PTR); ! Write data type
                      end;
                      BUF_LEN = 6;      ! Six bytes to write excluding
                                        ! data id and data type bytes

                      if .LENGTH geq .BUF_LEN
                      then
                          begin
                          literal DATA_TYPE = 0^7 + 0^6 + 0^4 + 1;

                          PUTB (DATA_TYPE, BUF_PTR); ! Write Data Type
                          PUTB (.NMLVER, BUF_PTR); ! Write version byte
                          PUTB (DATA_TYPE, BUF_PTR); ! Write Data Type
                          PUTB (.DECECO, BUF_PTR); ! Write version byte
                          PUTB (DATA_TYPE, BUF_PTR); ! Write Data Type
                          PUTB (.USRECO, BUF_PTR); ! Write version byte
                          end;

                      end;

                  [otherwise] :         ! Unknown multiple parameter
                      BUF_LEN = 0;
                  tes;
         end;

    .POINTER = .BUF_PTR;

    return .BUF_LEN;                    ! Return number of bytes written
    end;				! End of BUILD_PARAMETER_DATA