!TITLE Calling Director Procedures
! This chapter describes how a subsystem acquires access to the Director
! procedures by forming System Call descriptors from the pairs of values
! (i,j) associated with the identifiers of the procedures forming the
! Director interface.  Knowledge of the 2900 Series System Call mechanism
! (Ref. 5) is assumed.  The fields SC IDENS AD, SC IDENS and SCT DATE in
! the record format UINFF are relevant.  SC IDENS AD is the address of a
! record array whose elements have the following format:
!
!      %recordformat SC IDF (%string(31)IDEN, %integer I, J)
!
! SC IDENS is the number of elements in the record array.
!
! In the Edinburgh standard object module format, calls to external
! routines in modules compiled separately involve a machine instruction
! CALL with a 64-bit operand which is a descriptor descriptor.  If the
! operand instead is a System Call descriptor then the System Call
! mechanism is invoked, providing controlled access to higher-privilege
! procedures (such as the Director procedures).
!
! When a version of Director is created, a list of identifiers specifying
! permitted procedure entry points is referenced, a new System Call Table
! entry is created, and the identifier and (i,j) values are placed in the
! record array described above.  The task of a subsystem requiring access
! to a Director procedure is thus that of selecting the correct (i,j)
! pair from the record array, creating a System Call descriptor
! containing the (i,j) values, and making that descriptor the operand of
! a CALL instruction.  Subsystem writers using the Edinburgh standard
! object module format should consult Ref. 6.
!
! The field SCT DATE has been provided to remove the need for a
! subsystem to satisfy its references to Director procedures dynamically,
! and to enable them to be fixed up when the subsystem is created.
! SCT DATE is a unique identifier associated with a given version of
! Director.  If the SCT DATE current at the time a subsystem is entered
! is identical to that current when the subsystem was created, then
! clearly the (i,j) values and entry identifiers obtaining when the
! subsystem was created will serve for invocations of the new subsystem.
! The new subsystem will of course have to retain code for fixing up
! Director references dynamically should it find that SCT DATE is
! different from that current when it was created.
!<DNEWINWARDCALL
externalintegerfn  DNEW INWARD CALL(integer  KEY, DR0, DR1,
      integername  I, J)
!
! A new System call table entry is created for an inward call to the
! current ACR (ie the ACR of the program calling this procedure).  ACCESS
! KEY specifies the ACR at and below which access is allowed to the
! specified procedure, and DR0, DR1 is a descriptor descriptor to the
! entry descriptor for the procedure.  The i and j values specifying the
! System call table entry are returned in I and J.
!
! Entries created by this procedure are cumulative and cannot
! subsequently be removed from the System call table.
!>
! ADDS A NEW ENTRY TO THE "I=2" "VERTICAL" VECOTR, FOR AN
! INWARD CALL
INTEGER  TOP J2 VALUE,J2 VECTOR ADDRESS
RECORD (SCTIF)ARRAYFORMAT  SCTIAF(0:TOP I VALUE)
RECORD (SCTIF)ARRAYNAME  SCTI; ! 2 WORDS PER ENTRY
RECORD (SCTJF)ARRAYFORMAT  SCTJAF(0:TOP J VALUE)
RECORD (SCTJF)ARRAYNAME  SCTJ
INTEGER  F
!
      F = IN2(48)
      -> DOUT UNLESS  F = 0
!
      SCTI==ARRAY(SCTIAD,SCTIAF)
      J2 VECTOR ADDRESS=(ADDR(UINF_UEND)+15) & (¬15)
      SCTJ==ARRAY(J2 VECTOR ADDRESS,SCTJAF)
      TOP J2 VALUE=SCTI(2)_DR0 & X'3FFFF'
!
      F = 54
      -> DOUT IF  TOP J2 VALUE<=1; ! NO OUTWARD CALL SET UP
!
      F = 55
      -> DOUT IF  TOP J2 VALUE>=255; ! SCT FULL
!
      F = 45
      -> DOUT IF  VAL(ADDR(I), 4, 1, D CALLERS PSR) = NO
      -> DOUT IF  VAL(ADDR(J), 4, 1, D CALLERS PSR) = NO
      I = 2
!
      F = 8
      -> DOUT UNLESS  KEY>=D CALLERS ACR
!
      F = 0
      J=TOP J2 VALUE; ! J-VALUE BEING SUPPLIED
      SCTI(2)_DR0=VEC128 ! (TOP J2 VALUE+1)
      SCTJ(TOP J2 VALUE)_TYPE=X'80000000' ! (KEY)<<20
      SCTJ(TOP J2 VALUE)_ACR=D CALLERS ACR<<20
      SCTJ(TOP J2 VALUE)_DRDR0=DR0
      SCTJ(TOP J2 VALUE)_DRDR1=DR1
DOUT:
      RESULT  = OUT(F, "")
END ; ! DNEW INWARD CALL
!
!-----------------------------------------------------------------------
!
!<DNEWOUTWARDCALL
externalintegerfn  DNEW OUTWARD CALL(integer  NEWACR, EMAS,
   NEW STACK SEG, DR0, DR1, integername  I, J)
!
! A System call table entry is created for an outward call, according
! to Ref. 8.  In the entry created, KEY is set equal to the ACR of the
! program calling this function, E is set to 0 or 1 according to the
! value of EMAS. Target SSN is set with the value of NEW STACK SEG, which
! must be even and in the range 34 to HISEG.  DR0 and DR1 should supply the
! descriptor descriptor to the required entry descriptor for the
! procedure to be outward-called.  I and J are set on return to the i and
! j values to be used in making the outward call.
!
! Only one of these System call table entries will be extant at any time
! a further call of DNEW OUTWARD CALL will cause the previous outward
! call entry to be lost.
!
! The descriptor supplied is not checked.
!>
! CREATE NEW (OR OVER-WRITE EXISTING) SC TABLE ENTRY (I=2, J=1) FOR
! A (SINGLE) OUTWARD CALL. LOCATION OF THE "VERTICAL VECTOR" BEING
! CREATED (OR WRITTEN INTO) IS CURRENTLY EPAGE 2 (0,1M2,..) OF LOCAL
! SEGMENT 8. ROOM FOR 256 ENTRIES IN A PAGE - PLENTY.
INTEGER  TOP J2 VALUE,J2 VECTOR ADDRESS,CALLERS PRIV
INTEGER  F
RECORD (SCTIF)ARRAYFORMAT  SCTIAF(0:TOP I VALUE)
RECORD (SCTIF)ARRAYNAME  SCTI; ! 2 WORDS PER ENTRY
RECORD (SCTJF)ARRAYFORMAT  SCTJAF(0:TOP J VALUE)
RECORD (SCTJF)ARRAYNAME  SCTJ
!
      F = IN2(49)
      -> DOUT UNLESS  F = 0
!
      SCTI == ARRAY(SCTIAD, SCTIAF)
      J2 VECTOR ADDRESS = (ADDR(UINF_UEND)+15) & (¬15)
      SCTJ == ARRAY(J2 VECTOR ADDRESS, SCTJAF)
      TOP J2 VALUE = SCTI(2)_DR0 & X'3FFFF'
      UNLESS  0 < TOP J2 VALUE < 256 START ; ! FIRST TIME ONLY
         ! SET UP ENTRY 2 IN "HORIZONTAL" VECTOR
         SCTI(2)_DR0 = VEC128 ! 2
         SCTI(2)_DR1 = ADDR(SCTJ(0)_TYPE)
         SCTJ(0) = 0; ! ZERO ZEROTH ENTRY IN "VERTICAL" VECTOR
      FINISH 
!
      F = 45
      -> DOUT IF  VAL(ADDR(I), 4, 1, D CALLERS PSR) = NO
      -> DOUT IF  VAL(ADDR(J), 4, 1, D CALLERS PSR) = NO
      I = 2; ! VALUE IF SUCCESSFUL
      J = 1
!
      F = 8
      CALLERS PRIV = D CALLERS PSR & X'00040000'; ! PRIV BIT IN PSR
      -> DOUT UNLESS  15 >= NEWACR >= D CALLERS ACR
      -> DOUT UNLESS  0 <= EMAS <= 1
      -> DOUT UNLESS  NEW STACK SEG&1 = 0
      -> DOUT UNLESS  34 <= NEW STACK SEG <= UINF_HISEG
      -> DOUT UNLESS  SST(NEW STACK SEG+1) = ENDSST
!
      F = 0
! MAKE/OVER-WRITE ENTRY 2,1
      SCTJ(1)_TYPE = X'40000000' ! (D CALLERS ACR<<20) ! (EMAS<<16) ! NEW STACK SEG
      SCTJ(1)_ACR = NEWACR<<20 ! CALLERS PRIV
      SCTJ(1)_DRDR0 = DR0
      SCTJ(1)_DRDR1 = DR1
DOUT:
      RESULT  = OUT(F, "")
END ; ! DNEW OUTWARD CALL
!
!-----------------------------------------------------------------------
!
!<DNOMINATESTACK
externalintegerfn  DNOMINATE STACK(integer  SEG)
!
! This function is provided to satisfy requirement number 4 of  Ref. 8,
! by calling the OUT12 (defined in Ref. 9) to notify the Local Controller
! to enable it to supply the locked-down SSN+1.
!>
INTEGER  J
RECORD (PARMF)NAME  P
!
      J = IN2(52)
      -> DOUT UNLESS  J = 0
!
      P==RECORD(OUTPAD)
      J = 8
      ->DOUT UNLESS  SEG&1=0 AND  SST(SEG+1)=ENDSST
      P=0
      P_P1=3; ! STACK NUMBER
      P_P2=SEG
      IF  SEG>0 START 
         *OUT_12; ! NOMINATE STACK
      FINISH  ELSE  START 
         ! *OUT_13
      FINISH 
      J=P_DEST; ! 0=SUCCESS, -1 = FAIL
      J=36 IF  J<0
DOUT:
      RESULT  = OUT(J, "I")
END ; ! DNOMINATE STACK
!
!-----------------------------------------------------------------------
!
!<DPLUGINJVECTOR
externalintegerfn  DPLUGIN JVECTOR(integername  IVALUE,
      integer  ADDRESS, TOP ENTRY)
!
! ADDRESS points to the zeroth element of a record array (0:TOP ENTRY),
! format (integer TYPE, ACR, DR0, DR1), which is to be a new ("vertical")
! J-vector in the System Call table.  If the call is successful, IVALUE
! is set to the I-value to be used in subsequent System Calls accessing
! the vector.  The procedure allows a subsystem to cause outward calls
! and to allow users' programs to do inward calls to the subsystem.  The
! address must lie in a non-write-access file, readable at Director's
! ACR.    No target ACR in any of the entries may be less than the
! caller's ACR, nor may the target PRIV bit be set.  After a successful
! call, the file may not be disconnected (except by calling DSTOP), nor
! may its size or access mode be changed (error result 84 is returned if
! attempt is made).  The vector may contain a maximum of 512 System Call
! entries. If the vector exceeds this limit the error result 8 is
! returned.  Subsequent calls of DPLUGIN JVECTOR cause the previously
! plugged-in vector to be forgotten (though the file still may not be
! disconnected).
!>
INTEGER  J, FLAG, APF, SLAVED, NOTDRUM, SEG, CP
RECORD (SCTIF)ARRAYFORMAT  SCTIAF(0:TOP I VALUE)
RECORD (SCTIF)ARRAYNAME  SCTI; ! 2 WORDS PER ENTRY
RECORD (SCTJF)ARRAYFORMAT  SCTJAF(0:TOP J VALUE)
RECORD (SCTJF)ARRAYNAME  SCTJ
      FLAG = IN2(61)
      -> RES UNLESS  FLAG = 0
!
      FLAG = 8
      -> RES UNLESS  1<TOP ENTRY<=TOP J VALUE
      SEG = ADDRESS >> 18
      -> RES UNLESS  LOUSEG<=SEG<=HISEG 
!
      FLAG=45; ! area not accessible
      -> RES IF  VAL(ADDRESS,(TOP ENTRY+1)<<4,0,0)=0
!
      FLAG=8
      IVALUE=4; ! (if successful)
      SCTI==ARRAY(SCTIAD,SCTIAF)
      SCTJ==ARRAY(ADDRESS,SCTJAF)
      ! validate all entries: TARCGET ACR>= subsys acr
      !  and PRIV not set.
      J=1
      WHILE  J<=TOP ENTRY CYCLE 
         IF  SCTJ(J)_ACR&PRIV BIT#0 OR   C 
            (SCTJ(J)_ACR>>20)&15<DCALLERS ACR THEN  -> RES
         J=J+1
      REPEAT 
      ! Check also that seg is not write-able
      GIVE APF(APF,NOTDRUM,SLAVED,SEG)
      IF  (APF>>4)&15#0 THEN  -> RES
      ! Finally mark file not to be disconnected (until DSTOP
      ! called) nor to be changed in size nor changed in access.
      CP=DIROWN_CPOINT(SEG)
      UNLESS  CP>RESERVED THEN  -> RES
      DIROWN_CONLIST(CP)_NODISCO = 1
      SCTI(IVALUE)_DR0=VEC128 ! (TOP ENTRY+1)
      SCTI(IVALUE)_DR1=ADDRESS
      FLAG=0
RES:
      RESULT  = OUT(FLAG, "")
END ; ! DPLUGIN JVECTOR
!
!-------------------end-of-included-text---------------------------------
!