[net.sources] 6809 Assembler

wje@sii.UUCP (Bill Ezell) (05/01/84)

b
echo x - README
cat >README <<'!E!O!F!'
This is an assembler for the 6502 micro. It produces an Intel hex format
load file. Compiling it should require only typing 'make'.
If you are running systemIII or later, edit the Makefile to define the
system III flag.
Included files are:

	6809.h
	6809.l
	6809.y
	README
	asm6809.c
	asm6809.1
	codegen.c
!E!O!F!
echo x - 6809.h
cat >6809.h <<'!E!O!F!'
/* 6809.h - define various items used by the assembler */
/*
   This material is copyright 1984 by Software Innovations, Inc.
   Permission to copy without fee all or part of this material
   is granted provided that the copies are not made or distributed
   for direct commercial advantage, this notice is included in
   any copies so made, and notice is given that copying of this
   material is by permission of Software Innovations, Inc.
   Modified copies of this material may not be made unless it is
   clearly stated in such copies that the modifications were not
   made by Software Innovations, Inc.
*/

#ifndef TRUE
#define TRUE 1
#endif

#ifndef FALSE
#define FALSE 0
#endif

typedef struct node {					/* symbol tbl entry */
			struct node *left;
			struct node *right;
			char *name;			/* symbol name */
			unsigned int addr;		/* load addr */
			int lineno;			/* line in src file */
		    } NODE, *NODEP;

/* define the various address modes */

#define M1byte		1
#define M2byte		2
#define M3byte		3
#define Mrel		4
#define Mlongrel	5
#define Mpost1		6
#define Mpost2		7
#define Mword		8

/* these mark extended opcodes 0x10 and 0x11, respectively */

#define Xop1		0x100
#define Xop2		0x200
!E!O!F!
echo x - 6809.l
cat >6809.l <<'!E!O!F!'
%{
/* 6809.l - lex for 6809 assembler */
/*
   This material is copyright 1984 by Software Innovations, Inc.
   Permission to copy without fee all or part of this material
   is granted provided that the copies are not made or distributed
   for direct commercial advantage, this notice is included in
   any copies so made, and notice is given that copying of this
   material is by permission of Software Innovations, Inc.
   Modified copies of this material may not be made unless it is
   clearly stated in such copies that the modifications were not
   made by Software Innovations, Inc.
*/
#include <ctype.h>

extern int line_count;
extern char err_file[];

char *getmem();

#undef getc
#define getc(x) get_a_c(x)	/* so lex will use our routine */
%}

%e 1200
%p 3000
%%

^\#.*$			{
				sscanf(yytext,"# %u %s",&line_count,err_file);
			}

\/\*.*\*\/		;

\.org			{ return(ORG); }
\.offset		{ return(OFFSET); }
\.text			{ return(TEXT); }
\.data			{ return(DATA); }
\.byte			{ return(BYTE); }
\.word			{ return(WORD); }
\.mask			{ return(MASK); }

'.'			{ yylval.ival = (int)*(yytext+1); return(LITCHAR); }

\"			{
			register int tmpc;
			register int number;
			register int ctr;
			register char *cptr;
			char string[256];

			 cptr = string;
			 *cptr++ = '"';

			 while( (tmpc = input()) != '"' )
			 {
			    if( cptr >= (string+255) )
			    {
			      fprintf(stderr,"String too long!\n");
			      yymore();
			      return;
			    }

			    if( !tmpc )			/* EOF */
			    {
			      yymore();
			      return;
			    }

			    if( tmpc == '\\' )
			    {
			      switch( (tmpc = input()) ) /* process \ */
			      {
			case '\n':			/* \<newline> ignored */
				 tmpc = '\0';
				 line_count++;
				 break;

			case 'b':
				 tmpc = '\b';		/* a backspace */
				 break;

			case '^':			/* ^char */
				 tmpc = input() & 037;
				 break;

			case 'f':
				 tmpc= '\f';		/* formfeed */
				 break;

			case 'n':			/* a newline */
				 tmpc= '\n';
				 break;

			case 'r':
				 tmpc = '\r';		/* return */
				 break;

			case 't':			/* a tab */
				 tmpc = '\t';
				 break;

			case '\\':			/* an esc'd \ */
				 break;

			case '0':			/* numeric escape */
			case '1':
			case '2':
			case '3':
			case '4':
			case '5':
			case '6':
			case '7':
			case '8':
			case '9':
				 number = tmpc - '0';
				 ctr = 1;

				 tmpc = input();

				 while( isdigit(tmpc) && (ctr < 3) )
				 {
				    number = number*10 + (tmpc - '0');
				    ++ctr;
				    tmpc = input();
				 }

				 unput(tmpc);

				 tmpc = number;
				 break;

			default:		/* just char as is */
				 break;
			      }

			      if( tmpc )
				 *cptr++ = (char)tmpc;
			    }
			    else
			      *cptr++ = (char)tmpc;
			   }

			   *cptr = '\0';

			   yylval.sptr = getmem(strlen(string)+1);
			   strcpy(yylval.sptr,string);
			   return(STRING);
			}

\;			{ return(SEMI); }

\<\<			{ return(LSH); }
\>\>			{ return(RSH); }

a			{ return(AREG); }
b			{ return(BREG); }
cc			{ return(CCREG); }
dp			{ return(DPREG); }
x			{ return(XREG); }
y			{ return(YREG); }
u			{ return(UREG); }
s			{ return(SREG); }
d			{ return(DREG); }
pc			{ return(PCREG); }

bcc			{ return(BCC);}
bcs			{ return(BCS);}
beq			{ return(BEQ);}
bge			{ return(BGE);}
bgt			{ return(BGT);}
bhi			{ return(BHI);}
bhs			{ return(BHS);}
ble			{ return(BLE);}
blo			{ return(BLO);}
bls			{ return(BLS);}
blt			{ return(BLT);}
bmi			{ return(BMI);}
bne			{ return(BNE);}
bpl			{ return(BPL);}
bra			{ return(BRA);}
brn			{ return(BRN);}
bsr			{ return(BSR);}
bvc			{ return(BVC);}
bvs			{ return(BVS);}
cwai			{ return(CWAI);}
exg			{ return(EXG);}
jsr			{ return(JSR);}
lbcc			{ return(LBCC);}
lbcs			{ return(LBCS);}
lbeq			{ return(LBEQ);}
lbge			{ return(LBGE);}
lbgt			{ return(LBGT);}
lbhi			{ return(LBHI);}
lbhs			{ return(LBHS);}
lble			{ return(LBLE);}
lblo			{ return(LBLO);}
lbls			{ return(LBLS);}
lblt			{ return(LBLT);}
lbmi			{ return(LBMI);}
lbne			{ return(LBNE);}
lbpl			{ return(LBPL);}
lbra			{ return(LBRA);}
lbrn			{ return(LBRN);}
lbsr			{ return(LBSR);}
lbvc			{ return(LBVC);}
lbvs			{ return(LBVS);}
leas			{ return(LEAS);}
leau			{ return(LEAU);}
leax			{ return(LEAX);}
leay			{ return(LEAY);}
pshs			{ return(PSHS);}
pshu			{ return(PSHU);}
puls			{ return(PULS);}
pulu			{ return(PULU);}
swi			{ return(SWI);}
tfr			{ return(TFR);}

abx			{ yylval.ival = 0x3A; return(INHERENT); }
asla			{ yylval.ival = 0x48; return(INHERENT); }
aslb			{ yylval.ival = 0x58; return(INHERENT); }
asra			{ yylval.ival = 0x47; return(INHERENT); }
asrb			{ yylval.ival = 0x57; return(INHERENT); }
clra			{ yylval.ival = 0x4F; return(INHERENT); }
clrb			{ yylval.ival = 0x5F; return(INHERENT); }
coma			{ yylval.ival = 0x43; return(INHERENT); }
comb			{ yylval.ival = 0x53; return(INHERENT); }
daa			{ yylval.ival = 0x19; return(INHERENT); }
deca			{ yylval.ival = 0x4A; return(INHERENT); }
decb			{ yylval.ival = 0x5A; return(INHERENT); }
inca			{ yylval.ival = 0x4C; return(INHERENT); }
incb			{ yylval.ival = 0x5C; return(INHERENT); }
lsla			{ yylval.ival = 0x48; return(INHERENT); }
lslb			{ yylval.ival = 0x58; return(INHERENT); }
lsra			{ yylval.ival = 0x44; return(INHERENT); }
lsrb			{ yylval.ival = 0x54; return(INHERENT); }
mul			{ yylval.ival = 0x3D; return(INHERENT); }
nega			{ yylval.ival = 0x40; return(INHERENT); }
negb			{ yylval.ival = 0x50; return(INHERENT); }
nop			{ yylval.ival = 0x12; return(INHERENT); }
rola			{ yylval.ival = 0x49; return(INHERENT); }
rolb			{ yylval.ival = 0x59; return(INHERENT); }
rora			{ yylval.ival = 0x46; return(INHERENT); }
rorb			{ yylval.ival = 0x56; return(INHERENT); }
rti			{ yylval.ival = 0x3B; return(INHERENT); }
rts			{ yylval.ival = 0x39; return(INHERENT); }
sex			{ yylval.ival = 0x1D; return(INHERENT); }
sync			{ yylval.ival = 0x13; return(INHERENT); }
tsta			{ yylval.ival = 0x4D; return(INHERENT); }
tstb			{ yylval.ival = 0x5D; return(INHERENT); }

adca			{ yylval.ival = 0x89; return(CLASS1); }
adcb			{ yylval.ival = 0xC9; return(CLASS1); }
adda			{ yylval.ival = 0x8B; return(CLASS1); }
addb			{ yylval.ival = 0xCB; return(CLASS1); }
addd			{ yylval.ival = 0xC3; return(CLASS1); }
anda			{ yylval.ival = 0x84; return(CLASS1); }
andb			{ yylval.ival = 0xC4; return(CLASS1); }
andcc			{ yylval.ival = 0x1C; return(CLASS1); }
bita			{ yylval.ival = 0x85; return(CLASS1); }
bitb			{ yylval.ival = 0xC5; return(CLASS1); }
cmpa			{ yylval.ival = 0x81; return(CLASS1); }
cmpb			{ yylval.ival = 0xC1; return(CLASS1); }
cmpd			{ yylval.ival = Xop1+0x83; return(CLASS1); }
cmps			{ yylval.ival = Xop2+0x8C; return(CLASS1); }
cmpu			{ yylval.ival = Xop2+0x83; return(CLASS1); }
cmpx			{ yylval.ival = 0x8C; return(CLASS1); }
cmpy			{ yylval.ival = Xop1+0x8C; return(CLASS1); }
eora			{ yylval.ival = 0x88; return(CLASS1); }
eorb			{ yylval.ival = 0xC8; return(CLASS1); }
lda			{ yylval.ival = 0x86; return(CLASS1); }
ldb			{ yylval.ival = 0xC6; return(CLASS1); }
ldd			{ yylval.ival = 0xCC; return(CLASS1); }
lds			{ yylval.ival = Xop1+0xCE; return(CLASS1); }
ldu			{ yylval.ival = 0xCE; return(CLASS1); }
ldx			{ yylval.ival = 0x8E; return(CLASS1); }
ldy			{ yylval.ival = Xop1+0x8E; return(CLASS1); }
ora			{ yylval.ival = 0x8A; return(CLASS1); }
orb			{ yylval.ival = 0xCA; return(CLASS1); }
orcc			{ yylval.ival = 0x1A; return(CLASS1); }
sbca			{ yylval.ival = 0x82; return(CLASS1); }
sbcb			{ yylval.ival = 0xC2; return(CLASS1); }
suba			{ yylval.ival = 0x80; return(CLASS1); }
subb			{ yylval.ival = 0xC0; return(CLASS1); }
subd			{ yylval.ival = 0x83; return(CLASS1); }

asl			{ yylval.ival = 0x08; return(CLASS2); }
asr			{ yylval.ival = 0x07; return(CLASS2); }
clr			{ yylval.ival = 0x0F; return(CLASS2); }
com			{ yylval.ival = 0x03; return(CLASS2); }
dec			{ yylval.ival = 0x0A; return(CLASS2); }
inc			{ yylval.ival = 0x0C; return(CLASS2); }
jmp			{ yylval.ival = 0x0E; return(CLASS2); }
lsl			{ yylval.ival = 0x08; return(CLASS2); }
lsr			{ yylval.ival = 0x04; return(CLASS2); }
neg			{ yylval.ival = 0x00; return(CLASS2); }
rol			{ yylval.ival = 0x09; return(CLASS2); }
ror			{ yylval.ival = 0x06; return(CLASS2); }
tst			{ yylval.ival = 0x0D; return(CLASS2); }

sta			{ yylval.ival = 0x97; return(CLASS3); }
stb			{ yylval.ival = 0xD7; return(CLASS3); }
std			{ yylval.ival = 0xDD; return(CLASS3); }
sts			{ yylval.ival = Xop1+0xDF; return(CLASS3); }
stu			{ yylval.ival = 0xDF; return(CLASS3); }
stx			{ yylval.ival = 0x9F; return(CLASS3); }
sty			{ yylval.ival = Xop1+0x9F; return(CLASS3); }

[0-9]+			{
			   yylval.ival = atoi(yytext);
			   return(NUMBER);
			}

0[0-7]+			{
			register int value;
			register char *cptr;

			   cptr = yytext;
			   value = 0;

			   while( *cptr )
			   {
			      value *= 8;
			      value += *cptr++ - '0';
			   }

			   yylval.ival = value;
			   return(NUMBER);
			}

0[xX][0-9A-Fa-f]+	{
			register int value;
			register char *cptr;

			   cptr = yytext + 2;
			   value = 0;

			   while( *cptr )
			   {
			      value *= 16;

			      if( *cptr <= '9' )
				 value += *cptr++ - '0';
			      else if( *cptr <= 'F' )
				 value += *cptr++ - 'A' + 10;
			      else
				 value += *cptr++ - 'a' + 10;
			   }

			   yylval.ival = value;
			   return(NUMBER);
			}

[a-zA-Z_][a-zA-Z0-9_]*	{
			 yylval.sptr = getmem(yyleng+1);
			 strcpy(yylval.sptr,yytext);
			 return(IDENTIFIER);
			}

[\t ]+			;

\n			{
				line_count++;
			}

.			{
				return(*yytext);
			}
%%
!E!O!F!
echo x - 6809.y
cat >6809.y <<'!E!O!F!'
/* Yacc for 6809 ASM */
/*
   This material is copyright 1984 by Software Innovations, Inc.
   Permission to copy without fee all or part of this material
   is granted provided that the copies are not made or distributed
   for direct commercial advantage, this notice is included in
   any copies so made, and notice is given that copying of this
   material is by permission of Software Innovations, Inc.
   Modified copies of this material may not be made unless it is
   clearly stated in such copies that the modifications were not
   made by Software Innovations, Inc.
*/
%{
#include <stdio.h>
#include "6809.h"

extern int pass;
extern unsigned int pc;
extern unsigned int offset;
extern unsigned int mask;
extern NODEP root;

unsigned int pc = 0;				/* current pc */
unsigned int tpc = 0;				/* text pc */
unsigned int dpc = 0;				/* data pc */

static int dmode = FALSE;		/* TRUE => data, FALSE => text */
static int ind_addr = 0;		/* tmp for extended indirect addr */

NODEP findsym();
%}

%start	program

%union {
	int ival;
	char *sptr;
       }

/* lexical constructs that every assembler has */

%token <sptr> IDENTIFIER
%token <ival> NUMBER
%token <ival> LITCHAR
%token <sptr> STRING

%token SEMI
%token LSH
%token RSH

/* lexical constructs specific to the assembler at hand */

%token AREG
%token BREG
%token CCREG
%token DPREG
%token XREG
%token YREG
%token UREG
%token SREG
%token DREG
%token PCREG

/* stmt types that everyone has */

%token	ORG OFFSET TEXT DATA BYTE WORD MASK

/* stmt types for this assembler */

%token <ival> CLASS1 CLASS2 CLASS3 INHERENT

%token BCC BCS BEQ BGE BGT BHI BHS BLE BLO BLS BLT BMI BNE
%token BPL BRA BRN BSR BVC BVS CWAI EXG JSR LBCC LBCS LBEQ LBGE
%token LBGT LBHI LBHS LBLE LBLO LBLS LBLT LBMI LBNE LBPL LBRA LBRN LBSR
%token LBVC LBVS LEAS LEAU LEAX LEAY PSHS PSHU PULS PULU SWI TFR

/* precedence for operators */

%left	'|'
%left	'^'
%left	'&'
%left	LSH RSH
%left	'+' '-'
%left	'*' '/' '%'
%left	'!'
%left	UMINUS

/* declarations for non-terminals */

%type <ival> expr
%type <ival> reg_id
%type <ival> reg_set
%type <ival> reg_bit
%type <ival> ix_reg
%type <ival> mode_rel
%type <ival> mode_ix
%type <ival> ix_types
%type <ival> branch
%type <ival> long_branch

%%
program		:	statements
		;

statements	:	statements statement
		|	statement
		;

statement	:	ORG expr SEMI
			{
			   pc = $2;
			   list_word(pc);
			}
		|	OFFSET expr SEMI
			{
			   offset = (unsigned)$2;
			   list_word($2);
			}
		|	TEXT SEMI
			{
			   if( dmode )
			   {
			      dmode = FALSE;
			      dpc = pc;
			      pc = tpc;
			   }
			   list_word(pc);
			}
		|	DATA SEMI
			{
			   if( !dmode )
			   {
			      dmode = TRUE;
			      tpc = pc;
			      pc = dpc;
			   }
			   list_word(pc);
			}
		|	MASK expr SEMI
			{
			   mask = (unsigned)$2;
			   list_word($2);
			}
		|	BYTE blist SEMI
		|	WORD wlist SEMI
		|	IDENTIFIER ':'
			{
			register NODEP ptr;

			   if( pass == 1 )
			   {
			      if( !addsym(&root,$1,pc,line_count) )
			      {
				 fprintf(stderr,
				    "Multiply defined symbol %s at line %u\n",
				    $1,line_count);
				 free($1);
				 YYERROR;
			      }
			   }
			   else
			   {
			      ptr = findsym(root,$1);

			      if( ptr->addr != pc )
			      {
				 fprintf(stderr,
	       "Symbol %s, line %u, value changed between pass 1 and pass 2\n",
				    ptr->name,line_count);
	    fprintf(stderr,"Pass 1 value %u, pass 2 value %u\n",ptr->addr,pc);
				 free($1);
				 YYERROR;
			      }
			      free($1);
			   }
			} statement
		|	specifics
		;

blist		:	expr
			{
			   if( ($1 > 255) || ($1 < -128) )
			   {
			      yyerror("Must be byte value");
			      YYERROR;
			   }
			   emit($1,M1byte);
			}
		|	STRING
			{
			register char *cptr;

			   cptr = $1+1;
			   while( *cptr )
			      emit(*cptr++,M1byte);
			   free($1);
			}
		|	blist ',' expr
			{
			   if( ($3 > 255) || ($3 < -128) )
			   {
			      yyerror("Must be byte value");
			      YYERROR;
			   }
			   emit($3,M1byte);
			}
		|	blist ',' STRING
			{
			register char *cptr;

			   cptr = $3+1;
			   while( *cptr )
			      emit(*cptr++,M1byte);
			   free($3);
			}
		;

wlist		:	expr
			{
			   emit($1,Mword);
			}
		|	wlist ',' expr
			{
			   emit($3,Mword);
			}
		;

specifics	:	INHERENT SEMI
			{ emit($1,M1byte); }
		|	relative
		|	long_relative
		|	class1
		|	class2
		|	class3
		|	misc
		;

relative	:	branch mode_rel SEMI
			{ emit($1,Mrel,$2); }
		;

long_relative	:	long_branch expr SEMI
			{ emit($1,Mlongrel,$2); }
		|	LBRA expr SEMI
			{ emit(0x16,M3byte,$2); }
		|	LBSR expr SEMI
			{ emit(0x17,M3byte,$2-pc-3); }
		;

class1		:	CLASS1 '#' expr SEMI
			{
			   switch( $1 )		/* these have 16 bit args */
			   {
			   case 0xC3:			/* addd */
			   case 0x83:			/* subd */
			   case Xop1+0x83:		/* cmpd */
			   case Xop2+0x8C:		/* cmps */
			   case Xop2+0x83:		/* cmpu */
			   case 0x8c:			/* cmpx */
			   case Xop1+0x8C:		/* cmpy */
			   case 0xCC:			/* ldd */
			   case Xop1+0xCE:		/* lds */
			   case 0xCE:			/* ldu */
			   case 0x8E:			/* ldx */
			   case Xop1+0x8E:		/* ldy */
			      emit($1,M3byte,$3);
			      break;
			   default:			/* otherwise, 8 bit */
			      if( (unsigned)$3 > 0xFF )
			      {
				 yyerror("Immediate value too big");
				 YYERROR;
			      }
			      emit($1,M2byte,$3);
			   }
			}
		|	CLASS1 expr SEMI
			{
			   if( (unsigned)$2 > 0xFF )
			   {
			      yyerror("Direct address too big");
			      YYERROR;
			   }
			      emit($1+0x10,M2byte,$2);
			}
		|	CLASS1 '$' expr SEMI
			{
			   emit($1+0x30,M3byte,$3);
			}
		|	CLASS1 mode_ix SEMI
			{ do_ix($1+0x20,$2); }
		;

class2		:	CLASS2 expr SEMI
			{
			   if( (unsigned)$2 > 0xFF )
			   {
			      yyerror("Direct address too big");
			      YYERROR;
			   }
			   emit($1,M2byte,$2);
			}
		|	CLASS2 '$' expr SEMI
			{
			   emit($1+0x70,M3byte,$3);
			}
		|	CLASS2 mode_ix SEMI
			{ do_ix($1+0x60,$2); }
		;

class3		:	CLASS3 expr SEMI
			{
			   if( (unsigned)$2 > 0xFF )
			   {
			      yyerror("Direct address too big");
			      YYERROR;
			   }
			   emit($1,M2byte,$2);
			}
		|	CLASS3 '$' expr SEMI
			{
			   emit($1+0x20,M3byte,$3);
			}
		|	CLASS3 mode_ix SEMI
			{ do_ix($1+0x10,$2); }
		;

branch		:	BCC
			{ $$ = 0x24; }
		|	BCS
			{ $$ = 0x25; }
		|	BEQ
			{ $$ = 0x27; }
		|	BGE
			{ $$ = 0x2C; }
		|	BGT
			{ $$ = 0x2E; }
		|	BHI
			{ $$ = 0x22; }
		|	BHS
			{ $$ = 0x24; }
		|	BLE
			{ $$ = 0x2F; }
		|	BLO
			{ $$ = 0x25; }
		|	BLS
			{ $$ = 0x23; }
		|	BLT
			{ $$ = 0x2D; }
		|	BMI
			{ $$ = 0x2B; }
		|	BNE
			{ $$ = 0x26; }
		|	BPL
			{ $$ = 0x2A; }
		|	BRA
			{ $$ = 0x20; }
		|	BRN
			{ $$ = 0x21; }
		|	BSR
			{ $$ = 0x8D; }
		|	BVC
			{ $$ = 0x28; }
		|	BVS
			{ $$ = 0x29; }
		;

long_branch	:	LBCC
			{ $$ = 0x24; }
		|	LBCS
			{ $$ = 0x25; }
		|	LBEQ
			{ $$ = 0x27; }
		|	LBGE
			{ $$ = 0x2C; }
		|	LBGT
			{ $$ = 0x2E; }
		|	LBHI
			{ $$ = 0x22; }
		|	LBHS
			{ $$ = 0x24; }
		|	LBLE
			{ $$ = 0x2F; }
		|	LBLO
			{ $$ = 0x25; }
		|	LBLS
			{ $$ = 0x23; }
		|	LBLT
			{ $$ = 0x2D; }
		|	LBMI
			{ $$ = 0x2B; }
		|	LBNE
			{ $$ = 0x26; }
		|	LBPL
			{ $$ = 0x2A; }
		|	LBRN
			{ $$ = 0x21; }
		|	LBVC
			{ $$ = 0x28; }
		|	LBVS
			{ $$ = 0x29; }
		;

misc		:	SWI SEMI
			{ emit(0x3F,M1byte); }
		|	SWI expr SEMI
			{
			   if( ($2 != 2) && ($2 != 3) )
			   {
			      yyerror("Must be swi 1 or swi 2");
			      YYERROR;
			   }
			   if( $2 == 2 )
			      emit(0x10,M2byte,0x3F);
			   else
			      emit(0x11,M2byte,0x3F);
			}
		|	EXG reg_id ',' reg_id SEMI
			{
			   if( !ck_regs($2,$4) )
			   {
			      yyerror("Register sizes are different");
			      YYERROR;
			   }
			   emit(0x1E,M2byte,($2<<4)+$4);
			}
		|	TFR reg_id ',' reg_id SEMI
			{
			   if( !ck_regs($2,$4) )
			   {
			      yyerror("Register sizes are different");
			      YYERROR;
			   }
			   emit(0x1F,M2byte,($2<<4)+$4);
			}
		|	CWAI SEMI
			{ emit(0x3C,M1byte); }
		|	PSHS reg_set SEMI
			{ emit(0x34,M2byte,$2); }
		|	PSHU reg_set SEMI
			{ emit(0x36,M2byte,$2); }
		|	PULS reg_set SEMI
			{ emit(0x35,M2byte,$2); }
		|	PULU reg_set SEMI
			{ emit(0x37,M2byte,$2); }
		|	LEAS mode_ix SEMI
			{ do_ix(0x32,$2); }
		|	LEAU mode_ix SEMI
			{ do_ix(0x33,$2); }
		|	LEAX mode_ix SEMI
			{ do_ix(0x30,$2); }
		|	LEAY mode_ix SEMI
			{ do_ix(0x31,$2); }
		|	JSR expr SEMI
			{
			   if( (unsigned)$2 > 0xFF )
			   {
			      yyerror("Direct address too big");
			      YYERROR;
			   }
			   emit(0x9D,M2byte,$2);
			}
		|	JSR '$' expr SEMI
			{
			   emit(0xBD,M3byte,$3);
			}
		;

reg_id		:	DREG
			{ $$ = 0x0; }
		|	XREG
			{ $$ = 0x1; }
		|	YREG
			{ $$ = 0x2; }
		|	UREG
			{ $$ = 0x3; }
		|	SREG
			{ $$ = 0x4; }
		|	PCREG
			{ $$ = 0x5; }
		|	AREG
			{ $$ = 0x8; }
		|	BREG
			{ $$ = 0x9; }
		|	CCREG
			{ $$ = 0xA; }
		|	DPREG
			{ $$ = 0xB; }
		;

reg_set		:	reg_bit
		|	reg_set ',' reg_bit
			{ $$ = $1 | $3; }
		;

reg_bit		:	CCREG
			{ $$ = 1; }
		|	AREG
			{ $$ = 2; }
		|	BREG
			{ $$ = 4; }
		|	DPREG
			{ $$ = 8; }
		|	XREG
			{ $$ = 16; }
		|	YREG
			{ $$ = 32; }
		|	SREG
			{ $$ = 64; }
		|	PCREG
			{ $$ = 128; }
		;

ix_reg		:	XREG
			{ $$ = 0x00; }
		|	YREG
			{ $$ = 0x20; }
		|	UREG
			{ $$ = 0x40; }
		|	SREG
			{ $$ = 0x60; }
		;

mode_rel	:	expr
			{
			int tmp;

			   if( pass == 1 )
			      $$ = 0;
			   else
			   {
			      tmp = (int)((unsigned)($1) - pc);
			      if( (tmp > 129) || (tmp < -126) )
			      {
				 yyerror("Relative address out of range");
				 YYERROR;
			      }
			   }
			}
		;

mode_ix		:	ix_types
		|	'[' ix_types ']'
			{
			   switch( $2 & 0x9F )
			   {
			   case 0x80:
			   case 0x82:
			      yyerror("Indirection not allowed for +, -");
			      YYERROR;
			      break;
			   }

			   if( !($2 & 0x80) )	/* convert 5 bit to 8 bit */
			   {
			      ind_addr = $2 & 0x1F;
			      $$ = ($2 & 0x60) + 0x88;
			   }
			   else
			      $$ = $2 | 0x10;		/* set indirect bit */
			}
		|	'[' expr ']'
			{
			   ind_addr = $2;
			   $$ = 0x9F;
			}
		;

ix_types	:	expr ',' ix_reg
			{
			   if( $1 == 0 )
			      $$ = 0x84 + $3;
			   else if( ($1 <= 15) && ($1 >= -16) )
			      $$ = $3 + ($1 & 0x1F);	/* 5 bit */
			   else if( ($1 <= 127) && ($1 >= -128) )
			   {
			      $$ = 0x88 + $3;		/* 8 bit */
			      ind_addr = $1;
			   }
			   else
			   {
			      $$ = 0x89 + $3;		/* 16 bit */
			      ind_addr = $1;
			   }
			}
		|	',' ix_reg				/* 0 offset */
			{ $$ = 0x84 + $2; }
		|	AREG ',' ix_reg
			{ $$ = 0x86 + $3; }
		|	BREG ',' ix_reg
			{ $$ = 0x85 + $3; }
		|	DREG ',' ix_reg
			{ $$ = 0x8C + $3; }
		|	',' ix_reg '+'
			{ $$ = 0x80 + $2; }
		|	',' ix_reg '+' '+'
			{ $$ = 0x81 + $2; }
		|	',' '-' ix_reg
			{ $$ = 0x82 + $3; }
		|	',' '-' '-' ix_reg
			{ $$ = 0x83 + $4 ; }
		|	expr ',' PCREG
			{
			   ind_addr = $1;
			   if( ($1 <= 127) && ($1 >= -128) )
			      $$ = 0x8D;
			   else
			      $$ = 0x8E;
			}
		;

expr		:	'(' expr ')'
			{
			   $$ = $2;
			}
		|	'-' expr %prec UMINUS
			{
			   $$ = - $2;
			}
		|	'~' expr %prec UMINUS
			{
			   $$ = ~$2;
			}
		|	'!' expr %prec UMINUS
			{
			   $$ = !$2;
			}
		|	expr '+' expr
			{
			   $$ = $1 + $3;
			}
		|	expr '-' expr
			{
			   $$ = $1 - $3;
			}
		|	expr '%' expr
			{
			   $$ = $1 % $3;
			}
		|	expr '*' expr
			{
			   $$ = $1 * $3;
			}
		|	expr '/' expr
			{
			   $$ = $1 / $3;
			}
		|	expr LSH expr
			{
			   $$ = $1 << $3;
			}
		|	expr RSH expr
			{
			   $$ = $1 >> $3;
			}
		|	expr '&' expr
			{
			   $$ = $1 & $3;
			}
		|	expr '|' expr
			{
			   $$ = $1 | $3;
			}
		|	expr '^' expr
			{
			   $$ = $1 ^ $3;
			}
		|	'.'
			{
			   $$ = pc;
			}
		|	LITCHAR
		|	NUMBER
		|	IDENTIFIER
			{
			register NODEP ptr;

			   if( pass == 2 )
			   {
			      ptr = findsym(root,$1);

			      if( !ptr )
			      {
				 fprintf(stderr,
				    "Undefined symbol %s used at line %u\n",
				    $1,line_count);
				 free($1);
				 YYERROR;
			      }
			      free($1);

			      $$ = ptr->addr;
			   }
			   else
			   {
			      free($1);
			      $$ = 0;
			   }
			}
		;

%%	/* start of programs */

#include "lex.yy.c"

yyerror(s)
char *s;
{
printf("%s in line %u, file %s: %s\n",s,line_count,err_file,yytext);
}

yywrap()				/* tell lex to clean up */
{
	return(1);
}

int
do_ix(op,postbyte)			/* output an indexed op */

register int op;
register int postbyte;
{
   if( !(postbyte & 0x80) )		/* special case */
      emit(op,M2byte,postbyte);
   else switch( postbyte & 0x1F )
   {
   case 0x4:
   case 0x6:
   case 0x5:
   case 0xB:
   case 0x0:
   case 0x1:
   case 0x2:
   case 0x3:					/* only postbyte is added */
      emit(op,M2byte,postbyte);
      break;
   case 0x8:
   case 0x9:
      emit(op,Mpost1,postbyte,ind_addr);	/* post plus one byte */
      break;
   default:
      emit(op,Mpost2,postbyte,ind_addr);	/* post plus two bytes */
   }
}

int
ck_regs(a,b)					/* make sure reg pairs match */

register int a;
register int b;
{
   if( (a > 5) && (b > 5) )			/* a,b are 8bit regs */
      return(TRUE);
   if( (a <= 5) && (b <= 5) )			/* a,b are 16bit regs */
      return(TRUE);
   return(FALSE);
}
!E!O!F!
echo x - asm6809.1
cat >asm6809.1 <<'!E!O!F!'
.TH asm6809 1
.SH NAME
asm6809 \- assembler for the Motorola 6809
.SH SYNOPSIS
.B asm6809
[ -elnsv ] file.6809 ...
.SH DESCRIPTION
.I Asm6809
is the UNIX 6809 assembler. It accepts assembler source files and places the
results in Intel hex format in a file named
.I file.x.
.PP
The following options are recognized by
.I asm6809.
.TP 10
.B -e
Invoke the editor when an error occurs. The environment variable EDITOR is
used if it exists, otherwise, /usr/bin/ed is used.
.TP 10
.B -l
Produce an assembly listing on stdout.
.TP 10
.B -n
Do not run the C preprocessor on the input files.
.TP 10
.B -s
Print out the symbol table for each file assembled.
.TP 10
.B -v
Verbose mode. Give a running commentary on what is happening during
assembly.
.PP
The assembler syntax uses the standard Motorola mnemonics for instruction
names, but values are specified in a different manner.
.PP
All addresses are given as just the label name or the number; if there is
a leading '$', 16 bit addresses are used.
Otherwise, a direct address is assumed.
Note that if an instruction does not need to distinguish between direct
and extended addresses, the '$' is not used; e.g. bra, blt.
Constants are indicated by a leading '#'.
The C convention for specifying number base, i.e. 12 is decimal, 012 is
octal, 0x12 is hex, is used.
Statements must be terminated by a ';', and there may be multiple
statements per line.
.PP
Anywhere a numeric value may be used, an expression may also be used.
The allowed operators are +, -, *, /, <<, >>, |, &, ^, %, and unary -,
unary ~, and unary !.
These operators perform the same functions as in C, and have the same
precedence; see Kernigan & Ritchie page 215.
Operands may be numbers, labels, literal characters, represented by
a character surrounded by single quotes, and the special value dot,
represented by the period character, which is the value of the pc at
the beginning of the statement.
.PP
Labels are a string whose leading character is one of
A-Za-z or underscore, followed by any number of A-Za-z0-9 or underscore.
A label is defined by the label terminated with ':' appearing at the
beginning of a statement.
.PP
Several assembler directives are provided:
.TP 10
.B .mask expr;
The address fields of the output records are anded with this value, which
by default is 0xFFFF.
.br
.TP 10
.B .offset expr;
This value is added to the address fields of the output records.
The default value is 0.
.TP 10
.B .org expr;
Set the current pc to the value given.
.br
.TP 10
.B .text;
Select the text pc as current.
.br
.TP 10
.B .data;
Select the data pc as current.
.br
.TP 10
.B .byte expr[,expr,..];
Generate one or more bytes with the values given.
Expr may also be a string of characters surrounded by double quotes.
In this case, each character is inserted in order in the byte sequence;
no terminator is inserted.
A backslash '\\' may be followed by several special characters:
.RS 5
<nl>	ignore the newline; string continues on next line.
.br
b	backspace character
.br
f	formfeed character
.br
n	newline character
.br
r	carriage return character
.br
t	tab character
.br
^	next character is interpreted as a control char
.br
0-9	interptret up to 3 DECIMAL digits as the character code
.br
.RE
The backslash character itself may be represented by two backslashes.
.br
.TP 10
.B .word expr[,expr,..];
Generate one or more words with the values given.
.SH DIAGNOSTICS
.I
Asm6809
responds with various error messages, which are self-explanatory.
If the -e option was given, an editor is invoked with the offending
file as an argument, and if the editor is vi, with the offending line
number.
.SH FILES
/tmp/AS* - temporary for cpp output
.br
/lib/cpp
.br
/usr/bin/ed
.SH BUGS
The assembler uses cpp as its 'macro' facility; unfortunately, listings
are produced from the source after cpp has been run.
Therefore, any defines will be expanded in the listings.
There is no way to produce object modules, only executables, but what
do you want for free?
!E!O!F!
echo x - asm6809.c
cat >asm6809.c <<'!E!O!F!'
/*
   This material is copyright 1984 by Software Innovations, Inc.
   Permission to copy without fee all or part of this material
   is granted provided that the copies are not made or distributed
   for direct commercial advantage, this notice is included in
   any copies so made, and notice is given that copying of this
   material is by permission of Software Innovations, Inc.
   Modified copies of this material may not be made unless it is
   clearly stated in such copies that the modifications were not
   made by Software Innovations, Inc.
*/
/*
   Name:		6809asm
   Version:		1.0
   Function:		6809 assembler for Unix
   Author:		William J. Ezell
			Software Innovations, Inc.
			(603) 883-9300
			decvax!sii!wje
   Initial release:	1-May-84

   MODIFICATION HISTORY

   None
*/

#include <stdio.h>
#include <signal.h>
#include "6809.h"

char loadfile[129];
FILE *loadfid;

char linebuf[256];			/* buffer for get_a_c() */
char *lineptr = (char *)0;
int startofline = TRUE;

NODEP root;				/* root of symbol table */
int pass = 1;				/* which pass we are on */
unsigned int offset = 0;		/* output address offset */
unsigned int mask = 0xFFFF;		/* default output record mask */

long int curhdr;

int verbose = FALSE;
int dumpsym = FALSE;
int listing = FALSE;
int line_count;
char err_file[129];

extern int yyprevious;			/* for resetting lex */
extern int yytchar;
extern char *yysptr;
extern char yysbuf[];

extern unsigned int pc;				/* parser's pc */
extern unsigned int tpc;			/* text segment pc */
extern unsigned int dpc;			/* data segment pc */

char *getmem();

#ifdef S3
char *strrchr();
#else
char *rindex();
#endif

int quit();

static char cppfile[] = "/tmp/ASXXXXXX";

main(argc,argv)
int argc;
char **argv;
{
register char *str;
register int do_cpp;
register int do_edit;

register char *progname;

int status;

    do_edit = FALSE;
    do_cpp = TRUE;

    signal(SIGHUP,quit);
    signal(SIGINT,quit);
    signal(SIGQUIT,quit);

    argv++;

    if( argc == 1 )
    {
      printf("Usage: asm6809 [-elnsv] src.6809\n");
      exit(1);
   }

    mktemp(cppfile);		/* make a temp for the cpp file if needed */

    while( *argv )
    {
      if( **argv == '-' )		/* option switch */
      {
	 (*argv)++;

	 while( **argv )
	 {
	    switch( *(*argv)++ )
	    {
	       case 'e':			/* edit file on error */
	       do_edit = TRUE;
	       break;

	       case 'l':			/* make a listing */
	       listing = TRUE;
	       break;

	       case 'n':			/* don't run cpp */
	       do_cpp = FALSE;
	       break;

	       case 's':			/* print out the symtab */
	       dumpsym = TRUE;
	       break;

	       case 'v':
	       verbose = TRUE;			/* tell what's going on */
	       break;

	       default:
	       fprintf(stderr,"Unknown switch: '%s' ignored.\n",*argv);
	       break;
	    }
	 }
      }
      else for(;;)			/* loop on processing file */
      {
	 progname = *argv;

#ifdef S3
	 if( !(str = strrchr(progname,'.')) || strcmp(str+1,"6809") )
#else
	 if( !(str = rindex(progname,'.')) || strcmp(str+1,"6809") )
#endif
	 {
	    fprintf(stderr,"File %s must end with '.6809'\n",*argv);
	    goto errexit;
	 }

	 if( freopen(*argv,"r",stdin) == NULL )
	 {
	    fprintf(stderr,"Cannot open '%s'\n",*argv);
	    goto errexit;
	 }

#ifdef S3
	 if( (str = strrchr(progname,'/')) )	/* strip leading pathname */
#else
	 if( (str = rindex(progname,'/')) )	/* strip leading pathname */
#endif
	    progname = str + 1;

	 strcpy(loadfile,progname);		/* create output file */

#ifdef S3
	 if( (str = strrchr(loadfile,'.')) )
#else
	 if( (str = rindex(loadfile,'.')) )
#endif
	    *str = '\0';

	 strcat(loadfile,".x");
	 unlink(loadfile);			/* get rid of any leftovers */

	 if( !(loadfid = fopen(loadfile,"w")) )
	 {
	    fprintf(stderr,"Cannot create output file '%s'\n",loadfile);
	    goto errexit;
	 }

	 line_count = 1;		/* set up error file code */
	 err_file[0] = '"';
	 strcpy(&err_file[1],*argv);
	 strcat(err_file,"\"");

	 printf("\n%s:\n",progname);

	 while( do_cpp )		/* run c preprocessor on the file */
	 {
	    if( verbose )
	       printf("Preprocessor begins\n");

	    if( fork() )
	    {
	       wait(&status);

	       if( status )			/* an error occurred */
	       {
		  if( !do_edit || (doedit() == FALSE) )
		     goto errexit;	/* they don't want to try again */
		  else
		  {
		     unlink(cppfile);
		     continue;		/* try again */
		  }
	       }
	    }
	    else
	    {
	       execl("/lib/cpp","cpp",*argv,cppfile,0);

	       fprintf(stderr,"Cannot find cpp\n");
	       exit(1);
	    }
	 
	    if( freopen(cppfile,"r",stdin) == NULL )
	    {
	       fprintf(stderr,"Cannot open cpp output file\n");
	       goto errexit;
	    }
	    break;
	 }

	 line_count = 1;		/* set up error file code again */
	 err_file[0] = '"';
	 strcpy(&err_file[1],*argv);
	 strcat(err_file,"\"");

	 if( verbose )
	    printf("Parse tree generation begins\n Pass1\n");

	 curhdr = 0L;			/* for load module creation */

	 pc = tpc = dpc = 0;
	 pass = 1;
	 lineptr = (char *)0;		/* reset get_a_c() */

	 if( !(status = yyparse()) )
	 {
	    if( verbose )
	       printf(" Pass2\n");

	    pc = tpc = dpc = 0;
	    pass = 2;			/* do second pass */
	    fseek(stdin,0L,0);
	    lineptr = (char *)0;	/* reset get_a_c() */

	    init_out();			/* get ready for code generation */
	    status = yyparse();
	    term_out();			/* close output file */

	    if( dumpsym && !status )	/* print out the symtab */
	    {
	       printf("\n\tSymbol Table for file '%s'\nLine\tValue\tName\n\n",
		  progname);
	       printsym(root);
	    }
	 }

	 killtree(root);		/* clean up symbol table */
	 root = (NODEP)0;

	 if( status )
	 {
	    if( do_edit )		/* do we edit the file? */
	    {
	       yyprevious = '\n';		/* reset lex */
	       yytchar = 0;
	       yysptr = yysbuf;

	       fclose(loadfid);
	       unlink(loadfile);
	       unlink(cppfile);

	       if( !doedit() )
		  goto errexit;

	       continue;			/* try again */
	    }
	    else
	       goto errexit;
	 }
	 else
	    break;				/* done with this file */
      }

      fclose(loadfid);
      argv++;
   }

   unlink(cppfile);
   exit(0);

errexit:					/* here when a problem */
   unlink(loadfile);
   unlink(cppfile);
   exit(1);
}

NODEP
mknode(name,addr,line)		/* make a new node for the symbol table */

register char *name;		/* name of symbol */
unsigned int addr;		/* the value it has */
int line;			/* where it was defined */
{
register NODEP np;

   np = (NODEP)getmem(sizeof(NODE));

   np->name = name;
   np->addr = addr;
   np->lineno = line;

   np->left = (NODEP)0;
   np->right = (NODEP)0;

   return(np);
}

int
killtree(node)				/* free up the parse tree */

register NODEP node;
{
register NODEP tmp;

   if( node )
   {
      if( node->left )
	 killtree(node->left);

      if( node->right )
	 killtree(node->right);

      free(node->name);
      free(node);
   }
}

NODEP
findsym(ptr,name)			/* search for a node */

register NODEP ptr;
register char *name;
{
register int val;

   while( ptr )
   {
      if( !(val = strcmp(name,ptr->name)) )	/* found it */
	 return(ptr);

      if( val < 0 )
	 ptr = ptr->left;
      else
	 ptr = ptr->right;
   }

   return((NODEP)0);			/* not here */
}

int
addsym(root,name,addr,line)		/* add a node */

NODEP *root;
register char *name;
unsigned int addr;
int line;
{
register int val;
register NODEP ptr;
register NODEP new;

   new = mknode(name,addr,line);

   if( !(ptr = *root) )
   {
      *root = new;				/* first node in table */
      return(TRUE);
   }

   for(;;)
   {
      if( !(val = strcmp(name,ptr->name)) )	/* already here */
      {
	 killtree(new);
	 return(FALSE);
      }

      if( val < 0 )
      {
	 if( ptr->left )
	    ptr = ptr->left;
	 else
	 {
	    ptr->left = new;
	    return(TRUE);
	 }
      }
      else
      {
	 if( ptr->right )
	    ptr = ptr->right;
	 else
	 {
	    ptr->right = new;
	    return(TRUE);
	 }
      }
   }
}

int doedit()				/* edit a file, if wanted */
{
char answer[128];

   freopen("/dev/tty","r",stdin);	/* make sure we talk to the right one */

   printf("\nEdit file? ");
   gets(answer);

   if( answer[0] != 'y' )
      return(FALSE);			/* no, they don't */

   if( getenv("EDITOR") )		/* see what editor to use */
      strcpy(answer,getenv("EDITOR"));
   else
      strcpy(answer,"/usr/bin/ed");

   if( strcmp(&answer[strlen(answer)-2],"vi") == 0)	/* using vi */
      sprintf(&answer[strlen(answer)]," +%u",line_count);

   err_file[0] = ' ';
   strcat(answer,err_file);		/* the file, without the "'s */
   answer[strlen(answer)-1] = '\0';

   system(answer);
   return(TRUE);
}

int
quit()
{
   unlink(cppfile);				/* clean up before exiting */

   if( loadfile )
   {
      printf("\n%s removed\n",loadfile);
      unlink(loadfile);
   }

   exit(0);
}

char *
getmem(size)

unsigned int size;
{
register char *ptr;

char *malloc();

   if( !(ptr = malloc(size)) )
   {
      printf("Out of memory!\n");
      quit();
   }

   return(ptr);
}

int
printsym(node)				/* print out the symbol table */

register NODEP node;
{
   if( node )
   {
      printsym(node->left);

      printf("%d\t0x%04x\t%s\n",node->lineno,node->addr,node->name);

      printsym(node->right);
   }
}

int
get_a_c(fd)				/* char input routine */

FILE *fd;
{
int ch;

   if( !lineptr )
   {
      if( fgets(linebuf,sizeof(linebuf),fd) == NULL )
	 return(EOF);
      lineptr = linebuf;
      if( (*lineptr == '\n') && listing && (pass == 2) )	/* empty line */
	 putchar('\n');
      startofline = TRUE;
   }

   if( (ch = *lineptr++) == '\n' )
      lineptr = (char *)0;
   return(ch);
}
!E!O!F!
echo x - codegen.c
cat >codegen.c <<'!E!O!F!'
/* codegen - output the code */
/*
   This material is copyright 1984 by Software Innovations, Inc.
   Permission to copy without fee all or part of this material
   is granted provided that the copies are not made or distributed
   for direct commercial advantage, this notice is included in
   any copies so made, and notice is given that copying of this
   material is by permission of Software Innovations, Inc.
   Modified copies of this material may not be made unless it is
   clearly stated in such copies that the modifications were not
   made by Software Innovations, Inc.
*/

#include <stdio.h>
#include "6809.h"

#define RMAX 16				/* max bytes per output record */

extern int listing;
extern int startofline;
extern int line_count;
extern char linebuf[];

extern unsigned int pc;
extern unsigned int mask;
extern unsigned int offset;
extern int pass;

extern FILE *loadfid;

static unsigned int lastpc = (unsigned)(-1);
static unsigned int ldaddr = 0;
static int ccount = 0;
static char record[256];

emit(op,mode,addr,addr2)		/* generate proper code, update pc */

int op;
int mode;
int addr;
int addr2;
{
   switch( mode )			/* see what to do */
   {
   case M1byte:
      list_m1(pc,op);
      output(op);
      ++pc;
      break;

   case M2byte:
      if( op & (Xop1|Xop2) )			/* extended op code */
      {
	 list_m3(pc,(op&Xop1)?0x10:0x11,((op&0xFF)<<8)+addr);
	 output((op&Xop1)?0x10:0x11);
	 output(op);
	 output(addr);
	 pc += 3;
      }
      else
      {
	 list_m2(pc,op,addr);
	 output(op);
	 output(addr);
	 pc += 2;
      }
      break;

   case M3byte:
      if( op & (Xop1|Xop2) )			/* extended op code */
      {
	 list_m4(pc,(op&Xop1)?0x10:0x11,op&0xFF,addr);
	 output((op&Xop1)?0x10:0x11);
	 output(op);
	 output(addr>>8);
	 output(addr);
	 pc += 4;
      }
      else
      {
	 list_m3(pc,op,addr);
	 output(op);
	 output(addr>>8);
	 output(addr);
	 pc += 3;
      }
      break;

   case Mrel:
      list_m2(pc,op,addr-pc-2);
      output(op);
      output(addr-pc-2);
      pc += 2;
      break;

   case Mlongrel:
      list_m4(pc,0x10,op,addr-pc-4);
      output(0x10);
      output(op);
      output((addr-pc-4)>>8);
      output(addr-pc-4);
      pc += 4;
      break;

   case Mpost1:
      list_m3(pc,op,addr,addr2);
      output(op);
      output(addr);
      output(addr2);
      pc += 3;
      break;

   case Mpost2:
      list_m4(pc,op,addr,addr2);
      output(op);
      output(addr);
      output(addr2>>8);
      output(addr2&0xFF);
      pc += 4;
      break;

   case Mword:
      list_m2(pc,op>>8,op);
      output(op>>8);
      output(op&0xFF);
      pc += 2;
      break;
   }

   lastpc = pc;					/* remember pc for output */
}

int
output(val)					/* put out a byte */

char val;
{
   if( pass == 1 )				/* no output during pass 1 */
      return;

   if( pc != lastpc )				/* we changed to new address */
   {
      flush_out();
      ldaddr = lastpc = pc;
   }

   if( ccount >= RMAX )				/* filled record */
   {
      flush_out();
      ldaddr += RMAX;
   }

   record[ccount++] = val;			/* just add byte to record */
}

int
init_out()				/* set up output section */
{
   lastpc = (unsigned)(-1);
   ccount = 0;
}

int
flush_out()				/* write out current record */
{
register int i;
register int cksum;
register unsigned int tmp;

   if( ccount <= 0 )
      return;

   tmp = (ldaddr - offset) & mask;	/* apply the output mask and offset */

   fputc(':',loadfid);
   hexout(loadfid,2,ccount);
   hexout(loadfid,4,tmp);
   hexout(loadfid,2,0);

   i = 0;
   cksum = ccount + (tmp>>8) + (tmp & 0xFF);	/* generate checksum */

   while( ccount-- )
   {
      hexout(loadfid,2,(int)record[i]);
      cksum += record[i++];
   }

   hexout(loadfid,2,-cksum);
   fputc('\n',loadfid);
   ccount = 0;
}

int
term_out()				/* terminate loadfile */
{
   if( ccount )				/* stuff in buffer */
      flush_out();

   fprintf(loadfid,":00000001FF\n");
   ccount = 0;
}

int
hexout(fd,len,val)		/* output a value in ascii hex representation */

register FILE *fd;
register int len;
register int val;
{
register int tmp;
register char *cptr;

char buf[16];

   for( cptr = buf; len--; )
   {
      tmp = val & 0xF;
      val >>= 4;

      if( tmp < 0xA )
	 *cptr++ =tmp + '0';
      else
	 *cptr++ = (tmp - 0xA) + 'A';
   }

   while( --cptr >= buf )
      fputc(*cptr,fd);
}

int
list_m1(pc,op)				/* one byte output */

int pc;
int op;
{
   if( !listing || (pass == 1) )
      return;

   hexout(stdout,4,pc);
   fputs("- ",stdout);
   hexout(stdout,2,op);
   fputs("         ",stdout);
   list_line();
}

int
list_m2(pc,op,addr)			/* two byte output */

int pc;
int op;
int addr;
{
   if( !listing || (pass == 1) )
      return;

   hexout(stdout,4,pc);
   fputs("- ",stdout);
   hexout(stdout,2,op);
   putchar(' ');
   hexout(stdout,2,addr);
   fputs("      ",stdout);
   list_line();
}

int
list_m3(pc,op,addr)			/* three byte output */

int pc;
int op;
int addr;
{
   if( !listing || (pass == 1) )
      return;

   hexout(stdout,4,pc);
   fputs("- ",stdout);
   hexout(stdout,2,op);
   putchar(' ');
   hexout(stdout,2,addr>>8);
   putchar(' ');
   hexout(stdout,2,addr);
   fputs("   ",stdout);
   list_line();
}

int
list_m4(pc,op1,op2,addr)		/* four byte output */

int pc;
int op1;
int op2;
int addr;
{
   if( !listing || (pass == 1) )
      return;

   hexout(stdout,4,pc);
   fputs("- ",stdout);
   hexout(stdout,2,op1);
   putchar(' ');
   hexout(stdout,2,op2);
   putchar(' ');
   hexout(stdout,2,addr>>8);
   putchar(' ');
   hexout(stdout,2,addr);
   list_line();
}

int
list_word(word)

int word;
{
   if( !listing || (pass == 1) )
      return;

   hexout(stdout,4,word);
   fputs("             ",stdout);
   list_line();
}

list_line()
{
   if( startofline )
   {
      putchar('\t');
      fputs(linebuf,stdout);
      startofline = FALSE;
   }
   else
      putchar('\n');
}
!E!O!F!
echo x - Makefile
cat >Makefile <<'!E!O!F!'
# Define S3 for system III
#S3='-DS3=S3'

CFLAGS= -O $(DFLAGS) -c
LFLAGS= -i

asm6809: y.tab.o asm6809.o codegen.o
	cc $(LFLAGS) asm6809.o y.tab.o codegen.o\
	-o asm6809

y.tab.o:  y.tab.c lex.yy.c
	cc $(CFLAGS) y.tab.c

y.tab.c:  6809.y 6809.h
	yacc 6809.y

lex.yy.c:  6809.l
	lex 6809.l

asm6809.o: asm6809.c 6809.h
	cc $(CFLAGS) $(S3) asm6809.c

codegen.o: codegen.c 6809.h
	cc $(CFLAGS) $(S3) codegen.c
!E!O!F!