Google
 

Trailing-Edge - PDP-10 Archives - BB-P363B-SM_1985 - mcb/nml/nmlnic.bli
There are 2 other files named nmlnic.bli in the archive. Click here to see a list.
! <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.30'
		) =
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:
!
!	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
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
        SCAN_PARAMETER,                 ! Scan and verify parameter data fields
        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 (POINTER, COUNT) =
         POINTER = ch$plus (.POINTER, COUNT) %;

$show (all);

$field TABLE_ENTRY_FIELDS =
    set
    NICE_PARAMETER_NUMBER = [$integer],
    NICE_PARAMETER_ENTRY = [$address]
    tes;

literal
    TABLE_ENTRY_SIZE = $field_set_size;

macro
     NICE_PARAMETER_TABLE_ENTRY =
         block [TABLE_ENTRY_SIZE] field (TABLE_ENTRY_FIELDS) %;

$field PARAMETER_ENTRY_FIELDS =
    set
    %if not $MCB %then
    _NAME = [$pointer],                 ! Pointer to parameter name text
    %fi

    _DATA_FORMAT = [$byte],             ! Data format code
    _DATA_TYPE = [$byte],               ! Data type byte

        $align (byte)                   ! Restrictions
    _NML_PARAMETER = [$bit],            ! ON if NML owns this parameter
    _SETTABILITY = [$bits(2)],
    _APPLICABILITY = [$bits(5)],
        $overlay (_SETTABILITY)         ! Settability restrictions
    _READ_ONLY = [$bit],
    _WRITE_ONLY = [$bit],
        $continue
        $overlay (_APPLICABILITY)       ! Applicability restrictions
    _QUALIFIED = [$bit],
    _EXECUTOR_ONLY = [$bit],
    _OTHER_NODES = [$bits(3)],
        $overlay (_OTHER_NODES)
    _ADJACENT_ONLY = [$bit],
    _REMOTE_ONLY = [$bit],
    _SINK_ONLY = [$bit],
        $continue
        $continue

        $align (byte)                   ! Information type applicability
    _CHARACTERISTIC = [$bit],
    _STATUS = [$bit],
    _SUMMARY = [$bit],
    _EVENTS = [$bit],
    _QUALIFIER = [$bit],

    _CLEARABLE = [$bit],
    _UPPER_CASE = [$bit]
    tes;

literal
    PARAMETER_ENTRY_SIZE = $field_set_size;

macro
     PARAMETER_ENTRY =
         block [PARAMETER_ENTRY_SIZE] field (PARAMETER_ENTRY_FIELDS) %;

$show (none);

