Google
 

Trailing-Edge - PDP-10 Archives - BB-P363B-SM_1985 - t20/nmlt20/nmlrcv.bli
There are 2 other files named nmlrcv.bli in the archive. Click here to see a list.
! UPD ID= 306, SNARK:<6.1.NML>NMLRCV.BLI.6,  29-Apr-85 20:02:28 by GLINDELL
!   NCP$SEND_RESPONSE now has one more argument - add that to call.
!
! UPD ID= 252, SNARK:<6.1.NML>NMLRCV.BLI.5,   7-Feb-85 16:13:38 by GLINDELL
!  Fix a bug: the NML receiver would shut down a link after 60 seconds
!  without reading anything from it.  Howver, we may be writing on the
!  link.  Add flag PB_IN_USE to parameter block.

! UPD ID= 48, SNARK:<6.1.NML>NMLRCV.BLI.4,  29-May-84 17:31:01 by GLINDELL
! Always allow remote READ access
!
! UPD ID= 42, SNARK:<6.1.NML>NMLRCV.BLI.2,  24-May-84 16:32:41 by GLINDELL
! PH4:<HALPIN>NMLRCV.BLI.3 16-Feb-84 09:18:40, Edit by HALPIN
!
! Ident 15.
!   Send a NETWORK_REJECT when NMU$NETWORK_VALIDATE returns $false
!
!DSKC:NMLRCV.BLI[10,5665,SOURCE,TOPS10]  9-Oct-83 15:14:17, Edit by GROSSMAN
!
! Fix WAIT_FOR_CONNECT so that it resets the connect block correctly when 
! rejecting a connection.  This keeps NML from looping.
!
!<MCINTEE>NMLRCV.BLI.2,  5-Jul-83 12:10:28, Edit by MCINTEE
!
! Ident 14.
!   add use of debug flag NML_REMOTE_REQUEST
!
!<MCINTEE.WORK>NMLRCV.BLI.2, 15-Jun-83 13:08:53, Edit by MCINTEE
! 
! Ident 13.
!  Dot bug in CHECK_VERSION
!
! PH4:<PECKHAM>NMLRCV.BLI.6 13-Jun-83 15:07:08, Edit by PECKHAM
!
! Ident 12.
!   Fix CHECK_VERSION to return the remote version number in PB_VERSION,
!   and use NML$CNV_CHECK_VERSION to check if supported.  Store this version
!   number in the generated request blocks in READ_NICE_REQUESTS.  Use the
!   request block version number in DEQUEUE_REQUEST to translate responses
!   where necessary.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCV.BLI.8 25-Jun-82 19:43:17, Edit by PECKHAM
!
! Ident 11.
! Reduce NICE_BUFFER_LENGTH from 500 to 300 bytes.
! Define a parameter block so that access control can be passed from
! WAIT_FOR_CONNECT to READ_NICE_REQUEST (also good for code optimization). 
! Optimize linkages.
!
! NET:<PECKHAM.DEVELOPMENT>NMLRCV.BLI.3 23-Jun-82 11:04:21, Edit by PECKHAM
!
! Ident 10.
! Merge QUEUE_REQUEST into READ_NICE_REQUEST so that request block
! can be handled there.
! Set privledged bits on for now, later user info will be checked.
! Fix DEQUEUE_REQUEST to conditionally release memory from request block.
!
! <BRANDT.DEVELOPMENT>NMLRCV.BLI.2 7-Jun-82 11:21:45, Edit by BRANDT
!
! Ident 09.
!   1) In DEQUEUE_RESPONSE release memory allocated for node_id
!      in the request block.  Before this edit, this memory was
!      released in NML$NICE_EXECUTE.  Doing so allowed the memory to
!      be reallocated while still being referenced as a node_id.
!
! NET:<VOBA.NML.DEVELOPMENT>NMLRCV.BLI.3 30-Mar-82 10:48:02, Edit by VOBA
!
! Ident 08.
! Update copyright date and clean up code.
!
!NET:<DECNET20-V3P1.BASELEVEL-2.SOURCES>NMLRCV.BLI.21 20-Nov-81 13:39:24, Edit by WEBBER
!
! Ident 07.
! Fix ident 06 to use only addresses, not pointers, in memory gets and
! retrieves.
!
!NET:<DECNET20-V3P1.NML>NMLRCV.BLI.2 21-Oct-81 09:49:14, Edit by WEBBER
!
! Ident 06.
! Add response buffer and its length as parameters to NETWORK_OPEN.
!
! NET:<DECNET20-V3P1.BASELEVEL-2.SOURCES>NMLRCV.BLI.18  2-Oct-81 17:42:49, Edit by GUNN
!
! Ident 05.
! Fix typo in code returning $NICE$ERR_IID response code.
!
! NET:<DECNET20-V3P1.BASELEVEL-2.SOURCES>NMLRCV.BLI.15 12-Aug-81 12:52:01, Edit by JENNESS
!   
! Ident 04.
! Fix CHECK_VERSION to properly use the CB_DATA pointer as a pointer
! not as the address of the data buffer.
!
! NET:<DECNET20-V3P1.NML>NMLRCV.BLI.2  1-Jun-81 15:14:49, Edit by GUNN
!
! Ident 03.
! Fix problem preventing completion of SHOW KNOWN xxx command to a
! remote node. Make DEQUEUE_RESPONSE not release RB until the command
! processing is complete as indicated by RB_STATE.
!
! NET:<DECNET20-V3P1.NML>NMLRCV.BLI.3  3-Mar-81 16:25:05, Edit by GUNN
!
! Remove references to RB_NICE_SIZE and RB_DATA_SIZE and replace with
! RB_aaa_ALLOCATION field references.
!
! NET:<DECNET20-V3P1.NMU>NMLRCV.BLI.5  3-Feb-81 10:04:32, Edit by JENNESS
!    Remove literal definition for NICE_OBJECT (now in NMARCH).
!    Remove DEBUG logical link descriptor (NMUNET now creates user name
!	descriptor if .135 neq 0).
!    Fix access control validation to work properly.  NMU$NETWORK_VALIDATE
!	returns $true/$false instead of 0/not 0.
!    Add error code for 'ACCESS NOT PERMITTED' on connect reject (SC$_ANP).
!
%title 'NMLRCV -- NICE Remote Message Receiver'
module NMLRCV	(
		ident = 'X03.15'
		) =
begin

!                     COPYRIGHT (c) 1981, 1982 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 performs the NML NICE remote request receive function.
!
! ENVIRONMENT:	TOPS-10/20 & MCB/RSX11 User mode under NML
!
! AUTHOR: Dale C. Gunn , CREATION DATE: 20-Jan-81
!
! MODIFIED BY:
!
!	, : VERSION
! 01	-
!--
!
! INCLUDE FILES:
!

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

!
! TABLE OF CONTENTS
!

%if %bliss (bliss16)
%then linkage NML_LKG_PB = jsr (register = 5);
%else macro NML_LKG_PB = bliss36c %;
%fi

forward routine
        NML$RECEIVE_NICE : novalue;

forward routine
	SET_ACCESS_PRIVS: novalue,	! Set privs from NM$NETWORK_OPEN access code
        WAIT_FOR_CONNECT : NML_LKG_PB,  ! Wait for connection to target task
        CHECK_VERSION : NML_LKG_PB,     ! Validate network management version
        READ_NICE_REQUEST : NML_LKG_PB novalue, ! Read a NICE request message
        DEQUEUE_REQUEST : novalue;      ! Remove completed request from queue

!
! MACROS:
!

!
! EQUATED SYMBOLS:
!

literal
       NICE_BUFFER_LENGTH = 300,        ! NICE request buffer length in bytes
       NICE_BUFFER_SIZE = ch$allocation (NICE_BUFFER_LENGTH,8), ! In words
       NICE_BUFFER_ALLOCATION = NICE_BUFFER_SIZE * %upval; ! In addr units

!
! Parameter Block
!

$show (fields);                         ! Turn on XPORT field display
$show (literals);                       ! Turn on XPORT literal display

$field
    PARAMETER_FIELDS =
        set
        PB_BASE = [$sub_block (0)],
        PB_LINK_HANDLE = [$short_integer],
        PB_CBLK = [$address],
        PB_OPTD_PTR = [$pointer],
        PB_OPTD_CNT = [$short_integer],
        PB_VERSION = [$short_integer],
        PB_ACCESS = [$tiny_integer],
        PB_OBJECT = [$byte],
        PB_IN_USE = [$bits(1)]
        tes;

literal
    PARAMETER_BLOCK_SIZE = $field_set_size,
    PARAMETER_BLOCK_ALLOCATION = $field_set_units;

macro
     PARAMETER_BLOCK = block [PARAMETER_BLOCK_SIZE] field (PARAMETER_FIELDS) %;

$show (none);                           ! Turn off XPORT display

!
! OWN STORAGE:
!

own
    BUGPID;				! Poked for use by debug flag NML_REMOTE_REQUEST

!
! EXTERNAL REFERENCES:
!


external routine
	 NCP$SEND_RESPONSE,
         NML$CNV_CHECK_VERSION,
         NML$CNV_RESPONSE,
	 PUTBUF,
  	 NMU$PAGE_GET,
	 NMU$PAGE_RELEASE,
         NMU$NETWORK_UTILITIES;

external
        NMLVER,                         ! Network Managment version number
        DECECO,                         ! Digital ECO number
        USRECO;                         ! User ECO number

external %debug_data_base;		! Debugging flags used in this module
%global_routine ('NML$RECEIVE_NICE', TASK, RESOURCE) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!	This routine is the top level of the Network Management
!	NICE request listener. The listener is responsible for
!       accepting connections from remote NMLs, verifying their
!       privilege to perform NM functions based on access control
!       information provided with the connection.
!
! FORMAL PARAMETERS
!
!	TASK	 - Address of task block for this task
!	RESOURCE - Address of cell for this task to use as
!                  a resource variable.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    local
         PB : ref PARAMETER_BLOCK,
         PBA,
         BUFFER_PTR,                    ! Pointer to acceptance data buffer
         BUFFER : ch$sequence (3,8);    ! Acceptance data buffer, NM Version

!
! Allocate a parameter block
!
    if (PB = NMU$MEMORY_GET (PARAMETER_BLOCK_ALLOCATION)) eql 0 then return;

!
! Put our Network Management version number into the buffer
! to send as the optional data on a link connect acceptance.
!

    PB [PB_OBJECT] = NICE_OBJECT;
    PB [PB_OPTD_PTR] = ch$ptr (BUFFER,, 8);
    BUFFER_PTR = .PB [PB_OPTD_PTR];     ! Point to connect accept buffer
    PUTB (.NMLVER, BUFFER_PTR);         ! Store NM major version
    PUTB (.DECECO, BUFFER_PTR);         ! Store our minor (ECO) version
    PUTB (.USRECO, BUFFER_PTR);         ! Store customer ECO number
    PB [PB_OPTD_CNT] = ch$diff (.BUFFER_PTR, .PB [PB_OPTD_PTR]);

!
! Loop forever, wait for link connected, read requests until disconnected.
!

    PBA = PB [PB_BASE];                 ! For BLISS-16 optimization

    while $TRUE
    do begin
       WAIT_FOR_CONNECT (.PBA);
       READ_NICE_REQUEST (.PBA);
       NMU$NETWORK_CLOSE (.PB [PB_LINK_HANDLE], 0, 0);
       end;

    end;				! End of NML$RECEIVE_NICE
%routine ('WAIT_FOR_CONNECT', PB : ref PARAMETER_BLOCK) : NML_LKG_PB =

!++
! FUNCTIONAL DESCRIPTION:
!
!	This routine opens a target link for connection by
!	another task.  When a connect is attempted the user
!	access rights are checked and the source task's version
!	number is checked.  If all checks are ok, then the
!	link is accepted (sending the optional acceptance data)
!	and the LINK_ID is returned.  If any check fails,
!	a reject is sent with the appropriate error code.
!
! FORMAL PARAMETERS
!
!	PB - Parameter block
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	The LINK_ID of the opened link.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    local
         CBLK: CONNECT_BLOCK,           ! Link connection block
         REASON;                        ! Link rejection reason

    while $true                         ! Loop until the link is connected
    do begin

!
! Set the object code and clear the task name and descriptor.
!

       PB [PB_CBLK] = CBLK;
       CBLK[CB_OBJECT] = .PB [PB_OBJECT];
       CBLK[CB_TASK_LENGTH] = 0;
       CBLK[CB_DESCRIPTOR_LENGTH] = 0;
       CBLK[CB_HOST_LENGTH] = 0;
       CBLK[CB_USERID_LENGTH] = 0;
       CBLK[CB_PASSWORD_LENGTH] = 0;
       CBLK[CB_ACCOUNT_LENGTH] = 0;
       CBLK[CB_DATA_LENGTH] = 0;

       REASON = 0;
       PB [PB_LINK_HANDLE] = NMU$NETWORK_OPEN (TARGET_LINK, CBLK, 0, 0, 0);

!
! Check for user access and version number ok
!

	if (.PB [PB_LINK_HANDLE] gtr 0)
        and ((REASON = CHECK_VERSION (PB [PB_BASE])) eql 0)
        and ((PB [PB_ACCESS] = NMU$NETWORK_VALIDATE (CBLK)) geq 0)
	then begin
             NMU$NETWORK_ACCEPT (.PB [PB_LINK_HANDLE], .PB [PB_OPTD_CNT], .PB [PB_OPTD_PTR]);
             exitloop;
             end
	else begin
             local REJECT_BUFFER;
             ch$wchar (.REASON, ch$ptr (REJECT_BUFFER,,8));
             NMU$NETWORK_REJECT (.PB [PB_LINK_HANDLE],
                                 SC$_ANP,
                                 1,
                                 ch$ptr (REJECT_BUFFER,,8));
             NMU$NETWORK_CLOSE (.PB [PB_LINK_HANDLE], 0, 0);
             end;
	end;
!
! Return handle (id) of link that was opened and accepted.
!

    return .PB [PB_LINK_HANDLE];
    end;				! End of WAIT_FOR_CONNECT
%routine ('CHECK_VERSION', PB : ref PARAMETER_BLOCK) : NML_LKG_PB =

!++
! FUNCTIONAL DESCRIPTION:
!
!	This routine checks to see if the Network Management
!	version match.  If they don't, an error code is returned.
!
! FORMAL PARAMETERS
!
!	PB - Parameter block
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	Zero if ok, a non-zero error code if failed test
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    bind
       CBLK = .PB [PB_CBLK] : CONNECT_BLOCK;

    local
         VERSION;

    selectone .CBLK[CB_DATA_LENGTH] of
        set
        [0] : VERSION = 2;              ! Default to 2
        [3] : VERSION = ch$rchar (.CBLK[CB_DATA]);
        [otherwise] : return $NICE$ERR_IID; ! Is this the right code to return?
        tes;

    PB [PB_VERSION] = .VERSION;

    if not NML$CNV_CHECK_VERSION (.VERSION)
    then $NICE$ERR_IMV
    else 0
    end;				! End of CHECK_VERSION
%routine ('READ_NICE_REQUEST', PB : ref PARAMETER_BLOCK) : NML_LKG_PB novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!	This routine performs the NICE request receive function on 
!	a logical link that has already been opened. The looping 
!	continues until the task at the other end of the link closes 
!	it (or some other nefarious glitch takes it down).
!
! FORMAL PARAMETERS
!
!	PB - Parameter block
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    while $true                         ! Loop through reading NICE requests
    do begin                            ! as long as link stays up.

       literal
           TEXT_BUFFER_LENGTH = 80;	! A line's worth.

       local
           BYTE_COUNT,                  ! Received NICE request message length
           REQ : ref REQUEST_BLOCK;

       !
       ! Allocate storage for NICE request block
       !

       REQ = NMU$MEMORY_GET (REQUEST_BLOCK_ALLOCATION);
       REQ[RB_EXECUTOR] = 0;            ! Initialize to process locally
       REQ[RB_DATA] = .PB;               ! Save PB address
       REQ[RB_DATA_ALLOCATION] = 0;     ! No block allocated

       REQ[RB_VERSION] = .PB [PB_VERSION];

       SET_ACCESS_PRIVS (.PB [PB_ACCESS], .REQ); ! Set up privileges

       ! Get a buffer for the NICE message and store its address

       REQ[RB_NICE_ALLOCATION] = NICE_BUFFER_ALLOCATION; ! Units allocated
       REQ[RB_NICE] = NMU$MEMORY_GET (.REQ[RB_NICE_ALLOCATION]);
       REQ[RB_NICE_POINTER] = ch$ptr (.REQ[RB_NICE],0,8);

       ! Attempt to read a NICE request message

       PB[PB_IN_USE] = $false;          ! Clear used flag
       BYTE_COUNT = NMU$NETWORK_READ (.PB [PB_LINK_HANDLE],
                                      NICE_BUFFER_LENGTH,
                                      .REQ[RB_NICE_POINTER]);

       ! Check if we received a message, or read completed for some
       ! other reason. (Maybe the link was disconnected.)

       if .BYTE_COUNT gtr 0             ! Put the NICE request on the queue
       then begin                       ! to be processed.
            REQ[RB_NICE_LENGTH] = .BYTE_COUNT;
            REQ[RB_COMPLETION] = DEQUEUE_REQUEST; ! Completion routine

            !
            ! Enter the request into the NICE request queue.
            !

            NML$REQUEST_ENTER (.REQ);   ! Enter request in queue
	    %debug (NML_REMOTE_REQUEST, ! Print the content of the NICE
                   (begin               ! message buffer as an ASCII text
                    builtin LSH;
                    local PAGE, PTR, TMP;
                    
                    PAGE = NMU$PAGE_GET ();
                    PTR = TMP = ch$ptr (LSH (.PAGE,9));
                    $NMU$TEXT (TMP, TEXT_BUFFER_LENGTH,
                               '%/[NICE Remote Request Message]%/%N');
                    PUTBUF (TMP, 0, .REQ [RB_NICE], .REQ [RB_NICE_LENGTH]);
                    NCP$SEND_RESPONSE (0, .PTR, .BUGPID, 0);
                    NMU$PAGE_RELEASE (.PAGE);
                    end));

	    end
       else begin
            ! See if timeout and we are using link (long response)
            if not ((.BYTE_COUNT eql -1) and (.PB[PB_IN_USE]))
            then begin
                 
                 ! The link has been disconnected. Release the NICE buffer and
                 ! and and indicate no longer connected.
                 
                 REQ[RB_STATE] = RB$DONE;
                 DEQUEUE_REQUEST (.REQ);
                 exitloop;
                 end;
            end;
       end;

    end;				! End of READ_NICE_REQUEST
%routine ('SET_ACCESS_PRIVS', ACCESS, REQ: ref REQUEST_BLOCK): novalue =

!++
! Functional description:
!
!	This routine converts the access code from NMU$NETWORK_OPEN
!	into a set of privilege bits in the request block.
!
! Formal parameters:
!
!	ACCESS		Access code from NMU$NETWORK_OPEN
!			-2 if JSYS or UUO error
!			-1 if invalid access information
!			 0 if unprivileged user
!			 1 if WHEEL (POKE) privileged user
!			 2 if OPERATOR privileged user
!	REQ		Request block address
!
! Routine value:
!
!	None
!--

begin

    REQ [RB_PRV_READ] = (.ACCESS geq 0);
    REQ [RB_PRV_CHANGE] = (.ACCESS geq 1);
    REQ [RB_PRV_SYSTEM] = (.ACCESS geq 1);
    REQ [RB_PRV_SERVICE] = (.ACCESS geq 2);
    REQ [RB_PRV_TEST] = (.ACCESS geq 2);

end;
%routine ('DEQUEUE_REQUEST', REQ) : novalue =

!++
! FUNCTIONAL DESCRIPTION:
!
!	This routine handles the completion processing of remote NICE
!       requests when called by the NML request queue manager. It transmits
!       the NICE repsonse message back to the requestor and releases
!       all resources obtained when the request was created.
!
! FORMAL PARAMETERS
!
!	REQ - Address of the NML Request Block.
!
! IMPLICIT INPUTS
!
!	NONE.
!
! ROUTINE VALUE:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    begin

    map
       REQ: ref REQUEST_BLOCK;

    local
       PB : ref PARAMETER_BLOCK;

    if .REQ[RB_RESPONSE] neq 0
    then begin

         !
         ! Translate response message where necessary.
         !

         NML$CNV_RESPONSE (.REQ);

         !
         ! Attempt to transmit the NICE response message back to requestor.
         !

         PB = .REQ[RB_DATA];            ! Get PB address
         NMU$NETWORK_WRITE (.PB[PB_LINK_HANDLE], ! Link ID
                            $TRUE,      ! Complete message
                            .REQ[RB_RESPONSE_LENGTH], ! Message length in bytes
                            ch$ptr (.REQ[RB_RESPONSE],,8)); ! NICE response pointer
         PB[PB_IN_USE] = $true;         ! Using PB block
         end;

    !
    ! Release all memory resources when done.
    !

    if .REQ[RB_STATE] eql RB$DONE
    then begin
	 if .REQ[RB_NICE_ENTITY_ADR] neq 0 ! Release node id buffer
	 then NMU$MEMORY_RELEASE (.REQ[RB_NICE_ENTITY_ADR],
				  NODE_ID_BUFFER_ALLOCATION);
         if .REQ[RB_NICE] neq 0
         then NMU$MEMORY_RELEASE (.REQ[RB_NICE], .REQ[RB_NICE_ALLOCATION]);
         if .REQ[RB_RESPONSE] neq 0
         then NMU$MEMORY_RELEASE (.REQ[RB_RESPONSE], .REQ[RB_RESPONSE_ALLOCATION]);
         NMU$MEMORY_RELEASE (.REQ, REQUEST_BLOCK_ALLOCATION);
         end;

    end;				! End of DEQUEUE_REQUEST
end                                     ! End of Module NMLRCV
eludom
! Local Modes:
! Mode:BLISS
! Auto Save Mode:2
! Comment Column:40
! Comment Rounding:+1
! End: