Trailing-Edge
-
PDP-10 Archives
-
tops10and20_integ_tools_v9_3-aug-86
-
70,6067/tell10/tell.mac
There are 4 other files named tell.mac in the archive. Click here to see a list.
SEARCH MACROS
$TITLE TELL,<Tell InterFace for DECnet-10>
SUBTTL L.E.Snyder 22-Dec-1983
EXTERN FAO,CMARG,CMCMPR
;
; This program implements the TELL command for the DEC-10. It
; allows a user to send an access control string and a single
; command line to a remote system, where it is parsed and
; executed, the results coming back.
;
TELVER== 000000,,000003 ;(3)
LOC 137
EXP TELVER
RELOC
COMMENT &
REVISION HISTORY
[1] 22-Dec-1983 Initial version, unleashed upon an unsuspecting
Monsanto Ag Research user community.
[2] 20-Apr-1984 Made the TMPCOR stuff unreadable by way of a SECRET
encryption algorithm that only a child could figure
out. Actually, bytes are merely rotated a bit...
[3] 19-Jun-84 By Michael W. Smith.
Add continuation line capability.
This was needed to pass long commands thru
under BATCH with out truncation.
Area changed was RSCLU?:
& ;End comment
SUBTTL Internal Equivalences
STKSIZ== 300 ;Size of the stack
CMDBFS== ^D200 ;Max command length
RECSIZ== 32 ;Each TMPCOR record has 2 words sixbit plus 30 data
RECMAX== ^D18 ;Most records per user
RCVLEN== ^D200 ;Length of recevice buffer
CR== 15
BELL== 7
CTLZ== 32
ALT== 33
LF== 12
FF== 14
TELOBJ== ^D198 ;Object type
LOGCHN== 1 ;Channel to log activities on
SUBTTL Low Segment Shtuff
RELOCL
STACK: BLOCK STKSIZ ;The stack
CMDLIN: BLOCK <CMDBFS/5>+1 ;Buffer for command line
CONBLK: BLOCK .NSCAC+1 ;Connect block
NODNAM: BLOCK 1+<6/4>+1 ;String block for node name
USERID: BLOCK 1+<^D39/4>+1 ;String block for user ID
PASWRD: BLOCK 1+<^D39/4>+1 ;String block for password
ACOUNT: BLOCK 1+<^D39/4>+1 ;String for account
SRCPDB: BLOCK .NSDPN+1 ;Source process descriptor block
DSTPDB: BLOCK .NSDPP+1 ;Destination process descriptor block
NSPBLK: BLOCK .NSAA3+1 ;Block for NSP. UUO
TCRBUF: BLOCK 1000 ;Buffer for TMPCOR file
RCVBUF: BLOCK <RCVLEN/5>+1 ;Buffer for data from remote
SRCNAM: BLOCK 5 ;Place for name
LOGFLG: BLOCK 1 ;Flags whether we are logging or not
LOGOBF: BLOCK .BFCTR+1 ;Buffer ring header for logfile
SUBTTL Startup
RELOCH
START:
JFCL ;Ignore CCL entry
RESET ;Clear the world
MOVE SP,[IOWD STKSIZ,STACK] ;Set up stack pointer
MOVE CF,SP ;Current frame pointer
MOVE PF,SP ;Previous frame pointer
MOVE CG,SP ;And current global pointer
$CALL TELL ;Do it
EXIT 1, ;Stop
EXIT ;...
SUBTTL TELL - The Main Routine
$ENTRY TELL
SETZM LOGFLG ;Assume we are not logging
MOVX R1,.IOASC ;Get ASCII mode
MOVE R2,[SIXBIT /TELL/] ;Get device name
MOVSI R3,LOGOBF ;Get buffer header address
OPEN LOGCHN,R1 ;Try to open it.....
JRST SKPLOG ;Failed, so forget the whole mess
MOVSI R3,'LOG' ;Get extension
SETZB R4,R5 ;Clear these
ENTER LOGCHN,R2 ;Create the file
JRST [MOVEI R1,LOGCHN ;Get channel
RESDV. R1, ;Forget it ever existed
RELEAS LOGCHN, ;Try this...
JRST SKPLOG] ;And go on
SETOM LOGFLG ;Remember we are logging
SKPLOG:
RESCAN ;Get back what was typed at the monitor
SKPINL ;Anything there?
JRST TELASK ;no, we have to ask
SETZ R7, ;Remember we got a command line
TELRLP:
MOVE R1,[POINT 7,CMDLIN] ;Set up pointer to command line
MOVEI R2,CMDBFS ;Get max chars allowed
RSCLUP:
INCHWL T1 ;Get a character (already there)
PUSHJ SP,LOGCHR ;Log it
CAIN T1,CR ;Carriage return?
JRST RSCLUP ;Yes, ignore it
CAIE T1,LF ;Line feed?
CAIN T1,ALT ;Or alt?
JRST RSCDON ;Yes, done
CAIE T1,CTLZ ;Control-Z?
CAIN T1,BELL ;Or bell?
JRST RSCDON ;Yes
CAIN T1,"-" ;Possible line continuation character
JRST RSCLU1 ;Yes, go check for cont. line
PUSHJ SP,RSCLU2 ;No, store the charcter
JRST RSCLUP ;And go back for more
RSCLU1: ;Here to check for proper line continuation character
;Must have "-CR" to qualify for continuation line
; then we must eat the LF (if supplied) and go back for next line
INCHWL T1 ;Get the next character
PUSHJ SP,LOGCHR ;Log it
MOVE T2,T1 ;Save character
CAIE T1,CR ;CR?
JRST [MOVEI T1,"-" ;No, get hyphen back
PUSHJ SP,RSCLU2 ;And save it
MOVE T1,T2 ;Restore character
PUSHJ SP,RSCLU2 ;And save it
JRST RSCLUP] ;Go back for rest
INCHWL T1 ;Get what should be a line feed
PUSHJ SP,LOGCHR ;Log it
CAIN T1,LF ;Is it what we think?
JRST RSCLUP ;Yes, Go back to main stream for next
; line of input
PUSHJ SP,RSCLU2 ;Not CRLF, funny but save it
JRST RSCLUP ;And go back for rest of next line
RSCLU2:
SOSL R2 ;Don't store too many
IDPB T1,R1 ;Ordinary character, store it
POPJ SP, ;Pop back
RSCDON:
SKIPGE R2 ;Did we get too much?
JRST [MOVEI T1,[ASCIZ /
%TELCTL - Command line too long - truncation occurred
/]
PUSHJ SP,TYPSTR ;Output it
JRST .+1] ;Proceed
MOVEI T1,0 ;Store a null
IDPB T1,R1 ;To end the string
MOVE R1,[POINT 7,CMDLIN] ;Reset string pointer
JUMPN R7,RSCDN1 ;We already parsed this, go on
$CALL CMARG,<R1,R2> ;Get an arg
JUMPN RS,TELASK ;Too short, ask
$CALL CMCMPR,<R2,<[SIXBIT /TELL/]>>;Compare them
JUMPE RS,RSCDN1 ;OK, go on
TELASK:
MOVEI T1,[ASCIZ /
TELL> /]
PUSHJ SP,TYPSTR ;Output it
SETO R7, ;Remember, we don't need "TELL"
JRST TELRLP ;Go and read infor
RSCDN1:
;
; Now we look for NODE["acct password"]:: string <EOL>
;
$CALL CMARG,<R1,R2> ;Get the argument
JUMPN RS,TELCME ;Oops, command error
MOVEM R2,NODNAM ;Store in here for now
PUSHJ SP,CHKALS ;Fix up any default stuff
$CALL CMARG,<R1,R2> ;Get next arg
JUMPN RS,TELCME ;Oops, error
CAME R2,[SIXBIT /"/] ;Start of access control string?
JRST CHKEN0 ;See if all done
;
; Here we parse it ourselves, storing info in the string block
;
MOVE R5,[POINT 8,USERID+1] ;Store the user ID in here
SETZ R6, ;Clear a counter
MOVEI R7,^D39 ;max chars allowed
IDLOOP:
ILDB T1,R1 ;Get a byte from here
JUMPE T1,TELCME ;Error if it ends here
CAIE T1,42 ;A double quote?
CAIN T1,40 ;A space?
JRST IDDONE ;Yes, done
SOJL R7,IDLOOP ;Ignore if too many
IDPB T1,R5 ;Store in string
AOJA R6,IDLOOP ;Loop on
IDDONE:
HRLZS R6 ;Get byte length LH
HRRI R6,<^D30/4>+2 ;Get word length in RH
MOVEM R6,USERID ;And store
CAIN T1,42 ;Did we end it?
JRST [ILDB T1,R1 ;Get another byte
CAIE T1,":" ;Colon?
JRST TELCME ;no, error
JRST CHKEN1] ;go on
MOVE R5,[POINT 8,PASWRD+1] ;Set up pointer into password block
SETZ R6, ;Clear this again
MOVEI R7,^D39 ;Get max chars allowed
PWLOOP:
ILDB T1,R1 ;Get another byte
JUMPE T1,TELCME ;Error if it ends here
CAIE T1,42 ;Double quote?
CAIN T1,40 ;Space?
JRST PWDONE ;Done here
SOJL R7,PWLOOP ;Loop on
IDPB T1,R5 ;Store in block
AOJA R6,PWLOOP ;Go on
PWDONE:
HRLZS R6 ;Get byte count in LH
HRRI R6,<^D39/4>+2 ;Get word count in RH
MOVEM R6,PASWRD ;Store in string block
CAIN T1,42 ;Did we end it?
JRST CHKEND ;Yes, all done
MOVE R5,[POINT 8,ACOUNT+1] ;Set up pointer to account string
SETZ R6, ;Clear this
MOVEI R7,^D39 ;Get length
ACLOOP:
ILDB T1,R1 ;Get a byte
JUMPE T1,TELCME ;Oops!
CAIN T1,42 ;End?
JRST ACDONE ;Yes
SOJL R7,ACLOOP ;Ignore too many
IDPB T1,R5 ;Store
AOJA R6,ACLOOP ;Loop on
ACDONE:
HRLZS R6 ;Get byte count in LH
HRRI R6,<^D39/4>+2 ;Get word count in RH
MOVEM R6,ACOUNT ;Store
CHKEND:
$CALL CMARG,<R1,R2> ;Get next arg
JUMPN RS,TELCME ;Oops!
CHKEN0:
CAME R2,[SIXBIT /:/] ;A match?
JRST TELCME ;Oops, no
CHKEN1:
$CALL CMARG,<R1,R2> ;Get next one
JUMPN RS,TELCME ;Bad one
CAME R2,[SIXBIT /:/] ;Match?
JRST TELCME ;No!
;
; All is well - now we convert sixbit node name into 8-bit format
;
MOVE R2,NODNAM ;Get name of node in sixbit
MOVE R3,[POINT 8,NODNAM+1] ;Get a place to store this stuff
SETZ R4, ;Count bytes here
PUSH SP,R1 ;Preserve R1 for later
NAMLUP:
SETZ R1, ;Clear a receiver
LSHC R1,6 ;Get a byte from R2
JUMPE R1,NAMDON ;Done here
ADDI R1,40 ;Make ASCII
IDPB R1,R3 ;Store in string
AOJA R4,NAMLUP ;Loop on
NAMDON:
POP SP,R1 ;Get R1 back
HRLZS R4 ;Get byte length in LH
HRRI R4,<6/4>+2 ;Get length in words in RH
MOVEM R4,NODNAM ;Store here
;
; Now we set up the connect block
;
MOVEI T1,.NSCAC+1 ;Get length of the block
MOVEM T1,CONBLK+.NSCNL ;Store
MOVEI T1,NODNAM ;Get address of node name
MOVEM T1,CONBLK+.NSCND ;Store in block
MOVEI T1,SRCPDB ;Get address of source process desc.
MOVEM T1,CONBLK+.NSCSD ;Store in block
; SETZM CONBLK+.NSCSD ;No source PDB
MOVEI T1,DSTPDB ;Get destination process desc. addr
MOVEM T1,CONBLK+.NSCDD ;Store in block
MOVEI T1,USERID ;Get address of user ID block
MOVEM T1,CONBLK+.NSCUS ;Store in block
MOVEI T1,PASWRD ;Get password string block
MOVEM T1,CONBLK+.NSCPW ;Store in block
MOVEI T1,ACOUNT ;Get account string block
MOVEM T1,CONBLK+.NSCAC ;Store in block
;
; Set up the source process block
;
MOVEI T1,.NSDPN+1 ;Get length of block
MOVEM T1,SRCPDB+.NSDFL ;Store
MOVEI T1,1 ;Use format 1
MOVEM T1,SRCPDB+.NSDFM ;Store
SETZM SRCPDB+.NSDOB ;No object type
SETZM SRCPDB+.NSDPP ;Nothing here, too
MOVEI T1,SRCNAM ;Get address of source name
MOVEM T1,SRCPDB+.NSDPN ;Store
MOVE T1,[BYTE (8) "T","E","L","L"] ;Get this
MOVEM T1,SRCNAM+1 ;Store here
MOVE T1,[4,,4] ;Set this up
MOVEM T1,SRCNAM ;Store
;
; Now we set up the destination process field
;
MOVEI T1,.NSDOB+1 ;We want only object type
MOVEM T1,DSTPDB+.NSDFL ;Store
MOVEI T1,0 ;Get format zero
MOVEM T1,DSTPDB+.NSDFM ;Store
MOVEI T1,TELOBJ ;Get object type
MOVEM T1,DSTPDB+.NSDOB ;Store
;
; Now do the enter active
;
MOVE T1,[NS.WAI+<.NSFEA,,.NSAA1+1>] ;Set up function,,length
MOVEM T1,NSPBLK+.NSAFN ;Store
SETZM NSPBLK+.NSACH ;Clear this
MOVEI T1,CONBLK ;Get address of connect block
MOVEM T1,NSPBLK+.NSAA1 ;Store
MOVEI T1,NSPBLK ;Get address of block
NSP. T1, ;Connect...
PUSHJ SP,NSPERR ;Oops, fatal error
;
; Remember R1? It points to whatever else the user typed...
; First we'll skip over any leading spaces...
;
CLRSPC:
MOVE T2,R1 ;Copy the pointer
ILDB T1,R1 ;Get a byte
CAIG T1," " ;Greater than a space?
JRST CLRSPC ;No, loop on
MOVE R1,T2 ;Point back to that non-space char
;
; Now make sure the channel is ready for the data...
;
RDYCHK:
MOVE T1,[NS.WAI+<.NSFRS,,.NSACH+1>];Prepare to read status
MOVEM T1,NSPBLK+.NSAFN ;Store in block
MOVEI T1,NSPBLK ;Prepare for it
NSP. T1, ;Do it...
PUSHJ SP,NSPERR ;oops!
MOVX T1,NS.NDR ;May I send data?
TDNN T1,NSPBLK+.NSACH ;???
JRST [MOVEI T1,1 ;Nope, get a second
SLEEP T1, ;And stall
JRST RDYCHK] ;Try again
;
; Now we have to count the bytes for good old DECnet....
;
MOVE T2,R1 ;Copy the byte pointer
SETZ R2, ;Clear a counter
ENDLUP:
ILDB T1,T2 ;Get a byte
JUMPE T1,.+2 ;OK, at the end
AOJA R2,ENDLUP ;Loop on
JUMPE R2,REDLUP ;No data? Hmmm.....
MOVEM R2,NSPBLK+.NSAA1 ;Store as byte count
MOVEM R1,NSPBLK+.NSAA2 ;Store Byte pointer
MOVE T1,[NS.WAI+<NS.EOM+<.NSFDS,,.NSAA2+1>>] ;Set up function,,length
MOVEM T1,NSPBLK+.NSAFN ;Store
SNDDAT:
MOVEI T1,NSPBLK ;Prepare to do it
NSP. T1, ;Send our little data out
PUSHJ SP,NSPERR ;Go handle the error
SKIPN NSPBLK+.NSAA1 ;Did we get rid of ALL bytes?
JRST REDLUP ;Yes, all is well
;
; Piddle!! That first UUO failed to get all of our bytes pushed
; out over the network. So let's sleep a second and try again...
;
MOVEI T1,1 ;Get a second
SLEEP T1, ;And wait
JRST SNDDAT ;And try again
;
; Now we wait to get stuff back from the remote...
;
REDLUP:
MOVE T1,[NS.WAI+<.NSFDR,,.NSAA2+1>] ;Set up function,,length
MOVEM T1,NSPBLK+.NSAFN ;Store
MOVEI T1,RCVLEN ;Get length of buffer
MOVEM T1,NSPBLK+.NSAA1 ;Store
MOVE T1,[POINT 7,RCVBUF] ;make a pointer to buffer
MOVEM T1,NSPBLK+.NSAA2 ;Store
MOVEI T1,NSPBLK ;Get address of block
NSP. T1, ;Wait...
PUSHJ SP,NSPERR ;Check this out..
MOVE T1,NSPBLK+.NSAA2 ;Get copy of byte pointer
MOVEI T2,0 ;Get a null
IDPB T2,T1 ;End it
MOVEI T1,RCVBUF ;Get address of data
PUSHJ SP,TYPSTR ;Output it to proper places
MOVE T1,NSPBLK+.NSAFN ;Get flags
TXNN T1,NS.EOM ;End of message?
JRST REDLUP ;No, go on
MOVEI T1,[ASCIZ /
/]
PUSHJ SP,TYPSTR ;Type it
JRST REDLUP ;Go on
DONE:
MOVE T1,[.NSFRL,,.NSACH+1] ;Get ready to release channel
DONE1:
MOVEM T1,NSPBLK+.NSAFN ;Store function word
MOVEI T1,NSPBLK ;Get address of block
NSP. T1, ;Do it
JFCL ;Oh well, ignore it
SKIPN LOGFLG ;Logging?
JRST DONE2 ;No go on
CLOSE LOGCHN, ;Close it
RELEAS LOGCHN, ;Release it
DONE2:
EXIT 1,
EXIT
TELCME:
OUTSTR [ASCIZ /
?TELCLE - Command line error
/]
EXIT 1,
EXIT
SUBTTL CHKALS - Here To Check For ALIAS Stuff
CHKALS:
SETZM TCRBUF ;Clear out the buffer
MOVE T1,[TCRBUF,,TCRBUF+1] ;...
BLT T1,TCRBUF+777 ;Zappo!
MOVE R4,[IOWD 776,TCRBUF] ;Prepare to read file
MOVSI R3,'DCN' ;Get TMPCOR name
MOVE R2,[.TCRRF,,R3] ;Set up the call
TMPCOR R2, ;OK?
POPJ SP, ;No TMPCOR, just return
MOVEI R4,RECMAX ;Get max entries allowed
MOVEI R2,TCRBUF ;Get address of the buffer
CHKTMP:
MOVE R3,(R2) ;Get sixbit logical name
CAMN R3,NODNAM ;Was that typed as node name?
JRST CHKTM1 ;Yes, go change some stuff
ADDI R2,RECSIZ ;Point at next entry
SOJG R4,CHKTMP ;OK?
POPJ SP, ;No, all done
CHKTM1:
MOVE R4,1(R2) ;Get sixbit name of the node
MOVEM R4,NODNAM ;Store this here
MOVEI R2,2(R2) ;Set up address here
HRLI R2,(POINT 7,0) ;Make into a byte pointer
MOVEI T1,2+<^D39/4> ;Get length of block
HRRM T1,USERID ;Store here
HRRM T1,ACOUNT ;Here
HRRM T1,PASWRD ;and here
MOVEI R4,USERID ;Get address of user ID string
PUSHJ SP,TCRLNE ;Build string if any
MOVEI R4,ACOUNT ;Get address of account string
PUSHJ SP,TCRLNE ;Get it
MOVEI R4,PASWRD ;Get address of password string
PUSHJ SP,TCRLNE ;Get it
POPJ SP, ;All done
;
; Routine to get data from the TMPCOR buffer (obviously stolen from DFLNE)
; R2=byte pointer to TMPCOR buffer; R4=address of string block
;
TCRLNE: PUSH SP,R4 ;Save string block address
HRLI R4,(POINT 8,,31) ;Make into byte pointer to new string
MOVSI R3,-^D39 ;And get a byte counter
JRST TCRLN2 ;Enter loop
TCRLN1: AOBJP R3,TCRLN2 ;PitT1 T1aracter if too many
IDPB T1,R4 ;Stash one more character
TCRLN2: ILDB T1,R2 ;Get next byte from TMPCOR
ROT T1,-1 ;Rotate right a bit
TLZE T1,(1B0) ;Did we shift a set bit?
TRO T1,100 ;Yes, set this one
CAIN T1,CR ;If <CR>,
JRST TCRLN2 ;Just eat it up
CAIL T1,LF ;Else, if EOL
CAILE T1,FF ; (I.E., <LF>, <VT>, or <FF>)
JRST TCRLN1 ;Not EOL, stash it away
POP SP,R4 ;Restore string block address
CAILE R3,^D39 ;Max characters allowed
MOVEI R3,^D39 ;Max characters allowed
HRLM R3,0(R4) ;Set actual byte count of new string
POPJ SP, ;And return
SUBTTL NSPERR - Here When NSP. UUO fails
NSPERR:
POP SP,R7 ;Get return address here
MOVEI R7,-1(R7) ;Get just address of UUO
CAIN T1,NSDBO% ;Remote give us up?
JRST DONE ;Yes, go be nice
CAIL T1,MAXERR ;Within range?
SETZ T1, ;No, say unknown
MOVE R6,NSPECD(T1) ;Get error description
$CALL FAO,<<[ASCIZ "!/?TELNUF - NSP. UUO error at PC !O: !Z!/"]>,R7,@R6>
MOVE T1,[.NSFAB,,.NSACH+1] ;Set this
JRST DONE1 ;And quit
DEFINE X(ARG,STRING),<
[ASCIZ ~(ARG) STRING~]
ZZZ==ZZZ+1
>
ZZZ==0
NSPECD:
X \ZZZ,<Unknown Error Code>
X \ZZZ,<Arg block format error>
X \ZZZ,<Allocation failure>
X \ZZZ,<Bad channel number>
X \ZZZ,<Bad format type in process block>
X \ZZZ,<Connect block format error>
X \ZZZ,<Interrupt data too long>
X \ZZZ,<Illegal flow control mode>
X \ZZZ,<Illegal function>
X \ZZZ,<Job quota exhausted>
X \ZZZ,<Link quota exhausted>
X \ZZZ,<No connect data to read>
X \ZZZ,<Percentage input out of bounds>
X \ZZZ,<No privileges to perform function>
X \ZZZ,<Segment size too big>
X \ZZZ,<Unknown node name>
X \ZZZ,<Unexpected state: unspecified>
X \ZZZ,<Wrong number of arguments>
X \ZZZ,<Function called in wrong state>
X \ZZZ,<Connect block length error>
X \ZZZ,<Process block length error>
X \ZZZ,<String block length error>
X \ZZZ,<Unexpected state: Disconnect sent>
X \ZZZ,<Unexpected state: Disconnect confirmed>
X \ZZZ,<Unexpected state: No confidence>
X \ZZZ,<Unexpected state: No link>
X \ZZZ,<Unexpected state: No communication>
X \ZZZ,<Unexpected state: No restources>
X \ZZZ,<Connect was rejected by object>
X \ZZZ,<Disconnected by object>
X \ZZZ,<No resources at remote node>
X \ZZZ,<Unrecognized node name>
X \ZZZ,<Remote node shut down>
X \ZZZ,<Unrecognized object>
X \ZZZ,<Invalid object name format>
X \ZZZ,<Object too busy>
X \ZZZ,<Abort by management>
X \ZZZ,<Abort by object>
X \ZZZ,<Invalid node name format>
X \ZZZ,<Local node shut down>
X \ZZZ,<Access control rejected>
X \ZZZ,<No response from object>
X \ZZZ,<Node unreachable>
X \ZZZ,<No link>
X \ZZZ,<Disconnect complete>
X \ZZZ,<Image field too long>
X \ZZZ,<Unspecified reject reason>
X \ZZZ,<Bad combination of NS.EOM and NS. WAI flags>
X \ZZZ,<Address error>
MAXERR==ZZZ
SUBTTL LOG File Stuff
TYPSTR:
OUTSTR @T1 ;First, type it
SKIPN LOGFLG ;Logging?
POPJ SP, ;No, all done
MOVE T2,T1 ;Copy address
HRLI T2,(POINT 7,0) ;Make into a pointer
TYPST1:
ILDB T1,T2 ;Get a byte
JUMPE T1,[POPJ SP,] ;Done
PUSHJ SP,LOGCHR ;Output it
JRST TYPST1 ;Loop on
LOGCHR:
SKIPN LOGFLG ;Logging?
POPJ SP, ;No, just return
SOSG LOGOBF+.BFCTR ;Room for it?
JRST LOGCH2 ;No, make some
LOGCH1:
IDPB T1,LOGOBF+.BFPTR ;Store
POPJ SP, ;Return
LOGCH2:
OUT LOGCHN, ;Writei t
JRST LOGCH1 ;Go on
OUTSTR [ASCIZ /
%OUTPUT error on log file - closing it
/]
CLOSE LOGCHN,
RELEAS LOGCHN,
SETZM LOGFLG
POPJ SP, ;Return
END START