Google
 

Trailing-Edge - PDP-10 Archives - TOPS-20_V6.1_DECnetSrc_7-23-85 - mcb/xpt/xptdec.bli
There is 1 other file named xptdec.bli in the archive. Click here to see a list.
module XPTDEC	(
		IDENT = 'X01390'
		) =
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:	DECnet Transport
!
! ABSTRACT:
!
!	 Transport Decision process.  Maintains transport routing data bases
!	 and selects routing paths.
!
! ENVIRONMENT:	MCB
!
! AUTHOR: L. Webber , CREATION DATE: 16-Jul-79
!
! MODIFIED BY:
!
!	L. Webber, 16-Jul-79 : VERSION 1.00
!
! 1.01	L. Webber, 20-Dec-79
!	Modifications associated with splitting Transport Line Interface out
!
! 1.02	L. Webber, 24-Jan-80
!	Put Hop and Cost in a single matrix; modified algorithms as per
!	22-Jan-80 architecture change
!
! 1.03	L. Webber, 29-Jan-80
!	Modify interfaces to OPENT and CLOSET to match standard dispatch
!	linkage.
!
! 1.04	L. Webber, 2-Apr-80
!	Modify to support node and line sub-data-bases
!
! 1.05	L. Webber, 30-Jun-80
!	Modify to use MCBLIB macros
!
! 1.06	A. Peckham, 15-Oct-80
!	Update for new function modifiers.
!
! 1.07	A. Peckham, 21-Oct-80
!	Change CE_ERR return code to SIGNAL_STOP.
!
! 1.08	L. Webber, 11-Dec-80
!	Modify to support MCB 3.1
!
! 1.09	L. Webber, 20-Jan-81
!	Change definition of MATRIX structure to take NLN as an actual.
!
! 1.10	L. Webber, 26-Jan-81
!	Add Event Logging and Counter Incrementing
!
! 1.11	L. Webber, 10-Feb-81
!	MAPBUF is now a macro
!
! 1.12	L. Webber, 23-Feb-81
!	Add event logging for reachability changes and line up;
!	make Event Buffer image field
!
! 1.13	L. Webber, 1-Apr-81
!	Fix length of event buffer reason code in VALID_BUFFER.
!
! 1.14	L. Webber, 3-Apr-81
!	Transform all reason code insertions into calls to EP_REASON.
!	Add call to EP_EXNODE (expected node).
!
! 1.15	L. Webber, 3-Apr-81
!	Put in LIX as entity ID for all events (except for node reachability
!	change, which takes node address).
!
! 1.16	L. Webber, 14-Apr-81
!	Call $XPECLN when a node becomes unreachable, to clean out the
!	Link Translate Table of all links to/from the node.
!
! 1.17	L. Webber, 10-May-81
!	Add code to call do an $MCB_PAUSE every once in a while during the
!	routing algorithm.
!
! 1.18	L. Webber, 15-May-81
!	Do an $MCB_PAUSE every time there's something on the synch queue.
!	Make IncN the number of pauses this time through the algorithm.
!
! 1.19	L. Webber, 1-Jun-81
!	Modify all LOG_EVENT calls for a circuit entity to pass the NMXid.
!
! 1.20	L. Webber, 6-Jul-81
!	Fix VALID_BUFFER not to ignore routing messages with reachable nodes
!	past NN.  Also, modify the event logging of that event to give the
!	highest reachable node in the message instead of the local NN.
!
! 1.21	L. Webber, 13-Jul-81
!	Modify linkage to COSTCH.
!
! 1.22	L. Webber, 13-Jul-81
!	Fix 1.21 so that COSTCH doesn't call ROUTES (TLI is the wrong process
!	context).  Instead, it will cause the routing clock to go off.
!
! 1.23	L. Webber, 14-Jul-81
!	Map in Hopcost in COSTCH; change calls to MAPIN to MAP$'s.
!
! 1.24	L. Webber, 28-Jul-81
!	Re-map Hopcost after calling $XPECLN in ROUTES.
!
! 1.25	L. Webber, 5-Aug-81
!	Ignore "line up" CCB if the circuit isn't in TC state.
!
! 1.26	L. Webber, 11-Sep-81
!	Fix ROUTES so that OL goes "unspecified" when a node becomes
!	unreachable.
!
! 1.27	L. Webber, 17-Sep-81
!	Add support for Phase2_node flag in node data base.
!
! 1.28	L. Webber, 23-Sep-81
!	Add code to flag a node as "adjacent Phase II" when a circuit
!	comes up, and in ROUTES to make a node reachable if that flag
!	is on.  The purpose of this change is to make Phase II nodes
!	reachable to the local DN20 (and to all adjacent Phase II nodes)
!	but to mark them not reachable in the DN20's routing messages.
!
! 1.29	L. Webber, 24-Sep-81
!	Modify event logging code to use new macros for preparing the
!	Event Buffer.
!
! 1.30	L. Webber, 6-Oct-81
!	Fix LINEDN to make a Phase II node unreachable when its connecting
!	circuit goes down.
!
! 1.31	L. Webber, 20-Oct-81
!	Use the (new) "Reset" bit in LINEflags rather than Nty to determine
!	when a line going down had an adjacent Phase II node (Nty is zeroed
!	by Line Support).
!
! 1.32	L. Webber, 9-Nov-81
!	Fix dot bug in 1.31.
!
! 1.33	L. Webber, 21-Dec-81
!	Call CLN_RETRY for "Phase II" circuits in LINEDN.
!
! 1.34	L. Webber, 23-Feb-82
!	Add DLLquota maintenance.
!
! 1.35	L. Webber, 8-Mar-82
!	Don't process routing message if the input circuit is down.
!
! 1.36	L. Webber, 31-Mar-82
!	Call $XPECLN when a Phase II circuit goes down (since "node down"
!	doesn't handle in in that case).
!
! 1.37	A. Peckham, 19-Apr-82
!	Eliminate references to LOG_EVENT, GETLINE, GETNODE.
!       PKTA_HDR has gone to XPE.  Make local call now.
!       Optimize ROUTES and friends.
!
! 1.38	A. Peckham, 23-Aug-82
!	Fix bug in ROUTES which shows up as low core being modified (4:0 6:1).
!       The check for a $MCB_PAUSE allowed the loop on nodes to go beyond NN.
!       This ended up requesting the data base for a non-exisistent node,
!       which would produce a zero address for NODEb.
!       Move the _SYNQH check up to the top of the loop.
!
! 1.39	A. Peckham, 16-Sep-82
!	Add support for internal feature: SET NODE blah MAXIMUM ADDRESS num.
!       This causes XPT to ignore nodes above 'num' when it receives a
!       routing message from node 'blah'.
!
!--
!
! INCLUDE FILES:
!

require 'XPTMAC';

!
! TABLE OF CONTENTS
!

forward routine
	ROUTES: novalue,
	CHECK: novalue,
	LINEDN: CALL$ novalue,
	LINEUP: CALL$ novalue,
	RCVROU: CALL$ novalue,
	COSTCH: CALL$ novalue,
	OPENT: CALL$ novalue,
	CLOSET: CALL$ novalue,
	DECTIM: CALL$ novalue,
        SET_EACH_Srm_FLAG: novalue,
        SIGNAL_REACHABILITY: novalue,
	VALID_BUFFER;

!
! MACROS:
!

!
! EQUATED SYMBOLS:
!

!
! OWN STORAGE:
!

!
! EXTERNAL REFERENCES:
!

external _SYNQH;			! Synch queue header

external routine
	$XPECLN: CALL$ novalue,
	CLN_RETRY: novalue,
	TERM_XPT: novalue;
global routine ROUTES: novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Determines the reachability and output line for each destination
!  node.
!
!  This routine may have to be invoked multiple times to perform a single
!  resolution of the routing data base.  If a process needs to be
!  dispatched at synch level, ROUTES will do an $MCB_PAUSE.  MCB will call
!  ROUTES back at synch level (with no other invocations of Transport
!  intervening), at which time more nodes will be processed until all NN
!  are done.
!
! FORMAL PARAMETERS
!
!	NONE.
!
! IMPLICIT INPUTS
!
!	Hop - 2x2 matrix containing the hops to each node over each line.
!	Cost - 2x2 matrix containing the cost to each node over each line.
!	Minhop - vector containing the fewest hops to each destination.
!	Mincost - vector containing the least cost to each destination.
!	Maxh - Maximum number of hops (network diameter)
!	Maxc - Maximum cost to destination
!	Infh - Value denoting "infinite" hops
!	Infc - Value denoting "infinite" cost
!	Reach - vector containing the reachability for a destination.
!	NN - maximum node address; number of rows in the matrices.
!
!	MaxN - maximum node address that has been processed so far.
!	IncN - work variable
!	Synchblk - the Synch block used to reschedule this routine.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	Modifies matrices Hop and Cost.  Sometimes modifies vectors Minhop,
!	Mincost, Reach, OL and Srm.
!
!--

begin
require 'XPTSYM';
bind Hopcost = Hopcost_address: matrix;
local I;
MAP$(HOPcost_bias);			!Map in the matrix
I = .MaxN;				!Calculate starting node
if .I eql 0
then begin
     IncN = 0;                          ! Initialize pause count if starting
     Routing_changed = FALSE;
     end;
do begin				! Process while synch queue is empty
    local NODEb: ref NODEblock, Cost, Hops, Index;
    if ._SYNQH neqa 0                   ! If devices need attention
    then begin                          ! then
         MaxN = .I;                     !  save where we are
         IncN = .IncN + 1;              !  and give them a chance.
         $MCB_PAUSE(.Synchblk,.ROUTESaddr);
         return;
         end;
    I = .I + 1;				!  Increment node address
    Index = 0;                          !  Index for new line
    Hops = Infh;                        !  Minimum hops
    Cost = Infc;                        !  Minimum cost
    begin
    local CNT,X: ref vector;
    CNT = NLN + 1;                      ! Lines to do
    X = Hopcost[.I,0,.CNT - 1];         ! (Note: .CNT-1 optimizes code
    do                                  !        instead of NLN)
        begin                           ! Do this for all lines
        local Y;                        !  including the local.
        Y = .X[0];
        Y = .Y<Hop_P,Hop_S>;            ! Isolate hops over this line
        if .Hops gtr .Y then Hops = .Y; !  and get minimum.
        Y = .X[0];
        X = X[1];                       ! (get bliss-16 to auto-increment)%
        Y = .Y<Cost_P,Cost_S>;          ! Isolate cost over this line
        if .Cost gtr .Y                 !  and if this path is better
        then
            begin                       ! then
            Cost = .Y;                  ! save better cost
            Index = .CNT;               ! and better line.
            end;
        end
    while (CNT = .CNT - 1) neq 0;       ! (optimizes in bliss-16)
    end;
    if .Hops gtr .Maxh                  ! If too far away
    then begin
         Hops = Infh;                   ! then make unreachable
         Index = 0;                     ! with no line.
         end;
    if .Cost gtr .Maxc                  ! If too costly
    then begin
         Cost = Infc;                   ! then make unreachable
         Index = 0;                     ! with no line.
         end;
    if (Index = .Index - 1) geq 0       ! figure line number
    then begin
         Index = -.Index;               ! (while producing
         Index = .Index + NLN;          !  optimal bliss-16 code).
         end;
    begin
    local NODEb: ref NODEblock;
    NODEb = $XPT_GET_NODE_DB(.I);       ! Get the affected node.
    if .Phase2_node                     ! If phase II node,
    then Index = .OL;                   !  it is still reachable.
    if .Index geq 0                     ! If there is a path
    then                                ! then
        begin
        if not .Reach                   ! If reachability change
        then
            begin                       ! then
            Reach = TRUE;
            SIGNAL_REACHABILITY(.I,1);  ! log an event.
            end;
        end
    else
        begin
        if .Reach                       ! If reachability change
        then
            begin                       ! then
            Reach = FALSE;
            SIGNAL_REACHABILITY(.I,0);  ! log an event.
            end;
        end;
    if (.Minhop neq .Hops) or (.Mincost neq .Cost)      ! Changes in these
    then                                ! cause
        begin                           ! new routing messages
        Routing_changed = TRUE;         ! to be sent.
        Minhop = .Hops;                 ! Set new values.
        Mincost = .Cost;
        end;
    if not .Local_node
    then OL = .Index;                   ! Reachable through this line.
    end;
    end
while .I lssu NN;

if .Routing_changed then SET_EACH_Srm_FLAG();

MaxN = 0;
end;				!End of ROUTES
routine CHECK: novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Detects any corruption of column 0 (transport users) in the Hop and
!  Cost matrices.
!
! FORMAL PARAMETERS
!
!	NONE.
!
! IMPLICIT INPUTS
!
!	Hop - 2x2 matrix giving the number of hops to a destination
!	      over a line.
!	Cost - 2x2 matrix giving the cost to a destination over a line.
!	User - vector indicating node addresses associated with transport
!	       users rather than remote systems
!	Infh - value used as "infinite" number of hops
!	Infc - value used as "infinite" cost
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	If column 0 in either matrix is corrupted, terminate Transport.
!
!--

begin

require 'XPTSYM';
bind Hopcost = Hopcost_address: matrix;
bind Limit = NLN;

MAP$(HOPcost_bias);
decr I from NN to 1 do begin
    local NODEb: ref NODEblock;
    local X;
    NODEb = $XPT_GET_NODE_DB(.I);       ! Address node data base entry
    X = .Hopcost[.I,0,Limit];		! Pick up entry from matrix
    if
    (if .Local_node then
	if .X neq 0
	    then TRUE
	    else FALSE
    else
	if .X neq ((Infh^Hop_P) or (Infc^Cost_P))
	    then TRUE
	    else FALSE)
    then (BPT(XPT$_CHECK); CALL$L(TERM_XPT));
    end;
end;				!End of CHECK
global routine LINEDN (CCB): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Processes a "line down" event from Transport Initialization.
!
! FORMAL PARAMETERS
!
!	CCB[C_LIN] - Line number being declared down.
!
! IMPLICIT INPUTS
!
!	Hop,Cost,Infh,Infc
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	Sets column LINE of Hop and Cost to "infinite";
!  recalculates routing.
!
!--

begin

local NODEb,LINEb;
require 'XPTSYM';
require 'MCBCOM';
bind Hopcost = Hopcost_address: matrix;

Check();			!Make sure column 0 of the matrices is OK.

LINEb = $XPT_GET_LINE_DB(.CCB[C_LIN]);
NODEb = $XPT_GET_NODE_DB(.Nid);

Line_up = false;
Srm = false;
Send_hello = false;
Service_line = false;
Hello_clock = 0;

decr I from NN to 1 do
    Hopcost[.I,.LINEnumber,NLN] =       ! Make routing impossible
	((Infh^Hop_P) or (Infc^Cost_P));!  over the line

if .Phase2_node
then begin                              ! Phase II node:
     CLN_RETRY(.LINEb);                 !  clean out the retry queue
     $XPECLN(.Nid,0);                   !  send DC for each active link
     Reach = false;                     !  Cancel reachability
     Phase2_node = false;
     end;

ROUTES();                               ! Recalculate the data bases
CCB[C_FNC] = FC_RCE;                    ! Send down
CCB[C_STS] = CS_SUC;                    !  "line down complete"
$MCB_SCHEDULE_CCB(.CCB);                !  indication
end;				!End of LINEDN
global routine LINEUP (CCB): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Processes a "line up" indication from Transport Initialization.
!
! FORMAL PARAMETERS
!
!	CCB[C_LIN] - line being declared up.
!
! IMPLICIT INPUTS
!
!	Hop,Cost,Nty,Lcv,Srm,Nid
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	Initializes column J of the routing data base;
!  recalculates routing.
!
!
!--

begin
map CCB: ref block field (C_XPT_fields);
local NODEb,LINEb;
require 'XPTSYM';

CHECK();			!Make sure column 0 of matrices is OK

LINEb = $XPT_GET_LINE_DB(.CCB[C_LIN]);  ! Address line data base entry

!
!  If the line has gone down again, ignore line up
!

if .LINEstate eql TC
then begin
     !
     !  Otherwise - process the line up
     !
     NODEb = $XPT_GET_NODE_DB(.Nid);
     Phase2_node = false;

     selectone .Nty of
         set
         [PhTwo]:                       ! Adjacent node is Phase II:
             begin                      !  Don't include in routing data base.
             Phase2_node = true;        !  It can talk to Phase II nodes.
             Reach = TRUE;              !  Accessable
             OL = .LINEnumber;          !   over this line
             end;
         [Full]:
             Send_hello = true;
         [otherwise]:
             begin                      ! Adjacent node is not full routing:
             bind Hopcost = Hopcost_address: matrix;

             if .Lcv gtr 0              !  If the cost is positive then
             then                       !  that's the cost to the adjacent node
                 Hopcost[.Nid,.LINEnumber,NLN] = (.Lcv^Cost_P + 1^Hop_P)
             else                       !  otherwise
                 CALL$L(TERM_XPT);      !   corruption!

             if .Nty eql Small
             then Send_hello = true;
             end;
         tes;

     SET_EACH_Srm_FLAG();
     Hello_clock = .Hello_timer;
     Line_up = true;

     $NM_LOG_BEGIN();
     PARAMETER_CM(3,1);			! Log a
     PARAMETER_DU_2(,Nid);              !  "line up"
     $NM_LOG_END(4^6+$XPT$E_LUP,.NMXid);

     ROUTES();				! Recalculate routing data base
     end;

CCB[C_FNC] = FC_RCE;			!Send "line up
CCB[C_STS] = CS_SUC;			!  complete" to
$MCB_SCHEDULE_CCB(.CCB);                !  Transport Line Interface

end;				!End of LINEUP
global routine RCVROU (CCB): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Processes a received routing message.
!
! FORMAL PARAMETERS
!
!	CCB[C_LIN] - line message was received on
!	CCB[C_BIAS] - descriptor for message
!
! IMPLICIT INPUTS
!
!	Hop,Cost,Lcv
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	Updates routing data base from routing message;
!  recalculates routing
!
!--

begin

local LINEb;
require 'XPTSYM';
require 'MCBCOM';
bind Hopcost = Hopcost_address: matrix;
local BUFPTR,BUFLEN,NO_NODES;
pointer PTR;


!
!  Validate data base
!

CHECK();					!Make sure column 0 is OK

!
!  If the circuit is down, ignore the message
!

LINEb = $XPT_GET_LINE_DB(.CCB[C_LIN]);  ! Address line data base entry

if .LINEstate eql RU then begin			

!
!  Validate the message
!

    MAPBUF(.CCB,BUFPTR,BUFLEN);			!Map to and address buffer
    if .Lcv lss 0 then				!Line cost negative -
	CALL$L(TERM_XPT)			!  bring down transport
    else if VALID_BUFFER(.CCB,.BUFPTR,.BUFLEN)	!Make sure buffer is good
    then begin

!
!  Copy message fields into routing data base
!

         begin                          ! Get number of nodes to process
         local ADR;
         bind MXA = NO_NODES: ref vector;
         PTR = ch$plus(.BUFPTR,1);      ! Bump past control header
         ADR = getw(PTR);

         if (MXA = .NODEmaximum_address_vector) neqa 0
         then begin
              if (MXA = .MXA [.ADR - 1]) neq 0
              then begin
                   if .MXA gtr NN
                   then MXA = NN;
                   end
              else MXA = NN;
              end
         else MXA = NN;

         NO_NODES = minu (.MXA, (.BUFLEN-5)^-1);
         end;
         incr I from 1 to NN do
            begin
            local TEMP,COSTI;
            bind HOPI = TEMP;           ! (for optimization)
            TEMP = ((Infh^Hop_P) or (Infc^Cost_P)); ! assume not accessable.
            if .I leq .NO_NODES
            then begin
                 MAP$(.CCB[C_BIAS]);    ! Map in the buffer
                 TEMP = getw(PTR);      ! Pick up next routing field
                 COSTI = .TEMP<Cost_P,Cost_S>;  !  COST subfield
                 HOPI = .TEMP<Hop_P,Hop_S>;     !  HOP subfield
                 COSTI = .COSTI+.Lcv;           ! Add in our cost
                 HOPI = .HOPI+1;                !  and one more hop.
                 if .COSTI gtru Infc            ! Top off
                 then COSTI = Infc;
                 if .HOPI gtru Infh             !  if necessary.
                 then HOPI = Infh;
                 COSTI = .COSTI^Cost_P;         ! Position
                 HOPI = .HOPI^Hop_P;            ! and
                 TEMP = .HOPI;                  ! reconstruct.
                 TEMP = .TEMP+.COSTI;
                 end;
            MAP$(HOPcost_bias);                 ! Map in the Hop/Cost matrix
            Hopcost[.I,.LINEnumber,NLN] = .TEMP;        ! and update it
            end;
	 ROUTES();				!Recalculate routing
	 end;
    end;

!
!  Clean up the accounting and return the buffer
!

INPUTcount = .INPUTcount - 1;           ! Decrement outstanding buffers
DLLquota = .DLLquota + 1;               !  and increment global quota
CCB[C_FNC] = FC_RCE;                    ! Return buffer
$MCB_SCHEDULE_CCB(.CCB);                !  to TLI
end;				!End of RCVROU
global routine COSTCH (LINE,COSTJ): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Processes a cost change for a line
!
! FORMAL PARAMETERS
!
!	LINE	Line cost change is for
!	COSTJ	New cost for line
!
! IMPLICIT INPUTS
!
!	Cost, Lcv
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	Updates Cost and Lcv; recalculates routing.
!
!--

begin

local LINEb;
require 'XPTSYM';
bind Hopcost = Hopcost_address: matrix;

!
!  Validate new and old costs for line
!

LINEb = $XPT_GET_LINE_DB(.LINE);        ! Address line data base entry
if (.COSTJ leq 0) or (.Lcv leq 0) then
    CALL$L(TERM_XPT)

!
!  Update data base for cost change
!

else begin
    bind DIF = .COSTJ - .Lcv;
    Lcv = .COSTJ;
    MAP$(HOPcost_bias);
    decr I from NN to 1 do			!Update Cost matrix as well
	(Hopcost[.I,.LINE,NLN])<Cost_P,Cost_S> =
	    .(Hopcost[.I,.LINE,NLN])<Cost_P,Cost_S> + DIF;
    end;

!
!  Make sure timer goes off to recalculate routes
!

Routing_clock = 1;

end;				!End of COSTCH
global routine OPENT (CCB): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Opens a transport port to identify a local transport user.
!
! FORMAL PARAMETERS
!
!	CCB	Function CCB for the open.
!
! IMPLICIT INPUTS
!
!	User,Hop,Cost
!
! ROUTINE VALUE: Acceptance or rejection of the open
! COMPLETION CODES:
!
!	TRUE - Open accepted.
!	FALSE - Open rejected.
!
! SIDE EFFECTS:
!
!	Updates User,Hop and Cost; recalculates routing.
!
!--

begin
map CCB: ref block field (C_FIELDS);
local NODEb;
require 'XPTSYM';
bind Hopcost = Hopcost_address: matrix;

!
!  Validate routing data base
!

CHECK();
NODEb = $XPT_GET_NODE_DB(.CCB[C_PRM1]); ! Address node data base entry

if .Local_node                          ! Address already in use -
then return SIGNAL_STOP (CE_ERR);       !  reject request

!
!  Update data base entries for this user
!

Local_node = TRUE;
User = .CCB[C_PIX];                     ! Save process ID for user
Hopcost[.CCB[C_PRM1],0,NLN] = 0;        ! Free to get to local user
ROUTES();                               ! Recalculate routing
CCB [C_STS] = CS_SUC;

!
!  Terminate function CCB
!

CCB[C_FNC] = FC_CCP;
$MCB_SCHEDULE_CCB(.CCB);
end;				!End of OPENT
global routine CLOSET (CCB): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Processes close of a port for a transport user.
!
! FORMAL PARAMETERS
!
!	CCB	Function CCB for the close.
!
! IMPLICIT INPUTS
!
!	User,Hop,Cost
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	Updates User,Hop,Cost; recalculates routing.
!
!--

begin

local NODEb;
require 'XPTSYM';
require 'MCBCOM';
bind Hopcost = Hopcost_address: matrix;
local RET;

!
!  Validate routing data base
!

CHECK();
NODEb = $XPT_GET_NODE_DB(.CCB[C_PRM1]); ! Address node data base entry

if not .Local_node                      ! Continue only if port is local
then return SIGNAL_STOP (CE_ERR);       ! Invalid node address - abort function

!
!  Update routing data base
!

Local_node = FALSE;
User = 0;
Hopcost[.CCB[C_PRM1],0,NLN] =           ! Can't get there
    ((Infh^Hop_P) or (Infc^Cost_P));    !  from here
ROUTES();                               ! Recalculate routing
CCB [C_STS] = CS_SUC;

!
!  Terminate function CCB
!

CCB[C_FNC] = FC_CCP;
$MCB_SCHEDULE_CCB(.CCB);
end;				!End of CLOSET
global routine DECTIM: CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Processes a timer call for the Decision Module.  A call here does
!  not necessarily mean any timer has expired.
!
! FORMAL PARAMETERS
!
!	NONE.
!
! IMPLICIT INPUTS
!
!	LINEflags, Routing_clock
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	If Routing_clock has expired, set each Srm flag, restart the timer
!	and recalculate routing.
!
!--

begin
require 'XPTSYM';
CHECK();				! Make sure the data base's OK
SET_EACH_Srm_FLAG();                    ! Ask that routing messages be sent
ROUTES();				! Recalculate routing
end;                                    ! End of DECTIM
routine SET_EACH_Srm_FLAG: novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Set the bit on each line requesting a routing message to be sent.
!
! FORMAL PARAMETERS
!
!	None
!
! IMPLICIT INPUTS
!
!	None
!
! ROUTINE VALUE: Success/failure
! COMPLETION CODES:
!
!	None
!
! SIDE EFFECTS:
!
!	None
!
!--

begin
require 'XPTSYM';

$XPT_for_each_LINEb_do_begin
    Srm = true;                         ! Signal "send a routing message"
$XPT_next_LINEb_end;

end;				!End of SET_EACH_Srm_FLAG
routine SIGNAL_REACHABILITY (NODE,STATUS): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Logs a reachability event
!  and cleans up links for the node if transition to unreachable.
!
! FORMAL PARAMETERS
!
!	NODE - Number of unreachable node
!	STATUS - 0/transition to reachable, 1/transition to unreachable
!
! IMPLICIT INPUTS
!
!	None
!
! ROUTINE VALUE: Success/failure
! COMPLETION CODES:
!
!	None
!
! SIDE EFFECTS:
!
!	None
!
!--

begin
require 'XPTSYM';
$NM_LOG_BEGIN();
PARAMETER_C_1(7,STATUS);
$NM_LOG_END(4^6+$XPT$E_NRC,.NODE);
if .STATUS neq 0
then
    begin
    $XPECLN(.NODE,0);
    MAP$(HOPcost_bias);
    end;
end;				!End of SIGNAL_REACHABILITY
routine VALID_BUFFER (CCB,BUFPTR,BUFLEN) =

!++
! FUNCTIONAL DESCRIPTION:
!
!  Validates a routing message:
!	1) Checks the control header
!	2) Validates the checksum
!	3) Determines that the message contains no more than NN entries,
!	  except for unreachable ones.
!  In cases 1 and 2, an invalid message brings down the line it came
!  over.  In case 3, entries after NN are ignored anyway, and reachable
!  entries (Hops neq Infh or Cost neq Infc) will cause an error to be
!  logged.
!
! FORMAL PARAMETERS
!
!	BUFPTR - character pointer to buffer to be examined
!	BUFLEN - length of message in buffer (equal to 2*N+5 where N
!		 is the number of routing entries in the message)
!
! IMPLICIT INPUTS
!
!	Nid
!
! ROUTINE VALUE: Success/failure
! COMPLETION CODES:
!
!	TRUE - message is valid
!	FALSE - message is flawed; do not use it.
!
! SIDE EFFECTS:
!
!	If the buffer is not valid, an error will be logged;
!	if it is really bad (tests 1 or 2 fail) its line will
!	be dropped.
!
!--

