.MCALL .MODULE .MODULE SYSMAC,VERSION=182,COMMENT=,LIB=YES ; Copyright (c) 1998 by Mentec, Inc., Nashua, NH. ; All rights reserved ; ; This software is furnished under a license for use only on a ; single computer system and may be copied only with the ; inclusion of the above copyright notice. This software, or ; any other copies thereof, may not be provided or otherwise ; made available to any other person except for use on such ; system and to one who agrees to these license terms. Title ; to and ownership of the software shall at all times remain ; in Mentec, Inc. ; ; The information in this document is subject to change without ; notice and should not be construed as a commitment by Digital ; Equipment Corporation, or Mentec, Inc. ; ; Digital and Mentec assume no responsibility for the use or ; reliability of its software on equipment which is not supplied ; by Digital or Mentec, and listed in the Software Product ; Description. ;+ ;COND ; MAC$ER (0) test error message generation ; 0 do not (expect clean assembly) ; 1 do (expect error messages from assembly) ;- ;+TEST ;++ ; SYSMAC.MAC can be assembled to test macro definitions and to do some ; crosschecking of interdependencies of some macro definitions. If the ; symbol MAC$ER is not defined or is defined as 0 no error message ; generation testing will be done, that is, any error message produced ; from the assembly of SYSMAC would be a real error. If MAC$ER is 1, ; then many error messages may be produced (to test the correct detection ; of error conditions). Note that some (many) aspects of macro definitions ; will not be checked. ; ; NOTE: For proper testing SYSMAC.SML should correspond to the ; same version as SYSMAC.MAC. ;-- .NLIST BEX .PSect Active ;contains executable testing of SYSMAC .Enabl LSB .MCall .Print .TrpSet .MCall .Assume .Library "SRC:SYSTEM" .MCall .EMTDf .EMTDf Debug:: ;Entry point to test tests BPT Active:: ;Entry point for tests .TrpSet #Area,#Err410 ;Return error message .PSect Servic Err410: Mov SP,Error ;Indicate error Mov R0,-(SP) .Print #Msg410 ;Trap to 4/10 error message .TrpSet #Err410 ;Return error message Mov (SP)+,R0 RTI BegTst: .Print R0 ;ident subtest Br 20$ ;clear error flag SkpTst: .Print #SkipT ;test not (yet) written BisB #Warn$,@#UsErrB ; Indicate warning in exit code Inc WarCnt ;count warnings Return TemTst: .Print #SytemT ;tested in SYSTEM Return EndTst: Tst Error Bne 10$ ;AOK .Print #TestOK ;no failures Br 20$ ;return 10$: .Print #TestEr ;Not OK BisB #Error$,@#UsErrB ; Indicate error in exit code 20$: Clr Error ;no errors Return AreaSz =: 10. ;EMT block area size AreaM1: ;Set AREA to -1 Mov R5,-(SP) ;save Mov #Area,R5 ;Point to area .Rept AreaSz ;Clear whole area Mov #-1,(R5)+ ;set to -1 .EndR Mov (SP)+,R5 ;restore Return .IRpC x,<123456789> Err'x: Mov #Test'x'F,R0 Br FlgErr .EndR .IRp x,<1.1,1.2,1.3,1.4,1.5,1.6,1.7,1.8,1.9> Err'x: Mov #Tst'x,R0 Br FlgEr1 .EndR .IRp x,<2.1,2.2,2.3,2.4,2.5,2.6,2.7,2.8,2.9> Err'x: Mov #Tst'x,R0 Br FlgEr2 .EndR .IRp x,<3.1,3.2,3.3,3.4,3.5,3.6,3.7,3.8,3.9> Err'x: Mov #Tst'x,R0 Br FlgEr3 .EndR FlgErr: FlgEr1: FlgEr2: FlgEr3: Br FlgEr4 .IRp x,<4.1,4.2,4.3,4.4,4.5,4.6,4.7,4.8,4.9> Err'x: Mov #Tst'x,R0 Br FlgEr4 .EndR .IRp x,<5.1,5.2,5.3,5.4,5.5,5.6,5.7,5.8,5.9> Err'x: Mov #Tst'x,R0 Br FlgEr5 .EndR .IRp x,<6.1,6.2,6.3,6.4,6.5,6.6,6.7,6.8,6.9> Err'x: Mov #Tst'x,R0 Br FlgEr6 .EndR .IRp x,<7.1,7.2,7.3,7.4,7.5,7.6,7.7,7.8,7.9> Err'x: Mov #Tst'x,R0 Br FlgEr7 .EndR FlgEr4: FlgEr5: FlgEr6: FlgEr7: Br FlgEr8 .IRp x,<8.1,8.2,8.3,8.4,8.5,8.6,8.7,8.8,8.9> Err'x: Mov #Tst'x,R0 Br FlgEr8 .EndR .IRp x,<9.1,9.2,9.3,9.4,9.5,9.6,9.7,9.8,9.9> Err'x: Mov #Tst'x,R0 Br FlgEr9 .EndR .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErA .EndR .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErB .EndR FlgEr8: FlgEr9: FlgErA: FlgErB: Br FlgErC .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErD .EndR .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErE .EndR .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErF .EndR .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErG .EndR FlgErC: FlgErD: FlgErE: FlgErF: Br FlgErG .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErH .EndR .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErI .EndR .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErJ .EndR FlgErG: FlgErH: FlgErI: FlgErJ: Br FlgErK .IRp x, Err'x: Mov #Tst'x,R0 Br FlgErK .EndR FlgErK: .Print Mov SP,Error Inc ErrCnt Return .Dsabl LSB .PSect Data ;contains word data for executable testing of SYSMAC Zero =:000000 ;symbolic zero Patter =:153535 ;odd pattern for initing before testing UsErrB =:53 Warn$ =:2 ; warn bit Error$=:4 ; error bit Error: .BlkW 1 ;error flag WarCnt: .BlkW 1 ;number of warnings ErrCnt: .BlkW 1 ;number of errors Area: .BlkW AreaSz ;EMT block area .PSect Text ;contains text data for executable testing of SYSMAC MSG410: .Asciz "?SYSMAC-E-Trap to 4/10" TestOK: .Asciz "%SYSMAC-I-Successful test(s) for this request" TestER: .Asciz "?SYSMAC-W-Unsuccessful test(s) for this request" SkipT: .Asciz "?SYSMAC-W-No test written" SytemT: .Asciz "%SYSMAC-I-Tested in SYSTEM.MAC" .IRpC X,<123456789> Test'x'F: .ASCIZ "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<1.1,1.2,1.3,1.4,1.5,1.6,1.7,1.8,1.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<2.1,2.2,2.3,2.4,2.5,2.6,2.7,2.8,2.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<3.1,3.2,3.3,3.4,3.5,3.6,3.7,3.8,3.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<4.1,4.2,4.3,4.4,4.5,4.6,4.7,4.8,4.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<5.1,5.2,5.3,5.4,5.5,5.6,5.7,5.8,5.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<6.1,6.2,6.3,6.4,6.5,6.6,6.7,6.8,6.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<7.1,7.2,7.3,7.4,7.5,7.6,7.7,7.8,7.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<8.1,8.2,8.3,8.4,8.5,8.6,8.7,8.8,8.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X,<9.1,9.2,9.3,9.4,9.5,9.6,9.7,9.8,9.9> Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .IRp X, Tst'x': .Asciz "?SYSMAC-E-Test 'x' failed" .EndR .Even .PSect Static ;contains static testing (.assumes) of SYSMAC .IIf NDF MAC$ER MAC$ER=0 .IIf NE MAC$ER MAC$ER=1 ;-TEST .Page ;++ ; RESERVED SYMBOL NAMES ; --------------------- ; ; ...V1 GLOBAL -- controls .MCALLing of ...CM* & support of V1, V2 and ; V3 versions of the expansions. ; NDF means ...CM* not .MCalled ; = 1 means use version 1 EMTs ; = 2 means use version 2 EMTs ; = 3 means use version 3(+) EMTs ; ...V1% GLOBAL -- counts entries in .DRFMS by letter (%) ; ...V2 LOCAL -- reusable in macro def'ns as local symbols ; ...V3 LOCAL -- reusable in macro def'ns as local symbols ; ...V4 LOCAL -- reusable in macro def'ns as local symbols ; ...V5 GLOBAL -- controls generation of .AUDIT information. ; NDF means first call to .AUDIT ; = Location counter for .AUDIT information words ; ...V6 GLOBAL -- used to prevent phase errors between pass1 and pass2 ; in the .AUDIT macro. ; accumulates RAD50 of MODULE argument of .MODULE call ; to compare against ...V27 and ...V28 to detect ; the start of pass 2 ; ...V7 GLOBAL -- used to pass OFFSET= setting from .DRBOT to .DREND ; NDF means .DRBOT OFFSET=YES not specified ; = -1 same as NDF ; = 0 means .DRBOT OFFSET=YES was specified ; ...V8 GLOBAL -- used to pass info from ...CMZ to ...CMY ; = checksum value for ...CMZ ; ...V9 GLOBAL -- used to pass info between .DRPTR & DRBEG ; NDF means first invocation of any of .DR(PTR,BEG) ; bits 4--0 are from .DRPTR & or'ed into NOP in .DRBEG ; bit 4 is set by .DRBEG if UNIT64 specified in .DRDEF ; or (ADDRCK or SPFUN or NSPFUN) specified in .DRBEG ; It means the NOP is followed by BR and H1.FG2 ; and possibly more pointers ; bit 3 is .DRPTR UNLOAD=x; 1 means present ; bit 2 is .DRPTR LOAD=x; 1 means present ; bit 1 is .DRPTR RELEASE=x; 1 means present ; bit 0 is .DRPTR FETCH=x; 1 means present ; ...V10 LOCAL -- reusable in macro def'ns as local symbols ; ...V11 LOCAL -- reusable in macro def'ns as local symbols ; ...V12 GLOBAL -- used to pass info among .DRSPFs ; ...V13 GLOBAL -- used to pass info among .DRSPFs ; ...V14 GLOBAL -- used to pass info among .DRSPFs ; ...V15 GLOBAL -- used to pass info among .DRSPFs ; ...V16 GLOBAL -- used to pass info among .DRSPFs ; ...V17 GLOBAL -- used to pass info among .DRSPFs ; ...V12, ...V13, & ...V14 are the NN portion ; of NNX spfun codes. If = 0 means this pair ; (...V12/...V15, ...V13/...V16, & ...V14/...V17) ; are not in use (yet). ; ...V15, ...V16, & ...V16 are a bit mask corresponding ; to the X code(s) found for a specific NN value. ; If ...V15 is NDF, this is the first call to .DRSPF ; & ...V12--...V17 are set to zero ; ...V18 GLOBAL -- used to pass MOD byte information between .DRPTR & ; .DREST ; bits 7--0 are MOD value from .DREST and .DRPTR ; bits 15-8 are reserved ; ...V19 GLOBAL -- used to pass CQE information among .DRDEF, .DREST, ; .DRPTR, & .DRBEG of bits to be set in ddCQE word. ; bit 15 is .DRPTR FETCH=*NO* flag; 1 means present ; bit 15 is or'ed into CQE in .DRBEG ; bit 14 is .DREST MOD2=DV2.V2 flag; 1 means a second ; display only vector table follows the first vector ; table in the handler. ; bit 13 is .DRPTR LOAD=*NO* flag; 1 means present ; bit 12 is .DRDEF DMA=YES or PERMUMR=x (DV2.DM) flag; ; 1 means present ; bits 11-0 are reserved ; ...V20 GLOBAL -- used to pass information to .DRUSE from .DRDEF. ; Set to 0 by .DRDEF, if zero when .DRUSE is invoked, ; H.USER in block zero is pointed to the .DRUSE entry. ; .DRUSE then sets ...V20 non-zero ; ; ...V21 GLOBAL -- used to pass information to .DRTAB from .DRDEF. ; Set to 0 by .DRDEF, if zero when .DRTAB is invoked, ; H.DATA in block zero is pointed to the .DRTAB entry. ; .DRTAB then sets ...V21 non-zero ; ; ...V22 GLOBAL -- used to pass information to .DRBEG and .DREND ; from .DRDEF. ; Set to 0 by .DRDEF if UNIT64, DMA, OR PERMUMR not ; specified. 40000 bit set by .DRDEF if UNIT64 is ; specified. 10000 bit set by .DRDEF if DMA = YES ; or PERMUMRs are specified. ; 4000 bit set by .DRDEF if SERIAL = YES is specified. ; If non-zero when .DRBEG is invoked, H1.FG2 et al ; are generated and ...V22 value is "or'ed" in. ; If non-zero when .DREND is invoked, a 64-unit ; extended owner table is generated following the ; handler's table of vectors into the monitor. ; ; ...V23 GLOBAL -- used to pass information from .DEBUG to .DPRINT. ; This variable contains the bit(s) that select debug ; class(es) of messages to print. 0 indicates no ; output, each bit set on indicates a class. ; ; ...V24 GLOBAL -- used to pass information from .DEBUG to .DPRINT. ; If zero, indicates PIC is not required, if non-zero ; PIC is to be generated. ; ; ...V25 GLOBAL -- used to indicate the first invocation of .DRFMS ; (set in .DRFMT to 0) If .DRFMS is entered with ...V25 ; set to 0, it generates the default switch list and ; sets ...V25 to 1. ; ...V26 GLOBAL -- used to distinguish between pass1 and pass2 ; in the .DRFMS macro. (set in .DRFMT) ; NDF means starting PASS 1 of assembly ; = 1 means PASS 1 of assembly ; = 2 means PASS 2 of assembly ; = 3 means PASS 2 1-time code generated ; ...V27 GLOBAL -- used to prevent phase errors between pass1 and pass2 ; in the .AUDIT macro. ; accumulates RAD50 of first three characters of MODULE ; argument on the first call of .MODULE macro ; ...V28 GLOBAL -- used to prevent phase errors between pass1 and pass2 ; in the .AUDIT macro. ; accumulates RAD50 of second three characters of MODULE ; argument on the first call of .MODULE macro ; ; ...V* -- are reserved for more local and global values ; ; CK.* -- are used globally when the .CKXX macro is used ; to define CK.* macros. The * strings correspond ; to the entries in the .CKXX argument list ; .Page ; RESERVED MACRO NAMES ; -------------------- ; ; ..V1.. GLOBAL -- select V1 macro expansions ; ..V2.. GLOBAL -- select V2 macro expansions ; .MACS GLOBAL -- default to V3 macro expansions ; ...CM0 GLOBAL -- move a word to the stack, optionally gen EMT ; ...CM1 GLOBAL -- point R0 to AREA, set the CHAN and IC (subcode) ; ...CM2 GLOBAL -- move a word/byte to OFFSET(R0), optionally gen EMT ; ...CM3 GLOBAL -- move a channel and code to R0, gen EMT 374 ; ...CM4 GLOBAL -- setup a SDAT/RCVD EMT request ; ...CM5 GLOBAL -- move a word/byte (not R0) to R0, optionally gen EMT ; ...CM6 GLOBAL -- point R0 to area, move chan and code to @R0, ; then do ...CM2 ; ...CM7 GLOBAL -- setup a READ_/WRIT_ EMT request ; ...CM8 LOCAL -- macro used within .DRSPF ; ...CM9 LOCAL -- macro used within .DRFMS ; ...CMB GLOBAL -- macro used for mapping extension to several EMTs ; ...CMC GLOBAL -- setup a DSTAT/FETCH EMT request ; ...CMV GLOBAL -- defines system version number for BSTRAP/RMON*/VIDEO ; ...CMY GLOBAL -- generate bomb code ; ...CMZ GLOBAL -- generate bomb code ; ...CM. ?????? -- DEC copyright (so it appears in libraries) ; ...CM* -- are reserved for more local and global macros ;-- .Page ;+ ;ERROR ; ; Error Messages ; ;?BOOT-U-I/O error ; ; .DREND message generated for boot blocks ; ;?SYSMAC-MESSAGE; ; ; .ASSUME optional user specified message ; ;?SYSMAC-W-A R E A ignored when stack form used; ; ; .CMAP,.GCMAP, and .MSDS if AREA is specified and ; CODE=SP|STACK ; ;?SYSMAC-W-"A REL C" is not true; ; ; .ASSUME The relationship (REL) between A and C is ; not true. ; ;?SYSMAC-E-Argument interrelationship too complex; ; ; ...CMC Arguments overwhelm macro definition ; ; ;?SYSMAC-W-D A T A table specified, but no T Y P E; ; ; .DREST The address of a data table is specified, ; but the type of table is not specified. ; ;?SYSMAC-E-.DEBUG must be used before .DPRINT; ; ; .DPRINT .DPRINT wss used, but .DEBUG, which sets up ; for .DPRINT has not been previously invoked. ; ;?SYSMAC-E-Expecting a single letter, found - UNIT64; ; ; .DRDEF The letter to use for the 64 unit version of ; the handler was incorrectly specified. ; ;?SYSMAC-E-Invalid A D R, expecting #..., found - ADR; ; ; .ADDR The address specified was not in the form of ; an immediate reference. ; ; .CALLK The destination specified was not in the ; form of an immediate reference, and PIC was ; specified. ; ;?SYSMAC-E-Invalid argument, #0 in first argument position; ; ; .CSIGEN ; .CSISPC The first argument was specified as #0. ; This will cause the request to be treated as ; a .GTLIN request. ; ;?SYSMAC-W-Invalid argument, use #0, not 0; ; ; generally applicable to macros ; [...CM0] ; [...CM1] ; [...CM2] ; .DELETE ; .WAIT A value was specified as 0, it should have ; been specified as #0. ; ;?SYSMAC-E-Invalid BMODE, found - 'BM'; ; ; ...CMB expecting UD, SD, CD, UI, SI, or CI ; ;?SYSMAC-E-Invalid C O N T R O L, found - CONTROL; ; ; .DRBOT Expecting a (possible combination of) UBUS, ; QBUS, CBUS, UMSCP, QMSCP, or CMSCP. ; ;?SYSMAC-E-Invalid CMODE, found - 'CM'; ; ; ...CMB expecting U or S ; ;?SYSMAC-E-Invalid date, found - 'MON'; ; ; ...CMZ The expiration month was incorrectly ; specified. ***DO NOT DOCUMENT*** ; ;?SYSMAC-E-Invalid D M A, expecting YES/NO, found - DMA; ; ; .DRDEF ; ;?SYSMAC-E-Invalid O P T I O N, expecting NO/NUM/OCT, found - X; ; ; .DRSET ; ;?SYSMAC-E-Invalid R E G, expecting Rx/@Rx/-(SP), found - REG; ; ; .ADDR ; ;?SYSMAC-E-Invalid R E T U R N, expecting N,Z,V,C found - 'return'; ; ; .CALLS ; ;?SYSMAC-E-Invalid S I D E S, expecting 1/2, found - SIDES; ; ; .DRBOT ; ;?SYSMAC-E-Invalid T Y P E, expecting MOV/BIC/BIS, found - TYPE; ; ; .POKE ; .PVAL ; ;?SYSMAC-E-Invalid T Y P E, expecting GET/MOV/BIC/BIS/USER, found - TYPE; ; ; .SFINF ; .SFSTA ; ;?SYSMAC-E-Invalid T Y P E, expecting OCT/DEC, found - TYPE; ; ; .DPRINT ; ;?SYSMAC-W-Value specified for U C O D E, but T Y P E=TYPE; ; ; .SFINF ; .SFSTA ; ;?SYSMAC-E-Invalid T Y P E, expecting O/R/W/M/T, found - TYPE; ; ; .DRSPF ; ;?SYSMAC-E-Invalid U N I T 6 4, expecting YES/NO, found - UNIT64; ; ; .DRDEF ;?SYSMAC-E-Not at location TO; ; ; .BR ;?SYSMAC-E-Odd or invalid vector specified; ; ; .DRBEG ; .DRVTB ; ;?SYSMAC-E-P R M U M R value > 7; ; ; .DRDEF ; ;?SYSMAC-E-Primary boot too large; ; ; .DREND ; ;?SYSMAC-E-SPFUN values must be negative; ; ; [...CM8] ; .DRSPF ; ;?SYSMAC-E-S W I T C H value unknown, use ON or OFF; ; ; .DEBUG The user specified something other than ; ON or OFF (or any case insensitive version of same) ; ;?SYSMAC-W-This operation may produce random results; ; ; .ADDR The user specified adding the PIC address ; calculated by .ADDR to the word ABOVE the ; stack. ; ;?SYSMAC-E-TO is not defined; ; ; .BR Symbol referenced in .BR is not defined ; ;?SYSMAC-E-Too many different NN_ SPFUN codes; ; ; .DRSPF ; ;?SYSMAC-E-U N I T 6 4 = N O and NAME'$N64 = 1 ; ; .DRDEF SYSGEN conditional for this handler is set for ; 64 unit support, but this handler does not ; support 64 units. ;- .SbTtl ..V1.. Select V1 macro generation, .MCall ..CM(0-7) ;++ ; ..V1.. ; ; .MCALL the support routines and set the version to 1 ;-- .MACRO ..V1.. .MCALL ...CM0,...CM1,...CM2,...CM3,...CM4,...CM5,...CM6,...CM7,...CMB,...CMC ...V1=1 .ENDM ;+TEST ...V1=-1 ..V1.. .Assume ...V1 EQ 1 <...V1 ; ..V1.. generated wrong ...V1 value> ;-TEST .SbTtl ..V2.. Select V2 macro generation, .MCall ..CM(0-7) ;++ ; ..V2.. ; ; .MCALL the support routines and set the version to 2 ;-- .MACRO ..V2.. .MCALL ...CM0,...CM1,...CM2,...CM3,...CM4,...CM5,...CM6,...CM7,...CMB,...CMC ...V1=2. .ENDM ;+TEST ...V1=-1 ..V2.. .Assume ...V1 EQ 2. <...v1 ; ..V2.. generated wrong ...V1 value> ;-TEST .SbTtl .MACS Select V3+ macro generation, .MCall ..CM(0-7) ;++ ; .MACS ; ; .MCALL the support routines and set the version to [>=]3 ;-- .MACRO .MACS .MCALL ...CM0,...CM1,...CM2,...CM3,...CM4,...CM5,...CM6,...CM7,...CMB,...CMC ...V1=3. .ENDM ;+TEST ...V1=-1 .Macs .Assume ...V1 EQ 3 <...V1 ;.MACS generated wrong ...V1 value> ;-TEST .Page .SbTTl ...CM0 Move a word to the stack, optionally gen EMT ;++ ; ...CM0 ; ; Move a word to the stack. If argument blank or #0 ; Put a 0 on the stack. If second argument present, ; generate an EMT with that value ;-- .MACRO ...CM0 STARG,INS .IF B CLR -(SP) .IFF .IF IDN ,#0 CLR -(SP) .IFF .IIF IDN <0> .ERROR;?SYSMAC-W-Invalid argument, use #0, not 0; MOV STARG,-(SP) .ENDC .ENDC .IF NB EMT ^o .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $..CM0: .Asciz "%SYSMAC-I-Testing ...CM0" .PSect Active Mov #$..CM0,R0 ;Ident the test Call BegTst Mov SP,R5 ;save old SP pointer value Mov #Patter,-(SP) ;try to insure old strange pattern Tst (SP)+ ;restore stack ..CM01: ...CM0 Tst @SP ;is the top of the stack 0? Beq 10$ ;yes Call Err1 10$: Mov #Patter,-(SP) ;try to insure old strange pattern Tst (SP)+ ;restore stack ..CM02: ...CM0 #0 Tst @SP ;is the top of the stack 0? Beq 20$ ;yes Call Err2 20$: Mov #Patter,-(SP) ;try to insure old strange pattern Tst (SP)+ ;restore stack ..CM03: ...CM0 #100001 Cmp @SP,#100001 ;is the top of the stack right Beq 30$ ;yes Call Err3 30$: ..CM04: ...CM0 ,377 .=.-2. 35$: .=.+2. Cmp #EMT+^o377,35$ ;correct EMT code? Beq 40$ ;yes Call Err4 40$: Mov R5,SP ;restore stack .If NE MAC$ER ;Expect P error ...CM0 0 Mov R5,SP ;restore stack .EndC Call EndTst .DSABL LSB ;-TEST .Page .SbTtl ...CM1 Point R0 to AREA, Set CHAN & IC in 1st word, ARG in 2nd word, .SbTtl . Opt gen EMT 375 ;++ ; ...CM1 ; ; Setup R0 to point to AREA, set the CHAN and IC (subcode) ; value in first word. This macro optimises number of ; instructions to set up first word. ; IC is forced to decimal. ; ARG is set in the second word of AREA ; ; ...V1 used (in ...CM2) ; ...V2 used ;-- .MACRO ...CM1 AREA,IC,CHAN,FLAG,ARG,INS,CSET,BB ...CM5 ...V2=0 .IF B .IIF B ,...V2=1 .IFF .IIF DIF ,SET,...V2=1 .ENDC .IF NE ...V2 .IF IDN ,<#0> CLRB @R0 .IFF .IF NB MOVB CHAN,@R0 .ENDC .ENDC .IFF .IF B MOVB #IC'.,1(R0) .IFF .NTYPE ...V2,CHAN .IF EQ ...V2-^o27 MOV CHAN+,@R0 .IFF MOV #IC'.*^o400,@R0 MOVB CHAN,@R0 .ENDC .ENDC .ENDC .IIF IDN <0> .ERROR;?SYSMAC-W-Invalid argument, use #0, not 0; ...CM2 ,2,INS,CSET,BB .ENDM ;+TEST ; Area IC Chan Flag Arg Ins CSet BB ;1 - 132 - - ;2 - 132 - SET ;3 - 132 - NOSET ;4 - 132 277 - ;5 - 132 277 SET ;6 - 132 277 NOSET ;7 #Area 132 - - #123456 ;8 #Area 132 - SET - E C B ;9 #Area 132 - NOSET #123 E C B ;10 #Area 132 277 - ;11 #Area 132 277 SET ;12 #Area 132 277 NOSET .Enabl LSB .PSect Text $..CM1: .Asciz "%SYSMAC-I-Testing ...CM1" .PSect Active Mov #$..CM1,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Area,R0 ;load R0 ..CM11: ...CM1 ,132 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM12: ...CM1 ,132,FLAG=SET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 50$ ;yes Call Err2.1 ;no 50$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 60$ ;yes Call Err2.2 ;no 60$: CmpB #132.,(R1)+ ;is IC set? Beq 70$ ;yes Call Err2.3 ;no 70$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 80$ ;yes Call Err2.4 ;no 80$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM13: ...CM1 ,132,FLAG=NOSET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 90$ ;yes Call Err3.1 ;no 90$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 100$ ;yes Call Err3.2 ;no 100$: CmpB #-1.,(R1)+ ;is IC unchanged? Beq 110$ ;yes Call Err3.3 ;no 110$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 120$ ;yes Call Err3.4 ;no 120$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM14: ...CM1 ,132,#277 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 130$ ;yes Call Err4.1 ;no 130$: CmpB #277,(R1)+ ;is CHAN set? Beq 140$ ;yes Call Err4.2 ;no 140$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 150$ ;yes Call Err4.3 ;no 150$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 160$ ;yes Call Err4.4 ;no 160$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM15: ...CM1 ,132,#277,FLAG=SET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 170$ ;yes Call Err5.1 ;no 170$: CmpB #277,(R1)+ ;is CHAN set? Beq 180$ ;yes Call Err5.2 ;no 180$: CmpB #132.,(R1)+ ;is IC set? Beq 190$ ;yes Call Err5.3 ;no 190$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 200$ ;yes Call Err5.4 ;no 200$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM16: ...CM1 ,132,#277,FLAG=NOSET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 210$ ;yes Call Err6.1 ;no 210$: CmpB #277,(R1)+ ;is CHAN set? Beq 220$ ;yes Call Err6.2 ;no 220$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 230$ ;yes Call Err6.3 ;no 230$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 240$ ;yes Call Err6.4 ;no 240$: Call AreaM1 ..CM17: ...CM1 #Area,132 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 250$ ;yes Call Err7.1 ;no 250$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 260$ ;yes Call Err7.2 ;no 260$: CmpB #132.,(R1)+ ;is IC set? Beq 270$ ;yes Call Err7.3 ;no 270$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 280$ ;yes Call Err7.4 ;no 280$: Call AreaM1 ..CM18: ...CM1 #Area,132,,SET,,E,C,B .=.-2 ;smash EMT Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 290$ ;yes Call Err8.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err8.2 ;no 300$: CmpB #132.,(R1)+ ;is IC set? Beq 310$ ;yes Call Err8.3 ;no 310$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 320$ ;yes Call Err8.4 ;no 320$: .PSect Data ...CM1 #Area,132,,SET,,E,C,B 330$: .PSect Active Cmp #EMT+375,330$-2 ;is the EMT generated correctly? Beq 340$ ;yes Call Err8.5 ;no 340$: Call AreaM1 ..CM19: ...CM1 #Area,132,,NOSET,#123,E,C,B .=.-2 ;smash EMT Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 350$ ;yes Call Err9.1 ;no 350$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 360$ ;yes Call Err9.2 ;no 360$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 370$ ;yes Call Err9.3 ;no 370$: CmpB #123,(R1)+ ;is ARG (BYTE) set? Beq 380$ ;yes Call Err9.4 ;no 380$: CmpB #-1,(R1)+ ;is ARG high byte unchanged? Beq 390$ ;yes Call Err9.4 ;no 390$: .PSect Data ...CM1 #Area,132,,SET,,E,C,B 400$: .PSect Active Cmp #EMT+375,400$-2 ;is the EMT generated correctly? Beq 410$ ;yes Call Err9.5 ;no 410$: Call AreaM1 ..CM1A: ...CM1 #Area,132,#277 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 420$ ;yes Call ErrA.1 ;no 420$: CmpB #277,(R1)+ ;is CHAN set? Beq 430$ ;yes Call ErrA.2 ;no 430$: CmpB #132.,(R1)+ ;is IC set? Beq 440$ ;yes Call ErrA.3 ;no 440$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 450$ ;yes Call ErrA.4 ;no 450$: Call AreaM1 ..CM1B: ...CM1 #Area,132,#277,FLAG=SET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 460$ ;yes Call ErrB.1 ;no 460$: CmpB #277,(R1)+ ;is CHAN set? Beq 470$ ;yes Call ErrB.2 ;no 470$: CmpB #132.,(R1)+ ;is IC set? Beq 480$ ;yes Call ErrB.3 ;no 480$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 490$ ;yes Call ErrB.4 ;no 490$: Call AreaM1 ..CM1C: ...CM1 #Area,132,#277,FLAG=NOSET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 500$ ;yes Call ErrC.1 ;no 500$: CmpB #277,(R1)+ ;is CHAN set? Beq 510$ ;yes Call ErrC.2 ;no 510$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 520$ ;yes Call ErrC.3 ;no 520$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 530$ ;yes Call ErrC.4 ;no 530$: .If NE MAC$ER ;Expect P error ...CM1 ,,0 .EndC Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl ...CM2 Move an ARG to OFFSET(R0), Opt MOVB, Opt gen EMT 375 ;++ ; ...CM2 ; ; Move an argument value to OFFSET(R0). ; Use a CLR_ if the value is #0. ; Offset is forced to decimal. ; BB is blank or B for byte operations ; If INS NB generate an EMT 375 ; ; ...V1 used ;-- .MACRO ...CM2 ARG,OFFSE,INS,CSET,BB .IF B .IF NB .IF NE ...V1-3. CLR'BB OFFSE'.(R0) .ENDC .ENDC .IFF .IF IDN ,#0 CLR'BB OFFSE'.(R0) .IFF .IIF IDN <0> .ERROR;?SYSMAC-W-Invalid argument, use #0, not 0; MOV'BB ARG,OFFSE'.(R0) .ENDC .ENDC .IF NB EMT ^o375 .ENDC .ENDM ;+TEST ; Arg Offse Ins CSet BB ...V1 ; - 2 E - - 3 ; - 2 - - - 3 ; - 2 - - B 3 ; - 2 - C - 3 ; - 2 - C B 3 ; #0 2 - - - 3 ; #0 2 - - B 3 ; #0 2 - C - 3 ; #0 2 - C B 3 ; R1 2 - - - 3 ; R1 2 - - B 3 ; R1 2 - C - 3 ; R1 2 - C B 3 ; ;Version 2 variants NOT tested: ; ; - 2 - - - 2 ; - 2 - - B 2 ; - 2 - C - 2 ; - 2 - C B 2 ; #0 2 - - - 2 ; #0 2 - - B 2 ; #0 2 - C - 2 ; #0 2 - C B 2 ; R1 2 - - - 2 ; R1 2 - - B 2 ; R1 2 - C - 2 ; R1 2 - C B 2 ; .Enabl LSB .PSect Text $..CM2: .Asciz "%SYSMAC-I-Testing ...CM2" .PSect Active Mov #$..CM2,R0 ;Ident the test Call BegTst .PSect Data ..CM21: ...CM2 ,2,E .PSect Active Cmp #EMT+375,..CM21 ;correct EMT generated? Beq 10$ ;yes Call Err1 ;no 10$: ..CM22: ...CM2 ,2 20$: Tst #..CM22-20$ ;expect no code Beq 30$ ;none Call Err2 ;some 30$: ..CM23: ...CM2 ,2,,,B 40$: Tst #..CM23-40$ ;expect no code Beq 50$ ;none Call Err2 ;some 50$: ..CM24: ...CM2 ,2,,C 60$: Tst #..CM24-60$ ;expect no code Beq 70$ ;none Call Err4 ;some 70$: ..CM25: ...CM2 ,2,,C,B 80$: Tst #..CM25-80$ ;expect no code Beq 90$ ;none Call Err5 ;some 90$: Mov #Area,R0 ;point to area Call AreaM1 ;init it ..CM26: ...CM2 #0,2 Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 100$ ;yes Call Err6.1 ;no 100$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 110$ ;yes Call Err6.2 ;no 110$: Cmp #0,(R1)+ ;is the word set? Beq 120$ ;yes Call Err6.3 ;no 120$: Mov #Area,R0 ;point to area Call AreaM1 ;init it ..CM27: ...CM2 #0,2,,,B Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 130$ ;yes Call Err7.1 ;no 130$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 140$ ;yes Call Err7.2 ;no 140$: CmpB #0,(R1)+ ;is the byte set? Beq 150$ ;yes Call Err7.3 ;no 150$: CmpB #-1,(R1)+ ;is the byte unchanged? Beq 160$ ;yes Call Err7.4 ;no 160$: Mov #Area,R0 ;point to area Call AreaM1 ;init it ..CM28: ...CM2 #0,2,,C Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 170$ ;yes Call Err8.1 ;no 170$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 180$ ;yes Call Err8.2 ;no 180$: Cmp #0,(R1)+ ;is the word set? Beq 190$ ;yes Call Err8.3 ;no 190$: Mov #Area,R0 ;point to area Call AreaM1 ;init it ..CM29: ...CM2 #0,2,,C,B Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 200$ ;yes Call Err9.1 ;no 200$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 210$ ;yes Call Err9.2 ;no 210$: CmpB #0,(R1)+ ;is the byte set? Beq 220$ ;yes Call Err9.3 ;no 220$: CmpB #-1,(R1)+ ;is the byte unchanged? Beq 230$ ;yes Call Err9.4 ;no 230$: Mov #Area,R0 ;point to area Call AreaM1 ;init it Mov #3,R2 ..CM2A: ...CM2 R2,2 Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 240$ ;yes Call ErrA.1 ;no 240$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 250$ ;yes Call ErrA.2 ;no 250$: Cmp #3,(R1)+ ;is the word set? Beq 260$ ;yes Call ErrA.3 ;no 260$: Mov #Area,R0 ;point to area Call AreaM1 ;init it Mov #3,R2 ..CM2B: ...CM2 R2,2,,,B Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 270$ ;yes Call ErrB.1 ;no 270$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 280$ ;yes Call ErrB.2 ;no 280$: CmpB #3,(R1)+ ;is the byte set? Beq 290$ ;yes Call ErrB.3 ;no 290$: CmpB #-1,(R1)+ ;is the byte unchanged? Beq 300$ ;yes Call ErrB.4 ;no 300$: Mov #Area,R0 ;point to area Call AreaM1 ;init it Mov #3,R2 ..CM2C: ...CM2 R2,2,,C Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 310$ ;yes Call ErrC.1 ;no 310$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 320$ ;yes Call ErrC.2 ;no 320$: Cmp #3,(R1)+ ;is the word set? Beq 330$ ;yes Call ErrC.3 ;no 330$: Mov #Area,R0 ;point to area Call AreaM1 ;init it Mov #3,R2 ..CM2D: ...CM2 R2,2,,C,B Mov #Area,R1 ;point to area Cmp R0,R1 ;is R0 ok? Beq 340$ ;yes Call ErrD.1 ;no 340$: Cmp #-1,(R1)+ ;is the word unchanged? Beq 350$ ;yes Call ErrD.2 ;no 350$: CmpB #3,(R1)+ ;is the byte set? Beq 360$ ;yes Call ErrD.3 ;no 360$: CmpB #-1,(R1)+ ;is the byte unchanged? Beq 370$ ;yes Call ErrD.4 ;no 370$: Call EndTst .If NE MAC$ER ;Expect P error ...CM2 0 .EndC .Dsabl LSB ;-TEST .Page .SbTtl ...CM3 Move CHAN & IC to R0, Gen EMT 374 ;++ ; ...CM3 ; ; Move a channel and code to R0. ; If CHAN blank, treat as #0 ; Follow this with an EMT 374. ; This macro optimises the instructions used ; to load R0. ; ; If CHAN contains a reference to R0, R0 will no longer be cleared ; prior to use. ; ; ...V2 used ;-- .MACRO ...CM3 CHAN,IC .IF B MOV #IC*^o400,R0 .IFF .NTYPE ...V2,CHAN .IF EQ ...V2-^o27 MOV CHAN+,R0 .IFF .IF EQ ...V2&^o7 .IF NE ...V2 MOVB CHAN,-(SP) MOV #IC*^o400,R0 BISB (SP)+,R0 .IFF BIC #^c^o377,R0 BIS #IC*^o400,R0 .ENDC .IFF MOV #IC*^o400,R0 BISB CHAN,R0 .ENDC .ENDC .ENDC EMT ^o374 .ENDM ;+TEST ; Chan IC ; - 132. ; #0 132. ; R2 132. ; #32 132. ; #zero 132. ; R0 132. ; @R0 ; .Enabl LSB .PSect Text $..CM3: .Asciz "%SYSMAC-I-Testing ...CM3" .PSect Active Mov #$..CM3,R0 ;Ident the test Call BegTst Mov #Patter,R0 ;smash R0 ..CM31: ...CM3 ,132. .=.-2 ;smash EMT TstB R0 ;channel cleared? Beq 10$ ;yes Call Err1.1 ;no 10$: SwaB R0 CmpB #132.,R0 ;IC set? Beq 20$ ;yes Call Err1.2 ;no 20$: Mov #Patter,R0 ;smash R0 ..CM32: ...CM3 #0,132. .=.-2 ;smash EMT TstB R0 ;channel cleared? Beq 30$ ;yes Call Err2.1 ;no 30$: SwaB R0 CmpB #132.,R0 ;IC set? Beq 40$ ;yes Call Err2.2 ;no 40$: Mov #Patter,R0 ;point to area Mov #32,R2 ;channel number ..CM33: ...CM3 R2,132. .=.-2 ;smash EMT CmpB #32,R0 ;channel set? Beq 50$ ;yes Call Err3.1 ;no 50$: SwaB R0 CmpB #132.,R0 ;IC set? Beq 60$ ;yes Call Err3.2 ;no 60$: Mov #Patter,R0 ;point to area ..CM34: ...CM3 #32,132. .=.-2 ;smash EMT CmpB #32,R0 ;channel set? Beq 70$ ;yes Call Err4.1 ;no 70$: SwaB R0 CmpB #132.,R0 ;IC set? Beq 80$ ;yes Call Err4.2 ;no 80$: Mov #Patter,R0 ;point to area ..CM35: ...CM3 #Zero,132. .=.-2 ;smash EMT CmpB #0,R0 ;channel set? Beq 90$ ;yes Call Err5.1 ;no 90$: SwaB R0 CmpB #132.,R0 ;IC set? Beq 100$ ;yes Call Err5.2 ;no 100$: .PSect Data ..CM36: ...CM3 ,132. 110$: .PSect Active Cmp #EMT+374,110$-2 ;correct EMT generated? Beq 120$ ;yes Call Err6 ;no 120$: Mov #12,R0 ;load channel number ..CM37: ...CM3 R0,132. .=.-2 ;smash EMT CmpB #12,R0 ;channel set? Beq 130$ ;yes Call Err7.1 ;no 130$: SwaB R0 CmpB #132.,R0 ;IC set? Beq 140$ ;yes Call Err7.2 ;no 140$: ; @R0 Mov #150$,R0 ;load address of channel number .PSect Data 150$: .Word 11 .PSect Active ..CM38: ...CM3 @R0,132. .=.-2 ;smash EMT CmpB #11,R0 ;channel set? Beq 160$ ;yes Call Err8.1 ;no 160$: SwaB R0 CmpB #132.,R0 ;IC set? Beq 170$ ;yes Call Err8.2 ;no 170$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl ...CM4 Setup a SDAT/RCVD EMT block ;++ ; ...CM4 ; ; Setup for a SDAT/RCVD EMT block ;-- .MACRO ...CM4 AREA,BUF,WCNT,CRTN,IC,CODE,BM,CM .IIF IDN ,NOSET ...CM1 ,IC,, .IIF DIF ,NOSET ...CM1 ,IC,#0, ...CM2 ,4 ...CM2 ,6 ...CMB ,,,,, .ENDM ;+TEST ; Area Buf WCnt CRtn IC Code BM CM ; - - - - 10 ; - - - - 10 SET ; - - - - 10 NOSET ; #Area - - - 10 ; #Area - - - 10 SET ; #Area - - - 10 NOSET ; - #020000 #040000 #010000 10 ; #Area #020000 #040000 #010000 10 ; #Area - - - 10 CI S ; .Enabl LSB .PSect Text $..CM4: .Asciz "%SYSMAC-I-Testing ...CM4" .PSect Active Mov #$..CM4,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CM41: ...CM4 ,,,,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is "channel" cleared? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 70$ ;yes Call Err1.7 ;no 70$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 80$ ;yes Call Err1.8 ;no 80$: Call AreaM1 Mov #Area,R0 ;point to area ..CM42: ...CM4 ,,,,10,CODE=SET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 90$ ;yes Call Err2.1 ;no 90$: CmpB #0,(R1)+ ;is "channel" cleared? Beq 100$ ;yes Call Err2.2 ;no 100$: CmpB #10.,(R1)+ ;is IC set? Beq 110$ ;yes Call Err2.3 ;no 110$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 120$ ;yes Call Err2.4 ;no 120$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 130$ ;yes Call Err2.5 ;no 130$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 140$ ;yes Call Err2.6 ;no 140$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 150$ ;yes Call Err2.7 ;no 150$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 160$ ;yes Call Err2.8 ;no 160$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CM43: ...CM4 ,,,,10,CODE=NOSET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 170$ ;yes Call Err3.1 ;no 170$: CmpB #-1,(R1)+ ;is "channel" unaltered? Beq 180$ ;yes Call Err3.2 ;no 180$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 190$ ;yes Call Err3.3 ;no 190$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 200$ ;yes Call Err3.4 ;no 200$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 210$ ;yes Call Err3.5 ;no 210$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 220$ ;yes Call Err3.6 ;no 220$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 230$ ;yes Call Err3.7 ;no 230$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 240$ ;yes Call Err3.8 ;no 240$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 ..CM44: ...CM4 #Area,,,,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 250$ ;yes Call Err4.1 ;no 250$: CmpB #0,(R1)+ ;is "channel" cleared? Beq 260$ ;yes Call Err4.2 ;no 260$: CmpB #10.,(R1)+ ;is IC set? Beq 270$ ;yes Call Err4.3 ;no 270$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 280$ ;yes Call Err4.4 ;no 280$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 290$ ;yes Call Err4.5 ;no 290$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 300$ ;yes Call Err4.6 ;no 300$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 310$ ;yes Call Err4.7 ;no 310$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 320$ ;yes Call Err4.8 ;no 320$: Call AreaM1 ;init area Mov #Patter,R0 ;point to area ..CM45: ...CM4 #Area,,,,10,CODE=SET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 330$ ;yes Call Err5.1 ;no 330$: CmpB #0,(R1)+ ;is "channel" cleared? Beq 340$ ;yes Call Err5.2 ;no 340$: CmpB #10.,(R1)+ ;is IC set? Beq 350$ ;yes Call Err5.3 ;no 350$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 360$ ;yes Call Err5.4 ;no 360$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 370$ ;yes Call Err5.5 ;no 370$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 380$ ;yes Call Err5.6 ;no 380$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 390$ ;yes Call Err5.7 ;no 390$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 400$ ;yes Call Err5.8 ;no 400$: Call AreaM1 ;init area Mov #Patter,R0 ;point to area ..CM46: ...CM4 #Area,,,,10,CODE=NOSET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 410$ ;yes Call Err6.1 ;no 410$: CmpB #-1,(R1)+ ;is "channel" unaltered? Beq 420$ ;yes Call Err6.2 ;no 420$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 430$ ;yes Call Err6.3 ;no 430$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 440$ ;yes Call Err6.4 ;no 440$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 450$ ;yes Call Err6.5 ;no 450$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 460$ ;yes Call Err6.6 ;no 460$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 470$ ;yes Call Err6.7 ;no 470$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 480$ ;yes Call Err6.8 ;no 480$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CM47: ...CM4 ,#040000,#020000,#010000,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 490$ ;yes Call Err7.1 ;no 490$: CmpB #0,(R1)+ ;is "channel" cleared? Beq 500$ ;yes Call Err7.2 ;no 500$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 510$ ;yes Call Err7.3 ;no 510$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 520$ ;yes Call Err7.4 ;no 520$: Cmp #040000,(R1)+ ;is BUF set? Beq 530$ ;yes Call Err7.5 ;no 530$: Cmp #020000,(R1)+ ;is WCNT set? Beq 540$ ;yes Call Err7.6 ;no 540$: Cmp #010000,(R1)+ ;is CRTN set? Beq 550$ ;yes Call Err7.7 ;no 550$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 560$ ;yes Call Err7.8 ;no 560$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 ..CM48: ...CM4 #Area,#040000,#020000,#010000,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 570$ ;yes Call Err8.1 ;no 570$: CmpB #0,(R1)+ ;is "channel" cleared? Beq 580$ ;yes Call Err8.2 ;no 580$: CmpB #10.,(R1)+ ;is IC set? Beq 590$ ;yes Call Err8.3 ;no 590$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 600$ ;yes Call Err8.4 ;no 600$: Cmp #040000,(R1)+ ;is BUF set? Beq 610$ ;yes Call Err8.5 ;no 610$: Cmp #020000,(R1)+ ;is WCNT set? Beq 620$ ;yes Call Err8.6 ;no 620$: Cmp #010000,(R1)+ ;is CRTN set? Beq 630$ ;yes Call Err8.7 ;no 630$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 640$ ;yes Call Err8.8 ;no 640$: .PSect Data ..CM49: ...CM4 650$: .PSect Active Cmp #EMT+375,650$-2 ;Correct EMT generated? Beq 660$ ;yes Call Err9 ;no 660$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 ..CM4A: ...CM4 #Area,,,,10,BM=CI,CM=S .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 670$ ;yes Call ErrA.1 ;no 670$: CmpB #0,(R1)+ ;is "channel" cleared? Beq 680$ ;yes Call ErrA.2 ;no 680$: CmpB #10.,(R1)+ ;is IC set? Beq 690$ ;yes Call ErrA.3 ;no 690$: Cmp #-1,(R1)+ ;is "reserved" unaltered? Beq 700$ ;yes Call ErrA.4 ;no 700$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 710$ ;yes Call ErrA.5 ;no 710$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 720$ ;yes Call ErrA.6 ;no 720$: Cmp #..ISPA!..CURR!^o3,(R1)+ ;is the flag word correct? Beq 730$ ;yes Call ErrA.7 ;no 730$: Cmp #-1,(R1)+ ;is SRTN unaltered? Beq 740$ ;yes Call ErrA.8 ;no 740$: .PSect Data ..CM4B: ...CM4 CM=S,BM=SI 750$: .PSect Active Cmp #EMT+375,750$-2 ;Correct EMT generated? Beq 760$ ;yes Call ErrB.1 ;no 760$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl ...CM5 Move a value to R0, opt MOVB, opt gen EMT ;++ ; ...CM5 ; ; Move a (byte) value to R0 unless the src is ; blank or R0. If so, then generate nothing. ; BB is blank for word operations or B for byte. ; If second argument present, generate an EMT with ; that code value. ;-- .MACRO ...CM5 SRC,INS,BB .IF NB .IF DIF ,R0 MOV'BB SRC,R0 .ENDC .ENDC .IF NB EMT ^o .ENDC .ENDM ;+TEST ; SRC INS BB ; - - - ; - - B ; - 377 - ; - 377 B ; R0 - - ; #23 - B ; #23 377 - ; R1 377 B .Enabl LSB .PSect Text $..CM5: .Asciz "%SYSMAC-I-Testing ...CM5" .PSect Active Mov #$..CM5,R0 ;Ident the test Call BegTst 10$: ..CM51: ...CM5 20$: Tst #20$-10$ ;nothing generated? Beq 30$ ;yes Call Err1 ;no 30$ 30$: ..CM52: ...CM5 40$: Tst #40$-30$ ;nothing generated? Beq 50$ ;yes Call Err2 ;no 50$: ..CM53: ...CM5 ,377 Cmp #EMT+377,..CM53 ;correct EMT generated Beq 60$ ;yes Call Err3 60$: ..CM54: ...CM5 ,377 70$: Cmp #EMT+377,70$-2 ;correct EMT generated Beq 80$ ;yes Call Err4.1 80$: Cmp #70$-60$,#2 ;just EMT generated? Beq 90$ ;yes Call Err4.2 ;no 90$: 100$: ..CM55: ...CM5 R0 110$: Tst #110$-100$ ;nothing generated? Beq 120$ ;yes Call Err5 ;no 120$: Mov #Patter,R0 ;init R0 ..CM56: ...CM5 #23,,B Cmp #23,R0 ;channel set in R0? Beq 130$ ;yes Call Err6 ;no 130$: Mov #Patter,R0 ;init R0 ..CM57: ...CM5 #23,377 140$: Cmp #23,R0 ;channel set in R0? Beq 150$ ;yes Call Err7.1 ;no 150$: Cmp #EMT+377,140$-2 ;correct EMT generated? Beq 160$ ;yes Call Err7.2 ;no 160$: Mov #Patter,R0 ;init R0 Mov #377*^o400+23,R1 ;load register ..CM58: ...CM5 R1,377,B 170$: Cmp #23,R0 ;channel set in R0? Beq 180$ ;yes Call Err8.1 ;no 180$: Cmp #EMT+377,170$-2 ;correct EMT generated? Beq 190$ ;yes Call Err8.2 ;no 190$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTTl ...CM6 Move CODE & IC @R0, Move ARG to 2(R0), Opt gen EMT 375 ;++ ; ...CM6 ; ; Move a code and channel to @R0. This macro ; optimises the instructions needed to load R0. ; Do the first ...CM2 also. ; IC and CHAN are used in current radix. ; ; ...V1 used (...CM2) ;-- .MACRO ...CM6 AREA,IC,CHAN,FLAG,ARG,INS,CSET,BB ...CM5 .IF B .IF NB MOV #IC*^o400+CHAN,@R0 .ENDC .IFF .IF IDN ,SET MOV #IC*^o400+CHAN,@R0 .ENDC .ENDC ...CM2 ,2,INS,CSET,BB .ENDM ;+TEST ; Area IC Chan Flag Arg Ins CSet BB ;1 - 132. - - ;2 - 132. - SET ;3 - 132. - NOSET ;4 - 132. 177. - ;5 - 132. 177. SET ;6 - 132. 177. NOSET ;7 #Area 132. - - #123456 ;8 #Area 132. - SET - E C B ;9 #Area 132. - NOSET #123 E C B ;10 #Area 132. 177. - ;11 #Area 132. 177. SET ;12 #Area 132. 177. NOSET ; .Enabl LSB .PSect Text $..CM6: .Asciz "%SYSMAC-I-Testing ...CM6" .PSect Active Mov #$..CM6,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Area,R0 ;load R0 ..CM61: ...CM6 ,132. Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM62: ...CM6 ,132.,177.,FLAG=SET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 50$ ;yes Call Err2.1 ;no 50$: CmpB #177.,(R1)+ ;is CHAN unchanged? Beq 60$ ;yes Call Err2.2 ;no 60$: CmpB #132.,(R1)+ ;is IC set? Beq 70$ ;yes Call Err2.3 ;no 70$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 80$ ;yes Call Err2.4 ;no 80$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM63: ...CM6 ,132.,FLAG=NOSET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 90$ ;yes Call Err3.1 ;no 90$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 100$ ;yes Call Err3.2 ;no 100$: CmpB #-1.,(R1)+ ;is IC unchanged? Beq 110$ ;yes Call Err3.3 ;no 110$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 120$ ;yes Call Err3.4 ;no 120$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM64: ...CM6 ,132.,177. Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 130$ ;yes Call Err4.1 ;no 130$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 140$ ;yes Call Err4.2 ;no 140$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 150$ ;yes Call Err4.3 ;no 150$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 160$ ;yes Call Err4.4 ;no 160$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM65: ...CM6 ,132.,177.,FLAG=SET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 170$ ;yes Call Err5.1 ;no 170$: CmpB #177.,(R1)+ ;is CHAN set? Beq 180$ ;yes Call Err5.2 ;no 180$: CmpB #132.,(R1)+ ;is IC set? Beq 190$ ;yes Call Err5.3 ;no 190$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 200$ ;yes Call Err5.4 ;no 200$: Call AreaM1 Mov #Area,R0 ;load R0 ..CM66: ...CM6 ,132.,177.,FLAG=NOSET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 210$ ;yes Call Err6.1 ;no 210$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 220$ ;yes Call Err6.2 ;no 220$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 230$ ;yes Call Err6.3 ;no 230$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 240$ ;yes Call Err6.4 ;no 240$: Call AreaM1 ..CM67: ...CM6 #Area,132.,177. Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 250$ ;yes Call Err7.1 ;no 250$: CmpB #177.,(R1)+ ;is CHAN unchanged? Beq 260$ ;yes Call Err7.2 ;no 260$: CmpB #132.,(R1)+ ;is IC set? Beq 270$ ;yes Call Err7.3 ;no 270$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 280$ ;yes Call Err7.4 ;no 280$: Call AreaM1 ..CM68: ...CM6 #Area,132.,177.,SET,,E,C,B .=.-2 ;smash EMT Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 290$ ;yes Call Err8.1 ;no 290$: CmpB #177.,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err8.2 ;no 300$: CmpB #132.,(R1)+ ;is IC set? Beq 310$ ;yes Call Err8.3 ;no 310$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 320$ ;yes Call Err8.4 ;no 320$: .PSect Data ...CM6 #Area,132.,0,SET,,E,C,B 330$: .PSect Active Cmp #EMT+375,330$-2 ;is the EMT generated correctly? Beq 340$ ;yes Call Err8.5 ;no 340$: Call AreaM1 ..CM69: ...CM6 #Area,132.,,NOSET,#123,E,C,B .=.-2 ;smash EMT Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 350$ ;yes Call Err9.1 ;no 350$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 360$ ;yes Call Err9.2 ;no 360$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 370$ ;yes Call Err9.3 ;no 370$: CmpB #123,(R1)+ ;is ARG (BYTE) set? Beq 380$ ;yes Call Err9.4 ;no 380$: CmpB #-1,(R1)+ ;is ARG high byte unchanged? Beq 390$ ;yes Call Err9.4 ;no 390$: .PSect Data ...CM6 #Area,132.,0,SET,,E,C,B 400$: .PSect Active Cmp #EMT+375,400$-2 ;is the EMT generated correctly? Beq 410$ ;yes Call Err9.5 ;no 410$: Call AreaM1 ..CM6A: ...CM6 #Area,132.,177. Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 420$ ;yes Call ErrA.1 ;no 420$: CmpB #177.,(R1)+ ;is CHAN set? Beq 430$ ;yes Call ErrA.2 ;no 430$: CmpB #132.,(R1)+ ;is IC set? Beq 440$ ;yes Call ErrA.3 ;no 440$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 450$ ;yes Call ErrA.4 ;no 450$: Call AreaM1 ..CM6B: ...CM6 #Area,132.,177.,FLAG=SET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 460$ ;yes Call ErrB.1 ;no 460$: CmpB #177.,(R1)+ ;is CHAN set? Beq 470$ ;yes Call ErrB.2 ;no 470$: CmpB #132.,(R1)+ ;is IC set? Beq 480$ ;yes Call ErrB.3 ;no 480$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 490$ ;yes Call ErrB.4 ;no 490$: Call AreaM1 ..CM6C: ...CM6 #Area,132.,177.,FLAG=NOSET Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 500$ ;yes Call ErrC.1 ;no 500$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 510$ ;yes Call ErrC.2 ;no 510$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 520$ ;yes Call ErrC.3 ;no 520$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 530$ ;yes Call ErrC.4 ;no 530$: .If NE MAC$ER ;Expect P error ...CM6 ,,0. .EndC Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl ...CM7 Generate a READ_/WRIT_ request ;++ ; ...CM7 ; ; Generate READ_/WRIT_ requests ;-- .MACRO ...CM7 AREA,CHAN,BUF,WCNT,BLK,CRTN,IC,CODE,V1,BM,CM .IF NE ...V1-1 ...CM1 ,IC,,, ...CM2 ,4 ...CM2 ,6 ...CMB ,,,,, .MEXIT .ENDC ...CM5 ...CM0 ...CM0 ...CM0 , .ENDM ;+TEST ; Area Chan Buf WCnt Blk CRtn IC Code BM CM ; - - - - - - 10 ; - #0 - - - - 10 SET ; - - - - - - 10 NOSET ; #Area - - - - - 10 ; #Area #0 - - - - 10 SET ; #Area - - - - - 10 NOSET ; - R2 #020000 #040000 #010000 #000000 10 ; #Area #2 #020000 #040000 #010000 #000000 10 ; #Area - - - - - 10 UD S ; ; Version 1 not tested ; .Enabl LSB .PSect Text $..CM7: .Asciz "%SYSMAC-I-Testing ...CM7" .PSect Active Mov #$..CM7,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CM71: ...CM7 ,,,,,,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unaltered? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unaltered? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 70$ ;yes Call Err1.7 ;no 70$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 80$ ;yes Call Err1.8 ;no 80$: Call AreaM1 Mov #Area,R0 ;point to area ..CM72: ...CM7 ,#0,,,,,10,CODE=SET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 90$ ;yes Call Err2.1 ;no 90$: CmpB #0,(R1)+ ;is CHAN set? Beq 100$ ;yes Call Err2.2 ;no 100$: CmpB #10.,(R1)+ ;is IC set? Beq 110$ ;yes Call Err2.3 ;no 110$: Cmp #-1,(R1)+ ;is BLK unaltered? Beq 120$ ;yes Call Err2.4 ;no 120$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 130$ ;yes Call Err2.5 ;no 130$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 140$ ;yes Call Err2.6 ;no 140$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 150$ ;yes Call Err2.7 ;no 150$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 160$ ;yes Call Err2.8 ;no 160$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CM73: ...CM7 ,,,,,,10,CODE=NOSET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 170$ ;yes Call Err3.1 ;no 170$: CmpB #-1,(R1)+ ;is CHAN unaltered? Beq 180$ ;yes Call Err3.2 ;no 180$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 190$ ;yes Call Err3.3 ;no 190$: Cmp #-1,(R1)+ ;is BLK unaltered? Beq 200$ ;yes Call Err3.4 ;no 200$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 210$ ;yes Call Err3.5 ;no 210$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 220$ ;yes Call Err3.6 ;no 220$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 230$ ;yes Call Err3.7 ;no 230$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 240$ ;yes Call Err3.8 ;no 240$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 ..CM74: ...CM7 #Area,,,,,,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 250$ ;yes Call Err4.1 ;no 250$: CmpB #-1,(R1)+ ;is CHAN unaltered? Beq 260$ ;yes Call Err4.2 ;no 260$: CmpB #10.,(R1)+ ;is IC set? Beq 270$ ;yes Call Err4.3 ;no 270$: Cmp #-1,(R1)+ ;is BLK unaltered? Beq 280$ ;yes Call Err4.4 ;no 280$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 290$ ;yes Call Err4.5 ;no 290$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 300$ ;yes Call Err4.6 ;no 300$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 310$ ;yes Call Err4.7 ;no 310$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 320$ ;yes Call Err4.8 ;no 320$: Call AreaM1 ;init area Mov #Patter,R0 ;point to area ..CM75: ...CM7 #Area,#0,,,,,10,CODE=SET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 330$ ;yes Call Err5.1 ;no 330$: CmpB #0,(R1)+ ;is CHAN set? Beq 340$ ;yes Call Err5.2 ;no 340$: CmpB #10.,(R1)+ ;is IC set? Beq 350$ ;yes Call Err5.3 ;no 350$: Cmp #-1,(R1)+ ;is BLK unaltered? Beq 360$ ;yes Call Err5.4 ;no 360$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 370$ ;yes Call Err5.5 ;no 370$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 380$ ;yes Call Err5.6 ;no 380$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 390$ ;yes Call Err5.7 ;no 390$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 400$ ;yes Call Err5.8 ;no 400$: Call AreaM1 ;init area Mov #Patter,R0 ;point to area ..CM76: ...CM7 #Area,,,,,,10,CODE=NOSET .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 410$ ;yes Call Err6.1 ;no 410$: CmpB #-1,(R1)+ ;is CHAN unaltered? Beq 420$ ;yes Call Err6.2 ;no 420$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 430$ ;yes Call Err6.3 ;no 430$: Cmp #-1,(R1)+ ;is BLK unaltered? Beq 440$ ;yes Call Err6.4 ;no 440$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 450$ ;yes Call Err6.5 ;no 450$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 460$ ;yes Call Err6.6 ;no 460$: Cmp #-1,(R1)+ ;is CRTN unaltered? Beq 470$ ;yes Call Err6.7 ;no 470$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 480$ ;yes Call Err6.8 ;no 480$: Call AreaM1 ;init area Mov #Area,R0 ;point to area Mov #3,R2 ;setup reg ..CM77: ...CM7 ,R2,#040000,#020000,#010000,#000000,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 490$ ;yes Call Err7.1 ;no 490$: CmpB #3,(R1)+ ;is CHAN set? Beq 500$ ;yes Call Err7.2 ;no 500$: CmpB #-1,(R1)+ ;is IC unaltered? Beq 510$ ;yes Call Err7.3 ;no 510$: Cmp #010000,(R1)+ ;is BLK set? Beq 520$ ;yes Call Err7.4 ;no 520$: Cmp #040000,(R1)+ ;is BUF set? Beq 530$ ;yes Call Err7.5 ;no 530$: Cmp #020000,(R1)+ ;is WCNT set? Beq 540$ ;yes Call Err7.6 ;no 540$: Cmp #000000,(R1)+ ;is CRTN set? Beq 550$ ;yes Call Err7.7 ;no 550$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 560$ ;yes Call Err7.8 ;no 560$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 ..CM78: ...CM7 #Area,#2,#040000,#020000,#010000,#000000,10 .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 570$ ;yes Call Err8.1 ;no 570$: CmpB #2,(R1)+ ;is CHAN set? Beq 580$ ;yes Call Err8.2 ;no 580$: CmpB #10.,(R1)+ ;is IC set? Beq 590$ ;yes Call Err8.3 ;no 590$: Cmp #010000,(R1)+ ;is BLK set? Beq 600$ ;yes Call Err8.4 ;no 600$: Cmp #040000,(R1)+ ;is BUF set? Beq 610$ ;yes Call Err8.5 ;no 610$: Cmp #020000,(R1)+ ;is WCNT set? Beq 620$ ;yes Call Err8.6 ;no 620$: Cmp #000000,(R1)+ ;is CRTN set? Beq 630$ ;yes Call Err8.7 ;no 630$: Cmp #-1,(R1)+ ;is flag unaltered? Beq 640$ ;yes Call Err8.8 ;no 640$: .PSect Data ..CM79: ...CM7 650$: .PSect Active Cmp #EMT+375,650$-2 ;Correct EMT generated? Beq 660$ ;yes Call Err9 ;no 660$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 ..CM7A: ...CM7 #Area,,,,,,10,BM=UD,CM=S .=.-2 ;smash EMT Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 670$ ;yes Call ErrA.1 ;no 670$: CmpB #-1,(R1)+ ;is CHAN unaltered? Beq 680$ ;yes Call ErrA.2 ;no 680$: CmpB #10.,(R1)+ ;is IC set? Beq 690$ ;yes Call ErrA.3 ;no 690$: Cmp #-1,(R1)+ ;is BLK unaltered? Beq 700$ ;yes Call ErrA.4 ;no 700$: Cmp #-1,(R1)+ ;is BUF unaltered? Beq 710$ ;yes Call ErrA.5 ;no 710$: Cmp #-1,(R1)+ ;is WCNT unaltered? Beq 720$ ;yes Call ErrA.6 ;no 720$: Cmp #..DSPA!..USER!^o3,(R1)+ ;Is flag set correctly? Beq 730$ ;yes Call ErrA.7 ;no 730$: Cmp #-1,(R1)+ ;is SRTN unaltered? Beq 740$ ;yes Call ErrA.8 ;no 740$: .PSect Data ..CM7B: ...CM7 #Area,,,,,,10,BM=UD,CM=S 750$: .PSect Active Cmp #EMT+375,750$-2 ;Correct EMT generated? Beq 760$ ;yes Call ErrB.1 ;no 760$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl ...CMB Generate the extended mapping bits ;+ ; ...CMB ; ; The ...CMB macro generates extended mapping bits for buffer ; and crtn arguments. ; ; ...V2 used ; ...V3 used ; ; BM BUF mode and space argument ; CM CRTN mode and space argument ; FUNC function byte value ; SPFUN nb means always generate long form (with SRTN not CRTN) ; CODE SET/NOSET ; ; BM=*BYPASS* means that the CM string is substituted for the ; source argument. Example: ; ; ...CMB *BYPASS*,R4 ; MOV R4,8.(R0) ; ; *BYPASS* is primarily designed for SYSLIB routines. ; ;- .MACRO ...CMB BM,CM,CRTN,FUNC,SPFUN,CODE .IF B ...CM2 ,8,E .MEXIT .ENDC .IF IDN ,<*BYPASS*> MOV CM,8.(R0) ...CM2 ,10,E .MEXIT .ENDC ...V2=-1 ...V3=-1 .IF NB .IIF B ...V2=^o377 .IIF IDN , ...V2=^o3 .IIF IDN , ...V2=^o7 .IIF IDN , ...V2=^o13 .IIF IDN , ...V2=^o23 .IIF IDN , ...V2=^o27 .IIF IDN , ...V2=^o33 .IIF B ...V3=0 .IIF IDN , ...V3=0 .IIF IDN , ...V3=1 .IF EQ <...V2+1> .ERROR ;?SYSMAC-E-Invalid BMODE, found 'BM'; ...V2=^o377 .ENDC .IF EQ <...V3+1> .ERROR ;?SYSMAC-E-Invalid CMODE, found 'CM'; ...V3=0 .ENDC .IFF ...V2=^o377 ...V3=0 .ENDC .IF B MOV #...V2,8.(R0) .IFF .IF NB .NTYPE ...V4,FUNC .IF NE ...V4-^o27 .IF DIF ,NOSET MOVB #...V2,8.(R0) .ENDC ...CM2 ,9,,,B .IFF MOV FUNC'*^o400+...V2,8.(R0) .ENDC .ENDC .ENDC .IF EQ ...V3 ...CM2 ,10,E .IFF .IF NB .NTYPE ...V4,CRTN .IF NE ...V4-^o27 ...CM2 ,10 INC 10.(R0) EMT ^o375 .IFF ...CM2 ,10,E .ENDC .IFF EMT ^o375 .ENDC .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $..CMB: .Asciz "%SYSMAC-I-Testing ...CMB" .PSect Active Mov #$..CMB,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CMB1: ...CMB ,,#123456 .=.-2 ;crush EMT Mov #Area,R1 ;point to area Cmp #123456,8.(R1) ;is CRTN set? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #-1,10.(R1) ;is SRTN unchanged? Beq 20$ ;yes Call Err1.2 20$: Call AreaM1 ;init area Mov #Area,R0 ;point to area Mov #135353,R3 ..CMB2: ...CMB *BYPASS*,#123456,R3 .=.-2 ;crush EMT Mov #Area,R1 ;point to area Cmp #123456,8.(R1) ;is CRTN set? Beq 30$ ;yes Call Err2.1 ;no 30$: Cmp #135353,10.(R1) ;is SRTN set? Beq 40$ ;yes Call Err2.2 40$: Call AreaM1 ;init area Mov #135353,Area+8. ;expect -1 in a byte Mov #Area,R0 ;point to area ..CMB3: ...CMB ,U,#123456 .=.-2 ;crush EMT Mov #Area,R1 ;point to area CmpB #377,8.(R1) ;is TYPE set? Beq 50$ ;yes Call Err3.1 ;no 50$: CmpB #0,9.(R1) ;is FUNC set? Beq 60$ ;yes Call Err3.2 60$: Cmp #123456,10.(R1) ;is SRTN set? Beq 70$ ;yes Call Err3.3 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CMB4: ...CMB UD,S .=.-2 ;crush EMT Mov #Area,R1 ;point to area CmpB #..USER!..DSPA!^o3,8.(R1) ;is flag set correctly? Beq 80$ ;yes Call Err4.1 ;no 80$: CmpB #0,9.(R1) ;is FUNC set correctly? Beq 90$ ;yes Call Err4.2 90$: Cmp #-1,10.(R1) ;is SRTN set unchanged? Beq 100$ ;yes Call Err4.3 100$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CMB5: ...CMB SD,S,#123456 .=.-2 ;crush EMT Mov #Area,R1 ;point to area CmpB #..SUPY!..DSPA!^o3,8.(R1) ;is flag set correctly? Beq 110$ ;yes Call Err5.1 ;no 110$: CmpB #0,9.(R1) ;is FUNC set correctly? Beq 120$ ;yes Call Err5.2 120$: Cmp #123456+1,10.(R1) ;is SRTN set correctly? Beq 130$ ;yes Call Err5.3 130$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CMB6: ...CMB CD .=.-2 ;crush EMT Mov #Area,R1 ;point to area CmpB #..CURR!..DSPA!^o3,8.(R1) ;is flag set correctly? Beq 140$ ;yes Call Err6.1 ;no 140$: CmpB #0,9.(R1) ;is func set? Beq 150$ ;yes Call Err6.2 150$: Call AreaM1 ;init area Mov #Area,R0 ;point to area Mov #123456,R3 ..CMB7: ...CMB UI,S,R3 .=.-2 ;crush EMT Mov #Area,R1 ;point to area Cmp #..USER!..ISPA+^o3,8.(R1) ;is flag set correctly? Beq 160$ ;yes Call Err7.1 ;no 160$: Cmp #123456+1,10.(R1) ;is SRTN set correctly? Beq 170$ ;yes Call Err7.2 ;no 170$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CMB8: ...CMB SI .=.-2 ;crush EMT Mov #Area,R1 ;point to area Cmp #..SUPY!..ISPA!^o3,8.(R1) ;is flag set correctly? Beq 180$ ;yes Call Err8.1 ;no 180$: Cmp #-1,10.(R1) ;is SRTN unchanged? Beq 190$ ;yes Call Err8.1 ;no 190$: Call AreaM1 ;init area Mov #Area,R0 ;point to area ..CMB9: ...CMB CI .=.-2 ;crush EMT Mov #Area,R1 ;point to area Cmp #..CURR!..ISPA!^o3,8.(R1) ;is flag set correctly? Beq 200$ ;yes Call Err9.1 ;no 200$: Cmp #-1,10.(R1) ;is SRTN unchanged? Beq 210$ ;yes Call Err9.1 ;no 210$: Call AreaM1 ;init area Mov #Area,R0 ;point to area Mov #302,R3 Mov #101010,8.(R0) ;-1 is expected value ..CMBA: ...CMB ,,#123456,R3,S .=.-2 ;crush EMT Mov #Area,R1 CmpB #377,8.(R1) ;is flag set? Beq 220$ ;yes Call ErrA.1 ;no 220$: CmpB #302,9.(R1) ;is func set? Beq 230$ ;yes Call ErrA.2 ;no 230$: Cmp #123456,10.(R1) ;is SRTN set? Beq 240$ ;yes Call ErrA.3 ;no 240$: Call AreaM1 ;init area Mov #Area,R0 ;point to area Mov #302,R3 Mov #101010,8.(R0) ;-1 is expected value ..CMBB: ...CMB ,,#123456,R3,S,CODE=NOSET .=.-2 ;crush EMT Mov #Area,R1 CmpB #010,8.(R1) ;is flag unchanged? Beq 250$ ;yes Call ErrB.1 ;no 250$: CmpB #302,9.(R1) ;is func set? Beq 260$ ;yes Call ErrB.2 ;no 260$: Cmp #123456,10.(R1) ;is SRTN set? Beq 270$ ;yes Call ErrB.3 ;no 270$: Call AreaM1 ;init area Mov #Area,R0 ;point to area Mov #101010,8.(R0) ;-1 is expected value ..CMBC: ...CMB UD,S,#123456,#302,S .=.-2 ;crush EMT Mov #Area,R1 CmpB #..USER!..DSPA!^o3,8.(R1) ;is flag set? Beq 280$ ;yes Call ErrC.1 ;no 280$: CmpB #302,9.(R1) ;is func set? Beq 290$ ;yes Call ErrC.2 ;no 290$: Cmp #123456+1,10.(R1) ;is SRTN set? Beq 300$ ;yes Call ErrC.3 ;no 300$: .PSect Data ..CMBD: ...CMB ,,#123456 .=.-2 310$: .=.+2 .PSect Active Cmp #EMT+375,310$ Beq 320$ Call ErrD.1 320$: .PSect Data ..CMBE: ...CMB *BYPASS*,#1 .=.-2 330$: .=.+2 .PSect Active Cmp #EMT+375,330$ Beq 340$ Call ErrE.1 340$: .PSect Data ..CMBF: ...CMB SD,,#2 .=.-2 350$: .=.+2 .PSect Active Cmp #EMT+375,350$ Beq 360$ Call ErrF.1 360$: .PSect Data ..CMBG: ...CMB UI,S,R3 .=.-2 370$: .=.+2 .PSect Active Cmp #EMT+375,370$ Beq 380$ Call ErrG.1 380$: .PSect Data ..CMBH: ...CMB CI .=.-2 390$: .=.+2 .PSect Active Cmp #EMT+375,390$ Beq 400$ Call ErrH.1 400$: Call EndTst .Dsabl LSB .If NE MAC$ER ;Expect P errors ...CMB XX ...CMB ,X ...CMB X,XX .EndC ;-TEST .SbTtl ...CMC Support .DSTATUS and .FETCH ;+ ; ; ...CMC ; ; This macro places the first argument on the stack and the ; second in R0. It handles most cases when the arguments ; interfer with each other (e.g.: when the first argument ; references R0 and/or the second, SP). ; The third argument specifies the EMT code number ; ; Addressing modes of the form: ; ; STACK R0 @R0 (R0)+ @(R0)+ -(R0) @-(R0) x(R0) @x(R0) ; @SP (SP)+ @(SP)+ x(SP) @x(SP) ; ; RZERO R0 SP @SP (SP)+ @(SP)+ x(SP) @x(SP) ; ; are considered special and have specific code generated for ; them. ; ; Some combinations of the special addressing modes are "hard" ; and are rejected with an error message. ; ; Addressing modes of the form: PC @PC -(PC) @-(PC) ; -(SP) @-(SP) ; are considered silly and not treated specially in this macro. ; ; If STACK is omitted it is defaulted to (SP)+, which means ; the macro assumes the value for the STACK argument is on ; the stack prior to invocation and it to be popped. ; ; IF RZERO is omitted it is defaulted to R0, which means ; the macro assumes the value for the RZERO argument is in ; R0 prior to invocation (and is destroyed by the EMT). ; ; In general the arguments are processed left to right. ; When both arguments include references to SP, they may ; be processed in the reverse order. ; ; LOCAL SYMBOLS: ; ; ...V10 addressing type for STACK ; ...V11 addressing type for RZERO ; ...V2 =0 STACK is a special addressing mode ; <> STACK is a normal addressing mode ; ...V3 =0 RZERO is a special addressing mode ; <> RZERO is a normal addressing mode ; ...V4 =0 "hard" case if STACK is special ;- .MACRO ...CMC STACK,RZERO,INS ;get type/defaults .IF NB .NTYPE ...V10,STACK .IFF ...V10=^o26 ;default to (SP)+ .ENDC .IF NB .NTYPE ...V11,RZERO .IFF ...V11=0 ;default to R0 .ENDC ;sort out main types ...V2=^o<<...V10&7>*<...V10&7-6>> ;0=STACK is special ...V3=...V11*^o<...V11&7-6> ;0=RZERO is special ...V4=^o<<...V11-26>*<...V11-36>*<...V11-76>> ;0=probable hard case .IF NE ...V2&...V3 ;nothing special ...CM0 ...CM5 ,INS .MEXIT .ENDC .IF EQ ...V2!...V4 ;STACK special, hard case .ERROR;?SYSMAC-E-Argument interrelationship too complex; .MEXIT .ENDC ;args already in place? .IF EQ ...V11 ;RZERO=R0 .IF EQ ...V10-^o26 ;STACK=(SP)+ EMT ^o .IFF ;R0 is, STACK isn't ...CM0 ,INS .ENDC .MEXIT .ENDC .IF EQ ...V11-^o66 ;RZERO=x(SP) .IF EQ ...V2 ;STACK special ...CM0 ...CM5 <2.+RZERO>,INS .MEXIT .ENDC .ENDC .IF EQ ...V2 ;STACK is special .IF EQ ...V11-^o16 ;RZERO= @SP ...CM0 ...CM5 2.(SP),INS .MEXIT .ENDC .ENDC .IF EQ ...V10-^o26 ;STACK=(SP)+ ...CM5 ,INS .MEXIT .ENDC ...CM5 ...CM0 ,INS .ENDM ;+TEST ; STACK RZERO INS ; 200 ; R0 R0 200 ; SP SP 200 ; @R1 @SP 200 ; @SP x(R2) 200 ; (R4)+ (SP)+ 200 ; (SP)+ R0 200 ; (SP)+ (R3)+ 200 ; @(R1)+ @(SP)+ 200 ; @(PC)+ x(SP) 200 ; @x(R4) @x(SP) 200 ; R0 @SP 200 ; R0 x(SP) 200 ; @R0 @SP 200 ; @R0 x(SP) 200 ; @SP @SP 200 ; @SP x(SP) 200 ; (R0)+ @SP 200 ; (R0)+ x(SP) 200 ; (SP)+ @SP 200 ; (SP)+ x(SP) 200 ; @(R0)+ @SP 200 ; @(R0)+ x(SP) 200 ; @(SP)+ @SP 200 ; @(SP)+ x(SP) 200 ; -(R0) @SP 200 ; -(R0) x(SP) 200 ; @R0 @SP 200 ; @R0 x(SP) 200 ; @-(R0) x(SP) 200 ; @-(R0) @SP 200 ; x(R0) @SP 200 ; x(R0) x(SP) 200 ; x(SP) @SP 200 ; x(SP) x(SP) 200 ; @x(R0) @SP 200 ; @x(R0) x(SP) 200 ; @x(SP) @SP 200 ; @x(SP) x(SP) 200 ; R0 (SP)+ 200 Expect Error ; R0 @(SP)+ 200 Expect Error ; R0 @x(SP) 200 Expect error ; @R0 (SP)+ 200 Expect Error ; @R0 @(SP)+ 200 Expect Error ; @R0 @x(SP) 200 Expect error ; @SP (SP)+ 200 Expect Error ; @SP @(SP)+ 200 Expect Error ; @SP @x(SP) 200 Expect error ; (R0)+ (SP)+ 200 Expect Error ; (R0)+ @(SP)+ 200 Expect Error ; (R0)+ @x(SP) 200 Expect error ; (SP)+ (SP)+ 200 Expect Error ; (SP)+ @(SP)+ 200 Expect Error ; (SP)+ @x(SP) 200 Expect error ; @(R0)+ (SP)+ 200 Expect Error ; @(R0)+ @(SP)+ 200 Expect Error ; @(R0)+ @x(SP) 200 Expect error ; @(SP)+ (SP)+ 200 Expect Error ; @(SP)+ @(SP)+ 200 Expect Error ; @(SP)+ @x(SP) 200 Expect error ; -(R0) (SP)+ 200 Expect Error ; -(R0) @(SP)+ 200 Expect Error ; -(R0) @x(SP) 200 Expect error ; @R0 (SP)+ 200 Expect Error ; @R0 @(SP)+ 200 Expect Error ; @R0 @x(SP) 200 Expect error ; @-(R0) (SP)+ 200 Expect Error ; @-(R0) @(SP)+ 200 Expect Error ; @-(R0) @x(SP) 200 Expect error ; x(R0) (SP)+ 200 Expect Error ; x(R0) @(SP)+ 200 Expect Error ; x(R0) @x(SP) 200 Expect error ; x(SP) (SP)+ 200 Expect Error ; x(SP) @(SP)+ 200 Expect Error ; x(SP) @x(SP) 200 Expect error ; @x(R0) (SP)+ 200 Expect Error ; @x(R0) @(SP)+ 200 Expect Error ; @x(R0) @x(SP) 200 Expect error ; @x(SP) (SP)+ 200 Expect Error ; @x(SP) @(SP)+ 200 Expect Error ; @x(SP) @x(SP) 200 Expect error .Enabl LSB .PSect Text $..CMC: .Asciz "%SYSMAC-I-Testing ...CMC" $.CMC0: .Asciz "%SYSMAC-I-tests 01-09" $.CMC1: .Asciz "%SYSMAC-I-tests 11-19" $.CMC2: .Asciz "%SYSMAC-I-tests 21-29" $.CMC3: .Asciz "%SYSMAC-I-tests 31-39" $.CMC4: .Asciz "%SYSMAC-I-tests 41-49" $.CMC5: .Asciz "%SYSMAC-I-tests 51-59" .PSect Active Mov #$..CMC,R0 ;Ident the test Call BegTst .Print #$.CMC0 ; 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #377,R0 ;preload R0 Mov #123456,-(SP) ;value to stack .CMC01: ...CMC ,,200 ;blank arguments .=.-2 ;squash EMT Cmp #377,R0 ;is R0 ok? Beq 101$ ;yes Call Err1.1 101$: Cmp #123456,(SP)+ ;value on stack ok? Beq 102$ ;yes Call Err1.2 102$: Cmp SP,R5 ;stack aligned? Beq 103$ ;yes Call Err1.3 103$: Mov R5,SP ; R0 R0 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #12,R0 ;value for stack and R0 Mov #Patter,-(SP) ;put strange pattern on stack Tst (SP)+ ;restore stack .CMC02: ...CMC R0,R0,200 .=.-2 ;squash EMT Cmp #12,R0 ;is R0 ok? Beq 201$ ;yes Call Err2.1 201$: Cmp #12,(SP)+ ;value on stack ok? Beq 202$ ;yes Call Err2.2 202$: Cmp SP,R5 ;stack aligned? Beq 203$ ;yes Call Err2.3 203$: Mov R5,SP ; SP SP 200 ;;;.CMC03: ...CMC SP,SP,200 DELETED - causes Z error ; @R1 @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #404$,R1 .PSect Data 404$: .Word 12 .PSect Active Mov #255,-(SP) Mov #Patter,-(SP) ;put strange pattern on stack Tst (SP)+ ;restore stack .CMC04: ...CMC @R1,@SP,200 .=.-2 ;squash EMT Cmp #255,R0 ;is R0 ok? Beq 401$ ;yes Call Err4.1 401$: Cmp #12,(SP)+ ;value on stack ok? Beq 402$ ;yes Call Err4.2 402$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 403$ ;yes Call Err4.3 403$: Mov R5,SP ; @SP x(R2) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #504$-4,R2 .PSect Data 504$: .Word 12 .PSect Active Mov #255,-(SP) Mov #Patter,-(SP) ;put strange pattern on stack Tst (SP)+ ;restore stack .CMC05: ...CMC @SP,4(R2),200 .=.-2 ;squash EMT Cmp #12,R0 ;is R0 ok? Beq 501$ ;yes Call Err5.1 501$: Cmp #255,(SP)+ ;value on stack ok? Beq 502$ ;yes Call Err5.2 502$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 503$ ;yes Call Err5.3 503$: Mov R5,SP ; (R4)+ (SP)+ 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #605$,R4 .PSect Data 605$: .Word 12 .PSect Active Mov #255,-(SP) ;preload stack .CMC06: ...CMC (R4)+,(SP)+,200 .=.-2 ;squash EMT Cmp #255,R0 ;is R0 ok? Beq 601$ ;yes Call Err6.1 601$: Cmp #12,(SP)+ ;value on stack ok? Beq 602$ ;yes Call Err6.2 602$: Cmp SP,R5 ;stack aligned? Beq 603$ ;yes Call Err6.3 603$: Cmp R4,#605$+2 Beq 604$ Call Err6.4 604$: Mov R5,SP ; (SP)+ R0 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #7,R0 ;preload R0 Mov #255,-(SP) ;preload stack .CMC07: ...CMC (SP)+,R0,200 .=.-2 ;squash EMT Cmp #7,R0 ;is R0 ok? Beq 701$ ;yes Call Err7.1 701$: Cmp #255,(SP)+ ;value on stack ok? Beq 702$ ;yes Call Err7.2 702$: Cmp SP,R5 ;stack aligned? Beq 703$ ;yes Call Err6.3 703$: Mov R5,SP ; (SP)+ (R3)+ 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #805$,R3 .PSect Data 805$: .Word 12 .PSect Active Mov #255,-(SP) ;preload stack .CMC08: ...CMC (SP)+,(R3)+,200 .=.-2 ;squash EMT Cmp #12,R0 ;is R0 ok? Beq 801$ ;yes Call Err8.1 801$: Cmp #255,(SP)+ ;value on stack ok? Beq 802$ ;yes Call Err8.2 802$: Cmp SP,R5 ;stack aligned? Beq 803$ ;yes Call Err8.3 803$: Cmp R3,#805$+2 Beq 804$ Call Err8.4 804$: Mov R5,SP ; @(R1)+ @(SP)+ 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #909$,R1 Mov #907$,-(SP) .PSect Data 909$: .Word 908$ 908$: .Word 12 907$: .Word 34 .PSect Active .CMC09: ...CMC @(R1)+,@(SP)+,200 .=.-2 ;squash EMT Cmp #34,R0 ;is R0 ok? Beq 901$ ;yes Call Err9.1 901$: Cmp #12,(SP)+ ;value on stack ok? Beq 902$ ;yes Call Err9.2 902$: Cmp SP,R5 ;stack aligned? Beq 903$ ;yes Call Err9.3 903$: Cmp R1,#909$+2 Beq 904$ Call Err9.4 904$: .Print #$.CMC1 Mov R5,SP ; @(PC)+ x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #17,-(SP) ;argument value on stack Tst -(SP) ;junk on stack .CMC11: ...CMC #73,2(SP),200 .=.-2 ;squash EMT Cmp #17,R0 ;is R0 ok? Beq 1101$ ;yes Call Err1.1 1101$: Cmp #73,(SP)+ ;value on stack ok? Beq 1102$ ;yes Call Err1.2 1102$: Cmp (SP)+,(SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1103$ ;yes Call Err1.3 1103$: Mov R5,SP ; @x(R4) @x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1208$-2,R4 Mov #1209$,-(SP) ;argument value on stack .PSect Data 1209$: .Word 17 1208$: .Word 1207$ 1207$: .Word 3 .PSect Active Tst -(SP) ;junk on stack Mov #Patter,R0 .CMC12: ...CMC @2(R4),@2(SP),200 .=.-2 ;squash EMT Cmp #17,R0 ;is R0 ok? Beq 1201$ ;yes Call Err2.1 1201$: Cmp #3,(SP)+ ;value on stack ok? Beq 1202$ ;yes Call Err2.2 1202$: Cmp (SP)+,(SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1203$ ;yes Call Err2.3 1203$: Mov R5,SP ; R0 @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #773,R0 ;preload R0 Mov #221,-(SP) ;preload stack Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC13: ...CMC R0,@SP,200 .=.-2 ;squash EMT Cmp #221,R0 ;is R0 ok? Beq 1301$ ;yes Call Err3.1 1301$: Cmp #773,(SP)+ ;value on stack ok? Beq 1302$ ;yes Call Err3.2 1302$: Tst (SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1303$ ;yes Call Err3.3 1303$: Mov R5,SP ; R0 x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #773,R0 ;preload R0 Mov #321,-(SP) ;preload stack Mov #Patter,-(SP) ;junk on stack Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC14: ...CMC R0,2(SP),200 .=.-2 ;squash EMT Cmp #321,R0 ;is R0 ok? Beq 1401$ ;yes Call Err4.1 1401$: Cmp #773,(SP)+ ;value on stack ok? Beq 1402$ ;yes Call Err4.2 1402$: Cmp (SP)+,(SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1403$ ;yes Call Err4.3 1403$: Mov R5,SP ; @R0 @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1509$,R0 ;preload R0 .PSect Data 1509$: .Word 333 .PSect Active Mov #123,-(SP) ;preload stack Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC15: ...CMC @R0,@SP,200 .=.-2 ;squash EMT Cmp #123,R0 ;is R0 ok? Beq 1501$ ;yes Call Err5.1 1501$: Cmp #333,(SP)+ ;value on stack ok? Beq 1502$ ;yes Call Err5.2 1502$: Tst (SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1503$ ;yes Call Err5.3 1503$: Mov R5,SP ; @R0 x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1609$,R0 ;preload R0 Mov #332,-(SP) ;preload stack .PSect Data 1609$: .Word 321 .PSect Active Tst -(SP) ;push down stack Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC16: ...CMC @R0,2(SP),200 .=.-2 ;squash EMT Cmp #332,R0 ;is R0 ok? Beq 1601$ ;yes Call Err6.1 1601$: Cmp #321,(SP)+ ;value on stack ok? Beq 1602$ ;yes Call Err6.2 1602$: Cmp (SP)+,(SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1603$ ;yes Call Err6.3 1603$: Mov R5,SP ; @SP @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #222,-(SP) .CMC17: ...CMC @SP,@SP,200 .=.-2 ;squash EMT Cmp #222,R0 ;is R0 ok? Beq 1701$ ;yes Call Err7.1 1701$: Cmp #222,(SP)+ ;value on stack ok? Beq 1702$ ;yes Call Err7.2 1702$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 1703$ ;yes Call Err7.3 1703$: Mov R5,SP ; @SP x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #332,-(SP) ;preload stack Mov #223,-(SP) ;preload stack Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC18: ...CMC @SP,2(SP),200 .=.-2 ;squash EMT Cmp #332,R0 ;is R0 ok? Beq 1801$ ;yes Call Err8.1 1801$: Cmp #223,(SP)+ ;value on stack ok? Beq 1802$ ;yes Call Err8.2 1802$: Cmp (SP)+,(SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1803$ ;yes Call Err8.3 1803$: Mov R5,SP ; (R0)+ @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1909$,R0 ;Point to argument .PSect Data 1909$: .Word 222 .PSect Active Mov #223,-(SP) ;preload stack Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC19: ...CMC (R0)+,@SP,200 .=.-2 ;squash EMT Cmp #223,R0 ;is R0 ok? Beq 1901$ ;yes Call Err9.1 1901$: Cmp #222,(SP)+ ;value on stack ok? Beq 1902$ ;yes Call Err9.2 1902$: Tst (SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 1903$ ;yes Call Err9.3 1903$: .Print #$.CMC2 Mov R5,SP ; (R0)+ x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #2109$,R0 ;Point to argument .PSect Data 2109$: .Word 777 .PSect Active Mov #223,-(SP) ;preload stack Mov #Patter,-(SP) ;push it down Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC21: ...CMC (R0)+,2(SP),200 .=.-2 ;squash EMT Cmp #223,R0 ;is R0 ok? Beq 2101$ ;yes Call Err1.1 2101$: Cmp #777,(SP)+ ;value on stack ok? Beq 2102$ ;yes Call Err1.2 2102$: Cmp (SP)+,(SP)+ ;dump temp stuff Cmp SP,R5 ;stack aligned? Beq 2103$ ;yes Call Err1.3 2103$: Mov R5,SP ; (SP)+ @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #223,-(SP) ;preload stack Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC22: ...CMC (SP)+,@SP,200 .=.-2 ;squash EMT Cmp #223,R0 ;is R0 ok? Beq 2201$ ;yes Call Err2.1 2201$: Cmp #1234,(SP)+ ;value on stack ok? Beq 2202$ ;yes Call Err2.2 2202$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 2203$ ;yes Call Err2.3 2203$: Mov R5,SP ; (SP)+ x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #223,-(SP) ;preload stack Mov #Patter,-(SP) ;and push some more Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC23: ...CMC (SP)+,2(SP),200 .=.-2 ;squash EMT Cmp #223,R0 ;is R0 ok? Beq 2301$ ;yes Call Err3.1 2301$: Cmp #1234,(SP)+ ;value on stack ok? Beq 2302$ ;yes Call Err3.2 2302$: Cmp (SP)+,(SP)+ ;dump junk Cmp SP,R5 ;stack aligned? Beq 2303$ ;yes Call Err3.3 2303$: Mov R5,SP ; @(R0)+ @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #2409$,R0 ;preload R0 .PSect Data 2409$: .Word 2408$ 2408$: .Word 654 .PSect Active Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC24: ...CMC @(R0)+,@SP,200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 2401$ ;yes Call Err4.1 2401$: Cmp #654,(SP)+ ;value on stack ok? Beq 2402$ ;yes Call Err4.2 2402$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 2403$ ;yes Call Err4.3 2403$: Mov R5,SP ; @(R0)+ x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #2509$,R0 ;preload stack .PSect Data 2509$: .Word 2508$ 2508$: .Word 324 .PSect Active Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;and again Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC25: ...CMC @(R0)+,2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 2501$ ;yes Call Err5.1 2501$: Cmp #324,(SP)+ ;value on stack ok? Beq 2502$ ;yes Call Err5.2 2502$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 2503$ ;yes Call Err5.3 2503$: Mov R5,SP ; @(SP)+ @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1233,-(SP) ;push it down Mov #2609$,-(SP) ;preload stack .PSect Data 2609$: .Word 323 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC26: ...CMC @(SP)+,@SP,200 .=.-2 ;squash EMT Cmp #1233,R0 ;is R0 ok? Beq 2601$ ;yes Call Err6.1 2601$: Cmp #323,(SP)+ ;value on stack ok? Beq 2602$ ;yes Call Err6.2 2602$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 2603$ ;yes Call Err6.3 2603$: Mov R5,SP ; @(SP)+ x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;bury it Mov #2709$,-(SP) ;push .PSect Data 2709$: .Word 3333 .Psect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC27: ...CMC @(SP)+,2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 2701$ ;yes Call Err7.1 2701$: Cmp #3333,(SP)+ ;value on stack ok? Beq 2702$ ;yes Call Err7.2 2702$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 2703$ ;yes Call Err7.3 2703$: Mov R5,SP ; -(R0) @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #2809$+2,R0 ;preload R0 .PSect Data 2809$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC28: ...CMC -(R0),@SP,200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 2801$ ;yes Call Err8.1 2801$: Cmp #324,(SP)+ ;value on stack ok? Beq 2802$ ;yes Call Err8.2 2802$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 2803$ ;yes Call Err8.3 2803$: Mov R5,SP ; -(R0) x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;and cover it Mov #2909$+2,R0 ;preload R0 .PSect Data 2909$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC29: ...CMC -(R0),2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 2901$ ;yes Call Err9.1 2901$: Cmp #324,(SP)+ ;value on stack ok? Beq 2902$ ;yes Call Err9.2 2902$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 2903$ ;yes Call Err9.3 2903$: .Print #$.CMC3 Mov R5,SP ; @R0 @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #3109$,R0 ;preload R0 .PSect Data 3109$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC31: ...CMC @R0,@SP,200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3101$ ;yes Call Err1.1 3101$: Cmp #324,(SP)+ ;value on stack ok? Beq 3102$ ;yes Call Err1.2 3102$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 3103$ ;yes Call Err1.3 3103$: Mov R5,SP ; @R0 x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;and cover it up Mov #3209$,R0 ;preload R0 .PSect Data 3209$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC32: ...CMC @R0,2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3201$ ;yes Call Err2.1 3201$: Cmp #324,(SP)+ ;value on stack ok? Beq 3202$ ;yes Call Err2.2 3202$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 3203$ ;yes Call Err2.3 3203$: Mov R5,SP ; @-(R0) x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;and cover it up Mov #3309$+2,R0 ;preload R0 .PSect Data 3309$: .Word 3308$ 3308$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC33: ...CMC @-(R0),2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3301$ ;yes Call Err3.1 3301$: Cmp #324,(SP)+ ;value on stack ok? Beq 3302$ ;yes Call Err3.2 3302$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 3303$ ;yes Call Err3.3 3303$: Mov R5,SP ; @-(R0) @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #3409$+2,R0 ;preload R0 .PSect Data 3409$: .Word 3408$ 3408$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC34: ...CMC @-(R0),@SP,200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3401$ ;yes Call Err4.1 3401$: Cmp #324,(SP)+ ;value on stack ok? Beq 3402$ ;yes Call Err4.2 3402$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 3403$ ;yes Call Err4.3 3403$: Mov R5,SP ; x(R0) x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;and cover it up Mov #3509$-2,R0 ;preload R0 .PSect Data 3509$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC35: ...CMC 2(R0),2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3501$ ;yes Call Err5.1 3501$: Cmp #324,(SP)+ ;value on stack ok? Beq 3502$ ;yes Call Err5.2 3502$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 3503$ ;yes Call Err5.3 3503$: Mov R5,SP ; x(SP) @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #324,-(SP) ;preload R0 Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC36: ...CMC 2(SP),@SP,200 .=.-2 ;squash EMT Cmp #324,R0 ;is R0 ok? Beq 3601$ ;yes Call Err6.1 3601$: Cmp #1234,(SP)+ ;value on stack ok? Beq 3602$ ;yes Call Err6.2 3602$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 3603$ ;yes Call Err6.3 3603$: Mov R5,SP ; x(SP) x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #4321,-(SP) ;and put in another Mov #Patter,-(SP) ;and cover it up Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC37: ...CMC 2(SP),4(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3701$ ;yes Call Err7.1 3701$: Cmp #4321,(SP)+ ;value on stack ok? Beq 3702$ ;yes Call Err7.2 3702$: Cmp (SP)+,(SP)+ Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 3703$ ;yes Call Err7.3 3703$: Mov R5,SP ; @x(R0) @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #3809$-2,R0 ;preload R0 .PSect Data 3809$: .Word 3808$ 3808$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC38: ...CMC @2(R0),@SP,200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3801$ ;yes Call Err8.1 3801$: Cmp #324,(SP)+ ;value on stack ok? Beq 3802$ ;yes Call Err8.2 3802$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 3803$ ;yes Call Err8.3 3803$: Mov R5,SP ; @x(R0) x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;and cover it up Mov #3909$-2,R0 ;preload R0 .PSect Data 3909$: .Word 3908$ 3908$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC39: ...CMC @2(R0),2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 3901$ ;yes Call Err9.1 3901$: Cmp #324,(SP)+ ;value on stack ok? Beq 3902$ ;yes Call Err9.2 3902$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 3903$ ;yes Call Err9.3 3903$: .Print #$.CMC4 Mov R5,SP ; @x(SP) @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #4109$,-(SP) ;push it down .PSect Data 4109$: .Word 1234 .PSect Active Mov #350,-(SP) ;preload R0 Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC41: ...CMC @2(SP),@SP,200 .=.-2 ;squash EMT Cmp #350,R0 ;is R0 ok? Beq 4101$ ;yes Call Err1.1 4101$: Cmp #1234,(SP)+ ;value on stack ok? Beq 4102$ ;yes Call Err1.2 4102$: Cmp (SP)+,(SP)+ Cmp SP,R5 ;stack aligned? Beq 4103$ ;yes Call Err1.3 4103$: Mov R5,SP ; @x(SP) x(SP) 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #4209$,-(SP) ;preload R0 .PSect Data 4209$: .Word 2345 .PSect Active Mov #1234,-(SP) ;push it down Mov #Patter,-(SP) ;shove it down Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC42: ...CMC @4(SP),2(SP),200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 4201$ ;yes Call Err2.1 4201$: Cmp #2345,(SP)+ ;value on stack ok? Beq 4202$ ;yes Call Err2.2 4202$: Cmp (SP)+,(SP)+ Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 4203$ ;yes Call Err2.3 4203$: Mov R5,SP ; x(R0) @SP 200 Mov #Patter,R0 ;trash R0 Mov SP,R5 ;current stack alignment Mov #1234,-(SP) ;push it down Mov #4909$-2,R0 ;preload R0 .PSect Data 4909$: .Word 324 .PSect Active Mov #Patter,-(SP) ;junk on stack Tst (SP)+ ;pop junk .CMC49: ...CMC 2(R0),@SP,200 .=.-2 ;squash EMT Cmp #1234,R0 ;is R0 ok? Beq 4901$ ;yes Call Err9.1 4901$: Cmp #324,(SP)+ ;value on stack ok? Beq 4902$ ;yes Call Err9.2 4902$: Tst (SP)+ Cmp SP,R5 ;stack aligned? Beq 4903$ ;yes Call Err9.3 4903$: Mov R5,SP .Print #$.CMC5 .PSect Data .CMC52: ...CMC (SP)+,R0,200 .=.-2 5209$: .=.+2 .PSect Active Cmp #EMT+200,5209$ Beq 5201$ Call Err2.1 5201$: .PSect Data .CMC53: ...CMC R4,R0,200 .=.-2 5309$: .=.+2 .PSect Active Cmp #EMT+200,5309$ Beq 5301$ Call Err3.1 5301$: .PSect Data .CMC54: ...CMC (SP)+,2(SP),200 .=.-2 5409$: .=.+2 .PSect Active Cmp #EMT+200,5409$ Beq 5401$ Call Err4.1 5401$: .PSect Data .CMC55: ...CMC (SP)+,R4,200 .=.-2 5509$: .=.+2 .PSect Active Cmp #EMT+200,5509$ Beq 5501$ Call Err5.1 5501$: .PSect Data .CMC56: ...CMC R0,@SP,200 .=.-2 5609$: .=.+2 .PSect Active Cmp #EMT+200,5609$ Beq 5601$ Call Err6.1 5601$: .PSect Data .CMC57: ...CMC R4,2(SP),200 .=.-2 5709$: .=.+2 .PSect Active Cmp #EMT+200,5709$ Beq 5701$ Call Err7.1 5701$: .PSect Data .CMC58: ...CMC @R0,@SP,200 .=.-2 5809$: .=.+2 .PSect Active Cmp #EMT+200,5809$ Beq 5801$ Call Err8.1 5801$: Mov R5,SP .IF NE MAC$ER ...CMC R0 (SP)+ 200 ; Expect Error ...CMC R0 @(SP)+ 200 ; Expect Error ...CMC R0 @x(SP) 200 ; Expect error ...CMC @R0 (SP)+ 200 ; Expect Error ...CMC @R0 @(SP)+ 200 ; Expect Error ...CMC @R0 @x(SP) 200 ; Expect error ...CMC @SP (SP)+ 200 ; Expect Error ...CMC @SP @(SP)+ 200 ; Expect Error ...CMC @SP @x(SP) 200 ; Expect error ...CMC (R0)+ (SP)+ 200 ; Expect Error ...CMC (R0)+ @(SP)+ 200 ; Expect Error ...CMC (R0)+ @x(SP) 200 ; Expect error ...CMC (SP)+ (SP)+ 200 ; Expect Error ...CMC (SP)+ @(SP)+ 200 ; Expect Error ...CMC (SP)+ @x(SP) 200 ; Expect error ...CMC @(R0)+ (SP)+ 200 ; Expect Error ...CMC @(R0)+ @(SP)+ 200 ; Expect Error ...CMC @(R0)+ @x(SP) 200 ; Expect error ...CMC @(SP)+ (SP)+ 200 ; Expect Error ...CMC @(SP)+ @(SP)+ 200 ; Expect Error ...CMC @(SP)+ @x(SP) 200 ; Expect error ...CMC -(R0) (SP)+ 200 ; Expect Error ...CMC -(R0) @(SP)+ 200 ; Expect Error ...CMC -(R0) @x(SP) 200 ; Expect error ...CMC @R0 (SP)+ 200 ; Expect Error ...CMC @R0 @(SP)+ 200 ; Expect Error ...CMC @R0 @x(SP) 200 ; Expect error ...CMC @-(R0) (SP)+ 200 ; Expect Error ...CMC @-(R0) @(SP)+ 200 ; Expect Error ...CMC @-(R0) @x(SP) 200 ; Expect error ...CMC x(R0) (SP)+ 200 ; Expect Error ...CMC x(R0) @(SP)+ 200 ; Expect Error ...CMC x(R0) @x(SP) 200 ; Expect error ...CMC x(SP) (SP)+ 200 ; Expect Error ...CMC x(SP) @(SP)+ 200 ; Expect Error ...CMC x(SP) @x(SP) 200 ; Expect error ...CMC @x(R0) (SP)+ 200 ; Expect Error ...CMC @x(R0) @(SP)+ 200 ; Expect Error ...CMC @x(R0) @x(SP) 200 ; Expect error ...CMC @x(SP) (SP)+ 200 ; Expect Error ...CMC @x(SP) @(SP)+ 200 ; Expect Error ...CMC @x(SP) @x(SP) 200 ; Expect error .EndC; NE MAC$ER Call EndTst Mov R5,SP ;-TEST .Page .SbTtl ...CMV Define monitor prefix, release, version, and suffix ;+ ; ...CMV ; ; The ...CMV macro defines the system identification number ; and letters for various system components. It is provided ; in SYSMAC, so that changes to it need to be done only in one ; place and so that the monitor sources will be (potentially) ; version independent, in that a change to the system version ; identification will not require changing monitor sources. ; ; NOTE: to change the release value defaulted for .MODULE, you ; must also alter the .MODULE definition. The value in .MODULE ; RELEASE=prr should be defined as p being the same as ...CMV ; XPREFIX=p and rr being the same as ...CMV XRELEASE=rr ; ; SUFFIX should be defaulted to space. ; SUFFIX may be 1 or 2 characters long. ; ; Assuming XPREFIX=X, XRELEASE=05, XVERSION=09,XSUFFIX=ca ; ; TYPE=Z generate .ASCIZ (default) .ASCIZ "X05.09 ca" ; TYPE=I generate .ASCII .ASCII "X05.09 ca" ; TYPE=V generate values RT$%%% =: ... ; ; For TYPE=Z or I the following is generated: ; ; PART=ALL generate std ID (default) .ASCIZ "X05.09 ca" ; PART=PREFIX generate letter prefix .ASCIZ "X" ; PART=RELEASEgenerate release infix .ASCIZ "05" ; PART=VERSIONgenerate version infix .ASCIZ "09" ; PART=SUFFIX generate baselevel suffix .ASCIZ "ca" ; ; For TYPE=V the following is generated: ; ; PART=ALL all of the following ; PART=PREFIX RT$PRE =: 'X ; PART=RELEASE RT$RLS =: 05. ; PART=VERSION RT$VER =: 09. ; PART=SUFFIX RT$SUF =: 'c ; PART=SUBFIX RT$SUB =: 'a ;- .Page .MACRO ...CMV TYPE=Z,PART=ALL,XPREFIX=V,XRELEASE=05,XVERSION=07,XSUFFIX=< > .IF IDN .IF IDN RT$PRE =: ''XPREFIX RT$REL =: 'XRELEASE'. RT$VER =: 'XVERSION'. .IRPC x RT$SUF =: ''x .MEXIT .ENDR .IRPC x ...V2 = ''x .ENDR RT$SUB =: ...V2 .IFF .ASCI'TYPE' "'XPREFIX''XRELEASE'.'XVERSION' 'XSUFFIX'" .ENDC .ENDC .IF IDN .IF IDN RT$PRE =: ''XPREFIX .IFF .ASCI'TYPE' "'XPREFIX'" .ENDC .ENDC .IF IDN .IF IDN RT$REL =: 'XRELEASE'. .IFF .ASCI'TYPE' "'XRELEASE'" .ENDC .ENDC .IF IDN .IF IDN RT$VER =: 'XVERSION'. .IFF .ASCI'TYPE' "'XVERSION'" .ENDC .ENDC .IF IDN .IF IDN .IRPC x RT$SUF =: ''x .MEXIT .ENDR .IFF .ASCI'TYPE' "'XSUFFIX'" .ENDC .ENDC .IF IDN .IF IDN .IRPC x ...V2 = ''x .ENDR RT$SUB =: ...V2 .IFF .ASCI'TYPE' "'XSUFFIX'" .ENDC .ENDC .ENDM ;+TEST .Page .List ME .PSect Text ...CMV TYPE=I,PART=ALL ...CMV TYPE=I,PART=PREFIX ...CMV TYPE=I,PART=RELEASE ...CMV TYPE=I,PART=VERSION ...CMV TYPE=I,PART=SUFFIX ...CMV TYPE=Z,PART=ALL ...CMV TYPE=Z,PART=PREFIX ...CMV TYPE=Z,PART=RELEASE ...CMV TYPE=Z,PART=VERSION ...CMV TYPE=Z,PART=SUFFIX ...CMV TYPE=V,PART=ALL ...CMV TYPE=V,PART=PREFIX ...CMV TYPE=V,PART=RELEASE ...CMV TYPE=V,PART=VERSION ...CMV TYPE=V,PART=SUFFIX .NList ME ;-TEST .Page .SbTtl ...CMY Verify that ...CMZ has not been altered ;+ ; ...CMY ; ; The ...CMY checks that the user has not patched ; out the ...CMZ message. If the ...CMZ code or ; message has been altered, the ...CMY causes a ; trap to 10 from location -1. ; ;NOTE: ...CMY and ...CMZ need to be nulled out / reestablished ; as a pair. ;- .MACRO ...CMY L0,L1,L2,L3 .ENDM ;.MACRO ...CMY L0=...CMA,L1=...CMZ,?L2,?L3 ; MOV R0,-(SP) ; MOV R1,-(SP) ; MOV #L0,R0 ; CLR R1 ;L2: ADD (R0)+,R1 ; CMP R0,#L1+2. ; BNE L2 ; CMP #...V8,R1 ; BEQ L3 ; MOV #-1,-(SP) ; MOV @SP,-(SP) ; CLC ; JMP @10 ;L3: ; MOV (SP)+,R1 ; MOV (SP)+,R0 ;.ENDM ;+TEST .Enabl LSB .PSect Text $..CMY: .Asciz "%SYSMAC-I-Testing ...CMY" .PSect Active Mov #$..CMY,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl ...CMZ Field test / DECUS bomb ;+ ; ...CMZ ; ; This macro is designed to be included in the startup code ; of each of the CUSPs and monitor images. It is designed ; to irritate users who are using field test software after ; the end of field test. During generation of field test ; baselevels, use the long definition of ...CMZ. When ; building the actual release software, use the "null" ; (2 line) definition of ...CMZ to remove the message. ; ; The macro has one argument which is to be set in each ; program: ; ; FUDGE -- Should be set to the edit level (.SL in SL) ; of each module. This will "randomize" the number ; of days after expiration that each component will ; start hassling the user. This will increase the ; irritation. ; ; The macro has 3 additional arguments which should be set ; in SYSMAC.MAC by the project leader at an arbitrary date ; following the end of field test: ; ; DAY -- day of the month 1-31 ; MON -- three letter month name (in English) ; YEAR -- last 2 digits of the year. ; ; The L0, L1 and L2 arguments should be left to default. ; ; NOTE: The date comparison used is NOT exact, it is ; a +-1 day test since the low bit of the day is lost. ;- .Page ;NOTE: for field test, uncomment first .MACRO, delete second .MACRO ; Then remove the .IF EQ 1 conditional and leave the Field ; Test message ; ;NOTE: ...CMY and ...CMZ need to be nulled out / reestablished ; as a pair. .MACRO ...CMZ FUDGE,DAY,MON,YEAR,L0,L1,L2 .ENDM ;.MACRO ...CMZ FUDGE=0,DAY=15,MON=SEP,YEAR=92,L0=...CMA,?L1,L2=...CMZ ;...V8=0 ;...V2=0 ;...V3=-1 ;.IRP X, ;...V2=...V2+1 ;.IIF IDN , ...V3=...V2 ;.ENDR ;.IIF LT ...V3 .ERROR ;?SYSMAC-E-Invalid date, found - 'MON'; ;L0: MOV R0,-(SP) ;Save work reg ; ...V8=...V8+MOV+0000+46 ; MOV #12*^o400,R0 ;.DATE ; ...V8=...V8+MOV+2700+00 ; ...V8=...V8+<12*^o400> ; EMT 374 ;... ; ...V8=...V8+EMT+374 ; MOV R0,-(SP) ;Save date ; ...V8=...V8+MOV+0000+46 ; ASL R0 ;/4 ; ...V8=...V8+ASL+00 ; ASL R0 ;... ; ...V8=...V8+ASL+00 ; SWAB R0 ;/2 to low byte ; ...V8=...V8+SWAB+00 ; SWAB @SP ;Year to high byte ; ...V8=...V8+SWAB+16 ; MOVB R0,@SP ;Combine them ; ...V8=...V8+MOVB+0000+16 ; BIC #^c17777,@SP ;Mask junk ; ...V8=...V8+BIC+2700+16 ; ...V8=...V8+^c17777 ; CMP #<'YEAR'.-72.>*^o400+<...V3*20>+</2>+,(SP)+ ;Past limit? ; ...V8=...V8+CMP+2700+26 ; ...V8=...V8+<<'YEAR'.-72.>*^o400+<...V3*20>+</2>+> ; BGE L2 ;No, skip message ; ...V8=...V8+BGE+ ; MOV PC,R0 ;PIC ; ...V8=...V8+MOV+0700+00 ; ADD #L1-.,R0 ;Load message addr ; ...V8=...V8+ADD+2700+00 ; ...V8=...V8+L1-.+4 ; EMT 351 ;.Print ; ...V8=...V8+EMT+351 ; BR L2 ;Skip text ; ...V8=...V8+BR+ ;.IF EQ 0 ;L1: .ASCIZ "?RT11-W-Field test over" ; ...V8=...V8+'?+<'R*^o400> ; ...V8=...V8+'T+<'1*^o400> ; ...V8=...V8+'1+<'-*^o400> ; ...V8=...V8+'W+<'-*^o400> ; ...V8=...V8+'F+<'i*^o400> ; ...V8=...V8+'e+<'l*^o400> ; ...V8=...V8+'d+<' *^o400> ; ...V8=...V8+'t+<'e*^o400> ; ...V8=...V8+'s+<'t*^o400> ; ...V8=...V8+' +<'o*^o400> ; ...V8=...V8+'v+<'e*^o400> ; ...V8=...V8+'r+<000*^o400> ; .EVEN ;.IFF ;L1: .ASCIZ "?DECUS-U-Pirated system" ; ...V8=...V8+'?+<'D*^o400> ; ...V8=...V8+'E+<'C*^o400> ; ...V8=...V8+'U+<'S*^o400> ; ...V8=...V8+'-+<'U*^o400> ; ...V8=...V8+'-+<'P*^o400> ; ...V8=...V8+'i+<'r*^o400> ; ...V8=...V8+'a+<'t*^o400> ; ...V8=...V8+'e+<'d*^o400> ; ...V8=...V8+' +<'s*^o400> ; ...V8=...V8+'y+<'s*^o400> ; ...V8=...V8+'t+<'e*^o400> ; ...V8=...V8+'m+<000*^o400> ;.ENDC ;L2: MOV (SP)+,R0 ;Restore work reg ; ...V8=...V8+MOV+2600+00 ;.ENDM ;+TEST .Enabl LSB .PSect Text $..CMZ: .Asciz "%SYSMAC-I-Testing ...CMZ" .PSect Active Mov #$..CMZ,R0 ;Ident the test Call BegTst Call SkpTst .If NE MAC$ER ;Expect P error ...CMZ MON=XXX .EndC ;-TEST .SbTtl .ABTIO Abort I/O on a channel .MACRO .ABTIO CHAN .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM3 ,11. .ENDM ;+TEST .PAGE .Enabl LSB .PSect Text $ABTIO: .Asciz "%SYSMAC-I-Testing .ABTIO" .PSect Active Mov #$ABTIO,R0 ;Ident the test(s) Call BegTst Mov #Patter,R0 ABTIO1: .ABTIO #0 .=.-2 ;squash EMT Cmp #.ABTIO*^o400+0,R0 ;Is R0 right? Beq 10$ Call Err1 10$: Mov #Patter,R0 ABTIO2: .ABTIO #1 .=.-2 ;squash EMT Cmp #.ABTIO*^o400+1,R0 ;Is R0 right? Beq 20$ Call Err2 20$: Mov #Patter,R0 ABTIO3: .ABTIO #^o377 .=.-2 ;squash EMT Cmp #.ABTIO*^o400+^o377,R0 ;Is R0 right? Beq 30$ Call Err3 30$: Mov #12,R0 ABTIO4: .ABTIO R0 .=.-2 ;squash EMT Cmp #.ABTIO*^o400+12,R0 ;Is R0 right? Beq 40$ Call Err4 40$: Mov #Patter,R0 Mov #1,R1 ABTIO5: .ABTIO R1 .=.-2 ;squash EMT Cmp #.ABTIO*^o400+1,R0 ;Is R0 right? Beq 50$ Call Err5 50$: Mov #Patter,R0 ABTIO6: .ABTIO 65$ ;try getting chan from an odd addr .=.-2 ;squash EMT .PSect Data .Odd 65$: .Byte 2 ;Channel 2 at an odd addr .Even .PSect Active Cmp #.ABTIO*^o400+2.,R0 ;Is R0 right? Beq 60$ Call Err6 60$: .PSect Data ABTIO7: .ABTIO .=.-2. 73$: .=.+2. 75$: .PSect Active Cmp #EMT+...R0,73$ ;was the correct EMT generated? Beq 70$ ;Yes Call Err7 70$: Call EndTst .Dsabl LSB Mov R5,SP ;-TEST .Page .SbTtl .ADDR Generate PIC equivalent of MOV #___, .MACRO .ADDR ADR,REG,TYPE .NTYPE ...V2,ADR .IIF NE ...V2-^o27 .ERROR ...V2; ?SYSMAC-E-Invalid A D R, expecting #..., found - ADR; .NTYPE ...V2,REG .IF EQ ...V2-^o46 .IF IDN , ADD PC,-(SP) .ERROR ; ?SYSMAC-W-This operation may produce random results; .IFF MOV PC,-(SP) .ENDC ADD ADR-.,@SP .MEXIT .ENDC .IF IDN , .IF GT ...V2-5. MOV REG,-(SP) .IFF JSR REG,@PC ADD ADR-.,REG .MEXIT .ENDC .ENDC .IF IDN , ADD PC,REG .IFF MOV PC,REG .ENDC ADD ADR-.,REG .IRP X,<0,1,2,3,4,5,10,11,12,13,14,15,16> .IIF EQ ...V2-^o'x ...V2=0 .ENDR .IIF NE ...V2 .ERROR ; ?SYSMAC-E-Invalid R E G, expecting Rx/@Rx/-(SP), found - REG; .ENDM ;+TEST .PSect Static .If NE MAC$ER ;Expect P error .ADDR 1,R0 ;Expect P error .ADDR R0,R0 ;Expect P error .ADDR @R0,R0 ;Expect P error .ADDR 1(R0),R0 ;Expect P error .ADDR @(R0),R0 ;Expect P error .ADDR -(R0),R0 ;Expect P error .ADDR (R0)+,R0 ;Expect P error .ADDR #1,-(SP),ADD ;Expect P error .ADDR #1,SP ;Expect P error .ADDR #1,1 ;Expect P error .ADDR #1,#1 ;Expect P error .ADDR #1,-(R0) ;Expect P error .ADDR #1,(R0)+ ;Expect P error .ADDR #1,1(R0) .EndC ;-TEST .Page .SbTtl .ASSUME Verify assumption at assembly time .MACRO .ASSUME A,REL,C,MESSAGE .IF REL <>-<> .IFF .IF B .ERROR;?SYSMAC-W-"A REL C" is not true; .IFF .ERROR ;?SYSMAC-MESSAGE; .ENDC .ENDC .ENDM .ASSUME ;+TEST .PSect Static .If NE MAC$ER ;Expect P error .ASSUME 1 EQ 0 ;Expect P error .ASSUME 1 EQ 0 MESSAGE=<...V1 ; this is a test> ;Expect P error .ASSUME 1 EQ 0 MESSAGE=<...V1; this is another test> .EndC ;-TEST .Page .SbTtl .AUDIT Generate module audit information in abs 110+ ;++ ; .AUDIT ; ; macro to generate list of versions starting at abs 110 ; ; up to 26 names ; ; First reference generates a RAD50 value for 110 of release ;-- .MACRO .AUDIT Q,W,E,R,T,Y,U,I,O,P,A,S,D,F,G,H,J,K,L,Z,X,C,V,B,N,M .SAVE .ASECT .IIF NDF ...V5 ...V5=^o110 .=...V5 .IF EQ .-^o110 .GLOBL .AUDIT .WORD .AUDIT .ENDC .IRP ...V2 .IF NB <...V2> .GLOBL '...V2' .WORD '...V2' .ENDC .ENDR ...V5=. .WORD -1 .RESTORE .ENDM .AUDIT ;+TEST ;>>>no static test ;-TEST .Page .SbTtl .BR Verify assumption of "Drop through" coding .MACRO .BR TO .IF P2 .IF DF TO .IF NE TO-. .ERROR;?SYSMAC-E-Not at location TO; .ENDC .IFF .ERROR;?SYSMAC-E-TO is not defined; .ENDC .ENDC .ENDM .BR ;+TEST .PSect Static .If NE MAC$ER ;Expect P error .BR 10$ .Word 10$: .Globl Global .BR Global .EndC ;-TEST .Page .SbTtl .CALLK Call a routine in kernel mapping .MACRO .CALLK Dest,Pic .IF NDF .MACS .MCALL .MACS .MACS .ENDC .IF NB .IF B ...CM0 Dest .IFF .MCALL .ADDR .ADDR Dest,-(SP) .ENDC .ENDC EMT ^o373 .ENDM ;+TEST .Enabl LSB .PSect Text $CALLK: .Asciz "%SYSMAC-I-Testing .CALLK" .PSect Active Mov #$CALLK,R0 ;Ident the test(s) Call BegTst .PSect Data CALLK1: .CallK .PSect Active Cmp #EMT+...CAL,CALLK1 ;correct EMT generated? Beq 20$ ;yes Call Err1 20$: Mov SP,R1 ;save stack pointer CALLK2: .CallK .=.-2 ;squash EMT Cmp SP,R1 ;stack aligned? Beq 30$ ;yes Call Err2 30$: Mov SP,R1 ;save stack pointer CALLK3: .CallK #CALLK3 .=.-2 ;squash EMT Cmp (SP)+,#CALLK3 ;correct value stacked? Beq 40$ ;yes Call Err3.1 40$: Cmp SP,R1 ;stack aligned? Beq 50$ ;yes Call Err3.2 50$: .PSect Data CALLK4: .CallK ,PIC .PSect Active Cmp #EMT+...CALL,CALLK4 ;correct EMT generated? Beq 70$ ;yes Call Err4 70$: Mov SP,R1 ;save stack pointer CALLK5: .CallK ,PIC .=.-2 ;squash EMT Cmp SP,R1 ;stack aligned? Beq 80$ ;yes Call Err5 80$: Mov SP,R1 ;save stack pointer CALLK6: .CallK #CALLK6,PIC .=.-2 ;squash EMT Cmp (SP)+,#CALLK6 ;correct value stacked? Beq 90$ ;yes Call Err6.1 90$: Cmp SP,R1 ;stack aligned? Beq 100$ ;yes Call Err6.2 100$: Call EndTst ;end of test .Dsabl LSB ;-TEST .Page .SBTTL .CALLS call to supervisor mode ;+ ; .CALLS ; ; This macro generates a standardized call to supervisor mode ; that is designed to interface with the SHANDL interrupt ; handler. ; ; It may called in two forms: ; ; .CALLS #0 ;special "do anything call" ; .CALLS #non-zero ;standard call ; ; The #0 form requires that a PS and PC be pushed on the stack. ; These will be RTIed after the transfer to supervisor mode. ; ; The #non-zero form specifies a virtual address in supervisor I ; space to transfer to. The # addressing mode is recommended, as ; other addressing modes will not be simulated on non-CSM machines ; ; As part of the return path from a supervisor mode routine, SHANDL ; moves all or part of the condition code settings from the Supy PS ; to the User PS. The condition codes to be transferred are listed ; in the RETURN argument. It defaults to NZVC. ;- .MACRO .CALLS DEST,RETURN=NZVC .IF DIF ,<#0> ...V4=0 .IF DIF , ...V4 = 1 .DSABL LCM .ENDC ...V2=0 .IF NB .IRPC x,'RETURN' ...V3=0 .IIF IDN x,C ...V3=2. .IIF IDN x,V ...V3=4. .IIF IDN x,Z ...V3=8. .IIF IDN x,N ...V3=16. .IIF EQ ...V3,.ERROR;?SYSMAC-E-Invalid R E T U R N, expecting N,Z,V,C found - 'return'; ...V2=...V2!...V3 .ENDR .ENDC .IIF NE ...V4 .ENABL LCM MOV #...V2,-(SP) .ENDC CSM DEST .ENDM ;+TEST .PAGE .Enabl LSB .list meb;**DEBUG** .PSect Text $CALLS: .Asciz "%SYSMAC-I-Testing .CALLS" $CCNIL=0*2 $CCC=1.*2 $CCV=2.*2 $CCVC=3.*2 $CCZ=4.*2 $CCZC=5.*2 $CCZV=6.*2 $CCZVC=7.*2 $CCN=8.*2 $CCNC=9.*2 $CCNV=10.*2 $CCNVC=11.*2 $CCNZ=12.*2 $CCNZC=13.*2 $CCNZV=14.*2 $CCALL=15.*2 .PSect Active Mov #$CALLS,R0 ;Ident the test(s) Call BegTst .PSect Data CALLS1: .CALLS #0 10$: .=.-4. 20$: .=.+4. .PSect Active Cmp #4,#10$-CALLS1 ;was only one instruction generated? Beq 30$ ;yes Call Err1.1 30$: Cmp #CSM+27,20$ ;was the correct opcode generated? Beq 40$ ;Yes Call Err1.2 40$: Cmp #0,20$+2 ;was the correct immediate value generated? Beq 50$ ;Yes Call Err1.3 50$: .PSect Data CALLS2: .CALLS #1 60$: .=.-4. 70$: .=.+4. .PSect Active Cmp #8.,#60$-CALLS2 ;were two instructions generated? Beq 80$ ;yes Call Err2.1 80$: Cmp #MOV+2700+46,CALLS2 ;was the correct opcode generated? Beq 90$ ;Yes Call Err2.2 90$: Cmp #$CCALL,CALLS2+2 ;was the correct immediate value generated? Beq 100$ ;Yes Call Err2.3 100$: Cmp #CSM+27,70$ ;was the correct opcode generated? Beq 110$ ;Yes Call Err2.4 110$: Cmp #1,70$+2 ;was the correct immediate value generated? Beq 120$ ;Yes Call Err2.5 120$: Mov SP,R5 CALLS3: .CALLS #1,RETURN=<> .=.-4 ;crush CSM Cmp (SP)+,#$CCNIL ;correct return address? Beq 130$ ;yes Call Err3.1 130$: Cmp SP,R5 ;stack alignment correct? Beq 140$ ;yes Call Err3.2 Mov R5,SP 140$: Mov SP,R5 .CALLS #1,RETURN=c .=.-4 ;crush CSM Cmp (SP)+,#$CCC ;correct return address? Beq 150$ ;yes Call Err3.3 150$: Cmp SP,R5 ;stack alignment correct? Beq 160$ ;yes Call Err3.4 Mov R5,SP 160$: Mov SP,R5 .CALLS #1,RETURN=V .=.-4 ;crush CSM Cmp (SP)+,#$CCV ;correct return address? Beq 170$ ;yes Call Err3.5 170$: Cmp SP,R5 ;stack alignment correct? Beq 180$ ;yes Call Err3.6 Mov R5,SP 180$: Mov SP,R5 .CALLS #1,RETURN=Cv .=.-4 ;crush CSM Cmp (SP)+,#$CCVC ;correct return address? Beq 190$ ;yes Call Err3.7 190$: Cmp SP,R5 ;stack alignment correct? Beq 200$ ;yes Call Err3.8 Mov R5,SP 200$: Mov SP,R5 CALLS4: .CALLS #1,RETURN=Z .=.-4 ;crush CSM Cmp (SP)+,#$CCZ ;correct return address? Beq 210$ ;yes Call Err4.1 210$: Cmp SP,R5 ;stack alignment correct? Beq 220$ ;yes Call Err4.2 Mov R5,SP 220$: Mov SP,R5 .CALLS #1,RETURN=zC .=.-4 ;crush CSM Cmp (SP)+,#$CCZC ;correct return address? Beq 230$ ;yes Call Err4.3 230$: Cmp SP,R5 ;stack alignment correct? Beq 240$ ;yes Call Err4.4 Mov R5,SP 240$: Mov SP,R5 .CALLS #1,RETURN=VZ .=.-4 ;crush CSM Cmp (SP)+,#$CCZV ;correct return address? Beq 250$ ;yes Call Err4.5 250$: Cmp SP,R5 ;stack alignment correct? Beq 260$ ;yes Call Err4.6 Mov R5,SP 260$: Mov SP,R5 .CALLS #1,RETURN=cZV .=.-4 ;crush CSM Cmp (SP)+,#$CCZVC ;correct return address? Beq 270$ ;yes Call Err4.7 270$: Cmp SP,R5 ;stack alignment correct? Beq 280$ ;yes Call Err4.8 Mov R5,SP 280$: Mov SP,R5 CALLS5: .CALLS #1,RETURN=N .=.-4 ;crush CSM Cmp (SP)+,#$CCN ;correct return address? Beq 290$ ;yes Call Err5.1 290$: Cmp SP,R5 ;stack alignment correct? Beq 300$ ;yes Call Err5.2 Mov R5,SP 300$: Mov SP,R5 .CALLS #1,RETURN=Cn .=.-4 ;crush CSM Cmp (SP)+,#$CCNC ;correct return address? Beq 310$ ;yes Call Err5.3 310$: Cmp SP,R5 ;stack alignment correct? Beq 320$ ;yes Call Err5.4 Mov R5,SP 320$: Mov SP,R5 .CALLS #1,RETURN=NV .=.-4 ;crush CSM Cmp (SP)+,#$CCNV ;correct return address? Beq 330$ ;yes Call Err5.5 330$: Cmp SP,R5 ;stack alignment correct? Beq 340$ ;yes Call Err5.6 Mov R5,SP 340$: Mov SP,R5 .CALLS #1,RETURN=CvN .=.-4 ;crush CSM Cmp (SP)+,#$CCNVC ;correct return address? Beq 350$ ;yes Call Err5.7 350$: Cmp SP,R5 ;stack alignment correct? Beq 360$ ;yes Call Err5.8 Mov R5,SP 360$: Mov SP,R5 CALLS6: .CALLS #1,RETURN=ZN .=.-4 ;crush CSM Cmp (SP)+,#$CCNZ ;correct return address? Beq 370$ ;yes Call Err6.1 370$: Cmp SP,R5 ;stack alignment correct? Beq 380$ ;yes Call Err6.2 Mov R5,SP 380$: Mov SP,R5 .CALLS #1,RETURN=zNC .=.-4 ;crush CSM Cmp (SP)+,#$CCNZC ;correct return address? Beq 390$ ;yes Call Err6.3 390$: Cmp SP,R5 ;stack alignment correct? Beq 400$ ;yes Call Err6.4 Mov R5,SP 400$: Mov SP,R5 .CALLS #1,RETURN=NVZ .=.-4 ;crush CSM Cmp (SP)+,#$CCNZV ;correct return address? Beq 410$ ;yes Call Err6.5 410$: Cmp SP,R5 ;stack alignment correct? Beq 420$ ;yes Call Err6.6 Mov R5,SP 420$: Mov SP,R5 CALLS7: .CALLS #1,RETURN=nczv .=.-4 ;crush CSM Cmp (SP)+,#$CCALL ;correct return address? Beq 430$ ;yes Call Err7.1 430$: Cmp SP,R5 ;stack alignment correct? Beq 440$ ;yes Call Err7.2 440$: Mov R5,SP Mov SP,R5 .CALLS #1 .=.-4 ;crush CSM Cmp (SP)+,#$CCALL ;correct return address? Beq 450$ ;yes Call Err7.3 450$: Cmp SP,R5 ;stack alignment correct? Beq 460$ ;yes Call Err7.4 Mov R5,SP 460$: Call EndTst .nlist meb;**DEBUG** .Dsabl LSB Mov R5,SP .If NE MAC$ER ;Expect P errors .CALLS #1,test .EndC; NE MAC$ER ;-TEST .Page .SbTtl .CDFN Channel definition request .MACRO .CDFN AREA,ADDR,NUM,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,13.,0.,, ...CM2 ,4,E .ENDM ;+TEST .Enabl LSB .PSect Text $CDFN: .Asciz "%SYSMAC-I-Testing .CDFN" .PSect Active Mov #$CDFN,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s CDFN1: .CDFN #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.CDFN*^o400,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s CDFN2: .CDFN #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.CDFN*^o400,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 CDFN3: .CDFN ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.CDFN*^o400,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data CDFN4: .CDFN 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call AreaM1 ;set area to -1s CDFN5: .CDFN #Area,#123456,#121654 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 120$ ;yes Call Err5.1 ;no 120$: Cmp #.CDFN*^o400,(R1)+ ;is the subcode correct? Beq 130$ ;yes Call Err5.2 ;no 130$: Cmp #123456,(R1)+ ;is the address correct? Beq 140$ ;yes Call Err5.3 140$: Cmp #121654,(R1)+ ;is the address correct? Beq 150$ ;yes Call Err5.4 150$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .CHAIN Chain to another job request .MACRO .CHAIN MOV #^o4000,R0 EMT ^o374 .ENDM ;+TEST .Enabl LSB .PSect Text $CHAIN: .Asciz "%SYSMAC-I-Testing .CHAIN" .PSect Active Mov #$CHAIN,R0 ;Ident the test(s) Call BegTst Mov #Patter,R0 CHAIN1: .CHAIN .=.-2 ;squash EMT Cmp #.CHAIN*^o400,R0 ;Is R0 right? Beq 10$ Call Err1 10$: .PSect Data CHAIN2: .CHAIN .=.-2. 23$: .=.+2. 25$: .PSect Active Cmp #EMT+...R0,23$ ;was the correct EMT generated? Beq 20$ ;Yes Call Err2 20$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .CHCOPY Channel copy request .MACRO .CHCOP AREA,CHAN,OCHAN,JOBBLK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 ,11,,, .IF NB ...CM2 ,4,E .IFF ...CM2 #0,4,E .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $CHCOP: .Asciz "%SYSMAC-I-Testing .CHCOPY" .PSect Active Mov #$CHCOP,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 CHCO1: .CHCOPY #Area,#123,#123456,#23456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.CHCOP,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is OCHAN set? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #23456,(R1)+ ;is JOBBLK set? Beq 50$ ;yes Call Err1.5 ;no 50$: Call AreaM1 Mov #Area,R0 CHCO2: .CHCOPY ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 60$ ;yes Call Err2.1 ;no 60$: CmpB #123,(R1)+ ;is channel set? Beq 70$ ;yes Call Err2.2 ;no 70$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 80$ ;yes Call Err2.3 ;no 80$: Cmp #123456,(R1)+ ;is Addr set? Beq 90$ ;yes Call Err2.4 ;no 90$: Cmp #0,(R1)+ ;is JOBBLK set to 0? Beq 100$ ;yes Call Err2.4 ;no 100$: Call AreaM1 Mov #Area,R0 CHCO3: .CHCOPY ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 110$ ;yes Call Err3.1 ;no 110$: CmpB #123,(R1)+ ;is channel set? Beq 120$ ;yes Call Err3.2 ;no 120$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 130$ ;yes Call Err3.3 ;no 130$: Cmp #123456,(R1)+ ;is Addr set? Beq 140$ ;yes Call Err3.4 ;no 140$: .PSect Data CHCO4: .CHCOPY CODE=NOSET 150$: .PSect Active Cmp #EMT+...AR0,150$-2 ;correct EMT? Beq 160$ ;yes Call Err4 ;no 160$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .CKXX Meta-Macro to generate CK.__ macro definitions .SbTtl . which are used to verify auto-(inc/dec) .SbTtl . assumptions .MACRO .CKXX REG,LIST .MCALL .ASSUME .IRP X, .IF IDN , .MACRO CK.'X LABEL,CHANGE,RESULT .IF NB .IF LT CHANGE .LIST CK.'X=CK.'X''CHANGE .NLIST .ENDC .IFTF .IIF NB , ...v2 = 1 .Dsabl LCM .EndC ...v3 = 0 .IIf idn , ...V23 = Class .IIf idn , ...V3 = 1 .IIf idn , ...V23 = 0 .IIf idn , ...V3 = 1 .IIf eq ...v3 .ERROR;?SYSMAC-E-S W I T C H value unknown, use ON or OFF; .IIf ne ...v2 .enabl lcm .Macro .DPSec .PSect PSect .EndM .DPSec .If nb .Save .PSect Code .If nb Deb$8: Jsr R3,L1 ;save R3, point to oct table .Word ^o100000,^o10000,^o1000,^o100,^o10,^o1,0 ;This assumes that the high byte of JSR is 0 Deb$10=:. Jsr R3,L1 ;save R3, point to dec table .Word 10000.,1000.,100.,10.,1.,0,'.*^o400 .IfF Deb$8: Mov R3,-(SP) ;save R3 .If nb .Addr #Deb.8,R3 ;point to octal table .IfF Mov #Deb.8,R3 ;point to octal table .EndC Br L1 ;join common c o d e Deb$10: Mov R3,-(SP) ;save R3 .If nb .Addr #Deb.10,R3 ;point to decimal table .IfF Mov #Deb.10,R3 ;point to decimal table .EndC .PSect PSect Deb.8: .Word ^o100000,^o10000,^o1000,^o100,^o10,^o1,0,0 Deb.10: .Word 10000.,1000.,100.,10.,1.,0,'.*^o400 .PSect Code .EndC L1: Mov R2,-(SP) ;save work regs Mov R1,-(SP) ; ... Sub #8.,SP ;reserve 8 bytes on stack Mov SP,R1 ;point to char buffer on stack L2: Clr R2 ;accumulate here Tst @R3 ;done? - end of table Beq L4 ;yep end of digits L3: Inc R2 ;count Sub @R3,R0 ;reduce Bhis L3 ;unsigned output Add (R3)+,R0 ;correct overage Add #'0-1,R2 ;make ASCII MovB R2,(R1)+ ;stuff char away Br L2 ;and back for loop L4: MovB 3(R3),(R1)+ ;decimal point or nothing ClrB (R1)+ ;end string with zero Mov SP,R0 ;point to string Emt ^o351 ;print it Add #8.,SP ;restore stack Mov (SP)+,R1 ;restore regs Mov (SP)+,R2 Mov (SP)+,R3 Return .Restore .EndC .EndM .Debug ;+TEST .Enabl LSB .PSect Text $DEBUG: .Asciz "%SYSMAC-I-Testing .DEBUG" .PSect Active Mov #$DEBUG,R0 ;Ident the test Call BegTst Call SkpTst .If NE MAC$ER ;Expect P error .DEBUG SWITCH=YES .EndC .Dsabl LSB ;-TEST .Page .SbTtl .DELETE File deletion request .MACRO .DELET AREA,CHAN,DBLK,SEQNUM,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF NE ...V1-1 ...CM5 .IF IDN ,#0 CLR @R0 .IFF .IIF IDN <0> .ERROR;?SYSMAC-W-Invalid argument, use #0, not 0; ...V2=0 .IF B .IIF B ,...V2=1 .IFF .IIF DIF ,SET,...V2=1 .ENDC .IF NE ...V2 .IF NB MOVB CHAN,@R0 .ENDC .IFF .IF B CLRB 1(R0) .IFF .NTYPE ...V2,CHAN .IF EQ ...V2-^o27 MOV CHAN,@R0 .IFF CLR @R0 MOVB CHAN,@R0 .ENDC .ENDC .ENDC .ENDC ...CM2 ,2 ...CM2 ,4,E,C .MEXIT .ENDC ...CM5 , .ENDM ;+TEST ;NOTE: V1 version is not tested .Enabl LSB .PSect Text $DELET: .Asciz "%SYSMAC-I-Testing .DELETE" .PSect Active Mov #$DELET,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Area,R0 ;load R0 DELE2: .DELETE CODE=SET .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 10$ ;yes Call Err2.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err2.2 ;no 20$: CmpB #.DELET,(R1)+ ;is IC set? Beq 30$ ;yes Call Err2.3 ;no 30$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 40$ ;yes Call Err2.4 ;no 40$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 50$ ;yes Call Err2.5 ;no 50$: Call AreaM1 Mov #Area,R0 ;load R0 DELE3: .DELETE CODE=NOSET .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 60$ ;yes Call Err3.1 ;no 60$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 70$ ;yes Call Err3.2 ;no 70$: CmpB #-1.,(R1)+ ;is IC unchanged? Beq 80$ ;yes Call Err3.3 ;no 80$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 90$ ;yes Call Err3.4 ;no 90$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 100$ ;yes Call Err3.5 ;no 100$: Call AreaM1 Mov #Area,R0 ;load R0 DELE4: .DELETE ,#277 .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 110$ ;yes Call Err4.1 ;no 110$: CmpB #277,(R1)+ ;is CHAN set? Beq 120$ ;yes Call Err4.2 ;no 120$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 130$ ;yes Call Err4.3 ;no 130$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 140$ ;yes Call Err4.4 ;no 140$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 150$ ;yes Call Err4.5 ;no 150$: Call AreaM1 Mov #Area,R0 ;load R0 DELE5: .DELETE ,#277,CODE=SET .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 160$ ;yes Call Err5.1 ;no 160$: CmpB #277,(R1)+ ;is CHAN set? Beq 170$ ;yes Call Err5.2 ;no 170$: CmpB #.DELET,(R1)+ ;is IC set? Beq 180$ ;yes Call Err5.3 ;no 180$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 190$ ;yes Call Err5.4 ;no 190$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 200$ ;yes Call Err5.5 ;no 200$: Call AreaM1 Mov #Area,R0 ;load R0 DELE6: .DELETE ,#277,CODE=NOSET .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 210$ ;yes Call Err6.1 ;no 210$: CmpB #277,(R1)+ ;is CHAN set? Beq 220$ ;yes Call Err6.2 ;no 220$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 230$ ;yes Call Err6.3 ;no 230$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 240$ ;yes Call Err6.4 ;no 240$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 250$ ;yes Call Err6.5 ;no 250$: Call AreaM1 DELE7: .DELETE #Area .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 260$ ;yes Call Err7.1 ;no 260$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 270$ ;yes Call Err7.2 ;no 270$: CmpB #.DELET,(R1)+ ;is IC set? Beq 280$ ;yes Call Err7.3 ;no 280$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 290$ ;yes Call Err7.4 ;no 290$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 300$ ;yes Call Err7.5 ;no 300$: Call AreaM1 DELE8: .DELETE #Area,#0,CODE=SET .=.-2 ;smash EMT Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 310$ ;yes Call Err8.1 ;no 310$: CmpB #0,(R1)+ ;is CHAN set? Beq 320$ ;yes Call Err8.2 ;no 320$: CmpB #.DELET,(R1)+ ;is IC set? Beq 330$ ;yes Call Err8.3 ;no 330$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 340$ ;yes Call Err8.4 ;no 340$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 350$ ;yes Call Err8.4 ;no 350$: .PSect Data .DELETE 360$: .PSect Active Cmp #EMT+...AR0,360$-2 ;is the EMT generated correctly? Beq 370$ ;yes Call Err8.5 ;no 370$: Call AreaM1 DELE9: .DELETE #Area,,#123456,CODE=NOSET .=.-2 ;smash EMT Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 380$ ;yes Call Err9.1 ;no 380$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 390$ ;yes Call Err9.2 ;no 390$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 400$ ;yes Call Err9.3 ;no 400$: Cmp #123456,(R1)+ ;is DBLK set? Beq 410$ ;yes Call Err9.4 ;no 410$: Cmp #-1,(R1)+ ;is SEQNUM set? Beq 420$ ;yes Call Err9.5 ;no 420$: Call AreaM1 Mov #277,R3 DELEA: .DELETE #Area,R3 .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 430$ ;yes Call ErrA.1 ;no 430$: CmpB #277,(R1)+ ;is CHAN set? Beq 440$ ;yes Call ErrA.2 ;no 440$: CmpB #.DELET,(R1)+ ;is IC set? Beq 450$ ;yes Call ErrA.3 ;no 450$: Cmp #-1,(R1)+ ;is ARG unchanged? Beq 460$ ;yes Call ErrA.4 ;no 460$: Cmp #-1,(R1)+ ;is SEQNUM set? Beq 470$ ;yes Call ErrA.5 ;no 470$: Call AreaM1 DELEC: .DELETE #Area,#0,CODE=NOSET .=.-2 Mov #Area,R1 Cmp R1,R0 ;Is R0 correct? Beq 480$ ;yes Call ErrC.1 ;no 480$: CmpB #0,(R1)+ ;is CHAN set? Beq 490$ ;yes Call ErrC.2 ;no 490$: CmpB #.DELET,(R1)+ ;is IC set? Beq 500$ ;yes Call ErrC.3 ;no 500$: Cmp #-1,(R1)+ ;is DBLK unchanged? Beq 510$ ;yes Call ErrC.4 ;no 510$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 520$ ;yes Call ErrC.5 ;no 520$: Call AreaM1 Mov #Patter,R0 DELED: .DELETE #Area,#123,#123456,#0 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 530$ ;yes Call ErrD.1 ;no 530$: CmpB #123,(R1)+ ;is channel set? Beq 540$ ;yes Call ErrD.2 ;no 540$: CmpB #.DELET,(R1)+ ;is subcode set? Beq 550$ ;yes Call ErrD.3 ;no 550$: Cmp #123456,(R1)+ ;is DBLK set? Beq 560$ ;yes Call ErrD.4 ;no 560$: Cmp #0,(R1)+ ;is SEQNUM set? Beq 570$ ;yes Call ErrD.5 ;no 570$: Call EndTst .If NE MAC$ER ;Expect P error .DELETE ,0 .EndC .Dsabl LSB ;-TEST .Page .SbTtl .DEVICE Exit/Abort modification list specifying request .MACRO .DEVIC AREA,ADDR,LINK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF B LINK ...CM6 ,12.,0.,,,E .IFF ...CM6 ,12.,1.,,,E .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $DEVIC: .Asciz "%SYSMAC-I-Testing .DEVICE" .PSect Active Mov #$DEVIC,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s DEVI1: .DEVICE #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.DEVIC*^o400+..DNLK,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s DEVI2: .DEVICE #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.DEVIC*^o400+..DNLK,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 DEVI3: .DEVICE ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.DEVIC*^o400+..DNLK,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data DEVI4: .DEVICE 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call AreaM1 ;set area to -1s DEVI5: .DEVICE #Area,#123456,LINK=YES .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 120$ ;yes Call Err5.1 ;no 120$: Cmp #.DEVIC*^o400+..DLNK,(R1)+ ;is the subcode correct? Beq 130$ ;yes Call Err5.2 ;no 130$: Cmp #123456,(R1)+ ;is the address correct? Beq 140$ ;yes Call Err5.3 140$: Call AreaM1 ;set area to -1s DEVI6: .DEVICE #Area,LINK=YES .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 150$ ;yes Call Err6.1 ;no 150$: Cmp #.DEVIC*^o400+..DLNK,(R1)+ ;is the subcode correct? Beq 160$ ;yes Call Err6.2 ;no 160$: Cmp #177777,(R1)+ ;is the address correct? Beq 170$ ;yes Call Err6.3 170$: Call AreaM1 ;set area to -1s Mov #Area,R0 DEVI7: .DEVICE ,#123456,CODE=SET,LINK=YES .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 180$ ;yes Call Err7.1 ;no 180$: Cmp #.DEVIC*^o400+..DLNK,(R1)+ ;is the subcode correct? Beq 190$ ;yes Call Err7.2 ;no 190$: Cmp #123456,(R1)+ ;is the address correct? Beq 200$ ;yes Call Err7.3 200$: Call EndTst .Dsabl LSB ;-TEST .page ;+ ; ; .DPRINT ; ; This macro is designed to conditionally generate code to ; print a string. Its purpose is to make debug prints easy ; to install in modules and easy to suppress. It may be used ; display decimal or octal values from word sources. It may ; also be partitioned into up to 16 classes so that debug ; prints can be easily subset. ; ; String string to print, enclosed in <> ; .Asci is generated with "" as delimiters ; ; Value (omit) value to print if non-blank. ; Use R0 to print value in R0. ; Avoid stack references. ; ; Type (OCT) display value in octal format ; DEC display value in decimal format ; ; Class (177777) generate code if any class enabled ; xxxxxx generate code if ...V23 .and. Class non-zero ; ; L1 (xxxxx$) local symbol. If .ENABLE LSB is not ; in effect, supply symbol ;- .page .Macro .DPrint String,Value,Type=OCT,Class=-1,?L1 .If ndf ...V23 .Error;?SYSMAC-E-.DEBUG must be used before .DPRINT; .MExit .EndC .If ne ...V23& .If ne ...V24 .Addr #L1,R0,PUSH .IfF Mov R0,-(SP) Mov #L1,R0 .EndC Emt ^o351 .If nb .If idn , Mov @SP,R0 .IfF Mov Value,R0 .EndC .If idn , Call Deb$8 .IfF .If idn , Call Deb$10 .IfF Call Deb$8 .Error;?SYSMAC-E-Invalid T Y P E, expecting OCT/DEC, found - TYPE; .EndC .EndC .IfTF Mov (SP)+,R0 .Save .DPSec .IfF L1: .Asciz "String" .IfT L1: .Ascii "String"<^o200> .EndC .Restore .EndC .EndM .DPrint ;TEST+ .Enabl LSB .PSect Text $DPRIN: .Asciz "%SYSMAC-I-Testing .DPRINT" .PSect Active Mov #$DPRIN,R0 ;Ident the test Call BegTst Call SkpTst .Dsabl LSB ;TEST- .Page .SbTtl .DRAST Define interrupt entry point **Handler only** .MACRO .DRAST NAME,PRI,ABT .GLOBL $INPTR .IF B RETURN .IFF BR ABT .ENDC NAME'INT::JSR R5,@$INPTR .WORD ^C&^o340 .ENDM ;+TEST .Enabl LSB .PSect Text $DRAST: .Asciz "%SYSMAC-I-Testing .DRAST" .PSect Active Mov #$DRAST,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRBEG Define QMANGR entry point **Handler only** ; ;NOTE: the DSIZE contained in the body of his macro is a subtle hack: ; There is an argument to the macro with the name DSIZ, and it is ; desired to generate a reference to the symbol xxDSIZ if the argument ; DSIZ is blank. If DSIZ is used, it matches the DSIZ agument and becomes ; blank... ; .MACRO .DRBEG NAME,VEC,DSIZ,DSTS,VTBL,ADDRCK,SPFUN,CODE,?L1,LDTBL,NSPFUN .IIF NDF ...V9 ...V9=0 .IIF NDF ...V19 ...V19=0 .IIF NDF ...V22 ...V22=0 .ASECT .=^o52 .GLOBL NAME'END,NAME'INT .WORD .IF B .WORD NAME'DSIZE .IFF .WORD DSIZ .ENDC .IF B .WORD NAME'STS .IFF .WORD DSTS .ENDC .WORD ^o++> .PSECT NAME'DVR NAME'STRT:: .IF NB VTBL .GLOBL VTBL .WORD /2.-1+^o100000 .IFF .IF NB .IIF NE VEC&3.,.ERROR VEC;?SYSMAC-E-Odd or invalid vector specified; .WORD VEC&^C3. .IFF .IF DF NAME'$VTB .GLOBL NAME'$VTB .WORD /2.-1+^o100000 .IFF .IIF NE NAME'$VEC&3.,.ERROR NAME'$VEC;?SYSMAC-E-Odd or invalid vector specified; .WORD NAME'$VEC&^C3. .ENDC .ENDC .ENDC .WORD NAME'INT-.,^o340 NAME'SYS:: NAME'LQE:: .WORD 0 .IRP X,\...V19 NAME'CQE:: .WORD x .ENDR ...V2=0 .IIF NB ...V2=^o20 .IIF NE ...V22 ...V2=^o20 .IRP X,\<^o240!...V2!...V9> .WORD x .ENDR .IF NE ...V2 .IF B BR L1 .IFF BR CODE .ENDC ...V2=0 .IIF NB ...V2=1 .IIF NB ...V2=...V2!^o2 .IIF NB ...V2=...V2!^o4 .IIF NB ...V2=...V2!^o10 .IRP X,\<...V22!...V2> .WORD X .ENDR .IF NE ...V2&^o17 .WORD ADDRCK .ENDC .IF NE ...V2&^o16 .WORD SPFUN .ENDC .IF NE ...V2&^o14 .WORD LDTBL .ENDC .IF NE ...V2&^o10 .WORD NSPFUN .ENDC .IF B L1: .ENDC .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $DRBEG: .Asciz "%SYSMAC-I-Testing .DRBEG" .PSect Active Mov #$DRBEG,R0 ;Ident the test Call BegTst Call SkpTst .If NE MAC$ER XXVEC=^o3 ;Expect P error .DRBEG XX ;Expect P error .DRBEG YY,^o3 .EndC ;-TEST .Page .SbTtl .DRBOT Define beginning of Boot Code **Handler only** ;++ ; .DRBOT ; ; CONTROL= is used to generate the controller description bits ; in the boot block. The default value is correct for nearly ; all RT supported devices. As many options may be specified as ; are supported by the boot code: ; ; Unibus device ; Q-Bus device ; PC-Bus device ; Unibus MSCP device ; Q-Bus MSCP device ; PC-Bus MSCP device ; ; SIDES= is used to indicate the number of sides supported in ; floppy disk drive. Valid values are 1 and 2. Hard media ; sidedness is not coded. ; ; OFFSET= is used to indicate if the bootstrap will accept ; block offset and length information for a softboot from ; a file (or a softboot from some other o/s). The values ; are: ; ; OFFSET=NO ; default, offset not supported ; OFFSET=YES ; offset is supported ; ; OFFSET=NO places 4 words of -1 as the last 4 words of the ; bootblock, OFFSET=YES places 4 words of 0. ; ; FORCE is used to force the generation of the vector table. ; Assigning a value to FORCE causes the associated sysgen bit ; value to be "forced" on for purposes of generating the table. ; ; FORCE=1 will force generation of the error logging vector ; for instance. ; ; PSECT is used to force the DREND macro to be in a different ; PSECT from the expected dd'DVR one. This is used for cases ; when the memory resident part of a handler is built from ; several psects. ; ; NOTE: the definition of a code does NOT imply any present ; or future product committment. ;-- .MACRO .DRBOT NAME,ENTRY,READ,CONTROL=,SIDES=1,OFFSET=NO,FORCE=0,PSECT ...V7=-1 .IIF IDN OFFSET,YES,...V7=0 .DREND NAME,FORCE,PSECT .IIF NDF TPS,TPS=:^o177564 .IIF NDF TPB,TPB=:^o177566 LF=:^o12 CR=:^o15 B$BOOT=:^o1000 B$DEVN=:^o4716 B$DEVU=:^o4722 B$READ=:^o4730 .IF NDF B$DNAM .IF EQ MMG$T B$DNAM=:^R'NAME .IFF B$DNAM=:^R'NAME'X .ENDC ; EQ MMG$T .ENDC ; NDF B$DNAM .ASECT .=^o62 .WORD NAME'BOOT,NAME'BEND-NAME'BOOT,READ-NAME'BOOT .PSECT NAME'BOOT NAME'BOOT::NOP BR ENTRY-2. ...V2=^o100 .IRP X ...V3=0 .IIF IDN ...V3=1. .IIF IDN ...V3=2. .IIF IDN ...V3=4. .IIF IDN ...V3=^o10 .IIF IDN ...V3=^o20 .IIF IDN ...V3=^o40 .IIF EQ ...V3 .ERROR;?SYSMAC-E-Invalid C O N T R O L, found - CONTROL; ...V2=...V2!...V3 .ENDR .=ENTRY-6. .BYTE ^o20,...V2,^o20,^o^C<20+...V2+20> .IF EQ BR ENTRY .IFF .IF EQ BMI ENTRY .IFF .ERROR;?SYSMAC-E-Invalid S I D E S, expecting 1/2, found - SIDES; .ENDC .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $DRBOT: .Asciz "%SYSMAC-I-Testing .DRBOT" .PSect Active Mov #$DRBOT,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRDEF Define lots of handler info, .MCALL others **Handler only** ;+ ; CSR=*NO* means don't place any value in 176 ;- .MACRO .DRDEF NAME,CODE,STAT,SIZE,CSR,VEC,UNIT64=NO,DMA,PERMUMR,SERIAL=NO .MCALL .DRAST,.DRBEG,.DRBOT,.DREND,.DREST,.DRFIN,.DRFMS,.DRFMT .MCALL .DRINS,.DRPTR,.DRSET,.DRSPF,.DRTAB,.DRUSE,.DRVTB .MCALL .FORK,.QELDF .IIF NDF RTE$M RTE$M=0 .IIF NE RTE$M RTE$M=1 .IIF NDF TIM$IT TIM$IT=0 .IIF NE TIM$IT TIM$IT=1 .IIF NDF MMG$T MMG$T=0 .IIF NE MMG$T MMG$T=1 .IIF NDF ERL$G ERL$G=0 .IIF NE ERL$G ERL$G=1 .IIF NE TIM$IT, .MCALL .TIMIO,.CTIMI .QELDF HDERR$=:1 EOF$=:^o20000 VARSZ$=:^o400 ABTIO$=:^o1000 SPFUN$=:^o2000 HNDLR$=:^o4000 SPECL$=:^o10000 WONLY$=:^o20000 RONLY$=:^o40000 FILST$=:^o100000 NAME'DSIZ=:SIZE NAME'$COD=:CODE NAME'STS=:! .IIF NDF NAME'$VEC,NAME'$VEC=VEC .GLOBL NAME'$VEC .ASECT ...V2=0 ...V19=0 ...V20=0 ...V21=0 ...V22=0 .IIF NDF NAME'$NAM,NAME'$NAM=^r'NAME .IF DF NAME'$N64 .IF NE NAME'$N64 .IF IDN ...V22= 40000 .=^o76 .WORD NAME'$X64 .IF NDF NAME'$PN2 NAME'$PN2=NAME'$NAM .IF LT NAME'$PN2 NAME'$PN2=NAME'$PN2-^rT .IFTF NAME'$PN2=NAME'$PN2/^rA*^rA .IFT NAME'$PN2=NAME'$PN2+^rT .ENDC .ENDC ...V2=NAME'$PN2 .IF LT ...V2 ...V2=...V2-^rT .IFTF ...V2=...V2/^rA*^rA .IFT ...V2=...V2+^rT .ENDC .IIF NE ...V2-NAME'$PN2 .ERROR ;?SYSMAC-E-NAME'$PN2 is not a single character device; .IFF .IF DIF .ERROR ;?SYSMAC-E-Invalid U N I T 6 4, expecting YES/NO, found - UNIT64; .IFF .ERROR ;?SYSMAC-E-U N I T 6 4 = N O and NAME'$N64 = 1 .ENDC .ENDC .ENDC .ENDC .IF NB .IF IDN ...V2=...V2!^o60 ...V19=...V19!^o10000 ...V22=...V22!^o10000 .ENDC .IIF IDN ...V2=...V2!^o40 .IIF EQ ...V2 .ERROR ;?SYSMAC-E-Invalid D M A, expecting YES/NO, found - DMA; .ENDC .IF NB .IIF GT -7. .ERROR PERMUMR;?SYSMAC-E-P E R M U M R value > 7; ...V2=...V2!^o60! ...V19=...V19!^o10000 ...V22=...V22!^o10000 .ENDC .IIF IDN ...V22=...V22!^o4000 .IRP x,\...V2 .=^o100 .WORD x .ENDR .=^o176 .IF DIF ,<*NO*> .IIF NDF NAME'$CSR,NAME'$CSR=CSR .GLOBL NAME'$CSR .WORD NAME'$CSR .ENDC .ENDM ;+TEST DRDE1: .DRDEF AA,377,FILST$!VARSZ$,0,172150,154 AA$X64: .IIF NE ...V22 .ERROR ...V22 ; . . . V 2 2 not zero .IIF NE ...V2 .ERROR ...V2 ; . . . V 2 unexpected value .IF NE MAC$ER AB$N64= 1 ;Expect P error DRDE2: .DRDEF AB,377,FILST$!VARSZ$,0,172150,154 AB$X64: .IIF NE ...V22 .ERROR ...V22 ; . . . V 2 2 not zero .IIF NE ...V2 .ERROR ...V2 ; . . . V 2 unexpected value .ENDC DRDE3: .DRDEF AC,377,FILST$!VARSZ$,0,172150,154,UNIT64=XXX AC$X64: .IIF NE ...V22 .ERROR ...V22 ; . . . V 2 2 not zero .IIF NE ...V2 .ERROR ...V2 ; . . . V 2 unexpected value .IF NE MAC$ER AD$N64= 1 ;Expect P error DRDE4: .DRDEF AD,377,FILST$!VARSZ$,0,172150,154,UNIT64=XXX AD$X64: .IIF NE ...V22 .ERROR ...V22 ; . . . V 2 2 not zero .IIF NE ...V2 .ERROR ...V2 ; . . . V 2 unexpected value .ENDC DRDE5: .DRDEF AE,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES AE$X64: .IIF NE ...V22 .ERROR ...V22 ; . . . V 2 2 not zero .IIF NE ...V2 .ERROR ...V2 ; . . . V 2 unexpected value AF$N64= 1 DRDE6: .DRDEF AF,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES AF$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rA > .ERROR ...V2 ; . . . V 2 unexpected value BA$N64= 1 BA$NAM= ^RZ9 DRDE7: .DRDEF BA,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BA$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rZ > .ERROR ...V2 ; . . . V 2 unexpected value BB$N64= 1 BB$NAM= ^RZA DRDE8: .DRDEF BB,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BB$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rZ > .ERROR ...V2 ; . . . V 2 unexpected value BC$N64= 1 BC$NAM= ^RZ DRDE9: .DRDEF BC,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BC$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rZ > .ERROR ...V2 ; . . . V 2 unexpected value BD$N64= 1 BD$NAM= ^R DRDEA: .DRDEF BD,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BD$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^r > .ERROR ...V2 ; . . . V 2 unexpected value BE$N64= 1 BE$NAM= ^RA DRDEB: .DRDEF BE,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BE$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rA > .ERROR ...V2 ; . . . V 2 unexpected value BF$N64= 1 BF$NAM= ^RTS DRDEC: .DRDEF BF,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BF$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rT > .ERROR ...V2 ; . . . V 2 unexpected value BG$N64= 1 BG$NAM= ^RTT DRDED: .DRDEF BG,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BG$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rT > .ERROR ...V2 ; . . . V 2 unexpected value BH$N64= 1 BH$NAM= ^RU DRDEE: .DRDEF BH,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES BH$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rU > .ERROR ...V2 ; . . . V 2 unexpected value CA$N64= 1 CA$PN2= ^RP DRDEF: .DRDEF CA,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES CA$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rP > .ERROR ...V2 ; . . . V 2 unexpected value .IF NE MAC$ER CB$N64= 1 CB$PN2= ^RPA ;Expect P error DRDEG: .DRDEF CB,377,FILST$!VARSZ$,0,172150,154,UNIT64=YES CB$X64: .IIF NE ...V22-<^o040000> .ERROR ...V22 ; . . . V 2 2 not 040000 .IIF NE ...V2-<^rP > .ERROR ...V2 ; . . . V 2 unexpected value .ENDC .Enabl LSB .PSect Text $DRDEF: .Asciz "%SYSMAC-I-Testing .DRDEF" .PSect Active Mov #$DRDEF,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DREND Define end of mem-res code & boot code **Handler only** ;++ ; .DREND ; ; FORCE is used to force the generation of the vector table. ; Assigning a value to FORCE causes the associated sysgen bit ; value to be "forced" on for purposes of generating the table. ; ; FORCE=1 will force generation of the error logging vector ; for instance. ; ; PSECT is used to force the DREND macro to be in a different ; PSECT from the expected dd'DVR one. This is used for cases ; when the memory resident part of a handler is built from ; several psects. ; ; The setting of OFFSET= in .DRBOT controls the generation of ; the last 4 words of the boot block image. If .DRBOT has not ; been invoked or OFFSET=NO has been chosen (perhaps by default) ; the last 4 words will contain -1s. If OFFSET=YES has been ; chosen, the last 4 words will contain 0s. ;-- .MACRO .DREND NAME,FORCE=0,PSECT,?L1,?L2 .IF B .PSECT NAME'DVR .IFF .PSECT PSECT .ENDC .IIF NDF NAME'$END,NAME'$END:: .IF EQ .-NAME'$END .IF NE MMG$T! $RLPTR::.WORD 0 $MPPTR::.WORD 0 $GTBYT::.WORD 0 $PTBYT::.WORD 0 $PTWRD::.WORD 0 .ENDC .IF NE ERL$G! $ELPTR::.WORD 0 .ENDC .IF NE TIM$IT! $TIMIT::.WORD 0 .ENDC $INPTR::.WORD 0 $FKPTR::.WORD 0 .IIF NDF ...V22 ...V22=0 .IF NE ...V22&^o40000 NAME'$X64 =:. .REPT 16. .WORD 0 .ENDR .ENDC .GLOBL NAME'STRT NAME'END==. .IFF .PSECT NAME'BOOT .IIF LT ,.ERROR;?SYSMAC-E-Primary boot too large; .=NAME'BOOT+^o664 BIOERR: JSR R1,REPORT .WORD IOERR-NAME'BOOT REPORT: MOV #BOOTF-NAME'BOOT,R0 MOV #L2-NAME'BOOT,R2 CALL @R2 MOV @R1,R0 CALL @R2 MOV #CRLFLF-NAME'BOOT,R0 CALL @R2 L1: HALT BR L1 L2: TSTB @#TPS BPL L2 MOVB (R0)+,@#TPB BNE L2 RETURN BOOTF: .ASCIZ "?BOOT-U-" IOERR: .ASCII "I/O error" CRLFLF: .ASCIZ .EVEN .IIF NDF ...V7,...V7=-1 .REPT 4. .WORD ...V7 .ENDR NAME'BEND:: .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $DREND: .Asciz "%SYSMAC-I-Testing .DREND" .PSect Active Mov #$DREND,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DREST Define handler extended status **Handler only** ;++ ; Replace table format ; ; .BYTE some if 0 all blocks replacable (like RL01/2) ; if 1 some blocks replacable (like RK06/7) ; other bits reserved and 0 ; .BYTE sluff bad sector file at last_block+sluff ; .BYTE numsec bad sector file numsec sectors long ; .BYTE tpc tracks per cylinder ; .BYTE spt sectors per track ; .BYTE hack 2**hack sectors per block ; ; The replacement table must be contained within block 0 of ; the handler. ; ; MOD2 places values in the high byte of xxCQE, ; ; DVM.NF*^o400 100000 is placed there if FETCH=*NO* found ; DV2.V2 040000 is placed there if MOD2=DV2.V2 is ; specified and means (to RESORC only) ; that there is an additional vector ; table to display that follows the ; standard vector table. ;-- .MACRO .DREST CLASS=0,MOD=0,DATA=0,TYPE,SIZE=0,REPLACE=0,MOD2=0,STAT2=0 DVC.UK =:0 DVC.NL =:1 DVC.TT =:^o2 DVC.TP =:^o3 DVC.DK =:^o4 DVC.MT =:^o5 DVC.CT =:^o6 DVC.LP =:^o7 DVC.DE =:^o10 DVC.DP =:^o11 DVC.DL =:^o12 DVC.NI =:^o13 DVC.PS =:^o14 DVC.VT =:^o15 DVC.SI =:^o16 DVC.SO =:^o17 DVC.SB =:^o20 DVM.NS =:1 DVM.DX =:1 DVM.DM =:^o2 DVM.NF =:^o200 DV2.V2 =:^o40000 HS2.BI =:1 HS2.KI =:^o2 HS2.KL =:^o4 HS2.KU =:^o10 HS2.MO =:^o20 .IIF NDF ...V18,...V18=0 .IIF NDF ...V19,...V19=0 ...V18=...V18! ...V19=...V19! .ASECT .=0 .RAD50 "HAN" .=^o20 .BYTE CLASS .IRP X,\...V18 .BYTE X .ENDR .=^o32 .WORD REPLACE .=^o36 .WORD STAT2 .=^o70 ...V2=. .RAD50 "TYPE" .=...V2+2. .WORD DATA .WORD SIZE .IF B .IIF DIF ,<0> .ERROR ;?SYSMAC-W-D A T A table specified, but no T Y P E; .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $DREST: .Asciz "%SYSMAC-I-Testing .DREST" .PSect Active Mov #$DREST,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRFIN Define return to COMPLT exit **Handler only** .MACRO .DRFIN NAME .GLOBL NAME'CQE MOV PC,R4 ADD #NAME'CQE-.,R4 MOV @#^o54,R5 JMP @^o270(R5) .ENDM ;+TEST .Enabl LSB .PSect Text $DRFIN: .Asciz "%SYSMAC-I-Testing .DRFIN" .PSect Active Mov #$DRFIN,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRFMS Define FORMAT switch table **Handler only** .MACRO .DRFMS SWITCH .MCALL ...CM9 .IF NE ...V26-1 ...V26=3. .IRPC X,QWERTYUIOPASDFGHJKLZXCVBNM .IIF DF ...V1'X ...V1'X=0 .ENDR .ENDC .IF EQ ...V25 ...V25=1 .IRPC X,OOOOOOOOPPPPPPPPVWY ...CM9 0,X .ENDR .ENDC .IRP X, ...CM9 1,X .ENDR .ENDM ;+TEST .Enabl LSB .PSect Text $DRFMS: .Asciz "%SYSMAC-I-Testing .DRFMS" .PSect Active Mov #$DRFMS,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl ...CM9 Support macro for .DRFMS **Handler only** .MACRO ...CM9 Z,L,V .IF NDF SWI.'L SWI.'L: ...V1'L=0 .ENDC ...V2=0 .IRPC X,OPVWY .IIF IDN , ...V2=1 .ENDR .IF EQ ...V2*Z .WORD ''L,0,0,0 .ENDC ...V2=. .=...V1'L*8.+6.+SWI.'L .WORD V .=...V2 ...V1'L=...V1'L+1 .ENDM ;+TEST .Enabl LSB .PSect Text $..CM9: .Asciz "%SYSMAC-I-Testing ...CM9" .PSect Active Mov #$..CM9,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRFMT Define FORMAT Argument block **Handler only** .MACRO .DRFMT SETUP,SWITCH,SCCA,FMTCODE,DEVCK,VFYBEGIN,VFYREAD,VFYWRITE,VFYEND,FMTBEGIN,SIZE,?L1=$FMT$ ...V25=0 .IIF NDF ...V26 ...V26=0 ...V26=...V26+1 .SAVE .ASECT .=^o12 .WORD L1 .RESTORE L1:: .BYTE 0,0 .WORD SETUP .WORD SWITCH .WORD SCCA .WORD FMTCODE .WORD DEVCK .WORD VFYBEGIN .WORD VFYREAD .WORD VFYWRITE .WORD VFYEND .WORD FMTBEGIN .WORD SIZE .ENDM ;+TEST .Enabl LSB .PSect Text $DRFMT: .Asciz "%SYSMAC-I-Testing .DRFMT" .PSect Active Mov #$DRFMT,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRINS Define installation code area **Handler only** ;++ ; .DRINS ; ; If the NAME parameter is specified with a "-" prefix, ; the installation CSR is 0 and the first display CSR is ; the value of NAME'$CSR ;-- .MACRO .DRINS NAME,CSRS .ASECT .=^o172 .WORD 0 ...V2=0 .IRPC X, .IIF IDN <->, ...V2=1 .ENDR .IF NE ...V2 DISCSR: .WORD - INSCSR: .WORD 0 .IFF DISCSR: .WORD NAME'$CSR INSCSR: .WORD NAME'$CSR .ENDC ...V2=2. ...V3=^o170 .IRP X, .IRP Y,\...V2 .=...V3 .WORD 0 DISCS'Y: .WORD X .ENDR ...V2=...V2+1 ...V3=...V3-^o2 .ENDR .=^o202 INSSYS: .=^o200 INSDAT: .ENDM ;+TEST .Enabl LSB .PSect Text $DRINS: .Asciz "%SYSMAC-I-Testing .DRINS" .PSect Active Mov #$DRINS,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRPTR Define added handler entry points **Handler only** .MACRO .DRPTR FETCH=0,RELEASE=0,LOAD=0,UNLOAD=0 ...V2=0 .IIF NDF ...V9,...V9=0 .IIF NDF ...V18,...V18=0 .IIF NDF ...V19,...V19=0 .ASECT .=0 .RAD50 "HAN" .IF IDN ,<*NO*> ...V2=1 ...V18=...V18!^o200 ...V19=...V19!^o100000 .WORD 0 .IFF .WORD FETCH .IF DIF ,<0> ...V9=...V9!1 .ENDC .ENDC .WORD RELEASE .IF IDN ,<*NO*> .IF EQ ...V2 ...V18=...V18!^o100 ...V19=...V19!^o20000 .IFTF .WORD 0 .IFF .ERROR ;?SYSMAC-W-L O A D and F E T C H both *NO* - L O A D = 0 forced; .ENDC .IFF .WORD LOAD .IF DIF ,<0> ...V9=...V9!^o4 .ENDC .ENDC .WORD UNLOAD .IIF DIF ,<0> ...V9=...V9!^o2 .IIF DIF ,<0> ...V9=...V9!^o10 .=^o21 .IRP X,\...V18 .BYTE X .ENDR .ENDM ;+TEST .Enabl LSB .PSect Text $DRPTR: .Asciz "%SYSMAC-I-Testing .DRPTR" .PSect Active Mov #$DRPTR,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRSET Define SET option table entry **Handler only** .MACRO .DRSET OPTION,VAL,RTN,MODE .ASECT .IF LE .-^o400 .=^o400 .IFF .=.-2. .ENDC VAL ...V2=. .RAD50 \OPTION\ .=...V2+4. .BYTE /2. ...V2=0 .IRP X, .IF IDN , ...V2=...V2!^o100 .IFF .IF IDN , ...V2=...V2!^o200 .IFF .IF IDN , ...V2=...V2!^o140 .IFF .ERROR;?SYSMAC-E-Invalid O P T I O N, expecting NO/NUM/OCT, found - X; .ENDC .ENDC .ENDC .ENDR .BYTE ...V2 .WORD 0 .ENDM ;+TEST .Enabl LSB .PSect Text $DRSET: .Asciz "%SYSMAC-I-Testing .DRSET" .PSect Active Mov #$DRSET,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRSPF Define supported SPFUN request numbers **Handler only** .MACRO .DRSPF ARG,ARG2,TYPE=O .MCALL ...CM8 ...V10=0 .IRPC X, .IIF IDN ,<+> ...V10=1 .IIF IDN ,<-> ...V10=2. .MEXIT .ENDR .IF EQ ...V10-1 .=30 .WORD 0'ARG' .MEXIT .ENDC ...V4 = -1 ...V3 = 0 .IRPC X, .IIF IDN , ...V4 = ...V3 ...V3 = ...V3 + 1 .ENDR .IIF EQ ...V4+1 .ERROR ;?SYSMAC-E-Invalid T Y P E, expecting O/R/W/M/T, found - TYPE; .IF EQ ...V10-2. ...V2=0 ...V3=0 .IRP X, ...V10=0 ...V11= ...CM8 X,...V3,...V2 .IF EQ ...V10 .IF EQ ...V2 ...V2=...V11 .IFF .IIF NE ...V2-...V11 .ERROR ;?SYSMAC-E-Too many different NN_ SPFUN codes; .ENDC .ENDC ...CM8 X,...V3,...V2 .ENDR .IRP X,\...V3 .BYTE X .ENDR .IRP X,\...V2 .IRP Y,\...V4 .BYTE X!Y .ENDR .ENDR .MEXIT .ENDC .IF NDF ...V15 ...V15=0 ...V16=0 ...V17=0 ...V12=0 ...V13=0 ...V14=0 .ENDC .IRP X, ...V10=0 ...V11=!...V4 ...CM8 X,...V15,...V12 ...CM8 X,...V16,...V13 ...CM8 X,...V17,...V14 .IF EQ ...V10 ;...V10 = 0 implies that this is an .IF EQ ...V12 ;as yet unknow .spfun group ...V12=...V11 .IFF .IF EQ ...V13 ...V13=...V11 .IFF .IF EQ ...V14 ...V14=...V11 .IFF .ERROR ;?SYSMAC-F-Too many different NN_ SPFUN codes; .ENDC .ENDC .ENDC .ENDC ...CM8 X,...V15,...V12 ...CM8 X,...V16,...V13 ...CM8 X,...V17,...V14 .ENDR .ASECT .=^o22 .IRP X,<...V15,...V12,...V16,...V13,...V17,...V14> .IRP Y,\X .BYTE Y .ENDR .ENDR .WORD 000000 .ENDM ;+TEST .Enabl LSB .PSect Text $DRSPF: .Asciz "%SYSMAC-I-Testing .DRSPF" .PSect Active Mov #$DRSPF,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl ...CM8 Support macro for .DRSPF **Handler only** ;++ ; ...CM8 ; ; Verifies VAL to be negative ; Study .DRSPF & ...CM8 for further information (Tough luck?) ; Defines XXN as bottom octade of VAL ;++ .MACRO ...CM8 VAL,XXN,NNX .IIF EQ ...V11&^o200 .ERROR VAL ;?SYSMAC-E-SPFUN values must be negative; .IF EQ ...V11-NNX ...V10=1 .REPT VAL-<...V11&^o370> ...V10=...V10+...V10 .ENDR XXN=XXN!...V10 .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $..CM8: .Asciz "%SYSMAC-I-Testing ...CM8" .PSect Active Mov #$..CM8,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRTAB Define DEC table pointer table **Handler only** ;++ ; .DRTAB ; ; Used to setup a pointer for DEC defined handler data tables. ; ; The first argument is a RAD50 value. ; The second argument is a poiniter to a table. ; The third argument is the size in bytes ; of the table pointed to by the second argument. ; ; ; The table is terminated with an invocation of .DRTAB ; without any arguments. ; ; .DRTAB JFW,JIMS,SZJIM ; .DRTAB JBM,JIMS2,SZJIM2 ; .DRTAB ; ; The first invocation of .DRTAB also sets up locations 70--74 ; in block 0. 70 is set to -1 to indicate that 72 points to ; one or more entries generated by .DRTAB; 72 is the pointer to ; the first .DRTAB entry; and 74 is length of all the .DRTAB ; entries in bytes. ; ; DO NOT INVOKE in .ASECT (.SAVE /.RESTORE *B*U*G*) ;-- .MACRO .DRTAB TYPE,ADDR,SIZE,L1=$DEC$ .IF EQ ...V21 ...V21=1 .SAVE .ASECT .=^o070 .WORD -1 .WORD L1 .WORD L1'Z-L1 .RESTORE L1: .ENDC .IF NB ...V2=. .RAD50 "TYPE" .=...V2+2. .WORD ADDR .WORD SIZE .IFF .WORD 000000 L1'Z: .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $DRTAB: .Asciz "%SYSMAC-I-Testing .DRTAB" .PSect Active Mov #$DRTAB,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRUSE Define user pointer table **Handler only** ;++ ; .DRUSE ; ; Used to setup a pointer for user defined pointers. ; ; To define a user pointer, define the type as the ; first argument and the value or pointer as the second ; argument. The first argument is a RAD50 value. ; The third argument is, by convention the size in bytes ; of any table pointed to by the second argument. ; ; ; The table is terminated with an invocation of .DRUSE ; without any arguments. ; ; .DRUSE JFW,JIMS,SZJIM ; .DRUSE JBM,JIMS2,SZJIM2 ; .DRUSE ; ;JIMS: .WORD ^rJFW,1,2,3,4,5,6,7,8. ;SZJIM=:.-JIMS ;JIMS2: .WORD ^rJBM,10,1000,100000 ;SZJIM2=:.-JIMS2 ; ; The first invocation of .DRUSE sets up location 106 in block ; 0 of the handler to point to the first .DRUSE entry. ; ; DO NOT INVOKE in .ASECT (.SAVE /.RESTORE *B*U*G*) ;-- .MACRO .DRUSE TYPE,ADDR,SIZE,L1=$USER$ .IF EQ ...V20 ...V20=1 .SAVE .ASECT .=^o106 .WORD L1 .RESTORE L1: .ENDC .IF NB ...V2=. .RAD50 "TYPE" .=...V2+2. .WORD ADDR .WORD SIZE .IFF .WORD 000000 .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $DRUSE: .Asciz "%SYSMAC-I-Testing .DRUSE" .PSect Active Mov #$DRUSE,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DRVTB Define entry in multi vector table **Handler only** .MACRO .DRVTB NAME,VEC,INT,PS=0,SLOTID .IF NB NAME NAME'$VTB:: .IF NB SLOTID .WORD ^o100000,SLOTID .ENDC .IFF .=.-2. .ENDC .IIF NE VEC&3. .ERROR VEC;?SYSMAC-E-Odd or invalid vector specified; .WORD VEC&^C3.,INT-.,^o340!PS,^o100000 .ENDM ;+TEST .Enabl LSB .PSect Text $DRVTB: .Asciz "%SYSMAC-I-Testing .DRVTB" .PSect Active Mov #$DRVTB,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .DSTATUS Get device status request .MACRO .DSTAT RETSPC,DNAM .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CMC ,,342 .ENDM ;+TEST .Enabl LSB .PSect Text $DSTAT: .Asciz "%SYSMAC-I-Testing .DSTATUS" .PSect Active Mov #$DSTAT,R0 ;Ident the test Call BegTst Mov SP,R5 ;save stack pointer Mov #Patter,R0 ;init R0 DSTA1: .DSTATUS #111111,#123456 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp SP,R5 ;is stack correct? Beq 30$ ;yes Call Err1.3 ;no 30$: Mov SP,R5 ;save stack pointer Mov #123456,R0 ;init R0 DSTA2: .DSTATUS #111111,R0 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp SP,R5 ;is stack correct? Beq 60$ ;yes Call Err2.3 ;no 60$: Mov SP,R5 ;save stack pointer Mov #123456,R0 ;init R0 DSTA3: .DSTATUS #111111 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp SP,R5 ;is stack correct? Beq 90$ ;yes Call Err3.3 ;no 90$: .PSect Data DSTA4: .DSTATUS 100$: .PSect Active Cmp #EMT+...DST,100$-2 ;correct EMT? Beq 110$ ;yes Call Err4 ;no 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .ELAW Eliminate address window request .MACRO .ELAW AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,30.,3.,,,E .ENDM ;+TEST .Enabl LSB .PSect Text $ELAW: .Asciz "%SYSMAC-I-Testing .ELAW" .PSect Active Mov #$ELAW,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s ELAW1: .ELAW #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.ELAW*^o400+..ELAW,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s ELAW2: .ELAW #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.ELAW*^o400+..ELAW,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 ELAW3: .ELAW ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.ELAW*^o400+..ELAW,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data ELAW4: .ELAW 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .ELRG Eliminate region request .MACRO .ELRG AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,30.,1.,,,E .ENDM ;+TEST .Enabl LSB .PSect Text $ELRG: .Asciz "%SYSMAC-I-Testing .ELRG" .PSect Active Mov #$ELRG,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s ELRG1: .ELRG #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.ELRG*^o400+..ELRG,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s ELRG2: .ELRG #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.ELRG*^o400+..ELRG,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 ELRG3: .ELRG ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.ELRG*^o400+..ELRG,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data ELRG4: .ELRG 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .ENTER Create file request .MACRO .ENTER AREA,CHAN,DBLK,LEN,SEQNUM,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF NE ...V1-1 ...CM1 ,2,,, ...CM2 ,4,,C ...CM2 ,6,E,C .MEXIT .ENDC ...CM5 ...CM0 ,<40+AREA> .ENDM ;+TEST ;V1 not tested .Enabl LSB .PSect Text $ENTER: .Asciz "%SYSMAC-I-Testing .ENTER" .PSect Active Mov #$ENTER,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 ENTE1: .ENTER #Area,#123,#123456,#0,#101010 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.ENTER,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is DBLK set? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #0,(R1)+ ;is LEN set? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #101010,(R1)+ ;is SEQNUM set? Beq 51$ ;yes Call Err1.6 ;no 51$: Call AreaM1 Mov #Area,R0 ENTE2: .ENTER ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 60$ ;yes Call Err2.1 ;no 60$: CmpB #123,(R1)+ ;is channel set? Beq 70$ ;yes Call Err2.2 ;no 70$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 80$ ;yes Call Err2.3 ;no 80$: Cmp #123456,(R1)+ ;is DBLK set? Beq 90$ ;yes Call Err2.4 ;no 90$: Cmp #-1,(R1)+ ;is LEN unchanged? Beq 100$ ;yes Call Err2.5 ;no 100$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 52$ ;yes Call Err2.6 ;no 52$: Call AreaM1 Mov #Area,R0 ENTE3: .ENTER ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 110$ ;yes Call Err3.1 ;no 110$: CmpB #123,(R1)+ ;is channel set? Beq 120$ ;yes Call Err3.2 ;no 120$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 130$ ;yes Call Err3.3 ;no 130$: Cmp #123456,(R1)+ ;is DBLK set? Beq 140$ ;yes Call Err3.4 ;no 140$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 150$ ;yes Call Err3.5 ;no 150$: .PSect Data ENTE4: .ENTER CODE=NOSET 160$: .PSect Active Cmp #EMT+...AR0,160$-2 ;correct EMT? Beq 170$ ;yes Call Err4 ;no 170$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .EXIT Return to monitor request .MACRO .EXIT EMT ^o350 .ENDM ;+TEST .Enabl LSB .PSect Text $EXIT: .Asciz "%SYSMAC-I-Testing .EXIT" .PSect Active Mov #$EXIT,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data EXIT1: .EXIT .=.-2. 13$: .=.+2. 15$: .PSect Active Cmp #EMT+...EXI,13$ ;was the correct EMT generated? Beq 10$ ;Yes Call Err1 10$: Call EndTst .DSABL LSB .PSect Static ;-TEST .Page .SbTtl .FETCH Fetch device handler request .MACRO .FETCH ADDR,DNAM .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CMC ,,343 .ENDM ;+TEST .Enabl LSB .PSect Text $FETCH: .Asciz "%SYSMAC-I-Testing .FETCH" .PSect Active Mov #$FETCH,R0 ;Ident the test Call BegTst Mov SP,R5 ;save stack pointer Mov #Patter,R0 ;init R0 FETC1: .FETCH #111111,#123456 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp SP,R5 ;is stack correct? Beq 30$ ;yes Call Err1.3 ;no 30$: Mov SP,R5 ;save stack pointer Mov #123456,R0 ;init R0 FETC2: .FETCH #111111,R0 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp SP,R5 ;is stack correct? Beq 60$ ;yes Call Err2.3 ;no 60$: Mov SP,R5 ;save stack pointer Mov #123456,R0 ;init R0 FETC3: .FETCH #111111 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp SP,R5 ;is stack correct? Beq 90$ ;yes Call Err3.3 ;no 90$: .PSect Data FETC4: .FETCH 100$: .PSect Active Cmp #EMT+...FET,100$-2 ;correct EMT? Beq 110$ ;yes Call Err4 ;no 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .FORK Switch to completion routine status call *Handler mostly** .MACRO .FORK FKBLK JSR R5,@$FKPTR .WORD FKBLK-. .ENDM ;+TEST .Enabl LSB .PSect Text $FORK: .Asciz "%SYSMAC-I-Testing .FORK" .PSect Active Mov #$FORK,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .FPROT Set/Clear file protection request .MACRO .FPROT AREA,CHAN,DBLK,PROT=#1,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 ,35,,, ...CM2 ,4,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $FPROT: .Asciz "%SYSMAC-I-Testing .FPROTECT" .PSect Active Mov #$FPROT,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 FPRO1: .FPROT #Area,#123,#123456,#0 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.FPROT,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is DBLK set? Beq 40$ ;yes Call Err1.4 ;no 40$: CmpB #..PROT,(R1)+ ;is PROT set? Beq 50$ ;yes Call Err1.5 ;no 50$: Call AreaM1 Mov #Area,R0 FPRO2: .FPROT ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 60$ ;yes Call Err2.1 ;no 60$: CmpB #123,(R1)+ ;is channel set? Beq 70$ ;yes Call Err2.2 ;no 70$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 80$ ;yes Call Err2.3 ;no 80$: Cmp #123456,(R1)+ ;is DBLK set? Beq 90$ ;yes Call Err2.4 ;no 90$: CmpB #..UNPR,(R1)+ ;is PROT defaulted to 1? Beq 100$ ;yes Call Err2.5 ;no 100$: Call AreaM1 Mov #Area,R0 FPRO3: .FPROT ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 110$ ;yes Call Err3.1 ;no 110$: CmpB #123,(R1)+ ;is channel set? Beq 120$ ;yes Call Err3.2 ;no 120$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 130$ ;yes Call Err3.3 ;no 130$: Cmp #123456,(R1)+ ;is DBLK set? Beq 140$ ;yes Call Err3.4 ;no 140$: CmpB #..UNPR,(R1)+ ;is PROT defaulted to 1? Beq 150$ ;yes Call Err3.5 ;no 150$: .PSect Data FPRO4: .FPROT CODE=NOSET 160$: .PSect Active Cmp #EMT+...AR0,160$-2 ;correct EMT? Beq 170$ ;yes Call Err4 ;no 170$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .GCMAP return extended mapping status .MACRO .GCMAP AREA,CODE .MCALL .CMAP .IIF IDN ,NOSET .CMAP ,, .IIF DIF ,NOSET .CMAP ,#0, .ENDM .Enabl LSB .PSect Text $GCMAP: .Asciz "%SYSMAC-I-Testing .GCMAP" .PSect Active Mov #$GCMAP,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 GCMA1: .GCMAP #Area .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.GCMAP,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #0,(R1)+ ;is CMAP set? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 Mov #Area,R0 GCMA2: .GCMAP .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 50$ ;yes Call Err2.1 ;no 50$: CmpB #377,(R1)+ ;is channel unchanged? Beq 60$ ;yes Call Err2.2 ;no 60$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 70$ ;yes Call Err2.3 ;no 70$: Cmp #0,(R1)+ ;is CMAP set? Beq 80$ ;yes Call Err2.4 ;no 80$: Call AreaM1 Mov #Area,R0 GCMA3: .GCMAP CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 90$ ;yes Call Err3.1 ;no 90$: CmpB #377,(R1)+ ;is channel unchanged? Beq 100$ ;yes Call Err3.2 ;no 100$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 110$ ;yes Call Err3.3 ;no 110$: Cmp #177777,(R1)+ ;is CMAP unchanged? Beq 120$ ;yes Call Err3.4 ;no 120$: .PSect Data GCMA4: .GCMAP CODE=NOSET 130$: .PSect Active Cmp #EMT+...AR0,130$-2 ;correct EMT? Beq 140$ ;yes Call Err4 ;no 140$: Mov SP,R5 ;save the stack alignment GCMA5: .GCMAP CODE=STACK .=.-4 NOP ;Zap the EMT .=.+2 ;save the BIT Cmp SP,R5 ;is the stack alignment preserved? Beq 150$ ;yes Call Err5 ;nope 150$: Mov R5,SP ;restore it Mov SP,R5 ;save the stack alignment GCMA6: .GCMAP CODE=SP .=.-4 NOP ;Zap the EMT .=.+2 ;save the BIT Cmp SP,R5 ;is the stack alignment preserved? Beq 160$ ;yes Call Err6 ;nope 160$: Mov R5,SP ;restore it Mov SP,R5 ;save the stack alignment GCMA7: .GCMAP CODE=STACK .=.-4 ;ZAP EMT and BIT Mov R0,R1 ;point to argument area Cmp R0,SP ;R0 correct? Beq 170$ ;yes Call Err7.1 ;no 170$: CmpB #0,(R1)+ ;is channel set? Beq 180$ ;yes Call Err7.2 ;no 180$: CmpB #.GCMAP,(R1)+ ;is subcode set? Beq 190$ ;yes Call Err7.3 ;no 190$: Cmp #0,(R1)+ ;is CMAP set? Beq 200$ ;yes Call Err7.4 ;no 200$: Mov R5,SP ;restore stack alignment Call EndTst .Dsabl LSB .If NE MAC$ER ;Expect P errors .GCMAP AREA,CODE=STACK .GCMAP AREA,CODE=SP .EndC ;-TEST .Page .SbTtl .GFDATE Get file entry date word request .MACRO .GFDAT AREA,CHAN,DBLK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 ,36,,, ...CM2 #0,4 ...CM2 #12.*^o400,6,E .ENDM ;+TEST .Enabl LSB .PSect Text $GFDAT: .Asciz "%SYSMAC-I-Testing .GFDAT" .PSect Active Mov #$GFDAT,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .GFINFO Get file entry request .MACRO .GFINF AREA,CHAN,DBLK,OFFSE,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 ,36,,, ...CM2 #0,4 ...CM2 #0,6,,,B ...CM2 ,7,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $GFINF: .Asciz "%SYSMAC-I-Testing .GFINF" .PSect Active Mov #$GFINF,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .GFSTAT Get file entry status word request .MACRO .GFSTAT AREA,CHAN,DBLK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 ,36,,, ...CM2 #0,4 ...CM2 #0,6,E .ENDM ;+TEST .Enabl LSB .PSect Text $GFSTA: .Asciz "%SYSMAC-I-Testing .GFSTA" .PSect Active Mov #$GFSTA,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .GMCX Get mapping context request .MACRO .GMCX AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,30.,6.,,,E .ENDM ;+TEST .Enabl LSB .PSect Text $GMCX: .Asciz "%SYSMAC-I-Testing .GMCX" .PSect Active Mov #$GMCX,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s GMCX1: .GMCX #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.GMCX*^o400+..GMCX,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s GMCX2: .GMCX #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.GMCX*^o400+..GMCX,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 GMCX3: .GMCX ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.GMCX*^o400+..GMCX,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data GMCX4: .CRAW 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .GTIM Get current time request .MACRO .GTIM AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,17.,0.,,,E .ENDM ;+TEST .Enabl LSB .PSect Text $GTIM: .Asciz "%SYSMAC-I-Testing .GTIM" .PSect Active Mov #$GTIM,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s GTIM1: .GTIM #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.GTIM*^o400+0,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s GTIM2: .GTIM #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.GTIM*^o400+0,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 GTIM3: .GTIM ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.GTIM*^o400+0,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data GTIM4: .GTIM 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;Correct EMT? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .GTJB Get job information request .MACRO .GTJB AREA,ADDR,JOBBLK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,16.,1.,, .IF NB .IF IDN , ...CM2 #-1,4,E .IFF ...CM2 ,4,E .ENDC .IFF ...CM2 #-3.,4,E .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $GTJB: .Asciz "%SYSMAC-I-Testing .GTJB" .PSect Active Mov #$GTJB,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s GTJB1: .GTJB #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.GTJB*^o400+..GTJB,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Cmp #..GTV3,(R1)+ ;is the address correct? Beq 40$ ;yes Call Err1.4 40$: Call AreaM1 ;set area to -1s GTJB2: .GTJB #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 50$ ;yes Call Err2.1 ;no 50$: Cmp #.GTJB*^o400+..GTJB,(R1)+ ;is the subcode correct? Beq 60$ ;yes Call Err2.2 ;no 60$: Cmp #177777,(R1)+ ;is the address correct? Beq 70$ ;yes Call Err2.3 70$: Cmp #..GTV3,(R1)+ ;is the address correct? Beq 80$ ;yes Call Err2.4 80$: Call AreaM1 ;set area to -1s Mov #Area,R0 GTJB3: .GTJB ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 90$ ;yes Call Err3.1 ;no 90$: Cmp #.GTJB*^o400+..GTJB,(R1)+ ;is the subcode correct? Beq 100$ ;yes Call Err3.2 ;no 100$: Cmp #123456,(R1)+ ;is the address correct? Beq 110$ ;yes Call Err3.3 110$: Cmp #..GTV3,(R1)+ ;is the address correct? Beq 120$ ;yes Call Err3.4 120$: .PSect Data GTJB4: .GTJB 130$: .PSect Active Cmp #EMT+...AR0,130$-2 ;correct EMT code? Beq 140$ ;yes Call Err4 140$: Call AreaM1 ;set area to -1s GTJB5: .GTJB #Area,#123456,#121654 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 150$ ;yes Call Err5.1 ;no 150$: Cmp #.GTJB*^o400+..GTJB,(R1)+ ;is the subcode correct? Beq 160$ ;yes Call Err5.2 ;no 160$: Cmp #123456,(R1)+ ;is the address correct? Beq 170$ ;yes Call Err5.3 170$: Cmp #121654,(R1)+ ;is the address correct? Beq 180$ ;yes Call Err5.4 180$: Call AreaM1 ;set area to -1s GTJB6: .GTJB #Area,#123456,ME .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 190$ ;yes Call Err6.1 ;no 190$: Cmp #.GTJB*^o400+..GTJB,(R1)+ ;is the subcode correct? Beq 200$ ;yes Call Err6.2 ;no 200$: Cmp #123456,(R1)+ ;is the address correct? Beq 210$ ;yes Call Err6.3 210$: Cmp #..GTME,(R1)+ ;is the address correct? Beq 220$ ;yes Call Err6.4 220$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .GTLINE Get a line of input request .MACRO .GTLIN LINBUF,PROMPT,TYPE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM0 .IF NB ...CM0 #3. .IFF ...CM0 #1 .ENDC ...CM0 ...CM0 ,345 .ENDM ;+TEST .Enabl LSB .PSect Text $GTLIN: .Asciz "%SYSMAC-I-Testing .GTLINE" .PSect Active Mov #$GTLIN,R0 ;Ident the test Call BegTst Mov SP,R5 ;save Stack pointer GTLI1: .GTLIN #200 .=.-2 Cmp #..GTIS,(SP)+ ;is 0 on top of stack? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #0,(SP)+ ;is PROMPT next on stack? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #..GTAT,(SP)+ ;is "TYPE" next on stack? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #200,(SP)+ ;is LINBUF next on stack? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp SP,R5 ;is stack now aligned? Beq 50$ ;yes Call Err1.5 ;no 50$: Mov R5,SP ;force alignment Mov SP,R5 ;save Stack pointer GTLI2: .GTLIN #200,#400 .=.-2 Cmp #..GTIS,(SP)+ ;is 0 on top of stack? Beq 60$ ;yes Call Err2.1 ;no 60$: Cmp #400,(SP)+ ;is PROMPT at top of stack? Beq 70$ ;yes Call Err2.2 ;no 70$: Cmp #..GTAT,(SP)+ ;is "TYPE" next on stack? Beq 80$ ;yes Call Err2.3 ;no 80$: Cmp #200,(SP)+ ;is LINBUF next on stack? Beq 90$ ;yes Call Err2.4 ;no 90$: Cmp SP,R5 ;is stack now aligned? Beq 100$ ;yes Call Err2.5 ;no 100$: Mov R5,SP ;force alignment Mov SP,R5 ;save Stack pointer GTLI3: .GTLIN #200,#400,TYPE=TERM .=.-2 Cmp #..GTIS,(SP)+ ;is 0 on top of stack? Beq 110$ ;yes Call Err3.1 ;no 110$: Cmp #400,(SP)+ ;is PROMPT at top of stack? Beq 120$ ;yes Call Err3.2 ;no 120$: Cmp #..GTTT,(SP)+ ;is "TYPE" next on stack? Beq 130$ ;yes Call Err3.3 ;no 130$: Cmp #200,(SP)+ ;is LINBUF next on stack? Beq 140$ ;yes Call Err3.4 ;no 140$: Cmp SP,R5 ;is stack now aligned? Beq 150$ ;yes Call Err3.5 ;no 150$: Mov R5,SP ;force alignment Mov SP,R5 ;save Stack pointer GTLI4: .GTLIN #200,TYPE=TERM .=.-2 Cmp #..GTIS,(SP)+ ;is 0 on top of stack? Beq 160$ ;yes Call Err4.1 ;no 160$: Cmp #0,(SP)+ ;is PROMPT at top of stack? Beq 170$ ;yes Call Err4.2 ;no 170$: Cmp #..GTTT,(SP)+ ;is "TYPE" next on stack? Beq 180$ ;yes Call Err4.3 ;no 180$: Cmp #200,(SP)+ ;is LINBUF next on stack? Beq 190$ ;yes Call Err4.4 ;no 190$: Cmp SP,R5 ;is stack now aligned? Beq 200$ ;yes Call Err4.5 ;no 200$: Mov R5,SP ;force alignment .PSect Data GTLI5: .GTLIN 210$: .PSect Active Cmp #EMT+...GTL,210$-2 ;correct EMT generated? Beq 220$ ;yes Call Err5 ;no 220$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .GVAL Get contents of location in RMON request .MACRO .GVAL AREA,OFFSE,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,28.,0.,,,E .ENDM ;+TEST .Enabl LSB .PSect Text $GVAL: .Asciz "%SYSMAC-I-Testing .GVAL" .PSect Active Mov #$GVAL,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s GVAL1: .GVAL #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.GVAL*^o400+..GVAL,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s GVAL2: .GVAL #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.GVAL*^o400+..GVAL,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 GVAL3: .GVAL ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.GVAL*^o400+..GVAL,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data GVAL4: .GVAL 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .HERR Set hard error action request .MACRO .HERR MOV #^o2400,R0 EMT ^o374 .ENDM ;+TEST .Enabl LSB .PSect Text $HERR: .Asciz "%SYSMAC-I-Testing .HERR" .PSect Active Mov #$HERR,R0 ;Ident the test(s) Call BegTst ;Assume no errors Mov #Patter,R0 HERR1: .HERR .=.-2 ;squash EMT Cmp #.HERR*^o400,R0 ;Is R0 right? Beq 10$ Call Err1 10$: .PSect Data HERR2: .HERR .=.-2. 23$: .=.+2. 25$: .PSect Active Cmp #EMT+...R0,23$ ;was the correct EMT generated? Beq 20$ ;Yes Call Err2 20$: Call EndTst .Dsabl LSB .PSect Static ;-TEST .Page .SbTtl .HRESET Do a hard reset request .MACRO .HRESE EMT ^o357 .ENDM ;+TEST .Enabl LSB .PSect Text $HRESE: .Asciz "%SYSMAC-I-Testing .HRESE" .PSect Active Mov #$HRESE,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data HRESE1: .HRESE .=.-2. 13$: .=.+2. 15$: .PSect Active Cmp #EMT+...HRE,13$ ;was the correct EMT generated? Beq 10$ ;Yes Call Err1 10$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .INTEN Enter system state, lowering priority call .MACRO .INTEN PRIO,PIC .IF B PIC JSR R5,@^o54 .IFF MOV @#^o54,-(SP) JSR R5,@(SP)+ .ENDC .WORD ^C&224. .ENDM ;+TEST .Enabl LSB .PSect Text $INTEN: .Asciz "%SYSMAC-I-Testing .INTEN" .PSect Active Mov #$INTEN,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .LOCK Lock USR in memory and owned by this job .MACRO .LOCK EMT ^o346 .ENDM ;+TEST .Enabl LSB .PSect Text $LOCK: .Asciz "%SYSMAC-I-Testing .LOCK" .PSect Active Mov #$LOCK,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data LOCK1: .LOCK .=.-2. 13$: .=.+2. 15$: .PSect Active Cmp #EMT+...LOC,13$ ;was the correct EMT generated? Beq 10$ ;Yes Call Err1 10$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .LOOKUP Find an existing file request .MACRO .LOOKU AREA,CHAN,DBLK,SEQNUM,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF NE ...V1-1 ...CM1 ,1,,, ...CM2 ,4,E,C .MEXIT .ENDC ...CM5 ,<20+AREA> .ENDM ;+TEST .Enabl LSB .PSect Text $LOOKU: .Asciz "%SYSMAC-I-Testing .LOOKUP" .PSect Active Mov #$LOOKU,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 LOOK1: .LOOKUP #Area,#123,#123456,#0 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.LOOKU,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is DBLK set? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #0,(R1)+ ;is SEQNUM set? Beq 50$ ;yes Call Err1.5 ;no 50$: Call AreaM1 Mov #Area,R0 LOOK2: .LOOKUP ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 60$ ;yes Call Err2.1 ;no 60$: CmpB #123,(R1)+ ;is channel set? Beq 70$ ;yes Call Err2.2 ;no 70$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 80$ ;yes Call Err2.3 ;no 80$: Cmp #123456,(R1)+ ;is DBLK set? Beq 90$ ;yes Call Err2.4 ;no 90$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 100$ ;yes Call Err2.5 ;no 100$: Call AreaM1 Mov #Area,R0 LOOK3: .LOOKUP ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 110$ ;yes Call Err3.1 ;no 110$: CmpB #123,(R1)+ ;is channel set? Beq 120$ ;yes Call Err3.2 ;no 120$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 130$ ;yes Call Err3.3 ;no 130$: Cmp #123456,(R1)+ ;is DBLK set? Beq 140$ ;yes Call Err3.4 ;no 140$: Cmp #-1,(R1)+ ;is SEQNUM unchanged? Beq 150$ ;yes Call Err3.5 ;no 150$: .PSect Data LOOK4: .LOOKUP CODE=NOSET 160$: .PSect Active Cmp #EMT+...AR0,160$-2 ;correct EMT? Beq 170$ ;yes Call Err4 ;no 170$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MAP Map extended memory request .MACRO .MAP AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 ,30.,4.,,,E .ENDM ;+TEST .Enabl LSB .PSect Text $MAP: .Asciz "%SYSMAC-I-Testing .MAP" .PSect Active Mov #$MAP,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MAP1: .MAP #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MAP*^o400+..MAP,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s MAP2: .MAP #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.MAP*^o400+..MAP,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 MAP3: .MAP ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.MAP*^o400+..MAP,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data MAP4: .MAP 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MFPS Move from PS (processor independent) call .MACRO .MFPS ADDR MOV @#^o54,-(SP) ADD #^o362,(SP) CALL @(SP)+ .IF NB MOVB (SP)+,ADDR .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $MFPS: .Asciz "%SYSMAC-I-Testing .MFPS" .PSect Active Mov #$MFPS,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .MODULE Define symbols and macros for module identification .SbTtl . Meta-Macro which defines: .SbTtl . .NLCSI Define ASCII ident strings .SbTtl . .RMODULE Generate RAD50 of module name ;++ ; .MODULE ; ; Macro to define a standard identification for all ; modules. ; ; Inputs: ; ; MODULE 1-5 character symbol name (KEDIO) ; RELEASE 3 char release identification (X05) ; VERSION 2 char version number (09) ; COMMENT n char title string ; ; TITLE=YES generate .TITLE (default) ; TITLE=NO do not generate .TITLE ; ; IDENT=YES generate .IDENT (default) ; IDENT=NO do not generate .IDENT ; ; AUDIT=NO generate .AUDIT call (default) ; AUDIT=YES generate .AUDIT call ; ; LIB=NO generate .AUDIT global value (default) ; LIB=YES do not generate .AUDIT ; ; GLOBAL not specified (default) ; GLOBAL=gname substitutes gname for .'MODULE' ; ; MODNAME not specified uses MODULE (default) ; MODNAME=module name for .TITLE ; ; Outputs: ; ; .TITLE 'MODULE' - 'COMMENT' title for module ; .IDENT "'RELEASE'.'VERSION'" ident for module ; .'MODULE' ==: 'VERSION'. version value symbol Binary ; .AUDIT ==: ^R'RELEASE' release value symbol RAD50 ; ; .MCALL .AUDIT get .AUDIT definition ; .AUDIT .AUDIT .'MODULE' generate audit information ; ; ; definition of .NLCSI macro generate program ID string ; ; .NLCSI TYPE=,PART= ; TYPE=Z generate .ASCIZ (default) .ASCIZ "KEDIO X05.09 " ; TYPE=I generate .ASCII .ASCII "KEDIO X05.09 " ; ; PART=ALL generate std ID (default) .ASCIZ "KEDIO X05.09 " ; PART=NAME generate name .ASCIZ "KEDIO" ; PART=RLSVER generate release & version .ASCIZ "X05.09" ; PART=PREFIX generate message prefix .ASCIZ "?KEDIO-" ; ; definition of .RMODULE macro generate RAD50 for 'MODULE' ; ; .RMODULE ;-- .MACRO .MODULE MODULE,VERSION,COMMENT,TITLE=YES,IDENT=YES,AUDIT=NO,GLOBAL,LIB=NO,MODNAME,RELEASE=V05 .MCALL .AUDIT .IF NDF ...V27 ...V27 = 0 ...V28 = 0 ...V2 = 0 .IRPC X,'MODULE' .IF LT ...V2-6 ...V28 = ...V28*^o50+^r 'X ...V2 = ...V2+1 .IF EQ ...V2-3 ...V27 = ...V28 ...V28 = 0 .ENDC .ENDC .ENDR ...V5 = ^o110 .IFF ...V6 = 0 ...V2 = 0 .IRPC X,'MODULE' .IF LT ...V2-6 ...V6 = ...V6*^o50+^r 'X ...V2 = ...V2+1 .IF EQ ...V2-3 .IIF NE ...V6-...V27, ...V2 = ^o77777 ...V6 = 0 .ENDC .ENDC .ENDR .IIF NE ...V2-^o77777, .IIF EQ ...V6-...V28, ...V5 = ^o110 .ENDC .IF NB .IIF IDN <YES>, .TITLE 'MODNAME' - 'COMMENT' .IFF .IIF IDN <TITLE> <YES>, .TITLE 'MODULE' - 'COMMENT' .ENDC .IIF IDN <IDENT> <YES>, .IDENT "'RELEASE'.'VERSION'" .IIF IDN <LIB> <NO>,.AUDIT==:^R'RELEASE' .IF NB <GLOBAL> 'GLOBAL'==:'VERSION'. .IIF IDN <AUDIT> <YES>, .AUDIT 'GLOBAL' .IFF .'MODULE'==:'VERSION'. .IIF IDN <AUDIT> <YES>, .AUDIT .'MODULE' .ENDC .MACRO .NLCSI TYPE=Z,PART=ALL .IF IDN <PART> <ALL> .ASCI'TYPE' "'MODULE' 'RELEASE'.'VERSION' " .ENDC .IF IDN <PART> <NAME> .ASCI'TYPE' "'MODULE'" .ENDC .IF IDN <PART> <RLSVER> .ASCI'TYPE' "'RELEASE'.'VERSION' " .ENDC .IF IDN <PART> <PREFIX> .ASCI'TYPE' "?'MODULE'-" .ENDC .ENDM .MACRO .RMODULE .RAD50 "'MODULE'" .ENDM .ENDM ;>>> here convert RT$PRE||RT$??? to RAD50 and compare with .AUDIT ;+TEST .Enabl LSB .PSect Text $MODUL: .Asciz "%SYSMAC-I-Testing .MODUL" .PSect Active Mov #$MODUL,R0 ;Ident the test Call BegTst Call SkpTst .Enabl LSB .PSect Text $NLCSI: .Asciz "%SYSMAC-I-Testing .NLCSI" .PSect Active Mov #$NLCSI,R0 ;Ident the test Call BegTst Call SkpTst .Enabl LSB .PSect Text $RMODU: .Asciz "%SYSMAC-I-Testing .RMODU" .PSect Active Mov #$RMODU,R0 ;Ident the test Call BegTst Call SkpTst .Dsabl LSB ;-TEST .Page .SbTtl .MRKT Queue a timer completion routine request .MACRO .MRKT AREA,TIME,CRTN,ID,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,18.,0.,<CODE>,<TIME> ...CM2 <CRTN>,4 ...CM2 <ID>,6,E .ENDM ;+TEST .Enabl LSB .PSect Text $MRKT: .Asciz "%SYSMAC-I-Testing .MRKT" .PSect Active Mov #$MRKT,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MRKT1: .MRKT #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MRKT*^o400,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s MRKT2: .MRKT #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.MRKT*^o400,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 MRKT3: .MRKT ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.MRKT*^o400,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data MRKT4: .MRKT 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call AreaM1 ;set area to -1s MRKT5: .MRKT #Area,#123456,#121654,#154236 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 120$ ;yes Call Err5.1 ;no 120$: Cmp #.MRKT*^o400,(R1)+ ;is the subcode correct? Beq 130$ ;yes Call Err5.2 ;no 130$: Cmp #123456,(R1)+ ;is the address correct? Beq 140$ ;yes Call Err5.3 140$: Cmp #121654,(R1)+ ;is the address correct? Beq 150$ ;yes Call Err5.4 150$: Cmp #154236,(R1)+ ;is the address correct? Beq 160$ ;yes Call Err5.5 160$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MSDS control mapping of U/S D mode .MACRO .MSDS AREA,CMAP,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...V2=0 .IIF IDN <CODE>,<SP> ...V2=1 .IIF IDN <CODE>,<STACK> ...V2=1 .IF EQ ...V2 .IF NB <CMAP> .NTYPE ...V2,CMAP .IFF ...V2=0 .ENDC .IF EQ ...V2-^o27 .MCALL .CMAP .CMAP <AREA>,<CMAP!^o4000>,<CODE> .IFF ...CM6 <AREA>,38.,0.,<CODE>,<CMAP> .IF DIF <CODE>,<NOSET> BIS #^o4000,2(R0) .ENDC EMT ^o375 .ENDC .MEXIT .ENDC .IIF NB <AREA>,.ERROR;?SYSMAC-W-A R E A ignored when stack form used; ...CM0 <CMAP> BIS #^o4000,@SP ...CM0 <#^o<46*400>> MOV SP,R0 EMT 375 BIT (SP)+,(SP)+ .ENDM ;+TEST .Enabl LSB .PSect Text $MSDS: .Asciz "%SYSMAC-I-Testing .MSDS" .PSect Active Mov #$MSDS,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 MSDS1: .MSDS #Area,#123 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.MSDS,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #000123!CM.DUS,(R1)+ ;is CMAP set? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 Mov #Area,R0 MSDS2: .MSDS ,#123 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 50$ ;yes Call Err2.1 ;no 50$: CmpB #377,(R1)+ ;is channel unchanged? Beq 60$ ;yes Call Err2.2 ;no 60$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 70$ ;yes Call Err2.3 ;no 70$: Cmp #000123!CM.DUS,(R1)+ ;is CMAP set? Beq 80$ ;yes Call Err2.4 ;no 80$: Call AreaM1 Mov #Area,R0 MSDS3: .MSDS ,#123,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 90$ ;yes Call Err3.1 ;no 90$: CmpB #377,(R1)+ ;is channel unchanged? Beq 100$ ;yes Call Err3.2 ;no 100$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 110$ ;yes Call Err3.3 ;no 110$: Cmp #000123!CM.DUS,(R1)+ ;is CMAP set? Beq 120$ ;yes Call Err3.4 ;no 120$: .PSect Data MSDS4: .MSDS CODE=NOSET 130$: .PSect Active Cmp #EMT+...AR0,130$-2 ;correct EMT? Beq 140$ ;yes Call Err4 ;no 140$: Mov SP,R5 ;save the stack alignment MSDS5: .MSDS ,#123,CODE=STACK .=.-4 NOP ;Zap the EMT .=.+2 ;save the BIT Cmp SP,R5 ;is the stack alignment preserved? Beq 150$ ;yes Call Err5 ;nope 150$: Mov R5,SP ;restore it Mov SP,R5 ;save the stack alignment MSDS6: .MSDS ,#123,CODE=SP .=.-4 NOP ;Zap the EMT .=.+2 ;save the BIT Cmp SP,R5 ;is the stack alignment preserved? Beq 160$ ;yes Call Err6 ;nope 160$: Mov R5,SP ;restore it Mov SP,R5 ;save the stack alignment MSDS7: .MSDS ,#123,CODE=STACK .=.-4 ;ZAP EMT and BIT Mov R0,R1 ;point to argument area Cmp R0,SP ;R0 correct? Beq 170$ ;yes Call Err7.1 ;no 170$: CmpB #0,(R1)+ ;is channel set? Beq 180$ ;yes Call Err7.2 ;no 180$: CmpB #.MSDS,(R1)+ ;is subcode set? Beq 190$ ;yes Call Err7.3 ;no 190$: Cmp #000123!CM.DUS,(R1)+ ;is CMAP set? Beq 200$ ;yes Call Err7.4 ;no 200$: Mov R5,SP ;restore stack alignment Mov SP,R5 ;save the stack alignment MSDS8: .MSDS ,,CODE=SP .=.-4 ;ZAP EMT and BIT Mov R0,R1 ;point to argument area Cmp R0,SP ;R0 correct? Beq 210$ ;yes Call Err8.1 ;no 210$: CmpB #0,(R1)+ ;is channel set? Beq 220$ ;yes Call Err8.2 ;no 220$: CmpB #.MSDS,(R1)+ ;is subcode set? Beq 230$ ;yes Call Err8.3 ;no 230$: Cmp #CM.DUS,(R1)+ ;is CMAP defaulted? Beq 240$ ;yes Call Err8.4 ;no 240$: Mov R5,SP ;restore stack alignment Mov SP,R5 ;save the stack alignment Mov #123,R2 MSDS9: .MSDS ,R2,CODE=STACK .=.-4 ;ZAP EMT and BIT Mov R0,R1 ;point to argument area Cmp R0,SP ;R0 correct? Beq 250$ ;yes Call Err9.1 ;no 250$: CmpB #0,(R1)+ ;is channel set? Beq 260$ ;yes Call Err9.2 ;no 260$: CmpB #.MSDS,(R1)+ ;is subcode set? Beq 270$ ;yes Call Err9.3 ;no 270$: Cmp #000123!CM.DUS,(R1)+ ;is CMAP set? Beq 280$ ;yes Call Err9.4 ;no 280$: Mov R5,SP ;restore stack alignment Call EndTst .Dsabl LSB .If NE MAC$ER ;Expect P errors .MSDS AREA,CODE=STACK .MSDS AREA,CODE=SP .EndC ;-TEST .Page .SbTtl .MTATCH Attach to a Multi-Terminal LUN request .MACRO .MTATC AREA,ADDR,UNIT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,5.,<CODE>,<ADDR> ...CM2 <UNIT>,4,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTATC: .Asciz "%SYSMAC-I-Testing .MTATCH" .PSect Active Mov #$MTATC,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTAT1: .MTATCH #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTATC*^o400+..MTAT,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 40$ ;yes Call Err1.4 40$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 50$ ;yes Call Err1.5 50$: Call AreaM1 ;set area to -1s MTAT2: .MTATCH #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 60$ ;yes Call Err2.1 ;no 60$: Cmp #.MTATC*^o400+..MTAT,(R1)+ ;is the subcode correct? Beq 70$ ;yes Call Err2.2 ;no 70$: Cmp #177777,(R1)+ ;is the address correct? Beq 80$ ;yes Call Err2.3 80$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 90$ ;yes Call Err2.4 90$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 100$ ;yes Call Err2.5 100$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTAT3: .MTATCH ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 110$ ;yes Call Err3.1 ;no 110$: Cmp #.MTATC*^o400+..MTAT,(R1)+ ;is the subcode correct? Beq 120$ ;yes Call Err3.2 ;no 120$: Cmp #123456,(R1)+ ;is the address correct? Beq 130$ ;yes Call Err3.3 130$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 140$ ;yes Call Err3.4 140$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 150$ ;yes Call Err3.5 150$: .PSect Data MTAT4: .MTATCH 160$: .PSect Active Cmp #EMT+...AR0,160$-2 ;correct EMT code? Beq 170$ ;yes Call Err4 170$: Call AreaM1 ;set area to -1s MTAT5: .MTATCH #Area,#123456,#12 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 180$ ;yes Call Err5.1 ;no 180$: Cmp #.MTATC*^o400+..MTAT,(R1)+ ;is the subcode correct? Beq 190$ ;yes Call Err5.2 ;no 190$: Cmp #123456,(R1)+ ;is the address correct? Beq 200$ ;yes Call Err5.3 200$: CmpB #12,(R1)+ ;is the address correct? Beq 210$ ;yes Call Err5.4 210$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 220$ ;yes Call Err5.5 220$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTDTCH Detach from a Multi-Terminal LUN request .MACRO .MTDTC AREA,UNIT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,6.,<CODE> ...CM2 <UNIT>,4,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTDTC: .Asciz "%SYSMAC-I-Testing .MTDTCH" .PSect Active Mov #$MTDTC,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTDT1: .MTDTCH #Area,#123 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTDTC*^o400+..MTDT,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Tst (R1)+ ;skip unused word CmpB #123,(R1)+ ;is the LUN correct? Beq 30$ ;yes Call Err1.3 30$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 32$ ;yes Call Err1.5 32$: CmpB #-1,(R1)+ ;Is the high byte unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 ;set area to -1s MTDT2: .MTDTCH #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 50$ ;yes Call Err2.1 ;no 50$: Cmp #.MTDTC*^o400+..MTDT,(R1)+ ;is the subcode correct? Beq 60$ ;yes Call Err2.2 ;no 60$: Cmp #177777,(R1)+ ;is the address correct? Beq 70$ ;yes Call Err2.3 70$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 71$ ;yes Call Err2.4 71$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 72$ ;yes Call Err2.5 72$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTDT3: .MTDTCH ,#123,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 80$ ;yes Call Err3.1 ;no 80$: Cmp #.MTDTC*^o400+..MTDT,(R1)+ ;is the subcode correct? Beq 90$ ;yes Call Err3.2 ;no 90$: Tst (R1)+ ;skip unused word CmpB #123,(R1)+ ;is the LUN correct? Beq 100$ ;yes Call Err3.3 100$: CmpB #-1,(R1)+ ;Is the high byte unchanged? Beq 110$ ;yes Call Err3.4 ;no 110$: .PSect Data MTDT4: .MTDTCH 120$: .PSect Active Cmp #EMT+...AR0,120$-2 ;correct EMT code? Beq 130$ ;yes Call Err4 130$: Call AreaM1 ;set area to -1s MTDT5: .MTDTCH #Area,#123 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 140$ ;yes Call Err5.1 ;no 140$: Cmp #.MTDTC*^o400+..MTDT,(R1)+ ;is the subcode correct? Beq 150$ ;yes Call Err5.2 ;no 150$: Tst (R1)+ ;skip unused word CmpB #123,(R1)+ ;is the LUN correct? Beq 160$ ;yes Call Err5.3 160$: CmpB #-1,(R1)+ ;Is the high byte unchanged? Beq 170$ ;yes Call Err5.4 ;no 170$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTGET Get status information about a Multi-Terminal LUN request .MACRO .MTGET AREA,ADDR,UNIT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,1.,<CODE>,<ADDR> ...CM2 <UNIT>,4,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTGET: .Asciz "%SYSMAC-I-Testing .MTGET" .PSect Active Mov #$MTGET,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTGE1: .MTGET #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTGET*^o400+..MTGE,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 31$ ;yes Call Err1.4 31$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 32$ ;yes Call Err1.5 32$: Call AreaM1 ;set area to -1s MTGE2: .MTGET #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.MTGET*^o400+..MTGE,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 61$ ;yes Call Err2.4 61$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 62$ ;yes Call Err2.5 62$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTGE3: .MTGET ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.MTGET*^o400+..MTGE,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 91$ ;yes Call Err3.4 91$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 92$ ;yes Call Err3.5 92$: .PSect Data MTGE4: .MTGET 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call AreaM1 ;set area to -1s MTGE5: .MTGET #Area,#123456,#12 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 120$ ;yes Call Err5.1 ;no 120$: Cmp #.MTGET*^o400+..MTGE,(R1)+ ;is the subcode correct? Beq 130$ ;yes Call Err5.2 ;no 130$: Cmp #123456,(R1)+ ;is the address correct? Beq 140$ ;yes Call Err5.3 140$: CmpB #12,(R1)+ ;is the address correct? Beq 150$ ;yes Call Err5.4 150$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 102$ ;yes Call Err5.5 102$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTIN Get char(s) from a Multi-Terminal LUN request .MACRO .MTIN AREA,ADDR,UNIT,CHRCNT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,2.,<CODE>,<ADDR> ...CM2 <UNIT>,4,,,B ...CM2 <CHRCNT>,5,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTIN: .Asciz "%SYSMAC-I-Testing .MTIN" .PSect Active Mov #$MTIN,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTIN1: .MTIN #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 40$ ;yes Call Err1.4 40$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 50$ ;yes Call Err1.5 50$: Call AreaM1 ;set area to -1s MTIN2: .MTIN #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 60$ ;yes Call Err2.1 ;no 60$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 70$ ;yes Call Err2.2 ;no 70$: Cmp #177777,(R1)+ ;is the address correct? Beq 80$ ;yes Call Err2.3 80$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 90$ ;yes Call Err2.4 90$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 100$ ;yes Call Err2.5 100$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTIN3: .MTIN ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 110$ ;yes Call Err3.1 ;no 110$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 120$ ;yes Call Err3.2 ;no 120$: Cmp #123456,(R1)+ ;is the address correct? Beq 130$ ;yes Call Err3.3 130$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 140$ ;yes Call Err3.4 140$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 150$ ;yes Call Err3.5 150$: .PSect Data MTIN4: .MTIN 160$: .PSect Active Cmp #EMT+...AR0,160$-2 ;correct EMT code? Beq 170$ ;yes Call Err4 170$: Call AreaM1 ;set area to -1s MTIN5: .MTIN #Area,#123456,#12 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 180$ ;yes Call Err5.1 ;no 180$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 190$ ;yes Call Err5.2 ;no 190$: Cmp #123456,(R1)+ ;is the address correct? Beq 200$ ;yes Call Err5.3 200$: CmpB #12,(R1)+ ;is the address correct? Beq 210$ ;yes Call Err5.4 210$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 220$ ;yes Call Err5.5 220$: Call AreaM1 ;set area to -1s MTIN6: .MTIN #Area,#123456,,#55 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 230$ ;yes Call Err6.1 ;no 230$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 240$ ;yes Call Err6.2 ;no 240$: Cmp #123456,(R1)+ ;is the address correct? Beq 250$ ;yes Call Err6.3 250$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 260$ ;yes Call Err6.4 260$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 270$ ;yes Call Err6.5 270$: Call AreaM1 ;set area to -1s MTIN7: .MTIN #Area,,,#55 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 280$ ;yes Call Err7.1 ;no 280$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 290$ ;yes Call Err7.2 ;no 290$: Cmp #177777,(R1)+ ;is the address correct? Beq 300$ ;yes Call Err7.3 300$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 310$ ;yes Call Err7.4 310$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 320$ ;yes Call Err7.5 320$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTIN8: .MTIN ,#123456,,#55,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 330$ ;yes Call Err8.1 ;no 330$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 340$ ;yes Call Err8.2 ;no 340$: Cmp #123456,(R1)+ ;is the address correct? Beq 350$ ;yes Call Err8.3 350$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 360$ ;yes Call Err8.4 360$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 370$ ;yes Call Err8.5 370$: Call AreaM1 ;set area to -1s MTIN9: .MTIN #Area,#123456,#12,#55 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 380$ ;yes Call Err9.1 ;no 380$: Cmp #.MTIN*^o400+..MTIN,(R1)+ ;is the subcode correct? Beq 390$ ;yes Call Err9.2 ;no 390$: Cmp #123456,(R1)+ ;is the address correct? Beq 400$ ;yes Call Err9.3 400$: CmpB #12,(R1)+ ;is the address correct? Beq 410$ ;yes Call Err9.4 410$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 420$ ;yes Call Err9.5 420$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTOUT Send char(s) to a Multi-Terminal LUN request .MACRO .MTOUT AREA,ADDR,UNIT,CHRCNT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,3.,<CODE>,<ADDR> ...CM2 <UNIT>,4,,,B ...CM2 <CHRCNT>,5,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTOUT: .Asciz "%SYSMAC-I-Testing .MTOUT" .PSect Active Mov #$MTOUT,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTOU1: .MTOUT #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTOUT*^o400+..MTOU,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 40$ ;yes Call Err1.4 40$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 50$ ;yes Call Err1.5 50$: Call AreaM1 ;set area to -1s MTOU2: .MTOUT #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 60$ ;yes Call Err2.1 ;no 60$: Cmp #.MTOUT*^o400+..MTOUT,(R1)+ ;is the subcode correct? Beq 70$ ;yes Call Err2.2 ;no 70$: Cmp #177777,(R1)+ ;is the address correct? Beq 80$ ;yes Call Err2.3 80$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 90$ ;yes Call Err2.4 90$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 100$ ;yes Call Err2.5 100$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTOU3: .MTOUT ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 110$ ;yes Call Err3.1 ;no 110$: Cmp #.MTOUT*^o400+..MTOUT,(R1)+ ;is the subcode correct? Beq 120$ ;yes Call Err3.2 ;no 120$: Cmp #123456,(R1)+ ;is the address correct? Beq 130$ ;yes Call Err3.3 130$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 140$ ;yes Call Err3.4 140$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 150$ ;yes Call Err3.5 150$: .PSect Data MTOU4: .MTOUT 160$: .PSect Active Cmp #EMT+...AR0,160$-2 ;correct EMT code? Beq 170$ ;yes Call Err4 170$: Call AreaM1 ;set area to -1s MTOU5: .MTOUT #Area,#123456,#12 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 180$ ;yes Call Err5.1 ;no 180$: Cmp #.MTOUT*^o400+..MTOU,(R1)+ ;is the subcode correct? Beq 190$ ;yes Call Err5.2 ;no 190$: Cmp #123456,(R1)+ ;is the address correct? Beq 200$ ;yes Call Err5.3 200$: CmpB #12,(R1)+ ;is the address correct? Beq 210$ ;yes Call Err5.4 210$: CmpB #-1,(R1)+ ;is the chrcnt unchanged? Beq 220$ ;yes Call Err5.5 220$: Call AreaM1 ;set area to -1s MTOU6: .MTOUT #Area,#123456,,#55 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 230$ ;yes Call Err6.1 ;no 230$: Cmp #.MTOUT*^o400+..MTOU,(R1)+ ;is the subcode correct? Beq 240$ ;yes Call Err6.2 ;no 240$: Cmp #123456,(R1)+ ;is the address correct? Beq 250$ ;yes Call Err6.3 250$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 260$ ;yes Call Err6.4 260$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 270$ ;yes Call Err6.5 270$: Call AreaM1 ;set area to -1s MTOU7: .MTOUT #Area,,,#55 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 280$ ;yes Call Err7.1 ;no 280$: Cmp #.MTOUT*^o400+..MTOU,(R1)+ ;is the subcode correct? Beq 290$ ;yes Call Err7.2 ;no 290$: Cmp #177777,(R1)+ ;is the address correct? Beq 300$ ;yes Call Err7.3 300$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 310$ ;yes Call Err7.4 310$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 320$ ;yes Call Err7.5 320$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTOU8: .MTOUT ,#123456,,#55,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 330$ ;yes Call Err8.1 ;no 330$: Cmp #.MTOUT*^o400+..MTOU,(R1)+ ;is the subcode correct? Beq 340$ ;yes Call Err8.2 ;no 340$: Cmp #123456,(R1)+ ;is the address correct? Beq 350$ ;yes Call Err8.3 350$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 360$ ;yes Call Err8.4 360$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 370$ ;yes Call Err8.5 370$: Call AreaM1 ;set area to -1s MTOU9: .MTOUT #Area,#123456,#12,#55 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 380$ ;yes Call Err9.1 ;no 380$: Cmp #.MTOUT*^o400+..MTOU,(R1)+ ;is the subcode correct? Beq 390$ ;yes Call Err9.2 ;no 390$: Cmp #123456,(R1)+ ;is the address correct? Beq 400$ ;yes Call Err9.3 400$: CmpB #12,(R1)+ ;is the address correct? Beq 410$ ;yes Call Err9.4 410$: CmpB #55,(R1)+ ;is the chrcnt set? Beq 420$ ;yes Call Err9.5 420$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTPRNT Print an ASCIZ string on a Multi-Terminal LUN request .MACRO .MTPRN AREA,ADDR,UNIT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,7.,<CODE>,<ADDR> ...CM2 <UNIT>,4,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTPRN: .Asciz "%SYSMAC-I-Testing .MTPRNT" .PSect Active Mov #$MTPRN,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTPR1: .MTPRNT #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTPRN*^o400+..MTPR,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 31$ ;yes Call Err1.4 31$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 32$ ;yes Call Err1.5 32$: Call AreaM1 ;set area to -1s MTPR2: .MTPRNT #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.MTPRN*^o400+..MTPR,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 61$ ;yes Call Err2.4 61$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 62$ ;yes Call Err2.5 62$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTPR3: .MTPRNT ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.MTPRN*^o400+..MTPR,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 91$ ;yes Call Err3.4 91$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 92$ ;yes Call Err3.5 92$: .PSect Data MTPR4: .MTPRNT 100$: .PSect Active Cmp #EMT+375,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call AreaM1 ;set area to -1s MTPR5: .MTPRNT #Area,#123456,#12 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 120$ ;yes Call Err5.1 ;no 120$: Cmp #.MTPRN*^o400+..MTPR,(R1)+ ;is the subcode correct? Beq 130$ ;yes Call Err5.2 ;no 130$: Cmp #123456,(R1)+ ;is the address correct? Beq 140$ ;yes Call Err5.3 140$: CmpB #12,(R1)+ ;is the address correct? Beq 150$ ;yes Call Err5.4 150$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 82$ ;yes Call Err5.5 82$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTPS Move to PS (processor independent) call .MACRO .MTPS ADDR .IF NB <ADDR> CLR -(SP) .ENDC .IF NB <ADDR> MOVB ADDR,(SP) .ENDC MOV @#^o54,-(SP) ADD #^o360,(SP) CALL @(SP)+ .ENDM ;+TEST .Enabl LSB .PSect Text $MTPS: .Asciz "%SYSMAC-I-Testing .MTPS" .PSect Active Mov #$MTPS,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .MTRCTO Reset ^o on a Multi-Terminal LUN request .MACRO .MTRCT AREA,UNIT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,4.,<CODE> ...CM2 <UNIT>,4,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTRCT: .Asciz "%SYSMAC-I-Testing .MTRCTO" .PSect Active Mov #$MTRCT,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTRC1: .MTRCTO #Area,#12 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTRCT*^o400+..MTRC,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Tst (R1)+ ;skip unused area CmpB #12,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s MTRC2: .MTRCTO #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.MTRCT*^o400+..MTRC,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Tst (R1)+ ;skip unused area CmpB #-1,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTRC3: .MTRCTO ,#12,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.MTRCT*^o400+..MTRC,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Tst (R1)+ ;skip unused area CmpB #12,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data MTRC4: .MTRCTO 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTSET Set information on a Multi-Terminal LUN request .MACRO .MTSET AREA,ADDR,UNIT,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,0.,<CODE>,<ADDR> ...CM2 <UNIT>,4,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $MTSET: .Asciz "%SYSMAC-I-Testing .MTSET" .PSect Active Mov #$MTSET,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTSE1: .MTSET #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTSET*^o400+..MTSE,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 31$ ;yes Call Err1.4 31$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 32$ ;yes Call Err1.5 32$: Call AreaM1 ;set area to -1s MTSE2: .MTSET #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.MTSET*^o400+..MTSE,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 61$ ;yes Call Err2.4 61$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 62$ ;yes Call Err2.5 62$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTSE3: .MTSET ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.MTSET*^o400+..MTSE,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: CmpB #-1,(R1)+ ;is the LUN unchanged? Beq 91$ ;yes Call Err3.4 91$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 92$ ;yes Call Err3.5 92$: .PSect Data MTSE4: .MTSET 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call AreaM1 ;set area to -1s MTSE5: .MTSET #Area,#123456,#12 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 120$ ;yes Call Err5.1 ;no 120$: Cmp #.MTSET*^o400+..MTSE,(R1)+ ;is the subcode correct? Beq 130$ ;yes Call Err5.2 ;no 130$: Cmp #123456,(R1)+ ;is the address correct? Beq 140$ ;yes Call Err5.3 140$: CmpB #12,(R1)+ ;is the address correct? Beq 150$ ;yes Call Err5.4 150$: CmpB #-1,(R1)+ ;is the reserved area unchanged? Beq 132$ ;yes Call Err5.5 132$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MTSTAT Get general Multi-Terminal information request .MACRO .MTSTA AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,31.,8.,<CODE>,<ADDR> ...CM2 #0,4,E .ENDM ;+TEST .Enabl LSB .PSect Text $MTSTA: .Asciz "%SYSMAC-I-Testing .MTSTAT" .PSect Active Mov #$MTSTA,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s MTST1: .MTSTAT #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.MTSTA*^o400+..MTST,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Cmp #0,(R1)+ ;is the reserved area cleared? Beq 31$ ;yes Call Err1.4 31$: Call AreaM1 ;set area to -1s MTST2: .MTSTAT #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.MTSTA*^o400+..MTST,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address unchanged? Beq 60$ ;yes Call Err2.3 60$: Cmp #0,(R1)+ ;is the reserved area cleared? Beq 32$ ;yes Call Err1.4 32$: Call AreaM1 ;set area to -1s Mov #Area,R0 MTST3: .MTSTAT ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.MTSTA*^o400+..MTST,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: Cmp #0,(R1)+ ;is the reserved area cleared? Beq 91$ ;yes Call Err1.4 91$: .PSect Data MTST4: .MTSTAT 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .MWAIT Wait for a SDAT/RCVD request to finish request .MACRO .MWAIT MOV #^o4400,R0 EMT ^o374 .ENDM ;+TEST .Enabl LSB .PSect Text $MWAIT: .Asciz "%SYSMAC-I-Testing .MWAIT" .PSect Active Mov #$MWAIT,R0 ;Ident the test(s) Call BegTst ;Assume no errors Mov #Patter,R0 MWAIT1: .MWAIT .=.-2 ;squash EMT Cmp #.MWAIT*^o400,R0 ;Is R0 right? Beq 10$ Call Err1 10$: .PSect Data MWAIT2: .MWAIT .=.-2. 23$: .=.+2. 25$: .PSect Active Cmp #EMT+...R0,23$ ;was the correct EMT generated? Beq 20$ ;Yes Call Err2 20$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .PEEK Get a word from system mapping request .MACRO .PEEK AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,28.,1.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $PEEK: .Asciz "%SYSMAC-I-Testing .PEEK" .PSect Active Mov #$PEEK,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s PEEK1: .PEEK #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.PEEK*^o400+..PEEK,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s PEEK2: .PEEK #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.PEEK*^o400+..PEEK,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 PEEK3: .PEEK ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.PEEK*^o400+..PEEK,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data PEEK4: .PEEK 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .POKE Modify a word in system mapping request .MACRO .POKE AREA,ADDR,VALUE,TYPE=MOV,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...V2=1000. ...V3=3. .IRP x,<MOV,BIC,BIS> .IF IDN <x> <TYPE> ...V2=0 .MEXIT .ENDC ...V3=...V3+2. .ENDR .IIF GT ...V3-7.+...V2 .ERROR;?SYSMAC-E-Invalid T Y P E, expecting MOV/BIC/BIS, found - TYPE; ...CM6 <AREA>,28.,\...V3,<CODE>,<ADDR> ...CM2 <VALUE>,4,E .ENDM ;+TEST .Enabl LSB .PSect Text $POKE: .Asciz "%SYSMAC-I-Testing .POKE" .PSect Active Mov #$POKE,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s POKE1: .POKE #Area,#123456,#101010 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.POKE*^o400+..POKE,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Cmp #101010,(R1)+ ;is the value correct? Beq 40$ ;yes Call Err1.4 40$: Call AreaM1 ;set area to -1s POKE2: .POKE #Area,TYPE=BIC .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 50$ ;yes Call Err2.1 ;no 50$: Cmp #.POKE*^o400+..BICO,(R1)+ ;is the subcode correct? Beq 60$ ;yes Call Err2.2 ;no 60$: Cmp #177777,(R1)+ ;is the address correct? Beq 70$ ;yes Call Err2.3 70$: Cmp #177777,(R1)+ ;is the value correct? Beq 80$ ;yes Call Err2.4 80$: Call AreaM1 ;set area to -1s Mov #Area,R0 POKE3: .POKE ,#123456,CODE=SET,TYPE=BIS .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 90$ ;yes Call Err3.1 ;no 90$: Cmp #.POKE*^o400+..BISO,(R1)+ ;is the subcode correct? Beq 100$ ;yes Call Err3.2 ;no 100$: Cmp #123456,(R1)+ ;is the address correct? Beq 110$ ;yes Call Err3.3 110$: Cmp #-1,(R1)+ ;is the value correct? Beq 120$ ;yes Call Err3.4 120$: Call AreaM1 ;set area to -1s Mov #Area,R0 POKE4: .POKE ,#123456,CODE=SET,TYPE=MOV .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 130$ ;yes Call Err4.1 ;no 130$: Cmp #.POKE*^o400+..POKE,(R1)+ ;is the subcode correct? Beq 140$ ;yes Call Err4.2 ;no 140$: Cmp #123456,(R1)+ ;is the address correct? Beq 150$ ;yes Call Err4.3 150$: Cmp #-1,(R1)+ ;is the value correct? Beq 160$ ;yes Call Err4.4 160$: .PSect Data POKE5: .POKE 170$: .PSect Active Cmp #EMT+...AR0,170$-2 ;correct EMT code? Beq 180$ ;yes Call Err5 180$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .PRINT Print an ASCIZ string on the console request .MACRO .PRINT ADDR .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM5 <ADDR>,351 .ENDM ;+TEST .Enabl LSB .PSect Text $PRINT: .Asciz "%SYSMAC-I-Testing .PRINT" .PSect Active Mov #$PRINT,R0 ;Ident the test Call BegTst Mov #Patter,R0 ;init R0 PRIN1: .PRINT #123456 .=.-2 Cmp #123456,R0 ;R0 set? Beq 10$ ;yes Call Err1 ;no 10$: Mov #123456,R0 ;init R0 PRIN2: .PRINT .=.-2 Cmp #123456,R0 ;R0 set? Beq 20$ ;yes Call Err2 ;no 20$: Mov #123456,R0 ;init R0 PRIN3: .PRINT R0 .=.-2 Cmp #123456,R0 ;R0 set? Beq 30$ ;yes Call Err3 ;no 30$: .PSect Data PRIN4: .PRINT 40$: .PSect Active Cmp #EMT+...PRI,40$-2 ;correct EMT? Beq 50$ ;yes Call Err4 ;no 50$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .PROTECT Protect a vector request .MACRO .PROTE AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,25.,0.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $PROTE: .Asciz "%SYSMAC-I-Testing .PROTECT" .PSect Active Mov #$PROTE,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s PROT1: .PROTE #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.PROTE*^o400+..PROT,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s PROT2: .PROTE #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.PROTE.*^o400+..PROT,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 PROT3: .PROTE ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.PROTE*^o400+..PROT,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data PROT4: .PROTE 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .PURGE Disconnect a channel request .MACRO .PURGE CHAN .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM3 <CHAN>,3. .ENDM ;+TEXT .Enabl LSB ;NOTE: V1 version is not tested .PSect Text $PURGE: .Asciz "%SYSMAC-I-Testing .PURGE" .PSect Active MOV #$PURGE,R0 ;Ident the test(s) Call BegTst ;Assume no errors MOV #PATTER,R0 PURGE1: .PURGE #0 .=.-2 ;squash EMT CMP #.PURGE*^o400+0,R0 ;Is R0 right? BEQ 10$ Call ERR1 10$: MOV #PATTER,R0 PURGE2: .PURGE #1 .=.-2 ;squash EMT CMP #.PURGE*^o400+1,R0 ;Is R0 right? BEQ 20$ Call ERR2 20$: MOV #PATTER,R0 PURGE3: .PURGE #^o377 .=.-2 ;squash EMT CMP #.PURGE*^o400+^o377,R0 ;Is R0 right? BEQ 30$ Call ERR3 30$: MOV #4,R0 PURGE4: .PURGE R0 .=.-2 ;squash EMT CMP #.PURGE*^o400+4,R0 ;Is R0 right? BEQ 40$ Call ERR4 40$: MOV #PATTER,R0 MOV #1,R1 PURGE5: .PURGE R1 .=.-2 ;squash EMT CMP #.PURGE*^o400+1,R0 ;Is R0 right? BEQ 50$ Call ERR5 50$: MOV #PATTER,R0 PURGE6: .PURGE 65$ ;try getting chan from an odd addr .=.-2 ;squash EMT .PSect Data .ODD 65$: .BYTE 2 ;Channel 2 at an odd addr .EVEN .PSect Active CMP #.PURGE*^o400+2.,R0 ;Is R0 right? BEQ 60$ Call ERR6 60$: .PSect Data PURGE7: .PURGE .=.-2. 73$: .=.+2. 75$: .PSect Active CMP #EMT+...R0,73$ ;was the correct EMT generated? BEQ 70$ ;Yes Call ERR7 70$: Call EndTst .DSABL LSB ;-TEST .Page .SbTtl .PVAL Modify a word in the resident monitor request .MACRO .PVAL AREA,OFFSE,VALUE,TYPE=MOV,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...V2=1000. ...V3=2. .IRP x,<MOV,BIC,BIS> .IF IDN <x> <TYPE> ...V2=0 .MEXIT .ENDC ...V3=...V3+2. .ENDR .IIF GT ...V3-6.+...V2 .ERROR;?SYSMAC-E-Invalid T Y P E, expecting MOV/BIC/BIS, found - TYPE; ...CM6 <AREA>,28.,\...V3,<CODE>,<OFFSE> ...CM2 <VALUE>,4,E .ENDM ;+TEST .Enabl LSB .PSect Text $PVAL: .Asciz "%SYSMAC-I-Testing .PVAL" .PSect Active Mov #$PVAL,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .QELDF Define offsets in I/O Queue elements .MACRO .QELDF LIST,E=<=:> .IIF NDF MMG$T,MMG$T=1 .IIF NE MMG$T,MMG$T=1 .IIF IDN <LIST>,<YES> .LIST Q.LINK E 0 Q.CSW E 2. Q.BLKN E 4. Q.FUNC E 6. Q.2UNI E Q.FUNC Q.TYPE E Q.FUNC Q.FMSK E ^o17 Q.2MSK E ^o160 Q.TMSK E ^o200 Q.JNUM E 7. Q.UNIT E Q.JNUM Q.UMSK E ^o3400 Q.JMSK E ^o74000 Q.BUFF E ^o10 Q.WCNT E ^o12 Q.COMP E ^o14 .IIF IDN <LIST>,<YES> .NLIST .IRP X,<LINK,CSW,BLKN,FUNC,2UNI,TYPE,JNUM,UNIT,BUFF,WCNT,COMP> .IIF IDN <LIST>,<YES> .LIST Q$'X E Q.'X-^o4 .IIF IDN <LIST>,<YES> .NLIST .ENDR .IF EQ MMG$T .IIF IDN <LIST>,<YES> .LIST Q.ELGH E ^o16 .IIF IDN <LIST>,<YES> .NLIST .IFF .IIF IDN <LIST>,<YES> .LIST Q.PAR E ^o16 Q.MEM E ^o20 .IIF IDN <LIST>,<YES> .NLIST .IRP X,<PAR,MEM> .IIF IDN <LIST>,<YES> .LIST Q$'X E Q.'X-^o4 .IIF IDN <LIST>,<YES> .NLIST .ENDR .IIF IDN <LIST>,<YES> .LIST Q.ELGH E ^o24 .IIF IDN <LIST>,<YES> .NLIST .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $QELDF: .Asciz "%SYSMAC-I-Testing .QELDF" .PSect Active Mov #$QELDF,R0 ;Ident the test Call BegTst Call TemTst ;-TEST .Page .SbTtl .QSET Add elements to the available queue request .MACRO .QSET ADDR,LEN .IF NDF ...V1 .MCALL .MACS .MACS .ENDC MOV ADDR,-(SP) ...CM5 <LEN>,353 .ENDM ;+TEST .Enabl LSB .PSect Text $QSET: .Asciz "%SYSMAC-I-Testing .QSET" .PSect Active Mov #$QSET,R0 ;Ident the test Call BegTst Mov SP,R5 ;save stack pointer Mov #Patter,R0 ;init R0 QSET1: .QSET #111111,#123456 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp SP,R5 ;is stack correct? Beq 30$ ;yes Call Err1.3 ;no 30$: Mov SP,R5 ;save stack pointer Mov #123456,R0 ;init R0 QSET2: .QSET #111111,R0 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp SP,R5 ;is stack correct? Beq 60$ ;yes Call Err2.3 ;no 60$: Mov SP,R5 ;save stack pointer Mov #123456,R0 ;init R0 QSET3: .QSET #111111 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #111111,(SP)+ ;is top of stack correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp SP,R5 ;is stack correct? Beq 90$ ;yes Call Err3.3 ;no 90$: .PSect Data QSET4: .QSET #111111 100$: .PSect Active Cmp #EMT+...QSE,100$-2 ;correct EMT? Beq 110$ ;yes Call Err4 ;no 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .RCTRLO Reset ^o status on the console request .MACRO .RCTRL EMT ^o355 .ENDM ;+TEST .Enabl LSB .PSect Text $RCTRL: .Asciz "%SYSMAC-I-Testing .RCTRL" .PSect Active Mov #$RCTRL,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data RCTRL1: .RCTRL .=.-2. 13$: .=.+2. 15$: .PSect Active CMP #EMT+...RCT,13$ ;was the correct EMT generated? BEQ 10$ ;Yes Call ERR1 10$: Call EndTst .DSABL LSB ;-TEST .Page .SbTtl .RCVD Queue a message receive request .MACRO .RCVD AREA,BUF,WCNT,CRTN=#1,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM4 <AREA>,<BUF>,<WCNT>,<CRTN>,22,<CODE>,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $RCVD: .Asciz "%SYSMAC-I-Testing .RCVD" .PSect Active Mov #$RCVD,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVD1: .RCVD .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVD2: .RCVD ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVD3: .RCVD ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.RCVD,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVD4: .RCVD #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.RCVD,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVD5: .RCVD #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVD6: .RCVD #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.RCVD,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVD7: .RCVD #Area,#010000,#020000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.RCVD,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data RCVD8: .RCVD 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVD9: .RCVD #Area,#010000,#020000,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.RCVD,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data RCVDA: .RCVD BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .RCVDC Queue a message receive, specify a completion routine request .MACRO .RCVDC AREA,BUF,WCNT,CRTN,CODE,BMODE,CMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM4 <AREA>,<BUF>,<WCNT>,<CRTN>,22,<CODE>,<BMODE>,<CMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $RCVDC: .Asciz "%SYSMAC-I-Testing .RCVDC" .PSect Active Mov #$RCVDC,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVDC1: .RCVDC .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVDC2: .RCVDC ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVDC3: .RCVDC ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.RCVDC,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDC4: .RCVDC #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.RCVDC,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDC5: .RCVDC #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDC6: .RCVDC #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.RCVDC,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDC7: .RCVDC #Area,#010000,#020000,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.RCVDC,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #030000,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data RCVDC8: .RCVDC 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDC9: .RCVDC #Area,#010000,#020000,#030000,BMODE=UI,CMODE=S .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.RCVDC,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #030000+1,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data RCVDCA: .RCVDC ,BMODE=SI,CMODE=S 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .RCVDW Wait for a message request .MACRO .RCVDW AREA,BUF,WCNT,CRTN=#0,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM4 <AREA>,<BUF>,<WCNT>,<CRTN>,22,<CODE>,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $RCVDW: .Asciz "%SYSMAC-I-Testing .RCVDW" .PSect Active Mov #$RCVDW,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVDW1: .RCVDW .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVDW2: .RCVDW ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area RCVDW3: .RCVDW ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.RCVDW,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDW4: .RCVDW #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.RCVDW,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDW5: .RCVDW #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDW6: .RCVDW #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.RCVDW,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDW7: .RCVDW #Area,#010000,#020000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.RCVDW,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data RCVDW8: .RCVDW 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 RCVDW9: .RCVDW #Area,#010000,#020000,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.RCVDW,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data RCVDWA: .RCVDW ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .RDBBK Generate a region definition block .MACRO .RDBBK RGSIZ,RGSTA=0,NAME,BASE=0 .MCALL .RDBDF .RDBDF .WORD .WORD RGSIZ ...V2=0 .IIF NE BASE ...V2=RS.BAS .WORD RGSTA!...V2 .WORD 0,0 .WORD BASE .=.-6. ...V2=. .RAD50 \NAME\ .=...V2+6. .ENDM ;+TEST .Enabl LSB .PSect Text $RDBBK: .Asciz "%SYSMAC-I-Testing .RDBBK" .PSect Active Mov #$RDBBK,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .RDBDF Define bit patterns and offsets for a RDB .MACRO .RDBDF LIST,E=<=:> .IIF IDN <LIST>,<YES> .LIST R.GID E 0 R.GSIZ E 2. R.GSTS E 4. R.GLLN E 6. R.GNAM E 6. R.GBAS E 10. R.GLGH E 12. RS.CRR E ^o100000 RS.UNM E ^o40000 RS.NAL E ^o20000 RS.NEW E ^o10000 RS.GBL E ^o4000 RS.CGR E ^o2000 RS.AGE E ^o1000 RS.EGR E ^o400 RS.EXI E ^o200 RS.CAC E ^o100 RS.BAS E ^o40 RS.NSM E ^o20 RS.DSP E ^o2 RS.PVT E ^o1 .IIF IDN <LIST>,<YES> .NLIST .ENDM ;+TEST .Enabl LSB .PSect Text $RDBDF: .Asciz "%SYSMAC-I-Testing .RDBDF" .PSect Active Mov #$RDBDF,R0 ;Ident the test Call BegTst Call TemTst ;-TEST .Page .SbTtl .READ Queue a read request .MACRO .READ AREA,CHAN,BUF,WCNT,BLK,CRTN=#1,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM7 <AREA>,<CHAN>,<BUF>,<WCNT>,<BLK>,<CRTN>,8,<CODE>,200,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $READ: .Asciz "%SYSMAC-I-Testing .READ" .PSect Active Mov #$READ,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area READ1: .READ .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area READ2: .READ ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area READ3: .READ ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.READ,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READ4: .READ #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.READ,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READ5: .READ #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READ6: .READ #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.READ,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READ7: .READ #Area,#0,#010000,#020000,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.READ,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #030000,(R1)+ ;is BLK set? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data READ8: .READ 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READ9: .READ #Area,#0,#010000,#020000,#0,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.READ,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #0,(R1)+ ;is BLK set? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data READA: .READ ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .READC Queue a read request, specifying a completion routine .MACRO .READC AREA,CHAN,BUF,WCNT,CRTN,BLK,CODE,BMODE,CMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM7 <AREA>,<CHAN>,<BUF>,<WCNT>,<BLK>,<CRTN>,8,<CODE>,200,<BMODE>,<CMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $READC: .Asciz "%SYSMAC-I-Testing .READC" .PSect Active Mov #$READC,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area READC1: .READC .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area READC2: .READC ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area READC3: .READC ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.READC,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READC4: .READC #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.READC,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READC5: .READC #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READC6: .READC #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.READC,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READC7: .READC #Area,#0,#010000,#020000,#123456,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.READC,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #030000,(R1)+ ;is BLK set? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #123456,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data READC8: .READC 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READC9: .READC #Area,#0,#010000,#020000,#123456,#0,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.READC,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #0,(R1)+ ;is BLK set? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #123456,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data READCA: .READC ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst ;-TEST .Page .SbTtl .READW Wait for a read request .MACRO .READW AREA,CHAN,BUF,WCNT,BLK,CRTN=#0,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM7 <AREA>,<CHAN>,<BUF>,<WCNT>,<BLK>,<CRTN>,8,<CODE>,200,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $READW: .Asciz "%SYSMAC-I-Testing .READW" .PSect Active Mov #$READW,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area READW1: .READW .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area READW2: .READW ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area READW3: .READW ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.READW,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READW4: .READW #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.READW,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READW5: .READW #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READW6: .READW #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.READW,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READW7: .READW #Area,#0,#010000,#020000,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.READW,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #030000,(R1)+ ;is BLK set? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data READW8: .READW 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 READW9: .READW #Area,#0,#010000,#020000,#0,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.READW,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #0,(R1)+ ;is BLK set? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data READWA: .READW ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .REGDEF Ancient compatibility macro - defined reg symbols .MACRO .REGDEF .ENDM ;+TEST .Enabl LSB .PSect Text $REGDE: .Asciz "%SYSMAC-I-Testing .REGDEF" .PSect Active Mov #$REGDE,R0 ;Ident the test Call BegTst Call EndTst ;-TEST .Page .SbTtl .RELEASE Release a handler from memory request .MACRO .RELEA DNAM .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM5 <DNAM> ...CM0 ,343 .ENDM ;+TEST .Enabl LSB .PSect Text $RELEA: .Asciz "%SYSMAC-I-Testing .RELEASE" .PSect Active Mov #$RELEA,R0 ;Ident the test Call BegTst Mov SP,R5 ;save stack pointer Mov #Patter,R0 ;init R0 RELE1: .RELEASE #123456 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #0,(SP)+ ;is top of stack correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp SP,R5 ;is stack correct? Beq 30$ ;yes Call Err1.3 ;no 30$: Mov SP,R5 ;save stack pointer Mov #123456,R0 ;init R0 RELE2: .RELEASE R0 .=.-2 ;crush EMT Cmp #123456,R0 ;is R0 set? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #0,(SP)+ ;is top of stack correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp SP,R5 ;is stack correct? Beq 60$ ;yes Call Err2.3 ;no 60$: .PSect Data RELE3: .RELEASE 70$: .PSect Active Cmp #EMT+...REL,70$-2 ;correct EMT? Beq 80$ ;yes Call Err3 ;no 80$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .RENAME Rename a file request .MACRO .RENAM AREA,CHAN,DBLK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF NE ...V1-1 ...CM1 <AREA>,4,<CHAN>,<CODE>,<DBLK>,E .MEXIT .ENDC ...CM5 <CHAN>,<100+AREA> .ENDM ;+TEST .Enabl LSB .PSect Text $RENAM: .Asciz "%SYSMAC-I-Testing .RENAME" .PSect Active Mov #$RENAM,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 RENA1: .RENAME #Area,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.RENAM,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is Addr set? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 Mov #Area,R0 RENA2: .RENAME ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 50$ ;yes Call Err2.1 ;no 50$: CmpB #123,(R1)+ ;is channel set? Beq 60$ ;yes Call Err2.2 ;no 60$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 70$ ;yes Call Err2.3 ;no 70$: Cmp #123456,(R1)+ ;is Addr set? Beq 80$ ;yes Call Err2.4 ;no 80$: Call AreaM1 Mov #Area,R0 RENA3: .RENAME ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 90$ ;yes Call Err3.1 ;no 90$: CmpB #123,(R1)+ ;is channel set? Beq 100$ ;yes Call Err3.2 ;no 100$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 110$ ;yes Call Err3.3 ;no 110$: Cmp #123456,(R1)+ ;is Addr set? Beq 120$ ;yes Call Err3.4 ;no 120$: .PSect Data RENA4: .RENAME CODE=NOSET 130$: .PSect Active Cmp #EMT+...AR0,130$-2 ;correct EMT? Beq 140$ ;yes Call Err4 ;no 140$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .REOPEN Reopen a channel that was SAVESTATUSed request .MACRO .REOPE AREA,CHAN,CBLK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF NE ...V1-1 ...CM1 <AREA>,6,<CHAN>,<CODE>,<CBLK>,E .MEXIT .ENDC ...CM5 <CHAN>,<140+AREA> .ENDM .PAGE ;+TEST .Enabl LSB .PSect Text $REOPE: .Asciz "%SYSMAC-I-Testing .REOPEN" .PSect Active Mov #$REOPE,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 REOP1: .REOPEN #Area,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.REOPE,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is Addr set? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 Mov #Area,R0 REOP2: .REOPEN ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 50$ ;yes Call Err2.1 ;no 50$: CmpB #123,(R1)+ ;is channel set? Beq 60$ ;yes Call Err2.2 ;no 60$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 70$ ;yes Call Err2.3 ;no 70$: Cmp #123456,(R1)+ ;is Addr set? Beq 80$ ;yes Call Err2.4 ;no 80$: Call AreaM1 Mov #Area,R0 REOP3: .REOPEN ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 90$ ;yes Call Err3.1 ;no 90$: CmpB #123,(R1)+ ;is channel set? Beq 100$ ;yes Call Err3.2 ;no 100$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 110$ ;yes Call Err3.3 ;no 110$: Cmp #123456,(R1)+ ;is Addr set? Beq 120$ ;yes Call Err3.4 ;no 120$: .PSect Data REOP4: .REOPEN CODE=NOSET 130$: .PSect Active Cmp #EMT+...AR0,130$-2 ;correct EMT? Beq 140$ ;yes Call Err4 ;no 140$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .RSUM Resume a suspended job request .MACRO .RSUM MOV #^o1000,R0 EMT ^o374 .ENDM ;+TEST .Enabl LSB .PSect Text $RSUM: .Asciz "%SYSMAC-I-Testing .RSUM" .PSect Active Mov #$RSUM,R0 ;Ident the test(s) Call BegTst ;Assume no errors Mov #Patter,R0 RSUM1: .RSUM .=.-2 ;squash EMT Cmp #.RSUM*^o400,R0 ;Is R0 right? Beq 10$ Call Err1 10$: .PSect Data RSUM2: .RSUM .=.-2. 23$: .=.+2. 25$: .PSect Active CMP #EMT+...R0,23$ ;was the correct EMT generated? BEQ 20$ ;Yes Call ERR2 20$: Call EndTst .DSABL LSB ;-TEST .Page .SbTtl .SAVESTATUS Close a channel and save channel status request .MACRO .SAVES AREA,CHAN,CBLK,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF NE ...V1-1 ...CM1 <AREA>,5,<CHAN>,<CODE>,<CBLK>,E .MEXIT .ENDC ...CM5 <CHAN>,<120+AREA> .ENDM ;+TEST .Enabl LSB .PSect Text $SAVES: .Asciz "%SYSMAC-I-Testing .SAVESTATUS" .PSect Active Mov #$SAVES,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 SAVE1: .SAVEST #Area,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.SAVES,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is Addr set? Beq 40$ ;yes Call Err1.4 ;no 40$: Call AreaM1 Mov #Area,R0 SAVE2: .SAVEST ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 50$ ;yes Call Err2.1 ;no 50$: CmpB #123,(R1)+ ;is channel set? Beq 60$ ;yes Call Err2.2 ;no 60$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 70$ ;yes Call Err2.3 ;no 70$: Cmp #123456,(R1)+ ;is Addr set? Beq 80$ ;yes Call Err2.4 ;no 80$: Call AreaM1 Mov #Area,R0 SAVE3: .SAVEST ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 90$ ;yes Call Err3.1 ;no 90$: CmpB #123,(R1)+ ;is channel set? Beq 100$ ;yes Call Err3.2 ;no 100$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 110$ ;yes Call Err3.3 ;no 110$: Cmp #123456,(R1)+ ;is Addr set? Beq 120$ ;yes Call Err3.4 ;no 120$: .PSect Data SAVE4: .SAVEST CODE=NOSET 130$: .PSect Active Cmp #EMT+...AR0,130$-2 ;correct EMT? Beq 140$ ;yes Call Err4 ;no 140$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SCCA Set ^C blocking and flag word request .MACRO .SCCA AREA,ADDR,TYPE,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF IDN <TYPE>,<GLOBAL> ...CM6 <AREA>,29.,1.,<CODE>,<ADDR>,E .IFF ...CM6 <AREA>,29.,0.,<CODE>,<ADDR>,E .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $SCCA: .Asciz "%SYSMAC-I-Testing .SCCA" .PSect Active Mov #$SCCA,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s SCCA1: .SCCA #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.SCCA*^o400,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s SCCA2: .SCCA #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.SCCA*^o400+..LSCC,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 SCCA3: .SCCA ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.SCCA*^o400+..LSCC,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data SCCA4: .SCCA 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call AreaM1 ;set area to -1s SCCA5: .SCCA #Area,#123456,TYPE=GLOBAL .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 120$ ;yes Call Err5.1 ;no 120$: Cmp #.SCCA*^o400+..GSCC,(R1)+ ;is the subcode correct? Beq 130$ ;yes Call Err5.2 ;no 130$: Cmp #123456,(R1)+ ;is the address correct? Beq 140$ ;yes Call Err5.3 140$: Call AreaM1 ;set area to -1s SCCA6: .SCCA #Area,TYPE=GLOBAL .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 150$ ;yes Call Err6.1 ;no 150$: Cmp #.SCCA*^o400+..GSCC,(R1)+ ;is the subcode correct? Beq 160$ ;yes Call Err6.2 ;no 160$: Cmp #177777,(R1)+ ;is the address correct? Beq 170$ ;yes Call Err6.3 170$: Call AreaM1 ;set area to -1s Mov #Area,R0 SCCA7: .SCCA ,#123456,CODE=SET,TYPE=GLOBAL .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 180$ ;yes Call Err7.1 ;no 180$: Cmp #.SCCA*^o400+..GSCC,(R1)+ ;is the subcode correct? Beq 190$ ;yes Call Err7.2 ;no 190$: Cmp #123456,(R1)+ ;is the address correct? Beq 200$ ;yes Call Err7.3 200$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SDAT Queue a message send request .MACRO .SDAT AREA,BUF,WCNT,CRTN=#1,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM4 <AREA>,<BUF>,<WCNT>,<CRTN>,21,<CODE>,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $SDAT: .Asciz "%SYSMAC-I-Testing .SDAT" .PSect Active Mov #$SDAT,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area SDAT1: .SDAT .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area SDAT2: .SDAT ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area SDAT3: .SDAT ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.SDAT,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDAT4: .SDAT #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.SDAT,(R1)+ ;is IC set? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDAT5: .SDAT #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDAT6: .SDAT #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.SDAT,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDAT7: .SDAT #Area,#010000,#020000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.SDAT,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data SDAT8: .SDAT 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDAT9: .SDAT #Area,#010000,#020000,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.SDAT,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data SDATA: .SDAT BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SDATC Queue a message send, specifying a completion routine request .MACRO .SDATC AREA,BUF,WCNT,CRTN,CODE,BMODE,CMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM4 <AREA>,<BUF>,<WCNT>,<CRTN>,21,<CODE>,<BMODE>,<CMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $SDATC: .Asciz "%SYSMAC-I-Testing .SDATC" .PSect Active Mov #$SDATC,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area SDATC1: .SDATC .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area SDATC2: .SDATC ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area SDATC3: .SDATC ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #.SDATC,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATC4: .SDATC #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.SDATC,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATC5: .SDATC #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATC6: .SDATC #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.SDATC,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATC7: .SDATC #Area,#010000,#020000,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.SDATC,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #030000,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data SDATC8: .SDATC 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATC9: .SDATC #Area,#010000,#020000,#030000,BMODE=UI,CMODE=S .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.SDATC,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 590$ ;yes Call Err9.7 ;no 590$: Cmp #030000+1,(R1)+ ;is CRTN set? Beq 580$ ;yes Call Err9.8 ;no 580$: .PSect Data SDATCA: .SDATC ,BMODE=SI,CMODE=S 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SDATW Send a message, wait for for completion request .MACRO .SDATW AREA,BUF,WCNT,CRTN=#0,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM4 <AREA>,<BUF>,<WCNT>,<CRTN>,21,<CODE>,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $SDATW: .Asciz "%SYSMAC-I-Testing .SDATW" .PSect Active Mov #$SDATW,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area SDATW1: .SDATW .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area SDATW2: .SDATW ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.3 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.4 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.5 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.6 ;no 130$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.7 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area SDATW3: .SDATW ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err3.1 ;no 150$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 160$ ;yes Call Err3.2 ;no 160$: CmpB #21.,(R1)+ ;is IC set? Beq 170$ ;yes Call Err3.3 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err3.4 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err3.5 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err3.6 ;no 200$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err3.7 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATW4: .SDATW #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #21.,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATW5: .SDATW #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.3 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.4 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.5 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.6 ;no 340$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.7 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATW6: .SDATW #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #0,(R1)+ ;is CHAN cleared? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #21.,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.3 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.4 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.5 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.6 ;no 410$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.7 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATW7: .SDATW #Area,#010000,#020000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #21.,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.3 ;no 450$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 460$ ;yes Call Err7.4 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.5 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.6 ;no 480$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.7 ;no 490$: .PSect Data SDATW8: .SDATW 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 SDATW9: .SDATW #Area,#010000,#020000,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.SDATW,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #-1,(R1)+ ;is BLK skipped? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data SDATWA: .SDATW ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SDTTM Set system date and/or time request .MACRO .SDTTM AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,32.,0.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $SDTTM: .Asciz "%SYSMAC-I-Testing .SDTTM" .PSect Active Mov #$SDTTM,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s SDTT1: .SDTTM #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.SDTTM*^o400+0,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s SDTT2: .SDTTM #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.SDTTM*^o400+0,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 SDTT3: .SDTTM ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.SDTTM*^o400+0,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data SDTT4: .SDTTM 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SERR Select soft error handling request .MACRO .SERR MOV #^o2000,R0 EMT ^o374 .ENDM ;+TEST .Enabl LSB .PSect Text $SERR: .Asciz "%SYSMAC-I-Testing .SERR" .PSect Active Mov #$SERR,R0 ;Ident the test(s) Call BegTst ;Assume no errors Mov #Patter,R0 SERR1: .SERR .=.-2 ;squash EMT Cmp #.SERR*^o400,R0 ;Is R0 right? Beq 10$ Call Err1 10$: .PSect Data SERR2: .SERR .=.-2. 23$: .=.+2. 25$: .PSect Active Cmp #EMT+...R0,23$ ;was the correct EMT generated? Beq 20$ ;Yes Call Err2 20$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SETTOP Ask for memory request .MACRO .SETTO ADDR .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM5 <ADDR>,354 .ENDM ;+TEST .Enabl LSB .PSect Text $SETTO: .Asciz "%SYSMAC-I-Testing .SETTOP" .PSect Active Mov #$SETTO,R0 ;Ident the test Call BegTst Mov #Patter,R0 ;init R0 SETT1: .SETTOP #123456 .=.-2 Cmp #123456,R0 ;R0 set? Beq 10$ ;yes Call Err1 ;no 10$: Mov #123456,R0 ;init R0 SETT2: .SETTOP .=.-2 Cmp #123456,R0 ;R0 set? Beq 20$ ;yes Call Err2 ;no 20$: Mov #123456,R0 ;init R0 SETT3: .SETTOP R0 .=.-2 Cmp #123456,R0 ;R0 set? Beq 30$ ;yes Call Err3 ;no 30$: .PSect Data SETT4: .SETTOP 40$: .PSect Active Cmp #EMT+...SET,40$-2 ;correct EMT? Beq 50$ ;yes Call Err4 ;no 50$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SFDAT Set file date request .MACRO .SFDAT AREA,CHAN,DBLK,DATE=#0,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 <AREA>,34,<CHAN>,<CODE>,<DBLK> ...CM2 <DATE>,4,E .ENDM ;+TEST .Enabl LSB .PSect Text $SFDAT: .Asciz "%SYSMAC-I-Testing .SFDAT" .PSect Active Mov #$SFDAT,R0 ;Ident the test Call BegTst Call AreaM1 Mov #Patter,R0 SFDA1: .SFDAT #Area,#123,#123456,#1 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #123,(R1)+ ;is channel set? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #.SFDAT,(R1)+ ;is subcode set? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #123456,(R1)+ ;is DBLK set? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #1,(R1)+ ;is DATE set? Beq 50$ ;yes Call Err1.5 ;no 50$: Call AreaM1 Mov #Area,R0 SFDA2: .SFDAT ,#123,#123456 .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 60$ ;yes Call Err2.1 ;no 60$: CmpB #123,(R1)+ ;is channel set? Beq 70$ ;yes Call Err2.2 ;no 70$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 80$ ;yes Call Err2.3 ;no 80$: Cmp #123456,(R1)+ ;is DBLK set? Beq 90$ ;yes Call Err2.4 ;no 90$: Cmp #0,(R1)+ ;is DATE defaulted? Beq 100$ ;yes Call Err2.5 ;no 100$: Call AreaM1 Mov #Area,R0 SFDA3: .SFDAT ,#123,#123456,CODE=NOSET .=.-2 Mov #Area,R1 ;point to argument area Cmp R0,R1 ;R0 correct? Beq 110$ ;yes Call Err3.1 ;no 110$: CmpB #123,(R1)+ ;is channel set? Beq 120$ ;yes Call Err3.2 ;no 120$: CmpB #377,(R1)+ ;is subcode unchanged? Beq 130$ ;yes Call Err3.3 ;no 130$: Cmp #123456,(R1)+ ;is DBLK set? Beq 140$ ;yes Call Err3.4 ;no 140$: Cmp #0,(R1)+ ;is DATE defaulted? Beq 150$ ;yes Call Err3.5 ;no 150$: .PSect Data SFDA4: .SFDAT CODE=NOSET 160$: .PSect Active Cmp #EMT+...AR0,160$-2 ;correct EMT? Beq 170$ ;yes Call Err4 ;no 170$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SFINFO Set file entry request .MACRO .SFINF AREA,CHAN,DBLK,VALUE,TYPE=GET,OFFSE,UCODE,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 <AREA>,36,<CHAN>,<CODE>,<DBLK> ...CM2 <VALUE>,4 ...V2=1000. ...V3=0 .IRP x,<$GET,$BIC,$BIS,$MOV,$USER> .IF IDN <x> <$'TYPE> ...V2=0 .MEXIT .ENDC ...V3=...V3+1 .ENDR .IIF GT ...V3-4.+...V2 .ERROR;?SYSMAC-E-Invalid T Y P E, expecting GET/MOV/BIC/BIS/USER, found - TYPE; .IF EQ ...V3-4. ...CM2 <UCODE>,6,,,B .IFF ...CM2 #...V3,6,,,B .IIF NB <UCODE> .ERROR ;?SYSMAC-W-Value specified for U C O D E, but T Y P E=TYPE; .ENDC ...CM2 <OFFSE>,7,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $SFINF: .Asciz "%SYSMAC-I-Testing .SFINF" .PSect Active Mov #$SFINF,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .SFPA Set FP exception address request .MACRO .SFPA AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,24.,0.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $SFPA: .Asciz "%SYSMAC-I-Testing .SFPA" .PSect Active Mov #$SFPA,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s SFPA1: .SFPA #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.SFPA*^o400+0,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s SFPA2: .SFPA #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.SFPA*^o400+0,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 SFPA3: .SFPA ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.SFPA*^o400+0,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data SFPA4: .SFPA 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SFSTAT Set file entry status word request .MACRO .SFSTA AREA,CHAN,DBLK,VALUE,TYPE=GET,UCODE,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 <AREA>,36,<CHAN>,<CODE>,<DBLK> ...CM2 <VALUE>,4 ...V2=1000. ...V3=0 .IRP x,<$GET,$BIC,$BIS,$MOV,$USER> .IF IDN <x> <$'TYPE> ...V2=0 .MEXIT .ENDC ...V3=...V3+1 .ENDR .IIF GT ...V3-4.+...V2 .ERROR;?SYSMAC-E-Invalid T Y P E, expecting GET/MOV/BIC/BIS/USER, found - TYPE; .IF EQ ...V3-4. ...CM2 <UCODE>,6,,,B .IFF ...CM2 #...V3,6,,,B .IIF NB <UCODE> .ERROR ;?SYSMAC-W-Value specified for U C O D E, but T Y P E=TYPE; .ENDC ...CM2 <#0>,7,E,,B .ENDM ;+TEST .Enabl LSB .PSect Text $SFSTA: .Asciz "%SYSMAC-I-Testing .SFSTA" .PSect Active Mov #$SFSTA,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl SOB Provide compatibility for processors w/o SOB instruction .MACRO SOB R,DST DEC R BNE DST .ENDM ;+TEST .Enabl LSB .PSect Text $SOB: .Asciz "%SYSMAC-I-Testing .SOB" .PSect Active Mov #$SOB,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .SPCPS Set PC/PS derail from a completion routine request .MACRO .SPCPS AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,33.,0.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $SPCPS: .Asciz "%SYSMAC-I-Testing .SPCPS" .PSect Active Mov #$SPCPS,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s SPCP1: .SPCPS #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.SPCPS*^o400+0,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s SPCP2: .SPCPS #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.SPCPS*^o400+0,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 SPCP3: .SPCPS ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.SPCPS*^o400+0,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data SPCP4: .SPCPS 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SPFUN Issue a special device function request .MACRO .SPFUN AREA,CHAN,FUNC,BUF,WCNT,BLK,CRTN=#0,CODE,BMODE,CMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM1 <AREA>,26,<CHAN>,<CODE>,<BLK> ...CM2 <BUF>,4 ...CM2 <WCNT>,6 ...CMB <BMODE>,<CMODE>,<CRTN>,<FUNC>,S,<CODE> .ENDM ;+TEST .Enabl LSB .PSect Text $SPFUN: .Asciz "%SYSMAC-I-Testing .SPFUN" .PSect Active Mov #$SPFUN,R0 ;Ident the test Call BegTst Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Area,R0 ;point to area SPFUN1: .SPFUN .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: CmpB #-2,(R1)+ ;is the marker unchanged? Beq 70$ ;yes Call Err1.7 ;no 70$: CmpB #-1,(R1)+ ;is FUNC unchanged? Beq 80$ ;yes Call Err1.8 ;no 80$: Cmp #..WTIO,(R1)+ ;is CRTN set to wait? Beq 90$ ;yes Call Err1.9 ;no 90$: Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Area,R0 ;point to area SPFUN2: .SPFUN ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 100$ ;yes Call Err2.1 ;no 100$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 110$ ;yes Call Err2.2 ;no 110$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 120$ ;yes Call Err2.3 ;no 120$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 130$ ;yes Call Err2.4 ;no 130$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 140$ ;yes Call Err2.5 ;no 140$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 150$ ;yes Call Err2.6 ;no 150$: CmpB #-2,(R1)+ ;is the marker unchanged? Beq 160$ ;yes Call Err2.7 ;no 160$: CmpB #-1,(R1)+ ;is FUNC unchanged? Beq 170$ ;yes Call Err2.8 ;no 170$: Cmp #..WTIO,(R1)+ ;is CRTN unchanged? Beq 180$ ;yes Call Err2.9 ;no 180$: Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Area,R0 ;point to area SPFUN3: .SPFUN ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 190$ ;yes Call Err3.1 ;no 190$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 200$ ;yes Call Err3.2 ;no 200$: CmpB #.SPFUN,(R1)+ ;is IC set? Beq 210$ ;yes Call Err3.3 ;no 210$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 220$ ;yes Call Err3.4 ;no 220$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 230$ ;yes Call Err3.5 ;no 230$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 240$ ;yes Call Err3.6 ;no 240$: CmpB #-2,(R1)+ ;is the marker set? Beq 250$ ;yes Call Err3.7 ;no 250$: CmpB #-1,(R1)+ ;is FUNC unchanged? Beq 260$ ;yes Call Err3.8 ;no 260$: Cmp #..WTIO,(R1)+ ;is CRTN unchanged? Beq 270$ ;yes Call Err3.9 ;no 270$: Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Patter,R0 ;init R0 SPFUN4: .SPFUN #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 280$ ;yes Call Err4.1 ;no 280$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 290$ ;yes Call Err4.2 ;no 290$: CmpB #.SPFUN,(R1)+ ;is IC unchanged? Beq 300$ ;yes Call Err4.3 ;no 300$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 310$ ;yes Call Err4.4 ;no 310$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 320$ ;yes Call Err4.5 ;no 320$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 330$ ;yes Call Err4.6 ;no 330$: CmpB #-2,(R1)+ ;is the marker set? Beq 340$ ;yes Call Err4.7 ;no 340$: CmpB #-1,(R1)+ ;is FUNC unchanged? Beq 350$ ;yes Call Err4.8 ;no 350$: Cmp #..WTIO,(R1)+ ;is CRTN unchanged? Beq 360$ ;yes Call Err4.9 ;no 360$: Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Patter,R0 ;init R0 SPFUN5: .SPFUN #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 370$ ;yes Call Err5.1 ;no 370$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 380$ ;yes Call Err5.2 ;no 380$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 390$ ;yes Call Err5.3 ;no 390$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 400$ ;yes Call Err5.4 ;no 400$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 410$ ;yes Call Err5.5 ;no 410$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 420$ ;yes Call Err5.6 ;no 420$: CmpB #-2,(R1)+ ;is the marker set? Beq 430$ ;yes Call Err5.7 ;no 430$: CmpB #-1,(R1)+ ;is FUNC unchanged? Beq 440$ ;yes Call Err5.8 ;no 440$: Cmp #..WTIO,(R1)+ ;is CRTN unchanged? Beq 450$ ;yes Call Err5.9 ;no 450$: Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Patter,R0 ;init R0 SPFUN6: .SPFUN #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 460$ ;yes Call Err6.1 ;no 460$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 470$ ;yes Call Err6.2 ;no 470$: CmpB #.SPFUN,(R1)+ ;is IC set? Beq 480$ ;yes Call Err6.3 ;no 480$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 490$ ;yes Call Err6.4 ;no 490$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 500$ ;yes Call Err6.5 ;no 500$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 510$ ;yes Call Err6.6 ;no 510$: CmpB #-2,(R1)+ ;is the marker unchanged? Beq 520$ ;yes Call Err6.7 ;no 520$: CmpB #-1,(R1)+ ;is FUNC unchanged? Beq 530$ ;yes Call Err6.8 ;no 530$: Cmp #..WTIO,(R1)+ ;is CRTN set to wait? Beq 540$ ;yes Call Err6.9 ;no 540$: Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Patter,R0 ;init R0 SPFUN7: .SPFUN #Area,#0,#202,#010000,#020000,#030000,#123456 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 550$ ;yes Call Err7.1 ;no 550$: CmpB #0,(R1)+ ;is CHAN set? Beq 560$ ;yes Call Err7.2 ;no 560$: CmpB #.SPFUN,(R1)+ ;is IC set? Beq 570$ ;yes Call Err7.3 ;no 570$: Cmp #030000,(R1)+ ;is BLK set? Beq 580$ ;yes Call Err7.4 ;no 580$: Cmp #010000,(R1)+ ;is BUF set? Beq 590$ ;yes Call Err7.5 ;no 590$: Cmp #020000,(R1)+ ;is WCNT set? Beq 600$ ;yes Call Err7.6 ;no 600$: CmpB #..SPFV,(R1)+ ;is the marker unchanged? Beq 610$ ;yes Call Err7.7 ;no 610$: CmpB #202,(R1)+ ;is FUNC set? Beq 620$ ;yes Call Err7.8 ;no 620$: Cmp #123456,(R1)+ ;is CRTN set to wait? Beq 630$ ;yes Call Err7.9 ;no 630$: .PSect Data SPFUN8: .SPFUN 640$: .PSect Active Cmp #EMT+...AR0,640$-2 ;correct EMT? Beq 650$ ;yes Call Err8 ;no 650$: Call AreaM1 ;init area MovB #-2,Area+8. ;init marker byte to -2 Mov #Patter,R0 ;init R0 Mov #333,R3 ;FUNC from a register SPFUN9: .SPFUN #Area,#0,R3,#010000,#020000,#0,#123456,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 660$ ;yes Call Err9.1 ;no 660$: CmpB #0,(R1)+ ;is CHAN set? Beq 670$ ;yes Call Err9.2 ;no 670$: CmpB #.SPFUN,(R1)+ ;is IC set? Beq 680$ ;yes Call Err9.3 ;no 680$: Cmp #0,(R1)+ ;is BLK set? Beq 690$ ;yes Call Err9.4 ;no 690$: Cmp #010000,(R1)+ ;is BUF set? Beq 700$ ;yes Call Err9.5 ;no 700$: Cmp #020000,(R1)+ ;is WCNT set? Beq 710$ ;yes Call Err9.6 ;no 710$: SPFUNA: CmpB #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 720$ ;yes Call ErrA.1 ;no 720$: CmpB #333,(R1)+ ;is FUNC unchanged? Beq 730$ ;yes Call ErrA.2 ;no 730$: Cmp #123456,(R1)+ ;is SRTN set to wait? Beq 740$ ;yes Call ErrA.3 ;no 740$: .PSect Data SPFUNB: .SPFUN ,BMODE=SI 750$: .PSect Active Cmp #EMT+...AR0,750$-2 ;correct EMT? Beq 760$ ;yes Call ErrB.1 ;no 760$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SPND Suspend a job request .MACRO .SPND MOV #^o400,R0 EMT ^o374 .ENDM ;+TEST .Enabl LSB .PSect Text $SPND: .Asciz "%SYSMAC-I-Testing .SPND" .PSect Active Mov #$SPND,R0 ;Ident the test(s) Call BegTst ;Assume no errors Mov #Patter,R0 SPND1: .SPND .=.-2 ;squash EMT Cmp #.SPND*^o400,R0 ;Is R0 right? Beq 10$ Call Err1 10$: .PSect Data SPND2: .SPND .=.-2. 23$: .=.+2. 25$: .PSect Active Cmp #EMT+...R0,23$ ;was the correct EMT generated? Beq 20$ ;Yes Call Err2 20$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SRESET Soft reset request .MACRO .SRESE EMT ^o352 .ENDM ;+TEST .Enabl LSB .PSect Text $SRESE: .Asciz "%SYSMAC-I-Testing .SRESE" .PSect Active Mov #$SRESE,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data SRESE1: .SRESE .=.-2. 13$: .=.+2. 15$: .PSect Active Cmp #EMT+...SRE,13$ ;was the correct EMT generated? Beq 10$ ;Yes Call Err1 10$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .SYNCH Synchronize with the specified job call .MACRO .SYNCH AREA,PIC .IF B PIC .IF NB <AREA> MOV AREA,R4 .ENDC .IFF .IF NB AREA MOV PC,R4 .NTYPE ...V2,AREA .IF EQ ...V2-^o27 ADD AREA-.,R4 .IFF ADD #AREA-.,R4 .ENDC .ENDC .ENDC MOV @#^o54,R5 JSR R5,@^o324(R5) .ENDM ;+TEST .Enabl LSB .PSect Text $SYNCH: .Asciz "%SYSMAC-I-Testing .SYNCH" .PSect Active Mov #$SYNCH,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .TIMIO Time an I/O request call **Handler only** .MACRO .TIMIO TBK,HI,LO JSR R5,@$TIMIT .WORD TBK-. .WORD 0 .WORD HI .WORD LO .ENDM ;+TEST .Enabl LSB .PSect Text $TIMIO: .Asciz "%SYSMAC-I-Testing .TIMIO" .PSect Active Mov #$TIMIO,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .TLOCK Test for USR available, if so, lock in memory for this job .SbTtl . request .MACRO .TLOCK MOV #^o3400,R0 EMT ^o374 .ENDM ;+TEST .Enabl LSB .PSect Text $TLOCK: .Asciz "%SYSMAC-I-Testing .TLOCK" .PSect Active Mov #$TLOCK,R0 ;Ident the test(s) Call BegTst ;Assume no errors Mov #Patter,R0 TLOCK1: .TLOCK .=.-2 ;squash EMT Cmp #.TLOCK*^o400,R0 ;Is R0 right? Beq 10$ Call Err1 10$: .PSect Data TLOCK2: .TLOCK .=.-2. 23$: .=.+2. 25$: .PSect Active Cmp #EMT+...R0,23$ ;was the correct EMT generated? Beq 20$ ;Yes Call Err2 20$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .TRPSET Set trap 4 and 10 address request .MACRO .TRPSE AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,3.,0.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $TRPSE: .Asciz "%SYSMAC-I-Testing .TRPSET" .PSect Active Mov #$TRPSE,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s TRPS1: .TRPSET #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.TRPSE*^o400+0,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s TRPS2: .TRPSET #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.TRPSE*^o400+0,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 TRPS3: .TRPSET ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.TRPSE*^o400+0,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data TRPS4: .TRPSET 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .TTINR Get a character for console, report if none available request .MACRO .TTINR EMT ^o340 .ENDM ;+TEST .Enabl LSB .PSect Text $TTINR: .Asciz "%SYSMAC-I-Testing .TTINR" .PSect Active Mov #$TTINR,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data TTINR1: .TTINR .=.-2. 13$: .=.+2. .PSect Active Cmp #EMT+...TTI,13$ ;was the correct EMT generated? Beq 10$ ;Yes Call Err1 10$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .TTOUTR Send a char to console, report if buffer full request .MACRO .TTOUT EMT ^o341 .ENDM ;+TEST .Enabl LSB .PSect Text $TTOUT: .Asciz "%SYSMAC-I-Testing .TTOUT" .PSect Active Mov #$TTOUT,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data TTOUT1: .TTOUT .=.-2. 13$: .=.+2. .PSect Active Cmp #EMT+...TTO,13$ ;was the correct EMT generated? Beq 10$ ;Yes Call Err1 10$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .TTYIN Get a char from console, wait until available request .MACRO .TTYIN CHAR EMT ^o340 BCS .-2. .IF NB <CHAR> .IF DIF <CHAR>,R0 MOVB R0,CHAR .ENDC .ENDC .ENDM ;+TEST .Enabl LSB .PSect Text $TTYIN: .Asciz "%SYSMAC-I-Testing .TTYIN" .PSect Active Mov #$TTYIN,R0 ;Ident the test Call BegTst .PSect Data TTYI1: .TTYIN .PSect Active Cmp #EMT+...TTI,TTYI1 ;correct EMT generated? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #BCS!376,TTYI1+2 ;and the branch? Beq 20$ ;yes 20$: Mov #Patter,R1 ;init R1 to odd pattern Mov #100340,R0 ;init R0 to different pattern TTYI2: .TTYIN R1 .=.-6 ;smash EMT and BCS Nop ;smash EMT Nop ;smash BCS .=.+2 ;allow MOV Cmp #177600!340,R1 ;R1 loaded correctly? Beq 30$ ;yes Call Err2 ;no 30$: Mov #100340,R0 ;init R0 to different pattern TTYI3: .TTYIN R0 .=.-4 ;smash EMT and BCS Nop ;smash EMT Nop ;smash BCS Cmp #100340,R0 ;R0 loaded correctly? ;Note: MOV R0,R0 suppressed Beq 40$ ;yes Call Err3 ;no 40$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .TTYOUT Send a char to the console, wait until in buffer request .MACRO .TTYOU CHAR .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM5 <CHAR>,341,B BCS .-2. .ENDM ;+TEST .Enabl LSB .PSect Text $TTYOU: .Asciz "%SYSMAC-I-Testing .TTYOUT" .PSect Active Mov #$TTYOU,R0 ;Ident the test Call BegTst .PSect Data TTYO1: .TTYOUT .PSect Active Cmp #EMT+...TTO,TTYO1 ;correct EMT generated? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #BCS!376,TTYO1+2 ;and the branch? Beq 20$ ;yes 20$: Mov #Patter,R0 ;init R0 to odd pattern TTY02: .TTYOUT #123456 .=.-4 ;smash EMT and BCS Cmp #056,R0 ;R0 loaded correctly? Beq 30$ ;yes Call Err2 ;no 30$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .TWAIT Wait for specified time interval request .MACRO .TWAIT AREA,TIME,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,20.,0.,<CODE>,<TIME>,E .ENDM .PAGE ;+TEST .Enabl LSB .PSect Text $TWAIT: .Asciz "%SYSMAC-I-Testing .TWAIT" .PSect Active Mov #$TWAIT,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s TWAI1: .TWAIT #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.TWAIT*^o400+0,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s TWAI2: .TWAIT #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.TWAIT*^o400+0,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 TWAI3: .TWAIT ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.TWAIT*^o400+0,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data TWAI4: .TWAIT 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .UNLOCK Release USR from memory and job request .MACRO .UNLOC EMT ^o347 .ENDM ;+TEST .Enabl LSB .PSect Text $UNLOC: .Asciz "%SYSMAC-I-Testing .UNLOCK" .PSect Active Mov #$UNLOC,R0 ;Ident the test(s) Call BegTst ;Assume no errors .PSect Data UNLOC1: .UNLOC .=.-2. 13$: .=.+2. .PSect Active Cmp #EMT+...UNL,13$ ;was the correct EMT generated? Beq 10$ ;Yes Call Err1 10$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .UNMAP Unmap extended memory request .MACRO .UNMAP AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,30.,5.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $UNMAP: .Asciz "%SYSMAC-I-Testing .UNMAP" .PSect Active Mov #$UNMAP,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s UNMA1: .UNMAP #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.UNMAP*^o400+..UNMAP,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s UNMA2: .UNMAP #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.UNMAP*^o400+..UNMAP,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 UNMA3: .UNMAP ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.UNMAP*^o400+..UNMA,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data UNMA4: .UNMAP 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .UNPROTECT Unprotect specified vector request .MACRO .UNPRO AREA,ADDR,CODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM6 <AREA>,25.,1.,<CODE>,<ADDR>,E .ENDM ;+TEST .Enabl LSB .PSect Text $UNPRO: .Asciz "%SYSMAC-I-Testing .UNPROTECT" .PSect Active Mov #$UNPRO,R0 ;Ident the test Call BegTst Call AreaM1 ;set area to -1s UNPR1: .UNPRO #Area,#123456 .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 10$ ;yes Call Err1.1 ;no 10$: Cmp #.UNPRO*^o400+..UNPR,(R1)+ ;is the subcode correct? Beq 20$ ;yes Call Err1.2 ;no 20$: Cmp #123456,(R1)+ ;is the address correct? Beq 30$ ;yes Call Err1.3 30$: Call AreaM1 ;set area to -1s UNPR2: .UNPRO #Area .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 40$ ;yes Call Err2.1 ;no 40$: Cmp #.UNPRO*^o400+..UNPR,(R1)+ ;is the subcode correct? Beq 50$ ;yes Call Err2.2 ;no 50$: Cmp #177777,(R1)+ ;is the address correct? Beq 60$ ;yes Call Err2.3 60$: Call AreaM1 ;set area to -1s Mov #Area,R0 UNPR3: .UNPRO ,#123456,CODE=SET .=.-2 ;crush EMT Mov R0,R1 ;point to area Cmp R0,#Area ;was area pointed to correctly? Beq 70$ ;yes Call Err3.1 ;no 70$: Cmp #.UNPRO*^o400+..UNPR,(R1)+ ;is the subcode correct? Beq 80$ ;yes Call Err3.2 ;no 80$: Cmp #123456,(R1)+ ;is the address correct? Beq 90$ ;yes Call Err3.3 90$: .PSect Data UNPR4: .UNPRO 100$: .PSect Active Cmp #EMT+...AR0,100$-2 ;correct EMT code? Beq 110$ ;yes Call Err4 110$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .WAIT Wait for I/O completion .MACRO .WAIT CHAN .IF NDF ...V1 .MCALL .MACS .MACS .ENDC .IF NE ...V1-1 .IF B <CHAN> CLR R0 .IFF .NTYPE ...V2,CHAN .IF EQ ...V2-^o27 .IF IDN <CHAN>,#0 CLR R0 .IFF .IIF IDN <CHAN>,0,.ERROR;?SYSMAC-W-Invalid argument, use #0, not 0; MOV CHAN,R0 .ENDC .IFF .IF EQ ...V2&^o7 .IF NE ...V2 MOV CHAN,R0 .ENDC BIC #^c^o377,R0 .IFF CLR R0 BISB CHAN,R0 .ENDC .ENDC .ENDC EMT ^o374 .MEXIT .ENDC EMT ^o<240+CHAN> .ENDM ;+TEST .Enabl LSB .PSect Text $WAIT: .Asciz "%SYSMAC-I-Testing .WAIT" .PSect Active Mov #$WAIT,R0 ;Ident the test Call BegTst Mov #Patter,R0 ;trash R0 WAIT1: .WAIT .=.-2 ;crush EMT .Assume .WAIT EQ 0 Tst R0 ;zeroed? Beq 10$ ;yes Call Err1 ;no 10$: Mov #Patter,R0 ;trash R0 WAIT2: .WAIT #0 .=.-2 ;crush EMT .Assume .WAIT EQ 0 Tst R0 ;zeroed? Beq 20$ ;yes Call Err2 ;no 20$: Mov #Patter,R0 ;trash R0 WAIT3: .WAIT #Zero .=.-2 ;crush EMT .Assume .WAIT EQ 0 Tst R0 ;zeroed? Beq 30$ ;yes Call Err3 ;no 30$: Mov #3,R0 ;load R0 WAIT4: .WAIT R0 .=.-2 ;crush EMT .Assume .WAIT EQ 0 Cmp #3,R0 ;loaded correctly? Beq 40$ ;yes Call Err4 ;no 40$: Mov #Patter,R0 ;trash R0 Mov #3,R1 ;load R0 WAIT5: .WAIT R1 .=.-2 ;crush EMT .Assume .WAIT EQ 0 Cmp #3,R0 ;zeroed? Beq 50$ ;yes Call Err5 ;no 50$: Mov #60$,R0 ;load address in R0 .PSect Data 60$: .Word 3 .PSect Active WAIT6: .WAIT @R0 .=.-2 ;crush EMT .Assume .WAIT EQ 0 Cmp #3,R0 ;zeroed? Beq 70$ ;yes Call Err6 ;no 70$: Call EndTst .Dsabl LSB ;>>>emt test? ;-TEST .Page .SbTtl .WDBBK generate a Window Definition Block .MACRO .WDBBK WNAPR,WNSIZ,WNRID,WNOFF,WNLEN,WNSTS .MCALL .WDBDF .WDBDF .BYTE .BYTE WNAPR .WORD .WORD WNSIZ .WORD WNRID .WORD WNOFF .WORD WNLEN .WORD WNSTS .ENDM ;+TEST .Enabl LSB .PSect Text $WDBBK: .Asciz "%SYSMAC-I-Testing .WDBBK" .PSect Active Mov #$WDBBK,R0 ;Ident the test Call BegTst Call SkpTst ;-TEST .Page .SbTtl .WDBDF Define bits and offsets for a WDB .MACRO .WDBDF LIST,E=<=:> .IIF IDN <LIST>,<YES> .LIST W.NID E 0 W.NAPR E 1 W.NBAS E 2. W.NSIZ E 4. W.NRID E 6. W.NOFF E ^o10 W.NLEN E ^o12 W.NSTS E ^o14 W.NLGH E ^o16 WS.CRW E ^o100000 WS.UNM E ^o40000 WS.ELW E ^o20000 WS.DSI E ^o10000 WS.IDD E ^o4000 WS.OVR E ^o2000 WS.RO E ^o1000 WS.MAP E ^o400 WS.SPA E ^o14 WS.DEF E 0 WS.D E ^o10 WS.I E ^o4 WS.MOD E ^o3 WS.U E ^o0 WS.S E ^o1 WS.C E ^o2 .IIF IDN <LIST>,<YES> .NLIST .ENDM ;+TEST .Enabl LSB .PSect Text $WDBDF: .Asciz "%SYSMAC-I-Testing .WDBDF" .PSect Active Mov #$WDBDF,R0 ;Ident the test Call BegTst Call TemTst ;-TEST .Page .SbTtl .WRITC Queue a write operation, specifying completion routine request .MACRO .WRITC AREA,CHAN,BUF,WCNT,CRTN,BLK,CODE,BMODE,CMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM7 <AREA>,<CHAN>,<BUF>,<WCNT>,<BLK>,<CRTN>,9,<CODE>,220,<BMODE>,<CMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $WRITC: .Asciz "%SYSMAC-I-Testing .WRITC" .PSect Active Mov #$WRITC,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITC1: .WRITC .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITC2: .WRITC ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.2 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.3 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.4 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.5 ;no 130$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 140$ ;yes Call Err2.6 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITC3: .WRITC ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err2.1 ;no 150$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 160$ ;yes Call Err2.2 ;no 160$: CmpB #.WRITC,(R1)+ ;is IC set? Beq 170$ ;yes Call Err2.2 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err2.3 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err2.4 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err2.5 ;no 200$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 210$ ;yes Call Err2.6 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITC4: .WRITC #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.WRITC,(R1)+ ;is IC set? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITC5: .WRITC #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.2 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.3 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.4 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.5 ;no 340$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 350$ ;yes Call Err5.6 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITC6: .WRITC #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.WRITC,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.2 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.3 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.4 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.5 ;no 410$: Cmp #-1,(R1)+ ;is CRTN unchanged? Beq 420$ ;yes Call Err6.6 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITC7: .WRITC #Area,#0,#010000,#020000,#123456,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.WRITC,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.2 ;no 450$: Cmp #030000,(R1)+ ;is BLK set? Beq 460$ ;yes Call Err7.3 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.4 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.5 ;no 480$: Cmp #123456,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.6 ;no 490$: .PSect Data WRITC8: .WRITC 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITC9: .WRITC #Area,#0,#010000,#020000,#123654,#0,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.WRITC,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #0,(R1)+ ;is BLK set? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #123654,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data WRITCA: .WRITC ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .WRITE Queue a write operation request .MACRO .WRITE AREA,CHAN,BUF,WCNT,BLK,CRTN=#1,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM7 <AREA>,<CHAN>,<BUF>,<WCNT>,<BLK>,<CRTN>,9,<CODE>,220,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $WRITE: .Asciz "%SYSMAC-I-Testing .WRITE" .PSect Active Mov #$WRITE,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITE1: .WRITE .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITE2: .WRITE ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.2 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.3 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.4 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.5 ;no 130$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.6 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITE3: .WRITE ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err2.1 ;no 150$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 160$ ;yes Call Err2.2 ;no 160$: CmpB #.WRITE,(R1)+ ;is IC set? Beq 170$ ;yes Call Err2.2 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err2.3 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err2.4 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err2.5 ;no 200$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err2.6 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITE4: .WRITE #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.WRITE,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITE5: .WRITE #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.2 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.3 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.4 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.5 ;no 340$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.6 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITE6: .WRITE #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.WRITE,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.2 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.3 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.4 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.5 ;no 410$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.6 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITE7: .WRITE #Area,#0,#010000,#020000,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.WRITE,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.2 ;no 450$: Cmp #030000,(R1)+ ;is BLK set? Beq 460$ ;yes Call Err7.3 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.4 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.5 ;no 480$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.6 ;no 490$: .PSect Data WRITE8: .WRITE 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITE9: .WRITE #Area,#0,#010000,#020000,#0,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.WRITE,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #0,(R1)+ ;is BLK set? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..ISIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data WRITEA: .WRITE ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page .SbTtl .WRITW Issue a write operation, wait for completion request .MACRO .WRITW AREA,CHAN,BUF,WCNT,BLK,CRTN=#0,CODE,BMODE .IF NDF ...V1 .MCALL .MACS .MACS .ENDC ...CM7 <AREA>,<CHAN>,<BUF>,<WCNT>,<BLK>,<CRTN>,9,<CODE>,220,<BMODE> .ENDM ;+TEST .Enabl LSB .PSect Text $WRITW: .Asciz "%SYSMAC-I-Testing .WRITW" .PSect Active Mov #$WRITW,R0 ;Ident the test Call BegTst Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITW1: .WRITW .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 10$ ;yes Call Err1.1 ;no 10$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 20$ ;yes Call Err1.2 ;no 20$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 30$ ;yes Call Err1.3 ;no 30$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 40$ ;yes Call Err1.4 ;no 40$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 50$ ;yes Call Err1.5 ;no 50$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 60$ ;yes Call Err1.6 ;no 60$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 70$ ;yes Call Err1.7 ;no 70$: Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITW2: .WRITW ,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 80$ ;yes Call Err2.1 ;no 80$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 90$ ;yes Call Err2.2 ;no 90$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 100$ ;yes Call Err2.2 ;no 100$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 110$ ;yes Call Err2.3 ;no 110$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 120$ ;yes Call Err2.4 ;no 120$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 130$ ;yes Call Err2.5 ;no 130$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 140$ ;yes Call Err2.6 ;no 140$: Call AreaM1 ;init area Mov #Area,R0 ;point to area WRITW3: .WRITW ,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 150$ ;yes Call Err2.1 ;no 150$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 160$ ;yes Call Err2.2 ;no 160$: CmpB #.WRITW,(R1)+ ;is IC set? Beq 170$ ;yes Call Err2.2 ;no 170$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 180$ ;yes Call Err2.3 ;no 180$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 190$ ;yes Call Err2.4 ;no 190$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 200$ ;yes Call Err2.5 ;no 200$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 210$ ;yes Call Err2.6 ;no 210$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITW4: .WRITW #Area .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 220$ ;yes Call Err4.1 ;no 220$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 230$ ;yes Call Err4.2 ;no 230$: CmpB #.WRITW,(R1)+ ;is IC unchanged? Beq 240$ ;yes Call Err4.3 ;no 240$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 250$ ;yes Call Err4.4 ;no 250$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 260$ ;yes Call Err4.5 ;no 260$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 270$ ;yes Call Err4.6 ;no 270$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 280$ ;yes Call Err4.7 ;no 280$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITW5: .WRITW #Area,CODE=NOSET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 290$ ;yes Call Err5.1 ;no 290$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 300$ ;yes Call Err5.2 ;no 300$: CmpB #-1,(R1)+ ;is IC unchanged? Beq 310$ ;yes Call Err5.2 ;no 310$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 320$ ;yes Call Err5.3 ;no 320$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 330$ ;yes Call Err5.4 ;no 330$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 340$ ;yes Call Err5.5 ;no 340$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 350$ ;yes Call Err5.6 ;no 350$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITW6: .WRITW #Area,CODE=SET .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 360$ ;yes Call Err6.1 ;no 360$: CmpB #-1,(R1)+ ;is CHAN unchanged? Beq 370$ ;yes Call Err6.2 ;no 370$: CmpB #.WRITW,(R1)+ ;is IC set? Beq 380$ ;yes Call Err6.2 ;no 380$: Cmp #-1,(R1)+ ;is BLK unchanged? Beq 390$ ;yes Call Err6.3 ;no 390$: Cmp #-1,(R1)+ ;is BUF unchanged? Beq 400$ ;yes Call Err6.4 ;no 400$: Cmp #-1,(R1)+ ;is WCNT unchanged? Beq 410$ ;yes Call Err6.5 ;no 410$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 420$ ;yes Call Err6.6 ;no 420$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITW7: .WRITW #Area,#0,#010000,#020000,#030000 .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 430$ ;yes Call Err7.1 ;no 430$: CmpB #0,(R1)+ ;is CHAN set? Beq 440$ ;yes Call Err7.2 ;no 440$: CmpB #.WRITW,(R1)+ ;is IC set? Beq 450$ ;yes Call Err7.2 ;no 450$: Cmp #030000,(R1)+ ;is BLK set? Beq 460$ ;yes Call Err7.3 ;no 460$: Cmp #010000,(R1)+ ;is BUF set? Beq 470$ ;yes Call Err7.4 ;no 470$: Cmp #020000,(R1)+ ;is WCNT set? Beq 480$ ;yes Call Err7.5 ;no 480$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 490$ ;yes Call Err7.6 ;no 490$: .PSect Data WRITW8: .WRITW 500$: .PSect Active Cmp #EMT+...AR0,500$-2 ;correct EMT? Beq 510$ ;yes Call Err8 ;no 510$: Call AreaM1 ;init area Mov #Patter,R0 ;init R0 WRITW9: .WRITW #Area,#0,#010000,#020000,#0,BMODE=UI .=.-2 Mov #Area,R1 ;point to area Cmp R0,R1 ;R0 ok? Beq 520$ ;yes Call Err9.1 ;no 520$: CmpB #0,(R1)+ ;is CHAN set? Beq 530$ ;yes Call Err9.2 ;no 530$: CmpB #.WRITW,(R1)+ ;is IC set? Beq 540$ ;yes Call Err9.3 ;no 540$: Cmp #0,(R1)+ ;is BLK set? Beq 550$ ;yes Call Err9.4 ;no 550$: Cmp #010000,(R1)+ ;is BUF set? Beq 560$ ;yes Call Err9.5 ;no 560$: Cmp #020000,(R1)+ ;is WCNT set? Beq 570$ ;yes Call Err9.6 ;no 570$: Cmp #..USER!..ISPA!^o3,(R1)+ ;is FLAG set? Beq 580$ ;yes Call Err9.7 ;no 580$: Cmp #..WTIO,(R1)+ ;is CRTN set? Beq 590$ ;yes Call Err9.8 ;no 590$: .PSect Data WRITWA: .WRITW ,BMODE=SI 600$: .PSect Active Cmp #EMT+...AR0,600$-2 ;correct EMT? Beq 610$ ;yes Call ErrA.1 ;no 610$: Call EndTst .Dsabl LSB ;-TEST .Page ;+TEST .Enabl LSB .PSect Active .Debug SWITCH=ON,VALUE=YES .DPrint <> .DPrint <%SYSMAC-I-Warnings issued >,WarCnt,DEC .DPrint <%SYSMAC-I-Errors issued >,ErrCnt,DEC .Exit ;done .Dsabl LSB .End Active ;-TEST .End