Google
 

Trailing-Edge - PDP-10 Archives - TOPS-20_V6.1_DECnetSrc_7-23-85 - mcb/xpt/xpesel.bli
There is 1 other file named xpesel.bli in the archive. Click here to see a list.
module XPESEL	(
		IDENT = 'X01090'
		) =
begin

!
!                    COPYRIGHT (c) 1980, 1981, 1982
!                    DIGITAL EQUIPMENT CORPORATION
!                        Maynard, Massachusetts
!
!     This software is furnished under a license and may  be  used
!     and copied only in accordance with the terms of such license
!     and with the inclusion of the above copyright notice.   This
!     software  or any other copies thereof may not be provided or
!     otherwise made available to any other person.  No  title  to
!     and ownership of the software is hereby transferred.
!
!     The information  in  this  software  is  subject  to  change
!     without  notice  and should not be construed as a commitment
!     by DIGITAL EQUIPMENT CORPORATION.
!
!     DIGITAL assumes no responsibility for the use or reliability
!     of  its  software  on  equipment  which  is  not supplied by
!     DIGITAL.
!

!++
! FACILITY:	Transport
!
! ABSTRACT:
!
!	Transport Select extension module: Contains INTERCEPT, which
!	maintains the Link Translate Table.
!	This routine was originally part of the XPTSEL module.
!
! ENVIRONMENT:	MCB
!
! AUTHOR: L. Webber , CREATION DATE:  5-Mar-81
!
! MODIFIED BY:
!
!	L. Webber, 5-Mar-81 VERSION 1.00
!
! 1.01	L. Webber, 19-Mar-81
!	Added $XPECLN to explicitly clean out an LTT entry.
!	Broke SCAN out as a top-level routine so that both other routines
!	could call it.
!
! 1.02	L. Webber, 14-Apr-81
!	Fix SCAN so that if it is given a 0 link address, any table entry
!	containing the specified node address is a hit.  This allows
!	$XPECLN to clear out all links for a specified node.
!
! 1.03	L. Webber, 5-May-81
!	Change INTERCEPT so that when a duplicate CI is found, the matching
!	LTT entry is stolen for use by the new link.  (Note: this will do
!	horrible things if a real duplicate CI is encountered, i.e., one
!	where the duplicated link does not correspond to a defunct logical
!	link.)
!
! 1.04	L. Webber, 25-Jun-81
!	Add SEND_DC, a routine to format and send a DC message over a line.
!	Modify $XPECLN to send a DC if it is killing an ILT entry whose
!	"other end" (the one does not lead to the node responsible for the
!	table entry being killed) is a Phase II or TOPS20 node.
!
! 1.05	L. Webber, 21-Dec-81
!	Add CLN_RETRY to clean a specified circuit's CCBs out of the retry
!	queue.  This is called when the circuit goes down.
!
! 1.06	L. Webber, 3-Feb-81
!	Fix CLN_RETRY to tell _TERMINATE not to decrement INPUTcount when
!	returning a buffer; buffers on the retry queue aren't counted in
!	the first place.
!
! 1.07	L. Webber, 8-Feb-81
!	Fix 1.06 not to modify the buffer's CCB when returning it.
!
! 1.08	A. Peckham,20-Apr-82
!	Move $XPECLN global to low psect.
!       Eliminate GETLINE and GETNODE.
!
! 1.09	A. Peckham,2-Jul-82
!	Rename INTERCEPT to INTPH2.
!
!--
!
! INCLUDE FILES:
!

require 'XPTMAC';

!
! TABLE OF CONTENTS
!

forward routine
	SCAN,
	INTPH2: CALL$,
	CLEAN_LINK: CALL$ novalue,
	SEND_DC: CALL$ novalue,
	CLN_RETRY: novalue;

!
! MACROS:
!

!
! EQUATED SYMBOLS:
!

!
! OWN STORAGE:
!

literal JUMP_TO = %o'137';

psect
    global = XPEJMP (nowrite, execute);

global
    $XPECLN : vector [2] initial (JUMP_TO, CLEAN_LINK);

undeclare JUMP_TO;

!
! EXTERNAL REFERENCES:
!

external routine
    _TERMINATE: CALL$ novalue;
routine SCAN (TABLE,HALF,NODE,LINK) =