begin

local LINEb;
require 'XPTSYM';
require 'MCBCOM';
local CTLHDR,NO_NODES,PTR,RET,SUM;

LINEb = $XPT_GET_LINE_DB(.CCB[C_LIN]);  ! Address line table entry
PTR = .BUFPTR;				! Initialize work pointer
CTLHDR = getb(PTR);			! Pick up transport control header
if biton(.CTLHDR,%o'360') then RET = 1	! Reserved bits on
else if getw(PTR) neq .Nid then		! Invalid source node
    RET = 3
else begin
    local P;
    P = .PTR;
    NO_NODES = (.BUFLEN-5)^-1;		!Calculate number of cells in message
    SUM = 0;				!Initialize checksum
    decr I from .NO_NODES to 1 do	!Calculate
	checksum(SUM,getw(P));          !  checksum
    if .SUM neq getw(P) then RET = 2	!Checksum doesn't match one in message
    else if .NO_NODES leq NN then	!Message doesn't overextend data base,
	RET = 0				!  message is valid
    else begin				!Message reports on extra nodes:
	local NNN;
	NNN = 0;			!  Assume no reachable nodes past NN
	P=ch$plus(ch$plus(.PTR,NN),NN);	!  Point past nodes we know about
	incr I from NN+1 to .NO_NODES do!  Scan for the
	    (if (getw(P) neq		!    greatest node
	    ((Infh^Hop_P) or (Infc^Cost_P)))!address that
		then NNN = .I);		!    is reachable
	if .NNN eql 0 then		!All extra entries
	    RET = 0			!  are unreachable
	else RET = 4 + .NNN		!Some entry is real - that's bad
	end
    end;

