Google
 

Trailing-Edge - PDP-10 Archives - decuslib10-08 - 43,50512/int.b36
There are no other files named int.b36 in the archive.
MODULE INT=
!Interrupt and error handling module for NETSPL


%(

This module, together with macros defined in LIBRARY file INTR.BLI,
provides a condition handling facility for use on TOPS-10.  This 
interfaces to the software interrupt system so conditions may be
SIGNALed by the occurrance of a software interrupt.  Support for 
(simulated) mutiple processes is provided, with routines to allow
a process to cause a condition to be SIGNALed by another process.

Note that an 'Interrupt channel' as used herein consists of a 4-word
block in the interrupt vector (as used by the PISYS. UUO), a word
in INTTBL containing the address of an interrupt block (as defined in INTR.BLI),
and a bit in INTMAP indicating that the 'interrupt channel' is in use.

)%
BEGIN
COMPILETIME FTDEBUG=1;
!
! Table of contents
!
FORWARD ROUTINE
	INTINI,		!Initialize an interrupt block
	INTFREE,	!Free an interrupt channel
	FFINTC,		!Find a free interrupt channel
	UNWIND,		!Remove 1 or more routine calls from the stack
	%NAME('.SIGNL'),!Signal a condition
	PISYS,		!Do a PISYS. uuo on TOPS-10
	FSIGNL,		!Force a SIGNAL to a process
	INTCOPY,	!Make a temp copy of an interrupt block
	WAKE,		!Wake up a process
	QUIT,		!Tell our superior that we died
	QUITHANDLE,	!Handler for above
	SAYQUIT;	!For WHAT command to say process has terminated

!
! Libraries
!
REQUIRE 'INTR.REQ';
!
! Version
!
THIS_IS[INT]	VERSION [2]	EDIT [26]		DATE [12,Dec,79]

!
! R E V I S I O N   H I S T O R Y
!	
%(
[26]	Verify process handle in WAKE also (use CHECKF)
[25]	Don't turn off PS.V?? except PS.VIP or interrupts come when not wanted
[24]	Fix INTINI & INTFREE to use correct offset 
[23]	Defend against freeing partially-set-up interrupt block (INTFREE)
[22]	Fix QUIT routine to pass a proper interrupt block
[21]	Add QUIT routine to indicate process termination
[20]	Use NOINTS macro
[17]	Move INTSIG to its own module so INT can have DEBUG linkage
[16]	Add conditional interrupt signalling
[15]	Add INTINI routine (initialize int blk & assign slot)
[14]	Fix INTSIG to properly handle empty runlist
[13]	Move FORWARD declarations to before REQUIRE, to avoid conditional
	EXTERNAL declaration.

	E N D	R E V I S I O N   H I S T O R Y )%
!
! Externals
!

EXTERNAL ROUTINE
FREE,			!Give up some core
CHECKF,			!Verify fork handle
ZERO;			!Zero out some core

EXTERNAL TTYINT: INT_BLOCK;
EXTERNAL INTMAP: BITVECTOR;
!EXTERNAL INTTBL: VECTOR;
EXTERNAL RUN;		!Addr of process block of running process
!
! Builtin
!

BUILTIN MACHSKIP,MACHOP;
!
! Macros
!
MACRO PREFIX='INT'%;	!For MSG macro

!
! Routines
!

GLOBAL ROUTINE INTINI(IB)=
!Initialize interrupt block and assign an interrupt channel to it
!Argument:
!IB:	Address of interrupt block to initialize
!Returns: interrupt channel assigned to block
!Implicit outputs:
!	interrupt vector block for channel is initialized also
BEGIN
MAP IB: REF INT_BLOCK;
REGISTER			!For efficiency only
	OFF,			!Offset in INTVEC
	I;			!Index (= OFF/4)
ZERO(.IB,.IB+INT_LEN-1);	!Zero everything first
I=FFINTC();			!Find a free interrupt channel
IB[INT$OFFSET]=(OFF=(.I*4));	!Offset is index * 4
INTVEC[.OFF,INTVEC$STATUS]=
 (INTVEC[.OFF,INTVEC$REASON]=
 (INTVEC[.OFF,INTVEC$VIP]=0));
INTTBL[.I]=.IB;			!Store addr of this interrupt block
IB[INT$PROCESS]=.RUN;		!Accept responsibility for the interrupts
.I				!Return interrupt channel
END;	!INTINI
GLOBAL ROUTINE FFINTC=
!Find a free interrupt channel (vector location)

!
!Formal Parameters
!

!None

!
!Implicit Inputs
!

!INTMAP (a bit map of free interrupt channels)

!
!Returned value
!

!Interrupt channel (NOT the vector offset)

BEGIN
INCR T FROM 0 TO INTMAX DO
	IF .INTMAP[.T] EQL 0 THEN	BEGIN
					NOINTS((
						INTMAP[.T]=1;	!Mark it in use
					));
					RETURN .T
					END;
ERROR(NOINTC);	!Signal no free interrupt channels
END;	!FFINTC
GLOBAL ROUTINE INTFREE(INTBLK)=
!Free an interrupt channel
BEGIN
MAP INTBLK: REF INT_BLOCK;
REGISTER				!For efficiency only, can be LOCAL
	I,
	OFF;

IF (.INTBLK[INT$WHAT] NEQ 0) OR		!Make sure we really got set up OK
   (.INTBLK EQL TTYINT)			!Only TTY belongs on channel 0
    THEN INTERRUPTS(REMOVEC,.INTBLK);	!Get rid of any pending interrupts
OFF=.INTBLK[INT$OFFSET];		!Offset in interrupt vector
I=.OFF/4;				!Index to INTTBL & INTMAP
INTTBL[.I]=0;				!Get rid of pointer to this block
INTMAP[.I]=0;				!Mark it free
INTVEC[.OFF,INTVEC$STATUS]=		!Clear out anything left over
 (INTVEC[.OFF,INTVEC$REASON]=		!in the interrupt vector
 (INTVEC[.OFF,INTVEC$VIP]=0));
END;!INTFRE
GLOBAL ROUTINE UNWIND(DEPTH)=
!Remove DEPTH frames from the stack
!******************** WARNING **************************
!This routine must not use any LOCAL or REGISTER storage, or cause any
!to be generated by the compiler.  Locals become garbaged after the stack
!starts to be unwound, and registers would get restored to the wrong values
!after we had carefully restored them to the right ones. In particular,
!use no INCR/DECR loops, as these store their indices in DREGS.
!Software interrupts are disabled during UNWIND so we can use OWN variables.
BEGIN
MACRO POP(S,Y)=MACHOP(%O'262',S,Y) %;
MACRO POPJP=MACHOP(%O'263',SREG) %;
OWN NDREGS;		!# of DREGS to restore
OWN D;
BIND U_SIGNAL_ARGS=(PLIT(SS$_UNWIND^3)-1);	!Signal args for UNWIND
OWN U_MECH_ARGS: VECTOR[9] INITIAL (8,REP 8 OF (0));!Mechanism args for UNWIND
OWN U_ENABLE_ARGS_P;				!Ptr to enable args for UNWIND
LABEL FIND_PROLOGUE;
MACRO	NOINTS_OWN[]=	BEGIN
			EXTERNAL INTENC;
			INTERRUPTS(OFF);
			INTENC=.INTENC+1;
			(%REMAINING);
			IF (INTENC=.INTENC-1) LEQ 0 THEN
				INTERRUPTS(ON);
			END%;

%IF %SWITCHES(DEBUG)
	%THEN	BEGIN
		OWN URUN;	!Last process that went through here
		EXTERNAL RUN: REF PROCESS_BLOCK;
		URUN=.RUN;
		DEBUGMSG(MSG('[','','Unwinding ');TNUM(.DEPTH,10);
			 TYPE(' levels]',CRLF);
			)
		END
	%FI;
NOINTS_OWN((		!We can't have interrupts at a time like this!!
	D=.DEPTH;		!Move depth to OWN storage
	WHILE .D GEQ -2 DO BEGIN
		NDREGS=.(.FREG-1)<23,4>;
		!Find out how many DREGS he is saving by looking
		!in the AC field of the return address, where
		!our special version of the prologue saved it
		IF .FREG<18,18> NEQ 0 THEN !Signal 'UNWIND' to handler
		!We cannot use SIGNAL because we don't want to allow
		!the handler to RESIGNAL, or lower levels get signalled twice.
			BEGIN
			U_MECH_ARGS[MA_FRAME]=.FREG;
			U_ENABLE_ARGS_P=.FREG<18,18>+1;	!Addr of Enable args
			(..FREG<18,18>)
			    (U_SIGNAL_ARGS,U_MECH_ARGS,.U_ENABLE_ARGS_P-1);
			END;
		UNTIL .SREG<0,18> EQL .FREG<0,18>+.NDREGS DO
				SREG=.SREG-(XWD(1,1));
		UNTIL .NDREGS EQL -1 DO
				(POP(SREG,FREG-.NDREGS);NDREGS=.NDREGS-1;);
				!Restore DREGS & FREG
		D=.D-1;
		END;
	));	!End NOINTS block
%IF %SWITCHES(DEBUG)
	%THEN DEBUGMSG(TYPE('[NETUNW  Unwind complete]',CRLF));
	%FI
POPJP;		!Now do a return ourselves (we have already restored everything)

END;
GLOBAL ROUTINE %NAME('.SIGNL')(SIGNAL_ARGS)=
!Routine to signal a condition of some sort
BEGIN
MAP SIGNAL_ARGS: REF VECTOR;
LOCAL SIGARGS: VECTOR[INT_LEN];	!A little longer than needed
LOCAL HFP;
LOCAL MECHANISM_ARGS:VECTOR[MECH_ARGS_LEN+1];
MACRO PENDING=35,1%; !Corresponds to INT$PENDING in INT block
MACRO TEMPINT=34,1%;	!Corresponds to INT$TEMP in INT block

!Clear PENDING bit
(SIGNAL_ARGS[SA_LENGTH])<PENDING>=0;

INCR I FROM 0 TO .(.SIGNAL_ARGS)<RH> DO
	SIGARGS[.I]=.SIGNAL_ARGS[.I];

!Handle temporary block if we got one
IF .(SIGNAL_ARGS[SA_LENGTH])<TEMPINT>
THEN	BEGIN
	FREE((.SIGNAL_ARGS-%FIELDEXPAND(INT$SIGNAL_ARGS,0)),INT_LEN);
	!Free the whole interrupt block, though we got passed an address
	!in the middle of it.
	DEBUGMSG(MSG('[','','Temporary interrupt block @ ');
		 TNUM((.SIGNAL_ARGS-%FIELDEXPAND(INT$SIGNAL_ARGS,0)),8);
		 TYPE(' freed]',CRLF);
		)
	END;

MECHANISM_ARGS[MA_VREG]=.VREG;	!Contents of VREG get preserved here
MECHANISM_ARGS[MA_T2]=.T2;	!Save temporary registers
MECHANISM_ARGS[MA_T3]=.T3;
MECHANISM_ARGS[MA_T4]=.T4;
MECHANISM_ARGS[MA_T5]=.T5;
MECHANISM_ARGS[MA_LENGTH]=MECH_ARGS_LEN;
MECHANISM_ARGS[MA_DEPTH]=-1;	!Initialize
HFP=.FREG;

WHILE .HFP NEQ 0 DO BEGIN
	IF .HFP<18,18> NEQ 0
		THEN BEGIN
		LOCAL ENABLE_ARGS;
		MECHANISM_ARGS[MA_FRAME]=.HFP<0,18>;	!FP of establisher
		ENABLE_ARGS=.HFP<18,18>+1;	!2nd word of block
!Moved!!!!!!!	ENABLE_ARGS=.(.HFP-1)<18,18>;
		SELECTONE
		   (..HFP<18,18>)(SIGARGS,MECHANISM_ARGS,.ENABLE_ARGS)
		   OF SET
		  [SS$_CONTINUE]:	BEGIN	!Handler returned SS$_CONTINUE
					T2=.MECHANISM_ARGS[MA_T2];
					T3=.MECHANISM_ARGS[MA_T3];
					T4=.MECHANISM_ARGS[MA_T4];
					T5=.MECHANISM_ARGS[MA_T5];
					RETURN .MECHANISM_ARGS[MA_VREG];
						!Restore VREG
					END;
		  [SS$_RESIGNAL]:	;!Fall through to next handler
		  [OTHERWISE]:	CRASH('?Handler returned undefined value');
		TES;
		END;
	MECHANISM_ARGS[MA_DEPTH]=.MECHANISM_ARGS[MA_DEPTH]+1;
				!Increment depth for handler when we find it.
	HFP=..HFP;	!keep looking
	END;
CRASH('?No handler found for condition',CRLF);
END;	!SIGNL

GLOBAL ROUTINE PISYS(FLAGS,ADDR)=
BEGIN
REGISTER F;
F<18,18>=.FLAGS;
F<0,18>=.ADDR;
IF CALLI(F,%O'136') THEN RETURN -1
		ELSE RETURN (.F+PISERR);
END;


GLOBAL ROUTINE FSIGNL(IFORK,INTER)=
!Routine to force a signal at a process
!IFORK is the address of a process block
!INTER is an interrupt block
BEGIN
MAP	IFORK:	REF PROCESS_BLOCK,
	INTER:	REF INT_BLOCK;
LOCAL T:	REF INT_BLOCK;

IF .INTER[INT$PENDING] THEN	!This block is in use!!
	INTER=INTCOPY(.INTER);	!Make a copy of it

INTER[INT$PENDING]=1;		!It sure is now!!
IF (T=.IFORK[P$INTERRUPTS]) EQL 0 THEN IFORK[P$INTERRUPTS]=.INTER
ELSE	BEGIN
	WHILE .T[INT$NEXT] NEQ 0 DO T=.T[INT$NEXT]; !Find the end of the chain
	T[INT$NEXT]=.INTER;		!and put this interrupt there
	END;
WAKE(.IFORK);					!Schedule this process
DEBUGMSG((
	IF .INTER[INT$NEXT] NEQ 0 THEN
		CRASH('?NETIBS Interrupt block already linked');
));
END;
GLOBAL ROUTINE INTCOPY(INT)=
!Make a temporary copy of an interrupt block
!It will be the same as the old one except that
!It will not be linked into any process's interrupt list,
!It will have INT$TEMP set and INT$PENDING cleared
!INT: address of interrupt block (which may itself be a copy)
BEGIN
LOCAL NEWINT: REF INT_BLOCK;
EXTERNAL ROUTINE ALLOC,COPY;
NEWINT=ALLOC(INT_LEN);
COPY(.INT,.NEWINT,INT_LEN);	!Copy everything
NEWINT[INT$TEMP]=1;		!This new block is temporary
NEWINT[INT$PENDING]=0;		!It is therefore not pending yet
NEWINT[INT$NEXT]=0;		!Nor is it part of any linked list
DEBUGMSG((
	TYPE('[NETCPI Interrupt block @');
	TNUM(.INT,8);
	TYPE(' copied to ');
	TNUM(.NEWINT,8);
	TYPE(']',CRLF)
))
.NEWINT				!Return its address
END; !INTCOPY
GLOBAL ROUTINE WAKE(WFORK)=
!Put a process on the runlist unless it is already there or is running
BEGIN
EXTERNAL RUN: REF PROCESS_BLOCK;
MAP WFORK: REF PROCESS_BLOCK;
LOCAL FRK: REF PROCESS_BLOCK;

IF CHECKF(.WFORK) EQL 0 THEN RETURN 0;		!Old, dead process?

IF .RUN EQL 0 THEN (RUN=.WFORK; RETURN WIN);
FRK=.RUN;
DO	BEGIN
	IF .FRK EQL .WFORK THEN RETURN WIN;	!Already there
	IF .FRK[P$NEXT] EQL 0 THEN (FRK[P$NEXT]=.WFORK; RETURN WIN);!Add to list
	FRK=.FRK[P$NEXT];			!Walk down the list
	END WHILE 1;
END;!WAKE
GLOBAL ROUTINE QUIT(CODE)=
!Tell the process that created us that we're all washed up
!Superior process should then free up the storage from our stack & process blk
!The condition is signalled like ERROR(INFQIT,addr of process blk,.CODE)
BEGIN
EXTERNAL RUN: REF PROCESS_BLOCK;	!Current process
LOCAL SUP;	!Superior process

ESTABLISH(QUITHANDLE);		!do-nothing handler

RUN[P$DISPLAY]=SAYQUIT;	!Say we're already dead if anyone asks
IF (SUP=.RUN[P$SUPERIOR]) EQL 0 THEN CRASH('?Top level process terminated')
	ELSE BEGIN
	LOCAL ARGS: INT_BLOCK;
	CLEARV(ARGS);
	ARGS[INT$NEXT]=0;		!Just pass this one, please
	ARGS[INT$STSCODE]=INFQIT;	!Tell him one of his pets died
	ARGS[INT$STATUS]=.RUN;		!Namely, us
	ARGS[INT$SEVERITY]=SS$_WARN;	!Not all that serious, really
	(ARGS[INT$PC])<STSCODE>=.CODE;	!The cause of death
	ARGS[INT$SIGNAL_ARGS]=3;	!3 arguments given
	FSIGNL(.SUP,ARGS);
	WHILE 1 DO WAIT(FRKEND)	!If we wake, it must have been a mistake
	END;
END;!QUIT
ROUTINE QUITHANDLE(SIGNAL_ARGS,MECH_ARGS,ENABLE_ARGS)=
!Handler for QUIT. Let anything go, more or less
BEGIN
RETURN SS$_CONTINUE
END;	!QUITHANDLE
ROUTINE SAYQUIT=TYPE(' --- (Pending termination)');
END ELUDOM