!++
! FUNCTIONAL DESCRIPTION:
!
! Scans the Link Translate Table for an entry matching a specified one.
!
! FORMAL PARAMETERS
!
!	TABLE	Address of a BLISS value to be set to the address of
!		the LTT entry found (if any).
!
!	HALF	Address of a BLISS value to be set to the "half" of
!		the table entry containing specified node/link pair:
!		0 for first half, 1 for second.
!
!	NODE	Node address of node/link pair to find.
!
!	LINK	Link address of node/link pair to find, or 0 for
!		"any link for the node"
!
! IMPLICIT INPUTS
!
!	Ph2link_table, Ph2link_allocation
!
! ROUTINE VALUE: "Success" or "failure"
! COMPLETION CODES:
!
!	-1	Failure: LTT and HALF contents are undefined.
!	other	Index (from 1 to the number of entries) of the LTT
!		entry of the first match found.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

begin

require 'XPTSYM';
bind LTT = .TABLE: ref block field(LTTfields);

NODE = .NODE<0,16,0>;			! Mask node address and
LINK = .LINK<0,16,0>;			!  link address to 16 bits
LTT = .Ph2link_table;                   ! Address the first entry

incr I from 1 to .Ph2link_allocated do  ! Scan the LTT entries
    begin
    .HALF = 0;				! Try the first pair first
    if ((.NODE eql .LTT[LTTnode1])	! Compare the pair in
    and ((.LINK eql 0) or		!  the entry with
	(.LINK eql .LTT[LTTlink1])))	!  the specified pair
	then exitloop(.I);		! HIT
    .HALF = ..HALF + 1;			! Now try the second pair in the entry
    if ((.NODE eql .LTT[LTTnode2])	! Compare the pair in
    and ((.LINK eql 0) or		!  the entry with
    (.LINK eql .LTT[LTTlink2])))	!  the specified pair
	then exitloop(.I)		! HIT
    else LTT = LTT[LTTlen];		! Go on to the next LTT entry
    end
end;				!End of SCAN
global
routine INTPH2 (CCB,TYPE,DESTNODE,SRCNODE): CALL$ =

!++
! FUNCTIONAL DESCRIPTION:
!
! This routine handles Phase II packets without routing headers.
! It maintains the Link Translate Table in the Transport Data Base
! and uses it to map link addresses into a destination node address.
!
! The routine is called in two contexts: TYPE 0, when a message is
! received without a routing header and the link addresses must be
! mapped into a destination; and TYPE 1, when a Phase II message is
! received destined for another Phase II node and an LTT entry must
! be created and maintained to allow TYPE 0 calls for other messages
! on the same link.
!
! FORMAL PARAMETERS
!
!	CCB - the pass-through CCB for the packet to be processed
!	TYPE - the message type: 0 = packet has no header
!				 1 = packet has a header or is a CI
!	DESTNODE - the destination node address for the packet.  This
!		   is an output for TYPE 0 and an input for TYPE 1.
!	SRCNODE - the source node address for the packet.  This is an
!		  output for TYPE 0 and an input for TYPE 1.
!
! IMPLICIT INPUTS
!
!	Nty, Nid, Nnm, Tid
!
! ROUTINE VALUE: "Success" or "failure" (TYPE 1 always returns "success")
! COMPLETION CODES:
!
!	CS_SUC		Success; for TYPE 0, the destination or source node
!			addresses are returned.
!     - $XPT$E_FMT	Failure; packet header format error. This may mean
!			that the packet cannot be associated with an active
!			LTT entry.
!     - $XPT$E_RNG	Failure; node number out of range.
!
! SIDE EFFECTS:
!
!	Maintains and modifies the Link Translate Table.
!
!--

begin

local LINEb;
require 'XPTSYM';
require 'MCBCOM';
pointer PTR;
local ILINE,MSGFLG,SLINK,DLINK,DLINKX,RET,HALF,PTRA,LTTx;
local LTT: ref block field(LTTfields);

MAPBUF(.CCB,PTRA,RET);			!Map to and address message buffer
PTR = .PTRA;

		!******************************!
		!  TYPE 0 - no routing header  !
		!******************************!

if .TYPE eql 0 then begin

!
!  Determine the source node address
!