!
!  Message is no good - signal an event and maybe restart the line
!

if .RET neq 0 then begin

    $NM_LOG_BEGIN();
    $NM_LOG_END (4^6+    
    (selectone .RET of
    set

    [1]:	begin			! Routing message format error:
	COUNTER_INCREMENT(XPTDB,XPTfmt_loss); !   Increment packet counter
	CALL$L(PKTA_HDR,.BUFPTR);       !   Log packet hdr in Event Buffer
	$XPT$E_FMT
		end;

    [2]:	begin			! Checksum error:
	bind THREE = uplit(3);
	COUNTER_INCREMENT(LINEb,XPTlinedn);!   Increment "line downs" counter
	PARAMETER_C_1(5,THREE);
	CALL$L(PKTA_HDR,.BUFPTR);       !   Move in packet header
	$XPT$E_LSF
		end;

    [3]:	begin			! Invalid source node:
	COUNTER_INCREMENT(LINEb,XPTlinedn);!   Increment "line downs" counter
	PARAMETER_CM(4,1);		!   Move in as
	PARAMETER_DU_2(,Nid);		!     expected node ID
	PARAMETER_C_1(5,uplit(4));      !   Move in reason code
	CALL$L(PKTA_HDR,.BUFPTR);       !   Move in packet header
	$XPT$E_LOF
		end;

    [otherwise]:	begin		! Partial update loss:
	local NNN;
	COUNTER_INCREMENT(XPTDB,XPTrout_loss); !   Increment counter
	CALL$L(PKTA_HDR,.BUFPTR);       !   Move packet header into buffer
	NNN = .RET-4;			!   Move in highest reachable
	PARAMETER_DU_2(2,NNN);		!     node address
	$XPT$E_RUL
		end;

    tes),.NMXid);
	    
    if .RET lss 4                       ! Message is really bad:
    then begin                          ! Re-initialize.
         Service_line = true;
         return FALSE
         end;

    end;

TRUE                                    ! Acceptable message - give OK
end;                                    ! End of VALID_BUFFER
end					!End of module XPTDEC
eludom