[comp.sources.amiga] v89i023: a68k - 68000 assembler v2.42, Part01/04

page@swan.ulowell.edu (Bob Page) (03/08/89)

Submitted-by: jlydiatt@jlami.wimsey.bc.ca (Jeff Lydiatt)
Posting-number: Volume 89, Issue 23
Archive-name: languages/a68k242.1

#	This is a shell archive.
#	Remove everything above and including the cut line.
#	Then run the rest of the file through sh.
#----cut here-----cut here-----cut here-----cut here----#
#!/bin/sh
# shar:    Shell Archiver
#	Run the following text with /bin/sh to create:
#	A68k.doc
#	A68kmain.c
#	A68kglb.h
# This archive created: Tue Mar  7 20:39:36 1989
cat << \SHAR_EOF > A68k.doc
	A68k - a freely	distributable assembler	for the	Amiga

			by Charlie Gibbs

		     with special thanks to
		Brian R. Anderson and Jeff Lydiatt

		(Version 2.42 -	January	10, 1989)

     Note:  This program is Freely-Distributable, as opposed to	Public
Domain.	 Permission is given to	freely distribute this program provided	no
fee is charged,	and this documentation file is included	with the program.

     This assembler is based on	Brian R. Anderson's 68000 cross-
assembler published in Dr. Dobb's Journal, April through June 1986.
I have converted it to produce AmigaDOS-format object modules, and
have made many enhancements, such as macros and	INCLUDE	files.

     My	first step was to convert the original Modula-2	code into C.
I did this for two reasons.  First, I had access to a C	compiler, but
not a Modula-2 compiler.  Second, I like C better anyway.

     The executable code generator code	(GetObjectCode and MergeModes)
is essentially the same	as in the original article, aside from its
translation into C.  I have almost completely rewritten	the remainder
of the code, however, in order to remove restrictions, add enhancements,
and adapt it to	the AmigaDOS environment.  Since the only reference book
available to me	was the	AmigaDOS Developer's Manual (Bantam, February
1986), the assembler and the remainder of this document	work in	terms
of that	book.


RESTRICTIONS

     Let's get these out of the way first.  There are a few things that I
have not yet implemented, and some outright bugs that would take too long
to correct for this version.

      o	The verification file (-v) option is not supported.  Diagnostic
	messages always	appear on the console.	They also appear in the
	listing	file, however (see extensions below).  You can produce
	an error file by redirecting console output to a file -	the
	line number counter and	final summary are displayed on stderr
	so you can still see what's happening.

      o	The file names in the INCLUDE directory	list (-i) must be separated
	by commas.  The	list may not be	enclosed in quotes.

      o	Labels assigned	by EQUR	and REG	directives are case-sensitive.

      o	The following directives are not supported, and	will be	flagged	as
	invalid	op-codes:

		OFFSET
		NOPAGE
		LLEN
		PLEN
		NOOBJ
		FAIL
		FORMAT
		NOFORMAT
		MASK2

	I feel that NOPAGE, LLEN, and PLEN should not be defined within	a
	source module.	It doesn't make sense to me to have to change your
	program	just because you want to print your listings on	different
	paper.	The command-line option	"-p" (see below) can be used as a
	replacement for	PLEN; setting it to a high value (like 32767) is a
	good substitute	for NOPAGE.  The effect	of LLEN	can be obtained
	by running the listing file through an appropriate filter.


EXTENSIONS

     Now for the good stuff:

      o	Labels can be any length that will fit onto one	source line
	(currently 127 bytes maximum).	Since labels are stored	on the
	heap, the number of labels that	can be processed is limited only
	by available memory.

      o	Since section data and user macro definitions are stored in the
	symbol table (see above), they too are limited only by available
	memory.	 (Actually, there is a hard-coded limit	of 32767 sections,
	but I doubt anyone will	run into that one.)

      o	The only values	a label	cannot take are	the register names - the
	assembler can distinguish between the same name	used as	a label,
	instruction name or directive, macro name, or section name.

      o	Section	and user macro names appear in the symbol table	dump, and
	will also be cross-referenced.	Their names can	be the same as any
	label (see above); the assembler can sort them out.

      o	INCLUDEs and macro calls can be	nested indefinitely, limited only
	by available memory.  The message "Secondary heap overflow -
	assembly terminated" will be displayed if memory is exhausted.
	You can	increase the size of this heap using the -w parameter
	(see below).  Recursive	macros are supported; recursive	INCLUDEs
	will, of course, result	in a loop that will be broken only when
	the heap overflows.

      o	The EVEN directive forces alignment on a word (2-byte) boundary.
	It does	the same thing as CNOP 0,2.
	(This one is left over from the	original code.)

      o	Branch (Bcc) instructions to a previously-defined label	will be
	automatically converted	to short form if possible.  This feature is
	not available for forward branches, since in pass 1 the	assembler
	doesn't yet know how far the branch must go.  You can, however,
	ask A68k to tell you which instructions	can be coded as	short
	branches by using the -f command-line switch (see below).

      o	Backward references to labels within the current CODE section
	will be	converted to PC	relative addressing with displacement
	if this	mode is	legal for the instruction.

      o	If a MOVEM instruction only specifies one register, it is converted
	to the corresponding MOVE instruction.	Instructions such as
	MOVEM D0-D0,label will not be converted, however.

      o	ADD, SUB, and MOVE instructions	will be	converted to ADDQ, SUBQ,
	and MOVEQ respectively if possible.  Instructions coded	explicitly
	as (for	example) ADDA or ADDI will not be converted.

      o	ADD, CMP, SUB, and MOVE	to an address register are converted to
	ADDA, CMPA, SUBA, and MOVEA respectively, unless (for ADD, SUB,
	or MOVE) they have already been	converted to quick form.

      o	ADD, AND, CMP, EOR, OR,	and SUB	of an immediate	value are converted
	to ADDI, ANDI, CMPI, EORI, ORI,	and SUBI respectively (unless the
	address	register or quick conversion above has already been done).

      o	If both	operands of a CMP instruction are postincrement	mode, the
	instruction is converted to CMPM.

      o	Operands of the	form 0(An) will	be treated as (An) except for
	the MOVEP instruction, which always requires a displacement.

      o	The SECTION directive allows a third parameter.	 This can be
	specified as either CHIP or FAST (upper- or lower-case).  If this
	parameter is present, the hunk will be written with the	MEMF_CHIP
	or MEMF_FAST bit set.  This allows you to produce "pre-ATOMized"
	object modules.

      o	The synonyms DATA and BSS are accepted for SECTION directives
	starting data or BSS hunks.  The CHIP and FAST options mentioned
	above can also be used,	e.g. BSS name,CHIP.

      o	The following synonyms have been implemented for compatibility
	with the Aztec assembler:
		CSEG is	treated	the same as CODE or SECTION name,CODE
		DSEG is	treated	the same as DATA or SECTION name,DATA
		PUBLIC is treated as either XDEF or XREF, depending on
		    whether or not the symbol in question has been
		    defined in the current source module.
		    A single PUBLIC directive can name a mixture
		    internally-	and externally-defined symbols.

      o	The ability to produce Motorola	S-records is retained from the
	original code.	The -s option causes the assembler to produce
	S-format instead of AmigaDOS format.  Relocatable code cannot be
	produced in this format.

      o	Error messages consist of three	parts.
	    The	position of the	offending line is given	as a line number
	within the current module.  If the line	is within a macro expan-
	sion or	INCLUDE	file, the position of the macro	call or	INCLUDE
	statement in the outer module is given as well.	 This process
	is repeated until the outermost	source module is reached.
	    Next, the offending	source line itself is listed.
	    Finally, the errors	for that line are displayed.  A	flag
	(^) is placed under the	column where the error was detected.

      o	Named local labels are supported.  These work the same as the
	local labels supported by the Metacomco	assembler (nnn$) but
	can be formed in the same manner as normal labels, except that
	the first character must be a backslash	(\).

      o	The following synonyms have been implemented for compatibility
	with the Assempro assembler:
		ENDIF is treated the same as ENDC
		= is treated the same as EQU
		| is treated the same as ! (logical OR)

      o	Quotation marks	(") can be used as string delimiters
	as well	as apostrophes (').  Any given string must begin
	and end	with the same delimiter.  This allows such statements
	as the following:
		MOVEQ	'"',D0
		DC.B	"This is Charlie's assembler."
	Note that you can still	define an apostrophe within a string
	delimited by apostrophes if you	double it, e.g.
		MOVEQ	'''',D0
		DC.B	'This is Charlie''s assembler.'

      o	If any errors are found	in the assembly, the object code file
	will be	scratched, unless you specified	the -k (keep) flag
	on the command line.

      o	The symbols .A68K, .a68k, .a68K, and .A68k are automatically
	defined	as SET symbols having absolute values of 1.
	This enables a source program to determine whether it is
	being assembled	by this	assembler, and is effectively
	insensitive as to whether or not it is checked in upper	case.

      o	A zeroth positional macro parameter (\0) is supported.	It
	is replaced by the length of the macro call (B,	W, or L,
	defaulting to W).  For instance, given the macro:
		moov	MACRO
			move.\0	\1,\2
			ENDM
	the macro call
			moov.l	d0,d1
	would be expanded as
			move.l	d0,d1

      o	If an INCLUDE file doesn't generate any code and no listing
	file is	required (including suppression	of the listing using
	NOLIST), it won't be read again in pass 2.  The statement
	numbers	will be	bumped to keep in proper alignment.  This
	can really speed up assemblies that INCLUDE lots of EQUates.

      o	The ORG	directive is supported.	 It works like RORG, except
	that it	takes the actual address to be jumped to, rather
	than an	offset from the	start of the current section.
	The given address must be in the current section.
	As far as A68k is concerned, the only real difference
	between	ORG and	RORG is	that the ORG value must	be
	relocatable, while the RORG value must be absolute.


THE SMALL CODE / SMALL DATA MODEL

     Version 2.4 implements a rudimentary small	code/data model.
It consists of converting any data reference to	one of the following
three addressing modes:
	address	register indirect with displacement (using A4)
		(for references	to the DATA or BSS section)
	program	counter	indirect with displacement
		(for references	to the CODE section)
	absolute word
		(for absolute and 16-bit relocatable values)
These conversions do not take place unless a NEAR directive is
encountered.  Any operands on the NEAR directive are ignored.
Conversion is done for all operands until a FAR	directive is
encountered.  NEAR and FAR directives can occur	any number of
times, enabling	conversion to be turned	on and off at will.

     Backward references which cannot be converted (e.g. external
labels declared	as XREF) will remain as	absolute long addressing.
All forward references are assumed to be convertible, since during
pass 1 A68k has	no way of telling whether conversion is	possible.
If conversion turns out	to be impossible, invalid object code will
be generated - an error	message	("Invalid forward reference") will
indicate when this occurs.

     Although the small	code/data model	can greatly reduce the
size of	assembled programs, several restrictions apply:

      o	Small code and small data models are active simultaneously.
	You can't have one without the other, since during pass 1
	A68k doesn't know whether forward references are to CODE
	or to DATA/BSS.

      o	Programs can consist of	a maximum of two sections,
	one CODE, the other DATA or BSS.  If you try to	define
	a third	section, the message "Too many SECTIONs" will
	be displayed.  The NEAR	directive is active only within
	the CODE section.

      o	While the NEAR directive is active, external labels (XREF)
	must be	declared before	they are used, CODE section references
	must be	with 32K of the	current	position (i.e. expressible as
	PC-relative), and DATA/BSS section references must be in the
	first 64K of the DATA/BSS section (i.e.	expressible as
	address	register indirect with displacement).  Any instructions
	which do not satisfy these requirements	cannot be detected in
	pass 1,	so A68k	has no choice but to display an	error message
	in pass	2 ("Invalid forward reference") which in this case
	indicates that invalid code has	been generated.	 To properly
	assemble such instructions, you	can temporarily	disable
	conversion with	a FAR directive, then resume afterwards
	with another NEAR directive.

      o	Conversion cannot be done for references between modules.
	All external references	must be	left as	absolute long.

      o	A68k assumes that register A4 points to	the start of the
	DATA/BSS section plus 32768 bytes.  A4 must be preloaded
	with this value	before executing any code converted by the
	NEAR directive.	 One way to do this is to code the instruction
	that loads the register	prior to the NEAR directive.  Another
	way is to use a	MOVE.L with immediate mode, which is never
	converted.  Here are examples of the two methods:

		LEA	data+32768,a4		NEAR
		NEAR				MOVE.L	#data+32768,a4
	    <remainder of code>		    <remainder of code>
		BSS				BSS
	data:				data:
	    <data areas>		    <data areas>
		END				END

     I'll be the first to admit that this is a very crude and ugly
implementation.	 I hope	to improve it in future	versions.


HOW TO USE A68k

     The command-line syntax to	run the	assembler is as	follows:

	a68k <source file name>
	     [<object file name>]
	     [<listing file name>]
		[-d]
		[-e<equate file	name>]
		[-f]
		[-h<header file	name>]
		[-i<INCLUDE directory list>]
		[-k]
		[-l<listing file name>]
		[-o<object file>]
		[-p<page depth>]
		[-q[<quiet interval>]]
		[-s]
		[-t]
		[-w[<hash table	size>][,<secondary heap	size>]]
		[-x<listing file name>]
		[-y]
		[-z[<debug start line>][,<debug	end line>]]

These options can be given in any order, and the source	file name can
appear before all switches, after them,	or anywhere in the middle.
Option values, if any, must immediately	follow the keyword with
no intervening spaces.

     If	the -o keyword is omitted, the object file will	be given a default
name.  It is created by	replacing all characters after the last	period in
the source file	name by	"o".  For example, if the source file name is
"myprog.asm", the object file name defaults to "myprog.o".  A source name
of "my.new.prog.asm" produces a default object file name of "my.new.prog.o".
If the source file name	does not contain a period, ".o" is appended to it
to produce the default object file name.

     The default value for the listing file name is arrived at in the same
way as the object file name, except that ".lst" is appended instead of ".o".
If you don't specify this parameter, no listing file will be produced.
If you specify -x (see below), -l (with	the default name) is assumed,
although you can still use this	parameter if you wish.

     The default value for the equate file name	is arrived at in the same
way as the object file name, except that ".equ" is appended instead of ".o".

     The INCLUDE directory list	is a list of directory names separated by
commas.	 No embedded blanks are	allowed.  For example, the specification
	-imylib,df1:another.lib
will cause INCLUDE files to be searched	for first in the current directory,
then in	"mylib", then in "df1:another.lib".

     The -d keyword causes symbol table	entries	(hunk_symbol) to be written
to the object module for the use of symbolic debuggers.

     The -f keyword causes any forward branches	(Bcc, BRA, BSR)	that
could be converted to short form to be flagged.	 A68k can't convert them
automatically because it doesn't know in pass 1 how far the branch will
be.  This option tells you which instructions could be manually	converted.

     The -k keyword causes the object file to be kept if any errors were
found.	Otherwise, it will be scratched	if any errors occurred.

     The -l keyword causes a listing file to be	produced.  If you want
the listing file to include a symbol table dump	and cross-reference,
use the	-x keyword instead (see	below).

     The -p keyword causes the page depth to be	set to the specified value.
If omitted, a default of 60 lines (-p60) is assumed.

     The -q keyword changes the	interval at which A68k displays	the
current	line number (the default is every 10 lines, i.e. -q10).	 If
you specify -q0	or -q without a	value, no line numbers will be displayed.
This will speed	up assemblies slightly by reducing console I/O.	 If -q
is specified as	a negative number (e.g.	-q-10),	line numbers will still
be displayed at	the specified interval,	but will be given as positions
within the current module (source, macro, or INCLUDE) rather than
as a total statement count - the module	name will also be displayed.

     The -s keyword, if	specified, causes the object file to be	written	in
Motorola S-record format.  If omitted, AmigaDOS	format will be produced.
The default name for an	S-record file has ".s" appended to the source name,
rather than ".o"; this can still be overridden with the -o keyword, though.

     The -t keyword allows tabs	in the source file to be passed	through
to the listing file, rather than being expanded.  In addition, tabs will
be generated in	the listing file to skip from the object code to the
source statement, etc.	This can greatly reduce	the size of the	listing
file, as well as making	it quicker to produce.	Do not use this	option
if you will be displaying or listing the list file on a	device which
does not assume	a tab stop at every 8th	position.

     The -w keyword specifies the size of the fixed memory areas that
are allocated.	The first parameter gives the number of	entries	that
the hash table will contain (defaulting	to 2047).  This	should be enough
for all	but the	very largest programs.	The assembly will not fail if
this value is too small, but may slow down as a	result of A68k having
to search many long hash chains.  I've heard that you should really
specify	a prime	number for this	parameter, but I haven't gone into
hashing	theory enough to know whether it's actually necessary.
     The second	parameter of the -w keyword specifies the size of the
secondary heap (defaulting to 1024 bytes, which	should be enough
unless you use very deeply nested macros and/or	INCLUDE	files with long
path names).
     You can specify either or both parameters.	 For example:
	-w4093		secondary heap size remains at 1024 bytes
	-w,2000		hash table size	remains	at 2047	entries
	-w4093,2000	increases the size of both areas
     If	you're really tight for memory, and are assembling small modules,
you can	use this keyword to shrink these areas below their default sizes.
At the end of an assembly, a message will be displayed giving the sizes
actually used, in the form of the -w command you would have to enter to
allocate that much space.  This	is primarily useful to see how much
secondary heap space was used.
     NOTE: All other table storage (e.g. the actual symbol table) is
allocated as required (currently in 8K chunks).

     The -x keyword works the same as -l, except that a	symbol table
dump, including	cross-reference	information, will be added to the end
of the listing file.

     The -y keyword causes hashing statistics to be displayed.	First
the number of symbols in the table is given, followed by a breakdown
of hash	chains by length.  Chains with length zero denote unused hash
table entries.	Ideally	(i.e. if there were no collisions) there should
be as many chains with length 1	as there are symbols, and there	should
be no chains of	length 2 or greater.  I	added this option to help me
tune my	hashing	algorithm, but you can also use	it to see whether you
should allocate	a larger hash table (using the first parameter of the
-w option, see above).

     The -z keyword is provided	for debugging purposes.	 You can cause
the assembler to list a	range of source	lines, complete	with line number
and current location counter value, during both	passes.	 For example:
	-z		lists all source lines
	-z100,200	lists lines 100	through	200
	-z100		lists all lines	starting at 100
	-z,100		lists the first	100 lines


     If	you wish to override the default object	and (optionally) listing
file names, you	can omit the -o	and -l keywords.  The assembler	interprets
the first three	parameters without leading hyphens as the source, object,
and listing file names respectively.  Anything over three file names is	an
error, as is attempting	to respecify a file name with the -o or	-l keywords.


TECHNICAL INFORMATION

     The actual	symbol table entries (pointed to by the	hash table,
colliding entries are linked together) are stored in 8K	chunks which
are allocated as required.  The	first entry of each chunk is reserved
as a link to the next chunk (or	NULL in	the last chunk)	- this makes
it easy	to find	all the	chunks to free them when we're finished.  All
symbol table entries are stored	in pass	1.  During pass	2, cross-reference
table entries are built	in the same group of chunks, immediately following
the last symbol	table entry.  Additional chunks	will continue to be
linked in if necessary.

     Symbol names and macro text are stored in another series of linked
chunks.	 These chunks consist of a link	pointer	followed by strings
(terminated by nulls) laid end to end.	Symbols	are independent	entries,
linked from the	corresponding symbol table entry.  Macros are stored as
consecutive strings, one per line - the	end of the macro is indicated by
an ENDM	statement.  If a macro spans two chunks, the last line in the
original chunk is followed by a	newline	character to indicate that the
macro is continued in the next chunk.

     Relocation	information is built during pass 2 in yet another series
of linked chunks.  If more than	one chunk is needed to hold one	section's
relocation information,	all additional chunks are released at the end of
the section.

     The secondary heap	is built from both ends, and it	grows and shrinks
according to how many macros and INCLUDE files are currently open.  At
all times there	will be	at least one entry on the heap,	for the	original
source code file.  The expression parser also uses the secondary heap to
store its working stacks - this	space is freed as soon as an expression
has been evaluated.
     The bottom	of the heap holds the names of the source code file and
any macro or INCLUDE files that	are currently open.  The full path is
given.	A null string is stored	for user macros.  Macro	arguments are
stored by additional strings, one for each argument in the macro call line.
All strings are	stored in minimum space, similar to the	labels and user
macro text on the primary heap.	 File names are	pointed	to by the fixed
table entries (see below) - macro arguments are	accessed by stepping past
the macro name to the desired argument,	unless NARG would be exceeded.
     The fixed portion of the heap is built down from the top.	Each entry
occupies 16 bytes.  Enough information is stored to return to the proper
position in the	outer file once	the current macro or INCLUDE file has been
completely processed.
     The diagram below illustrates the layout of the secondary heap.

	Heap2 +	maxheap2 ----------->  ___________________________
				      |				  |
				      |	  Input	file table	  |
	struct InFCtl *InF ---------> |___________________________|
				      |				  |
				      |	  Parser operator stack	  |
	struct OpStack *Ops --------> |___________________________|
				      |				  |
				      |	  (unused space)	  |
	struct TermStack *Term -----> |___________________________|
				      |				  |
				      |	  Parser term stack	  |
	char *NextFNS --------------> |___________________________|
				      |				  |
				      |	  Input	file name stack	  |
	char *Heap2 ----------------> |___________________________|

     The "high-water mark" for NextFNS is stored in char *High2,
and the	"low-water mark" (to stretch a metaphor) for InF is stored
in struct InFCtl *LowInF.  These figures are used only to determine
the maximum heap usage.


AND FINALLY...

     Please send me any	bug reports, flames, etc.  I can be reached
on Mind	Link (604/533-2312), at	any Panorama (PAcific NORthwest	AMiga
Association) meeting, or via Jeff Lydiatt or Larry Phillips.
(I don't have the time or money to live on Usenet or CompuServe, etc.)

				Charlie	Gibbs
				2121 Rindall Avenue
				Port Coquitlam,	B.C.  V3C 1T9
SHAR_EOF
cat << \SHAR_EOF > A68kmain.c
/*------------------------------------------------------------------*/
/*								    */
/*		      MC68000 Cross Assembler			    */
/*								    */
/*	       Copyright (c) 1985 by Brian R. Anderson		    */
/*								    */
/*		   Main	program	- January 10, 1989		    */
/*								    */
/*   This program may be copied	for personal, non-commercial use    */
/*   only, provided that the above copyright notice is included	    */
/*   on	all copies of the source code.	Copying	for any	other use   */
/*   without the consent of the	author is prohibited.		    */
/*								    */
/*------------------------------------------------------------------*/
/*								    */
/*		Originally published (in Modula-2) in		    */
/*	    Dr.	Dobb's Journal, April, May, and June 1986.          */
/*								    */
/*	 AmigaDOS conversion copyright 1989 by Charlie Gibbs.	    */
/*								    */
/*------------------------------------------------------------------*/

char Version[] = "2.42 (January 10, 1989)";


#include <stdio.h>
#define	PRIMARY
#include "a68kdef.h"
#include "a68kglb.h"


#ifdef MSDOS
/********************************************************************/
/*								    */
/*     NOTE: the following line, plus any additional references	    */
/*     to _iomode, is inserted to make this program work under	    */
/*     the MS-DOS version of Lattice C.	 It is not necessary	    */
/*     for the Amiga version, but does no harm if left in.	    */
/*								    */
/********************************************************************/
int _iomode = 0;	/* File	mode - 0x8000 for binary */
#endif



/* Functions */
extern int  LineParts(), Instructions(), ObjDir();
extern int  GetInstModeSize(), GetMultReg(), CountNest();
extern int  ReadSymTab(), GetArgs(), GetAReg(),	OpenIncl();
extern long AddrBndW(),	AddrBndL(), GetValue(),	CalcValue ();
extern char *AddName(),	*GetField();
extern struct SymTab *NextSym();
extern struct SymTab **HashIt();



main (argc,argv) int argc; char	*argv[];
{
    char ListFN[MAXFN],	EquateFN[MAXFN]; /* File names */
    int	 makeequ;			/* Make	an equate file */
    int	 keepobj;			/* Keep	object file with errors	*/
    int	 endfile;			/* End-of-file flag */
    long maxheap2;			/* Maximum secondary heap size */
    int	 cmderror, dummy;
    long codesize, datasize, bsssize;
    int	 *intptr;
    long templong;
    char tempchar[MAXLINE];
    register struct SymTab *sym;
    register int i, j;
    struct SymTab **hashptr;

    Hash = NULL;	/* Clear all memory pointers - */
    SymStart = NULL;	/*  we haven't allocated anything yet. */
    NameStart =	NULL;
    RelStart = NULL;
    Heap2 = NULL;
    SymSort = NULL;
    In.fd = Eq.fd = List.fd = Srec.fd =	NULL;	/* No files are	open yet */
    In.Buf = Eq.Buf = List.Buf = Srec.Buf = NULL;

    cmderror = FALSE;		/* Clear command-line error flag */
    InclErrs = FALSE;
    SourceFN[0]	= '\0';                 /* Don't have source name yet */
    HeaderFN[0]	= EquateFN[0] =	'\0';   /* No header or equate files yet */
    makeequ = FALSE;
    ListFN[0] =	SrecFN[0] = '\0';       /* Indicate default file names */
    InclList[0]	= '\0';         /* Clear the include directory list */
    IdntName[0]	= '\0';         /* Clear program unit name */
    LnMax = 60;
    Quiet = 10;			/* Show	progress every 10 lines	*/
    strcpy (MacSize, "W");      /* Macro call size (\0) */
    XrefList = DumpSym = GotEqur = KeepTabs = keepobj =	FALSE;
    SuppList = TRUE;		/* Default to no listing file */
    HashStats =	FALSE;		/* Default to no hashing statistics */
    HashSize = DEFHASH;		/* Hash	table size default */
    maxheap2 = DEFHEAP2;	/* Secondary heap size default */
    DebugStart = 32767;	DebugEnd = 0;	/* Disable debug displays */

    for	(i = 0;	i < 256; i++)
	OpPrec[i] = '\0';       /* Set up the operator precedence table */
    i =	(unsigned int) '('; OpPrec[i] = 1;
    i =	(unsigned int) ')'; OpPrec[i] = 2;
    i =	(unsigned int) '+'; OpPrec[i] = 3;
    i =	(unsigned int) '-'; OpPrec[i] = 3;
    i =	(unsigned int) '*'; OpPrec[i] = 4;
    i =	(unsigned int) '/'; OpPrec[i] = 4;
    i =	(unsigned int) '&'; OpPrec[i] = 5;
    i =	(unsigned int) '!'; OpPrec[i] = 5;
    i =	(unsigned int) '|'; OpPrec[i] = 5;
    i =	(unsigned int) '<'; OpPrec[i] = 6;
    i =	(unsigned int) '>'; OpPrec[i] = 6;

    printf ("68000 Assembler - version %s\n", Version);
    printf ("Copyright 1985 by Brian R. Anderson\n");
    printf ("AmigaDOS conversion copyright 1989 by Charlie Gibbs.\n\n");

    for	(i = 1;	i < argc; i++) {	/* Analyze command line	*/
	if (argv[i][0] != '-') {
	    if (SourceFN[0] == '\0')
		strcpy (SourceFN, argv[i]);	/* Source file name */
	    else if (SrecFN[0] == '\0')
		strcpy (SrecFN,	argv[i]);	/* Object file name */
	    else if (ListFN[0] == '\0')
		strcpy (ListFN,	argv[i]);	/* Listing file	name */
	    else {
		fprintf	(stderr, "Too many file names.\n");
		cmderror = TRUE;
	    }
	} else {
	    switch (toupper(argv[i][1])) {
	    case 'D':                   /* Dump the symbol table */
		DumpSym	 = TRUE;
		cmderror |= checkswitch	(argv[i][2], "symbol table dump");
		break;
	    case 'E':                   /* Equate file name */
		makeequ	= TRUE;
		if (getfilename	(EquateFN, &argv[i][2],	"Equate", FALSE))
		    cmderror = keepobj = TRUE;
		break;
	    case 'F':                   /* Dump the symbol table */
		FwdProc	 = TRUE;
		cmderror |= checkswitch	(argv[i][2], "forward reference");
		break;
	    case 'H':                   /* Header file name */
		if (getfilename	(HeaderFN, &argv[i][2],	"Header", TRUE))
		    cmderror = keepobj = TRUE;
		break;
	    case 'I':                   /* Include directories */
		if (argv[i][2])	{
		    if (InclList[0])
			strcat (InclList, ","); /* Add to previous list */
		    strcat (InclList, &argv[i][2]);
		} else {
		    fprintf (stderr, "Include directory list is missing.\n");
		    cmderror = keepobj = TRUE;
		}
		break;
	    case 'K':                   /* Keep object code file */
		keepobj	 = TRUE;
		cmderror |= checkswitch	(argv[i][2], "object file keep");
		break;
	    case 'X':                   /* Cross-reference listing */
		XrefList = TRUE;	/* Falls through to case 'L': */
	    case 'L':                   /* Produce a listing file */
		SuppList = FALSE;
		if (getfilename	(ListFN, &argv[i][2], "List", FALSE))
		    cmderror = keepobj = TRUE;
		break;
	    case 'O':                   /* Object file name */
		if (getfilename	(SrecFN, &argv[i][2], "Object", TRUE))
		    cmderror = keepobj = TRUE;
		break;
	    case 'P':                   /* Page depth */
		if (argv[i][2] == '\0') {
		    fprintf (stderr, "Page depth is missing.\n");
		    cmderror = keepobj = TRUE;
		    break;
		}
		if ((LnMax = CalcValue (&argv[i][2], 0)) < 10) {
		    fprintf (stderr, "Page depth is invalid.\n");
		    cmderror = TRUE;
		}
		break;
	    case 'Q':                   /* Quiet console display */
		Quiet =	CalcValue (&argv[i][2],	0);
		break;
	    case 'S':                   /* Motorola S-format */
		SFormat	= TRUE;
		cmderror |= checkswitch	(argv[i][2], "S-format");
		break;
	    case 'T':                   /* Keep tabs in listing */
		KeepTabs = TRUE;
		cmderror |= checkswitch	(argv[i][2], "tab");
		break;
	    case 'W':                   /* Work storage size(s) */
		if (argv[i][2] == '\0') {
		    fprintf (stderr, "Work storage size is missing.\n");
		    cmderror = keepobj = TRUE;
		    break;
		}
		if (argv[i][2] != ',') {
		    GetField (argv[i]+2, tempchar);
		    HashSize = CalcValue (tempchar, 0);
		    if (HashSize >= 16384) {
			fprintf	(stderr, "Hash table size is too big.\n");
			cmderror = TRUE;
		    }
		}
		for (j = 2; argv[i][j];	j++) {
		    if (argv[i][j] == ',') {    /* Find secondary size */
			maxheap2 = CalcValue (&argv[i][j+1], 0);
			if (maxheap2 < MAXLINE)
			    maxheap2 = MAXLINE;
			maxheap2 &= ~3L;
			break;
		    }
		}
		break;
	    case 'Y':                   /* Display hashing statistics */
		HashStats = TRUE;
		cmderror |= checkswitch	(argv[i][2], "hash statistics");
		break;
	    case 'Z':                   /* Debug option */
		DebugStart = 0;
		DebugEnd = 32767;
		if (argv[i][2] != ',') {        /* Debug dump starts here */
		    GetField (argv[i]+2, tempchar);
		    DebugStart = CalcValue (tempchar, 0);
		}
		for (j = 2; argv[i][j];	j++) {
		    if (argv[i][j] == ',') {    /* Debug dump ends here */
			DebugEnd = CalcValue (&argv[i][j+1], 0);
			if (DebugEnd ==	0)
			    DebugEnd = 32767;
		    }
		}
		break;
	    default:
		fprintf	(stderr, "Unrecognized switch: %c\n", argv[i][1]);
		cmderror = TRUE;
		break;
	    }
	}
    }

    if (makeequ)
	defaultfile (EquateFN, ".equ"); /* Default equate file name */
    if (!SuppList)
	defaultfile (ListFN, ".lst");   /* Default list file name */
    else			/* If there's no listing, don't bother */
	KeepTabs = TRUE;	/*  expanding tabs - it's faster.      */
    if (SFormat)
	defaultfile (SrecFN, ".s");     /* Default S-format file name */
    else
	defaultfile (SrecFN, ".o");     /* Default object file name */

/* Check for duplicate file names. */

    if (SourceFN[0]) {
	cmderror |= checkdupfile (SourceFN, "Source", EquateFN, "equate");
	cmderror |= checkdupfile (SourceFN, "Source", ListFN, "listing");
	cmderror |= checkdupfile (SourceFN, "Source", SrecFN, "object");
    } else {
	fprintf	(stderr, "Source file name is missing.\n");
	cmderror = TRUE;
    }
    if (EquateFN[0]) {
	cmderror |= checkdupfile (EquateFN, "Equate", ListFN, "listing");
	cmderror |= checkdupfile (EquateFN, "Equate", SrecFN, "object");
    }
    if (ListFN[0]) {
	cmderror |= checkdupfile (ListFN, "Listing", SrecFN, "object");
    }

/*	Open files.	*/

    if (!cmderror) {				/* Source file */
	if ((In.Buf = (char *) malloc (BUFFSIZE)) == NULL)
	    quit_cleanup ("Out of memory!\n");
#ifdef MSDOS
	_iomode	= 0x8000;
#endif
	if ((In.fd = open (SourceFN, 0)) == -1)	{
	    fprintf (stderr, "Unable to open source file.\n");
	    In.fd = NULL;
	    cmderror = TRUE;
	}
	In.Ptr = In.Lim	= In.Buf;
    }
#ifdef MSDOS
    _iomode = 0;
#endif
    if (!cmderror && EquateFN[0])		/* Equate file */
	cmderror |= xopen (EquateFN, &Eq, "equate");

    if (!cmderror && !SuppList)			/* Listing file	*/
	cmderror |= xopen (ListFN, &List, "listing");

#ifdef MSDOS
    if (!SFormat)
	_iomode	= 0x8000;
#endif
    if (!cmderror)				/* Object code file */
	cmderror |= xopen (SrecFN, &Srec, "object code");
#ifdef MSDOS
    _iomode = 0x8000;
#endif

    if (cmderror) {
	fprintf	(stderr, "\n");
	fprintf	(stderr, "Usage: a68k <source file>\n");
	fprintf	(stderr, "            [-e<equate file>]\n");
	fprintf	(stderr, "            [-h<header file>]\n");
	fprintf	(stderr, "            [-i<include dirlist>]\n");
	fprintf	(stderr, "            [-l<listing file>]\n");
	fprintf	(stderr, "            [-o<object file>]\n");
	fprintf	(stderr, "            [-p<page depth>]\n");
	fprintf	(stderr, "            [-q[<quiet interval>]]\n");
	fprintf	(stderr, "            [-w[<hash size>][,<heap size>]]\n");
	fprintf	(stderr, "            [-z[<debug start>][,<debug end>]]\n");
	fprintf	(stderr, "            [-d] [-f] [-k] [-s] [-t] [-x] [-y]\n\n");
	fprintf	(stderr, "Command-line arguments can appear in any order.\n");
	fprintf	(stderr, "Heap size default:  -w");
	fprintf	(stderr, "%ld,%ld\n", (long) DEFHASH, (long) DEFHEAP2);
	if (keepobj)
	    SrecFN[0] =	'\0';   /* Don't scratch object file! */
	quit_cleanup ("\n");
    }

    printf ("Assembling %s\n\n", SourceFN);

/* Allocate initial symbol table chunks. */

    templong = sizeof (struct SymTab *)	* HashSize;
    Hash = (struct SymTab **) malloc ((unsigned) templong);
    if (Hash ==	NULL)
	quit_cleanup ("Out of memory!\n");
    for	(hashptr = Hash, i = 0;	i < HashSize; hashptr++, i++)
	*hashptr = NULL;	/* Clear the hash table	*/

    SymStart = (struct SymTab *) malloc	((unsigned) CHUNKSIZE);
    if (SymStart == NULL)
	quit_cleanup ("Out of memory!\n");
    SymCurr = SymStart;			/* Make	the first chunk	current	*/
    SymCurr->Link = NULL;		/* Clear forward pointer */
    SymLim = SymCurr;
    SymLim++;				/* Start of names */

    NameStart =	(struct	NameChunk *) malloc ((unsigned)	CHUNKSIZE);
    if (NameStart == NULL)
	quit_cleanup ("Out of memory!\n");
    NameCurr = NameStart;		/* Make	the first chunk	current	*/
    NameCurr->Link = NULL;		/* Clear forward pointer */
    NameLim = (char *) NameCurr	+ sizeof (char *);  /* Start of	names */

/* Allocate the	relocation attribute table. */

    RelStart = (struct RelTab *) malloc	((unsigned) CHUNKSIZE);
    if (RelStart == NULL)
	quit_cleanup ("Out of memory!\n");
    RelCurr = RelStart;			/* Relocation table */
    RelCurr->Link = NULL;		/* No additional chunks	*/
    RelLast = NULL;			/* There are no	entries	yet */
    RelLim = RelStart;
    RelLim++;				/* First unused	space */

/* Allocate the	secondary heap (input files and	parser stack). */

    Heap2 = malloc ((unsigned) maxheap2);
    if (Heap2 == NULL)
	quit_cleanup ("Out of memory!\n");

/* Allocate the	INCLUDE	skip table. */

    SkipLim = (struct SkipEnt *) malloc	((unsigned) INCSKSIZ);
    if (SkipLim	== NULL)
	quit_cleanup ("Out of memory!\n");
    SkipIdx = SkipLim;
    SetFixLim =	(struct	SetFixup *) ((char *) SkipLim +	INCSKSIZ);
    IncStart = 0;

/*-------------------------------------------------------------------

    Begin Pass 1.
								   */
    Pass2 = FALSE;
    startpass ('1', maxheap2);
    NumSyms = 0;	/* There's nothing in the symbol table yet */
    NextHunk = 0L;	/* Start in hunk zero */
    LowInF = InF;	/* Initialize secondary	heap usage pointers */
    High2 = NextFNS;
    Low2  = (char *) LowInF;

    /* Define ".A68K" as a SET symbol with an absolute value of 1.
	This allows programs to	identify this assembler.	*/
    AddSymTab (".A68K", 1L, (long) ABSHUNK, 0, 4);  /* All spellings */
    AddSymTab (".A68k", 1L, (long) ABSHUNK, 0, 4);
    AddSymTab (".a68K", 1L, (long) ABSHUNK, 0, 4);
    AddSymTab (".a68k", 1L, (long) ABSHUNK, 0, 4);

    endfile = FALSE;
    Dir	= None;
    while (!endfile && (Dir != End)) {
	PrevDir	= Dir;			/* Save	previous directive */
	endfile	= LineParts (dummy);	/* Get a statement */
	GetObjectCode (dummy);		/* Process the statement */

	if (IncStart !=	0) {
	    if ((OpCode[0] != '\0') && (Dir < SkipDir)) {
		IncStart = 0;			/* We can't      */
		if (SkipLim->Set1 != NULL) {	/*  skip this	 */
		    SetFixLim =	SkipLim->Set1;	/*  INCLUDE file */
		    SetFixLim++;		/*  in pass 2.	 */
		}
	    }
	}
	if ((HunkType == HunkNone) && (AddrAdv != 0)) {
	    DoSection ("", 0, "", 0, "", 0);    /* Start unnamed CODE section */
	    MakeHunk = TRUE;
	}
	if ((Label[0] != '\0')                  /* If statement is labeled */
	&& (Dir	!= Set)	&& (Dir	!= Equr) && (Dir != Reg)) {
	    if (!ReadSymTab (Label)) {		/* Make	a new entry */
		AddSymTab (Label, AddrCnt, CurrHunk, LineCount,	0);
	    } else if ((Sym->Flags & 1)		/* If dup., ignore */
	    || (Sym->Defn == NODEF)) {		/* else	fill in	*/
		Sym->Val = AddrCnt;		/* Current loc.	*/
		Sym->Hunk = CurrHunk;		/* Hunk	number */
		Sym->Defn = LineCount;		/* Statement number */
		Sym->Flags &= ~1;		/* Clear XREF flag */
		if (Sym->Flags & 0x80) {	/* If it's PUBLIC, */
		    Sym->Flags |= 2;		/*  make it XDEF */
		}
	    }
	    if (Dir == Equ) {
		Sym->Val = ObjSrc;		/* Equated value */
		Sym->Hunk = Src.Hunk;		/* Hunk	number */
	    }
	}
	AddrCnt	+= AddrAdv;	/* Advance location counter */
    }
    if ((HunkType == HunkNone) && (NumSyms != 0)) { /* Dummy section   */
	DoSection ("", 0, "", 0, "", 0);            /*  to get XDEF    */
	MakeHunk = TRUE;			    /*	symbols	if any */
    }
    if (HunkType != HunkNone)
	if (AddrCnt > OrgHigh)
	    Sect->Val =	AddrCnt;	/* End of the last section */
	else
	    Sect->Val =	OrgHigh;	/* We've ORGed higher */

    if (InclErrs)
	quit_cleanup ("Fatal errors - assembly aborted\n");

    if (Quiet >= 0)
	fprintf	(stderr, "%d\n", LineCount);
    else
	fprintf	(stderr, "%d\n\n", InF->Line);



/*----------------------------------------------------------------

	Begin Pass 2.
							       */
    Pass2 = TRUE;
    lseek (In.fd, 0L, 0);		/* "Rewind" the source file */
    In.Ptr = In.Lim = In.Buf;
    startpass ('2', maxheap2);
    RefLim = (struct Ref *) SymLim;	/* Cross-reference table */

/* Calculate the total size of each section type,
    reset all section pointers to the beginning, and
    write all absolute symbols to an equate file if desired. */

    codesize = datasize	= bsssize = 0;
    if (EquateFN[0]) {
	xputs (&Eq, "* Equate file for ");
	xputs (&Eq, SourceFN);
	xputs (&Eq, "\n* Created by");
	xputs (&Eq, " A68k version ");
	xputs (&Eq, Version);
	xputs (&Eq, "\n");
    }
    Sym	= SymChunk = SymStart;
    Sym++;
    SymChLim = (struct SymTab *) ((char	*) SymChunk + CHUNKSIZE);
    while (Sym)	{
	if (Sym->Flags & 0x10) {
	    templong = (Sym->Val + 3) &	~3L;		/* Hunk	size */
	    j =	(Sym->Hunk & 0x3FFF0000L) >> 16;	/* Hunk	type */
	    if (j == HunkCode)		    /* Accumulate sizes	by type	*/
		codesize += templong;
	    else if (j == HunkData)
		datasize += templong;
	    else
		bsssize	+= templong;
	    Sym->Val = 0L;	/* Back	to start of all	sections */
	}
	if (EquateFN[0]) {
	    if (((Sym->Hunk & 0x00007FFFL) == ABSHUNK)
	    && ((Sym->Flags == 0) || (Sym->Flags == 2))) {
		xputs (&Eq, Sym->Nam);
		xputs (&Eq, "\tEQU\t$");
		LongPut	(&Eq, Sym->Val,	4);
		xputs (&Eq, "\n");
	    }
	}
	Sym = NextSym (Sym);	/* Try for another symbol table	entry */
    }
    if (EquateFN[0])
	xclose (&Eq);

/* Write sign-on messages for listing file */

    LnCnt = LnMax;
    PgCnt = 0;
    if (!SuppList) {
	CheckPage (&List, FALSE);		/* Print headings */
	xputs (&List, "68000 Assembler - version ");
	xputs (&List, Version);
	xputs (&List, "\nCopyright 1985 by Brian R. Anderson.\n");
	xputs (&List, "AmigaDOS conversion copyright 1989");
	xputs (&List, " by Charlie Gibbs.\n\n");
	LnCnt += 4;
    }

    StartSrec (&Srec, IdntName);	/* Write object	header record */

/*	Process	the second pass.	*/

    endfile = FALSE;
    Dir	= None;
    while (!endfile && (Dir != End)) {
	PrevDir	= Dir;			/* Save	previous directive */
	endfile	= LineParts (dummy);	/* Get a statement */
	if (!endfile) {
	    GetObjectCode (dummy);	/* Process the statement */
	    if (Label[0] != '\0') {     /* If statement is labeled, */
		ReadSymTab (Label);	/*  check for duplicate	defn. */
		if (Sym->Defn != LineCount) {
		    AddRef (LineCount);	/* Got one - flag as reference */
		    if (Dir == Set) {
			if ((Sym->Flags	& 4) ==	0)
			    Error (LabLoc, SymDup); /* Can't SET normal label */
		    } else {
			Error (LabLoc, SymDup);	/* Ordinary duplicate */
		    }
		} else if (Dir == Set) {
		    AddRef (LineCount);	/* Flag	all SETs as references */
		} else {
		    if (Sym->Val != AddrCnt)
			if ((Dir != Equ) && (Dir != Equr) && (Dir != Reg))
			    Error (0, Phase);	/* Assembler error */
		}
	    }
	    WriteListLine (&List);
	    WriteSrecLine (&Srec);
	    AddrCnt += AddrAdv;		/* Advance location counter */
	} else {
	    Error (0, EndErr);		/* END statement is missing */
	    WriteListLine (&List);
	}
    }
    if ((HunkType == HunkNone) && (NumSyms != 0)) { /* Dummy section   */
	DoSection ("", 0, "", 0, "", 0);            /*  to get XDEF    */
	MakeHunk = TRUE;			    /*	symbols	if any */
    }

/*---------------------------------------------------------------------

	Clean up.
								*/

    if (HunkType != HunkNone)
	if (AddrCnt > OrgHigh)
	    Sect->Val =	AddrCnt;	/* End of the last section */
	else
	    Sect->Val =	OrgHigh;	/* We've ORGed higher */

    if (Quiet >= 0)
	fprintf	(stderr, "%d", LineCount);      /* Final line number */
    else
	fprintf	(stderr, "%d\n", InF->Line);
    fflush (stderr);			/* Make	sure it	gets out */

    close (In.fd);		/* Finished with source	file */
    In.fd = NULL;
    free (In.Buf);
    In.Buf = NULL;

    EndSdata (&Srec, EndAddr);	/* Write remaining data	and end	record */
    xclose (&Srec);		/* Finished with object	file */
    if ((ErrorCount != 0) && (!keepobj))
	unlink (SrecFN);	/* Scratch it if there were errors */

    RelCurr = RelStart;
    while (RelCurr != NULL) {
	RelLim = RelCurr;
	RelCurr	= RelCurr->Link;
	free (RelLim);		/* Free	the relocation table */
	RelCurr	= NULL;
    }

    if (Heap2 != NULL) {
	free (Heap2);		/* Free	the secondary heap */
	Heap2 =	NULL;
    }

    if (XrefList)
	WriteSymTab (&List);	/* List	the symbol table */

/* Display final error count. */
    fprintf (stderr, "\nEnd of assembly - ");
    if (!SuppList)
	xputs (&List, "\nEnd of assembly - ");
    if (ErrorCount == 0) {
	fprintf	(stderr, "no errors were found.\n");
	if (!SuppList)
	    xputs (&List, "no errors were found.\n");
    } else if (ErrorCount == 1)	{
	fprintf	(stderr, "1 error was found.\n");
	if (!SuppList)
	    xputs (&List, "1 error was found.\n");
    } else {
	fprintf	(stderr, "%d errors were found.\n", ErrorCount);
	if (!SuppList) {
	    sprintf (tempchar, "%d errors were found.\n", ErrorCount);
	    xputs (&List, tempchar);
	}
    }

/* Display heap	usage. */
    fprintf (stderr, "Heap usage:  -w%ld", HashSize);
    if (!SuppList) {
	sprintf	(tempchar, "Heap usage:  -w%ld", HashSize);
	xputs (&List, tempchar);
    }
    templong = (long) (High2 - Heap2);
    if (Low2 < (char *)	LowInF)
	templong += (long) (Heap2 + maxheap2 - Low2);
    else
	templong += (long) (Heap2 + maxheap2 - (char *)	LowInF);
    fprintf (stderr, ",%ld\n", templong);
    if (!SuppList) {
	sprintf	(tempchar, ",%ld\n", templong);
	xputs (&List, tempchar);
    }

/* Display the total size of all section types.	*/
    fprintf (stderr, "Total hunk sizes:  %lx code, ", codesize);
    fprintf (stderr, "%lx data, %lx BSS\n", datasize, bsssize);
    if (!SuppList) {
	sprintf	(tempchar, "Total hunk sizes:  %lx code, ", codesize);
	xputs (&List, tempchar);
	sprintf	(tempchar, "%lx data, %lx BSS\n", datasize, bsssize);
	xputs (&List, tempchar);
    }

/* Display hashing statistics if required. */
    if (HashStats && (NumSyms != 0)) {
	printf ("\n");
	printf ("HASH CHAIN STATISTICS - %d symbols\n\n", NumSyms);
	templong = (NumSyms + 1) * sizeof (int);
	HashCount = (int *) malloc ((unsigned) templong);
	if (HashCount == NULL)
	    quit_cleanup ("Out of memory!\n");

	printf ("Length     No. of chains\n");
	printf ("------     -------------\n");
	intptr = HashCount;
	for (i = 0; i <= NumSyms; i++)
	    *(intptr++)	= 0;	/* Clear hash chain length counters */

	hashptr	= Hash;
	for (i = 0; i <	HashSize; i++) {
	    j =	0;
	    if ((Sym = *hashptr) != NULL) {
		j++;		/* This	chain has at least one entry */
		while ((Sym = Sym->Link) != NULL) {
		    j++;	/* Count entries in the	chain */
		}
	    }
	    intptr = HashCount + j;
	    (*intptr)++;	/* Bump	counter	by chain length	*/
	    hashptr++;
	}
	intptr = HashCount;
	for (i = 0; i <= NumSyms; i++) {
	    if (*intptr)
		printf ("%4d          %4d\n", i, *intptr);
	    intptr++;
	}
	free (HashCount);		/* Free	hash statistics	table */
	HashCount = NULL;
    }

/* All done! */
    if (!SuppList) {
	xputs (&List, "\f");    /* One last page eject */
	xclose (&List);		/* Finished with listing file */
    }
    quit_cleanup ("");          /* Normal termination */
}



/*======================================================================*/
/*									*/
/*		Subroutines used by the	main program			*/
/*									*/
/*======================================================================*/



int getfilename	(name, arg, desc, needit)
char *name, *arg, *desc;
int needit;
/* If "name" is not a duplicate, copies "arg" to it, else flags
    duplicate using "desc".  If "needit" is TRUE, also flags
    an error if	"arg" is a null string.
    Returns TRUE if an error is	found, FALSE otherwise.	*/
{
    if (*name) {
	fprintf	(stderr, "%s file is declared more than once.\n", desc);
	return (TRUE);
    }
    if (*arg) {
	strcpy (name, arg);
	return (FALSE);
    }
    if (needit)	{
	fprintf	(stderr, "%s file name is missing\n", desc);
	return (TRUE);
    }
    return (FALSE);
}



int checkswitch	(c, name) char c, *name;
/* Displays an error message and returns TRUE if "c" isn't a NULL.
    Just returns FALSE otherwise.				*/
{
    if (c) {
	fprintf	(stderr, "Invalid %s switch.\n", name);
	return (TRUE);
    } else {
	return (FALSE);
    }
}



defaultfile (name, ext)	char *name, *ext;
/* If "name" is a null string, search for the last period in "name"
    (if	any) and append	"ext".
    If "name" doesn't contain a period, append a period and "ext". */
{
    char *s;

    if (*name == '\0') {        /* If name isn't specified... */
	strcpy (name,SourceFN);	/* Start with source file name */
	s = name+strlen(name);	/* Scan	backwards for period */
	while (--s > name) {
	    if (*s == '.') {
		*s = '\0';      /* Chop off name extension */
		break;
	    }
	}
	strcat (name, ext);	/* Add name extension */
    }
}



int checkdupfile (name1, desc1,	name2, desc2)
char *name1, *desc1, *name2, *desc2;
/* If "name1" is the same as "name2", display an error message using
    "desc1" and "desc2" and return TRUE.  Otherwise, return FALSE. */
{
    if (strcmp (name1, name2) == 0) {
	fprintf	(stderr,
	    "%s and %s file names are the same.\n", desc1, desc2);
	return (TRUE);
    } else {
	return (FALSE);
    }
}



startpass (pchar, maxheap2) char pchar;	long maxheap2;
/* Set up to start the next pass. */
{
    int	dummy;

    if (Quiet >= 0) {
	fprintf	(stderr, "PASS %c line ", pchar);
	fflush (stderr);
    } else {
	fprintf	(stderr, "PASS %c\n", pchar);
    }
    NextFNS = Heap2;
    InF	= (struct InFCtl *) (Heap2 + maxheap2);
    InF--;
    InFNum = OuterMac =	SkipNest = InF->Pos = InF->MCnt	= 0;
    InF->Line =	0;
    InF->UPtr =	0;
    InF->NPtr =	NextFNS;
    InF->NArg =	-1;
    InF->MCnt =	0;
    strcpy (NextFNS, SourceFN);
    ShowFile (FALSE);			/* Show	source file name */
    NextFNS += strlen (SourceFN) + 1;
    LineCount =	LabLine	= MacCount = ErrorCount	= 0;
    AddrCnt = CurrHunk = SectStart = EndAddr = 0L;
    HunkType = HunkNone;		/* We're not in a hunk yet */
    HunkFlags =	SectLine = HunkSeq = 0;
    ListOff = MakeHunk = InnrFMac = SmallData =	FALSE;
    TTLstring[0] = '\0';                /* Clear the title string */
}



quit_cleanup (s) char *s;
/* Clean up and	exit. */
{
    if (In.fd != NULL)			/* Close all files */
	close (In.fd);
    if (In.Buf != NULL)			/*  and	free buffers */
	free (In.Buf);
    if (Srec.fd	!= NULL)
	xclose (&Srec);
    if (List.fd	!= NULL)
	xclose (&List);
    if (Eq.fd != NULL)
	xclose (&Eq);

    if (Hash !=	NULL)
	free (Hash);			/* Free	the hash table */

    SymCurr = SymStart;
    while (SymCurr != NULL) {
	SymLim = SymCurr;
	SymCurr	= SymCurr->Link;
	free (SymLim);			/* Free	the symbol table */
    }

    NameCurr = NameStart;
    while (NameCurr != NULL) {
	NameLim	= (char	*) NameCurr;
	NameCurr = NameCurr->Link;
	free (NameLim);			/* Free	the name table */
    }

    RelCurr = RelStart;
    while (RelCurr != NULL) {
	RelLim = RelCurr;
	RelCurr	= RelCurr->Link;
	free (RelLim);			/* Free	the relocation table */
    }

    if (Heap2 != NULL)
	free (Heap2);			/* Free	the secondary heap */

    if (SymSort	!= NULL)
	free (SymSort);			/* Free	symbol table sort area */

    if (HashCount != NULL)
	free (HashCount);		/* Free	hash statistics	table */

    if (*s) {				/* If we have an error message,	*/
	if (SrecFN[0])
	    unlink (SrecFN);		/*  scratch the	object file,	*/
	fprintf	(stderr, "%s", s);      /*  display the error message,  */
	exit (20);			/*  and	die. */
    } else {
	exit (ErrorCount ? 10 :	0);	/* Normal termination */
    }
}
SHAR_EOF
cat << \SHAR_EOF > A68kglb.h
/*------------------------------------------------------------------*/
/*								    */
/*		      MC68000 Cross Assembler			    */
/*								    */
/*	       Copyright (c) 1985 by Brian R. Anderson		    */
/*								    */
/*		 Global	variables - January 4, 1989		    */
/*								    */
/*   This program may be copied	for personal, non-commercial use    */
/*   only, provided that the above copyright notice is included	    */
/*   on	all copies of the source code.	Copying	for any	other use   */
/*   without the consent of the	author is prohibited.		    */
/*								    */
/*------------------------------------------------------------------*/
/*								    */
/*		Originally published (in Modula-2) in		    */
/*	    Dr.	Dobb's Journal, April, May, and June 1986.          */
/*								    */
/*	 AmigaDOS conversion copyright 1989 by Charlie Gibbs.	    */
/*								    */
/*------------------------------------------------------------------*/

#ifdef PRIMARY
#define	GLOBAL
#else
#define	GLOBAL extern
#endif

GLOBAL char SourceFN[MAXFN];	/* Source file name */
GLOBAL char HeaderFN[MAXFN];	/* Header file name (-h) */
GLOBAL char SrecFN[MAXFN];	/* Object file name (-o) */
GLOBAL char InclList[MAXLINE];	/* List	of directories to search (-i) */
GLOBAL char IdntName[MAXLINE];	/* Program unit	name */

struct fs {
    int	fd;		/* File	handle */
    char *Buf;		/* Pointer to buffer */
    char *Ptr;		/* Current position in buffer */
    char *Lim;		/* Logical end of buffer */
};
GLOBAL struct fs In;	/* Input file */
GLOBAL struct fs Eq;	/* Equate file */
GLOBAL struct fs List;	/* Listing file	*/
GLOBAL struct fs Srec;	/* Object file */

/*	Command-line options	*/
GLOBAL int DumpSym;	/* -d Dump the symbol table */
GLOBAL int FwdProc;	/* -f Special processing for forward references	*/
GLOBAL int KeepTabs;	/* -k Keep tabs	in the listing file */
GLOBAL int SuppList;	/* (neither -l nor -x) Suppress	listing	file */
GLOBAL int LnMax;	/* -p Maximum number of	lines per page */
GLOBAL int Quiet;	/* -q Line no. display interval	(0 to suppress)	*/
GLOBAL long HashSize;	/* -w Number of	entries	in the hash table */
GLOBAL int XrefList;	/* -x Produce a	cross-reference	listing	*/
GLOBAL int HashStats;	/* -y Display hashing statistics */
GLOBAL int DebugStart;	/* -z Debug display starts here	*/
GLOBAL int DebugEnd;	/* -z Debug display ends here */

GLOBAL char TTLstring[MAXLINE];	/* Title string	*/

GLOBAL int  LabLine;		/* Last	labeled	line number */
GLOBAL int  LineCount;		/* Source line counter */
GLOBAL char Line[MAXLINE];	/* Current source line */
GLOBAL char Label[MAXLINE];	/* Instruction label */
GLOBAL char OpCode[MAXLINE];	/* Instruction mnemonic	*/
GLOBAL char SrcOp[MAXLINE];	/* First (source) operand */
GLOBAL char DestOp[MAXLINE];	/* Second (destination)	operand	*/
GLOBAL int  LabLoc, OpLoc;	/* Label and mnemonic start here */
GLOBAL int  SrcLoc, DestLoc;	/* Operands start here */
GLOBAL int  Dir, PrevDir;	/* Assembler directive */
GLOBAL int  NumSyms;		/* Number of symbols */
GLOBAL long ObjOp;		/* OpCode object code */
GLOBAL long ObjSrc;		/* Source operand object code */
GLOBAL long ObjDest;		/* Destination operand object code */
GLOBAL char ObjString[MAXLINE];	/* String data */
GLOBAL int  nO,	nS, nD,	nX;	/* Length of above components */
GLOBAL int  PrntAddr;		/* Print AddrCnt on listing */
GLOBAL int  MakeHunk;		/* We must make	a hunk */
GLOBAL int  ListOff;		/* NOLIST is supressing	listing	lines */
GLOBAL int  LnCnt;		/* Number of lines on current page */
GLOBAL int  PgCnt;		/* Page	number */
GLOBAL long Hunk2;		/* Hunk	number (from GetValue) */
GLOBAL int  DefLine2;		/* Definition line number */
GLOBAL int  GotEqur;		/* We have register equates */
GLOBAL int  SmallData;		/* Small data model */
GLOBAL int  AnyNear;		/* We got at least one NEAR directive */
GLOBAL int  FwdShort;		/* Forward reference could be made short */

GLOBAL int  Pass2;	/* Pass	2 flag */
GLOBAL long AddrCnt;	/* Location counter */
GLOBAL long AddrAdv;	/* Bump	AddrCnt	by this	much */
GLOBAL long OrgHigh;	/* Highest address reached if we ORG backwards */
GLOBAL long OrgSeek;	/* Return here in Srec if we ORG backwards */
GLOBAL long EndAddr;	/* END statement transfer address */
GLOBAL long SectStart;	/* Current section (or portion)	starts here */
GLOBAL int  SectLine;	/* Line	number where section started */
GLOBAL int  HunkSeq;	/* Hunk	sequence number	*/
GLOBAL long HunkType;	/* Current hunk	type */
GLOBAL long HunkFlags;	/* Hunk	flags (MEMF_FAST or MEMF_CHIP) */
GLOBAL long CurrHunk;	/* Current hunk	number */
GLOBAL long NextHunk;	/* Next	available hunk number */
GLOBAL long LenPos;	/* Seek	position of current hunk length	*/
GLOBAL char *LenPtr;	/* Pointer to length if	in buffer, else	NULL */
GLOBAL int  InclErrs;	/* Error processing INCLUDE statement(s) */
GLOBAL int  InnrFMac;	/* An inner file has been read by a user macro */
GLOBAL int  OrgFlag;	/* ORG may require object file fixup */

GLOBAL int  SFormat;	/* Generate S-record format */
GLOBAL long StartAddr;	/* Address that	record starts on */
GLOBAL long TempAddr;	/* Address of where we are now */

GLOBAL int  IncStart;	/* Start line number of	skippable INCLUDE */
GLOBAL struct InFCtl *IncPtr;	/* Copy	of InF for skippable INCLUDE */
struct SkipEnt {		/* Skippable INCLUDE description */
    struct SetFixup *Set1;	/*  Pointer to first SET fixup */
    int	Start;			/*  Starting line number of INCLUDE */
    int	Finish;			/*  Ending line	number of INCLUDE */
    int	MCount;			/*  Value of MacCount at end of	INCLUDE	*/
};
struct SetFixup	{		/* SET symbol fixup entry */
    struct SymTab *Sym;		/* Pointer to symbol table entry */
    long Val;			/* Fixup value */
    long Hunk;			/* Fixup hunk number */
};
GLOBAL struct SkipEnt *SkipLim;	/* Logical end of skippable INCLUDEs */
GLOBAL struct SkipEnt *SkipIdx;	/* Current skippable INCLUDE entry */
GLOBAL struct SetFixup *SetFixLim;	/* Next	available SetFixup */

struct SymTab {				/* Symbol table	*/
    struct SymTab *Link;	/* Link	to next	entry in hash chain */
    char *Nam;	/* Pointer to symbol */
    long Val;	/* Value */
    long Hunk;	/* Hunk	number (ORed with MEMF_CHIP or MEM_FAST
			if applicable SECTION
		   ~(pointer to	symbol)	if XREF
		   Pointer to macro text if MACRO		*/
    int	 Defn;	/* Line	number where defined */
    int	 Flags;	/* Flags bits:	0 - XREF
				1 - XDEF
				2 - SET
				3 - MACRO (symbol is preceded by blank)
				4 - SECTION (name preceded by 2	blanks
					and 4-digit hex	sequence number)
				5 - register name (EQUR)
				6 - register list (REG)
				7 - PUBLIC (XREF or XDEF will be set) */
    struct Ref *Ref1;	/* Pointer to first reference entry */
};
GLOBAL struct SymTab *SymStart;	/* The symbol table starts here	*/
GLOBAL struct SymTab *SymLim;	/* The symbol table ends here */
GLOBAL struct SymTab *SymCurr;	/* Start of current chunk of data */
GLOBAL struct SymTab *Sym;	/* ReadSymTab sets this	up */
GLOBAL struct SymTab *Sect;	/* Current section's entry */
GLOBAL struct SymTab *SymChunk;	/* Current symbol chunk	for NextSym */
GLOBAL struct SymTab *SymChLim;	/* End of *SymChunk chunk */
GLOBAL struct SymTab **Hash;	/* Pointer to hash table */
GLOBAL struct SymTab **SymSort;	/* Symbol sort area */
GLOBAL int  *HashCount;		/* Hashing summary table */

struct NameChunk {		/* Chunk of labels or macro text */
    struct NameChunk *Link;	/* Link	to the next chunk */
    char *Data[CHUNKSIZE-sizeof(struct NameChunk *)];	/* Data	area */
};
GLOBAL struct NameChunk	*NameStart;	/* Start of first name chunk */
GLOBAL char		*NameLim;	/* Next	available name entry */
GLOBAL struct NameChunk	*NameCurr;	/* Start of current name chunk */

struct Ref {			/* Reference entry */
    struct Ref *NextRef;	/* Pointer to next reference entry */
    int	RefNum[MAXREF];		/* Reference line numbers */
};
GLOBAL struct Ref *RefLim;	/* Next	available reference entry */

struct RelTab {			/* Relocation table entry */
    struct RelTab *Link;	/* Link	to the next entry */
    long Offset;		/* Offset to relocatable value */
    long Hunk;			/* Hunk	type to	relocate relative to */
    int	Size;			/* Size	of relocatable value */
};
GLOBAL struct RelTab *RelStart;	/* Relocation data starts here */
GLOBAL struct RelTab *RelLim;	/* Relocation data ends	here */
GLOBAL struct RelTab *RelCurr;	/* Start of current chunk of data */
GLOBAL struct RelTab *RelLast;	/* Last	relocation entry added */

struct TermStack {		/* Parser's term stack */
    long value;		/* Value */
    long hunk;		/* Hunk	number */
    int	 oploc;		/* Location in source statement	*/
    int	 defline;	/* Line	number where defined */
};
GLOBAL struct TermStack	*Term;	/* Term	stack pointer */

struct OpStack {		/* Parser's operator stack */
    char chr;		/* Operator character */
    int	 prec;		/* Precedence */
};
GLOBAL struct OpStack *Ops;	/* Operator stack pointer */

GLOBAL char OpPrec[256];	/* Operator precedence look-up table */

GLOBAL int  InFNum;		/* Current input nesting level */
struct InFCtl {
    long Pos;			/* Current position in input */
    char *UPtr;			/* Current position in user macro or 0 */
    char *NPtr;			/* File	name stack pointer */
    int	 Line;			/* Current line	number in this file */
    int	 NArg;			/* Number of macro arguments or	-1 */
    int	 MCnt;			/* Macro expansion number (for \@) */
};
GLOBAL struct InFCtl *InF;	/* Macro/include file stack pointer */
GLOBAL struct InFCtl *LowInF;	/* "Low-water mark" for InF */
GLOBAL char *Heap2;		/* Secondary heap */
GLOBAL char *NextFNS;		/* Next	input file path/name */
GLOBAL char *High2;		/* Secondary high-water	mark */
GLOBAL char *Low2;		/* Low limit from top of heap */

GLOBAL int  OuterMac;		/* Level number	of outermost macro */
GLOBAL int  MacCount;		/* Number of macros expanded */
GLOBAL int  SkipNest;		/* Skipped IF/ENDC nesting count */
GLOBAL char MacSize[2];		/* Macro call size ("B", "W", or "L") */

struct OpConfig	{		/* Operand configuration */
    long Value;	/* Value */
    long Hunk;	/* Hunk	number */
    int	 Defn;	/* Line	number where defined */
    int	 Mode;	/* Addressing mode */
    int	 Loc;	/* Location of operand on Line */
    int	 Rn;	/* Register number */
    int	 Xn;	/* Index register number */
    int	 Xsize;	/* Size	of index */
    int	 X;	/* Is index Data or Address reg? */
};
GLOBAL struct OpConfig Src, Dest;   /* Source and destination operands */

GLOBAL int Size;	/* size	for OpCode */
GLOBAL int InstSize;	/* Size	of instruction,	including operands */
GLOBAL int AdrModeA;	/* Addressing modes for	this instruction */
GLOBAL int AdrModeB;	/*		 ditto			 */
GLOBAL int Op;		/* Raw bit pattern for OpCode */

GLOBAL int ErrorCount;

/* Error message tables	*/
GLOBAL int ErrLim, ErrCode[ERRMAX], ErrPos[ERRMAX];
SHAR_EOF
#	End of shell archive
exit 0
-- 
Bob Page, U of Lowell CS Dept.  page@swan.ulowell.edu  ulowell!page
Have five nice days.