Google
 

Trailing-Edge - PDP-10 Archives - BB-R595B-SM_11-9-85 - mcb/sc/scres.bli
There is 1 other file named scres.bli in the archive. Click here to see a list.
 module SCRES (	! System Interface and NSP Interface Resource Wait
		ident = 'X01330'
		) =
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 module fields all interactions with the System
!		Interface and NSP Interface, when potential resource
!		waits are encountered.
!
! ENVIRONMENT:	MCB
!
! AUTHOR:	Buren Hoffman		CREATION DATE: 7-Apr-80
!
! MODIFIED BY:
!	X01010	Changed code to use $byt_ptr macro in place of the
!		ch$ptr macro.
!	X01020	Repaired inconsistent linkage declarations to
!		external routines.
!	X01030	Fixed connect processing to put dest PIX in connect
!		request sent to NSP.
!	X01040	Don't set C_CHN in outgoing connect.
!	X01050	Set proper state transition for connection refused
!		inside of SC.
!	X01060	Changed SX$CNW processing to ignore queued CCB when
!		link is in CID state - i.e., waiting for response
!		from other end.
!	X01070	Changed NR$CRW to try for immediate port replacement.
!	X01080	PIX was not being set in output ccb from SX$ACW.
!	X01090	PIX was not being set in several routines.
!	X01100	Fixed problem of missing ref's in several declarations.
!	X01110	Wrong CCB being forwarded to LLCRS in NR$DRW, NR$DTW,
!		and NR$INW.
!	X01120	Wrong LIX was being set in NR$CRW, on link reject.
!	X01130	Fixed dot bug in call from SX$ABW to I$CLS.
!	X01140	Link closing error in call to I$CLS in SX$ABW.
!	X01150	Change to prevent two reject calls on same link
!	X01160	Fixed dequeueing bug in SX$RJW
!	X01170	Fix to assure proper optional data format is generated
!	X01180	Minor documentation cleanup
!	X01190	Connect accept was not recording ULA, and received data
!		was not forwarding the eom indicator.
!	X01200	Use new Comm/Exec to process linkage (.CRDAT for database)
!	X01210	Modified connect-xmit call to NSP to use modified paramater
!		list.
!	X01220	Updated to use library calls, instead of requires.
!	X01230	Moved link OPNer code call to SCDSP.
!	X01240	Fixed disconnect reason processing.
!	X01250	Fixed bug introduced in above fix.
!	X01260	Fixed race between CNR and DSR.
!	X01270	Changed Disconnect-Received code to pass reason
!		code in C_PRM2, instead of in disconnect data.
!	X01280	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.
!	X01290	Optimization work.
!	X01300	Bug fix in disconnect-received processing.
!
!	x01310  Use DSR space instead of LDB's for connect info
!       x01320  Set local node number in when connecting to loop node
!	x01330	move some code around in SX$ABW
!
!--
!
! INCLUDE FILES:
!
library 'SCPRM';		! Our parameter and macro definitions
library 'MCB:MCBLIB';
library 'MCB:RSXLIB';
library 'MCB:XPORTX';
library 'MCB:SCSYS';

require 'NSP:NSINFO';

!
! TABLE OF CONTENTS:
!
forward routine
    NR$CRW: novalue,		! Connect Received
    NR$DRW: novalue,		! Disconnect Received
    NR$DTW: novalue,		! Data Received
    NR$INW: novalue,		! Interrupt Received

    SX$ABW: novalue,		! Abort
    SX$ACW: novalue,		! Accept
    SX$CNW: novalue,		! Connect
!   SX$DSW: novalue,		! Disconnect (See SX$ABW)
    SX$DRW: novalue,		! Data Request
    SX$IRW: novalue,		! Interrupt Request
!   SX$MRW: novalue,		! Message Request (See SX$DRW)
    SX$RJW: novalue,		! Reject
    SX$SDW: novalue,		! Send Data
    SX$SIW: novalue;		! Send Interrupt

!
! MACROS:
!
!
! EQUATED SYMBOLS:
!
!
! OWN STORAGE:
!
!
! EXTERNAL REFERENCES:
!

external routine
    CONBKI,				! Do connect block processing
    CONBKO,				! Do connect data translation
    STKCCB: novalue,			! Stack CCBs

    I$CLS: novalue,			! NSP port closing
    I$OPN: novalue;			! NSP port opening
global routine NR$CRW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Get resources to complete incoming connect notification.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    if not CCBGT$ (LCCB) then $SC_WAIT;
    CMQRM$ (LNK [L_IQUE], CCB);			! Got new CCB, so deque old one
    if CONBKI (.CCB, .LCCB, .LNK)		! Validate the connect message
    then
	begin					! OK, tell user about connect
	bind
	    CB = LCCB [C_ADDR]: ref block field (CB_FIELDS);
	$SC_DO_RCE (.CCB);			! Return NSP's CCB
	LCCB [C_STS] = S_SSUC;
	LCCB [C_PRM2] = LNK [L_TIMER] = .SCDB [SC_ITIME];
	$SC_DO_RCP (.LCCB, S$CNR, .LNK);	! Tell user
	LNK [LL_KLOK] = true;
	SCDB [SCF_KLOK] = true
	end
    else
	begin					! No good
	$SC_DO_RCE (.CCB);			! Return NSP's CCB
	LNK [L_PIX] = 0;			! Prevent disconnect race
	LCCB [C_ADDR] = byt$ptr (LCCB [C_PRM1]);
	%if %bliss (bliss16)
	%then
	    LCCB [C_PRM2] = 0;			! No optional data
	%else
	    begin
	    local PTR;
	    PTR = ch$plus (byt$ptr (LCCB [C_PRM1]), 2);
	    byt$tiny_string (uplit (0), PTR)
	    end;
	%fi
	LCCB [C_CNT] = 3;
	$SC_DO_XME (.LCCB, N_XREJ, .LNK)
	end
    end;
global routine NR$DRW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Get resources to handle incoming disconnect, or
!	receipt of confidence call on link.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	LLT mapped
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    if not CCBGT$ (LCCB) then $SC_WAIT;

    CMQRM$ (LNK [L_IQUE], CCB);
    STKCCB (.LCCB, .CCB);

    if .CCB [C_MOD] eql N_SCNF		! If confidence loss
    then				!  then
	LCCB [C_PRM2] = S_ENUR		!   set appropriate code
    else
	begin
	MAP$ (.LCCB [C_BIAS]);		! Look at data buffer
	if .LCCB [C_CNT] geq 2		! If have a reason code
	then
	    begin
	    byt$string_short (LCCB [C_ADDR], LCCB [C_PRM2]);
	    LCCB [C_CNT] = .LCCB [C_CNT] - 2
	    end
	else
	    begin
	    LCCB [C_PRM2] = 0;
	    LCCB [C_CNT] = 0
	    end;
	if .LCCB [C_CNT] gtr 1		! If have data
	then
	    begin
	    LCCB [C_ADDR] = ch$plus (.LCCB [C_ADDR], 1);
	    LCCB [C_CNT] = .LCCB [C_CNT] - 1
	    end
	else
	    begin
	    LCCB [C_ADDR] = 0;
	    LCCB [C_CNT] = 0
	    end;
	LCCB [C_PRM2] = -.LCCB [C_PRM2];
	if .LCCB [C_PRM2] eql 0 then LCCB [C_PRM2] = S_EDBO;
	MAP$ (.SCDB [SC_LLT_BIAS])
	end;

    $SC_DO_RCP (.LCCB, S$DSR, .LNK);
    LNK [L_STATE] = ST_DIR
    end;
global routine NR$DTW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Get resources to deliver incoming data.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	FLG,
	LCCB: ref block field (C_FIELDS);

    if not CCBGT$ (LCCB) then $SC_WAIT;

    CMQRM$ (LNK [L_IQUE], CCB);

    FLG = 0;
    if (.CCB [C_PRM1] and N$FBOM) neq 0 then FLG = .FLG or S$PBOM;
    if (.CCB [C_PRM1] and N$FEOM) neq 0 then FLG = .FLG or S$PEOM;
    if .FLG eql 0 then FLG = S$PMOM;
    LCCB [$sub_field (C_PRM1, HI_BYTE)] = .FLG;
    STKCCB (.LCCB, .CCB);
    $SC_DO_RCP (.LCCB, S$DAT, .LNK)
    end;
global routine NR$INW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Get resources to deliver incoming interrupt data.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    if not CCBGT$ (LCCB) then $SC_WAIT;

    CMQRM$ (LNK [L_IQUE], CCB);
    STKCCB (.LCCB, .CCB);
    $SC_DO_RCP (.LCCB, S$INT, .LNK)
    end;
global routine SX$ABW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	We are here to wait for resources to finish the abort,
!	or disconnect.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	PTR,
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

	! If we can't get the CCB, we are forced to wait awhile
	if not CCBGT$ (LCCB) then $SC_WAIT;

	! We got it - set our context into it
	CMQRM$ (LNK [L_OQUE], CCB);
	LCCB [C_STK] = .CCB;

    ! If not in RUN state, then don't call NSP
    if .LNK [L_STATE] eql ST_RUN
    then
	begin
	if .CCB [C_CNT] neq 0 then LCCB [C_CHN] = .CCB;
	PTR = LCCB [C_ADDR] = byt$ptr (LCCB [C_PRM2]);
	if .CCB [C_MOD] eql S$ABO
	then
	    begin
	    byt$short_string (uplit (-S_EABO), PTR);
	    LCCB [C_MOD] = N_XABT;
	    LNK [L_STATE] = ST_ABI
	    end
	else
	    begin
	    byt$short_string (uplit (0), PTR);	! -S_EDBO
	    LCCB [C_MOD] = N_XDSC;
	    LNK [L_STATE] = ST_DI
	    end;

	byt$tiny_string (CCB [C_CNT], PTR);
	LCCB [C_CNT] = 3;
	$SC_DO_XME (.LCCB, .LCCB [C_MOD], .LNK)
	end
    else
	begin
	LNK[L_STATE] = ST_CLI;
	$SC_DO_XME( .LCCB, N_PCLS, .LNK);
	end
    end;
global routine SX$ACW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	We are here to obtain resource to finish user link
!	acceptance.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB has been enqueued
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    ! If we can't get the CCB, we are forced to wait awhile
    if not CCBGT$ (LCCB) then $SC_WAIT;

    CMQRM$ (LNK [L_OQUE], CCB);			! Got it, set context into it
    LCCB [C_PRM1] =				! Flow control method
	begin
	if .CCB [$sub_field (C_PRM1, HI_BYTE)] eql S$PMSG
	then N$FMES
	else N$FSEG
	end;
    STKCCB (.LCCB, .CCB);			! Stack the CCBs
    if .CCB [C_CNT] neq 0 then LCCB [C_CHN] = .CCB;
    %if %bliss (bliss16)
    %then
	LCCB [C_PRM2] = .CCB [C_CNT];
    %else
	begin
	local
	    LEN,
	    PTR;
	PTR = byt$ptr (LCCB [C_PRM2]);
	LEN = .CCB [C_CNT];
	byt$tiny_string (LEN, PTR)
	end;
    %fi
    LCCB [C_CNT] = 1;
    LCCB [C_ADDR] = byt$ptr (LCCB [C_PRM2]);
    LNK [L_ULA] = .CCB [$sub_field (C_PRM1, LO_BYTE)];
    $SC_DO_XME (.LCCB, N_XACC, .LNK);
    LNK [L_STATE] = ST_CA
    end;
global routine SX$CNW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	This routine waits until a CCB/LDB is available, and
!	then proceeds with the Connect operation.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	Request CCB has been enqueued on the output queue for
!	this LL.
!
! IMPLICIT OUTPUTS:
!	Transition to next connect-state is made.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    if .LNK [L_STATE] eql ST_CID or
	.LNK[ L_STATE] eql ST_CLI then return;	! We are just waiting for
						!  response from other end
    if
	begin
	if CCBGT$( LCCB) then true else false
	end

	and

	begin
	if $MCB_GET_DSR( DSR_CONNECT_BLOCK_SIZE, LCCB[C_ADDR])
	then true 
	else 
		begin
		CCBRT$( .LCCB);
		false
		end
	end
    then
	LCCB[C_BIAS] = 0
    else
	$SC_WAIT;

    CMQRM$ (LNK [L_OQUE], CCB);			! Get request CCB off queue
    CONBKO (.CCB, .LCCB);			! Process connect block

    if .CCB [C_STS] lss 0			! If any error detected -
    then
	begin
	$MCB_RETURN_DSR( DSR_CONNECT_BLOCK_SIZE, .LCCB[C_ADDR]);
	CCBRT$( .LCCB);				! Give back resources, and
	$SC_DO_XCP (.CCB)			!  send request back to user
	end
    else
	begin					! Made it, so request connect
	LCCB [C_PRM1] = .LNK [L_RNA];		! Destination node address
        if .LCCB [C_PRM1] eql 0
        then
            LCCB [C_PRM1] = .SCDB [SC_LADDR];
	LCCB [C_PRM2] = 			! Set flow control method
	    begin
	    if .CCB [$sub_field (C_PRM1, HI_BYTE)] eql S$PMSG
	    then N$FMES
	    else N$FSEG
	    end;
	LCCB [C_PRM3] = .LNK [L_CHN];		! Channel #
	LCCB [C_PRM5] = .LNK;			! Remember our LL
	LCCB [C_STK] = .CCB;			! Remember user CCB
	$SC_DO_XME (.LCCB, N_XCON, .LNK);	! Finally send the Connect
	LNK [L_TIMER] = .SCDB [SC_OTIME];	! Set timer value
	LNK [L_STATE] = ST_CIS;			! Connect-Initiate-Sent
	end
    end;
global routine SX$DRW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Here to wait for resources to process a data segment request,
!	or supply a receive buffer (SX$MRW)
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    ! If we can't get the CCB, we are forced to wait awhile
    if not CCBGT$ (LCCB) then $SC_WAIT;

    ! We got it - set our context into it
    CMQRM$ (LNK [L_OQUE], CCB);

    if .CCB [C_MOD] eql S$DRQ
    then
	begin
	LCCB [C_MOD] = N_XDRQ;
	LCCB [C_PRM1] = .CCB [$sub_field (C_PRM1, HI_BYTE)]
	end
    else
	begin
	LCCB [C_MOD] = N_XBUF;
	LCCB [C_PRM1] = 1
	end;

    STKCCB (.LCCB, .CCB);
    $SC_DO_XME (.LCCB, .LCCB [C_MOD], .LNK)
    end;
global routine SX$IRW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Here to wait for resources to process an interrupt request
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    ! If we can't get the CCB, we are forced to wait awhile
    if not CCBGT$ (LCCB) then $SC_WAIT;

    ! We got it - set our context into it
    CMQRM$ (LNK [L_INTQ], CCB);
    LCCB [C_PRM1] = .CCB [C_PRM1];
    STKCCB (.LCCB, .CCB);
    $SC_DO_XME (.LCCB, N_XIRQ, .LNK)
    end;
global routine SX$RJW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	We are here to obtain resource to finish user link
!	rejection.
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB has been enqueued
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS),
	PTR;

    ! If we can't get the CCB, we are forced to wait awhile
    if not CCBGT$ (LCCB) then $SC_WAIT;

    ! We got it - set our context into it
    CMQRM$ (LNK [L_OQUE], CCB);			! Dequeue original CCB
    STKCCB (.LCCB, .CCB);			! Stack our's on top
    if .CCB [C_CNT] neq 0 then LCCB [C_CHN] = .CCB;
    LCCB [C_ADDR] = byt$ptr (LCCB [C_PRM1]);	! Point to our reason code
    if (.CCB [C_PRM2] gtr 0) or (.CCB [C_PRM2] eql S_ERBO)
    then CCB [C_PRM2] = 0;
    if .CCB [C_PRM2] lss 0 then CCB [C_PRM2] = -.CCB [C_PRM2];
    PTR = byt$ptr (LCCB [C_PRM1]);
    byt$short_string (CCB [C_PRM2], PTR);
    byt$tiny_string (CCB [C_CNT], PTR);
    LCCB [C_CNT] = 3;				! ...
    $SC_DO_XME (.LCCB, N_XREJ, .LNK)		! Send it to NSP
    end;
global routine SX$SDW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Here to wait for resources to process a data xmission
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    ! If we can't get the CCB, we are forced to wait awhile
    if not CCBGT$ (LCCB) then $SC_WAIT;

    ! We got it - set our context into it
    CMQRM$ (LNK [L_OQUE], CCB);
    STKCCB (.LCCB, .CCB);			! Stack CCBs
    LCCB [C_PRM1] =
	begin
	if .CCB [$sub_field (C_PRM1, HI_BYTE)] eql S$PEOM
	then N$FEOM
	else 0
	end;
    $SC_DO_XME (.LCCB, N_XDAT, .LNK)
    end;
global routine SX$SIW (LNK): novalue =

!++
! FUNCTIONAL DESCRIPTION:
!	Here to wait for resources to process an interrupt data xmission
!
! FORMAL PARAMETERS:
!	LNK	Logical link block address
!
! IMPLICIT INPUTS:
!	CCB contents
!
! IMPLICIT OUTPUTS:
!	None
!
! ROUTINE VALUE:
! COMPLETION CODES:
!	None
!
! SIDE EFFECTS:
!	None
!--
    begin
    $sc_get_data_base (SCDB);
    map	LNK: ref block field (LLT_FIELDS);
    local
	CCB: ref block field (C_FIELDS),
	LCCB: ref block field (C_FIELDS);

    if .LNK [LL_INTM] then return;		! Only one interrupt at a time

    ! If we can't get the CCB, we are forced to wait awhile
    if not CCBGT$ (LCCB) then $SC_WAIT;

    ! We got it - set our context into it
    CMQRM$ (LNK [L_INTQ], CCB);
    STKCCB (.LCCB, .CCB);			! Stack CCBs
    $SC_DO_XME (.LCCB, N_XINT, .LNK);
    LNK [LL_INTM] = true			! Interrupt outstanding now
    end;

end
eludom