Google
 

Trailing-Edge - PDP-10 Archives - BB-X117B-SB_1986 - 10,7/nml/nmlnic.bli
There are 2 other files named nmlnic.bli in the archive. Click here to see a list.
! UPD ID= 207, SNARK:<6.1.NML>NMLNIC.BLI.7,  10-Dec-84 15:28:51 by HALPIN
! Get MONSYM Library file out of default directory, not BLI:
!
! UPD ID= 126, SNARK:<6.1.NML>NMLNIC.BLI.6,  16-Oct-84 17:10:11 by HALPIN
! Fix bug in VY_TEST_REQUEST. The Check for the ENTITY_TYPE being
! NODE was missing a "." operator.
!
! UPD ID= 90, SLICE:<6.1.NML>NMLNIC.BLI.5,  18-Sep-84 15:09:26 by GUNN
!
! Ident 43.
! Change call to LOCAL_NODE_NUMBER to NMU$NETWORK_LOCAL.
!
! WORK:<GUNN.NML>NMLNIC.BLI.2 21-Aug-84 12:10:56, Edit by GUNN
!
! Change to accomodate new LIBRARY conventions. MONSYM.L36 and JLNKG.L36
! are now explicity declared here rather than in NMULIB.
!
! UPD ID= 72, SNARK:<6.1.NML>NMLNIC.BLI.4,   5-Sep-84 16:06:21 by HALPIN
! Fix bugs in previous edit, UPD ID= 66
!
! UPD ID= 66, SNARK:<6.1.NML>NMLNIC.BLI.2,  31-Aug-84 11:14:11 by HALPIN
! Check for zero AREA number in all Node ID's and insert Home
! AREA Number. NML$NICE_EXECUTE
!
! Changed value of RESPONSE_LENGTH in NML$NICE_RESPONSE from 256
! to 1024 (per GLINDELL)
!
! DSKT:NMLNIC.BLI[10,6026,NML703] 21-Aug-84 16:56:31, Edit by DAVENPORT
! Add back code in NML$NICE_EXECUTE to properly set up the NICE entity
! id length.  Code was lost in merge.
!
! PH4:<HALPIN>NMLNIC.BLI.2  9-Jan-84 17:05:49, Edit by HALPIN
!
! Ident 39.
! VY_TEST_REQUEST needed a 'not' prefix operator on its call to
! the NEXTB_NICE macro.  This was causing LOOP commands to fail
! with 'Invalid message formats'.
!
! PH4:<GLINDELL>NMLNIC.BLI.4 15-Nov-83 14:48:14, Edit by GLINDELL
!
! Ident 38
!  Problem: VERIFY_PARAMETERS skipped the parameter data if command was
!           CLEAR. However, for CLEAR EVENT the event parameter data is
!           needed.
!  Cure:    Special case LOGGING entity and EVENT parameter
!
!<MCINTEE.WORK>NMLNIC.BLI.3, 12-Jul-83 15:12:33, Edit by MCINTEE
!
! Ident 37.
!  Put full entity type into request block
!
! PH4:<PECKHAM>NMLNIC.BLI.2,  14-Jun-83 16:35:36, Edit by PECKHAM
!
! Ident 36.
!  Replace SCAN_PARAMETER by calls to NMLPRM routines.
!
!  Do ENTITY naming cleanup; support AREA entity.  Rework GET_ENTITY_ID.
!
!<MCINTEE.WORK>NMLNIC.BLI.3,  8-Jun-83 13:45:35, Edit by MCINTEE
!
! Ident 35.
!  Use the literal NO_ENTITY_ instead of a number
!
! PH4:<MCINTEE>NMLNIC.BLI.4,  1-Jun-83 10:37:57, Edit by MCINTEE
!
! Ident 34.
!  More of previous
!
! PH4:<MCINTEE>NMLNIC.BLI.2,  1-Jun-83 09:48:13, Edit by MCINTEE
!
! Ident 33.
!  Fix SCAN_PARAMETER to recognize negative QUALIFIERs
!   The assumption is that no QUALIFIER AI field will be larger than 127
!
! PH4:<PECKHAM>NMLNIC.BLI.10 17-May-83 13:04:57, Edit by PECKHAM
!
!  Ident 32.
!   Change references to DU1, DU2, etc. to extract from data type byte.
!   Also change NML$GET_PDB_DATA_TYPE reference to NML$DATA_TYPE, which
!   supplies a modified DATA TYPE byte when the parameter is CM-n. This
!   modified byte contains the data format index in bits 0-5 instead of
!   the number of parameters, so CM-n formats can be easily identified.
!
! <BRANDT.DEVELOPMENT>NMLNIC.BLI.1 22-Sep-82 10:45:21, Edit by BRANDT
!
!  Ident 31.
!   Change code in NML$NICE_RESPONSE so that the RB_ERROR_DETAIL field
!   of the REQUEST block is reset after the current value is obtained.
!   Otherwise, if the request block is reused for multiple response
!   messages, we would have an invalid entry in that field.
!
! NET:<BRANDT.DEVELOPMENT>NMLNIC.BLI.2 9-Jun-82 12:10:12, Edit by BRANDT
!
!  Ident 30.
!   Change code in NML$NICE_EXECUTE that returns the memory allocated
!   for node entity id so that the memory is returned by the completion
!   routine, since this field will still be referenced.
!
! NET:<BRANDT.DEVELOPMENT>NMLNIC.BLI.2 10-May-82 9:10:12, Edit by BRANDT
!
!  Ident 29.
!   Move code to NML$NICE_RESPONSE that inserts an entity id field into
!   the response message.  This code used to be in routine
!   COPY_RESP_PARAMETERS in module NMLRCZ.
!
! NET:<BRANDT.DEVELOPMENT>NMLNIC.BLI.2 5-May-82 14:17:12, Edit by BRANDT
!
! Ident 28.
! Initialize the error detail value in the Request Block to -1.
! Unless the response message is type 2 or -128, always put the error
! detail into the response message.  Error detail values of 0 could be
! significant.
!
! NET:<PECKHAM.DEVELOPMENT>NMLNIC.BLI.2 28-Apr-82 09:07:12, Edit by PECKHAM
!
! Ident 27.
! Do not abort function if node entity does not map in NML$NICE_EXECUTE.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.11 21-Apr-82 13:17:05, Edit by VOBA
!
! Ident 26.
! Fix code to check for CLEAR_PURGE bit inside the SCAN_PARAMETER routine,
! instead of prior to invoking it.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.5 26-Mar-82 18:17:12, Edit by VOBA
!
! Ident 25.
! Fix VY_ZERO_REQUEST to check for qualifier in ZERO MODULE message.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.11 25-Mar-82 16:43:55, Edit by VOBA
!
! Ident 24.
! Fix SCAN_PARAMETER not to allow multiple qualified NICE message to be
! processed.
! Fix NML$NICE_EXECUTE not to map LOGGING entity id to upper case.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.4 15-Mar-82 17:34:30, Edit by VOBA
!
! Ident 23.
! Fix SCAN_PARAMETER to recognize KNOWN SINKS which has CMN data format
! to be formatted with node count byte as -1.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.5 12-Mar-82 14:43:20, Edit by VOBA
!
! Ident 22.
! Fix SCAN_PARAMETER to recognize KNOWN qualifiers (i.e. NETWORKS, DTES,
! GROUPS, and DESTINATIONS) which have AI data format to be formatted with
! count byte as -1.
! Fix the local LENGTH in SCAN_PARAMETER to recognize signed byte value
! from the NICE message count byte.
! Remove checking of multiple qualifiers from SCAN_PARAMETER. Let the lower
! layers do that.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.5  5-Mar-82 10:37:06, Edit by VOBA
!
! Ident 21.
! Fix a typo in SCAN_PARAMETER.
!
! <VOBA.NML.DEVELOPMENT>NMLNIC.BLI.3  5-Mar-82 09:57:46, Edit by VOBA
!
! Ident 20.
! Fix bug in SCAN_PARAMETER to check for the count byte before proceeding
! to parse the rest of the AI and HI fields.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.3  2-Mar-82 15:37:57, Edit by VOBA
!
! Ident 19.
! Remove pointer to parameter name text in data structure of NICE parameter
! tables for MCB.
!
! <VOBA.NML.DEVELOPMENT>NMLNIC.BLI.3  1-Mar-82 17:25:19, Edit by VOBA
!
! Ident 18.
! Fix bug in SCAN_PARAMETER to obtain the NICE parameter entry to parameter
! table given to the routine.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLNIC.BLI.3  1-Mar-82 14:46:28, Edit by VOBA
!
! Ident 17.
! Assign HI a distinct value different from AI.
!
! <VOBA.NML.DEVELOPMENT>NMLNIC.BLI.24  1-Mar-82 11:31:04, Edit by VOBA
!
! Ident 16.
! Replace routines NODE_PARAMETERS, LINE_PARAMETERS, CIRCUIT_PARAMETERS,
! LOGGING_PARAMETERS, and MODULE_PARAMETERS with one single routine to do
! the parsing, SCAN_PARAMETER. This routine verifies the format of each
! parameter based on the data type information supplied by the data structure
! tables in NMLPRM module. The entry of each parameter in the tables is
! requested by reference to the routine NML$PARAMETER_LOOKUP in routine
! VERIFY_PARAMETERS.
!
! NET:<PECKHAM.DEVELOPMENT>NMLNIC.BLI                       Edit by PECKHAM
!
! Ident 15.
! Handle logging entity in GET_ENTITY_ID.
! Cleanup in VY_LOGGING_PARAMETERS.
!
! NET:<PECKHAM.DEVELOPMENT>NMLNIC.BLI.2  7-Feb-82 19:12:55, Edit by PECKHAM
!
! Ident 14.
! Fix HOST parameter number to 141 (bug introduced in #13.)
!
! NET:<PECKHAM.DEVELOPMENT>NMLNIC.BLI.3  7-Feb-82 17:46:53, Edit by PECKHAM
!
! Ident 13.
! Fix NODE_PARAMETERS, CIRCUIT_PARAMETERS, LINE_PARAMETERS, LOGGING_PARAMETERS
! to avoid references to NCPTAB variables.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.2 13-Nov-81 15:25:18, Edit by BRANDT
!
! Ident 12.
!   Fix NML$NICE_EXECUTE to have RB_NICE_ENTITY in the request block
!   point to an entity id that is always uppercase.  This allows NML and
!   lower layers to match either lower or uppercase entity id strings
!   without further checking for case distinction.
!
! NET:<DECNET20-V3P1.NMU.LIBRARY>NMLNIC.BLI.2 30-Jun-81 13:07:51, Edit by GUNN
!
! Ident 11.
! Fix VY_LOAD_REQUEST, VY_DUMP_REQUEST, and VY_TRIGGER_REQUEST to
! set RB_NICE_ENTITY_TYPE before calling GET_ENTITY_ID.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.2 16-Jun-81 17:05:14, Edit by GUNN
!
! Ident 10.
! Make VY_TEST_REQUEST set RB_NICE_ENTITY_TYPE to NODE when calling
! VERIFY_PARAMETERS. All LOOP parameters are NODE parameters regardless
! of the actual entity type for the request.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.8 10-Apr-81 11:26:06, Edit by GUNN
!
! Modify code in NML$DEQUEUE_REQUEST to not build a NICE response
! message on failure of the processing routine if the RB_RESPONSE_LENGTH
! is non-zero. This allows the lower level routines to build their own
! response messages if they desire.
! Modify NML$NICE_RESPONSE to allocate a response buffer only if one
! has not previously been allocated.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.6  7-Apr-81 12:22:49, Edit by GUNN
!
! Fix test for valid entity type in VY_LOAD_REQUEST, VY_DUMP_REQUEST,
! & VY_TRIGGER_REQUEST.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.4  1-Apr-81 16:35:26, Edit by GUNN
!
! Fix GET_ENTITY_ID to store pointer to non NODE entity ids pointing
! at length byte.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.3  1-Apr-81 10:26:09, Edit by GUNN
!
! Change allowed entity type in VY_LOAD_REQUEST, VY_DUMP_REQUEST,
! and VY_TRIGGER_REQUEST from LINE to CIRCUIT.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.2 13-Mar-81 12:40:18, Edit by GUNN
!
! Add code in NML$NICE_EXECUTE to convert executor node id to local
! name.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.3  6-Mar-81 11:19:27, Edit by GUNN
!
! Change all references to [RB_NICE_ENTITY_ID_LENGTH] to be treated
! as signed fullword value.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.10  3-Mar-81 16:12:57, Edit by GUNN
!
! Remove references to RB_RESPONSE_SIZE field of request block.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.8 27-Feb-81 15:19:12, Edit by GUNN
!
! Fix problem of passing length of buffer in $NML$MAP_NODE_ID macro call.
!
! NET:<DECNET20-V3P1.NML>NMLNIC.BLI.4 12-Feb-81 17:06:29, Edit by GUNN
!
! Add code to map an input node name to node address.
! Update copyright date.
!
%title 'NMLNIC -- NICE Message Verifier'
module NMLNIC	(
		ident = 'X03.39'
		) =
begin

!
!			  COPYRIGHT (c) 1980, 1981 BY
!	      DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASS.
!
! 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:
!
!	This module contains the routines which perform NICE request message
!	receipt and processing. NICE requests are processed from the NML
!	request queue. The queued NICE messages are checked for valid syntax
!	and converted to an internal format suitable for processing by the
!	local NML. Invalid NICE request messages result in a NICE error
!	response message being built and the NML request is terminated. Valid
!	NICE requests are dispatched for processing.
!
! ENVIRONMENT:	TOPS-10/20 & MCB/RSX11 User mode under NML
!
! AUTHOR: Dale C. Gunn , CREATION DATE:  5-Nov-80
!
! MODIFIED BY:
!
!	, : VERSION
! 01	-
!--
!
! INCLUDE FILES:
!

library 'NMLLIB';                       ! All required definitions

%if $TOPS20
    %then
	library 'MONSYM';		! Monitor symbols
	library 'JLNKG';		! JSYS linkage definitions
    %fi

require 'NMLEXT';                       ! NML External routines

!
! TABLE OF CONTENTS
!

forward routine
        NML$DEQUEUE_REQUEST : novalue,  ! Dequeues NICE requests for processing
	NML$NICE_VERIFY,                ! Performs syntax verification
        VY_LOAD_REQUEST,                ! Verify NICE load request message
        VY_DUMP_REQUEST,                ! Verify NICE dump request message
        VY_TRIGGER_REQUEST,             ! Verify NICE trigger request message
        VY_TEST_REQUEST,                ! Verify NICE test request message
        VY_CHANGE_REQUEST,              ! Verify NICE change request message
        VY_READ_REQUEST,                ! Verify NICE read request message
        VY_ZERO_REQUEST,                ! Verify NICE zero request message
        VY_SYSTEM_SPECIFIC,             ! Verify NICE system specific message
        GET_ENTITY_ID,                  ! Extracts entity id from NICE message
	NML$GET_SUBENTITY_ID,		! Extracts subentity id from NICE message
        VERIFY_PARAMETERS,              ! Verify NICE request parameters
	NML$NICE_EXECUTE,               ! Dispatches NICE request for execute
	NML$NICE_RESPONSE : novalue;    ! Builds NICE response message

!
! MACROS:
!

macro
     NEXTB_NICE =
         NEXTB (.REQ[RB_NICE_LENGTH],
                REQ[RB_NICE_POSITION]) %;

macro
     NEXTF_NICE =
         NEXTF (.REQ[RB_NICE_LENGTH],
                REQ[RB_NICE_POSITION],
                .REQ[RB_NICE_POINTER]) %;

macro
     NEXTW_NICE =
         NEXTW (.REQ[RB_NICE_LENGTH],
                REQ[RB_NICE_POSITION]) %;

macro
     NEXTN_NICE (N) =
         NEXTN (.REQ[RB_NICE_LENGTH],
                REQ[RB_NICE_POSITION],
                N) %;

macro
     ADVANCE_NICE (COUNT) =
         REQ[RB_NICE_POINTER] = ch$plus (.REQ[RB_NICE_POINTER], COUNT) %;

!
! EXTERNAL REFERENCES:
!

external routine
         NML$LOAD,                      ! Perform remote node load
         NML$DUMP,                      ! Perform remote node dump
         NML$TRIGGER,                   ! Perform remote node trigger boot
         NML$TEST,                      ! Perform loopback test
         NML$CHANGE,                    ! Perform change parameters
         NML$READ,                      ! Perform read information
         NML$ZERO,                      ! Perform zero counters
         NML$SYSTEM_SPECIFIC,           ! Perform system specific operations
         NML$DATA_TYPE,                 ! Get parameter data type/format
         NML$INFORMATION,               ! Check information type applicability
         NML$PARAMETER_DATA_SKIP,       ! Skip over parameter data
         NML$VALID_PARAMETER,           ! Check if parameter number valid
         NMU$NETWORK_LOCAL;             ! Obtain pointer to local node id
%global_routine ('NML$DEQUEUE_REQUEST') : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Retrieves NML NICE requests from the NML request queue, calls
!       NML$NICE_VERIFY to perform NICE message syntax verification and
!       preprocessing. If the NICE request message is valid calls
!       NML$NICE_EXECUTE to perform the requested NICE function, otherwise
!       calls NML$NICE_RESPONSE to build a NICE error response message and
!       NML$REQUEST_FINISH to remove the request from the active queue.
!       This is the main processing loop for NML requests.
!
! FORMAL PARAMETERS
!
!	NONE.
!
! IMPLICIT INPUTS
!
!	NML NICE request queue.
!
! ROUTINE VALUE:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	The processed NML NICE local request is removed from the active queue.
!
!--

    begin

    bind
	NULL = UPLIT(0);		! An "I-0" message

    local
         RTN_COD,                       ! NICE return code
         REQ: ref REQUEST_BLOCK;        ! Address of NML request block

    !
    ! Top level loop for NICE requests
    !

    while 1                             ! Main NML Request processing loop
    do begin
       REQ = NML$REQUEST_NEXT (RT$LOCAL); ! Get next local request to process
       REQ[RB_NICE_POSITION] = 0;       ! Initialize position in NICE message
       REQ[RB_NICE_POINTER] = ch$ptr(.REQ[RB_NICE],,8); ! Initialize pointer
       REQ[RB_ERROR_DETAIL] = -1;       ! Initialize for response msg
       REQ[RB_ERROR_POINTER] = ch$ptr (NULL,,8);

       RTN_COD = NML$NICE_VERIFY (.REQ); ! Verify the NICE message syntax

       if .RTN_COD eql 1                ! And if valid
       then RTN_COD = NML$NICE_EXECUTE (.REQ); ! Execute the request

       if .RTN_COD neq 1                ! If failed
       then begin                       ! Return reason if invalid
            if .REQ[RB_RESPONSE_LENGTH] eql 0
            then begin
                 REQ[RB_RETURN_CODE] = .RTN_COD; ! Set return code in RB
                 NML$NICE_RESPONSE (.REQ); ! Format response message
                 end;
            NML$REQUEST_FINISH (.REQ);  ! Queue request for completion
            end;
       end;

    end;				! End of NML$DEQUEUE_REQUEST
%routine ('NML$NICE_VERIFY', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    ! Get NICE request function code

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    REQ[RB_NICE_FUNCTION] = GETB (REQ[RB_NICE_POINTER]);

    !
    ! Assume no subentity type
    !
    ENTITY_TYPE[ENTITY_SUB] = NO_SUB_ENTITY;

    !
    ! Verify validity of NICE function code and dispatch to function
    ! specific verification routine if valid.
    !

    case .REQ[RB_NICE_FUNCTION] from LOAD_ to SYSTEM_SPECIFIC_ of
        set
        [LOAD_]:
             return VY_LOAD_REQUEST (.REQ);
        [DUMP_]:
             return VY_DUMP_REQUEST (.REQ);
        [TRIGGER_]:
             return VY_TRIGGER_REQUEST (.REQ);
        [TEST_]:
             return VY_TEST_REQUEST (.REQ);
        [CHANGE_]:
             return VY_CHANGE_REQUEST (.REQ);
        [READ_]:
             return VY_READ_REQUEST (.REQ);
        [ZERO_]:
             return VY_ZERO_REQUEST (.REQ);
        [SYSTEM_SPECIFIC_]:
             return VY_SYSTEM_SPECIFIC (.REQ);
        [inrange,
         outrange]:
            return $NICE$ERR_UFO;
        tes

    end;				! End of NML$NICE_VERIFY
%routine ('VY_LOAD_REQUEST', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE load request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           SET_DEFINE = 0;              ! Parameters with value as in SET

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         OPT: block[1] field (LOAD_OPTIONS), ! NICE request options
         RTN_COD;                       ! NICE return code

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    OPT = GETB (REQ[RB_NICE_POINTER]);  ! Get the option byte
    REQ[RB_NICE_OPTION] = .OPT;         ! Store option byte in RB

    if .OPT[LO_RESERVED] neq 0          ! Check for reserved bits all zero
    then return $NICE$ERR_UFO;

    selectone .OPT[LO_ENTITY_TYPE] of   ! Check for allowable entity
        set
       [ENTITY_NODE, ENTITY_CIRCUIT] : 0;
        [otherwise] : return $NICE$ERR_UFO;
        tes;

    ENTITY_TYPE  = .OPT[LO_ENTITY_TYPE]; ! Get the entity type
    RTN_COD = GET_ENTITY_ID (.REQ);     ! Process entity id

    if .RTN_COD neq NICE$_SUC           ! Check for valid entity id
    then return .RTN_COD;

    ENTITY_TYPE[ENTITY_MAIN] = ENTITY_NODE; ! Parameters belong to node
    RTN_COD = VERIFY_PARAMETERS (SET_DEFINE, .REQ);
    ENTITY_TYPE[ENTITY_MAIN] = .OPT[LO_ENTITY_TYPE]; ! Get the entity type

    return .RTN_COD
    end;				! End of VY_LOAD_REQUEST
%routine ('VY_DUMP_REQUEST', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE dump request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           SET_DEFINE = 0;              ! Parameters with value as in SET

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         OPT: block[1] field (DUMP_OPTIONS), ! NICE request options
         RTN_COD;                       ! NICE return code

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    OPT = GETB (REQ[RB_NICE_POINTER]);  ! Get the option byte
    REQ[RB_NICE_OPTION] = .OPT;         ! Store option byte in RB

    if .OPT[DO_RESERVED] neq 0          ! Check for reserved bits all zero
    then return $NICE$ERR_UFO;

    selectone .OPT[DO_ENTITY_TYPE] of   ! Check for allowable entity
        set
       [ENTITY_NODE, ENTITY_CIRCUIT] : 0;
        [otherwise] : return $NICE$ERR_UFO;
        tes;

    ENTITY_TYPE[ENTITY_MAIN] = .OPT[DO_ENTITY_TYPE]; ! Get the entity type
    RTN_COD = GET_ENTITY_ID (.REQ);     ! Process entity id

    if .RTN_COD neq NICE$_SUC           ! Check for valid entity id
    then return .RTN_COD;

    ENTITY_TYPE[ENTITY_MAIN] = ENTITY_NODE; ! Parameters belong to node
    RTN_COD = VERIFY_PARAMETERS (SET_DEFINE, .REQ);
    ENTITY_TYPE[ENTITY_MAIN] = .OPT[DO_ENTITY_TYPE]; ! Get the entity type

    return .RTN_COD
    end;				! End of VY_DUMP_REQUEST
%routine ('VY_TRIGGER_REQUEST', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE trigger boot request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           SET_DEFINE = 0;              ! Parameters with value as in SET

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         OPT: block[1] field (BOOT_OPTIONS), ! NICE request options
         RTN_COD;                       ! NICE return code

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    OPT = GETB (REQ[RB_NICE_POINTER]);  ! Get the option byte
    REQ[RB_NICE_OPTION] = .OPT;         ! Store option byte in RB

    if .OPT[BO_RESERVED] neq 0          ! Check for reserved bits all zero
    then return $NICE$ERR_UFO;

    selectone .OPT[BO_ENTITY_TYPE] of   ! Check for allowable entity
        set
       [ENTITY_NODE, ENTITY_CIRCUIT] : 0;
        [otherwise] : return $NICE$ERR_UFO;
        tes;

    ENTITY_TYPE[ENTITY_MAIN] = .OPT[BO_ENTITY_TYPE]; ! Get the entity type
    RTN_COD = GET_ENTITY_ID (.REQ);     ! Process entity id

    if .RTN_COD neq NICE$_SUC           ! Check for valid entity id
    then return .RTN_COD;

    ENTITY_TYPE[ENTITY_MAIN] = ENTITY_NODE; ! Parameters belong to node
    RTN_COD = VERIFY_PARAMETERS (SET_DEFINE, .REQ);
    ENTITY_TYPE[ENTITY_MAIN] = .OPT[BO_ENTITY_TYPE]; ! Get the entity type

    return .RTN_COD
    end;				! End of VY_TRIGGER_REQUEST
%routine ('VY_TEST_REQUEST', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE test request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           SET_DEFINE = 0;              ! Parameters with value as in SET

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         OPT: block[1] field (TEST_OPTIONS), ! NICE request options
         RTN_COD;                       ! NICE return code

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    ! Process option byte if present

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER]);
    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte

    if .OPT[TO_RESERVED] neq 0          ! Check for reserved bits all zero
    then return $NICE$ERR_IMF;

    ENTITY_TYPE[ENTITY_MAIN] = .OPT[TO_ENTITY_TYPE]; ! Get the entity type
    RTN_COD = GET_ENTITY_ID (.REQ);     ! Process entity id

    if .RTN_COD neq NICE$_SUC           ! Check for valid entity id
    then return .RTN_COD;

    if .ENTITY_TYPE[ENTITY_MAIN] neq ENTITY_NODE ! Get and check entity type
    then begin                          ! LINE type loop test
         local ENT_TYP;                 ! Temporary for entity type

         if .OPT[TO_ACCESS_CONTROL]     ! Access control not valid with LINE
         then return $NICE$ERR_IMF;
         ENT_TYP = .ENTITY_TYPE;  ! Save entity type
         ENTITY_TYPE[ENTITY_MAIN] = ENTITY_NODE; ! Parameters are for NODE entity
	 RTN_COD = VERIFY_PARAMETERS (SET_DEFINE,.REQ); ! Process parameters
         ENTITY_TYPE = .ENT_TYP;
         end
    else begin                          ! NODE type loop test

         ! Clear access control fields in RB for our use

         REQ[RB_USER_LENGTH] = REQ[RB_USER] = 0;
         REQ[RB_PASSWORD_LENGTH] = REQ[RB_PASSWORD] = 0;
         REQ[RB_ACCOUNT_LENGTH] = REQ[RB_ACCOUNT] = 0;

         if .OPT[TO_ACCESS_CONTROL]
         then begin                     ! Process the 3 access control fields
              if NEXTF_NICE
              then begin                ! Process User id field if in message
                   REQ[RB_USER_LENGTH] = GETB (REQ[RB_NICE_POINTER]);
                   if (.REQ[RB_USER_LENGTH] gtr 0)
                   and (.REQ[RB_NICE_LENGTH] gtr .REQ[RB_NICE_POSITION])
                   then REQ[RB_USER] = .REQ[RB_NICE_POINTER];
                   ADVANCE_NICE (.REQ[RB_USER_LENGTH]);
                   end
              else return $NICE$ERR_IMF;

              if NEXTF_NICE
              then begin                     ! Process password field
                   REQ[RB_PASSWORD_LENGTH] = GETB (REQ[RB_NICE_POINTER]);
                   if (.REQ[RB_PASSWORD_LENGTH] gtr 0)
                   and (.REQ[RB_NICE_LENGTH] gtr .REQ[RB_NICE_POSITION])
                   then REQ[RB_PASSWORD] = .REQ[RB_NICE_POINTER];
                   ADVANCE_NICE (.REQ[RB_PASSWORD_LENGTH]);
                   end
              else return $NICE$ERR_IMF;

              if NEXTF_NICE
              then begin                     ! Process account field
                   REQ[RB_ACCOUNT_LENGTH] = GETB (REQ[RB_NICE_POINTER]);
                   if (.REQ[RB_ACCOUNT_LENGTH] gtr 0)
                   and (.REQ[RB_NICE_LENGTH] gtr .REQ[RB_NICE_POSITION])
                   then REQ[RB_ACCOUNT] = .REQ[RB_NICE_POINTER];
                   ADVANCE_NICE (.REQ[RB_ACCOUNT_LENGTH]);
                   end
              else return $NICE$ERR_IMF;
              end;

	 RTN_COD = VERIFY_PARAMETERS (SET_DEFINE, .REQ);
         end;

    return .RTN_COD
    end;				! End of VY_TEST_REQUEST
%routine ('VY_CHANGE_REQUEST', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE change parameter request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         OPT: block[1] field (CHANGE_OPTIONS), ! NICE request options
         RTN_COD;                       ! NICE return code

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER]);
    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte

    if .OPT[CO_RESERVED] neq 0          ! Check for reserved bits all zero
    then return $NICE$ERR_UFO;

    ENTITY_TYPE[ENTITY_MAIN] = .OPT[CO_ENTITY_TYPE]; ! Get the entity type
    RTN_COD = GET_ENTITY_ID (.REQ);     ! Process entity id

    if .RTN_COD neq NICE$_SUC           ! Check for valid entity id
    then return .RTN_COD;

    return VERIFY_PARAMETERS (.OPT[CO_CLEAR_PURGE], .REQ)
    end;				! End of VY_CHANGE_REQUEST
%routine ('VY_READ_REQUEST', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE read information request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           SET_DEFINE = 0;              ! Parameters with value as in SET

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         OPT: block[1] field (READ_OPTIONS), ! NICE request options
         RTN_COD;                       ! NICE return code

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER]);
    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte

    if .OPT[RO_RESERVED] neq 0          ! Check for reserved bits all zero
    then return $NICE$ERR_UFO;

    selectone .OPT[RO_INFO_TYPE] of     ! Check for valid information type
        set
        [0 to INFORMATION_HI] : 0;
        [otherwise] : return $NICE$ERR_UFO;
        tes;

    ENTITY_TYPE[ENTITY_MAIN] = .OPT[RO_ENTITY_TYPE];   ! Get the entity type

    RTN_COD = GET_ENTITY_ID (.REQ);     ! Process entity id

    if .RTN_COD neq NICE$_SUC           ! Check for valid entity id
    then return .RTN_COD;

    return VERIFY_PARAMETERS (SET_DEFINE, .REQ)
    end;				! End of VY_READ_REQUEST
%routine ('VY_ZERO_REQUEST', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE zero counters request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    literal
           QUALIFIER_PARAMETER = 0;

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         OPT: block [1] field (ZERO_OPTIONS), ! NICE request options
         RTN_COD;                       ! NICE return code

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    ! Check for NICE option byte

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER]);
    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte

    if .OPT[ZO_RESERVED] neq 0          ! Check for reserved bits all zero
    then return $NICE$ERR_UFO;

    ENTITY_TYPE[ENTITY_MAIN] = .OPT[ZO_ENTITY_TYPE]; ! Get the entity type
    RTN_COD = GET_ENTITY_ID (.REQ);     ! Process entity id

    if .RTN_COD neq NICE$_SUC           ! Check for valid entity id
    then return .RTN_COD;

    if ENTITY_TYPE[ENTITY_MAIN] eql ENTITY_MODULE
    then return VERIFY_PARAMETERS (QUALIFIER_PARAMETER, .REQ)
    else return 1
    end;				! End of VY_ZERO_REQUEST
%routine ('VY_SYSTEM_SPECIFIC', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Performs syntax verification of NICE system-specific request messages.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         SYS_TYPE,                      ! Specific system type
         RTN_COD;                       ! NICE return code

    if not NEXTB_NICE then return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER]);
    SYS_TYPE = .REQ[RB_NICE_OPTION];    ! Get the system type

    if .SYS_TYPE nequ TOPS20_           ! Check for valid system type
    then return $NICE$ERR_UFO
    else return 1
    end;				! End of VY_SYSTEM_SPECIFIC
%routine ('GET_ENTITY_ID', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Extracts the entity id field from a NICE request message.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	NICE$_SUC if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local								     
         FORMAT: $SIGNED_BYTE_VALUE;    ! Local signed entity id length

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    !
    ! Get the entity format byte.
    !

    if not NEXTB_NICE then return $NICE$ERR_IMF; ! Entity id in message?

    FORMAT = GETB (REQ[RB_NICE_POINTER]); ! Fetch format byte
    REQ[RB_NICE_ENTITY_ID_LENGTH] = FORMAT = .FORMAT[VALUE]; ! Get class or length

    !
    ! Handle specific entity id. Note that we already accounted for the
    ! format byte which if greater than zero is the length byte of an
    ! of an I-field.
    !
    ! Process rest of entity id format according to entity type.
    !

    case .ENTITY_TYPE[ENTITY_MAIN] from ENTITY_LO to ENTITY_HI of
        set
       [ENTITY_NODE]:
            if .FORMAT lss 0
            then begin                  ! Selector
                 selectone .FORMAT of   ! verify legal set.
                     set
                     [KNOWN_,
                      ACTIVE_,
                      LOOPED_,
                      ADJACENT_,
                      SIGNIFICANT_]: 0;
                     [otherwise]: return $NICE$ERR_IID;
                     tes;
                 REQ[RB_NICE_ENTITY] = 0;
                 end
            else begin
                 !
                 ! If the format specifies zero length, it is followed
                 ! by two bytes of node address, otherwise a node name
                 ! follows.
                 !
                 selectone .FORMAT of
                     set
                     [0]: FORMAT = 2;
                     [1 to 6]: 0;
                     [otherwise]: return $NICE$ERR_IMF;
                     tes;

                 REQ[RB_NICE_ENTITY] = .REQ[RB_NICE_POINTER];
                 !
                 ! Pass the entity-id by.
                 !
                 if not NEXTN_NICE (.FORMAT) then return $NICE$ERR_IMF;
                 ADVANCE_NICE (.FORMAT);
                 end;

       [ENTITY_LINE,
        ENTITY_CIRCUIT]:
            if .FORMAT lss 0
            then begin
                 REQ[RB_NICE_ENTITY] = 0;
                 end
            else begin
                 REQ[RB_NICE_ENTITY] = ch$plus (.REQ[RB_NICE_POINTER], -1);
                 !
                 ! Pass the entity-id by.
                 !
                 if not NEXTN_NICE (.FORMAT) then return $NICE$ERR_IMF;
                 ADVANCE_NICE (.FORMAT);
                 end;

       [ENTITY_MODULE]:
            if .FORMAT lss 0
            then begin
                 REQ[RB_NICE_ENTITY] = 0;
                 end
            else begin
                 REQ[RB_NICE_ENTITY] = ch$plus (.REQ[RB_NICE_POINTER], -1);
                 if not NEXTN_NICE (.FORMAT) then return $NICE$ERR_IMF;

		 !
		 ! Extract the subentity type
		 !
		 if (ENTITY_TYPE[ENTITY_SUB] =
			NML$GET_SUBENTITY_ID (.FORMAT, .REQ [RB_NICE_POINTER]))
		    eql 0 then return $NICE$ERR_IMF;

                 !
                 ! Pass the entity-id by.
                 !
                 ADVANCE_NICE (.FORMAT);
                 end;


       [ENTITY_LOGGING]:
            if .FORMAT lss 0
            then begin
                 selectone .FORMAT of
                     set
                     [KNOWN_, ACTIVE_]: 0;
                     [otherwise]: return $NICE$ERR_IID;
                     tes;
                 REQ[RB_NICE_ENTITY] = 0;
                 end
            else REQ[RB_NICE_ENTITY] = ch$plus (.REQ[RB_NICE_POINTER], -1);

       [ENTITY_AREA]:
            if .FORMAT lss 0
            then begin
                 selectone .FORMAT of
                     set
                     [KNOWN_, ACTIVE_]: 0;
                     [otherwise]: return $NICE$ERR_IID;
                     tes;
                 REQ[RB_NICE_ENTITY] = 0;
                 end
            else if .FORMAT eql 0
                 then begin
                      FORMAT = .FORMAT + 1;
                      REQ[RB_NICE_ENTITY] = .REQ[RB_NICE_POINTER];
                      !
                      ! Pass the area by.
                      !
                      if not NEXTN_NICE (.FORMAT) then return $NICE$ERR_IMF;
                      ADVANCE_NICE (.FORMAT);
                      end
                 else return $NICE$ERR_IID;

        [outrange]:
            return $NICE$ERR_URC;
        tes;

    return NICE$_SUC
    end;				! End of GET_ENTITY_ID
%global_routine ('NML$GET_SUBENTITY_ID', LENGTH, POINTER) =

!++
! FUNCTIONAL DESCRIPTION:
!    	Return subentity type or zero if no match.
!
! FORMAL PARAMETERS
!
!	LENGTH -  Length of alleged module entity id
!
!	POINTER - Character pointer to alleged module entity id
!
! IMPLICIT INPUTS
!
!    	NONE.
!
! ROUTINE VALUE:
!
!	Subentity type.
!
! SIDE EFFECTS:
!
!    	NONE.
!--
    begin
!
! This iterative macro generates the neccesary code using the subentity
! list defined in NMARCH.REQ.
!
    macro
	$NML$SUB_ENT (LENGTH, POINTER) [STRING, VALUE] =
	    TEMP = ch$ptr (uplit (%string (STRING)));
	    if ch$eql (.LENGTH, .POINTER, .LENGTH, .TEMP)
	    then return %name ( 'MODULE_', %string (VALUE)) %;

    local TEMP;

    $NML$SUB_ENT (LENGTH, POINTER, $NML$MODULE_SUBENTITY_STRINGS);

    return NO_SUB_ENTITY;

    end;				! End of NML$GET_SUBENTITY_ID
%routine ('VERIFY_PARAMETERS', CLEAR_PURGE, REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    REQ[RB_NICE_PARAMETERS] = .REQ[RB_NICE_POINTER];  ! Store parameters

    selectone .ENTITY_TYPE[ENTITY_MAIN] of
        set
       [ENTITY_LO to ENTITY_HI] : 0;   ! Okay
        [otherwise] :                   ! Illegal entity type
            begin
            REQ[RB_ERROR_DETAIL] = .ENTITY_TYPE[ENTITY_MAIN];
            return $NICE$ERR_URC;
            end;
        tes;

    ! Loop through the NICE message, verifying each parameter, stopping
    ! at end of the message.

    while NEXTW_NICE                    ! Process parameter
    do begin
       local PARAMETER;                 ! NICE parameter number

       PARAMETER = GETW (REQ[RB_NICE_POINTER]); ! Get parameter number

       if not NML$VALID_PARAMETER (.ENTITY_TYPE, .PARAMETER)
       then return $NICE$ERR_UPT;       ! Unknown parameter

       if NML$INFORMATION (.ENTITY_TYPE, .PARAMETER, QUALIFIER_)
       then begin                       ! Yes, check if we already got one
            if .REQ[RB_NICE_QUALIFIER] neq 0
            then return $NICE$ERR_IPG;  ! Already got one, cannot handle second
            REQ[RB_NICE_QUALIFIER] = ch$plus (.REQ[RB_NICE_POINTER], -2);
            end
       else begin                       ! Come here if not qualifier
       
       ! If this is a CLEAR/PURGE data is not allowed to follow the parameter
       ! UNLESS it is the EVENT parameter that is being set. Therefore, check
       ! for EVENT parameter # = 201 and LOGGING entity
            if .CLEAR_PURGE
            and (not ((.REQ[RB_NICE_ENTITY_TYPE] = ENTITY_LOGGING)
                     and (.PARAMETER eql 201)))
            then PARAMETER = -1;        ! then indicate no data.
       end;

       if .PARAMETER geq 0              ! Is there data?
       then begin                       ! Yes, make sure it is there
            local LEN;                  ! and skip over it.

            LEN = NML$PARAMETER_DATA_SKIP (.ENTITY_TYPE, .PARAMETER,
                                           REQ[RB_NICE_POINTER]);

            if not NEXTN_NICE (.LEN) then return $NICE$ERR_IMF;

            end;

       end;

    return $TRUE                        ! All parameters are OK
    end;				! End of VERIFY_PARAMETERS
%routine ('NML$NICE_EXECUTE', REQ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Dispatches to the appropriate NML NICE request processing routine.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	1 if NICE request message has valid syntax.
!       NEGATIVE NICE error return code if invalid.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    local
         RESULT,
         EID_LEN: $SIGNED_BYTE_VALUE,   ! Signed length of entity id
         EID_PTR,
         EID_ADR;

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    ! Make sure we start at beginning of NICE request message.

    REQ[RB_NICE_POSITION] = 0;          ! Initialize position in NICE message
    REQ[RB_NICE_POINTER] = ch$ptr(.REQ[RB_NICE],,8); ! Initialize pointer
    REQ[RB_NICE_ENTITY_ADR] = 0;	! Initially no allocated memory

    RESULT = 1;                         ! Initially success unless error

    ! If the entity type is NODE,
    ! then transform node entity id from NICE input format
    ! to full address and name format for use internally.
    ! The contents of REQ[RB_NICE_ENTITY] which points into the entity
    ! entity id portion of the NICE message on entry to this routine
    ! will be replaced by a pointer into a buffer allocated here and
    ! filled in with the full node id.

    case .ENTITY_TYPE[ENTITY_MAIN] from ENTITY_LO to ENTITY_HI of
        set
       [ENTITY_NODE]:
            begin
            local L, ADDRESS;

            EID_ADR = NMU$MEMORY_GET (NODE_ID_BUFFER_ALLOCATION);
            if .EID_ADR eql 0           ! If cannot get buffer
            then return $NICE$ERR_REE;  ! return error

	    REQ[RB_NICE_ENTITY_ADR] = .EID_ADR;
            EID_PTR = ch$ptr (.EID_ADR,,8);
            EID_LEN = .REQ[RB_NICE_ENTITY_ID_LENGTH]; ! Pick up the id length
            L = NODE_ID_BUFFER_LENGTH;

            if .EID_LEN[VALUE] eql 0
            then begin                  ! NODE address format
                 ADDRESS = GETW (REQ[RB_NICE_ENTITY]); ! Get node address value
                 if .ADDRESS eql 0
                 then begin
                      ch$move (NODE_ID_BUFFER_LENGTH,
                               NMU$NETWORK_LOCAL (),
                               .EID_PTR);
                      REQ[RB_NICE_ENTITY] = ch$ptr (.EID_ADR,,8);
                      end
                 else begin
                      if .ADDRESS<10,6,0> eql 0  ! Check for AREA 0
                      then begin
                           local BUFFER : vector[NODE_ID_BUFFER_ALLOCATION],
                                 NODE_ID,
                                 AREA,
                                 BPTR;
                           BPTR = NMU$NETWORK_LOCAL ();
                           NODE_ID = GETW (BPTR);
                           AREA = .NODE_ID<10,6,0>;
                           ADDRESS<10,6,0> = .AREA;
                           end;
                      PUTW (ADDRESS, EID_PTR); ! Store node address
                      PUTB (0, EID_PTR); ! Zero length node name
                      REQ[RB_NICE_ENTITY] = ch$ptr (.EID_ADR,,8);
                      $NML$MAP_NODE_ID (L, .REQ[RB_NICE_ENTITY]);
		      REQ[RB_NICE_ENTITY_ID_LENGTH] = .L - 3;
                      end;
                 end
            else begin
                 if .EID_LEN[VALUE] gtr 0
                 then begin             ! NODE name format
                      ADDRESS = 0;      ! Node address is zero
                      PUTW (ADDRESS, EID_PTR); ! Store node address of zero
                      PUTB (.EID_LEN[VALUE], EID_PTR);
                      ch$move (.EID_LEN[VALUE], ! Move node name string
                               .REQ[RB_NICE_ENTITY],
                               .EID_PTR);
                      REQ[RB_NICE_ENTITY] = ch$ptr (.EID_ADR,,8);
                      $NML$MAP_NODE_ID (L, .REQ[RB_NICE_ENTITY]);
                      end
                 else REQ[RB_NICE_ENTITY] = 0; ! Means entity class
                 end;
            end;

       [ENTITY_LINE,
         ENTITY_CIRCUIT,
         ENTITY_MODULE]:                ! Other entities
            begin
            local PTR, LEN: $SIGNED_BYTE_VALUE;

            PTR = .REQ[RB_NICE_ENTITY]; ! Get string pointer
            LEN[VALUE] = ch$rchar (.PTR); ! Read count byte

            if .LEN[VALUE] gtr 0        ! If count byte is positive
            then begin
                 incr N from 1 to .LEN[VALUE]
                 do begin               ! Convert text to upper case
                    local C;

                    C = ch$a_rchar (PTR);
                    if (.C geq %c'a') and (.C leq %c'z')
                    then ch$wchar ((.C - %C'a' + %C'A'), .PTR);
                    end;
                 end;
            end;

       [ENTITY_LOGGING,
        ENTITY_AREA]:                  ! No mapping for these entities
            0;
        tes;

    if .RESULT eql 1
    then begin
         case .REQ[RB_NICE_FUNCTION] from LOAD_ to SYSTEM_SPECIFIC_ of
             set
             [LOAD_]:
                 RESULT = NML$LOAD (.REQ);

             [DUMP_]:
                 RESULT = NML$DUMP (.REQ);

             [TRIGGER_]:
                 RESULT = NML$TRIGGER (.REQ);

             [TEST_]:
                 RESULT = NML$TEST (.REQ);

             [CHANGE_]:
                 RESULT = NML$CHANGE (.REQ);

             [READ_]:
                 RESULT = NML$READ (.REQ);

             [ZERO_]:
                 RESULT = NML$ZERO (.REQ);

             [SYSTEM_SPECIFIC_]:
                 RESULT = NML$SYSTEM_SPECIFIC (.REQ);

             [inrange,                  ! NML's internal error if here
              outrange]:
                 RESULT = $NICE$ERR_MPE;
             tes;
        end;

    return .RESULT
    end;				! End of NML$NICE_EXECUTE
%global_routine ('NML$NICE_RESPONSE', REQ) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Builds a NICE response message for the current NML NICE request.
!       If a NICE response message buffer has not yet been allocated
!       will allocate one.
!
! FORMAL PARAMETERS
!
!	REQ - Address of NICE request block (RB).
!
! IMPLICIT INPUTS
!
!	Various fields in NICE request block set during processing.
!
! ROUTINE VALUE:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;          ! NICE RB structure

    literal
           RESPONSE_LENGTH = 1024,       ! Length of response buffer in bytes
           RESPONSE_SIZE = ch$allocation (RESPONSE_LENGTH,8),
           RESPONSE_ALLOCATION = RESPONSE_SIZE * %upval;

    local
	 EID_PTR,
	 EID_LEN,
         ERR_DTL,
	 LENGTH,
	 NICE_EID_LEN: $SIGNED_BYTE_VALUE,
         RESP_PTR;                      ! Pointer to NICE response message

    bind 
       ENTITY_TYPE = REQ[RB_NICE_ENTITY_TYPE] : FULL_ENTITY;	! Address of entity type in REQ

    !
    ! If there is no NICE repsonse buffer allocated then allocate one.
    ! Store allocation size for response message buffer.
    ! The NICE response buffer is released by the request completion
    ! routine.

    if .REQ[RB_RESPONSE_ALLOCATION] eql 0
    then begin
         REQ[RB_RESPONSE_ALLOCATION] = RESPONSE_ALLOCATION;
         REQ[RB_RESPONSE] = NMU$MEMORY_GET (RESPONSE_ALLOCATION);
         end;

    !
    ! Initialize buffer for NICE response.
    !

    REQ[RB_RESPONSE_LENGTH] = 0;        ! Initialize length of response
    RESP_PTR = ch$ptr (.REQ[RB_RESPONSE],,8); ! Initialize pointer to response

    PUTB (.REQ[RB_RETURN_CODE], RESP_PTR); ! Stash NICE return code
    REQ[RB_RESPONSE_LENGTH] = .REQ[RB_RESPONSE_LENGTH] + 1;

    if ((.REQ[RB_RETURN_CODE] eql 2) or ! If short response message
        (.REQ[RB_RETURN_CODE] eql -128)) ! we are done
    then return;

    ERR_DTL = .REQ[RB_ERROR_DETAIL];
    REQ[RB_ERROR_DETAIL] = -1;          ! Reset for next response msg
    PUTW (ERR_DTL, RESP_PTR);           ! Stash error detail
    REQ[RB_RESPONSE_LENGTH] = .REQ[RB_RESPONSE_LENGTH] + 2;

    LENGTH = ch$rchar(.REQ[RB_ERROR_POINTER]) + 1;
    RESP_PTR = ch$move (.LENGTH,        ! Text count
                        .REQ[RB_ERROR_POINTER],
                        .RESP_PTR);
    REQ[RB_RESPONSE_LENGTH] = .REQ[RB_RESPONSE_LENGTH] + .LENGTH;

    NICE_EID_LEN = .REQ[RB_NICE_ENTITY_ID_LENGTH];

    if ((.NICE_EID_LEN[VALUE] lss 0) or       ! If plural entity class
        (.REQ[RB_NICE_FUNCTION] eql READ_) or !  or READ
        (.REQ[RB_NICE_FUNCTION] eql ZERO_ and !  or READ and ZERO
         .REQ[$sub_field (RB_NICE_OPTION, ZO_READ_AND_ZERO)] eql 1))
    then
	begin				      ! include an entity ID
        EID_PTR = .REQ[RB_NICE_ENTITY];
        case .ENTITY_TYPE[ENTITY_MAIN] from ENTITY_LO to ENTITY_HI of
            set
           [ENTITY_NODE]:              ! NODE has special format
                begin
                local
                    NODE_ID_PTR,
                    LOCAL_NODE_PTR;

                LOCAL_NODE_PTR = NMU$NETWORK_LOCAL (); ! Local node id
                NODE_ID_PTR = .RESP_PTR; ! Make copy of current pointer

                EID_LEN = ch$rchar (ch$plus (.EID_PTR,2)) + 3;
                RESP_PTR = ch$move (.EID_LEN, .EID_PTR, .RESP_PTR);
                !
                ! If node addresses are equal this is the executor node,
                ! so set bit 7 in length byte to indicate this fact.
                !
                if GETB (NODE_ID_PTR) eql GETB (LOCAL_NODE_PTR)
                then if GETB (NODE_ID_PTR) eql GETB (LOCAL_NODE_PTR)
                     then ch$wchar ((ch$rchar (.NODE_ID_PTR) or (1 ^ 7)), .NODE_ID_PTR);

                REQ[RB_RESPONSE_LENGTH] = .REQ[RB_RESPONSE_LENGTH] + .EID_LEN;
                end;

           [ENTITY_LINE,
            ENTITY_CIRCUIT,
            ENTITY_MODULE]:
                begin
                EID_LEN = ch$rchar (.EID_PTR) + 1;
                RESP_PTR = ch$move (.EID_LEN, .EID_PTR, .RESP_PTR);
                REQ[RB_RESPONSE_LENGTH] = .REQ[RB_RESPONSE_LENGTH] + .EID_LEN;
                end;

           [ENTITY_LOGGING,
            ENTITY_AREA]:
                begin
                ch$wchar_a (ch$rchar (.EID_PTR),RESP_PTR);
                REQ[RB_RESPONSE_LENGTH] = .REQ[RB_RESPONSE_LENGTH] + 1;
                end;
            tes;
        end;

    end;				! End of NML$NICE_RESPONSE
end                                     ! End of Module NMLNIC
eludom
! Local Modes:
! Mode:BLISS
! Auto Save Mode:0
! Comment Column:40
! Comment Rounding:+1
! End: