Google
 

Trailing-Edge - PDP-10 Archives - BB-R595B-SM_11-9-85 - mcb/sc/scdsp.bli
There is 1 other file named scdsp.bli in the archive. Click here to see a list.
module SCDSP (			! CCB-Level Dispatching and Initialization
		ident = 'X01500'
		) =
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:	Session Control
!
! ABSTRACT:	This is the top level module in the MCB implementation
!		of Session Control.  It is through this module that all
!		CCBs are dispatched to the appropriate processing
!		routines.  Additionally, SC initialization is performed
!		within this module.
!
! ENVIRONMENT:	MCB
!
! AUTHOR:	Buren Hoffman		CREATION DATE: 2-Apr-80
!
! MODIFIED BY:
!	X01010	Fixed NM turn on of SC to wait until NSP has returned
!		the necessary results for SC to really be on.
!	X01020	Changed code to use $byt_ptr macro in place of the
!		ch$ptr macro.
!	X01030	Corrected mapping bug in FCRCP.
!	X01040	Fixed linkage mismatches to called external routines.
!	X01050	Added more state checking in accept/reject completion
!		handling.
!	X01060	Fixed dot bug in connect-rejection processing.
!	X01070	Corrected mapping bug in FCXCP.
!	X01080	Simple formatting changes to make code read easier.
!	X01090	Fixed dot bug in timeout handling.
!	X01100	Moved Port-Open code to routine I$CLS in SCSUB - removed
!		it from the timeout routine in this module.
!	X01110	Modified dispatch table definition to use the TABLE$ macro.
!	X01120	Fixed logic error in FCRCE - nonexistent ccb was being
!		released.
!	X01130	Fixed resource-release problem in connect-complete processing.
!		LDB was being released as an CCB.
!	X01140	Fixed connect-received processing to not forward data length
!		to user as part of data.
!	X01150	LIX was being retrieved from wrong CCB in FCRCE.
!	X01160	Removed redundant code in connect-received processing.
!	X01170	Fix in abort processing to cause processing of right lnk.
!	X01180	Dot bug fix in NR$CST
!	X01190	Set reject reason correctly on reject
!	X01200	Wrong state checking in NX$REJ fixed
!	X01210	Fixed code to prevent two rejects on one link
!	X01220	Fix to assure proper optional data format is generated
!	X01230	Improved documentation, and added info on SIGNAL_STOPs
!	X01240	Fixed completion of nonexistent CCB in reject code.
!	X01250	Removed network management stuff to its own module.
!	X01260	Made NM module an extension process.
!	X01270	Code cleanup, and status code reporting fixes.
!	X01280	Use new Comm/Exec to process linkage (.CRDAT for database)
!	X01290	Fixed state checking in NX$BUF, NX$DRQ, ..., to accept
!		ST_DIR state.
!	X01300	Changed GET-LOCAL-NODE-INFO to also be able to return
!		node addr / node name information.  Changed data-received
!		processing to give (beginning-of-message), (middle-of-message),
!		and (end-of-message) indications to the user.
!	X01310	Updated to use library calls, instead of requires.
!	X01320	Fixed bug in link selection in abort handling code.
!		Also, put call to I$OPN in connect received code.
!	X01330	Changed SC's state codes to correspond to NM's code numbers.
!	X01340	Fixed race between CNR and DSR.
!	X01350	More fix for above race.
!	X01360	Fixed length check for GLN function
!	X01370	Repaired info copy length in GLN.
!	X01380	Fixed state checking in SR$DAT and SR$INT to allow
!		ST_DIR state.
!	X01390	Modified connect-received processing to cause PIX-to-link
!		binding to be performed when the received connect is
!		acknowledged.
!	X01400	Changed Confidence-received call to be processed like a
!		disconnect-received, with status code of S_ENUR. This
!		change allows the task or process to synchronize with
!		the vanishing link - instead of being surprised when it
!		finds it gone.
!	X01410	Additional state check in XCP of disconnect complete from
!		NSP.
!	X01420	Implemented "paranoid" conditional assembly, and cleaned
!		up node-name location.
!	X01430	Upgraded to use new long timer capability.
!	X01440	User PIX was not being set for outgoing connects.
!	X01450	Optimization work.
!	X01460	Fixed CCB completion for NX$INI to do CCP.
!	X01470	Added Host-Node-ID processing capability.
!	x01480  Use DSR space instead of LDB's for connect info
!	x01490	add some in NX$CLS
!       x01500  Fix a race condition in FCXCP (patch around it actually).
!
!--
!
! REQUIRED FILES
!
library 'SCPRM';		! Our parameter and macro definitions
library 'MCB:MCBLIB';
library 'MCB:RSXLIB';
library 'MCB:NMXLIB';
library 'MCB:XPORTX';
library 'MCB:SCSYS';

require 'NSP:NSINFO';


!
! TABLE OF CONTENTS:
!
forward routine
    FCCTL: mcb_db_ccb_mod novalue,	! Control function
    FCRCE: mcb_db_ccb_mod novalue,	! Receive enable
    FCRCP: mcb_db_ccb_mod novalue,	! Receive complete
    FCTMO: mcb_db_ccb_mod novalue,	! Timeout
    FCXCP: mcb_db_ccb_mod novalue,	! Transmit complete
    FCXME: mcb_db_ccb_mod novalue;	! Transmit enable

!
! MACROS:
!
macro
    RAD50 (STR) =
    %if %bliss (bliss36) %then %rad50_10 STR %else %rad50_11 STR %fi %;

!
! EQUATED SYMBOLS:
!

!
! OWN STORAGE:
!
!
! EXTERNAL REFERENCES:
!
external
    $DSPCR;

external routine 		! BLISS Routines
    FINDLL,			! Find a logical link
    FINDND,			! Determine node address

    STSMAP,			! Map NSP status to SC status

    I$CLS: novalue,		! Close
    I$OPN: novalue,		! Open

    NR$CRW: novalue,		! Connect Received
    NR$DTW: novalue,		! Data Received
    NR$DRW: novalue,		! Disconnect Received
    NR$INW: novalue,		! Interrupt Received

    SX$ABW: novalue,		! Abort
    SX$ACW: novalue,		! Accept
    SX$CNW: novalue,		! Connect
    SX$DRW: novalue,		! Data Segment Request
    SX$IRW: novalue,		! Interrupt Request
    SX$RJW: novalue,		! Reject
    SX$SDW: novalue,		! Data Transmit
    SX$SIW: novalue;		! Interrupt Transmit
!+
!
! *** SESSION CONTROL DISPATCH VECTOR ***
!
! This vector is the route via which the MCB
! dispatches CCBs to Session Control.
!
!-

global bind
    $SCLL = TABLE$ ($DSPCR, FC_CCP,
	(FC_XME, FCXME),	! Transmit enable
	(FC_XCP, FCXCP),	! Transmit complete
	(FC_RCE, FCRCE),	! Receive enable
	(FC_RCP, FCRCP),	! Receive complete
	(FC_CTL, FCCTL),	! Control
	(FC_TIM, FCTMO)),	! Timeout


    RCPWT = TABLE$ ($DSPCR, N_RHI,
	(N_SCNF, NR$DRW),	! Confidence (treat as disc rcv'd)
	(N_RCON, NR$CRW),	! Connect received
	(N_RDSC, NR$DRW),	! Disconnect received
	(N_RDAT, NR$DTW),	! Data received
	(N_RINT, NR$INW)),	! Interrupt received

    XMEWT = TABLE$ ($DSPCR, S$XHI,
	(S$CON, SX$CNW),	! Connect
	(S$ACC, SX$ACW),	! Accept connect
	(S$REJ, SX$RJW),	! Reject connect
	(S$SND, SX$SDW),	! Transmit data
	(S$MRQ, SX$DRW),	! Data message request (SX$MRW)
	(S$DRQ, SX$DRW),	! Data segment request
	(S$SNI, SX$SIW),	! Transmit interrupt data
	(S$IRQ, SX$IRW),	! Interrupt data request
	(S$DIS, SX$ABW),	! Disconnect (SX$DSW)
	(S$ABO, SX$ABW));	! Abort
%sbttl 'Control Enable From Network Management'
routine FCCTL (SCDB, CCB, FCM): mcb_db_ccb_mod novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine is activated by receipt of a Control
!	Enable from Network Management.
!
!
! FORMAL PARAMETERS:
!	CCB	CCB to pass to handler routine
!	FCM	Function code modifier
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    $sc_get_data_base (SCDB);
    map CCB: ref block field (C_FIELDS);

    CALL$E (NM_EXT, .SCDB [SC_SNPIX], .CCB)
    end;
%sbttl 'Receive Complete From NSP'
routine FCRCP (SCDB, CCB, FCM): mcb_db_ccb_mod novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine is activated by receipt of a receive
!	complete CCB from NSP.
!
!
! FORMAL PARAMETERS:
!	CCB	CCB to pass to handler routine
!	FCM	Function code modifier
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    $sc_get_data_base (SCDB);
    map	CCB: ref block field (C_FIELDS);
    local
	LNK: ref block field (LLT_FIELDS),
	LCCB: ref block field (C_FIELDS),
	STATUS;
    bind
	LLT = SCDB [SC_LLT_ADDR]: ref blockvector [,L_SIZE] field (LLT_FIELDS),
	PIV = LLT [.SCDB [SC_LINKS], L_TOP]: byte_vector;

    MAP$ (.SCDB [SC_LLT_BIAS]);
    LNK = LLT [.PIV [.CCB [C_LIX]], L_TOP];


    case .FCM^-1 from 0 to N_RHI^-1 of
	set



	! ************
	! ** NR$CNR **
	! ************
	[N_RCON^-1]:
	    begin
	    %if paranoid %then
		if .LNK [L_STATE] neq ST_OPN
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    CMQIF$ (LNK [L_IQUE], .CCB);
	    LNK [L_STATE] = ST_CR;
	    LNK [L_RNA] = .CCB [C_PRM1];
	    SCDB [SC_IPORT] = .SCDB [SC_IPORT] - 1;	! We used up a port
	    I$OPN ()					! Try to replace it
	    end;



	! ************
	! ** NR$CST **
	! ************
	[N_SCNS^-1]:
	    begin
	    if .LNK [L_STATE] eql ST_CID		! Conn-Init-Delivered ?
	    then
		begin					! Yes !
		local
		    CNT,
		    PTR;
		CMQRM$ (LNK [L_OQUE], LCCB);		! Take user CCB off que
		LNK [L_TIMER] = 0;			! Disable timer
		if .CCB [C_STS] eql N$SACC		! Link accepted ?
		then LNK [L_STATE] = ST_RUN		! Yes, go to RUN state
		else I$CLS (.LNK);			! No, so close the port
		MAP$ (.CCB [C_BIAS]);			! Set to copy conn data
		if (CNT = .CCB [C_CNT] - 1) lss 0 then CNT = 0;
		LCCB [C_PRM4] = min (.LCCB [C_PRM4], .CNT);
		PTR = ch$plus (.CCB [C_ADDR], 1);
		MTBF$S (.LCCB [C_PRM4], .PTR, .LCCB [C_PRM2], .LCCB [C_PRM3]);
		$SC_DO_XCP (.LCCB, STSMAP (.CCB [C_STS])) ! Complete to user
		end;

		$SC_DO_RCE (.CCB);			! Return NSP's buffer
	    return
	    end;



	! *********************
	! ** NR$DAT & NR$INT **
	! *********************
	[N_RDAT^-1, N_RINT^-1]:
	    begin
	    if not (
		(.LNK [L_STATE] eql ST_RUN) or
		(.LNK [L_STATE] eql ST_DI))
	    then $SC_DO_RCE (.CCB)
	    else
		begin
		if .FCM eql N_RDAT
		then CMQIN$ (LNK [L_IQUE], .CCB)
		else CMQIF$ (LNK [L_IQUE], .CCB)
		end
	    end;



	! *********************
	! ** NR$CNF & NR$DSR **
	! *********************
	[N_SCNF^-1, N_RDSC^-1]:
	    begin
	    %if paranoid %then
		if (.LNK [L_STATE] eql ST_OFF) or
		   (.LNK [L_STATE] eql ST_OI) or
		   (.LNK [L_STATE] eql ST_OPN)
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    LNK [L_STS] = (if .FCM eql N_SCNF then S_EABL else S_EABS);
	    if	(.LNK [L_STATE] eql ST_CIS) or
		(.LNK [L_STATE] eql ST_CLI) or
		(.LNK [L_STATE] eql ST_ABI) or
		(.LNK [L_PIX] eql 0)		! CNR was rcv'dfor no-such obj
	    then
		begin
		$SC_DO_RCE (.CCB);
		I$CLS (.LNK);
		return
		end;

	    while CMQRM$ (LNK [L_IQUE], LCCB) do $SC_DO_RCE (.LCCB);
	    CMQIF$ (LNK [L_IQUE], .CCB)
	    end;



	! ************
	! ** NR$ERR **
	! ************
	[inrange, outrange]:
	    %if paranoid %then
		SIGNAL_STOP (SC$_ISC, .CCB)
	    %fi;
	tes;

    $SC_DISPATCH_INPUT (LNK [L_IQUE])
    end;
%sbttl 'Receive Enable From User'
routine FCRCE (SCDB, CCB, FCM): mcb_db_ccb_mod novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine is activated by a receive enable from
!	a System Interface user.
!
! FORMAL PARAMETERS:
!	CCB	CCB being returned
!	FCM	Function code modifier
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    $sc_get_data_base (SCDB);
    map	CCB: ref block field (C_FIELDS);
    local
	LCCB: ref block field (C_FIELDS),
	LNK: ref block field (LLT_FIELDS);
    bind
	LLT = SCDB [SC_LLT_ADDR]: ref blockvector [,L_SIZE] field (LLT_FIELDS);

    MAP$ (.SCDB [SC_LLT_BIAS]);
    LNK = LLT [.CCB [C_LIX], L_TOP];
    LCCB = .CCB [C_STK];

    case .FCM^-1 from 0 to S$RHI^-1 of
	set


	! ************
	! ** SR$CNR **
	! ************
	[S$CNR^-1]:
	    begin
	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_CR) or
		    (.LNK [L_STATE] eql ST_CLI))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    $MCB_RETURN_DSR (CB_SIZE*bytes_word, .CCB [C_ADDR]);
							! Release CB memory
	    LNK [L_TIMER] = 0;				! Turn off timer

	    ! Now do state checking to see if we go to next state
	    if (.LNK [L_STATE] eql ST_CR) and (.CCB [C_STS] eql S_SSUC)
	    then
		begin				! OK !
		LNK [L_PIX] = .CCB [C_PIX];	! Bind link to process
		LNK [L_STATE] = ST_CRA;		! Advance to next state
		CCBRT$ (.CCB)			! Release our CCB
		end
	    else
		begin				! OOPS !
		local
		    PTR;
		LNK [LL_ABTI] = true;		! Prevent two rejects
		CCB [C_ADDR] = byt$ptr (CCB [C_PRM1]);
		if (.CCB [C_STS] eql S_ERBO) or (.CCB [C_STS] gtr 0)
		then CCB [C_STS] = 0;
		if .CCB [C_STS] lss 0 then CCB [C_STS] = -.CCB [C_STS];
		PTR = byt$ptr (CCB [C_PRM1]);
		byt$short_string (CCB [C_STS], PTR);
		byt$tiny_string (uplit (0), PTR);
		CCB [C_CNT] = 3;
		$SC_DO_XME (.CCB, N_XREJ, .LNK)
		end;

	    return
	    end;



	! *********************
	! ** SR$DAT & SR$INT **
	! *********************
	[S$DAT^-1, S$INT^-1]:
	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_RUN) or
		    (.LNK [L_STATE] eql ST_DI) or
		    (.LNK [L_STATE] eql ST_DIR) or
		    (.LNK [L_STATE] eql ST_ABI) or
		    (.LNK [L_STATE] eql ST_CLI))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK)
	    %fi;



	! ************
	! ** SR$DSR **
	! ************
	[S$DSR^-1]:
	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_DIR) or
		    (.LNK [L_STATE] eql ST_CLI))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK)
	    %fi;




	! ************
	! ** SR$ERR **
	! ************
	[outrange]:
	    %if paranoid %then
		 SIGNAL_STOP (SC$_ISC, .CCB, .LNK)
	    %fi;
	tes;

    ! Complete LCCB to NSP, and release our CCB
    $SC_DO_RCE (.LCCB);
    CCBRT$ (.CCB)
    end;
%sbttl 'Timeout or Initialization From Comm/Exec'
routine FCTMO (SCDB, CCB, FCM): mcb_db_ccb_mod novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine is activated by some event noted by
!	the Comm/Exec.
!
! FORMAL PARAMETERS:
!	CCB	CCB to pass to handler routine
!	FCM	Function code modifier
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    $sc_get_data_base (SCDB);
    map	CCB: ref block field (C_FIELDS),
	SCDB: ref block field (SC_FIELDS);
    bind
	LLT = SCDB [SC_LLT_ADDR]: ref blockvector [,L_SIZE] field (LLT_FIELDS);

    MAP$ (.SCDB [SC_LLT_BIAS]);

    case .FCM^-1 from 0 to 3 of
	set


	! ************
	! ** CX$LTM **		! Long timer
	! ************
	[1]:
	    begin
	    local
		LL,
		LNK: ref block field (LLT_FIELDS),
		LCCB: ref block field (C_FIELDS);

	    SCDB [SC_TICK] = .SCDB [SC_TICK] + 1;	! Restart clock
	    SCDB [SCF_SUCC] = true;
	    LL = .SCDB [SC_LLINK];		! Figure which LL to start with

	    ! Check each logical link to see if something to do
	    incr L from 0 to .SCDB [SC_LINKS]-1 do
		begin

		if .SCDB [SCF_SUCC] then SCDB [SC_LLINK] = .LL;		! Remember last
		if (LL = .LL + 1) geq .SCDB [SC_LINKS] then LL = 0;	!  & next link
		LNK = LLT [.LL, L_TOP];

		if .SCDB [SCF_SUCC]
		then
		    begin			! Check on ...
		    $SC_DISPATCH_OUTPUT (LNK [L_INTQ]);	! ... interrupt resource wait
		    $SC_DISPATCH_INPUT (LNK [L_IQUE]);	! ... input resource wait
		    $SC_DISPATCH_OUTPUT (LNK [L_OQUE])	! ... output resource wait
		    end;

		! Finally, check to see if link timer running
		if .LNK [LL_KLOK]
		then
		    begin
		    if .LNK [L_TIMER] eql 0
		    then LNK [LL_KLOK] = false
		    else
			begin
			if (LNK [L_TIMER] = .LNK [L_TIMER] - 1) eql 0
			then 
				begin
				LNK[L_STS] = S_ENRO;
				I$CLS (.LNK);
				end
			end
		    end
		end;

	    I$OPN ()			! Open a port if needed
	    end;



	! ************
	! ** CX$PIN **		! Process initialization
	! ************
	[3]:
	    begin
	    PDVID$ (RAD50 ('SC1'), SCDB [SC_SNPIX]);
	    SCDB [SCF_STAT] = S_ST_OFF		! We are OFF
	    end;



	! ************
	! ** CX$PWF **		! Power failure recovery
	! ************
	[2]: return;



	! ************
	! ** CX$ERR **		! CX$STM
	! ************
	[inrange, outrange]:
	    %if paranoid %then
		SIGNAL_STOP (SC$_ISC)
	    %fi;

	tes
    end;
%sbttl 'Transmit Complete From NSP'
routine FCXCP (SCDB, CCB, FCM): mcb_db_ccb_mod novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine is activated by receipt of a transmit
!	complete CCB from NSP.
!
! FORMAL PARAMETERS:
!	CCB	CCB to pass to handler routine
!	FCM	Function code modifier
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    $sc_get_data_base (SCDB);
    map	CCB: ref block field (C_FIELDS);
    local
	LNK: ref block field (LLT_FIELDS),
	LCCB: ref block field (C_FIELDS),
	STATUS;
    bind
	LLT = SCDB [SC_LLT_ADDR]: ref blockvector [,L_SIZE] field (LLT_FIELDS),
	PIV = LLT [.SCDB [SC_LINKS], L_TOP]: byte_vector;

    MAP$ (.SCDB [SC_LLT_BIAS]);

    LNK = LLT [.PIV [.CCB [C_LIX]], L_TOP];
    STATUS = STSMAP (.CCB [C_STS]);		! Set appropriate status info
    LCCB = .CCB [C_STK];			! Get user's CCB address


    case .FCM^-1 from 0 to N_XHI^-1 of
	set



	! *********************
	! ** NX$ABT & NX$DSC **
	! *********************
	[N_XABT^-1, N_XDSC^-1]:
	    begin
	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_ABI) or
		    (.LNK [L_STATE] eql ST_DIR) or
		    (.LNK [L_STATE] eql ST_DI) or
		    (.LNK [L_STATE] eql ST_CLI))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    I$CLS (.LNK)
	    end;



	! ************
	! ** NX$ACC **
	! ************
	[N_XACC^-1]:
	    begin
	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_CA) or
		    (.LNK [L_STATE] eql ST_CLI) or
		    (.LNK [L_STATE] eql ST_DIR))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    if (.LNK [L_STATE] eql ST_CA) and (.STATUS eql S_SSUC)
	    then LNK [L_STATE] = ST_RUN
	    end;



	! ************
	! ** NX$REJ **
	! ************
	[N_XREJ^-1]:
	    begin
	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_CR) or
		    (.LNK [L_STATE] eql ST_CRA) or
		    (.LNK [L_STATE] eql ST_DIR) or
		    (.LNK [L_STATE] eql ST_CLI))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    I$CLS (.LNK)
	    end;



	! ************************************************
	! ** NX$BUF & NX$DRQ & NX$IRQ & NX$SND & NX$SNI **
	! ************************************************
	[N_XBUF^-1, N_XDRQ^-1, N_XIRQ^-1, N_XDAT^-1, N_XINT^-1]:
	    begin
	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_RUN) or
		    (.LNK [L_STATE] eql ST_DI) or
		    (.LNK [L_STATE] eql ST_DIR) or
		    (.LNK [L_STATE] eql ST_CLI) or
		    (.LNK [L_STATE] eql ST_ABI))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    selectoneu .FCM of
		set
		[N_XBUF]: LCCB [C_CNT] = .CCB [C_CNT];
		[N_XINT]: LNK [LL_INTM] = false;
		tes
	    end;



	! ************
	! ** NX$CLS **
	! ************
	[N_PCLS^-1]:
	    begin
            ! The following hack prevents us from crashing due to a
            ! race condition which seems to be related to
            ! retransmitted DIs.  Until a better solution is thought
            ! out, we'll just ignore the fact that the link may
            ! already be shut down here.  This much is known to work.
            if .LNK [L_STATE] neq ST_OFF
            then
                begin
                %if paranoid %then
                    if .LNK [L_STATE] neq ST_CLI
                    then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
                %fi

                LNK [L_STATE] = ST_OFF;
                LNK [L_FLAGS] = 0;
                while CMQRM$ (LNK [L_INTQ], LCCB) do
                      $SC_DO_XCP (.LCCB, .LNK [L_STS]);
                while CMQRM$ (LNK [L_OQUE], LCCB) do
                      begin
                      if (.LCCB [C_MOD] neq S$DIS) and (.LCCB [C_MOD] neq S$ABO)
                      then STATUS = .LNK [L_STS]
                      else STATUS =STSMAP (.CCB [C_STS]);
                      $SC_DO_XCP (.LCCB, .STATUS)
                      end;

                if (LCCB = .CCB[C_STK]) neq 0
                   then $SC_DO_XCP(.LCCB, S_SSUC);
                LCCB = 0
                end;
	    end;



	! ************
	! ** NX$CON **
	! ************
	[N_XCON^-1]:
	    begin
	    LNK = .CCB [C_PRM5];

	    %if paranoid %then
		if not (
		    (.LNK [L_STATE] eql ST_CIS) or
		    (.LNK [L_STATE] eql ST_CLI))
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    if .LNK [L_STATE] eql ST_CIS		! Connect-Initiate ?
	    then
		begin
		LNK [LL_KLOK] = true;			! Say we need timer
		SCDB [SCF_KLOK] = true;			! Start the clock
		LNK [L_PID] = .CCB [C_LIX];		! Set port id
		PIV [.CCB [C_LIX]] = .LNK [L_LLA];	! Set reverse mapping
		if .STATUS lss 0			! If connect failure
		then
		    begin				! Connect failure
		    if .CCB [C_STS] neq N$ERES		! If not resource error
		    then I$CLS (.LNK)			!   then close port
		    else
			begin
			LNK [L_STATE] = ST_OFF;		! Resource error, so
			LNK [L_FLAGS] = 0		!  no port to close
			end
		    end
		else
		    begin				! Connect ok so far
		    LNK [L_STATE] = ST_CID;		! Set next link state
		    CMQIF$ (LNK [L_OQUE], .LCCB);	! Put user CCB on queue
		    LCCB = 0				! No CCB to complete
		    end
		end
	    else
		STATUS = S_EABO;			! Link aborted

	    $MCB_RETURN_DSR( DSR_CONNECT_BLOCK_SIZE, .CCB[C_ADDR]);
	    CCBRT$( .CCB);
	    CCB = 0
	    end;



	! ************
	! ** NX$OPN **
	! ************
	[N_POPN^-1]:
	    begin
	    LNK = .CCB [C_PRM1];

	    %if paranoid %then
		if .LNK [L_STATE] neq ST_OI
		then SIGNAL_STOP (SC$_LWS, .CCB, .LNK);
	    %fi

	    LNK [L_PID] = .CCB [C_LIX];
	    PIV [.LNK [L_PID]] = .LNK [L_LLA];
	    if .STATUS eql S_SSUC
	    then
		begin
		LNK [L_STATE] = ST_OPN;
		SCDB [SC_IPORT] = .SCDB [SC_IPORT] + 1
		end
	    else
		begin
		LNK [LL_BUSY] = false;
		LNK [L_STATE] = ST_OFF
		end;

	    SCDB [SCF_OPEN] = false;
	    LCCB = 0
	    end;



	! ************
	! ** NX$INI **
	! ************
	[N_XINI^-1]:
	    begin
	    if .STATUS eql S_SSUC
	    then
		begin
		local
		    OLD_STATE;

		STATUS = NM$SUC;			! Say we made it
		SCDB [SC_LADDR] = .CCB [C_PRM1];	! Get our node address
		SCDB [SC_SSIZE] = .CCB [C_CNT];		!   and segment size
		OLD_STATE = .SCDB [SCF_STAT];		! Remember old state
		SCDB [SCF_STAT] = S_ST_ON;		! Say we are turned on
		CALL$E (NM_SIG, .SCDB [SC_SNPIX], 0, 1, .OLD_STATE);
							! Tell NMX
							! TYPE = 0, REASON = 1

		$MCB_ENABLE_LONG_TIMER ();		! Start the clock
		SCDB [SC_TICK] = .SCDB [SC_TICK] + 1	! ...
		end
	    else
		STATUS = $NM$ERR_UFO;

	    $SC_DO_CCP (.LCCB, .STATUS);		! Complete the CCB
	    LCCB = 0					! ...
	    end;



	! ************
	! ** NX$ERR **
	! ************
	[inrange, outrange]:
	    begin
	    %if paranoid %then
		SIGNAL_STOP (SC$_ISC, .CCB, .LNK);
	    %fi

	    STATUS = S_EERR
	    end;

	tes;

    if .CCB neq 0 then CCBRT$ (.CCB);
    if .LCCB neq 0 then $SC_DO_XCP (.LCCB, .STATUS)
    end;
