.title xhboot .enabl lc ;+ ; ; DELQA Boot ROM replacement. The original DEQNA/DELQA ROM is copyrighted by ; DEC and anyway the diagnostics depend on specific details of the hardware so ; even if were legal to use DEC's ROM it wouldn't work on emulated hardware. ; ; By John Wilson . ; ; Copyright (C) 2000, 2010 by Digby's Bitpile, Inc. All rights reserved. ; Free distribution is allowed as long as source is available, giving Digby's ; Bitpile, Inc. first billing as the author. ; ; 02/09/2000 JMBW Created. ; 02/24/2000 JMBW Works. ; 05/04/2010 JMBW Works again (huh?). RX timeouts (if LTC present). ; Displays MAC addresses of PDP-11 and MOP server. ; 11/01/2010 JMBW Leaves load server addr in 30::35. ; (Traced execution of TERQNA.SYS -- it needs this.) ; ; The code here is all position-independent, except for the addresses used for ; holding the boot/diag ROM and receive frame buffer while booting, and THEM ; which must be in low memory for TERQNA to find it. ; ;- laddr= 2000 ;load address for boot/diag ROM faddr= 120000 ;address of RX frame buffer haddr= 150000 ;high relocation addr (last 4 KB of memory) ; ttcsr= 177564 ;console DL11 output CSR ttbuf= 177566 ;console DL11 output buf lks= 177546 ;50/60 Hz clock CSR lkvec= 100 ;50/60 Hz clock vector pr7= 340 ;CPU priority with ints disabled timout= 5*60.+1 ;RX timeout = 5/6 seconds (for 60/50 Hz) ; lf= 12 cr= 15 ; xh$ad0= 00 ;offsets for reading 6-byte SA PROM xh$ad1= 02 xh$ad2= 04 xh$ad3= 06 xh$ad4= 10 xh$ad5= 12 ; xh$rdl= 04 ;offset for writing rcv buffer descriptor list xh$xdl= 10 ;offset for writing xmt buffer descriptor list ; xh$vec= 14 ;offset for reading/writing vec and DELQA bit xh$csr= 16 ;offset of CSR ; ; CSR bits: ; xh.ri= 100000 ;R/CL rcv int req ;xh.rr= 040000 ;(reserved) xh.ca= 020000 ;RO carrier xh.ok= 010000 ;RO xcvr fuse OK ;xh.rr= 004000 ;(reserved) xh.se= 002000 ;RW sanity timer enable xh.el= 001000 ;RW external loopback xh.il= 000400 ;RW internal loopback (active low) xh.xi= 000200 ;R/CL xmt int req xh.ie= 000100 ;RW interrupt enable xh.rl= 000040 ;RO rcv list invalid xh.xl= 000020 ;RO xmt list invalid xh.bd= 000010 ;RW put boot/diag ROM in rcv buf chain xh.ni= 000004 ;RO NXM int xh.sr= 000002 ;RW software reset xh.re= 000001 ;receiver enable ; xh.id= 000001 ;DELQA ID bit in XH$VEC ; .macro mova addr,reg ;move address (using PIC code) mov pc,reg ;addr of next instruction add #-.,reg ;add offset .endm ; .asect .=0 ; MOP frame layout mp$dst: .blkb 6 ;dest addr mp$src: .blkb 6 ;source addr mp$prt: .word ;protocol (60-01) mp$len: .word ;length of data field (PDP-11 byte order) mp$dat: ;data field mp$cod: .blkb ;first byte is command code ; .=0 ;starts at 0, so generate as .LDA not .SAV start: nop ;+00 = NOP like any bootstrap br boot1 ;+02 = BR to bootstrap br diag ;+04 = BR to hardware/citizenship test .word 7776 ;+06 = offset of checksum word br boot1 ;+10 = BR to test+bootstrap word12: .word 0 ;+12 = addr to JMP to on error, or 0 to HALT ; boot1: jmp boot ;(+14/16) jump over diagnostic/init code ; ;these fit in the gap here: us: .blkb 6 ;(+20-25) our Ethernet address prot: .byte 140,001 ;(+26) protocol (60-01) .=30 ;+30 TERQNA.SYS expects load server addr here them: ; their Ethernet address (whoever we're talking to right now) .byte 253,000,000,001,000,000 ;AB-00-00-01-00-00 ;+ ; ; Diagnostic entry point. ; ; r1 CSR address ; r2 work space (identity-mapped if MMU is turned on, so OK for DMA) ; pc *not* necessarily identity-mapped so no DMA ; ;- diag: inc r2 ;force even bic #1,r2 ; set up descriptor addresses in scratch buffer (DMA accessible) mov r2,txbdla ;transmit buffer descriptor list add #<6*3>*2,r2 ;leave space for three descriptors mov r2,rxbdla ;receive buffer descriptor list add #<6*3>*2,r2 ;SETUP frame buffer comes next ; reset port mov #xh.sr,xh$csr(r1) ;set SR clr xh$csr(r1) ;clear it again ; fetch SA PROM contents mov r1,r3 ;copy starting addr mova us,r4 ;point at where to keep our addr mov #6,r5 ;byte count 10$: mov (r3)+,r0 ;get next byte of addr movb r0,(r4)+ dec r5 ;done all? bne 10$ ;loop if not mov #xh.il,xh$csr(r1) ;no internal loopback ; get device type (DEQNA vs. DELQA) for REQUEST PROGRAM frames mov #xh.id,xh$vec(r1) ;set ID bit bit #xh.id,xh$vec(r1) ;did it stick? beq 20$ ;no, leave code/name for DEQNA movb #37.,devtyp ;change to code for DELQA mov #"LQ,name+2 ;fix name too 20$: ; build SETUP frame to set this receive address ; (no broadcast address needed yet though) mov #256.,r0 ;init byte count add r0,r2 ;point past end asr r0 ;word count 30$: clr -(r2) ;clear a word dec r0 ;done all? bne 30$ ;loop if not mov r2,r5 ;copy addr mova us,r0 ;point at our address mov #6,r3 ;outer loop count 40$: mov #7,r4 ;inner loop count inc r5 ;skip empty first column 50$: movb (r0),100(r5) ;write 2nd copy movb (r0),(r5)+ ;and 1st copy, increment dec r4 ;done all? bne 50$ ;loop if not inc r0 ;bump to next byte of addr dec r3 ;done all 6 bytes? bne 40$ ;loop if not ; add broadcast address to list mov r2,r5 ;copy again add #50+1,r5 ;point at end of first target addr 60$: movb #377,(r5) ;insert an FF sub #10,r5 ;back to previous byte cmp r5,r2 ;past beginning? bhi 60$ ;loop if not ; send frame 3 times, to turn off all LEDs on real DELQA mov r2,r5 ;copy yet again mov #128.+124,r4 ;timeout=4 minutes, and turn off LED #1 70$: ; DELQA gets stuck unless it has a valid receive buffer for dumping ; the ESETUP frame (echo of SETUP frame) mov rxbdla,r0 ;get starting RX BDL address mov r0,xh$rdl(r1) ;set low word of BDL address mov #100000,r3 ;handy constant mov r3,(r0)+ ;init flag word mov r3,(r0)+ ;set addr desc bits, addr MSBs=0 mov r5,(r0) ;starting addr add #1024.,(r0)+ ;receive ESETUP in memory following SETUP mov #-<400/2>,(r0)+ ;word count mov r3,(r0)+ ;not yet filled mov r3,(r0)+ ;unequal bytes, according to manual mov r3,(r0)+ ;next descriptor is owned by DELQA but invalid mov #5+6,r2 ;word count to finish 2 descs 80$: clr (r0)+ ;clear dec r2 ;done all? bne 80$ ;loop if not clr xh$rdl+2(r1) ;write high addr bits ; ready to receive (and ignore) ESETUP, now send SETUP mov r4,-(sp) ;save mov r5,-(sp) mov #130000,r2 ;valid, end of msg, SETUP frame call txfrm1 ;send it mov (sp)+,r5 ;restore mov (sp)+,r4 90$: mov xh$csr(r1),r0 ;fetch CSR bpl 90$ ;haven't received ESETUP echo yet mov r0,xh$csr(r1) ;here it is, clear XH.RI add #4,r4 ;bump to next LED bit #14,r4 ;done all 3? bne 70$ ;loop if not ; return success (as if we really tested something) clr r0 ;pointless to test emulated hardware rts pc ;so always say we're happy ; ; Buffer descriptor list for downloading boot/diag ROM. ; bdbdl: ; first buf is for first 2 KB (manual says 2 KB at a time) .word 100000 ;flag word .word 100000,laddr ;addr for first chunk (2 KB) .word -<2048./2> ;word count for 2 KB .word 100000,0 ;not yet filled ; second buf is for all but the last word of the second 2 KB .word 100000 ;flag word .word 100000,laddr+2048. ;addr for second chunk (2 KB -2) .word -<2048./2> ;word count for 2 KB bddone: .word 100000,0 ;not yet filled ; end of descriptor list .rept 2 ;just to be safe (does DELQA read an extra?) .word 100000 ;flag word .word 0,0 ;address (invalid) .word 0 ;length .word 0,0 ;status words, end of chain .endr ;+ ; ; Boot system from MOP dump/load server. ; ; r0 boot flag (should be 0) ; r1 CSR address ; ;- boot: ; download the rest of the boot/diag ROM mov #xh.sr,xh$csr(r1) ;set SR clr xh$csr(r1) ;clear it again mov #xh.el,xh$csr(r1) ;set external loopback mova bdbdl,r0 ;get addr of boot/diag BDL mov r0,xh$rdl(r1) ;low word of rcv BDL addr clr xh$rdl+2(r1) ;high word =0 mov #xh.el!xh.il!xh.bd,xh$csr(r1) ;set bit to download ROM mov #250.,r0 ;loop count 10$: tst (r1) ;Q-bus cycle, takes 1/2 usec or so dec r0 ;count it bne 10$ ;need to delay 100 usec mov #xh.el!xh.il,xh$csr(r1) ;clear it again, should start loading 20$: cmp bddone,#140000 ;buf control bits still 10? blt 20$ ;yes .iif gt <.-start>-512., .err ;too much code above this point ;("BOOT XH:" command loads only 512. bytes) jmp @#30$+laddr ;continue in new copy 30$: mov #haddr,sp ;11-word stack stack goes between buf + code mov #12000,r2 ;scratch area for SETUP frame etc. call diag ;reinit port, get value for US mov #xh.il!xh.re,xh$csr(r1) ;enable receiver ; I don't know what the rules are for load addresses, but the image ; I'm testing against starts at 002000 so we'll go to high mem on the ; assumption that that's typical mov #haddr,r5 ;high memory mov #laddr,r4 ;where we loaded mov #10000/2,r3 ;word count 40$: mov (r4)+,(r5)+ ;copy it dec r3 ;loop bne 40$ add #haddr-laddr,pc ;up we go ; say hello jsr r5,print name: .asciz /DEQNA / ;(patched by DIAG) .even mova us,r5 call pmac ; see if we have a 50/60 Hz clock mova 10$,r0 ;set vector for bus timeout mov r0,@#4 mov #pr7,@#4+2 tst @clkcsr ;probe KW11L clock br 20$ 10$: cmp (sp)+,(sp)+ ;flush stack from trap to 4 mov #dummy,clkcsr ;don't really touch clock 20$: ; set addresses of buffer descriptor lists mova txbdl,r0 ;find final addr of TX BDL mov r0,txbdla ;save for TXFRM mova rxbdl,r0 ;same for RX BDL mov r0,rxbdla 30$: ; send the "request program" frame (to load server mcast group) mova reqprg,r5 ;point at frame mov #60.,r4 ;length call txfrm ;send it 40$: call rxfrm ;get response bcs 30$ ;retry tst mp$len(r5) ;must have NZ length beq 40$ cmpb mp$cod(r5),#3 ;code = assistance volunteer? bne 40$ ; someone likes us, so ask them personally mov #them,r0 ;where to keep their addr mov #6,r2 ;count add r2,r5 ;point at source addr 50$: movb (r5)+,(r0)+ ;copy into THEM dec r2 bne 50$ .if ne 0 ; maybe this is too much clutter ; print their addr jsr r5,print .asciz /Server / .even mov #them,r5 call pmac .endc mova reqprg,r5 ;point at frame mov #60.,r4 ;length 60$: mov r5,frmadr ;save addr/length mov r4,frmlen 70$: mov frmadr,r5 ;fetch mov frmlen,r4 call txfrm ;send frame 80$: ; wait for next memory load [with transfer address] frame call rxfrm ;get response bcs 70$ ;retry tst mp$len(r5) ;must have NZ length beq 80$ movb mp$cod(r5),r0 ;get code beq 100$ ;code = memory load w/transfer addr cmp r0,#20. ;code = parameter load w/transfer addr? beq 130$ ;(only if we requested OS image) cmp r0,#2 ;code = memory load? beq 150$ br 70$ ;repeat the last thing we sent 90$: ; ask for whatever frame we expect now mova reqmld,r5 ;point at frame mov #60.,r4 ;length br 60$ ;go send it 100$: ; memory load w/transfer addr cmp mp$len(r5),#6 ;missing load address *and* image data? beq 120$ ;yes, easy sub #4,mp$len(r5) ;remove length from count bcs 70$ ;invalid frame, ignore call ldmem ;load memory bcs 70$ ;invalid 110$: jsr r5,print ;blank line .byte cr,lf,0,0 clr r0 ;clear addr bisb (r5)+,r0 ;load low 16 bits of xfr addr swab r0 bisb (r5)+,r0 swab r0 jmp (r0) ;and away we go 120$: call ldmem ;load nothing, check seq # bcs 70$ ;bad sequence # jsr r5,print ;blank line .byte cr,lf,0,0 jmp (r3) 130$: ; parameter load w/transfer addr mov mp$len(r5),r2 ;get length sub #1+1+4,r2 ;account for code, sequence #, load addr bcs 70$ ;length too short add #mp$cod+1,r5 ;advance to seq # cmpb (r5)+,seq ;check it bne 70$ 140$: dec r2 ;check next option bmi 70$ movb (r5)+,r0 ;fetch it beq 110$ ;end mark -- go get transfer addr and go dec r2 ;check length bmi 70$ clr r0 ;zero-extend bisb (r5)+,r0 ;get length of option add r0,r5 ;skip it sub r0,r2 ;deduct from count bpl 140$ ;loop if still .GE. 0 br 70$ 150$: ; memory load call ldmem ;load memory bcs 70$ ;invalid frame, ignore br 90$ ;+ ; ; Load memory from received frame. ; ; r5 base of frame buffer ; r1 preserved ; ; On return: ; C=1 if bad format ; Otherwise C=0 and: ; ; r5 updated to point past end of data ; r3 load addr ; ;- ldmem: mov mp$len(r5),r2 ;get length sub #1+1+4,r2 ;account for code, sequence #, load addr bcs 40$ ;length too short add #mp$cod+1,r5 ;advance to seq # clr r0 ;zero-extend bisb (r5)+,r0 ;get sequence # beq 10$ ;already 0, reset numbers cmpb r0,seq ;what we expect? bne 40$ ;no 10$: inc r0 ;# to expect next movb r0,seq ;update clr r3 ;init addr bisb (r5)+,r3 ;pick up low word swab r3 bisb (r5)+,r3 swab r3 ;get it the right way around add #2,r5 ;skip high 2 bytes of addr tst r2 ;check length beq 30$ ;nothing to do 20$: movb (r5)+,(r3)+ ;copy a byte dec r2 ;loop bne 20$ 30$: tst (pc)+ ;happy 40$: sec ;error rts pc ;+ ; ; Transmit a frame. ; ; r5 address of frame (in low 64 KB), dest/src addrs will be inserted ; r4 length (in bytes) ; r1 CSR base (preserved) ; ;- txfrm: ; prepend source address mov #them,r0 ;point at remote Ethernet address mov #6,r2 ;byte count mov r2,r3 ;(copy) 10$: movb (r0)+,(r5)+ ;insert our source address dec r2 ;done all? bne 10$ ;loop if not mova us,r0 ;same deal for local addr 20$: movb (r0)+,(r5)+ ;insert our source address dec r3 ;done all? bne 20$ ;loop if not sub #6+6,r5 ;point back at start ; fill out BDL for this frame mov #120000,r2 ;initialize addr descriptor bits txfrm1: ; enter here to send SETUP frame (regs as above, plus address ; descriptor bits (for 2nd word of buf descriptor) are in R2 cmp r4,#60. ;runt frame? bhi 10$ mov #60.,r4 ;add whatever junk follows it in memory if so 10$: bit #1,r4 ;odd? beq 20$ bis #200,r2 ;yes, set "low byte only termination" bit inc r4 ;and count it as a word 20$: mov txbdla,r0 ;get starting TX BDL address mov r0,xh$xdl(r1) ;set low word of BDL address mov #100000,(r0)+ ;init flag word mov r2,(r0)+ ;save addr desc bits, addr MSBs=0 mov r5,(r0)+ ;starting addr asr r4 ;word count neg r4 ;2's comp mov r4,(r0)+ ;save mov #100000,(r0)+ ;not yet filled mov #6+6+1,r2 ;word count to finish this and 2 more descs 30$: clr (r0)+ ;clear dec r2 ;done all? bne 30$ ;loop if not ; actually start transmission clr xh$xdl+2(r1) ;write high addr bits 50$: mov xh$csr(r1),r0 ;wait for XI tstb r0 bpl 50$ bic #100000,r0 ;don't acknowledge reception mov r0,xh$csr(r1) ;but clear XI rts pc ;+ ; ; Receive a frame. ; ; r5 returns address ; r4 returns length ; r1 CSR base (preserved) ; ; C=1 on timeout. ; ;- rxfrm: ; temporarily enable clock interrupts mov (sp),-(sp) ;duplicate return addr (for stack = PC, PS) mov #pr7,2(sp) ;disable ints again when we return mov #lkvec,r3 ;point at vector mova lkisr,r0 ;and int service routine mov (r3)+,-(sp) ;save (in case loaded program covers vector) mov (r3),-(sp) mov #pr7,(r3) ;set vector for our routine mov r0,-(r3) clr time ;init count mov #100,@clkcsr ;enable clock ints (or not if no clock) ;(can't just poll, since some Q-bus LTCs don't ;maintain the "monitor" bit in b7) clr -(sp) ;set up stack = PC, PS=0 call 60$ ;go enable ints 10$: ; make sure DELQA is ready to receive cmp #timout,time ;timed out? (C=1 if so) blo 50$ ;yes bit #xh.rl,xh$csr(r1) ;null desc. from last time picked up yet? beq 10$ ;can't set new RX BDL head until then, so spin mov #faddr,r5 ;point at frame buf mov rxbdla,r0 ;get starting RX BDL address mov r0,xh$rdl(r1) ;set low word of BDL address mov #100000,r3 ;handy constant mov r3,(r0)+ ;init flag word (DELQA owns descriptor) mov r3,(r0)+ ;set addr desc bits, addr MSBs=0 mov r5,(r0)+ ;starting addr mov #-<<6+6+2+1500.>/2>,(r0)+ ;word count mov r3,(r0)+ ;not yet filled mov r3,(r0)+ ;unequal bytes, according to manual mov r3,(r0)+ ;next descriptor is owned by DELQA but invalid mov #5+6,r2 ;word count to 2 empty descs 20$: clr (r0)+ ;clear dec r2 ;done all? bne 20$ ;loop if not ; actually start reception (frame probably buffered inside DELQA) clr xh$rdl+2(r1) ;write high addr bits 30$: cmp #timout,time ;timed out? (C=1 if so) blo 50$ ;yes mov xh$csr(r1),r0 ;wait for RI bpl 30$ bic #200,r0 ;don't acknowledge transmission mov r0,xh$csr(r1) ;but clear RI ; check dest addr to make sure it's ours mov r5,r3 ;copy start of frame mova us,r2 ;our addr mov #6,r0 ;byte count 40$: cmpb (r3)+,(r2)+ ;match? bne 10$ ;no, keep looking dec r0 ;count it bne 40$ ;loop if not done cmp mp$prt(r5),prot ;does protocol match? bne 10$ ;ignore if not ; it's ours, extract the length and return mov rxbdla,r0 ;get starting RX BDL address mov 10(r0),r4 ;get bits 10:8 of frame length bic #^C3400,r4 ;isolate bisb 12(r0),r4 ;get bits 7:0 add #60.,r4 ;add base length, C=0 50$: ; disable clock, restore vector, and disable interrupts ; C bit is set up adc 4+2(sp) ;add C bit to stacked PS (=PR7 from entry) clr @clkcsr ;disable clock (or not if none) mov (sp)+,@#lkvec+2 ;restore vector mov (sp)+,@#lkvec 60$: rti ;enable/disable ints (works on any CPU model) ; lkisr: ; 50/60 Hz clock ISR inc (pc)+ ;update time time: .word ;counts up during RXFRM rti ;+ ; ; Print a MAC address. ; ; r5 points at 6-byte MAC address ; ;- pmac: mova 20$,r4 ;where to write mov #6,r3 ;loop count 10$: movb (r5),r0 ;get high byte asr r0 ;right 4 bits asr r0 asr r0 asr r0 call 30$ movb (r5)+,r0 ;get low byte call 30$ inc r4 ;skip '-' (or not if last byte) dec r3 ;done all? bne 10$ ;loop if not jsr r5,print ;print it 20$: .asciz /AA-BB-CC-DD-EE-FF/ .even rts pc ; 30$: ; convert # in R0<3:0> to hex at (R4)+ bic #^C17,r0 ;isolate cmp r0,#10. ;A-F? blo 40$ add #'A-<'9+1>,r0 ;skip gap if so 40$: add #'0,r0 ;convert to digit movb r0,(r4)+ ;save rts pc ;+ ; ; Print inline string on TTY. ; ; JSR R5,PRINT ; .ASCIZ /string/ ; .EVEN ; ... return here ; ; r0 destroyed ; others preserved ; ;- print: movb (r5)+,r0 ;get char beq 20$ ;end of string (NUL) 10$: tstb @#ttcsr ;ready to send? bpl 10$ movb r0,@#ttbuf ;send if so br print 20$: inc r5 ;.EVEN bic #1,r5 rts r5 ; ; Copyright notice must appear in binary file: ; .ascii /Copyright (C) 2000, 2010 by Digby's Bitpile, Inc. / .asciz /All rights reserved./ ; ; REQUEST PROGRAM frame. ; reqprg: .blkb 6+6 ;dest, source addrs .byte 140,001 ;60-01 .word reqlen ;length, LSB first reqdat: .byte 8. ;CODE = REQUEST PROGRAM devtyp: .byte 5 ;DEVICE TYPE = DEQNA (5) or DELQA (37.) .byte 1 ;FORMAT VERSION = 1 .byte 1 ;PROGRAM TYPE = tertiary loader .byte 0 ;SOFTWARE ID (default -- no filename) .byte 0 ;PROCESSOR = system processor (default) .byte 401.&377,401./400 ;DATA LINK BUFFER SIZE .byte 2 ;(2 bytes) .byte 1514.&377,1514./400 ;1514. bytes (including DIX header) reqlen= .-reqdat .rept 60.-<.-reqprg> .byte 0 ;pad to minimum size .endm ; ; REQUEST MEMORY LOAD frame. ; reqmld: .blkb 6+6 ;dest, source addrs .byte 140,001 ;60-01 .word 3 ;length, LSB first .byte 10. ;CODE = REQUEST MEMORY LOAD seq: .byte 0 ;sequence # we want .byte 0 ;we would have crashed if there were an error .rept 60.-<.-reqmld> .byte 0 ;pad to minimum size .endm ; .even frmadr: .blkw ;addr of frame we're transmitting frmlen: .blkw ;length of frame we're transmitting ; txbdla: .blkw ;TX BDL address rxbdla: .blkw ;RX BDL address ; clkcsr: .word lks ;pointer to KW11L clock CSR, or DUMMY if none dummy: .blkw ;writing here has no effect ; ; These descriptor list areas are used for the bootstrap entry point. ; ; The diagnostic entry point allocates them in the scratch area that R2 points ; to, since the code area may not be identity-mapped so DMA may not work ; here). ; txbdl: .blkw 6*3 ;one real descriptor, two null ones mark end ;(just to be safe) rxbdl: .blkw 6*3 ;as above ; .end start