Classic Computer Magazine Archive COMPUTE! ISSUE 47 / APRIL 1984 / PAGE 124

MACHINE LANGUAGE

Jim Butterfield, Associate Editor

A Program Critique

Part 1

Over the next few columns, I'll be going through a program by Bud Rasmussen. This program performs a single disk file copy on the Commodore 64. It works well; I'll abridge the program slightly to save space.

The program is exceedingly well organized; it's a pleasure to read. It has good operator interface (there are lots of messages) and performs many useful functions in machine language that readers may wish to study and use.

The program was written using an assembler, in this case the PAL assembler by Brad Templeton. Other assemblers would do the job equally well, but they might require slight changes in syntax.

My role here will be (with Rasmussen's permission) to critique and comment. Since the program works, the criticism is one of style rather than of substance.

Different But Still Right

I should note that Rasmussen wrote this program, not for commercial purposes or publication, but for his own satisfaction and use. I'll be somewhat unfairly criticizing his program based on its appropriateness for general usage. For example, I may comment adversely on such things as his use of a BRK instruction to terminate the program on certain error conditions, because this would be undesirable in a public program. But in the final analysis, it's Rasmussen's personal program and it works the way he planned it.

Accept these comments as ideas on how to organize your own work. You'll find a lot of good machine language programming techniques in the program.

;
ML FILE COPIER
;
;
; IMMEDIATE VALUES
;
;
RK    = 13     ;RETURN KEY
H10   = 16     ;HEX TEN
DK    = 20     ;DEL KEY
C     = 44     ;','(COMMA)
EOFI  = 64     ;END OF FILE INDICATOR
W     = 87     ;'W'( WRITE)
CH    = 147    ;CLEAR/HOME

Many programmers like to equate constant values to labels. This way, if you want to print RETURN, you can write LDA #RK instead of LDA #$0D followed by JSR $FFD2 to print.

My preference is to skip the symbol and use the $0D value, as long as it is the same on all machines. It seems to me that the symbolic values are useful only when different machines use different values for the same function. In such a case, you would indeed equate the appropriate value to a label and save yourself work.

The next section (not given here) defines zero page, working storage, and Kernal addresses. You will be able to pick these out directly from the program, as needed.

C000	* = $C000

A Program Counter

Many assemblers use the asterisk character (*) as a program counter. In this case, the program will start at hexadecimal C000. The asterisk is often read as "here"; so a programmer may verbalize this line as "Here is hex C000."

                ;
                ;
                ;SCREEN ROUTINE
                ;                ;CLEAR SCREEN
                ;
                ;
                CS   =  *
                ;
C000 A9 93          LDA #CH        ; LOAD CLR/HOME
C002 20 D2 FF 	  JSR CHROUT     ; PUT IT
                ;
	       ;
	       ;CHG COLORS
	       ;
	       ;
	       CC  =  *
                ;
C005 A9 07	 LDA #7         ;SET
C007 8D 20 D0      STA BCA	       ;BORDER COLOR
C00A A9 05	 LDA #5         ;SET
CO0C 8D 21 D0      STA BGCA       ;BACK GROUND COLOR
C00F A9 01	 LDA #1         ;SET
C011 8D 86 02      STA CCA	       ;CHARACTER COLOR

As you can see, the documentation is extensive. The program is placed at address $C000, the spare RAM block in high memory.

"CS = *" means "label CS is this point," or "CS is here"; it's a way of defining symbolic locations so that they stand out. Rasmussen uses this type of label definition extensively. Placing the label on the next program line will work just as well; to save space, I'll do this in most cases.

Character color could also be set by calling the CHROUT routine, $FFD2, with the appropriate ASCII color character in the A register.

                  ;
		;POSITION CURSOR
                  ;
                  ;
C014 A2 03       PC     LDX #3	;ROW = 3
C016 A0 00	      LDY #0	;COLUMN = 0
C018 18                 CLC		;AND
C019 20 F0 FF	      JSR PLOT	;SET CURSOR

I'd just as soon print three cursor-down or return characters.

		;
		;CLEAR FILE NAME AREA
		;
		;
C01C A9 00	CFNA LDA #0	;SET'A'=O
CO1E AA                TAX		;SET'X' = O
                  ;
COIF 9D 40 03     CFNL STA FNA,X	;CLEAR FILE NAME
C022 E8                INX		;INCR INDEX
C023 EO 15             CPX #21       ;ISX = 21 (16 + 4 + 1)
C025 FO 02	     BEQ PM        ;IF SO, EXIT
C027 DO F6	     BNE CFNL      ;ELSE, LOOP
		;

This is probably overkill, since the area will be filled with appropriate characters before it is used. I would opt for insertion of a prefix "0:" which here would appear ahead of the file name. Sometimes the disk seems to work better if drive 0 is explicitly identified.

BNE Alone Also Works

I would have put the BNE ahead of the BEQ. Then I would have dropped the BEQ since the program would proceed to the next statement, PM, anyway.

	
		         ;
			; PUT MESSAGE
			;
			;
C029 A2 F4		PM    LDX #ML	; LOAD LENGTH
C02B A0 CO 		      LDY #>IM	; LOAD HI BYTE		
C02D A9 35 		      LDA #<IM	; LOAD LO BYTE
C02F 20 75 Cl                    JSR PR 	; PRINT MSG
		  	;	
C032 4C 29 Cl                    JMP GI 	; GOTO GET INPUT
			;
			;
			; INFORMATION MESSAGE
			;
			;
C035 12                    IM    .BYTES12
C036 20 20 4B 		     .ASC" KEY IN THE FILE NAME OF"
C050 0D 0D 12 		     .BYTE$0D,$0D,$12
C053 20 20 54 		     .ASC "THE FILE TO BE COPIED,"
C06C 0D 0D 12 		     .BYTE$0D,$0D,$12
C06F 20 20 41 		     .ASC"ASN…..,T-"
C081 0D 0D 12 		     .BYTE$0D,$0D,$12
C084 20 20 4E 		     .ASC"N = NAME, T = TYPE(PORS)"
C09E 0D 0D 12 		     .BYTE$0D,$0D,$12
C0A1 20 20 4D 		     .ASC"MAXIMUM NAME = 16BYTES"
C0BB 0D 0D 12 		     .BYTE$0D,$0D,$12
COBE 20 20 4B 		     .ASC"KEY<RET> WHENFINISHED."
C0D8 0D 0D 12 		     .BYTE$OD,$0D,$12
C0DB 20 20 49 		     .ASC "IF YOU MAKE A MISTAKE,"
C0F5 0D 0D 12 		     .BYTE$0D,$0D,$12
C0F8 20 20 55 		     .ASC "USE THE DELETE KEY. "
C10E 0D 0D 12 		     .BYTE$0D,$0D,$12
Clll 20 20 20 		     .ASC"CHEERSH!!!"
C126 0D 0D 0D 		     .BYTE$OD,$0D,$OD
                           ML    = * - IM
			;
			;
			;GET INPUT
			;
			;
			GL    = *
			;

Note how the message length is calculated automatically by the assembler (ML = * - IM). The end of message plus one ("here") minus the start of message gives the length.

Subroutine PR is shown later. As can be seen from the program segment above, the high and low parts of the message address are loaded into registers Y and A respectively, the length into register X; then PR is called. We'll look at that subroutine when it comes up.

An Unusual Place For Messages

The message text is thrown in-line directly behind the program segment that uses it. This is unusual: It's more common for all text, tables, and variables to be placed at the end of the program. During the program development phase things might be out of order, but it's usual to clean that up later. No big deal: It costs us a JMP instruction leap over the message to get to address GI. In the meantime, it's convenient for us, the readers, since as we read the code which prints the message, the message is right there for us to see.

Rasmussen shows exceptional modesty. Even though the user sees a lengthy opening message, the author's identity is not included.

Next comes a "friendly" input routine:

		;
		;GET INPUT
		;
		;
C129 A2 00 	GI	LDX #0		;SET INDEX=0
C12B 8E A8 02     SI	STX SIV		;STORE INDEX VALUE
		 ;
		 ;
		 ;GET NEXT CHARACTER	
		 ;
		 ;
C12E 20 E4 FF      GNC  JSR  GETIN	;GET A CHARACTER
C131 F0 FB	      BEQ GNC	;IF NONE, TRY AGAIN
C133 AE A8 02	      LDX SIV	;LOAD INDEX VALUE
C136 C9 0D 	      CMP #RK	;IS THIS RETURN
C138 F0 1C 	      BEQ FNE     ;KEY
C13A C9 14 	      CMP #DK	;IS THIS DEL.
C13C F0 03 	      BEQ PDR	;KEY
C13E 4C 4C C            JMP AI	;GOTO ACCEPT INPUT

We look for a character, and go back to try again if no character is there. If the character is RETURN (RK), we're finished and go to FNE. If it's DELETE (DK), we go the special delete routine. Otherwise, we go to "accept input." The Accept Input (AI) routine could have been inserted at this point to save the JMP instruction.

		;
		; PROCESS DEL REQUEST
		;
		;
C141 E0 00 	PDR 	CPX #0          ;INDEX VS ZERO
C143 F0 E6 	   	BEQ SI          ;IF SO, BYPASS
C145 CA                     DEX            ;DEL.
C146 20 D2 FF               JSR CHROUT     ;CHARACTER
C149 4C 2B Cl               JMP SI         ;GOTO STORE INDEX

X counts the input characters. If we see a DELETE character, we must decrease X provided it's greater than zero. We should print the delete using CHROUT ($FFD2) in order to erase the previous character on the screen.

		;
		;ACCEPT INPUT	
		;
		;
C14C 9D 40 03	AI  STA FNA,X	;STORE FILE NAME BYTE
C14F 20 D2 FF         JSR CHROUT	;PUT IT
C1S2 E8		    INX		;INCR POINTER
C153 4C 2B Cl	    JMP SI	;GOTO STORE INDEX
		;

An Alternative To JMP

An "ordinary" character is stored and printed. The X counter is increased and we return to get more input. It would be safe to use BNE instead of JMP here, since X will always be nonzero.

	      ;
	      ;FILE NAME END
               ;
               ;
C156 20 D2 FF  FNE   JSR CHROUT ; DOUBLE
C159 20 D2 FF	   JSR CHROUT ; SPACE
	      ;			
	      ;
	      ;ADD THE REST OF THE
	      ;FILE NAME FOR WRITE (,W)			
	      ;
	      ;
C15C A9 2C    	   LDA #C       ;LOAD AND
C15E 9D 40 03 	   STA FNA,X    ;STORE COMMA
C161 E8 		   INX          ;INCR POINTER
C162 A9 57 	   LDA #W       ;LOAD AND
C164 9D 40 03 	   STA FNA,X    ;STORE'W'
C167 E8 		   INX 	       ;INCR POINTER
C168 8E AB02 	   STX OFNL     ;STORE OUTPUT FILE NL
C16B 38 		   SEC 	       ;SUBTRACT 4
C16C 8A 		   TXA 	       ;FOR
C16D E9 04 	   SBC #4       ;INPUT FILE
C16F 8DAA02 	   STA IFNL     ;NAME LENGTH
C172 4C 8A Cl 	   JMP DIOR     ;GOTO DISK I/O ROUTN
	     ;

The program trusts the user to correctly type in a name such as DFILE,S or LPROG,P. It's dangerous to depend upon a user to input exactly the right thing: At the very least, I'd have the program check that the last two characters typed in were a comma followed by P or S.

Indirect Addressing

Now we reach the print subroutine previously used by the program.

	      ;
	      ;PRINT ROUTINE
	      ;
	      ;
C175 8E A9 02  PR	  STX SLV       ;STORE LENGTH
C178 85 22          STA LB        ;STORE LO BYTE
C17A 84 23	  STY HB        ;STORE HI BYTE
C17C A0 00	  LDY #0        ;SET INDEX = 0
	      ;
C17E Bl 22     PRL  LDA (LB),Y	;GET CHARACTER
C180 20 D2 FF 	 JSR CHROUT	;PUT IT
C183 C8 		 INY		;INCR INDEX
C184 CE A9 02	 DEC SLV          ;DECR LENGTH
C187 D0 F5	 BNE PRL          ;IF NOT 0, CARRY ON
C189 60            RTS		;RETURN

A quite straightforward use of indirect addressing for a print subroutine. I might have used CPY SLV instead of DEC SLV, but it works out the same.

C18A A9 00		DIOR = *

In the next session, the program opens the command channel and an input data file, and reads the selected file into memory. We'll continue with critical comments on this program.