!
! 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$PARAMETER_LOOKUP,          ! Lookup NICE parameter
         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

    if NEXTB_NICE                       ! Get NICE request function code
    then REQ[RB_NICE_FUNCTION] = GETB (REQ[RB_NICE_POINTER])
    else return $NICE$ERR_IMF;

    !
    ! 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

    if NEXTB_NICE
    then OPT = GETB (REQ[RB_NICE_POINTER]) ! Get the option byte
    else return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = .OPT;         ! Store option byte in RB

    if (.OPT[LO_ENTITY_TYPE] neq NODE_E) ! Check for allowable entity
    and (.OPT[LO_ENTITY_TYPE] neq CIRCUIT_)
    then return $NICE$ERR_UFO;

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

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

    if .RTN_COD leq -1                  ! Check for valid entity id
    then return .RTN_COD;

    REQ[RB_NICE_ENTITY_TYPE] = NODE_E;  ! Parameters belong to node
    RTN_COD = VERIFY_PARAMETERS (SET_DEFINE, .REQ);
    REQ[RB_NICE_ENTITY_TYPE] = .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

    if NEXTB_NICE
    then OPT = GETB (REQ[RB_NICE_POINTER]) ! Get the option byte
    else return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = .OPT;         ! Store option byte in RB

    if (.OPT[DO_ENTITY_TYPE] neq NODE_E) ! Check for allowable entity
    and (.OPT[DO_ENTITY_TYPE] neq CIRCUIT_)
    then return $NICE$ERR_UFO;

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

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

    if .RTN_COD leq -1                  ! Check for valid entity id
    then return .RTN_COD;

    REQ[RB_NICE_ENTITY_TYPE] = NODE_E;  ! Parameters belong to node
    RTN_COD = VERIFY_PARAMETERS (SET_DEFINE, .REQ);
    REQ[RB_NICE_ENTITY_TYPE] = .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

    if NEXTB_NICE
    then OPT = GETB (REQ[RB_NICE_POINTER]) ! Get the option byte
    else return $NICE$ERR_IMF;

    REQ[RB_NICE_OPTION] = .OPT;         ! Store option byte in RB

    if (.OPT[BO_ENTITY_TYPE] neq NODE_E) ! Check for allowable entity
    and (.OPT[BO_ENTITY_TYPE] neq CIRCUIT_)
    then return $NICE$ERR_UFO;

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

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

    if .RTN_COD leq -1                  ! Check for valid entity id
    then return .RTN_COD;

    REQ[RB_NICE_ENTITY_TYPE] = NODE_E;  ! Parameters belong to node
    RTN_COD = VERIFY_PARAMETERS (SET_DEFINE, .REQ);
    REQ[RB_NICE_ENTITY_TYPE] = .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

    if NEXTB_NICE                       ! Process option byte if present
    then REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER])
    else return $NICE$ERR_IMF;

    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte
    REQ[RB_NICE_ENTITY_TYPE] = .OPT[TO_ENTITY_TYPE]; ! Get the entity type

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

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

    if .RTN_COD leq -1                  ! Check for valid entity id
    then return .RTN_COD;

    if .REQ[RB_NICE_ENTITY_TYPE] neq NODE_E ! 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 = .REQ[RB_NICE_ENTITY_TYPE]; ! Save entity type
         REQ[RB_NICE_ENTITY_TYPE] = NODE_E; ! Parameters are for NODE entity
	 RTN_COD = VERIFY_PARAMETERS (SET_DEFINE,.REQ); ! Process parameters
         REQ[RB_NICE_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 (REQ[RB_NICE_POINTER], .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 (REQ[RB_NICE_POINTER], .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 (REQ[RB_NICE_POINTER], .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

    if NEXTB_NICE
    then REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER])
    else return $NICE$ERR_IMF;

    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte
    REQ[RB_NICE_ENTITY_TYPE] = .OPT[CO_ENTITY_TYPE]; ! Get the entity type

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

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

    if .RTN_COD leq -1                  ! 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

    if NEXTB_NICE
    then REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER])
    else return $NICE$ERR_IMF;

    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte
    REQ[RB_NICE_ENTITY_TYPE] = .OPT[RO_ENTITY_TYPE]; ! Get the entity type

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

    if .OPT[RO_INFO_TYPE] gtru 4        ! Check for valid information type
    then return $NICE$ERR_UFO;

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

    if .RTN_COD leq -1                  ! 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

    if NEXTB_NICE                       ! Check for NICE option byte
    then REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER])
    else return $NICE$ERR_IMF;

    OPT = .REQ[RB_NICE_OPTION];         ! Get the option byte
    REQ[RB_NICE_ENTITY_TYPE] = .OPT[ZO_ENTITY_TYPE]; ! Get the entity type

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

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

    if .RTN_COD leq -1                  ! Check for valid entity id
    then return .RTN_COD;

    if .REQ[RB_NICE_ENTITY_TYPE] eql 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 NEXTB_NICE
    then REQ[RB_NICE_OPTION] = GETB (REQ[RB_NICE_POINTER])
    else return $NICE$ERR_IMF;

    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:
!
!	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
         FORMAT: $SIGNED_BYTE_VALUE;    ! Local signed entity id length

    !
    ! Get the entity format byte, checking for entity class case first.
    !

    if NEXTB_NICE                       ! Entity id in message?
    then begin                          ! Handle entity classes
         FORMAT = GETB (REQ[RB_NICE_POINTER]); ! Fetch format byte
         REQ[RB_NICE_ENTITY_ID_LENGTH] = .FORMAT[VALUE]; ! Get class or length
         if .FORMAT[VALUE] lss 0        ! Check for entity class, ACTIVE, 
         then begin                     ! KNOWN, or LOOP
              REQ[RB_NICE_ENTITY] = 0;  ! Null entity pointer
              return 1;                 ! Done if entity class
              end
         else begin                     ! Back up position so not counted twice
              REQ[RB_NICE_POSITION] = .REQ[RB_NICE_POSITION] - 1;
              ADVANCE (REQ[RB_NICE_POINTER], -1);
              end;
         end
    else return $NICE$ERR_IMF;

    !
    ! 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 .REQ[RB_NICE_ENTITY_TYPE] from NODE_E to MODULE_ of
        set
        [NODE_E]:
            begin
            if NEXTF_NICE               ! Is the id field present
            then begin
                 if .REQ[RB_NICE_LENGTH] geq .REQ[RB_NICE_POSITION]
                 then ADVANCE (REQ[RB_NICE_POINTER], 1)
                 else return $NICE$ERR_IMF; ! No room for image text
                 end
            else return $NICE$ERR_IMF;

            if .FORMAT[VALUE] eql 0
            then begin                  ! NODE address format
                 if not NEXTW_NICE
                 then return $NICE$ERR_IMF
                 else begin             ! Set pointer to id
                      REQ[RB_NICE_ENTITY] = .REQ[RB_NICE_POINTER];
                      ADVANCE (REQ[RB_NICE_POINTER], 2);
                      end;
                 end
            else if .FORMAT[VALUE] gtr 0
                 then begin             ! NODE name format, point to id
                      REQ[RB_NICE_ENTITY] = .REQ[RB_NICE_POINTER];
                      ADVANCE (REQ[RB_NICE_POINTER], .FORMAT[VALUE]);
                      end
                 else REQ[RB_NICE_ENTITY] = 0;
            end;

        [LINE_,
         CIRCUIT_,
         MODULE_]:
            begin
            if NEXTF_NICE               ! Is the id field present ?
            then begin
                 if .REQ[RB_NICE_LENGTH] geq .REQ[RB_NICE_POSITION]
                 then ADVANCE (REQ[RB_NICE_POINTER], 1)
                 else return $NICE$ERR_IMF; ! No room for image text
                 end
            else return $NICE$ERR_IMF;

            if .FORMAT[VALUE] gtr 0     ! Save pointer to id string,
            then begin                  ! including length as first byte
                 REQ[RB_NICE_ENTITY] = ch$plus (.REQ[RB_NICE_POINTER],-1);

                 ! Bump past the complete entity id.

                 ADVANCE (REQ[RB_NICE_POINTER], .FORMAT[VALUE]);
                 end
            else REQ[RB_NICE_ENTITY] = 0;
            end;

        [LOGGING_]:
            begin
            REQ[RB_NICE_ENTITY] = .REQ[RB_NICE_POINTER];
            if NEXTB_NICE
            then ADVANCE (REQ[RB_NICE_POINTER], 1) ! Bypass sink type
            else return $NICE$ERR_URC;
            end;

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

    return $TRUE;
    end;				! End of GET_ENTITY_ID
%routine ('SCAN_PARAMETER', ENTRY, REQ, CLEAR_PURGE) =

!++
! FUNCTIONAL DESCRIPTION:
!
!
! FORMAL PARAMETERS
!
!       ENTRY           Address of the entry to the parameter data base.
!	REQ             Address of NICE request block (RB).
!       CLEAR_PURGE     Flag to indicate if this request is a CLEAR/PURGE
!                       request message.
!
! 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,
       ENTRY: ref NICE_PARAMETER_TABLE_ENTRY;

    local
         PARAMETER: ref PARAMETER_ENTRY;

    PARAMETER = .ENTRY[NICE_PARAMETER_ENTRY]; ! Get data block entry

    ! Upon return if this parameter is a qualifier, the pointer stored
    ! in RB_NICE_QUALIFIER field points to the field of the qualifier
    ! parameter, STARTING WITH THE PARAMETER NUMBER.

    if .PARAMETER[_QUALIFIER]           ! Is this parameter a qualifier ?
    then begin                          ! Yes, check if we already got one
         if .REQ[RB_NICE_QUALIFIER] eql 0
         then REQ[RB_NICE_QUALIFIER] = ch$plus (.REQ[RB_NICE_POINTER], -2)
         else return $NICE$ERR_IPG;     ! Already got one, cannot handle second
         end;

    if .CLEAR_PURGE                     ! If this is CLEAR/PURGE NICE request
    and not .PARAMETER[_QUALIFIER]      ! and parameter is not a qualifier
    then return NICE$_SUC;              ! do not bother checking for data

    case .PARAMETER[_DATA_FORMAT] from DU1 to HX8 of
        set                             ! Parse and verify data format
        [DU1] :                         ! 1 byte field (C1)
            begin
            if NEXTB_NICE               ! Is there 1 byte to get ?
            then ADVANCE (REQ[RB_NICE_POINTER], 1) ! Yes
            else return $NICE$ERR_IMF;  ! No
            end;

        [DU2] :                         ! 2 byte field
            begin
            if NEXTW_NICE               ! Are there 2 bytes to get ?
            then ADVANCE (REQ[RB_NICE_POINTER], 2) ! Yes
            else return $NICE$ERR_IMF;  ! No
            end;

        [DU4] :                         ! 4 byte field (O4)
            begin
            if NEXTN_NICE (4)           ! Are there 4 bytes to get ?
            then ADVANCE (REQ[RB_NICE_POINTER], 4) ! Yes
            else return $NICE$ERR_IMF;  ! No
            end;

        [CM2] :                         ! Coded 2 2-byte field
            begin
            incr I from 0 to 1          ! Do it twice
            do if NEXTW_NICE            ! Are there 2 bytes to get ?
               then ADVANCE (REQ[RB_NICE_POINTER], 2) ! Yes
               else return $NICE$ERR_IMF; ! No
            end;

        [CMN,                           ! Coded node (address/name) field
         CMO] :                         ! Coded object (number/name) field
            begin
            if NEXTB_NICE               ! Is there a count byte to get ?
            then begin                  ! Yes
                 local LENGTH: $SIGNED_BYTE_VALUE;

                 LENGTH = GETB (REQ[RB_NICE_POINTER]);
                 if .LENGTH[VALUE] eql 0
                 then begin             ! Node address or Object number
                      if .PARAMETER[_DATA_FORMAT] eql CMN
                      then begin        ! Node address
                           if NEXTW_NICE ! Are there 2 bytes of node address ?
                           then ADVANCE (REQ[RB_NICE_POINTER], 2) ! Yes
                           else return $NICE$ERR_IMF; ! No
                           end
                      else begin        ! Object number
                           if NEXTB_NICE ! Is there 1 byte of object number ?
                           then ADVANCE (REQ[RB_NICE_POINTER], 1) ! Yes
                           else return $NICE$ERR_IMF; ! No
                           end;
                      end
                 else begin             ! Node name or Object name
                      if .LENGTH[VALUE] gtr 0
                      then begin
                           if NEXTN_NICE (.LENGTH[VALUE])
                           and .REQ[RB_NICE_LENGTH] geq .REQ[RB_NICE_POSITION]
                           then ADVANCE (REQ[RB_NICE_POINTER], .LENGTH[VALUE])
                           else return $NICE$ERR_IMF;
                           end
                      else if not .PARAMETER[_EVENTS] ! Is it KNOWN SINKS ?
                           then return $NICE$ERR_IMF; ! If not, return error
                      end;
                 end
            else return $NICE$ERR_IMF;  ! No
            end;

        [CMU] :                         ! Coded user/owner field
            begin
            if NEXTB_NICE               ! Is there an entity byte to get ?
            then begin                  ! Yes
                 local ENTITY, LENGTH: $SIGNED_BYTE_VALUE;

                 ENTITY = GETB (REQ[RB_NICE_POINTER]); ! Get entity byte

                 if NEXTB_NICE          ! Is there a count byte to get ?
                 then LENGTH = GETB (REQ[RB_NICE_POINTER]) ! Yes, get it
                 else return $NICE$ERR_IMF; ! No

                 if (.ENTITY eql NODE_E) and (.LENGTH[VALUE] eql 0)
                 then begin             ! Get node address
                      if NEXTW_NICE     ! Are there 2 bytes of address
                      then ADVANCE (REQ[RB_NICE_POINTER], 2) ! Yes
                      else return $NICE$ERR_IMF; ! No
                      end
                 else begin             ! Get entity id
                      if (.LENGTH[VALUE] gtr 0) ! Is the count positive ?
                      and NEXTN_NICE (.LENGTH[VALUE]) ! Does the field exist ?
                      and .REQ[RB_NICE_LENGTH] geq .REQ[RB_NICE_POSITION]
                      then ADVANCE (REQ[RB_NICE_POINTER], .LENGTH[VALUE]) ! Yes
                      else return $NICE$ERR_IMF; ! No
                      end;
                 end
            else return $NICE$ERR_IMF;  ! No
            end;

        [AI,                            ! ASCII image field
         HI] :                          ! Hexadecimal image field
            begin
            if NEXTB_NICE               ! Is there a count byte to get ?
            then begin                  ! Yes
                 local LENGTH: $SIGNED_BYTE_VALUE;

                 LENGTH = GETB (REQ[RB_NICE_POINTER]); ! Get count byte
                 if .LENGTH[VALUE] gtr 0 ! Is the count positive ?
                 then begin
                      if NEXTN_NICE (.LENGTH[VALUE]) ! Does the field exist ?
                      and (.REQ[RB_NICE_LENGTH] geq .REQ[RB_NICE_POSITION])
                      then ADVANCE (REQ[RB_NICE_POINTER], .LENGTH[VALUE]) ! Yes
                      else return $NICE$ERR_IMF; ! No
                      end
                 else begin
                      if .LENGTH[VALUE] eql 0
                      then return $NICE$ERR_IMF ! Null parameter id field
                      else begin        ! If parameter count byte is negative
                           if (.PARAMETER[_DATA_FORMAT] eql AI) ! Check if
                           and not .PARAMETER[_QUALIFIER] ! it is a qualifier
                           then return $NICE$ERR_UPT; ! If not, return error
                           end;         ! Otherwise, do nothing
                      end;              ! Already got the count byte
                 end
            else return $NICE$ERR_IMF;  ! No
            end;

        [HX8] :                         ! Hexadecimal 8 byte field
            begin
            if NEXTN_NICE (8)           ! Are there 8 bytes to get ?
            then ADVANCE (REQ[RB_NICE_POINTER], 8) ! Yes
            else return $NICE$ERR_IMF;  ! No
            end;

        [inrange,
         outrange] :
            return $NICE$ERR_UPT;
        tes;

    return $TRUE;
    end;                                ! End of SCAN_PARAMETER
%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

    local
         ENTITY,                        ! Entity type
         PARAMETER;                     ! NICE parameter number

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

    if (.ENTITY lss NODE_E) or (.ENTITY gtr MODULE_)
    then begin                          ! Illegal entity type
         REQ[RB_ERROR_DETAIL] = .REQ[RB_NICE_ENTITY_TYPE];
         return $NICE$ERR_URC;
         end;

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

    while NEXTW_NICE                    ! Process parameter
    do begin
       local CODE, ENTRY;

       PARAMETER = GETW (REQ[RB_NICE_POINTER]); ! Get parameter number
       if (ENTRY = NML$PARAMETER_LOOKUP (.ENTITY, .PARAMETER)) eql 0
       then return $NICE$ERR_UPT;       ! Cannot find parameter in tables

       if (CODE = SCAN_PARAMETER (.ENTRY, .REQ, .CLEAR_PURGE)) neq $TRUE
       then return .CODE;               ! Verify parameter data fields
       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;

    ! 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. 

    selectone .REQ[RB_NICE_ENTITY_TYPE] of
        set
        [NODE_E]:
            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
                      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]);
                      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;

        [LOGGING_]:                     ! No mapping for LOGGING entity
            0;

        [otherwise]:                    ! 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;
        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 = 256,       ! 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

    !
    ! 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];
        selectone .REQ[RB_NICE_ENTITY_TYPE] of
            set
            [NODE_E]:			! 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;

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

            [otherwise]:
                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;
            tes;
        end;

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