6502.org Forum  Projects  Code  Documents  Tools  Forum
It is currently Tue Sep 24, 2024 11:20 pm

All times are UTC




Post new topic Reply to topic  [ 57 posts ]  Go to page 1, 2, 3, 4  Next
Author Message
PostPosted: Tue Aug 24, 2021 3:34 am 
Offline

Joined: Sun May 30, 2021 2:16 am
Posts: 374
Hi. I've been reading through some of the posts on the site, and I can across this document:
http://www.6502.org/source/interpreters/sweet16.htm which has Woz's Sweet16 code in it. Unfortunately, I don't understand some of the operands and directives. Can anyone help?

These are the ones I can't pin down:
Code:
AST  32

No clue here

Code:
SW16D   LDA  >SET           

What does the ">" do, here?

Code:
        LDA  OPTBL-2,Y

Is this "-2" from the value of OPTBL?

Code:
OPTBL   DFB  SET-1          ;1X
BRTBL   DFB  RTN-1          ;0

Again a "-" minus sign. And, what is DFB? What does this all do?

Code:
LD      LDA  R0L,X
BK      EQU  *-1

Another minus sign... and an asterisk?

Thanks in advance to any help you can offer!

Jon


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 4:02 am 
Offline
User avatar

Joined: Thu May 28, 2009 9:46 pm
Posts: 8395
Location: Midwestern USA
Jmstein7 wrote:
Hi. I've been reading through some of the posts on the site, and I can across this document:
http://www.6502.org/source/interpreters/sweet16.htm which has Woz's Sweet16 code in it. Unfortunately, I don't understand some of the operands and directives. Can anyone help?

These are the ones I can't pin down:
Code:
AST  32

No clue here

AST appears to be an assembler pseudo-op. No idea what it does.

Quote:
Code:
SW16D   LDA  >SET           

What does the ">" do, here?

The greater-than symbol usually means to take the most-significant byte of a 16-bit value. It is mostly used with immediate-mode addressing, however.

Quote:
Code:
        LDA  OPTBL-2,Y

Is this "-2" from the value of OPTBL?

Correct. The assembler will subtract 2 from whatever OPTBL represents and use the difference as the base address for the instruction.

Quote:
Code:
OPTBL   DFB  SET-1          ;1X
BRTBL   DFB  RTN-1          ;0

Again a "-" minus sign. And, what is DFB? What does this all do?

DFB is an assembler pseudo-op that likely defines storage. As with AST, DFB is specific to the assembler being used.

Quote:
Code:
LD      LDA  R0L,X
BK      EQU  *-1

Another minus sign... and an asterisk?

The asterisk represents the program counter in almost all 6502 assemblers. Therefore, the symbol BK is being set to the program counter minus 1.

_________________
x86?  We ain't got no x86.  We don't NEED no stinking x86!


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 5:56 am 
Offline
User avatar

Joined: Sat Dec 01, 2018 1:53 pm
Posts: 727
Location: Tokyo, Japan
The source code to which you linked looks a lot like input for Apple's EDASM, though that doesn't have an AST directive. Many pseudo-ops and conventions are common to a lot of assemblers, though, so reading through the EDASM manual would at least give you a fair amount of background for interpreting early assembler listings.

`DFB SET-1` places a byte in memory which is the lower byte of the address of the routine SET, minus 1. He's using this technique to create a lookup table of the start offsets of each routine to interpret a Sweet-16 opcode. He uses only the low byte of the address to save space and time; this is why you see the later comment that that section must reside entirely on one page. (You can see at SW16D where he handles the common high byte.)

Pushing the start address minus one is a common technique you'll see in tables of entry points on the 6502 because they are often used with the very technique you see here: look up the address, push it on the stack, and then RTS to "jump" to it. If you carefully examine what the JSR and RTS instructions do, you'll see that the address on the stack is always one less than the address to which you actually return. It's faster and smaller to pre-calculate the offset minus one than to do this at runtime.

_________________
Curt J. Sampson - github.com/0cjs


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 7:00 am 
Offline

Joined: Tue Sep 03, 2002 12:58 pm
Posts: 325
I suspect that's Wozniak's own assembler, and it looks a rather idiosyncratic one.
http://www.easy68k.com/paulrsm/6502/SW16RB.TXT has what looks like the same source code with a different (and much more standard) syntax, along with the assembled code.

Code:
LDA >set

becomes
Code:
LDA #SW16PAG

which is the (common) high byte of the addresses of the routines that handle the commands. So > means 'high byte', and there's a # missing because this is definitely an immediate LDA.

A couple of lines later we have
Code:
LDY $0

which (in context) is clearly meant to be an immediate load. Most assemblers would want you to write
Code:
LDY #$0


My guess is that AST reserves a block of zero page memory. Sweet16 needs 32 bytes there.


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 7:37 am 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10938
Location: England
I can't figure out what the AST directive could be for! There's a disk sector editor with both source and binary here: http://www.apple-iigs.info/doc/fichiers/poms15.pdf which uses AST 32 more than once in the source, and still I can't imagine. I thought it might be alignment, but it isn't.

Crossed in post: John's idea that AST might allocate some zero page. I can't quite see it, but it's plausible.

Edit: it's for ASTerisks! Print out 32 asterisks in the listing.


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 7:54 am 
Offline

Joined: Tue Sep 03, 2002 12:58 pm
Posts: 325
BigEd wrote:
Edit: it's for ASTerisks! Print out 32 asterisks in the listing.


OK, I was NOT expecting that! But of course it is.


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 9:37 am 
Offline
User avatar

Joined: Wed Feb 14, 2018 2:33 pm
Posts: 1467
Location: Scotland
Jmstein7 wrote:
Hi. I've been reading through some of the posts on the site, and I can across this document:
http://www.6502.org/source/interpreters/sweet16.htm which has Woz's Sweet16 code in it. Unfortunately, I don't understand some of the operands and directives. Can anyone help?


That listing is sublty different from the one in the original "Red Book" (1978).

See here:
Attachment:
IMG_20210824_103128.jpg
IMG_20210824_103128.jpg [ 378.22 KiB | Viewed 4968 times ]


Quote:
These are the ones I can't pin down:
Code:
AST  32

No clue here


My suspicion is that it's simply to place a line of asterisks in the output listing.

Quote:
Code:
OPTBL   DFB  SET-1          ;1X
BRTBL   DFB  RTN-1          ;0

Again a "-" minus sign. And, what is DFB? What does this all do?


DeFine Byte.

The minus sign is simple arithmetic, so place the byte value of the constant SET minus 1 into the output object file. SET is a label and so 16-bits wide, so my suspicion is that the assembler just takes the lower 8-bits.

Hope that helps,

-Gordon

_________________
--
Gordon Henderson.
See my Ruby 6502 and 65816 SBC projects here: https://projects.drogon.net/ruby/


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 9:46 am 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10938
Location: England
(There's a general observation here: the operand for any given opcode can always be an expression, even if it's generally just a symbol or a literal. That is, if we first recognise syntax like "opcode (operand),Y" and concentrate on the inner part of the operand. So, adding or subtracting 1 is a simple case, but a complex expression might also appear.)


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 12:44 pm 
Offline

Joined: Sun May 30, 2021 2:16 am
Posts: 374
I'm going to re-write it with more contemporary directives and see if I can get it to work, using what you guys have proffered. I'll post the results here. If anyone wants to give it a shot, too, and do the same, I'm curious how it goes. Let me know, and I'll report back, too.

Jon


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 1:13 pm 
Offline
User avatar

Joined: Wed Feb 14, 2018 2:33 pm
Posts: 1467
Location: Scotland
Jmstein7 wrote:
I'm going to re-write it with more contemporary directives and see if I can get it to work, using what you guys have proffered. I'll post the results here. If anyone wants to give it a shot, too, and do the same, I'm curious how it goes. Let me know, and I'll report back, too.

Jon


I re-wrote it some time back to remove the position dependence and make it a little faster for a project I was working on at the time (a 'malloc' style memory allocator) Woz was a master of saving space but with that limitation gone in my systems I opted to make it a little faster and possibly easier to read.

Link here: https://project-downloads.drogon.net/misc6502/sw16.tgz

Also a little Larson scanner test program in both sw16 and 6502 to compare...

However it's always a good exercise to do something like this to get a better feel for it.


-Gordon

_________________
--
Gordon Henderson.
See my Ruby 6502 and 65816 SBC projects here: https://projects.drogon.net/ruby/


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 1:57 pm 
Offline

Joined: Sun May 30, 2021 2:16 am
Posts: 374
The good news: I seem to have gotten Sweet16 working (I think).

The bad news: now my "Frankenstein" mash-up of a monitor isn't working... the XModem receive stopped working, and I can't find the problem.

Can anyone figure this out?

Code:
;-------------------------- The Code ----------------------------
;
; zero page variables (adjust these to suit your needs)
;
;
        .target "65C02"
   *=    $C000              ; Start of program (adjust to your needs)
        .setting "HandleLongBranch", true
crc      =   $D8      ; CRC lo byte  (two byte variable)
crch      =   $D9      ; CRC hi byte 
ptr      =   $DA      ; data pointer (two byte variable)
ptrh      =   $DB      ;   "    "
blkno      =   $DC      ; block number
retry      =   $DD      ; retry counter
retry2      =   $DE      ; 2nd counter
bflag      =   $DF      ; block flag
;
;Monitor Variables
;
IN          = $0200          ;*Input buffer
XAML        = $E4            ;*Index pointers
XAMH        = $E5
STL         = $E6
STH         = $E7
L           = $E8
H           = $E9
YSAV        = $EA
MODE        = $EB
MSGL      = $EC
MSGH      = $ED
;
; non-zero page variables and buffers
;
;
Rbuff      =   $0300         ; temp 132 byte receive buffer
               ;(place anywhere, page aligned)
;
; XMODEM Control Character Constants
SOH      =   $F1      ; start block
EOT      =   $F4      ; end of text marker
ACK      =   $F6      ; good block acknowledged
NAK      =   $F5      ; bad block acknowledged
CAN      =   $F8      ; cancel (not standard, not supported)
CR      =   $FD      ; carriage return
LF      =   $FA      ; line feed
ESC      =   $FB      ; ESC to exit
;Sweet16 Zero Page Variables
R0L     .EQU  $0
R0H     .EQU  $1
R14H    .EQU  $1D
R15L    .EQU  $1E
R15H    .EQU  $1F
;
 ;-------------------------------
 ACC    .EQU $20
 XREG   .EQU $21
 YREG   .EQU $22
 STATUS .EQU $23
 ;
 SAVE16
    STA ACC
    STX XREG
    STY YREG
    PHP
    PLA
    STA STATUS
    CLD
    RTS
 ;------------------------------
 RESTORE16
    LDA STATUS
    PHA
    LDA ACC
    LDX XREG
    LDY YREG
    PLP
    RTS
;
;^^^^^^^^^^^^^^^^^^^^^^ Start of Program ^^^^^^^^^^^^^^^^^^^^^^
;
; Xmodem/CRC upload routine
; By Daryl Rictor, July 31, 2002
;
; v0.3  tested good minus CRC
; v0.4  CRC fixed!!! init to $0000 rather than $FFFF as stated   
; v0.5  added CRC tables vs. generation at run time
; v 1.0 recode for use with SBC2
; v 1.1 added block 1 masking (block 257 would be corrupted)
        .org $C020          ;jump to address
        JSR  SAVE16         ;PRESERVE 6502 REG CONTENTS
        PLA
        STA  R15L           ;INIT SWEET16 PC
        PLA                 ;FROM RETURN
        STA  R15H           ;ADDRESS
SW16B   JSR  SW16C          ;INTERPRET AND EXECUTE
        JMP  SW16B          ;ONE SWEET16 INSTR.
SW16C   INC  R15L
        BNE  SW16D          ;INCR SWEET16 PC FOR FETCH
        INC  R15H
SW16D   LDA  >SET           ;COMMON HIGH BYTE ">" FOR ALL ROUTINES
        PHA                 ;PUSH ON STACK FOR RTS
        LDY  $0
        LDA  (R15L),Y       ;FETCH INSTR
        AND  $F             ;MASK REG SPECIFICATION
        ASL                 ;DOUBLE FOR TWO BYTE REGISTERS
        TAX                 ;TO X REG FOR INDEXING
        LSR
        EOR  (R15L),Y       ;NOW HAVE OPCODE
        BEQ  TOBR           ;IF ZERO THEN NON-REG OP
        STX  R14H           ;INDICATE "PRIOR RESULT REG"
        LSR
        LSR                 ;OPCODE*2 TO LSB'S
        LSR
        TAY                 ;TO Y REG FOR INDEXING
        LDA  OPTBL-2,Y      ;LOW ORDER ADR BYTE
        PHA                 ;ONTO STACK
        RTS                 ;GOTO REG-OP ROUTINE
TOBR    INC  R15L
        BNE  TOBR2          ;INCR PC
        INC  R15H
TOBR2   LDA  BRTBL,X        ;LOW ORDER ADR BYTE
        PHA                 ;ONTO STACK FOR NON-REG OP
        LDA  R14H           ;"PRIOR RESULT REG" INDEX
        LSR                 ;PREPARE CARRY FOR BC, BNC.
        RTS                 ;GOTO NON-REG OP ROUTINE
RTNZ    PLA                 ;POP RETURN ADDRESS
        PLA
        JSR  RESTORE16        ;RESTORE 6502 REG CONTENTS
        JMP  (R15L)         ;RETURN TO 6502 CODE VIA PC
SETZ    LDA  (R15L),Y       ;HIGH ORDER BYTE OF CONSTANT
        STA  R0H,X
        DEY
        LDA  (R15L),Y       ;LOW ORDER BYTE OF CONSTANT
        STA  R0L,X
        TYA                 ;Y REG CONTAINS 1
        SEC
        ADC  R15L           ;ADD 2 TO PC
        STA  R15L
        BCC  SET2
        INC  R15H
SET2    RTS
OPTBL   .lobyte  SET-1          ;1X
BRTBL   .lobyte  RTN-1          ;0
        .lobyte  LD-1           ;2X
        .lobyte  BR-1           ;1
        .lobyte  ST-1           ;3X
        .lobyte  BNC-1          ;2
        .lobyte  LDAT-1         ;4X
        .lobyte  BC-1           ;3
        .lobyte  STAT-1         ;5X
        .lobyte  BP-1           ;4
        .lobyte  LDDAT-1        ;6X
        .lobyte  BM-1           ;5
        .lobyte  STDAT-1        ;7X
        .lobyte  BZ-1           ;6
        .lobyte  POP-1          ;8X
        .lobyte  BNZ-1          ;7
        .lobyte  STPAT-1        ;9X
        .lobyte  BM1-1          ;8
        .lobyte  ADD-1          ;AX
        .lobyte  BNM1-1         ;9
        .lobyte  SUB-1          ;BX
        .lobyte  BK-1           ;A
        .lobyte  POPD-1         ;CX
        .lobyte  RS-1           ;B
        .lobyte  CPR-1          ;DX
        .lobyte  BS-1           ;C
        .lobyte  INR-1          ;EX
        .lobyte  NUL-1          ;D
        .lobyte  DCR-1          ;FX
        .lobyte  NUL-1          ;E
        .lobyte  NUL-1          ;UNUSED
        .lobyte  NUL-1          ;F

; FOLLOWING CODE MUST BE
; CONTAINED ON A SINGLE PAGE!
        .org  $C0B0         ;single page start
       
SET     BPL  SETZ           ;ALWAYS TAKEN
LD      LDA  R0L,X
BK      .EQU *-1           ;"*" refers to the program counter
        STA  R0L
        LDA  R0H,X          ;MOVE RX TO R0
        STA  R0H
        RTS
ST      LDA  R0L
        STA  R0L,X          ;MOVE R0 TO RX
        LDA  R0H
        STA  R0H,X
        RTS
STAT    LDA  R0L
STAT2   STA  (R0L,X)        ;STORE BYTE INDIRECT
        LDY  $0
STAT3   STY  R14H           ;INDICATE R0 IS RESULT NEG
INR     INC  R0L,X
        BNE  INR2           ;INCR RX
        INC  R0H,X
INR2    RTS
LDAT    LDA  (R0L,X)        ;LOAD INDIRECT (RX)
        STA  R0L            ;TO R0
        LDY  $0
        STY  R0H            ;ZERO HIGH ORDER R0 BYTE
        BEQ  STAT3          ;ALWAYS TAKEN
POP     LDY  $0             ;HIGH ORDER BYTE = 0
        BEQ  POP2           ;ALWAYS TAKEN
POPD    JSR  DCR            ;DECR RX
        LDA  (R0L,X)        ;POP HIGH ORDER BYTE @RX
        TAY                 ;SAVE IN Y REG
POP2    JSR  DCR            ;DECR RX
        LDA  (R0L,X)        ;LOW ORDER BYTE
        STA  R0L            ;TO R0
        STY  R0H
POP3    LDY  $0             ;INDICATE R0 AS LAST RESULT REG
        STY  R14H
        RTS
LDDAT   JSR  LDAT           ;LOW ORDER BYTE TO R0, INCR RX
        LDA  (R0L,X)        ;HIGH ORDER BYTE TO R0
        STA  R0H
        JMP  INR            ;INCR RX
STDAT   JSR  STAT           ;STORE INDIRECT LOW ORDER
        LDA  R0H            ;BYTE AND INCR RX. THEN
        STA  (R0L,X)        ;STORE HIGH ORDER BYTE.
        JMP  INR            ;INCR RX AND RETURN
STPAT   JSR  DCR            ;DECR RX
        LDA  R0L
        STA  (R0L,X)        ;STORE R0 LOW BYTE @RX
        JMP  POP3           ;INDICATE R0 AS LAST RESULT REG
DCR     LDA  R0L,X
        BNE  DCR2           ;DECR RX
        DEC  R0H,X
DCR2    DEC  R0L,X
        RTS
SUB     LDY  $0             ;RESULT TO R0
        CPR  SEC            ;NOTE Y REG = 13*2 FOR CPR
        LDA  R0L
        SBC  R0L,X
        STA  R0L,Y          ;R0-RX TO RY
        LDA  R0H
        SBC  R0H,X
SUB2    STA  R0H,Y
        TYA                 ;LAST RESULT REG*2
        ADC  $0             ;CARRY TO LSB
        STA  R14H
        RTS
ADD     LDA  R0L
        ADC  R0L,X
        STA  R0L            ;R0+RX TO R0
        LDA  R0H
        ADC  R0H,X
        LDY  $0             ;R0 FOR RESULT
        BEQ  SUB2           ;FINISH ADD
BS      LDA  R15L           ;NOTE X REG IS 12*2!
        JSR  STAT2          ;PUSH LOW PC BYTE VIA R12
        LDA  R15H
        JSR  STAT2          ;PUSH HIGH ORDER PC BYTE
BR      CLC
BNC     BCS  BNC2           ;NO CARRY TEST
BR1     LDA  (R15L),Y       ;DISPLACEMENT BYTE
        BPL  BR2
        DEY
BR2     ADC  R15L           ;ADD TO PC
        STA  R15L
        TYA
        ADC  R15H
        STA  R15H
BNC2    RTS
BC      BCS  BR
        RTS
BP      ASL                 ;DOUBLE RESULT-REG INDEX
        TAX                 ;TO X REG FOR INDEXING
        LDA  R0H,X          ;TEST FOR PLUS
        BPL  BR1            ;BRANCH IF SO
        RTS
BM      ASL                 ;DOUBLE RESULT-REG INDEX
        TAX
        LDA  R0H,X          ;TEST FOR MINUS
        BMI  BR1
        RTS
BZ      ASL                 ;DOUBLE RESULT-REG INDEX
        TAX
        LDA  R0L,X          ;TEST FOR ZERO
        ORA  R0H,X          ;(BOTH BYTES)
        BEQ  BR1            ;BRANCH IF SO
        RTS
BNZ     ASL                 ;DOUBLE RESULT-REG INDEX
        TAX
        LDA  R0L,X          ;TEST FOR NON-ZERO
        ORA  R0H,X          ;(BOTH BYTES)
        BNE  BR1            ;BRANCH IF SO
        RTS
BM1     ASL                 ;DOUBLE RESULT-REG INDEX
        TAX
        LDA  R0L,X          ;CHECK BOTH BYTES
        AND  R0H,X          ;FOR $FF (MINUS 1)
        EOR  $FF
        BEQ  BR1            ;BRANCH IF SO
        RTS
BNM1    ASL                 ;DOUBLE RESULT-REG INDEX
        TAX
        LDA  R0L,X
        AND  R0H,X          ;CHECK BOTH BYTES FOR NO $FF
        EOR  $FF
        BNE  BR1            ;BRANCH IF NOT MINUS 1
NUL     RTS
RS      LDX  $18            ;12*2 FOR R12 AS STACK POINTER
        JSR  DCR            ;DECR STACK POINTER
        LDA  (R0L,X)        ;POP HIGH RETURN ADDRESS TO PC
        STA  R15H
        JSR  DCR            ;SAME FOR LOW ORDER BYTE
        LDA  (R0L,X)
        STA  R15L
        RTS
RTN     JMP  RTNZ
;End of Sweet16
;
XModem      jsr   PrintMsg   ; send prompt and info
      lda   #$01
      sta   blkno      ; set block # to 1
      sta   bflag      ; set flag to get address from block 1
StartCrc   lda   #"C"      ; "C" start with CRC mode
      jsr   Put_Chr      ; send it
      lda   #$FF   
      sta   retry2      ; set loop counter for ~3 sec delay
      lda   #$00
            sta   crc
      sta   crch      ; init CRC value   
      jsr   GetByte      ; wait for input
            bcs   GotByte      ; byte received, process it
      bcc   StartCrc   ; resend "C"

StartBlk   lda   #$FF      ;
      sta   retry2      ; set loop counter for ~3 sec delay
      lda   #$00      ;
      sta   crc      ;
      sta   crch      ; init CRC value   
      jsr   GetByte      ; get first byte of block
      bcc   StartBlk   ; timed out, keep waiting...
GotByte      cmp   #ESC      ; quitting?
                bne   GotByte1   ; no
;      lda   #$FE      ; Error code in "A" of desired
                rts         ; YES - do BRK or change to RTS if desired
GotByte1        cmp   #SOH      ; start of block?
      beq   BegBlk      ; yes
      cmp   #EOT      ;
      bne   BadCrc      ; Not SOH or EOT, so flush buffer & send NAK   
      jmp   Done      ; EOT - all done!
BegBlk      ldx   #$00
GetBlk      lda   #$ff      ; 3 sec window to receive characters
      sta    retry2      ;
GetBlk1      jsr   GetByte      ; get next character
      bcc   BadCrc      ; chr rcv error, flush and send NAK
GetBlk2      sta   Rbuff,x      ; good char, save it in the rcv buffer
      inx         ; inc buffer pointer   
      cpx   #$84      ; <01> <FE> <128 bytes> <CRCH> <CRCL>
      bne   GetBlk      ; get 132 characters
      ldx   #$00      ;
      lda   Rbuff,x      ; get block # from buffer
      cmp   blkno      ; compare to expected block #   
      beq   GoodBlk1   ; matched!
      jsr   Print_Err   ; Unexpected block number - abort   
      jsr   Flush      ; mismatched - flush buffer and then do BRK
;      lda   #$FD      ; put error code in "A" if desired
      rts         ; unexpected block # - fatal error - BRK or RTS
GoodBlk1   eor   #$ff      ; 1's comp of block #
      inx         ;
      cmp   Rbuff,x      ; compare with expected 1's comp of block #
      beq   GoodBlk2    ; matched!
      jsr   Print_Err   ; Unexpected block number - abort   
      jsr    Flush      ; mismatched - flush buffer and then do BRK
;      lda   #$FC      ; put error code in "A" if desired
      brk         ; bad 1's comp of block#   
GoodBlk2   ldy   #$02      ;
CalcCrc      lda   Rbuff,y      ; calculate the CRC for the 128 bytes of data   
      jsr   UpdCrc      ; could inline sub here for speed
      iny         ;
      cpy   #$82      ; 128 bytes
      bne   CalcCrc      ;
      lda   Rbuff,y      ; get hi CRC from buffer
      cmp   crch      ; compare to calculated hi CRC
      bne   BadCrc      ; bad crc, send NAK
      iny         ;
      lda   Rbuff,y      ; get lo CRC from buffer
      cmp   crc      ; compare to calculated lo CRC
      beq   GoodCrc      ; good CRC
BadCrc      jsr   Flush      ; flush the input port
      lda   #NAK      ;
      jsr   Put_Chr      ; send NAK to resend block
      jmp   StartBlk   ; start over, get the block again         
GoodCrc      ldx   #$02      ;
      lda   blkno      ; get the block number
      cmp   #$01      ; 1st block?
      bne   CopyBlk      ; no, copy all 128 bytes
      lda   bflag      ; is it really block 1, not block 257, 513 etc.
      beq   CopyBlk      ; no, copy all 128 bytes
      lda   Rbuff,x      ; get target address from 1st 2 bytes of blk 1
      sta   ptr      ; save lo address
      inx         ;
      lda   Rbuff,x      ; get hi address
      sta   ptr+1      ; save it
      inx         ; point to first byte of data
      dec   bflag      ; set the flag so we won't get another address      
CopyBlk      ldy   #$00      ; set offset to zero
CopyBlk3   lda   Rbuff,x      ; get data byte from buffer
      sta   (ptr),y      ; save to target
      inc   ptr      ; point to next address
      bne   CopyBlk4   ; did it step over page boundary?
      inc   ptr+1      ; adjust high address for page crossing
CopyBlk4   inx         ; point to next data byte
      cpx   #$82      ; is it the last byte
      bne   CopyBlk3   ; no, get the next one
IncBlk      inc   blkno      ; done.  Inc the block #
      lda   #ACK      ; send ACK
      jsr   Put_Chr      ;
      jmp   StartBlk   ; get next block
Done      lda   #ACK      ; last block, send ACK and exit.
      jsr   Put_Chr      ;
      jsr   Flush      ; get leftover characters, if any
      jsr   Print_Good   ;
      jmp RESET         ;can be rts
;
;^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
;
; subroutines
;
;               ;
GetByte      lda   #$00      ; wait for chr input and cycle timing loop
      sta   retry      ; set low value of timing loop
StartCrcLp   jsr   Get_chr      ; get chr from serial port, don't wait
      bcs   GetByte1   ; got one, so exit
      dec   retry      ; no character received, so dec counter
      bne   StartCrcLp   ;
      dec   retry2      ; dec hi byte of counter
      bne   StartCrcLp   ; look for character again
      clc         ; if loop times out, CLC, else SEC and return
GetByte1   rts         ; with character in "A"
;
Flush      lda   #$70      ; flush receive buffer
      sta   retry2      ; flush until empty for ~1 sec.
Flush1      jsr   GetByte      ; read the port
      bcs   Flush      ; if chr recvd, wait for another
      rts         ; else done
;
PrintMsg   ldx   #$00      ; PRINT starting message
PrtMsg1      lda      Msg,x      
      beq   PrtMsg2         
      jsr   Put_Chr
      inx
      bne   PrtMsg1
PrtMsg2      rts
Msg      .textz   "Begin XMODEM/CRC upload. "
      ;.lobyte     CR, LF
                  ;.lobyte   0
;
Print_Err   ldx   #$00      ; PRINT Error message
PrtErr1      lda      ErrMsg,x
      beq   PrtErr2
      jsr   Put_Chr
      inx
      bne   PrtErr1
PrtErr2      rts
ErrMsg      .textz    "Upload Error!"
      ;.lobyte     CR, LF
                ;.lobyte   0
;
Print_Good   ldx   #$00      ; PRINT Good Transfer message
Prtgood1   lda      GoodMsg,x
      beq   Prtgood2
      jsr   Put_Chr
      inx
      bne   Prtgood1
Prtgood2   rts
GoodMsg      .textz    "Upload Successful!"
      ;.lobyte     CR, LF
                ;.lobyte   0
;
;
;======================================================================
;  I/O Device Specific Routines
;
;  Two routines are used to communicate with the I/O device.
;
; "Get_Chr" routine will scan the input port for a character.  It will
; return without waiting with the Carry flag CLEAR if no character is
; present or return with the Carry flag SET and the character in the "A"
; register if one was present.
;
; "Put_Chr" routine will write one byte to the output port.  Its alright
; if this routine waits for the port to be ready.  its assumed that the
; character was send upon return from this routine.
;
; Here is an example of the routines used for a standard 6551 ACIA.
; You would call the ACIA_Init prior to running the xmodem transfer
; routine.
;
VIA_REG     =  $8800
VIA_DATA    =  $8801
VIA_DDRR    =  $8802
VIA_DDRD    =  $8803
VIA_HS      =  $880C
;
PSP_DATA    =  $9000
;
ACIA_Data   =   $8000      ; Adjust these addresses to point
ACIA_Status   =   $8001      ; to YOUR 6551!
ACIA_Command   =   $8002      ;
ACIA_Control   =   $8003      ;
ACIA        = $8000
ACIA_CTRL   = ACIA+3
ACIA_CMD    = ACIA+2
ACIA_SR     = ACIA+1
ACIA_DAT    = ACIA
ACIA_Init         lda   #$10      ; 115.2k init is #%00010000
                  sta   ACIA_Control      ; control reg
                  lda   #$C9              ; N parity/echo off/rx int off/ dtr active low
                  sta   ACIA_Command      ; command reg
                lda   #$99
                sta   VIA_HS
                lda   #$FF
                sta   VIA_DDRR
                sta   VIA_DDRD
                sta   VIA_REG
                  rts                     ; done
;
; input chr from ACIA (no waiting)
;
Get_Chr      clc         ; no chr present
                  lda   ACIA_Status     ; get Serial port status
                  and   #$08            ; mask rcvr full bit
                 beq   Get_Chr2   ; if not chr, done
                  Lda   ACIA_Data       ; else get chr
             sec         ; and set the Carry Flag
Get_Chr2       rts         ; done
;
; output to OutPut Port
;
Put_Chr         PHA                     ; save registers
Put_Chr1        lda   ACIA_Status     ; serial port status
                 and   #$10            ; is tx buffer empty
                  beq   Put_Chr1        ; no, go back and test it again
                  PLA                     ; yes, get chr to send
                  sta   ACIA_Data       ; put character to Port
                jsr Delay
                  RTS                     ; done
;=========================================================================
;Main Routines/Program
RESET       CLD             ;Clear decimal arithmetic mode.
            CLI
            JSR ACIA_Init        ;* Init ACIA
         LDA #$0D
         JSR ECHO      ;* New line.
         LDA #<MSG1
         STA MSGL
         LDA #>MSG1
         STA MSGH
         JSR SHWMSG      ;* Show Welcome.
         LDA #$0D
         JSR ECHO      ;* New line.
         LDA #<MSG5
         STA MSGL
         LDA #>MSG5
         STA MSGH
         JSR SHWMSG 
         LDA #$0D
         JSR ECHO      ;* New line.
SOFTRESET   LDA #$9B      ;* Auto escape.
NOTCR       CMP #$88        ;"<-"? * Note this was chaged to $88 which is the back space key.
            BEQ BACKSPACE   ;Yes.
            CMP #$9B        ;ESC?
            BEQ ESCAPE      ;Yes.
            INY             ;Advance text index.
            BPL NEXTCHAR    ;Auto ESC if >127.
ESCAPE      LDA #$DC        ;"\"
            JSR ECHO        ;Output it.
GETLINE     LDA #$8D        ;CR.
            JSR ECHO        ;Output it.
            LDY #$01        ;Initiallize text index.
BACKSPACE   DEY             ;Backup text index.
            BMI GETLINE     ;Beyond start of line, reinitialize.
         LDA #$A0      ;*Space, overwrite the backspaced char.
         JSR ECHO
         LDA #$88      ;*Backspace again to get to correct pos.
         JSR ECHO
NEXTCHAR    LDA ACIA_SR     ;*See if we got an incoming char
            AND #$08        ;*Test bit 3
            BEQ NEXTCHAR    ;*Wait for character
            LDA ACIA_DAT    ;*Load char
         CMP #$60      ;*Is it Lower case
         BMI   CONVERT      ;*Nope, just convert it
         AND #$5F      ;*If lower case, convert to Upper case
CONVERT     ORA #$80        ;*Convert it to "ASCII Keyboard" Input
            STA IN,Y        ;Add to text buffer.
            JSR ECHO        ;Display character.
            CMP #$8D        ;CR?
            BNE NOTCR       ;No.
            LDY #$FF        ;Reset text index.
            LDA #$00        ;For XAM mode.
            TAX             ;0->X.
SETSTOR     ASL             ;Leaves $7B if setting STOR mode.
SETMODE     STA MODE        ;$00 = XAM, $7B = STOR, $AE = BLOK XAM.
BLSKIP      INY             ;Advance text index.
NEXTITEM    LDA IN,Y        ;Get character.
            CMP #$8D        ;CR?
            BEQ GETLINE     ;Yes, done this line.
            CMP #$AE        ;"."?
            BCC BLSKIP      ;Skip delimiter.
            BEQ SETMODE     ;Set BLOCK XAM mode.
            CMP #$BA        ;":"?
            BEQ SETSTOR     ;Yes, set STOR mode.
            CMP #$D2        ;"R"?
            BEQ RUN         ;Yes, run user program.
            CMP #$D8           ;"X"?
            BEQ XModem         ;Yes, run XModem transfer.
            STX L           ;$00->L.
            STX H           ; and H.
            STY YSAV        ;Save Y for comparison.
NEXTHEX     LDA IN,Y        ;Get character for hex test.
            EOR #$B0        ;Map digits to $0-9.
            CMP #$0A        ;Digit?
            BCC DIG         ;Yes.
            ADC #$88        ;Map letter "A"-"F" to $FA-FF.
            CMP #$FA        ;Hex letter?
            BCC NOTHEX      ;No, character not hex.
DIG         ASL
            ASL             ;Hex digit to MSD of A.
            ASL
            ASL
            LDX #$04        ;Shift count.
HEXSHIFT    ASL             ;Hex digit left MSB to carry.
            ROL L           ;Rotate into LSD.
            ROL H           ;Rotate into MSD's.
            DEX             ;Done 4 shifts?
            BNE HEXSHIFT    ;No, loop.
            INY             ;Advance text index.
            BNE NEXTHEX     ;Always taken. Check next character for hex.
NOTHEX      CPY YSAV        ;Check if L, H empty (no hex digits).
         BNE NOESCAPE   ;* Branch out of range, had to improvise...
            JMP ESCAPE      ;Yes, generate ESC sequence.

RUN         JSR ACTRUN      ;* JSR to the Address we want to run.
         JMP   SOFTRESET   ;* When returned for the program, reset monitor.
ACTRUN      JMP (XAML)      ;Run at current XAM index.

NOESCAPE    BIT MODE        ;Test MODE byte.
            BVC NOTSTOR     ;B6=0 for STOR, 1 for XAM and BLOCK XAM
            LDA L           ;LSD's of hex data.
            STA (STL, X)    ;Store at current "store index".
            INC STL         ;Increment store index.
            BNE NEXTITEM    ;Get next item. (no carry).
            INC STH         ;Add carry to 'store index' high order.
TONEXTITEM  JMP NEXTITEM    ;Get next command item.
NOTSTOR     BMI XAMNEXT     ;B7=0 for XAM, 1 for BLOCK XAM.
            LDX #$02        ;Byte count.
SETADR      LDA L-1,X       ;Copy hex data to
            STA STL-1,X     ;"store index".
            STA XAML-1,X    ;And to "XAM index'.
            DEX             ;Next of 2 bytes.
            BNE SETADR      ;Loop unless X = 0.
NXTPRNT     BNE PRDATA      ;NE means no address to print.
            LDA #$8D        ;CR.
            JSR ECHO        ;Output it.
            LDA XAMH        ;'Examine index' high-order byte.
            JSR PRBYTE      ;Output it in hex format.
            LDA XAML        ;Low-order "examine index" byte.
            JSR PRBYTE      ;Output it in hex format.
            LDA #$BA        ;":".
            JSR ECHO        ;Output it.
PRDATA      LDA #$A0        ;Blank.
            JSR ECHO        ;Output it.
            LDA (XAML,X)    ;Get data byte at 'examine index".
            JSR PRBYTE      ;Output it in hex format.
XAMNEXT     STX MODE        ;0-> MODE (XAM mode).
            LDA XAML
            CMP L           ;Compare 'examine index" to hex data.
            LDA XAMH
            SBC H
            BCS TONEXTITEM  ;Not less, so no more data to output.
            INC XAML
            BNE MOD8CHK     ;Increment 'examine index".
            INC XAMH
MOD8CHK     LDA XAML        ;Check low-order 'exainine index' byte
            AND #$0F        ;For MOD 8=0 ** changed to $0F to get 16 values per row **
            BPL NXTPRNT     ;Always taken.
PRBYTE      PHA             ;Save A for LSD.
            LSR
            LSR
            LSR             ;MSD to LSD position.
            LSR
            JSR PRHEX       ;Output hex digit.
            PLA             ;Restore A.
PRHEX       AND #$0F        ;Mask LSD for hex print.
            ORA #$B0        ;Add "0".
            CMP #$BA        ;Digit?
            BCC ECHO        ;Yes, output it.
            ADC #$06        ;Add offset for letter.
ECHO        PHA             ;*Save A
            AND #$7F        ;*Change to "standard ASCII"
            STA ACIA_DAT    ;*Send it.
            jsr Delay       ; try delay
WAIT       LDA ACIA_SR     ;*Load status register for ACIA
            AND #$10        ;*Mask bit 4.
            BEQ    WAIT    ;*ACIA not done yet, wait.
            PLA             ;*Restore A
            RTS             ;*Done, over and out...

SHWMSG      LDY #$0
PRINT      LDA (MSGL),Y
         BEQ DONEX
         JSR ECHO
         INY
         BNE PRINT
DONEX      RTS
;Interrupt Service Routines
IRQ_ISA     SEI
            PHA
            PHX
            PHY
            ;actual routine
            PLY
            PLX
            PLA
            CLI
            RTI
;
NMI_ISA     SEI
            PHA
            PHX
            PHY
            ;actual routine
            PLY
            PLX
            PLA
            CLI
            RTI
;=========================================================================
;
;
;  CRC subroutines
;
;
UpdCrc      eor    crc+1       ; Quick CRC computation with lookup tables
             tax          ; updates the two bytes at crc & crc+1
             lda    crc      ; with the byte send in the "A" register
             eor    CRCHI,X
             sta    crc+1
             lda    CRCLO,X
             sta    crc
             rts
;
; The following tables are used to calculate the CRC for the 128 bytes
; in the xmodem data blocks.  You can use these tables if you plan to
; store this program in ROM.  If you choose to build them at run-time,
; then just delete them and define the two labels: crclo & crchi.
;
; low byte CRC lookup table (should be page aligned)
      *= $ED00
crclo
 .lobyte $00,$21,$42,$63,$84,$A5,$C6,$E7,$08,$29,$4A,$6B,$8C,$AD,$CE,$EF
 .lobyte $31,$10,$73,$52,$B5,$94,$F7,$D6,$39,$18,$7B,$5A,$BD,$9C,$FF,$DE
 .lobyte $62,$43,$20,$01,$E6,$C7,$A4,$85,$6A,$4B,$28,$09,$EE,$CF,$AC,$8D
 .lobyte $53,$72,$11,$30,$D7,$F6,$95,$B4,$5B,$7A,$19,$38,$DF,$FE,$9D,$BC
 .lobyte $C4,$E5,$86,$A7,$40,$61,$02,$23,$CC,$ED,$8E,$AF,$48,$69,$0A,$2B
 .lobyte $F5,$D4,$B7,$96,$71,$50,$33,$12,$FD,$DC,$BF,$9E,$79,$58,$3B,$1A
 .lobyte $A6,$87,$E4,$C5,$22,$03,$60,$41,$AE,$8F,$EC,$CD,$2A,$0B,$68,$49
 .lobyte $97,$B6,$D5,$F4,$13,$32,$51,$70,$9F,$BE,$DD,$FC,$1B,$3A,$59,$78
 .lobyte $88,$A9,$CA,$EB,$0C,$2D,$4E,$6F,$80,$A1,$C2,$E3,$04,$25,$46,$67
 .lobyte $B9,$98,$FB,$DA,$3D,$1C,$7F,$5E,$B1,$90,$F3,$D2,$35,$14,$77,$56
 .lobyte $EA,$CB,$A8,$89,$6E,$4F,$2C,$0D,$E2,$C3,$A0,$81,$66,$47,$24,$05
 .lobyte $DB,$FA,$99,$B8,$5F,$7E,$1D,$3C,$D3,$F2,$91,$B0,$57,$76,$15,$34
 .lobyte $4C,$6D,$0E,$2F,$C8,$E9,$8A,$AB,$44,$65,$06,$27,$C0,$E1,$82,$A3
 .lobyte $7D,$5C,$3F,$1E,$F9,$D8,$BB,$9A,$75,$54,$37,$16,$F1,$D0,$B3,$92
 .lobyte $2E,$0F,$6C,$4D,$AA,$8B,$E8,$C9,$26,$07,$64,$45,$A2,$83,$E0,$C1
 .lobyte $1F,$3E,$5D,$7C,$9B,$BA,$D9,$F8,$17,$36,$55,$74,$93,$B2,$D1,$F0

; hi byte CRC lookup table (should be page aligned)
      *= $EE00
crchi
 .lobyte $00,$10,$20,$30,$40,$50,$60,$70,$81,$91,$A1,$B1,$C1,$D1,$E1,$F1
 .lobyte $12,$02,$32,$22,$52,$42,$72,$62,$93,$83,$B3,$A3,$D3,$C3,$F3,$E3
 .lobyte $24,$34,$04,$14,$64,$74,$44,$54,$A5,$B5,$85,$95,$E5,$F5,$C5,$D5
 .lobyte $36,$26,$16,$06,$76,$66,$56,$46,$B7,$A7,$97,$87,$F7,$E7,$D7,$C7
 .lobyte $48,$58,$68,$78,$08,$18,$28,$38,$C9,$D9,$E9,$F9,$89,$99,$A9,$B9
 .lobyte $5A,$4A,$7A,$6A,$1A,$0A,$3A,$2A,$DB,$CB,$FB,$EB,$9B,$8B,$BB,$AB
 .lobyte $6C,$7C,$4C,$5C,$2C,$3C,$0C,$1C,$ED,$FD,$CD,$DD,$AD,$BD,$8D,$9D
 .lobyte $7E,$6E,$5E,$4E,$3E,$2E,$1E,$0E,$FF,$EF,$DF,$CF,$BF,$AF,$9F,$8F
 .lobyte $91,$81,$B1,$A1,$D1,$C1,$F1,$E1,$10,$00,$30,$20,$50,$40,$70,$60
 .lobyte $83,$93,$A3,$B3,$C3,$D3,$E3,$F3,$02,$12,$22,$32,$42,$52,$62,$72
 .lobyte $B5,$A5,$95,$85,$F5,$E5,$D5,$C5,$34,$24,$14,$04,$74,$64,$54,$44
 .lobyte $A7,$B7,$87,$97,$E7,$F7,$C7,$D7,$26,$36,$06,$16,$66,$76,$46,$56
 .lobyte $D9,$C9,$F9,$E9,$99,$89,$B9,$A9,$58,$48,$78,$68,$18,$08,$38,$28
 .lobyte $CB,$DB,$EB,$FB,$8B,$9B,$AB,$BB,$4A,$5A,$6A,$7A,$0A,$1A,$2A,$3A
 .lobyte $FD,$ED,$DD,$CD,$BD,$AD,$9D,$8D,$7C,$6C,$5C,$4C,$3C,$2C,$1C,$0C
 .lobyte $EF,$FF,$CF,$DF,$AF,$BF,$8F,$9F,$6E,$7E,$4E,$5E,$2E,$3E,$0E,$1E
;
; End of File
;*****************************************************
;   Delay
;
;   Delay For 65535 Cycles
;
;*****************************************************
Delay
      phx
      phy
      ldy #$8F ; restore to #$00
AL2      ldx #$05 ; restore to #$00
AL1      dex
      bne AL1
      dey
      bne AL2
      ply
      plx
      rts
;
MSG1      .textz "Welcome to JSMON 2.0."
MSG2      .textz "Start Intel Hex Transfer."
MSG3      .textz "Intel Hex Imported."
MSG4      .textz "Intel Hex Imported with  error."
MSG5      .textz "Sweet16 Enabled at JSR $C020" ;modify accordingly
                .ORG    $FFFA
NMI_VEC         .word   NMI_ISA         ;IRQ vector
RESET_VEC       .word   RESET           ;RESET vector $C33F
IRQ_VEC         .word   IRQ_ISA         ;IRQ vector


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 2:38 pm 
Offline

Joined: Sun May 30, 2021 2:16 am
Posts: 374
Wow. Still no luck. This will drive me bonkers.


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 2:52 pm 
Offline
User avatar

Joined: Fri Aug 30, 2002 9:02 pm
Posts: 1738
Location: Sacramento, CA
These are values, not addresses. It looks like you changed them thinking they were zero page addresses.

Code:
SOH      =   $01      ; start block
EOT      =   $04      ; end of text marker
ACK      =   $06      ; good block acknowleged
NAK      =   $15      ; bad block acknowleged
CAN      =   $18      ; cancel (not standard, not supported)
CR       =   13
LF       =   10
ESC      =   27       ; ESC to exit


I did not look over the rest of the code.

Daryl

_________________
Please visit my website -> https://sbc.rictor.org/


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 3:03 pm 
Offline

Joined: Sun May 30, 2021 2:16 am
Posts: 374
8BIT wrote:
These are values, not addresses. It looks like you changed them thinking they were zero page addresses.

Code:
SOH      =   $01      ; start block
EOT      =   $04      ; end of text marker
ACK      =   $06      ; good block acknowleged
NAK      =   $15      ; bad block acknowleged
CAN      =   $18      ; cancel (not standard, not supported)
CR       =   13
LF       =   10
ESC      =   27       ; ESC to exit


I did not look over the rest of the code.

Daryl


Daryl, I'm a BIG fan of your work! The XModem problem seems to be fixed. Now let's see if I can get Sweet16 fully operational.

Jon

edit: now XModem works but Sweet16 doesn't. Hmmmm... :lol:
edit2: I wish there was a "smacking my forehead" emoji here :lol:


Top
 Profile  
Reply with quote  
PostPosted: Tue Aug 24, 2021 3:19 pm 
Offline
User avatar

Joined: Sat Dec 01, 2018 1:53 pm
Posts: 727
Location: Tokyo, Japan
John West wrote:
I suspect that's Wozniak's own assembler, and it looks a rather idiosyncratic one.
http://www.easy68k.com/paulrsm/6502/SW16RB.TXT has what looks like the same source code with a different (and much more standard) syntax, along with the assembled code.

That's a great find; it appears to be a machine-readable version of the listing from the original 1977-11 BYTE article by Wozniak.

The 6502.org page appears to be a reformatted copy of a file called sweet16.txt that dates back to at least 2000. That contains the material from the 1979 Call-A.P.P.L.E. Woz Pak II (which includes a version of Woz's article without source code and another article on Sweet 16 by Dick Sedgewick), bits of other documentation, and a different (and much worse) version of the source code. It's not only been reworked for whatever strange assembler doesn't use `#` to indicate immediate addressing, but also has at least two typos (loss of the SW16 entry point label and indentation of the CPR label). It does, however, add the "Following code must be contained on a single page!" comment.

My recommendation for anybody playing with this is to use the SW16RB.TXT listing and just trim off the address and data columns at the left.

_________________
Curt J. Sampson - github.com/0cjs


Top
 Profile  
Reply with quote  
Display posts from previous:  Sort by  
Post new topic Reply to topic  [ 57 posts ]  Go to page 1, 2, 3, 4  Next

All times are UTC


Who is online

Users browsing this forum: commodorejohn and 18 guests


You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot post attachments in this forum

Search for:
Jump to: