I've made progress getting my S-100 system up and running but not quite there yet. The big news is I found the listings I made for Dos/65, including
the Loader version that I wrote to ROM. This particular listing is for a ROM in my S-100 system but I believe it is the same as what I wrote to the Monitor ROM except of the load address. Attached is the scan of the listing.
Upgrade 610 from 2114 RAM to 6264 8K x 8
-
- Posts: 204
- Joined: Sat Aug 27, 2022 4:52 pm
Re: Upgrade 610 from 2114 RAM to 6264 8K x 8
- Attachments
-
- DOS-65LoaderInROM.pdf
- (405.92 KiB) Downloaded 341 times
-
- Posts: 333
- Joined: Tue Sep 16, 2008 6:04 am
- Location: Madison, WI
- Contact:
Re: Upgrade 610 from 2114 RAM to 6264 8K x 8
I was able to run the pdf through an OCR program and generate text from it.
Besides the starting address, it matches the ROM dump you had earlier except the version number is 2.1 instead of 2.0, and the screen clear was corrected (starts at $D000 instead of $D300).
The attached file can be assembled by A65 or the DOS/65 assembler.
I'll included it below too...
At some point it would be great if you could dump the data from your DOS/65 floppy. I don't think there are any DOS/65 C1P disk dumps floating around out there yet.
Cheers!
Besides the starting address, it matches the ROM dump you had earlier except the version number is 2.1 instead of 2.0, and the screen clear was corrected (starts at $D000 instead of $D300).
The attached file can be assembled by A65 or the DOS/65 assembler.
I'll included it below too...
At some point it would be great if you could dump the data from your DOS/65 floppy. I don't think there are any DOS/65 C1P disk dumps floating around out there yet.
Cheers!
Code: Select all
;DOS/65 LOADER
;OSI Version
;for c1p and sbii
;Version 2.10
;released: 4 august 1983
;The OSI LOADER and BOOT are unique due to
;the total impossibility of putting all BOOT
;code into a single DOS/65 sector. The
;approach taken is to have all the code in
;LOADER and to have BOOT supply the variable
;data such as load address and sectors to
;load. LOADER can be located in ROM
;and need not change as MSIZE or PAGES
;changes.
;definitions
speed = 49 ;49=1MHz
numtrk = 40 ;number of tracks
sectrs = 16 ;sectors per track
stprte = 5 ;step rate in ms
;osi addresses and parameters ;
scrpgs = 4 ;pages to clear in screen
screen = $d385 ;prompt location
scrcnt = $d800 ;control port for video
romkbd = $fd00 ;rom polled keyboard input
;pia ;
flpsts = $c000 ;status port
;bit definitions
; 0 drive 0 ready if 0
; 1 track 0 if 0
; 2
; 3
; 4
; 5 write protect if 0
; 6 drive select (0=B or D, 1=A or C)
; 7 index if 0
flpcnt = flpsts+2
;bit definitions
; 0 write enable if 0
; 1 erase enable if 0
; enable 200us after write enable
; disable 530us after write disable
; 2 step
; 4 0 if in
; 1 if out (to track zero)
; 3 step on falling edge
; 4
; 5 side select (0=C or D, 1=A or B)
; 6
; 7 head load if 0
;acia
flpdta = $c011 data port
;page zero data initialized by boot
* =$00
ldeadr *=*+2 load address
pointr =ldeadr just used for screen clear
simadr *=*+2 sim entry address
seclde *=*+1 sectors to load
sectrk *=*+1 sectors per track
nxtsec *=*+1 next sector to read
;page zero data used by LOADER but not
;initialized by BOOT
trkpnt *=*+2 track pointer
rdeadr *=*+2 read address
curtrk *=*+1 current track
;main program
; if in rom change the next line to the appropriate address
* = $e340
ldx #$FF set stack
txs
cld binary mode
sei disable interrupts
;clear screen
loader ldx #scrpgs pages to clear
lda #$d0 starting page
sta pointr+1 and set
ldy #0 clear lower part
sty pointr of pointer
lda #' ' get space
clrslp sta (pointr),y put space on screen
iny bump index
bne clrslp loop if more
inc pointr+1 bump high pointer
dex drop page count
bne clrslp loop if more
;do opening
opnlpe lda opnmsg,x get char
sta screen,x put on screen
inx bump index
cpx #11 see if past end
bne opnlpe loop if not
;initialize pia
lda #%01000000
ldy #0
ldx #%00000100
sty flpsts+1 ddr on a side
sta flpsts all but one are input
stx flpsts+1 back to data
sta flpsts set output to high
sty flpcnt+1 ddr on b side
dey y to ff
sty flpcnt all are output
stx flpcnt+1 back to data
sty flpcnt set all high
jsr home home it
jsr rdytrk get header
bne error branch if error
getv jsr rdlbyt look for rest of header
cmp #'v'
bne getv loop until v
jsr rdlbyt now get number
cmp #1 if not 1
bne error is error
jsr rdlbyt now get length
cmp #sectrs/2 see if correct
bne error error if not
;got good header
ldx #0 clear index
btelpe lda #%00000001 mask for ready
tstflp bit flpdta-1 test acia
beq tstflp loop if not ready
lda flpdta else get byte
bvs error parity error
sta $00,x else put in page zero
inx bump index
bpl btelpe then loop
;got a good boot so all is initialized
;start read again
gettrk jsr rdetrk read entire track
bcs error exit if error
gottrk jsr strkpt set pointer
ldy #0 now move a sector
mvesec lda (trkpnt),y
sta (ldeadr),y
iny
bpl mvesec of 128 bytes
clc add 128 to pointer
tya
adc ldeadr
sta ldeadr
bcc *+4
inc ldeadr+1
dec seclde drop count
beq alllde done if all loaded
inc nxtsec else bump sector
lda nxtsec get it
cmp sectrk compare to max
beq gottrk ok if equal
bcc gottrk or less
lda #1 else reset
sta nxtsec sector
jsr stepin step in a track
jmp gettrk and loop to read
;data all read and moved
alllde jmp (simadr) execute
;general error handler
error jsr unldhd unload head
ldx #0 now send error message
errlpe lda errmsg,x get char
sta screen,x send to screen
inx bump index
cpx #6 see if too big
bne errlpe loop if not
forevr beq forevr else loop forever
;messages
opnmsg .byt 'DOS/65 V2.1'
errmsg .byt 'ERROR!'
;home drive to track zero
home jsr stepin step head in one
jsr dly12m delay 12ms
hlp lda #%00000010 mask for track zero
bit flpsts test it
bne nthome continue if not there
lda #0 clear current
sta curtrk track
rts else done
nthome jsr stepot step out
jmp hlp and loop
;step towards track zero
stepot lda flpcnt get control
ora #%00000100 set direction to out
bne step
;step away from track zero
stepin inc curtrk bump track
lda flpcnt get control
and #%11111011 get direction to in
step sta flpcnt set it
jsr dly12 wait 12 cycles
and #%11110111 set step bit
sta flpcnt set it
jsr dly24 delay 24 cycles
ora #%00001000 clear bit
sta flpcnt set it
ldx #stprte get rate in ms
jmp dlyxm delay the right time
;delay=20*y+14 cycles
dlyy20 jsr dly15 delay 15 cycles
dey drop count
bne dlyy20 loop if more
nop waste time
rts
;delay=15 cycles(if z=0)
dly15 bne *+2
;delay=12 cycles
dly12 rts
;delay=24 cycles
dly24 jsr dly12 do 12
rts
;delay=l2ms
dly12m ldx #12
;delay=xms
dlyxm ldy #speed
jsr dlyy20 do 20 cycles
dex
bne dlyxm loop if more
rts
;load head and wait 40 ms
loadhd lda #%01111111 set load bit
and flpcnt to active
sta flpcnt
ldx #40 delay 40 ms
jmp dlyxm
;unload head
unldhd lda #%10000000 set load bit
ora flpcnt to inactive
sta flpcnt
rts
;set up to read track into buffer
;if header ok then z=1 else z=0
rdytrk jsr loadhd load head with settling delay
sei disable interrupts
fndind lda flpsts read status
bmi fndind not there yet
gotind lda flpsts read again
bpl gotind loop while index
lda #%00000011 master reset
sta flpdta-1
lda #%01011000 no interrupt,rts* high,8+ep+s,/1
sta flpdta-1
trkstr lda flpsts get status
bpl inderr error if index
jsr rdlbyt read a byte
tryc cmp #'C' see if start code
bne trkstr if not keep looking
jsr rdlbyt read next byte
cmp #'W' see if second half
bne tryc if not try for C
jsr rdlbyt get another byte
;the following line works because system tracks
;are low numbers and hex = bcd
cmp curtrk see if correct
bne rdyext error it wrong tract
jsr rdlbyt get next byte
cmp #'X' see if X
rdyext rts
inderr lda #1 say error
rts
;read a byte from disk into a (ignore parity)
rdlbyt lda flpdta-1 get acia status
lsr a check for ready
bcc rdlbyt loop if not
lda flpdta get byte
rts
;set trkpnt to first byte of desired sector in track buffer .
strkpt lda nxtsec get next sector
sec drop b y one
sbc #1
ldy #0 clear high part of pointer
sty trkpnt+1
ldy #7 log2 128
mul128 asl a multiply
rol trkpnt+1
dey
bne mul128 loop til done
clc now add buffer start
adc #<trkbuf
sta trkpnt
lda trkpnt+1
adc #>trkbuf
sta trkpnt+1
rts
;read track into buffer
; if ok then c=0
; if error then c=1
rdetrk lda #<trkbuf point to start of buffer
ldy #>trkbuf
sta rdeadr set pointer
sty rdeadr+1
jsr rdytrk get ready to read
bne rdeerr bad header error
tryv jsr rdlbyt get next byte
cmp #'v' see if v
bne tryv loop until is
jsr rdlbyt and another
cmp #1 if not 1
bne rdeerr is error
jsr rdlbyt get track length
cmp #sectrs/2 compare to correct
bne rdeerr error if wrong
tax make a counter
ldy #0 clear index
rdelpe lda #%00000001 get mask for ready
tstaca bit flpdta-1 test acia
beq tstaca loop if not ready
lda flpdta get byte
bvs rdeerr parity error
sta (rdeadr),y put in memory
iny bump index
bne rdelpe loop if more in page
inc rdeadr+1 bump pointer
dex drop page count
bne rdelpe loop if more pages
clc else done and ok
bcc rdeext then exit
;read error
rdeerr sec
;common read exit
;unload must not alter c bit
rdeext jmp unldhd un load head
;data area
* =$300
trkbuf =*
*=sectrs/2*256+* ;track buffer
.END
- Attachments
-
- DOS-65LoaderInROM.asm
- Text of previously posted pdf assembler listing
- (13.94 KiB) Downloaded 308 times
-
- Posts: 204
- Joined: Sat Aug 27, 2022 4:52 pm
Re: Upgrade 610 from 2114 RAM to 6264 8K x 8
Mark, Danny,
What tool do you use to create the commented source files from my ROM dumps? Or is there an OSI tool that reliably disassembles ROM or memory? The extended monitor will only do one page at a time which is slow. Thanks.
What tool do you use to create the commented source files from my ROM dumps? Or is there an OSI tool that reliably disassembles ROM or memory? The extended monitor will only do one page at a time which is slow. Thanks.
-
- Posts: 460
- Joined: Thu Apr 16, 2015 2:27 pm
- Location: Bronx, NY USA
Re: Upgrade 610 from 2114 RAM to 6264 8K x 8
I don't know what Mark uses to create those re-assemblable disassemblies. I was hoping he would post a reply here answering that, but so far he hasn't.
Standard disassembly can be done with the Extended Monitor, which is actually quite fast. While it pauses after each page of output, the listing can be continued by pressing the <linefeed> key.
There is also the disassembler that I wrote in BASIC, and include as Program 1 on my "Enhanced Pico-Dos" disks. I am including a listing of it here for those who can't use those disk images. It will run on all versions of OSI BASIC: ROM (with or without a garbage-collection fix, including under Hexdos and Pico-Dos), 65D, and 65U (and on a UK101 if an ESCape key is added to the keyboard matrix). It is useful for examining 65D BASIC, which normally gets replaced when the Extended Monitor is loaded, and 65U as well.
Standard disassembly can be done with the Extended Monitor, which is actually quite fast. While it pauses after each page of output, the listing can be continued by pressing the <linefeed> key.
There is also the disassembler that I wrote in BASIC, and include as Program 1 on my "Enhanced Pico-Dos" disks. I am including a listing of it here for those who can't use those disk images. It will run on all versions of OSI BASIC: ROM (with or without a garbage-collection fix, including under Hexdos and Pico-Dos), 65D, and 65U (and on a UK101 if an ESCape key is added to the keyboard matrix). It is useful for examining 65D BASIC, which normally gets replaced when the Extended Monitor is loaded, and 65U as well.
Code: Select all
10 REM DISAS2 PORTIONS COPYRIGHT (C) 1980 ORION SOFTWARE ASSOCIATES
20 DATABRK1,ORA-XI,X,X,X,ORA-Z,ASL-Z,X,PHP1,ORA-IM,ASL-A,X,X,ORA3,ASL3
30 DATAX,BPL2,ORA-IY,X,X,X,ORA-ZX,ASL-ZX,X,CLC1,ORA-Y,X,X,X,ORA-X
40 DATAASL-X,X,JSR3,AND-XI,X,X,BIT-Z,AND-Z,ROL-Z,X,PLP1,AND-IM,ROL-A,X
50 DATABIT3,AND3,ROL3,X,BMI2,AND-IY,X,X,X,AND-ZX,ROL-ZX,X,SEC1,AND-Y,X
60 DATAX,X,AND-X,ROL-X,X,RTI1,EOR-XI,X,X,X,EOR-Z,LSR-Z,X,PHA1,EOR-IM
70 DATALSR-A,X,JMP3,EOR3,LSR3,X,BVC2,EOR-IY,X,X,X,EOR-ZX,LSR-ZX,X,CLI1
80 DATAEOR-Y,X,X,X,EOR-X,LSR-X,X,RTS1,ADC-XI,X,X,X,ADC-Z,ROR-Z,X,PLA1
90 DATAADC-IM,ROR-A,X,JMP-I,ADC3,ROR3,X,BVS2,ADC-IY,X,X,X,ADC-ZX
100 DATAROR-ZX,X,SEI1,ADC-Y,X,X,X,ADC-X,ROR-X,X,X,STA-XI,X,X,STY-Z
110 DATASTA-Z,STX-Z,X,DEY1,X,TXA1,X,STY3,STA3,STX3,X,BCC2,STA-IY,X,X
120 DATASTY-ZX,STA-ZX,STX-ZY,X,TYA1,STA-Y,TXS1,X,X,STA-X,X,X,LDY-IM
130 DATALDA-XI,LDX-IM,X,LDY-Z,LDA-Z,LDX-Z,X,TAY1,LDA-IM,TAX1,X,LDY3
140 DATALDA3,LDX3,X,BCS2,LDA-IY,X,X,LDY-ZX,LDA-ZX,LDX-ZY,X,CLV1,LDA-Y
150 DATATSX1,X,LDY-X,LDA-X,LDX-Y,X,CPY-IM,CMP-XI,X,X,CPY-Z,CMP-Z,DEC-Z
160 DATAX,INY1,CMP-IM,DEX1,X,CPY3,CMP3,DEC3,X,BNE2,CMP-IY,X,X,X,CMP-ZX
170 DATADEC-ZX,X,CLD1,CMP-Y,X,X,X,CMP-X,DEC-X,X,CPX-IM,SBC-XI,X,X
180 DATACPX-Z,SBC-Z,INC-Z,X,INX1,SBC-IM,NOP1,X,CPX3,SBC3,INC3,X,BEQ2
190 DATASBC-IY,X,X,X,SBC-ZX,INC-ZX,X,SED1,SBC-Y,X,X,X,SBC-X,INC-X,X
200 ES=27:IFPEEK(65025)=0THENK=64513:GOTO230
210 K=57089:IFPEEK(65261)=76THENK=K-1:ES=33:IFPEEK(64774)=32THENES=94
230 DIMMN$(255),L(2),H(4),OP(2):PRINT:PRINT:PRINT
240 PRINT" 6502 DISASSEMBLER":PRINT
260 PRINT:PRINT"PRESS 'ESC' TO STOP THE LISTING":PRINT:PRINT:PRINT
270 FORX=0TO255:READMNEM$(X):NEXT
280 LP=129:HP=130:IF1E8+1>1E8THENLP=128:HP=129
290 PL=PEEK(LP):PH=PEEK(HP)
295 IFLP=128ANDPEEK(2039)=34ANDPEEK(14948)=76THENGOSUB1950:REM 65U TS
300 INPUT"START HEX ADDRESS";A$
305 IF LEFT$(A$,1)=CHR$(27) THEN A$=MID$(A$,2)
306 IF LEN(A$)=0 THEN END:GOTO 300
307 IF K=57088 THEN POKE K,1-253*(ES=94)
310 IFLEN(A$)>4ORA$>"FFFE"THENPRINT:GOTO300
320 IFLEN(A$)<4THENA$="0"+A$:GOTO320
330 FORP=1TO4
340 C=ASC(MID$(A$,P))
350 IFC<48ORC>70ORC>57ANDC<65THENPRINT:GOTO300
360 H(P)=C-48+7*(C>60)
370 NEXTP
380 PRINT:PRINT
390 A=4096*H(1)+256*H(2)+16*H(3)+H(4)
400 IFA>65535THENPRINT:GOTO300
410 PRINTA$;" ";
420 OP=PEEK(A)
440 MNEM$=MNEM$(OP)
450 IF MN$="X" THEN MN$="???":B=1:M=0:GOTO 500
460 I=VAL(RIGHT$(MNEM$,1)):IFITHENMNEM$=LEFT$(MNEM$,3):M=I:GOTO491
470 M$=RIGHT$(MN$,2):FOR I=0 TO 9
480 IF M$=MID$("-X-Y-I-ZZXZYIM-AXIIY",2*I+1,2) THEN M=I+4:I=9
490 NEXT:MN$=LEFT$(MN$,3)
491 IF M=1 OR M=11 THEN B=1
492 IF M>2 AND M<7 THEN B=3
493 IF M>6 AND M<>11 OR M=2 THEN B=2
500 FOR I=0 TO B-1
510 D=PEEK(A+I):H=INT(D/16):L=D-16*H
520 PRINTCHR$(H+48-7*(H>9));CHR$(L+48-7*(L>9));:NEXT
525 PRINTTAB(12);MN$;" ";
530 ON M GOSUB 800,850,900,950,1000,1050,1100,1150,1200,1250,1300,1350
540 IF M=13 THEN GOSUB 1400
545 IF M=0 THEN PRINT
670 POKELP,PL:POKEHP,PH
680 A=A+B:GOSUB 710
690 IF(PEEK(K)AND127)=ESTHENPRINT:GOTO300
700 GOTO400
710 OP(1)=INT(A/256):OP(2)=A-256*OP(1)
720 FORI=1TO2
730 O=OP(I)
740 OH=INT(O/16):OL=O-16*OH
750 H=OH+48-7*(OH>9):L=OL+48-7*(OL>9)
760 H(I)=H:L(I)=L
770 NEXTI
780 A$=CHR$(H(1))+CHR$(L(1))+CHR$(H(2))+CHR$(L(2))
790 RETURN
800 PRINT:RETURN
850 AR=A:A=AR+2+PEEK(AR+1):IF A>=AR+130 THEN A=A-256
860 PR$="":SF$="":GOTO 1800
900 AR=A:A=PEEK(AR+1)+256*PEEK(AR+2)
910 PR$="":SF$="":GOTO 1800
950 AR=A:A=PEEK(AR+1)+256*PEEK(AR+2)
960 PR$="":SF$=",X":GOTO 1800
1000 AR=A:A=PEEK(AR+1)+256*PEEK(AR+2)
1010 PR$="":SF$=",Y":GOTO 1800
1050 AR=A:A=PEEK(AR+1)+256*PEEK(AR+2):PR$="(":SF$=")":GOTO 1800
1100 Z=PEEK(A+1):PR$="":SF$="":GOTO 1900
1150 Z=PEEK(A+1):PR$="":SF$=",X":GOTO 1900
1200 Z=PEEK(A+1):PR$="":SF$=",Y":GOTO 1900
1250 Z=PEEK(A+1):PR$="#":SF$="":GOTO 1900
1300 PRINT"A":RETURN
1350 Z=PEEK(A+1):PR$="(":SF$=",X)":GOTO 1900
1400 Z=PEEK(A+1):PR$="(":SF$="),Y":GOTO 1900
1800 GOSUB 710:PRINTPR$;"$";A$;SF$:A=AR:RETURN
1900 H=INT(Z/16):L=Z-16*H
1910 PRINTPR$;"$";CHR$(H+48-7*(H>9));CHR$(L+48-7*(L>9));SF$:RETURN
1950 U=PEEK(55381):NH=PEEK(56556)
1960 IF U=0 AND NH>0 THEN RETURN
1970 K=52737+2*(U-SGN(NH)):RETURN
No current OSI hardware
Former programmer for Dwo Quong Fok Lok Sow and Orion Software Associates
Former owner of C1P MF (original version) and C2-8P DF (502-based)
Former programmer for Dwo Quong Fok Lok Sow and Orion Software Associates
Former owner of C1P MF (original version) and C2-8P DF (502-based)
-
- Posts: 333
- Joined: Tue Sep 16, 2008 6:04 am
- Location: Madison, WI
- Contact:
Re: Upgrade 610 from 2114 RAM to 6264 8K x 8
Hey, just saw this...
So to decode random 6502 binary I found an interactive 6502 disassembler called WFDIS at https://www.white-flame.com/wfdis/
Basically I load up a binary blob and set WFDis at it at the appropriate starting address. It halts on areas it doesn't execute, but I find the next starting point, highlight the byte and hit SHIFT-A to continue disassembly (or undo if it's garbage). Once I've gone through the main points of the code, I copy it into Notepad++.
I have a custom language definition for 6502 which does syntax coloring which I find makes it easier to read.
In notepad++ I reformat the code, fix the indents, remove spaces before and after "=" as A65 doesn't like those, highlight areas of hex data and insert , and $ and turn them into .BYTE directives. I also change labels into more meaningful words, comment the code etc. Later I check the work with the A65 assembler & compare generated to original ROM.
WFDis doesn't know about OSI, it is more of a PET/CBM disassembler, but it works well enough.
Some of the disassembly comments have built upon previous works by Ed, as he did most of the OSI ROMs years ago. Others come from other OSI users or myself. Rectangular/column cut & paste works well for moving comments between files.
Some of the binary to disassemble gets exported from WinOSI from the debugger, say if I want to disassemble a machine language file stored with a custom loader, or if I want to include system ROMs in the image from a particular configuration.
Attached is the language definition file for 6502 syntax highlighting in Notepad++. Save the XML & Import to user-defined language dialog in np++
Save your file with .asm extension to have it enabled automatically. It can be customized as needed.
So to decode random 6502 binary I found an interactive 6502 disassembler called WFDIS at https://www.white-flame.com/wfdis/
Basically I load up a binary blob and set WFDis at it at the appropriate starting address. It halts on areas it doesn't execute, but I find the next starting point, highlight the byte and hit SHIFT-A to continue disassembly (or undo if it's garbage). Once I've gone through the main points of the code, I copy it into Notepad++.
I have a custom language definition for 6502 which does syntax coloring which I find makes it easier to read.
In notepad++ I reformat the code, fix the indents, remove spaces before and after "=" as A65 doesn't like those, highlight areas of hex data and insert , and $ and turn them into .BYTE directives. I also change labels into more meaningful words, comment the code etc. Later I check the work with the A65 assembler & compare generated to original ROM.
WFDis doesn't know about OSI, it is more of a PET/CBM disassembler, but it works well enough.
Some of the disassembly comments have built upon previous works by Ed, as he did most of the OSI ROMs years ago. Others come from other OSI users or myself. Rectangular/column cut & paste works well for moving comments between files.
Some of the binary to disassemble gets exported from WinOSI from the debugger, say if I want to disassemble a machine language file stored with a custom loader, or if I want to include system ROMs in the image from a particular configuration.
Attached is the language definition file for 6502 syntax highlighting in Notepad++. Save the XML & Import to user-defined language dialog in np++
Save your file with .asm extension to have it enabled automatically. It can be customized as needed.
- Attachments
-
- 6502.xml
- Notepad++ language definition
- (5.55 KiB) Downloaded 209 times