Google
 

Trailing-Edge - PDP-10 Archives - BB-R595B-SM_11-9-85 - mcb/xpt/xptnmi.bli
There is 1 other file named xptnmi.bli in the archive. Click here to see a list.
module XPTNMI   (				! Network Management stuff
		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:	This is the Network Management interface for the MCB
!		implementation of Transport.  It dispatches to a processing
!		routine in XPTNMX.
!
! ENVIRONMENT:	MCB
!
! AUTHOR:	L. Webber,	CREATION DATE: 20-Nov-80
!
! MODIFIED BY:
!
! 1.00	L. Webber, 11-Dec-80
!	Modified the model interface template to match XPT.
!
! 1.01	L. Webber, 22-Dec-80
!	Split into XPT and TLI parts
!
! 1.02	L. Webber, 25-Feb-81
!	NMX entries are now in process XNM.
!
! 1.03	L. Webber, 14-Sep-81
!	Fix "zero" call to actually do a zero.
!
! 1.04	A. Peckham 21-Sep-81
!	Save some space.
!
! 1.05	A. Peckham 16-Sep-82
!	Add MAXIMUM ADDRESS parameter support for non-EXECUTOR node.
!
! 1.06	A. Peckham 27-Sep-82
!	Make parameter #2500 as FENCE with compatability to MAXIMUM ADDRESS.
!
! 1.07	A. Peckham  1-Oct-82
!	Make CLEAR NODE ALL work in CLEAR_NODE.
!
! 1.08	A. Peckham 11-Oct-82
!	Fix ref bug introduced into NODE_COUNTERS during code optimization.
!
! 1.09	D. Brannon 22-Sep-83
!	Fix typo in PKTA_HDR which caused the source node address to be wrong.
!
!--

!
! REQUIRED FILES
!

require 'XPTMAC';

!
! TABLE OF CONTENTS:
!
%if %bliss (bliss16)
%then linkage XPT_LKG_DB_CCB = jsr (register = 3, register = 4),
              XPT_LKG_NODEb = jsr (register = 2);
%else macro XPT_LKG_DB_CCB = BLISS36C %;
%fi

forward routine
    XPE_NM: CALL$ novalue,              ! Control (i.e., NM)
    PKTA_HDR: CALL$ novalue,
    NODE_DB: LINKAGE_CCB,
    CLEAR_NODE: XPT_LKG_DB_CCB novalue, ! Clear a node parameter
    NODE_COUNTERS: novalue,             ! Get node counters
    RETURN_NODE_LIST: XPT_LKG_DB_CCB novalue,
                                        ! Return list of known nodes
    SET_NODE: XPT_LKG_DB_CCB novalue,   ! Set a node parameter
    SHOW_AND_ZERO_NODE_COUNTERS: XPT_LKG_DB_CCB novalue,
                                        ! Show and zero node counters
    SHOW_NODE: XPT_LKG_DB_CCB novalue,  ! Show node parameters
    SHOW_NODE_CIRCUIT : XPT_LKG_NODEb novalue,
    SHOW_NODE_STATE : XPT_LKG_NODEb novalue,
    ZERO_NODE_COUNTERS: XPT_LKG_DB_CCB novalue; ! Zero node counters

!
! MACROS:
!

!
! EQUATED SYMBOLS:
!

literal
    NODEtype = NMX$ENT_nod,
    CIRCUITtype = NMX$ENT_ckt;

!
! OWN STORAGE:
!

!
! EXTERNAL REFERENCES:
!
!       None
%sbttl 'Network Management'
global routine XPE_NM (CCB): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine is activated by a control request from
!	Network Management.
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    external MCB$GAW_PROCESS_DATA_BASE: vector[2];
    bind XPTDB = .MCB$GAW_PROCESS_DATA_BASE[1]: XPTDBblock;
    map CCB: ref block field (C_NM_FIELDS);
    require 'XPTSYM';

    selectone .CCB [C_NM_ENTITY] of
	    set
	    [NMX$ENT_nod]: 			! NM fnc for node parameter
		case .CCB [C_NM_FUNC] from NMX$FNC_lo to NMX$FNC_hi of
		    set 			! *** MODULE ***
		    [NMX$FNC_set]:		! Set parameters
			SET_NODE(XPTDB,.CCB);
		    [NMX$FNC_clr]: 		! Clear parameters:
			CLEAR_NODE(XPTDB,.CCB);
		    [NMX$FNC_zro]: 		! Zero counters
			ZERO_NODE_COUNTERS(XPTDB,.CCB);
		    [NMX$FNC_sho]: 		! Show selected items
			SHOW_NODE(XPTDB,.CCB);
		    [NMX$FNC_szc]: 		! Show and zero counters
			SHOW_AND_ZERO_NODE_COUNTERS(XPTDB,.CCB);
		    [NMX$FNC_ret]: 		! Return selected items
			RETURN_NODE_LIST(XPTDB,.CCB);
		    [inrange, outrange]: CCB [C_STS] = $NM$ERR_MPE;
		    tes;
	    [otherwise]: CCB [C_STS] = $NM$ERR_URC;
	    tes;

    CCB [C_FNC] = FC_CCP;
    $MCB_SCHEDULE_CCB (.CCB);
    end;
global routine PKTA_HDR (SPTR): CALL$ novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
! Constructs a "packet header" parameter block in the event logging
! area.  It is assumed that the destination and source areas are both
! mapped.
!
! FORMAL PARAMETERS
!
!	SPTR	A pointer to an area which contains a packet (routing)
!		header.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

begin

local F,T;
pointer S;
S = .SPTR;

T = (if biton((F=getb(S)),1)	! Message type
    then 2			!   is control
    else 4);			!   or data
PARAMETER_CM(0,.T);		! Multiple fields, 2 or 4 of them
PARAMETER_H_1(,F);		! Hex field, 1 byte: routing flags
if .T eql 4 then begin		! Data header only:
    F = getw(S);		!   Decimal unsigned, 2 bytes:
    PARAMETER_DU_2(,F);		!     destination node address
    end;
F = getw(S);			! Decimal unsigned, 2 bytes:
PARAMETER_DU_2(,F);		!   source node address
if .T eql 4 then begin		! Data header only:
    F = getb(S);		!   Hex field, 1 byte:
    PARAMETER_DU_2(,F);		!     forwarding flags
    end;

end;				!End of PKTA_HDR
routine NODE_DB (CCB): LINKAGE_CCB =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine gets the node data base
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    map CCB: ref block field(C_NM_FIELDS);
    bind NMPAR = CCB[C_NM_NMPAR]: ref block field(NMX_NMPAR_FIELDS);
    local NODEb;
    require 'XPTSYM';

    !
    ! Determine the entity whose parameter is to be set
    !

    if (NODEb = $XPT_GET_NODE_DB(
              begin
              local ADDR;
              if (ADDR = .NMPAR[NMX_NMPAR_NODE_ADDRESS]) eql 0
              then return .ADDR;
              .ADDR
              end)) eqla 0
    then CCB [C_STS] = $NM$ERR_URC;

    .NODEb
    end;                                ! of NODE_DB
routine CLEAR_NODE (XPTDB,CCB): XPT_LKG_DB_CCB novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine clears a circuit parameter
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    map CCB: ref block field(C_NM_FIELDS);
    bind NMPAR = CCB[C_NM_NMPAR]: ref block field(NMX_NMPAR_FIELDS),
         NODE_ADDRESS = .NMPAR[NMX_NMPAR_NODE_ADDRESS];
    local NODEb;
    require 'XPTSYM';
    local PNUM;

    !
    ! Determine the entity whose parameter is to be set
    !

    if (NODEb = NODE_DB(.CCB)) eqla 0
    then return;                        ! Invalid node address

    PNUM = 2500;

    if .CCB[C_CNT] neq 0
    then begin
         pointer PTR;
         MAPBUF(.CCB,PTR);
         PNUM = getw(PTR);
         end;

    selectone .PNUM of                 ! Dispatch on parm #
        set
        [2500]:                        ! FENCE
            begin
            local MXA: ref vector;
            if (MXA = .NODEmaximum_address_vector) neqa 0
            then begin
                 MXA [.NODEaddress - 1] = 0;
                 CCB [C_STS] = NM$SUC;
                 end;
            end;
        [otherwise]:                    ! Parameter not applicable
            CCB [C_STS] = $NM$ERR_PNA;
        tes;
    end;                                ! of CLEAR_NODE
routine NODE_COUNTERS (NODEb): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine inserts the counters for the specified node
!       in the NM buffer.
!
! FORMAL PARAMETERS:
!
!	NODEb	Node data base pointer
!
! IMPLICIT INPUTS:
!	None
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    map NODEb: ref NODEblock;
    external MCB$GAW_PROCESS_DATA_BASE: vector[2];
    bind XPTDB = .MCB$GAW_PROCESS_DATA_BASE[1]: XPTDBblock;
    COUNTER_8(900,Aged_Loss);           ! Local Aged Packet Loss
    COUNTER_16(901,Unreach_Loss);	! Local Node Unreachable Packet Loss
    COUNTER_8(902,Range_Loss);          ! Local Node Out-of-Range Packet Loss
    COUNTER_8(903,Oversize_Loss);	! Local Node Over Size Packet Loss
    COUNTER_8(910,Format_Errors);	! Packet Format Errors
    COUNTER_8(920,Routing_Loss);	! Partial Routing Update Loss
    COUNTER_8(930,Verify_Rejects);	! Verification Rejects
    end;                                ! of NODE_COUNTERS
routine RETURN_NODE_LIST (XPTDB,CCB): XPT_LKG_DB_CCB novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
! Returns a list of all reachable nodes in the network.
!
! FORMAL PARAMETERS
!
!	CCB	Function CCB
!		CCB[C_BUF]	Doubleword pointer to parameter block
!				in which the list of node IDs requested
!				is returned.
!		CCB[C_CNT]	Maximum length of buffer; on return contains
!				the length of returned data.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE: "Success" or a failure code
! COMPLETION CODES:
!
!	NM$SUC		Success; the node IDs of all active nodes are
!			returned in the supplied buffer.
!
!	$NM$ERR_REE	The full list of node IDs will not fit into the
!			supplied buffer.  All possible data are returned;
!			CCB[C_CNT] is valid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

begin
map CCB: ref block field(C_NM_FIELDS);
local BUFLEN;
pointer PTR;
require 'XPTSYM';

MAPBUF(.CCB,PTR,BUFLEN);		! Map in buffer
CCB [C_CNT] = 0;

!
!  Check each node number for inclusion
!

$XPT_for_each_NODEb_do_begin
    if .Reach                           ! Reachable node:
    then if (BUFLEN = .BUFLEN - 3) geq 0 !   Data will fit
         then begin                     !   Move in node number
              putb(.(NODEaddress)<0,8>,PTR);
              putb(.(NODEaddress)<8,8>,PTR);
              putb(0,PTR);               !     and a null node name
              CCB [C_CNT] = .CCB [C_CNT] + 3;
              end;
$XPT_next_NODEb_end;

!
! Set status if all fits
!

CCB [C_STS] = $NM$ERR_REE;

if .BUFLEN geq 0 then CCB [C_STS] = NM$SUC;

end;				!End of RETURN_NODE_LIST
routine SET_NODE (XPTDB,CCB): XPT_LKG_DB_CCB novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine sets a node parameter
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    map CCB: ref block field(C_NM_FIELDS);
    bind NMPAR = CCB[C_NM_NMPAR]: ref block field(NMX_NMPAR_FIELDS),
         NODE_ADDRESS = .NMPAR[NMX_NMPAR_NODE_ADDRESS];
    local NODEb;
    require 'XPTSYM';
    local PNUM,PVAL;

!
! Determine the entity whose parameter is to be set
!

if (NODEb = NODE_DB(.CCB)) eqla 0
then return;                            ! Invalid node address

begin
pointer PTR;
MAPBUF(.CCB,PTR);
PNUM = getw(PTR);
PVAL = getw(PTR);
end;

if NODE_ADDRESS eql .Tid
then begin
     selectone .PNUM of                 ! Dispatch on parm #
         set

    [910]:				! ROUTING TIMER (T1)
        selectoneu .PVAL of
            set
            [1 to 65535]:
                begin
                Routing_timer = .PVAL;  !   Update timer resetting value
                !
                ! Fix current clock to be within reason.
                !
                if .Routing_clock gtru .Routing_timer
                then Routing_clock = .Routing_timer;

                CCB [C_STS] = NM$SUC;
                end;
            [otherwise]:
                CCB [C_STS] = $NM$ERR_IPV;
            tes;

    [920]:				! MAXIMUM ADDRESS (NN)
        selectoneu .PVAL of
            set
            [1 to .XPTDB[XPT$nn]]:
                begin                   !   Value OK -
                XPTDB[XPTnn] = .PVAL;	!     update NN
                CCB [C_STS] = NM$SUC;
                end;
            [otherwise]:
                CCB [C_STS] = $NM$ERR_IPV;
            tes;

    [922]:				! MAXIMUM COST (Maxc)
        selectoneu .PVAL of
            set
            [1 to 1022]:
                begin
                Maxc = .PVAL;
                CCB [C_STS] = NM$SUC;
                end;
            [otherwise]:
                CCB [C_STS] = $NM$ERR_IPV;
            tes;

    [923]:				! MAXIMUM HOPS (Maxh)
        selectoneu (PVAL = .PVAL<0,8>) of
            set
            [1 to 30]:
                begin
                Maxh = .PVAL;
                CCB [C_STS] = NM$SUC;
                end;
            [otherwise]:
                CCB [C_STS] = $NM$ERR_IPV;
            tes;

    [924]:				! MAXIMUM VISITS (Maxv)
        selectoneu (PVAL = .PVAL<0,8>) of
            set
            [.Maxh to 255]:
                begin
                Maxv = .PVAL;
                CCB [C_STS] = NM$SUC;
                end;
            [otherwise]:
                CCB [C_STS] = $NM$ERR_IPV;
            tes;

    [otherwise]:                        ! Parameter not applicable
        CCB [C_STS] = $NM$ERR_PNA;
        tes;
    end
else begin
     selectone .PNUM of                 ! Dispatch on parm #
         set
         [920,				! MAXIMUM ADDRESS (NN)
          2500]:                        ! FENCE
             selectoneu .PVAL of
                 set
                 [1 to .XPTDB[XPT$nn]]:
                     begin              !   Value OK -
                     local MXA: ref vector;
                     while (MXA = .NODEmaximum_address_vector) eqla 0
                     do begin
                        if not $MCB_GET_DSR ((.XPTDB[XPT$nn]*%upval), MXA)
                        then begin
                             CCB [C_STS] = $NM$ERR_REE;
                             return;
                             end;
                        NODEmaximum_address_vector = .MXA;
                        decru IDX from .XPTDB[XPT$nn] to 1
                        do begin
                           MXA [0] = 0;
                           MXA = MXA [1];
                           end;
                        end;
                     if .PVAL eql NN then PVAL = 0;
                     MXA [.NODEaddress - 1] = .PVAL;
                     CCB [C_STS] = NM$SUC;
                     end;
                 [otherwise]:
                     CCB [C_STS] = $NM$ERR_IPV;
                 tes;
        [otherwise]:                    ! Parameter not applicable
            CCB [C_STS] = $NM$ERR_PNA;
        tes;
     end;
end;                                    ! of SET_NODE
routine SHOW_AND_ZERO_NODE_COUNTERS (XPTDB,CCB): XPT_LKG_DB_CCB novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine show the counters for the specified node
!       and then zeroes them.
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    map CCB: ref block field(C_NM_FIELDS);
    bind NMPAR = CCB[C_NM_NMPAR]: ref block field(NMX_NMPAR_FIELDS),
         NODE_ADDRESS = .NMPAR[NMX_NMPAR_NODE_ADDRESS];
    local NODEb;
    require 'XPTSYM';

    if (NODEb = NODE_DB (.CCB)) eqla 0
    then return;                        ! Invalid node address

!
!  Map in the return buffer
!

    $NM_RESPONSE_BEGIN(.CCB);
    if NODE_ADDRESS eqlu .Tid
    then NODE_COUNTERS (.NODEb);
    $NM_RESPONSE_END(.CCB);
    begin
    local STS_SAVE;
    STS_SAVE = .CCB [C_STS];
    ZERO_NODE_COUNTERS (.XPTDB,.CCB);
    CCB [C_STS] = .STS_SAVE;
    end;
    end;                                ! of SHOW_AND_ZERO_CIRCUIT_COUNTERS
routine SHOW_NODE (XPTDB,CCB): XPT_LKG_DB_CCB novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine shows node parameters
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    map CCB: ref block field(C_NM_FIELDS);
    bind NMPAR = CCB[C_NM_NMPAR]: ref block field(NMX_NMPAR_FIELDS);
    bind NODE_ADDRESS = .NMPAR[NMX_NMPAR_NODE_ADDRESS];
    literal                             ! Node types:
        TYPE_2 = 0,                     !  Phase II
        TYPE_A = 1,                     !  Adjacent
        TYPE_R = 2,                     !  Remote
        TYPE_U = 3,                     !  Local XPT user
        TYPE_E = 4,                     !  Executor
        TYPE_L = 5,                     !  Loop
        TYPE_bad = 6,                   !  (invalid)
        TYPE_lo = min (TYPE_E, TYPE_A, TYPE_R, TYPE_L, TYPE_U, TYPE_bad),
        TYPE_hi = max (TYPE_E, TYPE_A, TYPE_R, TYPE_L, TYPE_U, TYPE_bad);
    local NODE_TYPE,NODEb,LINEb;
    require 'XPTSYM';

!
!  Determine the entity whose data are to be shown
!

$NM_RESPONSE_BEGIN(.CCB);		! Initialize response buffer

!
!  Figure out the node type
!

if (NODEb = $XPT_GET_NODE_DB (NODE_ADDRESS)) neqa 0
then begin
     if .Local_node
     then begin
          if NODE_ADDRESS eql .Tid
          then NODE_TYPE = TYPE_E
          else NODE_TYPE = TYPE_U;
          end
     else if .Reach
          then begin
               LINEb = $XPT_GET_LINE_DB(.OL);
               selectone .Nty of
                        set
                        [PHtwo,TOPS20]:
                            NODE_TYPE = TYPE_2;
                        [otherwise]:
                            if .Minhop eql 1
                            then NODE_TYPE = TYPE_A
                            else NODE_TYPE = TYPE_R;
                        tes;
               end
          else NODE_TYPE = TYPE_R;
     end
else if NODE_ADDRESS eql 0
     then NODE_TYPE = TYPE_L
     else NODE_TYPE = TYPE_bad;

case .CCB [C_NM_SELECT] from NMX$SEL_lo to NMX$SEL_hi of
    set
    [NMX$SEL_sum]:
        selectu .NODE_TYPE of
            set
            [TYPE_U]:
                SHOW_NODE_STATE (.NODEb);       ! STATE
            [TYPE_2,TYPE_A,TYPE_R]:
                begin
                SHOW_NODE_STATE (.NODEb);       ! STATE
                SHOW_NODE_CIRCUIT (.NODEb);     ! CIRCUIT
                end;
            tes;
    [NMX$SEL_sta]:
        selectu .NODE_TYPE of
            set
            [TYPE_2,TYPE_A,TYPE_R,TYPE_U]:
                SHOW_NODE_STATE (.NODEb);       ! STATE
            [TYPE_2,TYPE_A]:
                begin                           ! TYPE
                local VALUE;
                LINEb = $XPT_GET_LINE_DB (.OL);
                case .Nty from 2 to 5 of
                    set                         !   Move in node type:
                    [Full]: VALUE = 0;          !     Routing
                    [Small]: VALUE = 1;         !     Non-routing
                    [PhTwo,TOPS20]: VALUE = 2;  !     Phase II
                    tes;
                PARAMETER_C_1(810,VALUE);
                end;
            [TYPE_A,TYPE_R]:
                begin
                PARAMETER_DU_2(820,Mincost);    ! COST
                PARAMETER_DU_1(821,Minhop);     ! HOPS
                end;
            [TYPE_2,TYPE_A,TYPE_R]:
                SHOW_NODE_CIRCUIT (.NODEb);     ! CIRCUIT
            tes;
    [NMX$SEL_cha]:
        selectu .NODE_TYPE of
            set
            [TYPE_E]:
                begin                   ! ROUTING VERSION
                PARAMETER_CM(900,3);            ! Three fields:
                PARAMETER_DU_1(,uplit(1));      !   Version # = 1
                PARAMETER_DU_1(,uplit(3));      !   Routing ECO = 3
                PARAMETER_DU_1(,uplit(0));      !   User ECO = 0
                PARAMETER_C_1(901,uplit(0));    ! TYPE
                PARAMETER_DU_2(910,Routing_timer);! ROUTING TIMER
                begin
                local VALUE;
                VALUE = NN;                     ! MAXIMUM ADDRESS
                PARAMETER_DU_2(920,VALUE);
                VALUE = NLN;                    ! MAXIMUM CIRCUITS
                PARAMETER_DU_2(921,VALUE);
                end;
                PARAMETER_DU_2(922,Maxc);       ! MAXIMUM COST
                PARAMETER_DU_1(923,Maxh);       ! MAXIMUM HOPS
                PARAMETER_DU_1(924,Maxv);       ! MAXIMUM VISITS
                begin                           ! MAXIMUM BUFFERS
                local VALUE;
                VALUE = .XPTDB[XPT$updq]        !   Store routing/update quota
                        + .XPTDB[XPT$eclq]      !     plus ECL quota
                        + $LINQ;                !     plus total line quota
                PARAMETER_DU_2(930,VALUE);
                end;
                PARAMETER_DU_2(931,DLLsize);    ! BUFFER SIZE
                end;
            [TYPE_2,TYPE_A,TYPE_E,TYPE_R,TYPE_U]:
                begin
                local MXA: ref vector;
                if (MXA = .NODEmaximum_address_vector) neqa 0
                then if (MXA = .MXA [.NODEaddress - 1]) neq 0
                     then PARAMETER_DU_2(2500,MXA);    ! MAXIMUM ADDRESS
                end;
            tes;
    [NMX$SEL_cou]:
        selectu .NODE_TYPE of
            set
            [TYPE_E]:
                NODE_COUNTERS (.NODEb);
            tes;
    tes;

    $NM_RESPONSE_END(.CCB);
    end;                                ! of SHOW_NODE
routine SHOW_NODE_CIRCUIT (NODEb): XPT_LKG_NODEb novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine shows the node circuit
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    local LINEb;
    require 'XPTSYM';

    LINEb = $XPT_GET_LINE_DB(.OL);
    NMX$PARAMETER_CIRCUIT(PD_NMX,.NMXid,822);
    end;                                ! of SHOW_NODE_CIRCUIT
routine SHOW_NODE_STATE (NODEb): XPT_LKG_NODEb novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine shows the node state
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    local VALUE;
    require 'XPTSYM';

    VALUE = 4;                          !   4 if reachable,
    if not .Reach then
       VALUE = .VALUE + 1;              !   5 if unreachable
    PARAMETER_C_1(0,VALUE);
    end;                                ! of SHOW_NODE_STATE
routine ZERO_NODE_COUNTERS (XPTDB,CCB): XPT_LKG_DB_CCB novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine zeroes counters for the specified node
!
! FORMAL PARAMETERS:
!
!	CCB	CCB to pass to handler routine
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    map CCB: ref block field(C_NM_FIELDS);
    bind NMPAR = CCB[C_NM_NMPAR]: ref block field(NMX_NMPAR_FIELDS),
         NODE_ADDRESS = .NMPAR[NMX_NMPAR_NODE_ADDRESS];
    local NODEb;
    require 'XPTSYM';

    if (NODEb = NODE_DB (.CCB)) eqla 0
    then return;                        ! Invalid node address

    if NODE_ADDRESS eqlu .Tid
    then begin
         Aged_Loss = 0;
         Unreach_Loss = 0;
         Range_Loss = 0;
         Oversize_Loss = 0;
         Format_Errors = 0;
         Routing_Loss = 0;
         Verify_Rejects = 0;
         end;

    CCB [C_STS] = NM$SUC;
    end;                                ! of ZERO_NODE_COUNTERS

end
eludom			! End of module XPTNMI