%sbttl 'Transmit Enable From User'
routine FCXME (SCDB, CCB, FCM): mcb_db_ccb_mod novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine is activated by a transmit enable from
!	a System Interface user.
!
! FORMAL PARAMETERS:
!	CCB	CCB to pass to handler routine
!	FCM	Function code modifier
!
! IMPLICIT INPUTS:
!	CCB Contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--

    begin
    $sc_get_data_base (SCDB);
    map	CCB: ref block field (C_FIELDS);
    local
	LNK: ref block field (LLT_FIELDS),
	QUE_TO_TAIL,
	STATUS;
    bind
	LLT = SCDB [SC_LLT_ADDR]: ref blockvector [,L_SIZE] field (LLT_FIELDS);

    MAP$ (.SCDB [SC_LLT_BIAS]);
    LNK = LLT [.CCB [C_LIX], L_TOP];
    QUE_TO_TAIL = true;
    STATUS = S_SSUC;

    if .SCDB [SCF_STAT] neq S_ST_ON
    then STATUS = S_ELNS
    else case .FCM^-1 from 0 to S$XHI^-1 of
	set



	! ************
	! ** SX$ABO **
	! ************
	[S$ABO^-1]:
	    begin
	    ! Locate which LL the user is talking about
	    STATUS = S_ENSL;		! Assume no such link
	    incr LL from 0 to .SCDB [SC_LINKS]-1 do
		begin
		LNK = LLT [.LL, L_TOP];
		if  (.LNK [L_ULA] eql .CCB [$sub_field (C_PRM1, LO_BYTE)]) and
		    (.LNK [L_PIX] eql .CCB [C_PIX]) and
		    (.LNK [L_STATE] neq ST_OFF) and
		    (.LNK [L_STATE] neq ST_OPN) and
		    (.LNK [L_STATE] neq ST_OI)
		then
		    begin
		    STATUS = S_SSUC;		! We have a link
		    LNK [L_STS] = S_EABO;	! User abort
		    CCB [C_LIX] = .LNK [L_LLA];
		    if
			begin
			(not .LNK [LL_ABTI]) and
			((.LNK [L_STATE] eql ST_RUN) or
			(.LNK [L_STATE] eql ST_DI) or
			(.LNK [L_STATE] eql ST_CA) or
			(.LNK [L_STATE] eql ST_CID) or
			(.LNK [L_STATE] eql ST_DIR) or
			not (.LNK [L_STATE] eql ST_CIS))
			end
		    then
			begin
			local
			    LCCB;
			if .LNK [L_STATE] neq ST_DIR
			then
			    begin
			    LNK [LL_KLOK] = false;
			    LNK [LL_ABTI] = true		! Abort started
			    end;

			! *** Now to free queued input CCBs
			while CMQRM$ (LNK [L_IQUE], LCCB) do $SC_DO_RCE (.LCCB)
			end
		    else
			STATUS = (if .LNK [L_STATE] eql ST_CLI then S_ENOF else S_ELWS);

		    exitloop
		    end
		end;

	    QUE_TO_TAIL = false
	    end;



	! *********************
	! ** SX$ACC & SX$REJ **
	! *********************
	[S$ACC^-1, S$REJ^-1]:
	    begin
	    if (.LNK [L_STATE] eql ST_CRA) and 	not .LNK [LL_ABTI]
	    then
		begin
		if .FCM eql S$REJ then LNK [LL_ABTI] = true;
		LNK [LL_KLOK] = false
		end
	    else
		STATUS = (if .LNK [L_STATE] eql ST_CLI then S_ENOF else S_ELWS)
	    end;



	! ************
	! ** SX$CON **
	! ************
	[S$CON^-1]:
	    begin
	    local
		LL;

	    if FINDLL (LL)			! Get logical link
	    then
	    ! We have found an available LL, so enqueue CCB,
	    ! record user link address, determine destination
	    ! node address, and  call the resource-wait routine.
		begin
		LNK = LLT [.LL, L_TOP];		! Record link block address
		LNK [L_ULA] = .CCB [C_PRM1];	! Set ULA
		LNK [L_PIX] = .CCB [C_PIX];	! Remember user PIX
		CCB [C_LIX] = .LL;		! Tell user the LLA

		if FINDND (.CCB, .LNK)		! Find the node
		then LNK [LL_BUSY] = true	! Mark the link in-use
		else STATUS = S_EUNN
		end
	    else
		STATUS = S_ERES			! No logical links available
	    end;



	! ************
	! ** SX$DIS **
	! ************
	[S$DIS^-1]:
	    begin
	    if	(not (
		(.LNK [L_STATE] eql ST_RUN) or
		(.LNK [L_STATE] eql ST_DIR))) or
		(.LNK [LL_ACDW] neq 0)
	    then
		STATUS = (if .LNK [L_STATE] eql ST_CLI then S_ENOF else S_ELWS)
	    else
		begin
		if .LNK [L_STATE] neq ST_DIR
		then LNK [LL_DSCI] = true
		end
	    end;



	! ******************************
	! ** SX$DRQ & SX$IRQ & SX$MRQ **
	! ******************************
	[S$DRQ^-1, S$IRQ^-1, S$MRQ^-1]:
	    begin
	    if (not
		((.LNK [L_STATE] eql ST_RUN) or
		(.LNK [L_STATE] eql ST_DI))) or
		(.LNK [LL_ABTI] neq 0)
	    then
		STATUS = (if .LNK [L_STATE] eql ST_CLI then S_ENOF else S_ELWS)
	    else
		begin
		if .FCM eql S$IRQ
		then
		    begin
		    CMQIF$ (LNK [L_INTQ], .CCB);
		    $SC_DISPATCH_OUTPUT (LNK [L_INTQ]);
		    return
		    end
		end
	    end;



	! ************
	! ** SX$GLN **
	! ************
	[S$GLN^-1]:
	    begin
	    local
		PTR,
		DPTR,
		LPTR,
		TMP,
		NAML,
		BUF: vector [NODE_ENTITY_LEN];

	    if .CCB [C_CNT] lss 9
	    then
		begin
		$SC_DO_XCP (.CCB, S_ELST);
		return
		end;

	    PTR = byt$ptr (BUF);

	    case .CCB [C_PRM1] from 0 to 3 of
		set

		[0, 1, 3]:
		    begin
		    LPTR = .PTR;
		    TMP = (if .CCB [C_PRM1] eql 3 then .SCDB [SC_HADDR] else .SCDB [SC_LADDR]);
		    byt$short_string (TMP, LPTR);	! Specify our node addr
		    ch$wchar_a (0, LPTR)		! Zero length name
		    end;

		[2]:
		    MFBF$S (9, .CCB [C_BIAS], .CCB [C_ADDR], .PTR);

		[outrange]:
		    begin
		    $SC_DO_XCP (.CCB, S_EERR);
		    return
		    end;
		tes;

	    CALL$E (NM_NOD, .SCDB [SC_SNPIX], .PTR);
	    LPTR = .PTR;				! Now, look at address
	    byt$string_short (LPTR, TMP);		! ...
	    if .TMP eql -1
	    then
		begin
		$SC_DO_XCP (.CCB, S_EUNN);		! Zero means no findum
		return
		end;

	    NAML = ch$rchar_a (LPTR);			! Get name length
	    MAP$ (.CCB [C_BIAS]);
	    DPTR = .CCB [C_ADDR];

	    case .CCB [C_PRM1] from 0 to 3 of
		set

		[0]:
		    begin
		    local
			DPTR;
		    DPTR = ch$move (.NAML, .LPTR, .DPTR);
		    DPTR = ch$fill (%c' ', (6 - .NAML), .DPTR);
		    TMP = .SCDB [SC_SSIZE];
		    byt$short_string (TMP, DPTR)
		    end;

		[1, 2, 3]:
		    DPTR = ch$move (.NAML + 3, .PTR, .DPTR);

		tes;

	    CCB [C_CNT] = ch$diff (.DPTR, .CCB [C_ADDR]);
	    $SC_DO_XCP (.CCB, S_SSUC);
	    return
	    end;



	! *********************
	! ** SX$SND & SX$SNI **
	! *********************
	[S$SND^-1, S$SNI^-1]:
	    begin
	    if	(.LNK [L_STATE] eql ST_RUN) and
		(.LNK [LL_ACDW] eql 0)
	    then
		begin
		if .FCM eql S$SNI
		then
		    begin
		    CMQIN$ (LNK [L_INTQ], .CCB);
		    $SC_DISPATCH_OUTPUT (LNK [L_INTQ]);
		    return
		    end
		end
	    else
		STATUS = (if .LNK [L_STATE] eql ST_CLI then S_ENOF else S_ELWS)
	    end;



	! ************
	! ** SX$ERR **
	! ************
	[outrange, inrange]: STATUS = S_EERR;

	tes;



    if .STATUS neq S_SSUC then $SC_DO_XCP (.CCB, .STATUS)
    else
	begin
	if .QUE_TO_TAIL
	then CMQIN$ (LNK [L_OQUE], .CCB)
	else CMQIF$ (LNK [L_OQUE], .CCB);
	$SC_DISPATCH_OUTPUT (LNK [L_OQUE])
	end
    end;

end
eludom