Google
 

Trailing-Edge - PDP-10 Archives - BB-P363B-SM_1985 - mcb/nml/nmlrcz.bli
There are 2 other files named nmlrcz.bli in the archive. Click here to see a list.
! <BRANDT.DEVELOPMENT>NMLRCZ.BLI.1 23-Sep-82 10:54:34 Edit by BRANDT
!
!  Ident 35.
!    In READ_SPECIFIC_ENTITY and ZERO_SPECIFIC_ENTITY, copy the value
!    of ERROR_DETAIL (returned by NMLVDB) into the REQUEST block
!    so that it will be formatted into the response message.
!
! <BRANDT.DEVELOPMENT>NMLRCZ.BLI.1 22-Sep-82 15:21:29 Edit by BRANDT
!
!  Ident 34.
!    Add OWN variable ERROR_DETAIL, and include it as an argument
!    in all NML$VDB calls.  In CHANGE_SPECIFIC_ENTITY, copy the value
!    of ERROR_DETAIL (returned by NMLVDB) into the REQUEST block
!    so that it will be formatted into the response message.
!
! <BRANDT.DEVELOPMENT>NMLRCZ.BLI.2 17-Sep-82 10:12:37, Edit by BRANDT
!
!  Ident 33.
!    Rework edit 31 so that CLEAR entity ALL does not get rejected.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2 23-Jun-82 11:30:26, Edit by PECKHAM
!
! Ident 32.
! Check RB_PRV_* bits in request block before performing requests.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2  5-Jun-82 12:05:11, Edit by PECKHAM
!
! Ident 31.
! Fix CHANGE_SPECIFIC_ENTITY to reject the no-parameter case (SET entity ALL).
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2 27-May-82 13:05:53, Edit by PECKHAM
!
! Ident 30.
! Add routine MULTIPLE_PARAMETERS to detect a message with multiple parameters.
! Use this in NML$CHANGE to reject requests with multiple parameters.
!
! NET:<BRANDT.DEVELOPMENT>NMLRCZ.BLI.2 11-May-82 9:00:28, Edit by BRANDT
!
!  Ident 29.
!   1)  Move code that puts entity id into response message from routine
!       COPY_RESP_PARAMETERS to NML$NICE_RESPONSE.
!   2)  In PROCESS_ENTITY_CLASS remove call to COPY_RESP_PARAMETERS
!       since this was only called to insert the entity id.
!   3)  Add code to READ_SPECIFIC_ENTITY to handle the case where the
!       data returned requires multiple response messages.  The complete
!	fix for this problem is to put the code added to this routine
!	into a new function which can also be called anytime
!	COPY_RESP_PARAMETERS is called.  This will cover all cases.
!   4)  In READ_SPECIFIC_ENTITY change buffer size to 192 chars from
!	256 chars.  Thus only 192 chars of data will be requested for
!	a single NICE response message.  If 256 chars were obtained,
!	it would not fit in the space currently allocated for NICE
!	resp messages (256 chars) since the NICE message also includes
!	some header info.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLRCZ.BLI.23 25-Mar-82 17:52:28, Edit by VOBA
!
! Ident 28.
! Fix GET_NEXT_PARAMETER to parse cluster of parameters with different
! values. For example, CHANNELS parameter of MODULE entity with more than
! one range in a NICE message and formatted in a cluster, i.e. one follows
! another, would be parsed and passed to the parameter processing routine
! as one single unit.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.3 11-Mar-82 08:58:36, Edit by PECKHAM
!
! Ident 27.
! Fix BUFFER1_LENGTH handling in PROCESS_ENTITY_CLASS.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2  8-Mar-82 17:56:17, Edit by PECKHAM
!
! Ident 26.
! Change test on results of MEMORY_GET so that we don't get
! resource errors in ZERO_SPECIFIC_ENTITY.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2  8-Mar-82 11:05:04, Edit by PECKHAM
!
! Ident 25.
! Eliminate duplicate response at end of SHOW KNOWN in PROCESS_REQUEST.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.4  8-Mar-82 01:24:11, Edit by PECKHAM
!
! Ident 24.
! Fix up buffer length maintenance understanding with NML$VDB.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2  6-Mar-82 22:58:06, Edit by PECKHAM
!
! Ident 23.
! Remove direct references to lower level and go through NML$VDB.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.9  6-Mar-82 21:35:17, Edit by PECKHAM
!
! Ident 22.
! Fix SET KNOWN bug - save and restore RB_NICE_PARAMETERS pointer.
! Re-organization to fix response handling for multiple responses
! on SET, SHOW, and ZERO commands.
! Eliminate distinction between qualified and unqualified $NML$xxx calls
! (changes made in NMXINT).
!
! NET:<VOBA.NML.DEVELOPMENT>NMLRCZ.BLI.8  5-Mar-82 08:40:28, Edit by VOBA
!
! Ident 21.
! Added code to handle MODULE entities.
! Undo last change made in PROCESS_ENTITY_CLASS (for PECKHAM).
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.3  3-Mar-82 10:59:44, Edit by PECKHAM
!
! Ident 20.
! De-optimize code in PROCESS_ENTITY_CLASS in order to avoid confusing
! BLIS16 compiler into creating stack bug.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.3 26-Feb-82 15:16:59, Edit by PECKHAM
!
! Ident 19.
! Fix PROCESS_ENTITY_CLASS so that it generates an isolated '2' response
! before sending back the entity responses.
! General handling of NMU$MEMORY_GET failures.
!
! NET:<GROSSMAN.NML-SOURCES>NMLRCZ.BLI.3 24-Feb-82 09:13:39, Edit by GROSSMAN
!
! Fix PROCESS_ENTITY_CLASS so that it is sensitive to the resource error code
! returned by Tops-10's cruddy NMX. (Ie: it returns Parameter Value Too Long
! when attempting returning a list of active or known items.)
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2                   , Edit by PECKHAM
!
! Ident 18.
! Fix logging entity insertion in COPY_RESPONSE_PARAMETERS.
! Also fix logging list processing in PROCESS_ENTITY_CLASS.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.2  8-Feb-82 12:52:27, Edit by PECKHAM
!
! Ident 17.
! Fix EID_ADR buffer mismanagement bug in PROCESS_ENTITY_CLASS
! introduced by #16.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCZ.BLI.19 25-Jan-82 15:30:01, Edit by PECKHAM
!
! Ident 16.
! Change GETWs to GETBs in node name comparison in
! READ_SPECIFIC_ENTITY to get around BLISS compiler bug.
! In ZERO_SPECIFIC_ENTITY, always do a "show and zero" to the lower layer
! and use the result for a "counters zeroed" event.
!
! NET:<BRANDT.DEVELOP>NMLRCZ.BLI.1 21-Jan-82 12:15:27, Edit by BRANDT
!
! Ident 15.
! In routine PROCESS_ENTITY_CLASS, change a 7-bit pointer to an 8-bit
! pointer to resolve a problem with bad node addresses.
!
! NET:<GUNN>NMLRCZ.BLI.4 20-Jan-82 12:11:03, Edit by GUNN
!
! Ident 14.
! Update copyright date to 1982.
! Fix PROCESS_ENTITY_CLASS to be smart about handling the buffer
! size required for the list of known entities.
!
! NET:<BRANDT.DEVELOP>NMLRCZ.BLI.1 17-Dec-81 15:28:57, Edit by BRANDT
!
! Ident 13.
!   Fix routine CHANGE_SPECIFIC_ENTITY to correctly handle NICE messages
!   that have no parameters.  (e.g., CLEAR CIRCUIT foo ALL)
!   Update comments in GET_NEXT_PARAMETER and change interface to
!   expect only one argument.
!
! <GROSSMAN>NMLRCZ.BLI.2  1-Dec-81 19:07:14, Edit by GROSSMAN
! Ident 12.  (No change from previous)
! Fix a bug introduced accidentally by the previous edit. Makes this module
! compile.
!
! 1-Dec-81 16:59:19, Edit by GROSSMAN, Ident 12.
! Set buffer size to 256*3 in PROCESS_ENTITY_CLASS so that we can accomodate
! all the nodes on the engineering network at once.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.2 16-Sep-81 12:27:43, Edit by GUNN
! Ident 11.
! Set buffer count to zero if call to $NML$SHOW fails.
!
! NET:<DECNET20-V3P1.NMU.LIBRARY>NMLRCZ.BLI.4 30-Jun-81 11:25:37, Edit by GUNN
!
! Ident 10.
! Fix code in READ_SPECIFIC_ENTITY to set error return code only if both
! call to VDB and call to NMX fail.
!
! LTNML:<V3-LT.NCPNML.NMLMCB>NMLRCZ.BLI.4 17-Jun-81 09:01:54, Edit by SROBINSON
! X03.09
! Fix NODE_ processing in PROCESS_ENTITY_CLASS to get right ID length
!   and be defensive.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.3 12-Jun-81 14:16:51, Edit by GUNN
!
! Ident 08.
! Fix call to $NML$MAP_NODE_ID in PROCESS_ENTITY_CLASS to pass 
! address of length not literal.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.5  6-May-81 10:36:50, Edit by GUNN
!
! Pass along updated buffer pointer when calling $NML$SHOxx interface.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.4  6-May-81 10:15:43, Edit by GUNN
!
! Add code to read parameters from volatile data base and merge in
! buffer with parameters from lower layers.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.2 29-Mar-81 22:47:22, Edit by GUNN
!
! Change GET_NEXT_PARAMETER routine to calculate length of current
! parameter. It now uses NML$PARAMETER_DATA.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.2 13-Mar-81 17:13:44, Edit by GUNN
!
! Fix PROCESS_ENTITY_CLASS to release NODE id buffer only if one
! has been previously allocated.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.4 10-Mar-81 17:49:13, Edit by GUNN
!
! Fix loop in PROCESS_ENTITY_CLASS routine to cycle through all
! entities. Length of executor node id name was not getting bit 7
! masked.
!
! NET:<DECNET20-V3P1.NML>NMLRCZ.BLI.2 13-Feb-81 08:51:27, Edit by GUNN
!
! Add code to expand NODE entity ids returned in class list to full format.
!
! NET:<DECNET20-V3P1.BASELEVEL-2.SOURCES>NMLRCZ.BLI.14 11-Feb-81 16:18:34, Edit by GUNN
!
! Add code to set bit 7 of node entity name length byte if
! it is the executor.
!
! Change reference to entity id length in request block to be
! treated as signed 8 bit byte.
!
%title 'NMLRCZ -- NICE Read/Change/Zero Processing'
module NMLRCZ	(
		ident = 'X03.35'
		) =
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-10/20 V3.0 Network Management Layer (NML)
!
! ABSTRACT:
!
!	Performs read parameters and counters, change parameters, and zero
!	counters.
!
! ENVIRONMENT:	TOPS-10/20 & MCB/RSX11 User mode under NML
!
! AUTHOR: Dale C. Gunn , CREATION DATE: 12-Nov-80
!
! MODIFIED BY:
!
!	, : VERSION
! 01	-
!--
!
! INCLUDE FILES:
!

library 'NMLLIB';                       ! All required definitions
require 'NMLEXT';                       ! NML External routines

!
! TABLE OF CONTENTS
!

forward routine
    NML$READ,                           ! Perform read information
    READ_SPECIFIC_ENTITY : novalue,     ! Reads information for single ID
    NML$CHANGE,                         ! Perform change parameters
    CHANGE_SPECIFIC_ENTITY : novalue,
    MULTIPLE_PARAMETERS,
    GET_NEXT_PARAMETER,
    NML$ZERO,                           ! Perform zero counters
    ZERO_SPECIFIC_ENTITY : novalue,
    PROCESS_REQUEST,
    PROCESS_ENTITY_CLASS,               ! Process 'KNOWN' or 'ACTIVE' entities
    COPY_RESP_PARAMETERS;

!
! MACROS:
!


!
! EQUATED SYMBOLS:
!

!
! OWN STORAGE:
!

own
    ERROR_DETAIL: initial (-1);	 ! For error detail returned from NMLVDB

!
! EXTERNAL REFERENCES:
!

external routine
         NMU$NETWORK_LOCAL,
         NML$VDB_PARAMETER,
         NML$DECLARE_EVENT,
         NML$PARAMETER_DATA,
         NML$VDB,
         NML$PDB_READ,
         NML$PDB_CHANGE,
         NML$NICE_RESPONSE;
%global_routine ('NML$READ', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs the NICE read information request for the local
!       Network Management Layer.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request has completed successfully.
!       NEGATIVE NICE error return code if request failed.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    if not .REQ[RB_PRV_READ] then return NICE$_PRV;

    PROCESS_REQUEST (.REQ, READ_SPECIFIC_ENTITY)
    end;				! End of NML$READ
%routine ('READ_SPECIFIC_ENTITY', REQ) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs a NICE read information request for a single
!       named entity.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           OB_LENGTH = 192,             ! Length of output buffer
           OB_SIZE = ch$allocation (OB_LENGTH,8),
           OB_ALLOCATION = OB_SIZE * %upval;

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         BUFFER_ADDR,                   ! Address of output buffer
         BUFFER_ALLOC,			! Allocation adjustment
         BUFFER_LEFT,                   ! Output buffer length available
         BUFFER_LEN,                    ! Output buffer length
         BUFFER_USED,                   ! Last item # in current buffer
         BUFFER_OFFSET,                 ! Offset from start of buffer
         BUFFER_PTR,                    ! Pointer to output buffer
         RTN_COD,                       ! NICE return code
	 BUFFER_PART: vector[10],
	 N,				! Loop counter
	 NN,				! Loop counter
         TEMP;

    ERROR_DETAIL = -1;      	        ! Initialize for response msg
    BUFFER_ALLOC = 0;			! Initial allocation adjustment
    N = 0;				! Initialize loop counter

    do begin
        BUFFER_ALLOC = .BUFFER_ALLOC + OB_ALLOCATION;
        BUFFER_LEN = (.BUFFER_ALLOC/OB_ALLOCATION)*OB_LENGTH;
        BUFFER_LEFT = .BUFFER_LEN;
        if (BUFFER_ADDR = NMU$MEMORY_GET (.BUFFER_ALLOC)) eqla 0
        then begin
             REQ[RB_RETURN_CODE] = NICE$_REE;
             REQ[RB_NICE_PARAMETERS] = 0;   ! No parameter data returned
             NML$NICE_RESPONSE (.REQ);      ! Build response message
             return;
             end;

        BUFFER_PTR = ch$ptr (.BUFFER_ADDR,,8);

        if .REQ[$sub_field (RB_NICE_OPTION, RO_PERMANENT)]
        then begin
             RTN_COD = $NML$GETPDB (.REQ[RB_NICE_ENTITY_TYPE],
                                    .REQ[RB_NICE_ENTITY],
                                    .REQ[RB_NICE_QUALIFIER],
                                    .REQ[$sub_field (RB_NICE_OPTION, RO_INFO_TYPE)],
                                    BUFFER_LEFT,
                                    ch$ptr (.BUFFER_ADDR,,8));
             end
        else begin
             RTN_COD = NML$VDB (%bliss36($NTSHO) %bliss16(N$FSHO),
                                .REQ[RB_NICE_ENTITY_TYPE],
                                .REQ[RB_NICE_ENTITY],
                                .REQ[RB_NICE_QUALIFIER],
                                .REQ[$sub_field (RB_NICE_OPTION, RO_INFO_TYPE)],
                                BUFFER_LEFT,
                                BUFFER_PTR,
				ERROR_DETAIL);
             end;
        end
    while (if .RTN_COD eql NICE$_REE    ! Resource error?
           then begin                   ! Release insufficient buffer 
                NMU$MEMORY_RELEASE (.BUFFER_ADDR, .BUFFER_ALLOC);
		BUFFER_PART[.N] = .BUFFER_LEN - .BUFFER_LEFT;
		N = .N + 1;
		if .N lss 10
                then $TRUE
                else $FALSE
                end
           else begin
		BUFFER_PART[.N] = .BUFFER_LEN - .BUFFER_LEFT;
		N = .N + 1;
		$FALSE
		end);

    if .RTN_COD lss 1
    then begin
         REQ[RB_RETURN_CODE] = .RTN_COD; 	! Set NICE return code
         REQ[RB_ERROR_DETAIL] = .ERROR_DETAIL;	! And error detail
	 end;

    if .N gtr 1				! If multiple buffers required
    then
	begin
	local
	    MD_SEQ;			! More/Done sequence flag

	if .REQ[RB_STATE] neq RB$MORE	! If not already in a
	then				!  More/Done sequence 
	    begin
	    REQ[RB_RETURN_CODE] = 2;	! Start More/Done sequence now
	    NML$NICE_RESPONSE (.REQ);   ! Build response message
	    NML$REQUEST_FINISH (.REQ);  ! Send it off
	    MD_SEQ = $TRUE;		! Indicate sequence started here
	    end
	else
	    MD_SEQ = $FALSE;		! Sequence not started here

	NN = 0;				! Start counter
	BUFFER_OFFSET = 0;		! Start at beginning of buffer
	do
	    begin
	    if .NN neq (.N - 1)
	    then
		REQ[RB_RETURN_CODE] = 3  ! Indicate partial reply
	    else
		REQ[RB_RETURN_CODE] = 1; ! Indicate complete reply
	    NML$NICE_RESPONSE (.REQ);   ! Build response message
	    BUFFER_USED = .BUFFER_PART[.NN];
	    COPY_RESP_PARAMETERS (.REQ,
	                          (.BUFFER_USED - .BUFFER_OFFSET),
	                          ch$ptr (.BUFFER_ADDR,.BUFFER_OFFSET,8));
	    if .REQ[RB_RETURN_CODE] eql 3 or .MD_SEQ
	    then
		NML$REQUEST_FINISH (.REQ);  ! Send it off

	    BUFFER_OFFSET = .BUFFER_OFFSET + .BUFFER_USED;
	    NN = .NN + 1;
	    end
	until (.NN geq .N);

	if .MD_SEQ			! If we started sequence
	then				!  then terminate it here
	    begin
	    REQ[RB_RETURN_CODE] = -128;	! End More/Done sequence
	    NML$NICE_RESPONSE (.REQ);   ! Build response message
	    end;
	end
    else
	begin
	NML$NICE_RESPONSE (.REQ);       ! Build single response message
	COPY_RESP_PARAMETERS (.REQ,
	                      (.BUFFER_LEN - .BUFFER_LEFT),
	                      ch$ptr (.BUFFER_ADDR,,8));
	end;

    NMU$MEMORY_RELEASE (.BUFFER_ADDR, .BUFFER_ALLOC); ! Release buffer

    end;				! End of READ_SPECIFIC_ENTITY
%global_routine ('NML$CHANGE', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs the NICE change parameters request for the local
!       Network Management Layer.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request has completed successfully.
!       NEGATIVE NICE error return code if request failed.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    if not .REQ[RB_PRV_CHANGE] then return NICE$_PRV;

    if not .REQ[RB_PRV_LOCAL] and
       MULTIPLE_PARAMETERS (.REQ)
    then return NICE$_IPG;

    PROCESS_REQUEST (.REQ, CHANGE_SPECIFIC_ENTITY)
    end;				! End of NML$CHANGE
%routine ('CHANGE_SPECIFIC_ENTITY', REQ) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs a NICE change parameter request for a single
!       named entity.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request has completed successfully.
!       NEGATIVE NICE error return code if request failed.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         LENGTH,                        ! Length of parameter
         RTN_COD;                       ! NICE return code

    if (GET_NEXT_PARAMETER (.REQ) or    ! Get first parameter (if any)
        (.REQ[$sub_field (RB_NICE_OPTION, CO_CLEAR_PURGE)])) ! ALL is OK
    then begin
         REQ[RB_RETURN_CODE] = 1;       ! Assume success
         ERROR_DETAIL = -1;      	! Initialize for response msg

         do begin
            LENGTH = .REQ[RB_NICE_PARAMETER_LENGTH]; ! Set length of parameter

            if .REQ[$sub_field (RB_NICE_OPTION, CO_PERMANENT)]
            then begin                  ! Permanent parameters
                 if .REQ[$sub_field (RB_NICE_OPTION, CO_CLEAR_PURGE)]
                 then begin             ! Purge
                      RTN_COD = $NML$DELPDB (.REQ[RB_NICE_ENTITY_TYPE],
                                             .REQ[RB_NICE_ENTITY],
                                             .REQ[RB_NICE_QUALIFIER],
                                             LENGTH,
                                             .REQ[RB_NICE_PARAMETERS]);
                      end
                 else begin             ! Define
                      RTN_COD = $NML$PUTPDB (.REQ[RB_NICE_ENTITY_TYPE],
                                             .REQ[RB_NICE_ENTITY],
                                             .REQ[RB_NICE_QUALIFIER],
                                             LENGTH,
                                             .REQ[RB_NICE_PARAMETERS]);
                      end;
                 end
            else begin                  ! Volatile parameters
                 if .REQ[$sub_field (RB_NICE_OPTION, CO_CLEAR_PURGE)]
                 then begin             ! Clear
                      RTN_COD = NML$VDB (%bliss36($NTCLR) %bliss16(N$FCLR),
                                         .REQ[RB_NICE_ENTITY_TYPE],
                                         .REQ[RB_NICE_ENTITY],
                                         .REQ[RB_NICE_QUALIFIER],
                                         0 %(selector)%,
                                         LENGTH,
                                         .REQ[RB_NICE_PARAMETERS],
					 ERROR_DETAIL);
                      end
                 else begin             ! Set
                      RTN_COD = NML$VDB (%bliss36($NTSET) %bliss16(N$FSET),
                                         .REQ[RB_NICE_ENTITY_TYPE],
                                         .REQ[RB_NICE_ENTITY],
                                         .REQ[RB_NICE_QUALIFIER],
                                         0 %(selector)%,
                                         LENGTH,
                                         .REQ[RB_NICE_PARAMETERS],
					 ERROR_DETAIL);
                      end;
                 end;

        REQ[RB_RETURN_CODE] = .RTN_COD;		! Set NICE return code 
        REQ[RB_ERROR_DETAIL] = .ERROR_DETAIL;	! And error detail

%( N.B. - Does this code handle the case of failures during a multiple
          parameter message correctly? )%

            end
         while GET_NEXT_PARAMETER (.REQ); ! Do all parameters
         end
    else begin
         REQ[RB_RETURN_CODE] = $NICE$ERR_OPF;
         end;

    NML$NICE_RESPONSE (.REQ);           ! Build response message
    end;				! End of CHANGE_SPECIFIC_ENTITY
%routine ('MULTIPLE_PARAMETERS', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Detect multiple parameters in a request.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	REQ[RB_NICE_PARAMETERS]
!               Contains a pointer to the previous parameter.
!       REQ[RB_NICE_PARAMETER_LENGTH]
!               Contains the length of the previous parameter in bytes.
!
! ROUTINE VALUE:
!
!	$TRUE, if greater than one parameter
!       $FALSE, otherwise.
!
! SIDE EFFECTS:
!
!	None
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
        RTN,
        SAVE_NICE_PARAMETERS;

    SAVE_NICE_PARAMETERS = .REQ[RB_NICE_PARAMETERS];
    RTN = GET_NEXT_PARAMETER (.REQ) and GET_NEXT_PARAMETER (.REQ);
    REQ[RB_NICE_PARAMETERS] = .SAVE_NICE_PARAMETERS;
    REQ[RB_NICE_PARAMETER_LENGTH] = 0;
    .RTN
    end;				! End of MULTIPLE_PARAMETERS
%routine ('GET_NEXT_PARAMETER', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Obtains the next parameter in the NICE request message.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	REQ[RB_NICE_PARAMETERS]
!               Contains a pointer to the previous parameter.
!       REQ[RB_NICE_PARAMETER_LENGTH]
!               Contains the length of the previous parameter in bytes.
!
! ROUTINE VALUE:
!
!	$TRUE, if the next parameter exists.
!       $FALSE, otherwise.
!
! SIDE EFFECTS:
!
!	Updates REQ[RB_NICE_PARAMETER_LENGTH] to be the length of
!	the current parameter.
!	Updates REQ[RB_NICE_PARAMETERS] to point to the current
!       parameter.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    REQ[RB_NICE_PARAMETERS] = ch$plus (.REQ[RB_NICE_PARAMETERS],
                                       .REQ[RB_NICE_PARAMETER_LENGTH]);

    !
    ! Return false when all parameters have been processed.
    !

    if ch$diff (.REQ[RB_NICE_PARAMETERS], .REQ[RB_NICE_POINTER]) geq .REQ[RB_NICE_LENGTH]
    then begin
         REQ[RB_NICE_PARAMETER_LENGTH] = 0;
         return $FALSE;
         end;

    !
    ! Get length of the parameter, to include the data portion plus
    ! two bytes for the DATA ID field.
    !

        begin
        local PARAMETER, NEXT, POINTER, DATA, LENGTH;

        POINTER = .REQ[RB_NICE_PARAMETERS]; ! Make copy of pointer
        LENGTH = 0;                     ! Initialize length

        do begin                        ! Scan parameters and their data
           local LEN;

           PARAMETER = GETW (POINTER);  ! Get parameter number

           if .REQ[$sub_field(RB_NICE_OPTION,CO_CLEAR_PURGE)]
           and (.REQ[RB_NICE_PARAMETERS] neq .REQ[RB_NICE_QUALIFIER])
           then LEN = 0                 ! No parameter data for CLEAR/PURGE
           else begin                   ! Otherwise, get data follow
                LEN = NML$PARAMETER_DATA (.REQ[RB_NICE_ENTITY_TYPE],
                                          .PARAMETER,
                                          POINTER,
                                          DATA);

                if .LEN leq 0           ! Illegal parameter data length
                then return $FALSE;
                end;

           NEXT = (if ((LENGTH = .LENGTH + 2 + .LEN) lss .REQ[RB_NICE_LENGTH])
                   and (.REQ[RB_NICE_ENTITY_TYPE] eql MODULE_) ! MODULE entity
                   and (.PARAMETER eql 1130) ! CHANNELS parameter
                   then GETW_NA (.POINTER) ! Peek at next parameter number
                   else -1);            ! End of NICE request message
           end                          ! Continue parsing if next parameter
        while (.NEXT eql .PARAMETER);   ! is identical to the current one

        REQ[RB_NICE_PARAMETER_LENGTH] = .LENGTH; ! Final length of the data
        end;

    !
    ! If this parameter is a qualifier, then call ourself recursively
    ! to skip over the qualifier to the next real parameter.
    !

    if .REQ[RB_NICE_PARAMETERS] eql .REQ[RB_NICE_QUALIFIER]
    then return GET_NEXT_PARAMETER (.REQ);

    return $TRUE;
    end;				! End of GET_NEXT_PARAMETER
%global_routine ('NML$ZERO', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs the NICE zero counters request for the local
!       Network Management Layer.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request has completed successfully.
!       NEGATIVE NICE error return code if request failed.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    if not .REQ[RB_PRV_CHANGE] then return NICE$_PRV;

    PROCESS_REQUEST (.REQ, ZERO_SPECIFIC_ENTITY)
    end;				! End of NML$ZERO
%routine ('ZERO_SPECIFIC_ENTITY', REQ) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request has completed successfully.
!       NEGATIVE NICE error return code if request failed.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           OB_LENGTH = 256,             ! Length of output buffer
           OB_SIZE = ch$allocation (OB_LENGTH,8),
           OB_ALLOCATION = OB_SIZE * %upval;

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         BUFFER_ADDR,                   ! Address of output buffer
         BUFFER_LEFT,                   ! Output buffer length
         RTN_COD;                       ! NICE return code

    REQ[RB_RETURN_CODE] = 1;            ! Assume success
    ERROR_DETAIL = -1;      	        ! Initialize for response msg
    BUFFER_LEFT = OB_LENGTH;            ! Get buffer for info

    if (BUFFER_ADDR = NMU$MEMORY_GET (OB_ALLOCATION)) neqa 0
    then begin

         %( N.B. - Insert expression here to read and zero NML counters for
            this entity into the buffer, and bump the buffer address and 
            length appropriately before calling the lower layers. )%

         begin
         local BUFFER_PTR;
         BUFFER_PTR = ch$ptr (.BUFFER_ADDR,,8);
         RTN_COD = NML$VDB (%bliss36($NTSZC) %bliss16(N$FSZC),
                            .REQ[RB_NICE_ENTITY_TYPE],
                            .REQ[RB_NICE_ENTITY],
                            .REQ[RB_NICE_QUALIFIER],
                            0 %(no selector)%,
                            BUFFER_LEFT,
                            BUFFER_PTR,
			    ERROR_DETAIL);
         end;

         !
         ! If ZERO only and the read got a resource error,
         ! the function succeeded anyway.
         !

         if (.REQ[$sub_field (RB_NICE_OPTION, ZO_READ_AND_ZERO)] eql 0) and
            (.RTN_COD eql NICE$_REE)
         then RTN_COD = 1;

         REQ[RB_RETURN_CODE] = .RTN_COD; 	! Set NICE return code
         REQ[RB_ERROR_DETAIL] = .ERROR_DETAIL;	! And error detail
         %(set time zeroed)%

         begin
         local REB : RAW_EVENT_BLOCK;

         REB [REB_EVENT_CODE] = 0^6 + 9; ! Counters Zeroed
         REB [REB_ENTITY_TYPE] = .REQ [RB_NICE_ENTITY_TYPE];
         REB [REB_ENTITY_POINTER] = .REQ [RB_NICE_ENTITY];
         REB [REB_DATA_POINTER] = ch$ptr (.BUFFER_ADDR,, 8);
         REB [REB_DATA_LENGTH] = (OB_LENGTH - .BUFFER_LEFT);
         REB [REB_TIME_BLOCK] = 0;
         NML$DECLARE_EVENT (REB);
         end;
         end
    else
         REQ [RB_RETURN_CODE] = NICE$_REE;

     NML$NICE_RESPONSE (.REQ);          ! Build response message

    if .REQ [RB_RETURN_CODE] gtr 0
    then

        if .REQ[$sub_field (RB_NICE_OPTION, ZO_READ_AND_ZERO)]
        then COPY_RESP_PARAMETERS (.REQ,
                                   (OB_LENGTH - .BUFFER_LEFT),
                                   ch$ptr (.BUFFER_ADDR,,8));

    if .BUFFER_ADDR neqa 0              ! Release buffer if there is one
    then NMU$MEMORY_RELEASE (.BUFFER_ADDR, OB_ALLOCATION);
    end;				! End of ZERO_SPECIFIC_ENTITY
%routine ('PROCESS_REQUEST', REQ, ACTION_ROUTINE) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Choose to handle single or multiple requests
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request has completed successfully.
!       NEGATIVE NICE error return code if request failed.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         EID_LEN: $SIGNED_BYTE_VALUE,   ! Signed length of entity id
         RTN_COD;                       ! NICE return code

    EID_LEN = .REQ[RB_NICE_ENTITY_ID_LENGTH];  ! Pick up the id length

!
! Determine whether a specific entity or class of entities was specified
!

    if .EID_LEN[VALUE] geq 0
    then begin                          ! Specific entity request
         REQ[RB_RETURN_CODE] = 1;       ! Success for single response
         (.ACTION_ROUTINE) (.REQ);
         NML$REQUEST_FINISH (.REQ);     ! Queue request for completion
         return $TRUE;
         end;

    !
    ! Acknowledge the command first
    !

    REQ[RB_RETURN_CODE] = 2;            ! Set return code for multiple response
    NML$NICE_RESPONSE (.REQ);           ! Build response message
    NML$REQUEST_FINISH (.REQ);          ! Queue request for completion

    !
    ! Now do the indiviual responses
    !

    RTN_COD = PROCESS_ENTITY_CLASS (.REQ, ! Perform read for each entity
                                    (.ACTION_ROUTINE),
                                    .REQ[$sub_field (RB_NICE_OPTION, RO_PERMANENT)]);

    !
    ! Finish it up
    !

    REQ[RB_RETURN_CODE] = -128;         ! Indicate no more responses coming
    NML$NICE_RESPONSE (.REQ);           ! Build final response message
    NML$REQUEST_FINISH (.REQ);          ! Queue request for completion
    return $TRUE;
    end;				! End of PROCESS_REQUEST
%routine ('PROCESS_ENTITY_CLASS', REQ, ACTION_ROUTINE, PERMANENT) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs processing for a class of entities, i.e., KNOWN or
!       ACTIVE nodes.
!
! FORMAL PARAMETERS
!
!	REQ - The address of the NML Request Block for this request.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request has completed successfully.
!       NEGATIVE NICE error return code if request failed.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           OB_LENGTH = 32 * 3,          ! Initial length of class entity buffer
           OB_SIZE = ch$allocation (OB_LENGTH,8),
           OB_ALLOCATION = OB_SIZE * %upval;

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         BUFFER1_ADDR,                  ! Return list buffer address
         BUFFER1_LENGTH,
         BUFFER1_ALLOC,
         ENT_PTR,                       ! Pointer to specific ID in list
         EID_LEN: $SIGNED_BYTE_VALUE,   ! Signed length of entity id
         RTN_COD,                       ! NICE return code
         TEMP;

    bind routine
         NML_FUNCTION = .ACTION_ROUTINE;

    ! Process a 'KNOWN' or 'ACTIVE' entity class

    !
    ! Try to get a big enough buffer.
    !

    BUFFER1_ALLOC  = 0;

    do begin
       RTN_COD = NICE$_REE;             ! Set resource error initially
       BUFFER1_ALLOC  = .BUFFER1_ALLOC + OB_ALLOCATION; ! Bump buffer allocation
       BUFFER1_LENGTH  = (.BUFFER1_ALLOC/OB_ALLOCATION)*OB_LENGTH;
       if (BUFFER1_ADDR = NMU$MEMORY_GET (.BUFFER1_ALLOC)) eqla 0
       then exitloop;                   ! Can't get large enough buffer

       !
       ! Get list of IDs for either qualified or unqualified entities
       !

       ENT_PTR = ch$ptr (.BUFFER1_ADDR,,8);
       EID_LEN = .REQ[RB_NICE_ENTITY_ID_LENGTH]; ! Pick up the id length

       if .PERMANENT
       then RTN_COD = $NML$RETURNPDB (.REQ[RB_NICE_ENTITY_TYPE],
                                      .EID_LEN[VALUE],
                                      .REQ[RB_NICE_QUALIFIER],
                                      BUFFER1_LENGTH,
                                      .ENT_PTR)
       else begin
            local BUF_LNG;

            BUF_LNG = .BUFFER1_LENGTH;
            RTN_COD = NML$VDB (%bliss36($NTRET) %bliss16(N$FRET),
                               .REQ[RB_NICE_ENTITY_TYPE],
                               0 %(no entity)%,
                               .REQ[RB_NICE_QUALIFIER],
                               .EID_LEN[VALUE],
                               BUF_LNG,
                               ENT_PTR,
			       ERROR_DETAIL);
            if .RTN_COD eql 1
            then BUFFER1_LENGTH = .BUFFER1_LENGTH - .BUF_LNG;
            ENT_PTR = ch$ptr (.BUFFER1_ADDR,,8);
            end;
       end
    while (if .RTN_COD eql NICE$_REE    ! Resource error?

           %if $TOPS10 %then            ! For TOPS-10
           or .RTN_COD eql NICE$_PVL    ! Or parameter value too long?
           %fi

           then begin                   ! Release insufficient buffer 
                NMU$MEMORY_RELEASE (.BUFFER1_ADDR, .BUFFER1_ALLOC);
                $TRUE
                end
           else $FALSE);

    !
    ! Exit here if the list could not be obtained
    !

    if (.RTN_COD neq 1)
    or (.BUFFER1_LENGTH leq 0)
    then begin
         if .RTN_COD lss 0
         then begin
              REQ[RB_RETURN_CODE] = .RTN_COD; ! Set failure return code
              NML$NICE_RESPONSE (.REQ); ! Build response message
              end;

         if .BUFFER1_ADDR neqa 0 ! Release buffer
         then NMU$MEMORY_RELEASE (.BUFFER1_ADDR, .BUFFER1_ALLOC);

         return .RTN_COD;
         end;

    !
    ! Perform the appropriate action for each ID in list
    !

    REQ[RB_RETURN_CODE] = 1;            ! Code for subsequent responses

    while .BUFFER1_LENGTH gtr 0
    do begin                            ! For each specific entity
       local EID_ADR;                   ! Address of NODE entity id buffer
       label MAP_NODE;

       REQ[RB_NICE_ENTITY] = .ENT_PTR;  ! Point to this entity ID
       EID_ADR = 0;                     ! Set to zero to indicate no allocation
                                        ! only if necessary...

       selectone .REQ[RB_NICE_ENTITY_TYPE] of
           set
           [NODE_E]:
               MAP_NODE: begin          ! Map node id to full entity format
               local LENGTH;            ! Length temporary for MAPping

               if (TEMP = (ch$rchar (ch$plus (.ENT_PTR,2)) and %O'177')) neq 6
               then begin
                    EID_ADR = NMU$MEMORY_GET (NODE_ID_BUFFER_ALLOCATION);

                    if .EID_ADR eqla 0  ! If cannot allocate memory, exit loop
                    then leave MAP_NODE;

                    REQ[RB_NICE_ENTITY] = ch$ptr (.EID_ADR,,8);
                    ch$move (minu(.TEMP,6)+3, .ENT_PTR, .REQ[RB_NICE_ENTITY]);
                    end;

               LENGTH = NODE_ID_BUFFER_LENGTH; ! Get length and map in all
               $NML$MAP_NODE_ID (LENGTH, .REQ[RB_NICE_ENTITY]); ! cases
               end;

           [otherwise]:
               0;
           tes;

       begin
       local SAVE_NICE_PARAMETERS;

       SAVE_NICE_PARAMETERS = .REQ [RB_NICE_PARAMETERS];

       NML_FUNCTION (.REQ);             ! Perform the function
       NML$REQUEST_FINISH (.REQ);       ! Queue request for completion

       REQ[RB_NICE_PARAMETERS] = .SAVE_NICE_PARAMETERS;
       REQ[RB_NICE_PARAMETER_LENGTH] = 0;
       end;

    if .EID_ADR neqa 0                  ! Release only if allocated
    then NMU$MEMORY_RELEASE (.EID_ADR, NODE_ID_BUFFER_ALLOCATION);

    if .REQ[RB_RETURN_CODE] geq 1       ! Successful?
    then REQ[RB_RETURN_CODE] = 1        ! Yes, set code for success
    else exitloop;                      ! No, quit now with reason

    selectone .REQ[RB_NICE_ENTITY_TYPE] of
        set
        [NODE_E]:
            begin                       ! Node has special entity format
            GETW (ENT_PTR);             ! Bump past node address
            BUFFER1_LENGTH = .BUFFER1_LENGTH - 2;
            TEMP = GETB (ENT_PTR) and %O'177'; ! Bump buffer count
            BUFFER1_LENGTH = .BUFFER1_LENGTH - 1 - .TEMP;
            ENT_PTR = ch$plus (.ENT_PTR,.TEMP); ! Point to next entity
            end;

        [LOGGING_]:
            begin                       ! Logging has special entity format
            GETB (ENT_PTR);             ! Bump past sink
            BUFFER1_LENGTH = .BUFFER1_LENGTH - 1;
            end;

        [otherwise]:
            begin
            TEMP = GETB (ENT_PTR);      ! Bump buffer count
            BUFFER1_LENGTH = .BUFFER1_LENGTH - 1 - .TEMP;
            ENT_PTR = ch$plus (.ENT_PTR,.TEMP); ! Point to next entity
            end;
        tes;
    end;

    if .BUFFER1_ADDR neqa 0             ! Release buffer if there is one
    then NMU$MEMORY_RELEASE (.BUFFER1_ADDR, .BUFFER1_ALLOC);

    return .REQ[RB_RETURN_CODE];        ! Return final NICE return code
    end;				! End of PROCESS_ENTITY_CLASS
%routine ('COPY_RESP_PARAMETERS', REQ, PAR_LEN, PAR_PTR) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Copies parameter data into response message.
!
! FORMAL PARAMETERS
!
!	NONE.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
	 LEN,
	 REM,
         TEMP,
         RESP_MAX,
         RESP_PTR;

    !
    ! Point to end of entity id field in response message
    !

    RESP_PTR = ch$ptr (.REQ[RB_RESPONSE],.REQ[RB_RESPONSE_LENGTH],8);

    !
    ! Determine the number of 8 bit bytes that can be copied into this
    ! response message and set REM to the number of bytes that
    ! could not be included.
    !

    RESP_MAX = (.REQ[RB_RESPONSE_ALLOCATION] / %upval) * (%bpval / 8);

    if (.PAR_LEN + .REQ[RB_RESPONSE_LENGTH]) gtr .RESP_MAX
    then
	begin
	LEN = .RESP_MAX - .REQ[RB_RESPONSE_LENGTH];
	REM = .PAR_LEN - .LEN;
	end
    else
	begin
	LEN = .PAR_LEN;
	REM = 0;
	end;

    !
    ! Copy parameters to DATA BLOCK field of repsonse message
    !

    RESP_PTR = ch$move (.LEN, .PAR_PTR, .RESP_PTR);
    REQ[RB_RESPONSE_LENGTH] = .REQ[RB_RESPONSE_LENGTH] + .LEN;

    .REM
    end;				! End of COPY_RESP_PARAMETERS
end                                   ! End of Module NMLRCZ
eludom
! Local Modes:
! Mode:BLISS
! Auto Save Mode:2
! Comment Column:40
! Comment Rounding:+1
! End: