.TITLE PD DATACOMMUNICATION HANDLER WITH RSP PROTOCOL. ; Multiprocessor V5 ; file PDL50X.MAC, this is the standard LOOPING handler with XM support for ; DR(V)-11(C/00), and WB(V)-11 HARDWARE ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++; ; COPYRIGHT (c) 1981,82,83,84,85,86 by ; ; H.H. Klin. Neuro. AZG ; ; ; ; This software is furnished under a LICENSE and may be USED ONLY IN ; ; ACCORDANCE WITH THE TERMS OF SUCH LICENSE. This software or ; ; any other copies thereof may not be provided or otherwise made ; ; available to any other person. NO TITLE TO AND OWNERSHIP OF THE ; ; SOFTWARE IS HEREBY TRANSFERRED. ; ; ; ; The information in this software is subject to change without notice. ; ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++; .IIF NDF,TIM$IT TIM$IT= 1 ;Default TIME-OUT support! .IIF NDF,MMG$T MMG$T = 1 WB = 0 ;0= DR-11(V)/(C), 1= WB-11(V) HARDWARE CKS = 1 ;1=Enable checksum calculation, 0=minimal checking. TIMOUT = 200. ;Time-out initial setting ( ca. 0.1*TIMOUT sec. for PDP11/34 ; or LSI 11/23, does NOT require "device time-out" support!) UNIT0 = 0 ;RSP unit start number UNITS = 8. ;No. of device units CH = 1 ;1= Insert cache macro QLEN = 5 ;Nr. of (pseudo)devices which can simultaneous generate a ;request for datacommunication I/O.(=Queuelength) CHECK = 125252 ;*** ATTENTION: 1. IO-page address and vector to be set in .DRDEF macro!! ; 2. If PD is NOT the name of the bootable driver on disk, then ; set B$DNAM=XX, where XX.SYS is the name on disk. B$DNAM is ; located after the .DRBOT macro. .IDENT /V 5.0/ ; ; * Extra protection data outside buffer, when receiving DATA. ; * Implementation of internal device queue for queueing (pseudo)- ; device requests. Queue contains pointers to handler blocks with ; the following format: ; ----------------------------------------- ; HDBLK: ! SPFUN CODE 0-377 ! UNIT NR. 0-377 ! ; ----------------------------------------- ; ! Q-ELEMENT POINTER ! ; ----------------------------------------- ; ! RETURN ADRES ! ; ----------------------------------------- ; ! SPFUN DATA ! ; ----------------------------------------- QLEN=QLEN+QLEN ;Make byte length of handler queue. ; Q-Input !------! /----------\ No !-------! !--------------! ; --------->! QIN !---< IO going? >------! QOUT !-->! Handler code !-- ; !------! \----------/ !-------! !--------------! ; ! Yes ^ ; RETURN ! ; ! ; /---------\ no !------------! ! ; --------< Q empty? >----! CALL HDRET !-----/ ; \---------/ !------------! ; ! yes ; JMP HDRET ;----------------------------------------------------------------------- .ENABL LC .SBTTL MACROS AND DEFINITIONS ;----------------------------- .MCALL .DRDEF, .MTPS, .PRINT ; Define device: minimal size = 16. blocks .IF EQ,WB .DRDEF PD,276,FILST$!SPFUN$!VARSZ$,16.,167770,310 ;Parallel line .IFF .DRDEF PD,275,FILST$!SPFUN$!VARSZ$,16.,175610,270 ;"Serial" WB-11 .ENDC ; Level 2 codes (OPCODE byte) R$$NOP = 0 ;NOP R$$INT = 1 ;Initialize R$$RED = 2 ;Read function R$$WRT = 3 ;Write function R$$END = 100 ;End packet ; Level 1 codes (FLAG byte) R$CONT = 20 ;Continue R$CDAT = 40 ;Continue with data R$INIT = 4 ;Init R$DATA = 1 ;Data packet R$MSG = 2 ;Message/Command packet R$MSIZ = 5. ; " / " " size in words. R$DSIZ = 256. ;Max. data-packet size in words. R$ASIZ = 2*R$DSIZ ; Adress offset size for DATA-packet. ; .SBTTL SET OPTION PARAMETER TABLE ;--------------------------------- SETTIM = TIMOUT .DRSET SHOW,-1,S.SHOW ;;SHOW .DRSET UNITS,8.,S.UNITS, ;;Set No. Device Units. .DRSET TIME,-1,S.TIME, ;;TIME-OUT ; .SBTTL SET OPTION PROCESSING ROUTINES ;------------------------------------- NR=7 S.SHOW: MOV R4,-(SP) MOV R5,-(SP) MOV PC,R4 ADD #NUMBER-.,R4 MOV PC,R5 ADD #TEXT-.,R5 MOV #NR,R2 MOV PC,R1 ADD #OUTP-.,R1 LOOP: MOV (R4)+,R0 MOV R1,R3 ;+ CALL CNV8 ; Routine converts bits to octal ASCII string. ; R0; Contains bits to be converted ; R3; Points to output area ; Size of area should be nr. digits plus two ; On return R3 points to string terminator ; Note: Contens of R0, R3 is changed!! CNV8:: MOV R1,-(SP) CALL CONVRT MOVB #' ,(R3)+ MOVB #200,@R3 MOV (SP)+,R1 ;- End CNV8 .PRINT R5 .PRINT R1 ADD #8.,R5 SOB R2,LOOP MOV PC,R0 ADD #CRLF-.,R0 .PRINT MOV (SP)+,R5 MOV (SP)+,R4 CLC RETURN S.UNIT: CMP R0,R3 BHI 2$ ;Not too high! MOV R0,SUNITS ;Copy DEVICE UNITs for SHOW BLE 2$ MOV R0,NUNITS ;Set No DEVICE UNITs. RETURN 2$: SEC RETURN S.TIME: MOV R0,TIMDAT ; On entry Carry = clear ASR R0 ;/2 ASR R0 ;/4 MOV R0,TIMVAL ;New timout value! Carry unaffected! RETURN NUMBER: .WORD PDSTS .WORD PD$CSR .WORD PD$VEC .WORD QLEN/2 .WORD UNIT0 SUNITS: .WORD UNITS TIMDAT: .WORD SETTIM TEXT: .ASCII /Status=/<200> .IIF EQ,WB .ASCII /DRLOOP=/<200> .IIF NE,WB .ASCII /WBLOOP=/<200> .ASCII /Vector=/<200> .ASCII <15><12>/QLEN=/<200> .ASCII /Unit0 =/<200> .ASCII /Units =/<200> .iif EQ,CKS .ASCII/No / .ASCII /CKS Time=/<200> OUTP: .BLKB 10. CRLF: .BYTE 0 .EVEN ;+ CONVRT CONVRT: MOV R0,R1 CLR R0 DIV #8.,R0 MOV R1,-(SP) TST R0 BEQ DONE CALL CONVRT DONE: MOVB (SP)+,@R3 BISB #'0,(R3)+ RETURN ;- End CONVRT .IIF GT <.-1000>, .ERROR .-1000 ;SET code too big! .SBTTL START I/O ENTRY ;---------------------- ;========================================================= .DRBEG PD .IIF NE,CH CACHE ;Caching Link!! MOV PDCQE,R4 ;COPY Q-pointer MOVB Q$UNIT(R4),R1 ;Get device unit nr. BIC #^C<7>,R1 ;strip to 0-7 CMP NUNITS,R1 ;Valid nr.? BLOS PDERR ADD #UNIT0,R1 ;Make RSP unitnr. CLR SPDATA ;Clear SPFUN data word in HDBLK. CLR R0 BISB Q$FUNC(R4),R0 BEQ RDWT ;Read/write only. ;-----------------------------------------------------------------------; SPFUN: CMP R0,#373 ;Size request? BNE PDERR ; ; Variable size support; setup for remote spfun 373 request: ; SWAB R0 BIS R0,R1 MOV #1,Q$WCNT(R4) ;Read 1 word (=size) from remote dev. MOV #1,SPDATA ;Read 1 word SPFUN ; Standard read/write: RDWT: ;------------Set up HDBLK for this handler---------------- ; MOV PC,R2 ;PIC ADD #HDBLK-.,R2 ; of Handler block MOV R2,R0 ;R0 must point to HDBLK MOV R1,(R2)+ ;copy unitnr. in HDBLK MOV R4,(R2)+ ; " Q-pointer " " MOV PC,R1 ADD #PDFIN-.,R1 MOV R1,(R2)+ ;copy return adress in HDBLK ;-----------Put IO request in handler queue---------------- QIN: ;R0 points to HDBLK .MTPS #340 ;Do not disturb us while MOV PC,R1 ; we are queueing. ADD #HDQB-.,R1 ADD INQP,R1 MOV R0,(R1) ;Store HDBLK pointer in Q CMP #QLEN,INQP ;End of Queue? BNE 1$ CLR INQP ;Reset to begin. BR 2$ 1$: ADD #2,INQP ;To next free slot 2$: TST IOFLAG ;IO going? BEQ QOUT RETURN PDERR: BIS #1,@-(R4) ;SET HARD-ERROR BIT in CSW PDFIN: .DRFIN PD ;exit to completion I/O NUNITS: .WORD UNITS ;No. of device units HDBLK: .WORD 0 ;Handler block of PD .WORD 0 ;Q-POINTER .WORD 0 ;Return address SPDATA: .WORD 0 ;Saved SPFUN word count HDBLKP: .WORD 0 ;Pointer to current HDBLK HLPCQE: .WORD 0 ;Help Q-pointer IOFLAG: .WORD 0 INQP: .WORD 0 ;Pointer to next free slot in Q. OUTQP: .WORD 0 ;Pointer to next available HDBLK. HDQB: .WORD 0 ;Begin of handler queue .=HDQB+QLEN+2 ;Set end of queue ;-----------Get IO request from handler queue---------------- QOUT: MOV PC,R4 ADD #HDQB-.,R4 ADD OUTQP,R4 MOV (R4),HDBLKP ;Points to current HDBLK CMP #QLEN,OUTQP ;End of Q? BNE 3$ CLR OUTQP BR 4$ 3$: ADD #2,OUTQP 4$: BIS #1,IOFLAG ;-----------Start with datacommunication IO.------------------ IOGO: .MTPS #0 BR STARIO ;Startup RSP IO. VECTAB: .DRVTB PD,PD$VEC,PDINT .DRVTB ,PD$VEC+4,PDINT ; .SBTTL Q, Abort & Interrupt entry ;--------------------------------- BR QIN ; Entry point for Pseudo-H's RETURN ; Does not make sense in a looping handler! ;-----------------------------------------------------------------------; PDINT:: RTI ;..and nothing else: Looping handler .SBTTL COMPLETION EXIT ;---------------------- ERROR: MOV HLPCQE,R4 BIS #1,@Q$CSW(R4) ;SET HARD-ERROR BIT in CSW CMPB I$MSUC,#-2 ;EOF? BNE PDEXIT BIS #20000,@Q$CSW(R4);Set EOF bit also! PDEXIT: ;------------Check if there's still IO to be done------------ ;------------Again an IO done, examine HANDLER Q ------------ IODONE: .MTPS #340 MOV HDBLKP,R4 ADD #6,R4 ;Point to SPDATA MOV PC,@R4 ;Get adres for ADD #I$SPFE-.,@R4 ; error-return block. Fill it. CMP INQP,OUTQP ;Q empty? BNE 5$ BIC #1,IOFLAG ;Set all IO done. JMP @-(R4) ;Q empty--> do not return 5$: CALL @-(R4) ;Link out Q-element, and return here. BR QOUT ;Examine Handler queue. .SBTTL STARIO - START I/O CODE ;------------------------------- ; R0-R5 available TIMVAL: .WORD TIMOUT/4 STARIO::MOV HDBLKP,R0 MOV (R0)+,PK$UNT ;Store unit nr.+SPFUN in packet MOV (R0)+,R3 MOV R3,HLPCQE ;R3 -> to Queue-element TST (R0)+ MOV (R0)+,PK$SSQ ;SPFUN DATA CLR PK$OPC ;Set wordcount=0 MOV Q$WCNT(R3),R1 ;R1 -> word count. BEQ 9$ BPL 8$ ;+ means read MOVB #R$$WRT,PK$OPC ;make write NEG R1 ;and make + word count BR 9$ ;normal I/O 8$: MOVB #R$$RED,PK$OPC ;assume read, clear modifier 9$: .if eq,MMG$T MOV Q$BUFF(R3),I$ADRS ;address for TX .iff CLR I$ADRS ;address for TX .endc ;eq,MMG$T MOV R1,I$WRDC ;save word count MOV R1,PK$BCT ;copy word count into packet CLR PK$FLG ;Indicate nothing processed yet. MOV @R3,PK$RCD ;block nr. into packet CLR R3 ;Reset low order time CLR TIMHI ; " high " " MOV #PD$CSR,R0 ;STATUS (Output WB-11 = +4) .IF EQ,WB MOV #PD$CSR+4,R1 ;INPUT MOV #PD$CSR+2,R2 ;OUTPUT .IFF MOV #PD$CSR+2,R1 ;INPUT MOV #PD$CSR+6,R2 ;OUTPUT .ENDC TST @R1 ;Dump input buffer. MOV #177777,@R2 ;Reset logic DRV-11 00 .SBTTL TXGO - START TRANSFER ;------------------------------- TXGO: MOV #R$MSG,PK$FLG ;flagbyte= command type MOVB #R$MSIZ,PK$MWC ;set packet size MOV #R$MSIZ,WCNT ;Set locally counter. MOV PC,R5 ;PIC-address ADD #PK$OPC-.,R5 ; of message OPCODE CALL SNDPKT ;send packet to start I/O, R5 = data pointer ; speeding up by receive CONTINUE in SNDPKT in case of write. 2$: MOV I$ADRS,R5 ;get the DATA address MOV I$WRDC,R4 ; and the wordcount BEQ TXEND ;No bytes -> position get END-packet CMPB PK$OPC,#R$$WRT ;write? BNE 4$ MOV R4,WCNT ;Set locally counter. CMP R4,#R$DSIZ ;too large for one packet? BLOS 3$ ;nope, use this count MOV #R$DSIZ,WCNT ;set counter CLR R4 ;full packet TX 3$: MOVB R4,PK$MWC ;Set pack size. MOVB #R$DATA,PK$FLG ;Set data-flag. CALL SNDPKT ;send data-packet BR 5$ ;go, send next data packet 4$: MOV #R$DATA,I$EFLG ;Set flag expected CALL RCVPKT ;read, receive data-packet 5$: .iif eq,MMG$T ADD #R$ASIZ,I$ADRS ;adjust the address, use nr. BYTES! SUB #R$DSIZ,I$WRDC ;count one packet from the wordcount BHI 2$ ;still more to go CLR I$WRDC ;all has been TX'erred ; ; .SBTTL TXEND - READ THE END PACKET AFTER A TRANSFER ;----------------------------------------------------- TXEND: MOV PC,R5 ;point to message packet ADD #I$MBFR-.,R5 MOV #R$MSG,I$EFLG ;Set flag expexted. CALL RCVPKT ;get a packet ; .SBTTL Analyze the END PACKET ;----------------------------- ENDANA: CMPB PK$FLG,#R$MSG ;message packet? BNE ABORT ;no, protocol screwup, try reinitializing CMPB I$MOPC,#R$$END ;End-packet? BNE ABORT ;no -> error TSTB I$MSUC ;check for succes via succes byte in mess. BPL CPLRTN ;OK, so complete without error FATAL: JMP ERROR ;completion ERROR exit CPLRTN: JMP PDEXIT ;completion exit .SBTTL ABORT - COMMUNICATIONS ERROR ;------------------------------------- ABORT: ; Initialize the device ; if a checksum error occurs, a unexpected packet type is ; received, or something else happens which indicates the ; transmission line or protocol is out of sync, we send RSP-init ; 7 attempts are made to signal the device/JOB after transfer, then ; we quit and return hard error. TXINIT: TST @R1 ;dump input to clear ready flag INITS: CALL OUTPUT ;OUTPUT WAIT MOV #R$INIT,@R2 ;send INIT CALL INPUT CMP @R1,#R$CONT ;is it CONTINUE? BNE INITS ;try again, wait until we have it BR FATAL ; or time-out! ; Basic input / output routines: ; ------------------------------ INPUT: INC R3 ; Update low-order time BEQ 1$ .IF EQ,WB TST @R0 ; Check input status ready .IFF TSTB @R0 .ENDC ; WB BPL INPUT RETURN 1$: INC TIMHI CMP TIMHI,TIMVAL BHIS TIMER BR INPUT OUTPUT: INC R3 ; Update low-order time BEQ 1$ .IF EQ,WB TSTB @R0 ; Check output status ready .IFF TSTB 4(R0) .ENDC ; WB BPL OUTPUT RETURN 1$: INC TIMHI CMP TIMHI,TIMVAL BHIS TIMER BR OUTPUT TIMER: TST (SP)+ ; Pop-off return address BR FATAL TIMHI: .WORD 0 ; High order timout value .SBTTL SNDPKT - SEND RADIAL SERIAL PACKET ;------------------------------------------ SNDPKT: MOV (SP)+,I$SUBR ;save subr. return .if NE,CKS MOV PK$FLG,PK$CKS ;init checksum .iff MOV #CHECK,PK$CKS ;Set CHECK pattern .endc CALL OUTPUT ;wait for output ready. MOV PK$FLG,@R2 ;output 1st word. ;XMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXXM .if ne,MMG$T MOV HLPCQE,R4 TST R5 ;User- of local buffer? BEQ XLOOPX .endc ; ne,MMG$T XLOOP: CALL OUTPUT ;wait for output ready. .if NE,CKS MOV (R5),@R2 ;outp. data ADD (R5)+,PK$CKS ;add it to the checksum ADC PK$CKS ;end around carry .iff MOV (R5)+,@R2 ;outp. data .endc DEC WCNT ;are we done? BNE XLOOP .if ne,MMG$T BR ENDXLP XLOOPX: CALL OUTPUT ;wait for output ready. CALL @$GTBYT MOVB (SP)+,XMSAVE ;store the data local buffer CALL @$GTBYT MOVB (SP)+,XMSAVE+1 ;store the data local buffer MOV XMSAVE,@R2 ;outp. data .if NE,CKS ADD XMSAVE,PK$CKS ;add it to the checksum ADC PK$CKS ;end around carry .endc DEC WCNT ;are we done? BNE XLOOPX ENDXLP: .endc ; ne,MMG$T ;XMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXXM CALL OUTPUT ;wait for output ready. MOV PK$CKS,@R2 ;output checksum c.q. CHECK ; ; speeding up: ; CMPB PK$OPC,#R$$WRT ;is it a write? BNE PKTRTN ;No, then to PacKeTReTurN CMPB PK$FLG,#R$MSG ;Command? BEQ 5$ ;Yes then go. No, next check. CMP I$WRDC,#R$DSIZ ;Last packet for write? BLOS GTXEND ;Then don't expect a CONTINUE 5$: CALL INPUT ;Wait for input RCVCNT: MOV @R1,R4 ;Get it CMPB R4,#R$CDAT ;Is it CONTINUE WITH DATA? BEQ PKTRTN ;Yes normal return MOV R4,PK$FLG ;Set flag for RCVPKT CLR I$EFLG ;This flag is never expected BR GETEND ;Get ?END?-packet GTXEND: JMP TXEND ; packet routine return PKTRTN: JMP @I$SUBR ;and return from subroutine ; ; .SBTTL RCVPKT - RECEIVE A RADIAL SERIAL PACKET ;----------------------------------------------- ; I$EFLG expected flagbyte, entered in .INTEN state ; CALL RCVPKT ; I$MBFR = packet if not expected type, unless data packet in which ; case abort is entered. RCVPKT: MOV (SP)+,I$SUBR ;save subr. return CALL INPUT ;and come back here RCVGO: MOV @R1,R4 ;save word. MOV R4,PK$FLG ;save the char for a flag CMPB R4,I$EFLG ;flag expected? BEQ OKEY ;yes OK. GETEND: CMPB R4,#R$MSG ;message packet? BNE ABORCV ;No, then unexpected error MOV PC,R5 ;PIC ADD #I$MBFR-.,R5 ; address of message buffer OKEY: MOV #R$DSIZ,WCNT ;Set counter for full pkt. TSTB PK$MWC ;O.K.? BEQ 6$ ;Yes, go. CLR WCNT ;No BISB PK$MWC,WCNT ; then set correctly. 6$: CMPB #R$DATA,PK$FLG ;Going to receive DATA? BNE 1$ MOV I$WRDC,R4 ;See if we are going SUB WCNT,R4 ; outside mem. buffer. BLT ABORCV ;If so do'not do it. 1$: .if NE,CKS MOV PK$FLG,PK$CKS ;init. checksum .iff MOV #CHECK,PK$CKS ;init. with CHECK .endc ;XMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXXM .if ne,MMG$T MOV HLPCQE,R4 TST R5 BEQ RLOOPX .endc ; eq,MMG$T RLOOP: CALL INPUT .if NE,CKS MOV @R1,(R5) ;store the data in buffer ADD (R5)+,PK$CKS ;add in current checksum ADC PK$CKS ;add in end around carry .iff MOV @R1,(R5)+ ;store the data in buffer .endc DEC WCNT ;any more words? BNE RLOOP ;yes, go get 'em .if ne,MMG$T BR ENDRLP RLOOPX: CALL INPUT MOV @R1,-(SP) ;Value on stack .if NE,CKS ADD (SP),PK$CKS ;add in current checksum ADC PK$CKS ;add in end around carry .endc CALL @$PTWRD ;store the data in buffer DEC WCNT ;any more words? BNE RLOOPX ;yes, go get 'em ENDRLP: .endc ; ne,MMG$T ;XMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXMXXM CALL INPUT MOV @R1,R4 CMP R4,PK$CKS ;is it correct? BNE 5$ ;checksum error CMPB PK$FLG,I$EFLG ;flag we expected? BEQ PKTRTN ;yes, OK goto common return JMP ENDANA ;no signal(INIT?) error, i.e. END-packet 5$: ABORCV: JMP ABORT ;Nope- fatal error .SBTTL DATA AREA ; WCNT: .WORD 0 ;Locally counter for nr. packet words. I$ADRS: .WORD 0 I$WRDC: .WORD 0 I$SUBR: .WORD 0 I$EFLG: .WORD 0 I$MBFR: I$MOPC: .BYTE 0 I$MSUC: .BYTE 0 I$SPFE: .WORD 0,0,0,0 ;SPFUN/SPDIR error return block! PK$FLG: .BYTE 0 PK$MWC: .BYTE 0 PK$OPC: .BYTE 0 PK$MOD: .BYTE 0 PK$UNT: .BYTE 0 PK$SPF: .BYTE 0 PK$SSQ: .BYTE 0,0 PK$BCT: .BYTE 0,0 PK$RCD: .BYTE 0,0 PK$CKS: .BYTE 0,0 .iif ne,MMG$T XMSAVE: .WORD 0 ; .SBTTL BOOTSTRAP READ ROUTINE ;----------------------------- .DRBOT PD,BOOT1,READ PDCNT = 7 ; ATTENTION: Omit the next assignment if the name of the bootable Handler ; on disk is PD.SYS!! .IF EQ,WB B$DNAM=^RDR ;DR is the name of the bootable driver on disk .IFF B$DNAM=^RWB ;WB is the name of the bootable driver on disk .ENDC ;WB . = PDBOOT+40 BOOT1: JMP @#BOOT-PDBOOT . = PDBOOT+210 READ: MOV #PDCNT,RTRCNT MOV @#B$DEVU,PDUNIT ADD #UNIT0,PDUNIT MOV R0,PDBLK ;Contains blocknr. to read MOV R1,PDBTCT ; " nr. words to read BRESTR: MOV R2,-(SP) ;Mem. buff. adres, save. MOV (PC)+,R0 .IF EQ,WB BOOCSR: .WORD PD$CSR ;Output status reg. .IFF BOOCSR: .WORD PD$CSR+4 ;Output status reg. .ENDC WAIT: TSTB @R0 ;Output ready? BPL WAIT .IF EQ,WB TST 4(R0) ;clear input reg. .IFF TST -2(R0) ;clear input reg. .ENDC ; ; Send command packet. ; MOV #B$CHK-PDBOOT,R4;Point to checksum. .if NE,CKS CLR @R4 ;Init=clear checksum. .iff MOV #CHECK,@R4 ;Init=CHECK .endc MOV #B$PKT-PDBOOT,R5;Point to packet. 1$: MOV (R5)+,R3 ;Get packet word. .if NE,CKS ADD R3,@R4 ;update ADC @R4 ; checksum. .endc CALL BCHROS ;send word CMP R5,R4 ;End of packet BLOS 1$ ;no ; ; Receive bootstrap data and store them. ; BRDPKT: CALL BICHR ;R1 contains receiv. word. MOV #R$DSIZ,R4 ;Set to full packet count. TSTB R3 ;O.K. BEQ 3$ ;Yes, then go. CLR R4 ;No. BISB R3,R4 ;R3 " swapped R1, packetwordcnt. 3$: .if NE,CKS MOV R1,-(SP) ;init checksum .iff MOV #CHECK,-(SP) ;init with CHECK .endc CMPB R1,#R$DATA ;data packet? BNE BEND ;no, then must be endpacket. 2$: CALL BICHR ;input next. MOV R1,(R2)+ ;store data in memory buff. .if NE,CKS ADD R1,@SP ;Update ADC @SP ; checksum .endc SOB R4,2$ CALL BICHR ;checksum! CMP R1,(SP)+ ;O.K.? BNE BFATAL ;no, then branch. BR BRDPKT ;and again. BEND: CALL BICHR ;Receive Endpacket MOVB R3,R5 ;Save succescode. 1$: .if NE,CKS ADD R1,@SP ;and ADC @SP ; receive .endc CALL BICHR ; rest SOB R4,1$ ; of END CMP R1,(SP)+ ; packet. BNE BFATAL ;checksum O.K.? TSTB R5 ;check BMI BFATAL ;Succes or error? MOV (SP)+,R2 CLC ;make sure carry clear upon RETURN ;return. BFATAL: MOV (SP)+,R2 DEC RTRCNT BNE BRESTR BR BIOERR ; BICHR: .IF EQ,WB TST (R0) ;Input ready bit = highest bit! BPL BICHR MOV 4(R0),R1 ;R0 points to status reg.: .IFF TSTB -4(R0) ;Input ready bit = highest bit! BPL BICHR MOV -2(R0),R1 ;R0 points to status reg.: .ENDC MOV R1,R3 ;COPY, lowbyte R3=packet word cnt. SWAB R3 ; 2 = PD$CSR+2 = output buffer RETURN ; 4 = PD$CSR+4 = input buffer BCHROS: MOV R3,2(R0) 1$: TSTB (R0) ;Output ready bit = No. 7 !! BPL 1$ RETURN B$PKT: .BYTE R$MSG,R$MSIZ,R$$RED,0 PDUNIT: .WORD 0 .BYTE 0,0 PDBTCT: .WORD 0 PDBLK: .WORD 0 B$CHK: .WORD 0 RTRCNT: .WORD 0 ; ; ; . = PDBOOT+606 BOOT: MOV #10000,SP MOV R0,@#B$DEVU ;001 MOV R0,-(SP) ;**-1 MOV #2,R0 MOV #<4*400>,R1 MOV #1000,R2 JSR PC,READ MOV #READ-PDBOOT,@#B$READ MOV #B$DNAM,@#B$DEVN MOV (SP)+,@#B$DEVU JMP @#B$BOOT .DREND PD .END