ILINE = .CCB[C_LIN];			!Determine input line
LINEb = $XPT_GET_LINE_DB(.ILINE);	!  and address its data base entry
if ((.Nty neq PhTwo)			!If the line doesn't have
and (.Nty neq TOPS20))			!  a Phase II adjacent node
then SIGNAL_STOP (CE_ERR)		!  then return "failure"
else .SRCNODE = .Nid;			!Otherwise, pick up source node address

!
!  Parse the NSP header for the message
!

MSGFLG = getb(PTR);			!NSP message flags
DLINK = getw(PTR);			!Destination link address
SLINK = getw(PTR);			!Source link address

!
!  Scan the LTT for a match with the source node/link pair
!

if SCAN (LTT,HALF,..SRCNODE,.SLINK)

!
!  No match - only valid for CI and CC
!

eql -1 then
    if ((.MSGFLG eql CI_MSGflgs)	!Any CI or CC message
    or (.MSGFLG eql CC_MSGflgs))	!with no routing header
    then begin				!must be assumed to be for self
	.DESTNODE = .Tid;		!    Indicate that message is for Self
	INTPH2(.CCB,1,.DESTNODE,	!    Re-call INTPH2
	    .SRCNODE);			!      for Type 1 processing
	return (CS_SUC)			!    Return "success"
	end
    else return (-$XPT$E_FMT)		!Not a CI or CC message - invalid

!
!  Match - pick up the destination node/link pair from the LTT
!

else begin
    if .HALF eql 0 then LTT = LTT[LTTnode2]; !Choose which half to use
    .DESTNODE = .LTT[LTTnode];
    DLINKX = .LTT[LTTlink];

!
!  Invalid destination pair - return error
!

    if ..DESTNODE gtru NN then
	return (-$XPT$E_RNG)
    else if .DLINK neq .DLINKX then
	return (-$XPT$E_FMT)
!
!  Destination pair is OK - return "success"
!	Also, delete the table entry if the message is a DC
!

    else begin
	if .MSGFLG eql DC_MSGflgs then INTPH2(.CCB,1,.DESTNODE,.SRCNODE);
	return (CS_SUC)
	end
    end
end


		!***********************************!
		!  TYPE 1 - routing header present  !
		!***********************************!


else begin

!
!  Skip over the routing header, if any
!

MSGFLG = getb(PTR);
if biton(.MSGFLG,2) then begin		!Routing header present -
    RET = getb(PTR);			!Pick up dest. node name length
    PTR = ch$plus(.PTR,.RET);		!Skip over name
    RET = getb(PTR);			!Pick up source node name length
    PTR = ch$plus(.PTR,.RET);		!Skip over name
    MSGFLG = getb(PTR);			!Pick up NSP message flags
    end;

!
!  Pick up source and destination link addresses
!

DLINK = getw(PTR);
SLINK = getw(PTR);

!
!  Message not CI, CC, DI or DC - ignore it
!

select .MSGFLG of
set

!
!  CI message
!

[CI_MSGflgs]:		begin
    if SCAN(LTT,HALF,..SRCNODE,.SLINK)	!Scan for a match on the source pair
    neq -1 then begin			 !Found: cannibalize the entry -
	BPT(XPT$_ICPT0,..SRCNODE,.SLINK, !  flag the "duplicate
	    ..DESTNODE,.DLINK);          !    CI" event
	if .HALF eql 0 then		 !  determine which half of
	    LTT = LTT[LTTnode2];	 !    the entry the match was on
	LTT[LTTnode] = ..DESTNODE;	 !  fill in the
	LTT[LTTlink] = 0;		 !    other half
	end
    else				 !Not found -
	if SCAN(LTT,HALF,-1,-1)		 !  scan for a free entry
	    eql -1 then	BPT(XPT$_NFI)	 !  none found - ignore message
	else begin
	    LTT[LTTnode1] = ..SRCNODE;	 !  fill in pair 1 in the entry
	    LTT[LTTlink1] = .SLINK;	 !    with the source pair from the msg
	    LTT[LTTnode2] = ..DESTNODE;	 !  fill in node slot 2 with dest. node
	    LTT[LTTlink2] = 0;		 !    and clear link slot 2 for CC
	    end
		end;

!
!  CC, DI or DC message - scan LTT for match on destination node/link pair
!

[CC_MSGflgs,DI_MSGflgs,DC_MSGflgs]:	begin
    RET = SCAN (LTT,HALF,..DESTNODE,.DLINK);
    LTTx = .LTT;
    if .RET eql -1 then begin		!No match - BUG
	if .MSGFLG neq DC_MSGflgs then
	    BPT(XPT$_ICPT1,.MSGFLG,..SRCNODE,.SLINK,..DESTNODE,.DLINK);
	return(CS_SUC)
	end
    else if .HALF eql 0 then LTT = LTT[LTTnode2];	!Match - choose half
				end;

!
!  CC or DI message - fill in second half of LTT entry
!

[CC_MSGflgs,DI_MSGflgs]: begin
    if ..SRCNODE neq .LTT[LTTnode] then		!No source node match - BUG
	BPT(XPT$_ICPT2,.MSGFLG,..SRCNODE,.SLINK,
	    ..DESTNODE,.DLINK)
    else LTT[LTTlink] = .SLINK;			!Fill in other link entry
			 end;

!
!  DC message - delete matched entry from LTT
!

[DC_MSGflgs]:		begin
    if ((..SRCNODE eql .LTT[LTTnode])		! If the source node/link
    and (.SLINK eql .LTT[LTTlink]))		!   pair matches the
    then begin					!   LLT entry,
	LTT = .LTTx;				!   clear out
	incr I from 0 to 3 do			!   the entry
	    VECTOR[.LTT,.I] = -1;		!
	end;
!	then BPT(XPT$_ICPT2,.MSGFLG,..SRCNODE,		!* Old "unmatch" code:
!	    .SLINK,..DESTNODE,.DLINK);          	!* eliminate eventually
			end;
tes;

return (CS_SUC)		!Always return success; caller never looks
end;
end;				!End of INTPH2
global
routine CLEAN_LINK (NODE,LINK): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
! Cleans out the Link Translate Table.  All entries containing the
! node/link pair specified are deleted from the table.  If the link
! address specified is 0, all entries containing the specified node
! address are deleted.
!
! The purpose of this routine is to allow a link which has been closed
! due to timeout or other abnormal conditions, and which has not gone
! through the standard DI/DC interchange which would clean the link out
! of the Link Translate Table, to be cleaned out explicitly by NSP (for
! a local link) or the Decision module (for a route-through link).
!
! FORMAL PARAMETERS
!
!	NODE	Node address of link(s) to be deleted.  This will be the
!		local node address (if NSP called), or the address of a
!		node that has become unreachable.
!
!	LINK	Link address of link(s) to be deleted, or 0 for "all links
!		for the node".
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	Any messages which come into Transport for the link will cause
!	debugging SIGNALS (if present) to be invoked by INTPH2.
!
!--

begin

local LINEb,NODEb;
require 'XPTSYM';
local HALF,DN,DL,SL,DN_L,DN_P,SN_L,SN_P;
local LTT: ref block field(LTTfields);
local CCB: ref block field(C_XPT_fields);

while (SCAN(LTT,HALF,.NODE,.LINK) neq -1)	! Scan for a matching entry
do begin
    if .HALF eql 0 then begin
	DN = .LTT[LTTnode2];
	DL = .LTT[LTTlink2];
	SL = .LTT[LTTlink1];
	end
    else begin
	DN = .LTT[LTTnode1];
	DL = .LTT[LTTlink1];
	SL = .LTT[LTTlink2];
	end;
    NODEb = $XPT_GET_NODE_DB(.DN);
    LINEb = $XPT_GET_LINE_DB(.OL);
    if (not .Local_node
    and ((.Nty eql PhTwo) or (.Nty eql TOPS20))
    and (.Nid eql .DN)
    and $MCB_GET_CCB_AND_BUFFER(22,CCB)) then begin
	CCB[C_XPT_ALLOCATION] = 22;
	DN_L = .Nnml;
	DN_P = byt$ptr(Nnm);
	SN_L = .NODEname_length;
	SN_P = byt$ptr(NODEname,0);
	SEND_DC(.CCB,.LINEb,.DN_L,.DN_P,.SN_L,.SN_P,.DL,.SL,NO_PATH_ERROR);
	end;
    LTT[LTTnode1] = -1;				!   Found one -
    LTT[LTTlink1] = -1;				!     clear it out
    LTT[LTTnode2] = -1;
    LTT[LTTlink2] = -1;
    end;
    
end;				!End of CLEAN_LINK
global
routine SEND_DC (CCB,LINEb,DEST_L,DEST_P,SOURCE_L,SOURCE_P,
                 DESTLNK,SRCLNK,REASON): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
! Constructs and sends a Phase II DC message over a given line.
!
! FORMAL PARAMETERS
!
!	CCB		CCB to use to send the DC.
!			CCB[C_BIAS]	A buffer large enough to contain the DC
!			CCB[C_ADDR]	  (anywhere from 12 to 22 bytes)
!			CCB[C_XPT_ALLOCATION]	The length of the buffer
!				  	(for its eventual release)
!
!	DEST_L		Length of the destination node name.  If this value
!			is zero, a routing header is not built.
!
!	DEST_P		Pointer to the destination node name.
!
!	SOURCE_L	Length of the source node name.
!
!	SOURCE_P	Pointer to the source name name.
!
!	DESTLNK		Destination link address.
!
!	SRCLNK		Source link address.
!
!	REASON		DC reason code.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

begin

require 'XPTSYM';
map CCB: ref block field(C_XPT_fields);
pointer P;

P = .CCB[C_ADDR];				! Address message buffer
if .DEST_L neq 0 then begin			! Build a routing header:
    putb(PH2_RTflgs,P);				!   Routing flags
    putb(.DEST_L,P);				!   Dest. node name length
    P = ch$move(.DEST_L,.DEST_P,.P);		!   Destination node name
    putb(.SOURCE_L,P);				!   Source node name length
    P = ch$move(.SOURCE_L,.SOURCE_P,.P);	!   Source node name
    end;					! Build the message:
putb(DC_MSGflgs,P);				!   Message flags
putw(.DESTLNK,P);				!   Destination link address
putw(.SRCLNK,P);				!   Source link address
putw(.REASON,P);				!   Reason code
CCB[C_CNT] = ch$diff(.P,.CCB[C_ADDR]);		! Set up message length

CCB[C_XPT_TYPE] = NOcode;			! Set "don't use counters" code

CCB[C_HANDLE] = .TLIhandle;
CCB[C_FNC] = FC_XME;				! Send the
CCB[C_MOD] = TM_DAT;				!   message out
$MCB_SCHEDULE_CCB(.CCB);

end;				!End of SEND_DC
global
routine CLN_RETRY (LINEb): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
! This routine cleans out of the retry queue all CCBs which:
!
!	1)  arrived over a specific circuit, or
!	2)  have as a destination the adjacent node over that circuit.
!
! FORMAL PARAMETERS
!
!	LINEb	Address of a circuit's data base entry.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

begin

require 'XPTSYM';
local CCB: ref block field(C_XPT_fields);

local TEMP_QUEUE: vector[2];
local LEN;
pointer P;

$MCB_INITIALIZE_QUEUE(TEMP_QUEUE);

!
!  Pick up each CCB on the retry queue.  If the CCB doesn't "belong" to
!  the specified circuit, place in the temporary holding queue.
!

while $MCB_DEQUEUE_CCB(REqueue,CCB) do
    if not
	((.CCB[C_LIN] eql .LINEnumber)		! CCB arrived over circuit
	or begin
	    MAP$(.CCB[C_BIAS]);			! Map to and
	    P = .CCB[C_ADDR];			!   address buffer
	    if bitoff((getb(P)),%o'10') then	! No header -
		FALSE				!   for local node
	    else begin
		LEN = getb(P);			! Pick up dest. name length
		((.LEN eql .Nnml)		! Name length must match
		and ch$eql(.LEN,.P,.LEN,	!   and names must compare
		    byt$ptr(Nnm),0))    	! equal
		end
	    end)
    then CMQIN$(TEMP_QUEUE,.CCB)		! No match - keep this one
    else begin
	local SAVE;				! Otherwise -
	SAVE = .CCB[C_XPT_TYPE];		!   throw the CCB
	CCB[C_XPT_TYPE] = NOcode;               !   out (but don't
	_TERMINATE(.CCB,CE_DIS);		!   affect the quotas)
	CCB[C_XPT_TYPE] = .SAVE;
	end;

!
!  Now put back everything we kept into the retry queue.
!

while CMQRM$(TEMP_QUEUE,CCB) do
    CMQIN$(REqueue,.CCB);

end;				!End of CLN_RETRY

end				!End of module XPESEL
eludom