6502.org Forum  Projects  Code  Documents  Tools  Forum
It is currently Fri Nov 01, 2024 8:23 am

All times are UTC




Post new topic Reply to topic  [ 321 posts ]  Go to page Previous  1 ... 8, 9, 10, 11, 12, 13, 14 ... 22  Next
Author Message
PostPosted: Mon Apr 24, 2017 4:19 am 
Offline

Joined: Sat Mar 11, 2017 1:56 am
Posts: 276
Location: Lynden, WA
I'm gonna post my code thus far. I'm getting spurts of perfect operation, mixed with periods of constant crashes. I still suspect it's a wiring issue, but if I'm doing something clearly stupid in the code that could cause instability...

Couple things first. I'm still very much in the learning processes with 6502 assembly, so I'm sure I'm doing some stuff the hard way. For instance, other than initializing it, I use no stack instructions, although I'm sure I'd benefit from them. Still getting to that!

While I'm not specifically looking for critique of my methods, I do welcome it.

The one thing that I think might be bad is how much happens inside the ISR for reading the keyboard. the ISR itself is short, but it calls a routine that includes my entire command recognition code. The ACIA is the only interrupt generator, but I suppose it still might be a thing.

My problems are, lock-ups (often), garbage on the screen (less often), and other strange behaviors.

Here's the code: (formating sure doesn't look as nice on here as it does on my editor)

Code:
;WOPRjr OS


      .ORG $0000      
      
      
      
ACIA_DAT = $5000
ACIA_STA = ACIA_DAT+1
ACIA_CON = ACIA_DAT+3
ACIA_COM = ACIA_DAT+2



STRING_PTR    .DS    $02      ;pointer to current output message string
STRING_INDEX    .DS    $01      ;index into input buffer
LINE_CNT    .DS   $01      ;clear screen line count
CMD_INDEX   .DS   $02      ;index into command string list
SELECTED_CMD:   .DS   $02      ;pointer to slected command routine

      .ORG   $0200
                             
ACIA_RXBUF    .DS   $100      ;input buffer

      .ORG $8000
      
      

;command strings      
commands:   
cmd_empty:   .BYTE   $0D, $00   ;empty:user pressed enter with no characters
cmd_write:   .BYTE   "write", $00   ;command to write to memory
cmd_read:   .BYTE    "read", $00   ;command to read from memory
cmd_test:   .BYTE   "test", $00   ;command for system self-test
cmd_list_end:   .BYTE   $FF      ;marker for end of list

;list of pointers to command strings
cmd_indices:
empty_index:   .WORD   cmd_empty
write_index:    .WORD   cmd_write
read_index:    .WORD    cmd_read
test_index:    .WORD   cmd_test

;list of pointers to command routines
cmd_routines:
empty_rtn_ptr:   .WORD   empty_rtn
write_rtn_ptr:   .WORD   write_rtn
read_rtn_ptr:   .WORD   read_rtn
test_rtn_ptr:   .WORD   test_rtn
no_cmd_rtn_ptr: .WORD   no_cmd_rtn   
      
strings:
prompt:      .BYTE   $0D, $0A, "WOPRjr:" ,$00    ;commandline prompt
empty_msg   .BYTE   $0D, $0A, $00         ;empty string
message:   .BYTE   $0D, $0A, "You entered: ", $00   ;input response message
write_msg:   .BYTE   $0D, $0A, "writing", $00   ;temp write message
read_msg:   .BYTE   $0D, $0A, "reading", $00   ;temp read message
test_msg:   .BYTE   $0D, $0A, "testing", $00   ;temp test message
no_cmd_msg:   .BYTE   $0D, $0A, "unknown command", $00 ;default message for unknown string
      
            
start:      LDX   #$FF   
      TXS         ;Set stack pointer to top of page 1
      STZ   STRING_INDEX   ;initialize string index to 0
      JSR   uartinit   ;initialize ACIA
      CLI         ;turn on interrupts
      LDX    #$1A
clr_loop:   LDA   ACIA_STA   ;get ACIA status register
      AND   #@00010000   ;check Tx buffer empty. 1 is empty, 0 is not empty
      BEQ    clr_loop   ;keep waiting until Tx buffer is empty
      LDA    #$0A
      STA    ACIA_DAT
      DEX
      BNE   clr_loop
      STA   ACIA_DAT
      LDA    #$0D
      STA   ACIA_DAT         
      LDA   #<prompt   ;get lower byte of prompt message
      STA   STRING_PTR   ;store it in first byte of the string pointer
      LDA   #>prompt;   ;get upper byte of prompt message
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;display prompt
inf_loop:   NOP
      JMP   inf_loop            
               
            
      
      
uartinit:   
      STZ   ACIA_STA   ;write a zero to ACIA status regidter to reset chip
      LDA   #@00011110   ;ACIA control register setting for 1 stop,, 8 data, 9600 baud         
      STA   ACIA_CON   ;set ACIA control register
      LDA   #@00001001   ;no parity, no echo, no Tx IRQ, RTSB LOW, Rx IRQ enabled, DTRB LOW
      STA    ACIA_COM   ;set ACIA command register
      RTS

   
terminal_w:   LDY   #$00      ;set index to zero
write_loop:   LDA   ACIA_STA   ;get ACIA status register
      AND   #@00010000   ;check Tx buffer empty. 1 is empty, 0 is not empty
      BEQ    write_loop   ;keep waiting until Tx buffer is empty
      LDA   (STRING_PTR),Y   ;put current character A
      BEQ   tw_end
      STA   ACIA_DAT   ;send character to ACIA
      INY         ;move to next character
      BNE   write_loop   ;if not NULL keep going
tw_end:      RTS
      
terminal_r:   LDA   ACIA_DAT   ;get data  from ACIA Rx   
      CMP   #$0D      ;check if enter was pressed
      BEQ   process_cmd   ;if enter pressed, write string to screen
      STA   ACIA_DAT
      LDX   STRING_INDEX   ;get string index
      STA    ACIA_RXBUF,X   ;place recieved data into input buffer
      INX         ;increment it
      STX   STRING_INDEX   ;put incremented version back in memory
      RTS
process_cmd:   
      STZ   ACIA_RXBUF,X   ;put NULL on end of string
      STZ   STRING_INDEX   ;reset index
      JSR   parse_cmd   ;parse the command
      JMP    (SELECTED_CMD)   ;run routine for selected command
rtn_to_tr:   LDA   #<prompt   ;get lower byte of prompt message
      STA   STRING_PTR   ;store it in first byte of the string pointer
      LDA   #>prompt;   ;get upper byte of prompt message
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;display prompt
      RTS      
      
      
      
      
      
parse_cmd:   LDX   #$00      ;reset X register
cmd_list_lp:   LDA   cmd_routines,X   ;get address of currently being checked command's routine
      STA   SELECTED_CMD   ;store it in first byte of command routine pointer
                LDA   cmd_indices,X   ;get address of next command string
      STA   CMD_INDEX   ;store it in zero page so it can used as a pointer
      INX         ;increment x so we can get next byte of command string address
      LDA   cmd_routines,X   ;get second byte of current command routine pointer
      STA   SELECTED_CMD+1   ;put byte in secdond half of 0 page command routine pointer
      LDA   cmd_indices,X   ;get next byte of command string address
      STA   CMD_INDEX+1   ;put byte in zero page to form the completed address
      INX         ;increment X in case we need to check next command string
      LDY   #$00      ;reset Y register
      LDA    #$FF      ;$FF is marker for end of command string list
      CMP   (CMD_INDEX),Y   ;check if we are at end of command string list
      BEQ   no_match   ;got to no match routine
string_cmp:   LDA   ACIA_RXBUF,Y   ;get current character of input string   
      CMP   (CMD_INDEX),Y   ;compare character to same char position in command string being checked
      BNE   cmd_list_lp   ;if no match, try next command string
      INY         ;incrementY to index of next character in case we need to loop again
      CMP   #$00      ;check if current character is NULL (end of string)
      BNE   string_cmp   ;if not NULL, check next characters for match
      RTS         ;if IS NULL, we have a match at this point. Proper routine's pointer will be in SELECTED_CMD
no_match:   LDA    #<no_cmd_rtn   ;get lower byte of Unknown Command rotine's address
      STA   SELECTED_CMD   ;put in first byte of selcected command pointer
      LDA   #>no_cmd_rtn   ;get upper byte
      STA   SELECTED_CMD+1   ;put in second byte of pointer
      RTS         ;return. Unknown Command routine is in sELECTED_CMD      
                                    


empty_rtn:   STZ   STRING_INDEX   ;reset index
      LDA   #<empty_msg   ;get lower byte of canned output response
      STA   STRING_PTR   ;put it in first byte of the string pointer
      LDA   #>empty_msg   ;get upper byte
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;output canned message   
      JMP    rtn_to_tr   ;back to command handler
      
write_rtn:   STZ   STRING_INDEX   ;reset index
      LDA   #<write_msg   ;get lower byte of canned output response
      STA   STRING_PTR   ;put it in first byte of the string pointer
      LDA   #>write_msg   ;get upper byte
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;output canned message   
      JMP    rtn_to_tr   ;back to command handler
      
read_rtn:   STZ   STRING_INDEX   ;reset index
      LDA   #<read_msg   ;get lower byte of canned output response
      STA   STRING_PTR   ;put it in first byte of the string pointer
      LDA   #>read_msg   ;get upper byte
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;output canned message   
      JMP    rtn_to_tr   ;back to command handler               
      
test_rtn:   STZ   STRING_INDEX   ;reset index
      LDA   #<test_msg   ;get lower byte of canned output response
      STA   STRING_PTR   ;put it in first byte of the string pointer
      LDA   #>test_msg   ;get upper byte
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;output canned message   
      JMP    rtn_to_tr   ;back to command handler

no_cmd_rtn:   STZ   STRING_INDEX   ;reset index
      LDA   #<no_cmd_msg   ;get lower byte of canned output response
      STA   STRING_PTR   ;put it in first byte of the string pointer
      LDA   #>no_cmd_msg   ;get upper byte
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;output canned message   
      JMP    rtn_to_tr   ;back to command handler
      
isr:      LDA   ACIA_STA   ;get ACIA status register
      BPL   end_isr      ;if no IRQ, return from ISR
      JSR   terminal_r   
end_isr:   RTI   
                        
      .ORG $FFFA      ;6502 NMI, RST, and IRQ vectors
      
      .WORD start      ;NMI
      .WORD start      ;RST
      .WORD isr      ;IRQ


Top
 Profile  
Reply with quote  
PostPosted: Mon Apr 24, 2017 5:27 am 
Offline
User avatar

Joined: Tue Nov 16, 2010 8:00 am
Posts: 2353
Location: Gouda, The Netherlands
Also, if you have JSR followed by RTS, you can use a JMP. For instance, in some of my code I have a 'putdigit' routine that converts a value 0-9 to ASCII, and prints it using the 'putchar' routine. Instead of calling putchar with JSR, it uses JMP. At the end of putchar, the RTS takes it back to where it came from.
Code:
putdigit:
        ADC     #'0'
        JMP     putchar

Sometimes, you don't even have to use the JMP, you can just put the second routine after the first one, and just 'fall through'. I do that in my code too in the 'putnibble' routine which converts a single hex digit to ASCII and prints it:
Code:
putnibble:
        CMP     #10
        BCC     putdigit
        ADC     #'a'-'0'-11
putdigit:
        ADC     #'0'
        JMP     putchar

If called with a value < 10, it jumps to putdigit to print it directly. If it's more than 10, it adds a correction value first, and then falls into the putdigit routine just the same. Now, if you want to print a hex byte instead of just a nibble, you can do this:
Code:
puthex:
        PHA                             
        LSR     A                       
        LSR     A                       
        LSR     A                       
        LSR     A                       
        JSR     putnibble               
        PLA                             
        AND     #$0F                   
putnibble:
        CMP     #10
        BCC     putdigit
        ADC     #'a'-'0'-11
putdigit:
        ADC     #'0'
        JMP     putchar

Notice how I first use a 'JSR putnibble' to print the left nibble, and then fall through the same putnibble routine to print the right nibble. And each of the 3 routines can also be called from other places in the code. For instance, when writing a decimal number, I call the same putdigit routine.


Top
 Profile  
Reply with quote  
PostPosted: Mon Apr 24, 2017 6:04 am 
Offline
User avatar

Joined: Thu May 28, 2009 9:46 pm
Posts: 8468
Location: Midwestern USA
Here is how I do command parsing in Supermon 816:

Code:
;================================================================================
;
;MACHINE LANGUAGE MONITOR — COMMAND EXECUTIVE
;   
monce    shorta                ;set 8 bit accumulator
         lda #0                ;default buffer index
;
moncea   shortr                ;all registers 8 bits
         sta ibufidx           ;(re)set buffer index
         pea #mm_prmpt
         jsr sprint            ;display input prompt
;
monceb   jsr input             ;wait for console input
;
.0000010 jsr getcharc          ;read from buffer
         beq monce             ;terminator, just loop
;
         cmp #a_blank
         beq .0000010          ;strip leading blanks
;
         ldx #n_mpctab-1       ;number of primary commands
;
.0000020 cmp mpctab,x          ;search primary command list
         bne .0000040
;
         txa                   ;get index
         asl a                 ;double for offset
         tax
         longa                 ;16 bit accumulator
         lda mpcextab,x        ;load command address -1
;
.0000030 pha                   ;prime the stack
         shorta                ;8 bit accumulator
         jmp getparm           ;evaluate 1st parameter & execute command
;
.0000040 dex
         bpl .0000020          ;continue searching primary commands
;
         ldx #n_radix-1        ;number of radices
;
.0000050 cmp radxtab,x         ;search conversion command list
         bne .0000060
;
         jmp monenv            ;convert & display parameter
;
.0000060 dex
         bpl .0000050
;
         cmp #scsipre          ;SCSI command preamble?
         bne monerraa          ;no, unknown command — error
;
.0000070 jsr getcharc          ;read next char from buffer
         beq monerraa          ;no char — error
;
         cmp #a_blank
         beq .0000070          ;ignore blanks
;
         ldx #n_spctab-1       ;number of SCSI commands
;
.0000080 cmp spctab,x          ;search SCSI command list
         bne .0000090
;
         txa                   ;get index
         asl a                 ;double for offset
         tax
         longa                 ;16 bit accumulator
         lda spcextab,x        ;load command address -1
         bra .0000030          ;eval parm & execute command
;
.0000090 dex
         bpl .0000080
;
;================================================================================
;
;MACHINE LANGUAGE MONITOR — COMMON ERROR HANDLER
;
monerr   shortr                ;8 bit registers
;
monerraa jsr dpyerr            ;indicate an error
         bra monce             ;return to input loop

The interesting part is at label .0000030. Once the command has been found in the supported commands table (all commands are one letter), the resulting index is used to prime the stack with the address of the desired function minus one. A jump is made to getparm, which evaluates the first argument to the command, if an argument is present. getparm is a subroutine, so the RTS that ends it causes the function address that was pushed before the jmp getparm instruction to become the return address. Hence the desired function is executed after the command argument evaluation has been completed without error.

getparm converts the argument to a binary value in the range $00000000-$FFFFFFFF and indicates if an argument was converted and if so, its magnitude in significant bytes. If the argument can't be converted to binary from one of the four number bases supported by the monitor getparm aborts to the error handler.

Incidentally, since the 65C816 natively handles 16 bit values the process of "priming" the stack is reduced to a single read of the address table and one accumulator push. With the 65C02, two reads and pushes will have to be made, with the most significant byte being pushed first.

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


Top
 Profile  
Reply with quote  
PostPosted: Mon Apr 24, 2017 6:56 am 
Offline
User avatar

Joined: Wed Mar 01, 2017 8:54 pm
Posts: 660
Location: North-Germany
Dan Moos wrote:
Code:
;WOPRjr OS

...
CMD_INDEX   .DS   $02      ;index into command string list
DISPATCH: BYTE $20            ;use JSR DISPATCH to call your selected command
SELECTED_CMD:   .DS   $02      ;pointer to slected command routine
          BYTE $60            ;return to caller
...
      .ORG   $0200
...
start:      LDX   #$FF   
      TXS         ;Set stack pointer to top of page 1
      STZ   STRING_INDEX   ;initialize string index to 0
      JSR   uartinit   ;initialize ACIA
      CLI         ;turn on interrupts
      LDX    #$1A
clr_loop:   LDA   ACIA_STA   ;get ACIA status register
      AND   #@00010000   ;check Tx buffer empty. 1 is empty, 0 is not empty
      BEQ    clr_loop   ;keep waiting until Tx buffer is empty
      LDA    #$0A
      STA    ACIA_DAT
      DEX
      BNE   clr_loop
      STA   ACIA_DAT  ; <==== either 1 LF too much or missing Tx_free wait for CR
      LDA    #$0D
      STA   ACIA_DAT   ; <===== no wait here, destroys prev. LF      
      LDA   #<prompt   ;get lower byte of prompt message
      STA   STRING_PTR   ;store it in first byte of the string pointer
      LDA   #>prompt;   ;get upper byte of prompt message
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;display prompt
inf_loop:   NOP
      JMP   inf_loop            
...

I didn't scan the rest of your code - no time left. At top I added two bytes as another alternative to substitute JSR (GOAL).


Top
 Profile  
Reply with quote  
PostPosted: Mon Apr 24, 2017 7:07 pm 
Offline
User avatar

Joined: Wed Mar 01, 2017 8:54 pm
Posts: 660
Location: North-Germany
Dan Moos wrote:
Code:
...

terminal_r:   LDA   ACIA_DAT   ;get data  from ACIA Rx   
      CMP   #$0D      ;check if enter was pressed
      BEQ   process_cmd   ;if enter pressed, write string to screen
      STA   ACIA_DAT
      LDX   STRING_INDEX   ;get string index
      STA    ACIA_RXBUF,X   ;place recieved data into input buffer
      INX         ;increment it
      STX   STRING_INDEX   ;put incremented version back in memory
      RTS
process_cmd:   
      STZ   ACIA_RXBUF,X   ;put NULL on end of string
      STZ   STRING_INDEX   ;reset index
      JSR   parse_cmd   ;parse the command
      JMP    (SELECTED_CMD)   ;run routine for selected command
rtn_to_tr:   LDA   #<prompt   ;get lower byte of prompt message
      STA   STRING_PTR   ;store it in first byte of the string pointer
      LDA   #>prompt;   ;get upper byte of prompt message
      STA   STRING_PTR+1   ;store it in second byte of string pointer
      JSR   terminal_w   ;display prompt
      RTS      
...

In terminal_r you echo and put any char you received into your buffer - except <CR>. This is neither echoed nor placed into the buffer. But your "cmd_empty" is <CR><NULL>.
If <CR> is detected you branch directly to the parser. It's a bit hard to see how you return to the interrupted program once parsing is done. Perhaps you could verify the stackpointer, whether it doesn't run away during/after parsing - just to be sure.


Top
 Profile  
Reply with quote  
PostPosted: Tue Apr 25, 2017 12:38 am 
Offline

Joined: Sat Mar 11, 2017 1:56 am
Posts: 276
Location: Lynden, WA
I was aware of my problem with an empty CR. It will be tended to.

Could you elaborate on your notion of keeping track of the stack?


Top
 Profile  
Reply with quote  
PostPosted: Tue Apr 25, 2017 6:44 am 
Offline
User avatar

Joined: Wed Mar 01, 2017 8:54 pm
Posts: 660
Location: North-Germany
So, it took a while, but I'm through. :)
No, there is no JSR without corresponding RTS. That was, what I feared, because this would corrupt the stack. But it's OK :D

Beside the <CR> handling, I have found only this: every time you get a character (BTW you didn't check the status register against RDRF) and it is not <CR> you echo it immediately - without looking whether Tx is currently in use.

I have no experience how the 6551 behaves and whether there are side effects, if one writes to its data register before it's empty. But if you put a small wait_while_Tx_not_free_loop in front of your character echo you can verify whether things changes or not.


Top
 Profile  
Reply with quote  
PostPosted: Tue Apr 25, 2017 7:48 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8534
Location: Southern California
GaBuZoMeu wrote:
No, there is no JSR without corresponding RTS. That was, what I feared, because this would corrupt the stack. But it's OK :D

I can't find where this came from, but maybe it's because we're on page 11 of this topic now. But for interest's sake, or in case it matters for the WOPR Jr., the following is from the middle of the "Synthesizing instructions with RTS, RTI, and JSR" chapter of the 6502 stacks treatise:

    In section 7, we looked at how a subroutine can find inlined data following a call to that subroutine, by the fact that the JSR puts its own ending address on the hardware stack. The subroutine adjusted the return address on the stack so that when the processor gets back to the main program, it would skip over the data and not try to execute it as if it were instructions and crash.

    Now we'll add another twist. You can do the same thing without the JSR having a matching RTS. The called code piece will probably still end in RTS, but it will have removed a return address from the stack after having used it to find the data, so the RTS will instead take the program pointer back to the routines that called label1, label2, etc. (shown below). In the following example, we have various places in the code that start with optional individualized actions, and they have individualized data, but then have a common way to handle that data:

    Code:
    label1: <do "A" stuff>
            <do "A" stuff>
            JSR  Foobar
            <data_relating_to_A>


      (and elsewhere in the program,)


    label2: <do "B" stuff>
            <do "B" stuff>
            JSR  Foobar
            <data_relating_to_B>


      (etc.)


    Foobar: <Do the process common to A, B, and relatives, using the data following the
              JSRs.  After using the address stacked by a JSR to find data, discard
              that address.  (You will not RTS to the JSRs that called Foobar.)>

    From WDC's excellent programming manual which I can never pass up an opportunity to recommend, "Programming the 65816, Including the 6502, 65C02 and 65802," chapter 12, and page 190:

      Apple Computer's ProDOS operating system takes this method a step further: all operating system routines are called via a JSR to a single ProDOS entry point. One of the parameters that follow the JSR specifies the routine to be called, the second parameter specifies the address of the routine's parameter block. This method allows the entry points of the internal ProDOS routines to "float" from one version of ProDOS to the next; user programs don't need to know where any given routine is located.

_________________
http://WilsonMinesCo.com/ lots of 6502 resources
The "second front page" is http://wilsonminesco.com/links.html .
What's an additional VIA among friends, anyhow?


Top
 Profile  
Reply with quote  
PostPosted: Tue May 02, 2017 2:29 am 
Offline

Joined: Sat Mar 11, 2017 1:56 am
Posts: 276
Location: Lynden, WA
This falls under the heading of "programming style" question

So as I work on my monitor, I am using more and more variables in RAM. Many (most?) would be variables that would be done as local variables in C.

so as it stands now, I have a unique label in RAM for all these things. Mostly in 0 page. Not to many yet, but the list will only grow.

So, this seems like a kinda inefficient use of a limited resource to me.

I could also give the labels more generic names, and basically treat RAM like a bunch of multi use registers, but that sacrifices readability.

I suppose I could also use multiple labels for the same RAM location, but that seems kinda messy to me too.

So what do you guys tend to do? As it stands now, I'm only using 7 bytes of 0 page, and a 256 byte buffer in page 2. So I'm really small at the moment. I just want some ideas of how more seasoned assembly programmers deal with this.


Top
 Profile  
Reply with quote  
PostPosted: Tue May 02, 2017 3:35 am 
Offline
User avatar

Joined: Tue Mar 05, 2013 4:31 am
Posts: 1385
Dan Moos wrote:
This falls under the heading of "programming style" question

So as I work on my monitor, I am using more and more variables in RAM. Many (most?) would be variables that would be done as local variables in C.

so as it stands now, I have a unique label in RAM for all these things. Mostly in 0 page. Not to many yet, but the list will only grow.

So, this seems like a kinda inefficient use of a limited resource to me.

I could also give the labels more generic names, and basically treat RAM like a bunch of multi use registers, but that sacrifices readability.

I suppose I could also use multiple labels for the same RAM location, but that seems kinda messy to me too.

So what do you guys tend to do? As it stands now, I'm only using 7 bytes of 0 page, and a 256 byte buffer in page 2. So I'm really small at the moment. I just want some ideas of how more seasoned assembly programmers deal with this.


It really depends on what your monitor functions are, how many there are and how you want to structure things. I maintain a small BIOS that handles a 6551 and 6522 and provides full duplex interrupt-driven I/O, timers for RTC and delay routines (also interrupt-driven), a BRK handler, NMI handler, Port I/O for the VIA, etc. I reserve the top 32 bytes of Page 0 for the BIOS and currently have one spare byte left. The Monitor uses a bit more as there several pointers, both 8- and 16-bit used for various functions. I reserve 48 bytes of Page 0 for the monitor and have one spare byte there as well. Overall stack use is 28 bytes deep regardless of what you do. I also consume page 2 which is split into two 128-byte buffers for the 6551 input/output and Page 3 is consumed for Vectors, Vector inserts, I/O config data, Search buffer, Xmodem buffer and a Motorola S-Record buffer.

Have you designed your Monitor from a set of base requirements that define everything or are you just winging it as you start writing code and making programming and memory layout/usage decisions on the fly? Granted you can do it anyway you like, but things tend to get a bit messy without some sort of overall design/plan. Here's a list of the BIOS variables setup in Page 0 for what I'm using, just to give you an idea on how I'm using it:

Code:
;
;   BIOS variables, pointers, flags located at top of Page Zero.
BIOS_PG0   .EQU   $E0   ;PGZERO_ST+96   ;Start of BIOS page zero use ($E0-$FF)
;   - BRK handler routine
PCL            .EQU   BIOS_PG0+0   ;Program Counter Low index
PCH            .EQU   BIOS_PG0+1   ;Program Counter High index
PREG         .EQU   BIOS_PG0+2   ;Temp Status reg
SREG         .EQU   BIOS_PG0+3   ;Temp Stack ptr
YREG         .EQU   BIOS_PG0+4   ;Temp Y reg
XREG         .EQU   BIOS_PG0+5   ;Temp X reg
AREG         .EQU   BIOS_PG0+6   ;Temp A reg
;
;   - 6551 IRQ handler pointers and status
ICNT         .EQU   BIOS_PG0+7   ;Input buffer count
IHEAD         .EQU   BIOS_PG0+8   ;Input buffer head pointer
ITAIL         .EQU   BIOS_PG0+9   ;Input buffer tail pointer
OCNT         .EQU   BIOS_PG0+10   ;Output buffer count
OHEAD         .EQU   BIOS_PG0+11   ;Output buffer head pointer
OTAIL         .EQU   BIOS_PG0+12   ;Output buffer tail pointer
STTVAL      .EQU   BIOS_PG0+13   ;6551 BIOS status byte
;
;   - Real-Time Clock variables
TICKS         .EQU   BIOS_PG0+14   ;# timer countdowns for 1 second (250)
SECS         .EQU   BIOS_PG0+15   ;Seconds: 0-59
MINS         .EQU   BIOS_PG0+16   ;Minutes: 0-59
HOURS         .EQU   BIOS_PG0+17   ;Hours: 0-23
DAYSL         .EQU   BIOS_PG0+18   ;Days: (2 bytes) 0-65535 >179 years
DAYSH         .EQU   BIOS_PG0+19   ;High order byte
;
;   - Delay Timer variables
MSDELAY      .EQU   BIOS_PG0+20   ;Timer delay countdown byte (255 > 0)
MATCH         .EQU   BIOS_PG0+21   ;Delay Match flag, $FF is set, $00 is cleared
SETIM         .EQU   BIOS_PG0+22   ;Set timeout for delay routines - BIOS use only
DELLO         .EQU   BIOS_PG0+23   ;Delay value BIOS use only
DELHI         .EQU   BIOS_PG0+24   ;Delay value BIOS use only
XDL            .EQU   BIOS_PG0+25   ;XL Delay count
STVVAL      .EQU   BIOS_PG0+26   ;Status for VIA IRQ flags
;
;   - I/O port variables
IO_DIR      .EQU   BIOS_PG0+27   ;I/O port direction temp
IO_IN         .EQU   BIOS_PG0+28   ;I/O port Input temp
IO_OUT      .EQU   BIOS_PG0+29   ;I/O port Output temp
;
; - Xmodem variables
XMFLAG      .EQU   BIOS_PG0+30   ;Xmodem transfer active flag
SPARE_B      .EQU   BIOS_PG0+31   ;Spare BIOS page zero byte
;

_________________
Regards, KM
https://github.com/floobydust


Top
 Profile  
Reply with quote  
PostPosted: Tue May 02, 2017 4:50 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8534
Location: Southern California
Dan Moos wrote:
Many (most?) would be variables that would be done as local variables in C.

I cover some of the ways to do local variables in assembly in the stacks treatise, especially section 5, Stack addressing, both hardware and virtual, plus tricks and section 14, "Local variables & environments. Locals that are on the hardware stack won't have all the addressing modes of ZP, but you can move something into a ZP temporary register when needed.

Quote:
so as it stands now, I have a unique label in RAM for all these things. Mostly in 0 page. Not to many yet, but the list will only grow.

So, this seems like a kinda inefficient use of a limited resource to me.

ZP is efficient of course, but a lot of things, especially in a monitor where the speed of the human eye or typing limits the need for computing speed, most of your variables could go elsewhere.

Quote:
I could also give the labels more generic names, and basically treat RAM like a bunch of multi use registers, but that sacrifices readability.

I suppose I could also use multiple labels for the same RAM location, but that seems kinda messy to me too.

Been there, done that. You have to be so careful to avoid using a variable for one thing while another pending routine might still need the data in it for something else. It's really asking for trouble that's difficult to debug; so consider it a last resort.

_________________
http://WilsonMinesCo.com/ lots of 6502 resources
The "second front page" is http://wilsonminesco.com/links.html .
What's an additional VIA among friends, anyhow?


Top
 Profile  
Reply with quote  
PostPosted: Tue May 02, 2017 5:39 am 
Offline
User avatar

Joined: Thu May 28, 2009 9:46 pm
Posts: 8468
Location: Midwestern USA
Dan Moos wrote:
This falls under the heading of "programming style" question

So as I work on my monitor, I am using more and more variables in RAM. Many (most?) would be variables that would be done as local variables in C.

so as it stands now, I have a unique label in RAM for all these things. Mostly in 0 page. Not to many yet, but the list will only grow.

So, this seems like a kinda inefficient use of a limited resource to me.

I could also give the labels more generic names, and basically treat RAM like a bunch of multi use registers, but that sacrifices readability.

I suppose I could also use multiple labels for the same RAM location, but that seems kinda messy to me too.

So what do you guys tend to do? As it stands now, I'm only using 7 bytes of 0 page, and a 256 byte buffer in page 2. So I'm really small at the moment. I just want some ideas of how more seasoned assembly programmers deal with this.

As a matter of programming style, I use zero page only for things that can only be done on zero page, such as indirect addressing, or for data that are accessed a lot in a very short time. Supermon 816 uses quite a bit of direct page (zero page) for pointers and flags, but also uses absolute RAM for buffering, string assembly and temporary storage. As string assembly and character input never simultaneously occur the same piece of RAM is used for both purposes. This is also true for some direct page locations, which serve dual or even triple purposes.

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


Top
 Profile  
Reply with quote  
PostPosted: Tue May 02, 2017 7:12 am 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10971
Location: England
Hmm, I would have thought a few re-used locations in zero page was a good model for the local variables in a language like C. In neither case do you expect the values to be retained from one invocation to the next. Of course if you have nested routines you need to take care that the inner routines don't use the locations used by the outer ones. But if your call graph is simple enough, and static, and there's no recursion, I would think you could plan it out.


Top
 Profile  
Reply with quote  
PostPosted: Tue May 02, 2017 8:03 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8534
Location: Southern California
BigEd wrote:
Hmm, I would have thought a few re-used locations in zero page was a good model for the local variables in a language like C. In neither case do you expect the values to be retained from one invocation to the next. Of course if you have nested routines you need to take care that the inner routines don't use the locations used by the outer ones. But if your call graph is simple enough, and static, and there's no recursion, I would think you could plan it out.

One thing that makes it difficult is that a routine needing its own variables will get called from multiple various routines (if it were always from the same one, you might as well straightline it), at different depths of nesting, and the different sequences of outer routines may have different needs for local variable space. It becomes pretty much impossible to assign a static address for these variables. When I said earlier, "Been there, done that," I was thinking of work projects on the PIC16 whose RAM is very limited and its stack (both hardware and virtual) capabilities are even more limited. I had to be extremely careful, and put a lot of notes about such variables in the comments.

A ZP virtual stack can be used, with X as the stack pointer. It has various pros and cons compared to putting the temporary variables on the page-1 hardware stack, but I think the net effect would be rather favorable.

There is another possibility which I mention in the stacks treatise, a way to have a small local-variable space that does not involve a stack, and that is Forth's N, a space of usually around 8 bytes which any primitive can use any way it likes, but it must be completely done with it when the primitive finishes executing. It is never to be used to pass data from one primitive to another, or to keep data for the next time the same primitive runs.

I'm always straining for additional tools, possibly better ways, to do these things though.

_________________
http://WilsonMinesCo.com/ lots of 6502 resources
The "second front page" is http://wilsonminesco.com/links.html .
What's an additional VIA among friends, anyhow?


Top
 Profile  
Reply with quote  
PostPosted: Tue May 02, 2017 8:49 am 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10971
Location: England
OK, different depths, good point! It seems like a packing puzzle. What would be nice is a way to express these overlapping allocations in the assembly source code without having a maintenance nightmare.


Top
 Profile  
Reply with quote  
Display posts from previous:  Sort by  
Post new topic Reply to topic  [ 321 posts ]  Go to page Previous  1 ... 8, 9, 10, 11, 12, 13, 14 ... 22  Next

All times are UTC


Who is online

Users browsing this forum: No registered users and 11 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: