Trailing-Edge
-
PDP-10 Archives
-
LCG_Integration_Tools_Clearinghouse_T20_v7_30Apr86
-
tools/decnet10/mlib10.mac
There are 4 other files named mlib10.mac in the archive. Click here to see a list.
TITLE MACLIB -- MACRO SUBROUTINE LIBRARY
SUBTTL SECTION 10. -- DECnet/10 FORTRAN ROUTINES
;
;
; =================================================================
;
; MAPC DECSYSTEM-10 MACRO SUBROUTINE LIBRARY
;
; Developed by R. W. Stamerjohn, DEC-10 Systems Group
;
; These routines and all related documentation were developed at
; Monsanto Agricultural Products Company, St. Louis, Mo. 63167.
;
; =================================================================
;
; Use the following DECsystem-10 Monitor command to include
; the MACLIB subroutine library as part of a user program:
;
; .EX YOURS,REL:MACLIB/SEARCH
;
; If you do not include the /SEARCH switch, you will load
; the entire library as part of your program.
;
;
;
;
COMMENT %
;+
List of Routines in This Section:
--------------------------------
ABTNT Abort a connection
ACCNT Accept an incoming connect
CONNT[W] Connect (active) to remote node
DSCNT Disconnect a connection
PASNT[W] Connect (passive) from remote node
RCCNT[W] Read connect confirm data
RCINT[W] Read incoming connect initiate data
RDCNT Read disconnect data
RECNT[W] Receive data message
REJNT Reject an incoming connect
RLSNT Release channel
RXINT[W] Read interrupt data
SNDNT[W] Send data message
STSNT Return general channel status
SXINT[W] Send interrupt message
BCON Build a initial connect block
BNOD Build nodname block string
BUID Build user-id block string
BPWD Build password block string
BACC Build account block string
BDAT Build user data block string
BOPT Build optional block string
BSRC Build a source (active) descriptor
BDST Build a destination (passive) descriptor
RNOD Read nodname block string
RUID Read user-id block string
RPWD Read password block string
RACC Read account block string
RDAT Read user data block string
ROPT Read optional block string
RSRC Read a source (active) descriptor
RDST Read a destination (passive) descriptor
ISTAST Check current link state against list
IRECST Check for available input buffers
IRXIST Check for available interrupt message
ISNDST Check for available output buffers
ISXIST Check for available interrupt buffer
;-
Module Revision History
------------------------
Edit 1: 1 Aug 83 RWS Original
END COMMENT %
PRGEND
TITLE ABTNT
SUBTTL Abort a Connection
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine aborts a DECnet/10 logical link and
; releases the I/O channel.
;
; If the link is in the "running" (.NSSRN) state, the
; call will disconnect the link. In all other states
; this function is illegal, but the channel is always
; released and no further functions are allowed.
;
; Usage: CALL ABTNT(chan,stat[,strmsg])
;
; Arguments: chan Integer variable with DECnet/10 channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or zero (if
; success) in the low half.
;
; strmsg Optional integer array containing message in
; NSP string notation (see BOPT) to send to the
; remote partner. A maximum of 16 8-bit bytes
; may be sent.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY ABTNT
ABTNT: MOVE T0,[.NSFAB,,2] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
CAIGE AN,3 ;Do we have optional data
JRST ABT.1 ; No, skip optional data handling
MOVEI T0,@2(A) ;Get address of string pointer
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
AOS .NSAFN(NS) ; and bump number of arguments
ABT.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore any errors
POPJ P, ;Return to caller
PRGEND
TITLE ACCNT
SUBTTL Accept an Incoming Connect
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine accepts an incoming connect from
; a remote node.
;
; The link must be in the "connect receive" (.NSSCR)
; state to issue this call. The link is left in the
; "running" (.NSSRN) state. The routine will fail if
; the link is in any other state.
;
; Usage: CALL ACCNT(chan,stat[,strmsg])
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by passive network connect
; request (PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or zero (if
; success) in the low half.
;
; strmsg Optional integer array containing message in
; NSP string notation (see BOPT) to send to the
; remote partner. A maximum of 16 8-bit bytes
; may be sent.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY ACCNT
ACCNT: MOVE T0,[.NSFAC,,2] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
CAIGE AN,3 ;Do we have optional data
JRST ACC.1 ; No, skip optional data handling
MOVEI T0,@2(A) ;Get address of block
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
AOS .NSAFN(NS) ;and bump number of arguments
ACC.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore errors
POPJ P, ;Return to caller
PRGEND
TITLE CONNTW
SUBTTL Connect (Active) to Remote Node
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine makes a connect request to a remote
; node. The channel number is returned for use in the
; future network I/O requests.
;
; If the non-blocking (CONNT) form is used, the routine
; will return immediately with the link state "connect
; sent" if the call was successful. If the blocking form
; (CONNTW) is used, the routine will wait and give a
; success return when the link is established or a
; failure if the connect request is rejected.
;
;
; Usage: CALL CONNT[W] (chan,stat,conblk)
;
; Arguments: chan Integer variable to return the channel number
; for a successful call. This number must be used
; in future calls.
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or zero (if
; success) in the low half.
;
; conblk Integer array setup for the connect request
; (see BCON, BSRC, BDST, etc).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY CONNTW
ENTRY CONNT
CONNTW: MOVE T0,[NS.WAI+<.NSFEA,,3>] ;Get function code,,size
SKIPA ; Skip to common code
CONNT: MOVE T0,[.NSFEA,,3] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
MOVEI T0,@2(A) ;Get address of connect block
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore errors
MOVE T1,.NSACH(NS) ;Get channel number
MOVEM T1,@0(A) ;Return to caller
POPJ P, ;Return to caller
PRGEND
TITLE DSCNT
SUBTTL Disconnect a Connection
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine disconnects a DECnet/10 logical link.
;
; If the link is in the "running" (.NSSRN) state, the
; call will send a disconnect to the remote end and put
; the link in the "disconnect sent" (.NSSDS) state. In
; all other states, this function is illegal.
;
; After a successful function call, data may still be
; received from the remote but no further data can be
; sent. The channel can be released when the disconnect
; confirmed is seen.
;
; Usage: CALL DSCNT (chan,stat[,strmsg])
;
; Arguments: chan Integer variable with DECnet/10 channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or zero (if
; success) in the low half.
;
; strmsg Optional integer array containing message in
; NSP string notation (see BOPT) to send to the
; remote partner. A maximum of 16 8-bit bytes
; may be sent.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY DSCNT
DSCNT: MOVE T0,[.NSFSD,,2] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
CAIGE AN,3 ;Do we have optional data
JRST DSC.1 ; No, skip optional data handling
MOVEI T0,@2(A) ;Get address of string pointer
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
AOS .NSAFN(NS) ; and bump number of arguments
DSC.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore any errors
POPJ P, ;Return to caller
PRGEND
TITLE PASNTW
SUBTTL Connect (Passive) to Remote Node
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine prepares for a connect request from
; a remote node. The channel number is returned for use
; in future network I/O requests.
;
; If the non-blocking (PASNT) form is used, the routine
; will return immediately with the link state "connect
; wait" if the call was successful. If the blocking form
; (PASNTW) is used, the routine will wait and give a
; success return when an incoming connect is received.
;
; Usage: CALL PASNT[W] (chan,stat,conblk)
;
; Arguments: chan Integer variable to return the channel number
; for a successful call. This number must be used
; in future calls.
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or zero (if
; success) in the low half.
;
; conblk Integer array setup for the connect request
; (see BCON, BSRC, BDST, etc.).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY PASNTW
ENTRY PASNT
PASNTW: MOVE T0,[NS.WAI+<.NSFEP,,3>] ;Get function code,,size
SKIPA ; Skip to common code
PASNT: MOVE T0,[.NSFEP,,3] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
MOVEI T0,@2(A) ;Get address of connect block
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore errors
MOVE T1,.NSACH(NS) ;Get channel number
MOVEM T1,@0(A) ;Return to caller
POPJ P, ;Return to caller
PRGEND
TITLE RCCNTW
SUBTTL Read Connect Confirm Data
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads any optional data returned from
; the remote node when it accepts a connect from us.
;
; The non-blocking version (RCCNT) is only legal from
; the "running" (.NSSRN) state. The blocking version
; (RCCNTW) can also be issued from the "connect sent"
; (.NSSCS) state and will wait till the remote node
; accepts or rejects the connection request.
;
; The optional data is only available until a normal
; send/receive is issued.
;
; Usage: CALL RCCNT[W] (chan,stat[,strbuf])
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or zero (if
; success) in the low half.
;
; strmsg Optional integer array to get possible message
; from remote partner. The first word in the
; array must be set with the size of the array.
; The message will be returned in NSP string
; notation.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RCCNTW
ENTRY RCCNT
RCCNTW: MOVE T0,[NS.WAI+<.NSFRC,,2>] ;Get function code,,size
SKIPA ; and continue
RCCNT: MOVE T0,[.NSFRC,,2] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
CAIGE AN,3 ;Do we have optional data
JRST RCC.1 ; No, skip optional data handling
MOVEI T0,@2(A) ;Get address of block
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
AOS .NSAFN(NS) ;and bump number of arguments
RCC.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ;Ignore any errors
POPJ P, ;Return to caller
PRGEND
TITLE RCINTW
SUBTTL Read Incoming Connect Data
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads the data from an incoming connect
; request into a connect block. This information can then
; be used to accept or reject the connect request.
;
; If the non-blocking (RCINT) form is used, the routine
; must be called from link state "connect received".
; If the blocking form is used, the call be also be
; used from the "connect wait" (.NSSCW) state and will
; not return until a connect is received.
;
;
; Usage: CALL RCINT[W] (chan,stat,conblk)
;
; Arguments: chan Integer variable to return the channel number
; for a successful call. This number must be used
; in future calls.
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or zero (if
; success) in the low half.
;
; conblk Integer array setup for the connect request
; (see BCON, BSRC, BDST, etc.).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RCINTW
ENTRY RCINT
RCINTW: MOVE T0,[NS.WAI+<.NSFRI,,3>] ;Get function code,,size
SKIPA ; Skip to common code
RCINT: MOVE T0,[.NSFRI,,3] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
MOVEI T0,@2(A) ;Get address of connect block
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore errors
POPJ P, ;Return to caller
PRGEND
TITLE RDCNT
SUBTTL Read Disconnect Data
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads the disconnect reason and
; optional data from the remote when it disconnects.
;
; The function is only legal from the "disconnect
; received" (.NSSDR) state and no change of state
; occurs.
;
; Usage: CALL RDCNT(chan,stat[,strbuf])
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The next
; word gets the resulting network status in the
; high half and the NSP. error code or reason
; code for disconnect (if success) in the low
; half.
;
; strmsg Optional integer array to get possible message
; from remote partner. The first word in the
; array must be set with the size of the array.
; The message will be returned in NSP string
; notation.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RDCNT
RDCNT: MOVE T0,[.NSFRD,,4] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
CAIGE AN,3 ;Do we have optional data
JRST RDC.1 ; No, continue
MOVEI T0,@2(A) ;Yes, Get address of string pointer
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
RDC.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
JRST RDC.2 ;Exit on an error
MOVE T0,.NSAA2(NS) ;Get the disconnect reason
HRRM T0,1(EA) ; and store in status block
RDC.2: POPJ P, ;Return to caller
PRGEND
TITLE RECNTW
SUBTTL Receive a Message
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine receives an incomming message from
; a remote node. The link must be in the "running
; (.NSSRN) state to issue this call.
;
; Whole messages are always received. If a blocking
; receive (RECNTW) is issued, the routine will wait
; until an entire message is received, the user buffer
; is filled, or a network error occurs. If the non-
; blocking (RECNT) is issued, the routine will return
; success immediately if no data is currently available
; but with a byte count of zero in the status. If any
; data is received, the routine will block until the
; entire message is received.
;
; Usage: CALL RECNT[W] (chan,stat,msgsiz,msgbuf)
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The
; second word gets the resulting network status
; in the high half and the NSP. error code or
; bytes received (if success) in the low half.
;
; msgsiz Integer variable or value with size of receive
; message in 8-bit bytes.
;
; msgbuf Integer array to receive message. Must be at
; least (msgsiz/4)+1 in size.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RECNTW
ENTRY RECNT
RECNTW: MOVE T0,[NS.WAI+NS.EOM+<.NSFDR,,4>] ;Get function code,,size
SKIPA ; and continue
RECNT: MOVE T0,[.NSFDR,,4] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
MOVE T1,@2(A) ;Get size of block
MOVEM T1,.NSAA1(NS) ;Store size of buffer
MOVEI T1,@3(A) ;Get address of buffer
ADD T1,[POINT 8,,] ;Form 8-bit byte pointer
MOVEM T1,.NSAA2(NS) ;Store byte pointer to buffer
REC.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
JRST REC.3 ; Exit on any error
MOVE T0,.NSAFN(NS) ;Get the function and flags
TDOE T0,[NS.WAI] ;Was this a blocking request?
JRST REC.2 ; Yes, exit with buffer
MOVE T1,@2(A) ;Get size of buffer
CAMN T1,.NSAA1(NS) ;Were any bytes input?
JRST REC.2 ; No, just exit with zero transfer
TDOE T0,[NS.EOM] ;Was a complete message received?
JRST REC.2 ; Yes, exit with complete transfer
MOVEM T0,.NSAFN(NS) ;Set function for wait, full message
JRST REC.1 ; and reissue input.
REC.2: MOVE T1,@2(A) ;Get size of buffer
SKIPLE .NSAA1(NS) ;Skip if full or overrun
SUB T1,.NSAA1(NS) ;Get size of bytes transferd
HRRM T1,1(EA) ;Store the size transfered
REC.3: POPJ P, ;Return to caller
PRGEND
TITLE REJNT
SUBTTL Reject an Incoming Connect
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine rejects an incoming connect from
; a remote node.
;
; The link must be in the "connect receive" (.NSSCR)
; state to issue this call. The channel is released
; if this UUO is successful.
;
; Usage: CALL REJNT (chan,stat[,strmsg])
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The
; second word gets the resulting network status
; in the high half and the NSP. error code or
; zero if success in the low half.
;
; strmsg Integer array containing optional message in
; NSP. string block notation (see BOPT).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY REJNT
REJNT: MOVE T0,[.NSFRJ,,2] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
CAIGE AN,3 ;Do we have optional data
JRST REJ.1 ; No, skip optional data handling
MOVEI T0,@2(A) ;Get address of block
MOVEM T0,.NSAA1(NS) ;Store pointer to optional data
AOS .NSAFN(NS) ;and bump number of arguments
REJ.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore any errors
POPJ P, ;Return to caller
PRGEND
TITLE RLSNT
SUBTTL Release Channel
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine releases the DECnet/10 channel. This
; function can only be issued if the link is in the
; the "connect wait" (.NSSCW), "disconnect received"
; (.NSSDR), or "disconnect confirmed" (.NSSDC) states.
;
; Usage: CALL RLSNT[W] (chan,stat)
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The
; second word gets the resulting network status
; in the high half and the NSP. error code or
; zero if success in the low half.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RLSNT
RLSNT: MOVE T0,[.NSFRL,,2] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore any errors
POPJ P, ;Return to caller
PRGEND
TITLE RXINTW
SUBTTL Recieve an Interrupt Message
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine receives am interrupt message from a
; remote node. The link must be in the "running (.NSSRN)
; state to issue this call.
;
; Usage: CALL RXINT[W] (chan,stat,strbuf)
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The
; second word gets the resulting network status
; in the high half and the NSP. error code or
; zero if success in the low half.
;
; strbuf Integer array that will receive NSP. string
; block format message (see BOPT). The first
; word in array must be set to size of array.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RXINTW
ENTRY RXINT
RXINTW: MOVE T0,[NS.WAI+<.NSFIR,,3>] ;Get function code,,size
SKIPA ; and continue
RXINT: MOVE T0,[.NSFIR,,3] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
MOVEI T1,@2(A) ;Get address of buffer
MOVEM T1,.NSAA1(NS) ;Store pointer to buffer
PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ;Ignore any errors
POPJ P, ;Return to caller
PRGEND
TITLE SNDNTW
SUBTTL Send a Message
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine sends a message to a remote node. The
; link must be in the "running (.NSSRN) state to issue
; this call.
;
; Whole messages are always transmitted. If a blocking
; send (SNDNTW) is issued, the routine will wait until
; an entire message is transmitted or a network error
; occurs. If the non-blocking (SNDNT) is issued, the
; routine will return success immediately if no data is
; currently transmitted but with a byte count of zero.
; If any data is sent, the routine will block until the
; entire message is tranmitted.
;
; Usage: CALL SNDNT[W] (chan,stat,msgsiz,msgbuf)
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The
; second word gets the resulting network status
; in the high half and the NSP. error code or
; bytes transfered (if success) in the low half.
;
; msgsiz Integer variable or value with size of message
; in 8-bit bytes.
;
; msgbuf Integer array to send to remote node. Must be
; at least (msgsiz/4)+1 in size.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY SNDNTW
ENTRY SNDNT
SNDNTW: MOVE T0,[NS.WAI+NS.EOM+<.NSFDS,,4>] ;Get function code,,size
SKIPA ; and continue
SNDNT: MOVE T0,[NS.EOM+<.NSFDS,,4>] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
MOVE T1,@2(A) ;Get size of block
MOVEM T1,.NSAA1(NS) ;Store size of buffer
MOVEI T1,@3(A) ;Get address of buffer
ADD T1,[POINT 8,,] ;Form 8-bit byte pointer
MOVEM T1,.NSAA2(NS) ;Store byte pointer to buffer
SND.1: PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
JRST SND.3 ; Exit on any error
MOVE T0,.NSAFN(NS) ;Get the function and flags
TDOE T0,[NS.WAI] ;Was this a blocking request?
JRST SND.2 ; Yes, exit with buffer
MOVE T1,@2(A) ;Get size of buffer
CAMN T1,.NSAA1(NS) ;Were any bytes transmitted?
JRST SND.2 ; No, just exit with zero transfer
SKIPN .NSAA1(NS) ;Was entire message sent?
JRST SND.2 ; Yes, exit with complete transfer
MOVEM T0,.NSAFN(NS) ;Set function for wait, full message
JRST SND.1 ; and reissue send.
SND.2: MOVE T1,@2(A) ;Get size of buffer
SKIPLE .NSAA1(NS) ;Skip if full or overrun
SUB T1,.NSAA1(NS) ;Get size of bytes transferd
HRRM T1,1(EA) ;Store the size transfered
SND.3: POPJ P, ;Return to caller
PRGEND
TITLE STSNT
SUBTTL Get Network Status
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine gets the status for the given channel.
;
; Usage: CALL STSNT (chan,stat[,segsiz[,flow]])
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The
; second word gets the resulting network status
; in the high half and the NSP. error code or
; zero if success in the low half.
;
; segsize Optional integer variable to return segment
; size for this link.
;
; flow Optional integer variable to return remote
; flow control in high half and local flow
; control in low half.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY STSNT
STSNT: MOVE T0,[.NSFRS,,4] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ; Ignore any errors
MOVE T0,.NSAA1(NS) ;Get the segment size
CAIL AN,3 ;Is segment argument present
MOVEM T0,@2(A) ;Return segment size
MOVE T0,.NSAA2(NS) ;Get flow control
CAIL AN,4 ;Is flow argument present
MOVEM T0,@3(A) ;Return flow argument
POPJ P, ;Return to caller
PRGEND
TITLE SXINTW
SUBTTL Send a Interrupt Message
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine sends a interrupt message to a remote
; mode. The link must be in the "running (.NSSRN) state
; to issue this call.
;
; Usage: CALL SXINT[W] (chan,stat,strbuf)
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; stat Two-word integer array to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure. The
; second word gets the resulting network status
; in the high half and the NSP. error code or
; zero if success in the low half.
;
; strbuf Integer array in NSP. string block format to
; to send to remote node. Message cannot be
; larger than 16 bytes (see BOPT).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY SXINTW
ENTRY SXINT
SXINTW: MOVE T0,[NS.WAI+<.NSFIS,,3>] ;Get function code,,size
SKIPA ; and continue
SXINT: MOVE T0,[.NSFIS,,3] ;Get function code,,size
PUSHJ P,NSPA..## ;Setup for NSP. call.
MOVEI T1,@2(A) ;Get address of buffer
MOVEM T1,.NSAA1(NS) ;Store pointer to buffer
PUSHJ P,NSPU..## ;Issue NSP. UUO and process errors
SKIP ;Ignore any errors
POPJ P, ;Return to caller
PRGEND
TITLE BCON
SUBTTL Build an Initial Connect Block
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine intialized the given array in NSP
; connect block format, including the space for the
; various string fields. This call must proceed any
; BSRC, BDST, BNOD, BUID, BPWD, BACC, or BDAT calls.
;
; Usage: CALL BCON (conblk)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block. This array will be initialized with
; a dummy structure that has empty string
; pointers of full size.
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
T3=3 ;Temporary AC
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
R=1B0 ;Relocate address
ENTRY BCON
BCON: MOVEI T1,@0(A) ;Get address of user connect block
MOVE T2,[-LEN,,CONBLK] ;Get length, address of dummy block
BCON.1: HRRZ T3,(T2) ;Get template word
SKIPGE (T2) ;Get next word in block
ADDI T3,@0(A) ; Add in start of array
MOVEM T3,(T1) ;Store in user array
AOS T1 ;Bump the array pointer
AOBJN T2,BCON.1 ; and loop till done
POPJ P, ;Return to caller
CONBLK:
PHASE 0
XWD 0,10 ;(.NSCNL) Length of argument block
EXP NOD!R ;(.NSCND) Node name string pointer
EXP SRCDSC!R ;(.NSCND) Source process pointer
EXP DSTDSC!R ;(.NSCDD) Destination process pointer
EXP UID!R ;(.NSCUS) User-id string pointer
EXP PWD!R ;(.NSCPW) Password string pointer
EXP ACC!R ;(.NSCAC) Account string pointer
EXP DAT!R ;(.NSCUD) User data string pointer
SRCDSC: XWD 0,5 ;(.NSDSL) Source process descriptor
EXP 0 ;(.NSDFM) Format type (0,1,2)
EXP 0 ;(.NSDOB) Object type (0-255)
XWD 0,0 ;(.NSDPP) PPN in half words
EXP SRC!R ;(.NSDPN) Source process name
DSTDSC: XWD 0,5 ;(.NSDSL) Destination process descriptor
EXP 0 ;(.NSDFM) Format type (0,1,2)
EXP 0 ;(.NSDOB) Object type (0-255)
XWD 0,0 ;(.NSDPP) PPN in half words
EXP DST!R ;(.NSDPN) Destination process name
NOD: XWD 0,3 ;Node name string
BLOCK 2
SRC: XWD 0,5 ;Source process string
BLOCK 4
DST: XWD 0,5 ;Destination process string
BLOCK 4
UID: XWD 0,13 ;User-ID string
BLOCK 12
PWD: XWD 0,13 ;Password string
BLOCK 12
ACC: XWD 0,13 ;Account string
BLOCK 12
DAT: XWD 0,5 ;User data string
BLOCK 4
LEN:
DEPHASE
PRGEND
TITLE BNOD
SUBTTL Build Connect Block Nodename String
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine intialized the connect block with
; the given nodename string. The BCON routine must
; be called to initialize the connect block before
; this routine is called.
;
; Usage: CALL BNOD (conblk,stat,nodnam,nodlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; nodnam String with node name to store in connect
; block. If present, may have size of 1-6
; characters.
;
; nodlen Number of characters in nodnam or -1 if
; name is self-counting (ASCIZ).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY BNOD
BNOD: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get nodename string
MOVE T2,@3(A) ;Get nodename string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCND(W1) ;Get address of nodename block
MOVE W2,[^D6,,^D3] ;Get maximum size of string,,block
PUSHJ P,NSPS..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE BUID
SUBTTL Build User-ID Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine intialized the access user-id control
; field in a Fortan connect block. The BCON routine must
; be called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL BUID (conblk,stat,uidnam,uidlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; uidnam String with user-id to store in connect block
; String may have have size of 1-39 characters.
;
; uidlen Number of characters in uidnam or -1 if string
; is self-counting (ASCIZ).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY BUID
BUID: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get user-id string
MOVE T2,@3(A) ;Get user-id string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCUS(W1) ;Get address of user-id block
MOVE W2,[^D39,,^D11] ;Get maximum size of string,,block
PUSHJ P,NSPS..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE BPWD
SUBTTL Build Password Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine intialized the access password control
; field in a Fortan connect block. The BCON routine must
; be called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL BPWD (conblk,stat,pwdnam,pwdlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; pwdnam String with password to store in connect block
; String may have have size of 1-39 characters.
;
; pwdlen Number of characters in uidnam or -1 if string
; is self-counting (ASCIZ).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY BPWD
BPWD: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get password string
MOVE T2,@3(A) ;Get password string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCPW(W1) ;Get address of password block
MOVE W2,[^D39,,^D11] ;Get maximum size of string,,block
PUSHJ P,NSPS..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE BACC
SUBTTL Build Account Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine intialized the access account control
; field in a Fortan connect block. The BCON routine must
; be called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL BACC (conblk,stat,accnam,acclen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; accnam String with account to store in connect block
; String may have have size of 1-39 characters.
;
; acclen Number of characters in accnam or -1 if string
; is self-counting (ASCIZ).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY BACC
BACC: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get account string
MOVE T2,@3(A) ;Get account string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCAC(W1) ;Get address of account block
MOVE W2,[^D39,,^D11] ;Get maximum size of string,,block
PUSHJ P,NSPS..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE BDAT
SUBTTL Build User Data Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine intialized the user data control field
; in a Fortan connect block. The BCON routine must be
; called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL BDAT (conblk,stat,datnam,datlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; datnam String with user date to store in connect block
; String may have have size of 1-16 characters.
;
; datlen Number of characters in datnam or -1 if string
; is self-counting (ASCIZ).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY BDAT
BDAT: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get user data string
MOVE T2,@3(A) ;Get user data string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCUD(W1) ;Get address of user data block
MOVE W2,[^D16,,^D5] ;Get maximum size of string,,block
PUSHJ P,NSPS..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE BOPT
SUBTTL Build Optional Data Buffer
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine setups a 5-word integer array with a
; optional message buffer that can be used with various
; NSP functions (DSCNT, ABTNT, REJNT, ACCNT).
;
; Usage: CALL BOPT (optblk,stat,optmsg,optlen)
;
; Arguments: optblk Integer 5-word array to receive optmsg string.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; optmsg String with user data to store in optblk.
; String may have have size of 1-16 characters.
;
; optlen Number of characters in optmsg or -1 if string
; is self-counting (ASCIZ).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY BOPT
BOPT: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get user data string
MOVE T2,@3(A) ;Get user data string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCUD(W1) ;Get string pointer
MOVE W2,[^D16,,^D5] ;Get maximum size of string,,block
PUSHJ P,NSPS..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE BSRC
SUBTTL Build Source/Destination Process Descriptor
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine builds either the source or destination
; process descriptors used for the Fortran NSP connect
; block. The BCON routine must be called before these
; routines.
;
; Usage: CALL BSRC (conblk,stat,fmt,obj,[pronam,prolen[,ppn]])
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; fmt Descriptor format type (0,1,or 2).
;
; obj Object type for descriptor. Must be 1-255 if
; fmt type 0 and 0 if fmt 1 or 2.
;
; pronam String with process name to store in the
; descriptor. string may have have size of
; 1-16 characters and is not used for fmt 0.
;
; prolen Number of characters in pronam or -1 if string
; is self-counting (ASCIZ).
;
; ppn PPN to use for descriptor, stored in half-word
; format. Only used for fmt 2.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY BSRC
ENTRY BDST
BSRC: MOVEI T1,.NSCSD ;Get source descriptor offset
SKIPA ; and continue
BDST: MOVEI T1,.NSCDD ;Get destination descriptor offset
MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
ADDI T1,@0(A) ;Get address of descriptor pointer
MOVEI W1,@(T1) ;Get address of descriptor block
SETZM .NSDFM(W1) ;Zero any preexisting values
SETZM .NSDOB(W1) ;Zero any preexisting values
SETZM .NSDPP(W1) ;Zero any preexisting values
SKIPE T1,@2(A) ;Get the format type
JRST BSRC.1 ; Jump if non-zero
SKIPN T2,@3(A) ;Get the object type
JRST BSRC.E ; If zero, error
MOVEM T2,.NSDOB(W1) ;Store the object type
POPJ P, ;Return to caller
BSRC.1: MOVEM T1,.NSDFM(W1) ;Store the descriptor type
SKIPE T2,@3(A) ;Get the object type
JRST BSRC.E ; If non-zero, error
CAIN T1,1 ;Is this format type 1
JRST BSRC.2 ; Jump if yes
CAIE T1,2 ;Is this format type 2
JRST BSRC.E ; If not, error
MOVE T1,6(A) ;Get the PPN
MOVEM T1,.NSDPP(W1) ; and store in the block
BSRC.2: MOVEI T1,4(A) ;Get user data string
MOVE T2,@5(A) ;Get user data string size
MOVE W1,.NSDPN(W1) ;Get start of process name
MOVE W2,[^D16,,^D5] ;Get maximum size of string,,block
PUSHJ P,NSPS..## ;Construct string block
POPJ P, ;Return to caller
BSRC.E: SETZM (EA) ;Flag setup error
POPJ P, ;Return to caller
PRGEND
TITLE RNOD
SUBTTL Read Connect Block Nodename String
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads the nodename string from the
; the given connect block. The BCON routine must be
; called to initialize the connect block before this
; routine is called.
;
; Usage: CALL RNOD (conblk,stat,nodnam,nodlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1)
; for success and .FALSE. (0) for failure.
;
; nodnam String to return nodenode string. Nodenames can
; be up to 6 characters in length.
;
; nodlen Number of characters allowed in nodnam or
; -1 if name is self-counting (ASCIZ). If the
; length is insufficent for the actual node
; name, an error is returned. If too large,
; nodnam will be blank filled.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RNOD
RNOD: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get nodename string
MOVE T2,@3(A) ;Get nodename string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCND(W1) ;Get address of nodename block
PUSHJ P,NSPR..## ;Return string block
POPJ P, ;Return to caller
PRGEND
TITLE RUID
SUBTTL Read User-ID Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads the access user-id control field
; in a Fortan connect block. The BCON routine must be
; called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL RUID (conblk,stat,uidnam,uidlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; uidnam String to return user-id. User-id can
; be up to 39 characters in length.
;
; uidlen Number of characters allowed in uidnam or
; -1 if name is self-counting (ASCIZ). If the
; length is insufficent for the actual user-id
; an error is returned. If too large, uidnam
; will be blank filled.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RUID
RUID: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get user-id string
MOVE T2,@3(A) ;Get user-id string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCUS(W1) ;Get address of user-id block
PUSHJ P,NSPR..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE RPWD
SUBTTL Read Password Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads the access password control
; field in a Fortan connect block. The BCON routine must
; be called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL RPWD (conblk,stat,pwdnam,pwdlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; pwdnam String to return password. Pasword can
; be up to 39 characters in length.
;
; pwdlen Number of characters allowed in pwdnam or
; -1 if name is self-counting (ASCIZ). If the
; length is insufficent for the actual password
; an error is returned. If too large, pwdnam
; will be blank filled.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RPWD
RPWD: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get password string
MOVE T2,@3(A) ;Get password string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCPW(W1) ;Get address of password block
PUSHJ P,NSPR..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE RACC
SUBTTL Read Account Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads the access account control
; field in a Fortan connect block. The BCON routine must
; be called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL RACC (conblk,stat,accnam,acclen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; accnam String to return account. Account can
; be up to 39 characters in length.
;
; acclen Number of characters allowed in accnam or
; -1 if name is self-counting (ASCIZ). If the
; length is insufficent for the actual account
; an error is returned. If too large, accnam
; will be blank filled.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RACC
RACC: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get account string
MOVE T2,@3(A) ;Get account string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCAC(W1) ;Get address of account block
PUSHJ P,NSPR..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE RDAT
SUBTTL Read User Data Control Information
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads the user data control field
; in a Fortan connect block. The BCON routine must be
; called prior to this routine to initial the 69-word
; connect block array.
;
; Usage: CALL RDAT (conblk,stat,datnam,datlen)
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; datnam String to return user data. User data can
; be up to 16 characters in length.
;
; datlen Number of characters allowed in datnam or
; -1 if name is self-counting (ASCIZ). If the
; length is insufficent for the actual user data
; an error is returned. If too large, datnam
; will be blank filled.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RDAT
RDAT: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get user data string
MOVE T2,@3(A) ;Get user data string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCUD(W1) ;Get address of user data block
PUSHJ P,NSPR..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE ROPT
SUBTTL Read Optional Data Buffer
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads an optional message buffer and
; returns the ASCII data. It should only be used to
; change from the 8-bit to 7-bit format for ASCII.
;
; Usage: CALL ROPT (optblk,stat,optmsg,optlen)
;
; Arguments: optblk Integer 5-word array to read optmsg string.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; optmsg String to return string from optblk.
; String may have have size of 1-16 characters.
;
; optlen Number of characters in optmsg or -1 if string
; is self-counting (ASCIZ). If insufficient space
; for message, an error will be returned.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY ROPT
ROPT: MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
MOVEI T1,2(A) ;Get user data string
MOVE T2,@3(A) ;Get user data string size
MOVEI W1,@0(A) ;Get start of connect block
MOVE W1,.NSCUD(W1) ;Get string pointer
PUSHJ P,NSPR..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE RSRC
SUBTTL Read Source/Destination Process Descriptor
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This subroutine reads either the source or destination
; process descriptors used for the Fortran NSP connect
; block. The BCON routine must be called before these
; routines.
;
; Usage: CALL RSRC (conblk,stat,fmt,obj,[pronam,prolen[,ppn]])
;
; Arguments: conblk Integer 69-word array to use as NSP connect
; block.
;
; stat Integer variable to receive status of
; operation. First word is set .TRUE. (-1) for
; success and .FALSE. (0) for failure.
;
; fmt Integer variable to receive descriptor format
; type (0,1,or 2).
;
; obj Integer variable to receive object type for
; descriptor.
;
; pronam String to return with process name in the
; descriptor. String may have have size of
; 1-16 characters and is not used for fmt 0.
;
; prolen Number of characters in pronam or -1 if string
; is self-counting (ASCIZ).
;
; ppn Integer variable to receive PPN for descriptor,
; stored in half-word format.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY RSRC
ENTRY RDST
RSRC: MOVEI T1,.NSCSD ;Get source descriptor offset
SKIPA ; and continue
RDST: MOVEI T1,.NSCDD ;Get destination descriptor offset
MOVEI EA,@1(A) ;Get error block address
SETOM 0(EA) ;Preset to success
ADDI T1,@0(A) ;Get address of descriptor pointer
MOVEI W1,@(T1) ;Get address of descriptor block
MOVE T1,.NSDFM(W1) ;Get format type
MOVEM T1,@2(A) ;Return format type
MOVE T1,.NSDOB(W1) ;Get object type
MOVEM T1,@3(A) ;Return object type
MOVE T1,.NSDPP(W1) ;Get ppn
MOVEM T1,@6(A) ;Return ppn value
MOVEI T1,4(A) ;Get user data string
MOVE T2,@5(A) ;Get user data string size
MOVE W1,.NSDPN(W1) ;Get start of process name
PUSHJ P,NSPR..## ;Construct string block
POPJ P, ;Return to caller
PRGEND
TITLE ISTAST
SUBTTL Check link state status
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This function checks the current channel state against
; a given list of states and returns a Fortran index to
; the matching state or a zero if no state matches. The
; result can be used in a computed GOTO or other areas.
;
; Usage: ivar = ISTAST(chan,state1[,state2,...staten])
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
; staten Integer variable or value corresponding to
; DECnet/10 link states.
;
; Returns ivar set to one (1) if current link state matches state1, two
; (2) if matches state2, and so forth. If no matches, set ivar to zero.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY ISTAST
ISTAST: MOVE T1,@0(A) ;Get the channel number
HRRZM T1,STABLK+.NSACH ; and store in NSP. block
MOVEI T1,STABLK ;Get status NSP. block
NSP. T1, ;Get the current link status
JRST ISTA.2 ; UUO failed, return false
MOVE T1,STABLK+.NSACH ;Get current channel status
AND T1,[NS.STA] ;Get just state field
MOVS T1,T1 ; and position in low part
HLL A,-1(A) ;Get number of arguments
SETZ T0, ;Set index to zero
ISTA.1: AOBJP A,ISTA.2 ;Skip first argument
AOS T0 ;Count the argument
CAME T1,0(A) ;Is this the correct state
JRST ISTA.1 ; No, continue check
SKIPA ;Skip to return
ISTA.2: SETZ T0, ;Return not found
POPJ P, ;Return to caller
STABLK: XWD .NSFRS,2
XWD 0,0
PRGEND
TITLE I???ST
SUBTTL Check link data status
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: These functions check various data status for a DECnet
; channel and return .TRUE. (-1) or .FALSE. (0) values.
; The four routines correspond to the available NSP.
; status indicators:
;
; IRECST(chan) returns .TRUE. if normal data is
; available to read (NS.NDA).
;
; IRXIST(chan) returns .TRUE. if interrupt data is
; available to read (NS.IDA).
;
; ISNDST(chan) returns .TRUE. if buffers are available
; to send normal data to remote (NS.NDR).
;
; ISXIST(chan) returns .TRUE. if buffers are available
; to send interrupt message (NS.IDR).
;
; Usage: ivar = IxxxST(chan)
;
; Arguments: chan Integer variable with DECnet channel number
; that was returned by active or passive network
; connect requests (CONNT/PASNT).
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY IRECST
ENTRY IRXIST
ENTRY ISNDST
ENTRY ISXIST
IRECST: MOVE T1,[NS.NDA] ;Set status bit to test
JRST ICHKST ; and continue in common
IRXIST: MOVE T1,[NS.IDA] ;Set status bit to test
JRST ICHKST ; and continue in common
ISNDST: MOVE T1,[NS.NDR] ;Set status bit to test
JRST ICHKST ; and continue in common
ISXIST: MOVE T1,[NS.IDR] ;Set status bit to test
ICHKST: PUSH P,T2 ;Save a worker
SETZ T0, ;Set return to .FALSE.
MOVE T2,@0(A) ;Get the channel number
HRRZM T2,CHKBLK+.NSACH ; and store in NSP. block
MOVEI T2,CHKBLK ;Get status NSP. block
NSP. T2, ;Get the current link status
JRST ICHK.1 ; UUO failed, return false
TDNE T1,CHKBLK+.NSACH ;Is the desired status set?
SETO T0, ;Yes, return true
ICHK.1: POP P,T2 ;Restore worker
POPJ P, ;Return to caller
CHKBLK: XWD .NSFRS,2
XWD 0,0
PRGEND
TITLE NSPU..
SUBTTL Issue NSP UUO and Return Errors
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This internal routine issues a NSP UUO and does the
; Fortran error processing.
;
; Usage: PUSHJ P,NSPU..##
;
; Arguments: NS NSP. argument block pointer
; EA Address of error routine or zero.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
P=17 ;Push-down stack pointer
ENTRY NSPU..
NSPU..: AOS (P) ;Preset success return
SETOM 0(EA) ;Preset success return
SETZM 1(EA) ;Zero secondary status
MOVE T1,NS ;Copy NSP. data block
NSP. T1, ;Issue NSP. UUO
SKIPA ; Process the error
JRST NSPU.1 ;Continue in common code
SOS (P) ;Set failure return
SETZM 0(EA) ;Set failure return
HRRZM T1,1(EA) ;Return error status
MOVE T0,[.NSFRS,,2] ;Get read channel code
MOVEM T0,.NSAFN(NS) ; and store in argument block
MOVE T1,NS ;Copy NSP. data block
NSP. T1, ;Issue NSP. UUO
SKIP ; Ignore any errors
NSPU.1: HLL T1,.NSACH(NS) ;Get status for network
HLLM T1,1(EA) ; and return to caller
POPJ P, ;Return to caller
PRGEND
TITLE NSPA..
SUBTTL Setup NSP. UUO Block
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This internal routine sets up the NSP. UUO block
; from the standard Fortran call.
;
; Usage: PUSHJ P,NSPA..##
;
; Arguments: T0 NSP. function code,,default length
;
; Routine returns address of NSP. data block in NS, address (if any)
; of error return in EA, and positive number of Fortran arguments in
; NA. Expects calls in format:
;
; CALL xxxNT[W] (chan,stat[,...])
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
AN=13 ;Number of Fortran arguments
NS=14 ;NSP. argument block pointer
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY NSPA..
NSPA..: MOVEI NS,NSPBUF ;Get address of NSP. data block
MOVEM T0,.NSAFN(NS) ; and store function,,length
HLRE AN,-1(A) ;Get number of arguments
MOVN AN,AN ; and convert to positive
MOVEI EA,@1(A) ;Get address of error block
MOVE T0,@0(A) ;Get channel number
MOVEM T0,.NSACH(NS) ; and store in NSP. data block
SETZM .NSAA1(NS) ;Zero rest of block
SETZM .NSAA2(NS) ; ...
SETZM .NSAA3(NS) ; ...
POPJ P, ;Return to caller
NSPBUF: BLOCK 5 ;NSP. UUO buffer
PRGEND
TITLE NSPS..
SUBTTL Setup NSP. String Block
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This internal routine sets up the NSP. string block.
;
; Usage: PUSHJ P,NSPS..##
;
; Arguments: T1 Address of user string
; T2 Length of string or -1 if ASCIZ
; W1 Address of NSP string block buffer
; W2 Maximum characters,,string block size
; EA Address of error return variable.
;
; Routine gets address of string, checks for valid length, and copies
; 7-bit ASCII into 8-bit NSP. string block. Will return .FALSE. (0) if
; length error seen. Null strings are allowed.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY NSPS..
NSPS..: PUSH P,T2 ;Save string length
PUSHJ P,CKSA..## ;Get type for format string
CAIN T0,15 ;Check of F77 string
MOVEM T2,(P) ; Set F77 string length
POP P,T2 ;Restore string length
JUMPGE T2,NSPS.2 ;Do we need to count string?
PUSH P,T1 ;Save pointer
SETZ T2, ;Zero the counter
NSPS.1: ILDB T0,T1 ;Get next byte
SKIPE T0 ;Skip of no more
AOJA T2,NSPS.1 ; Loop till done
POP P,T1 ;Restore pointer
NSPS.2: HLRZ T0,W2 ;Get maximum size of string
CAMLE T2,T0 ;Is the size in range?
JRST NSPS.E ; No, take error exit
HRRM W2,.NSASL(W1) ;Put size of field in words
HRLM T2,.NSASL(W1) ;Put actual character count
HRRZ W1,W1 ;Wipe upper half of word
ADD W1,[POINT 8,.NSAST,] ;Update address and form byte pointer
NSPS.3: SOJL T2,NSPS.S ;Count a move and exit when done
ILDB T0,T1 ;Get next character
IDPB T0,W1 ;Store in the byte field
JRST NSPS.3 ; and loop till finished
NSPS.E: SETZM (EA) ;Set bad return
NSPS.S: POPJ P, ;Return to caller
PRGEND
TITLE NSPR..
SUBTTL Read NSP. String Block
SEARCH UUOSYM
;
; Author: R. W. Stamerjohn, MAPC DEC-10 Systems Group
; Written: 25-Apr-83
;
;+
; Purpose: This internal routine reads NSP. string block.
;
; Usage: PUSHJ P,NSPR..##
;
; Arguments: T1 Address of user string
; T2 Length of string or -1 if ASCIZ
; W1 Address of NSP string block buffer
; EA Address of error return variable.
;
; Routine gets address of string, checks for valid length, and copies
; 8-bit NSP. string block into 7-bit ASCII. Will return .FALSE. (0) if
; length error seen. Null strings are allowed.
;
;-
; Register Definition:
;
T0=0 ;Temporary AC
T1=1 ;Temporary AC
T2=2 ;Temporary AC
W1=3 ;Worker AC
W2=4 ;Worker AC
EA=15 ;Address of error return block or zero
A=16 ;Fortran argument block pointer
P=17 ;Push-down stack pointer
ENTRY NSPR..
NSPR..: MOVE W2,T2 ;Save string length
PUSHJ P,CKSA..## ;Get type for format string
CAIN T0,15 ;Check if F77 string
MOVEM T2,W2 ; Set F77 string length
SKIPGE W2 ;Skip if size specified
MOVE W2,T2 ;Get size from call
HLRZ T2,.NSASL(W1) ;Get field character count
HRRZ W1,W1 ;Wipe any upper halfword stuff
ADD W1,[POINT 8,.NSAST,] ;Update address and form byte pointer
NSPR.1: SOJL T2,NSPR.2 ;Count char to move and jump if none
SOJL W2,NSPR.E ;Count char to move and jump if none
ILDB T0,W1 ;Get next byte
IDPB T0,T1 ;Store byte in user string
JRST NSPR.1 ; and loop
NSPR.2: MOVEI T0,40 ;Get blank
NSPR.3: SOJL W2,NSPR.S ;Count char to move and jump if none
IDPB T0,T1 ;Blank fill the rest.
JRST NSPR.3 ; and loop
NSPR.E: SETZM (EA) ;Set bad return
NSPR.S: POPJ P, ;Return to caller
END