[mod.mac.sources] Unpit version 0.3.1 Source

macintosh@felix.UUCP (02/13/87)

[Unpit version 0.3.1 Source - part 1 of 3]

---
/*

		unpit - Macintosh PackIt file packer/unpacker
		
   This program is a Macintosh translation/expansion of 'unpit', a
Unix program written by Allan G. Weber (Weber%Brand@USC-ECL) that
unpacks Packit-I and -II files.  Why port it to the Mac?  Well,
Packit-II is not free, but many people are posting {public domain,
noncommercial, or shareware} programs to USENET's net.sources.mac
and various other places in Packit-II format, apparently due to
the popularity achieved by the free Packit-I.  This program is
intended to get rid of the need to choose between these undesirable
alternatives:

    (1) losing access to freely-distributed software
        that's in Packit II format

    (2) uploading Packit-II files to a Unix box just
        for the purpose of running unpit on them (unpit
        is great if the files are already on the Unix
        box, but what does one do with files that come
        from, say, GENIE?)

    (3) forking over $10 not because one wants to use
        Packit-II but because one can't put up with (1)
        or (2), and has a sense of ethics that prevents:

    (4) using Packit-II to decode downloaded files without
        paying for it

Translation by Thomas D. Newton (ARPA address: Thomas.Newton@spice.cs.cmu.edu)

Copyright Information:
    By now, this program has a little bit of everything in it.  I
would assume that the Unix version is (C) 1986 Allan Weber, except
for the pieces taken from macput.c and macget.c.  I suspect that
this version doesn't have much of the macget/macput code left (when
on a Mac, it makes sense just to call the filesystem rather than to
write an .INFO file).  On the other hand, it does have some code
taken from BINConvert ((C) 1986 Thomas D. Newton), and some code
taken from SKEL, and some code from standard CS textbooks.  As I am
writing this using LightSpeed C, the executable version will have a 
C) Think notice.  Taking everything into account, this version of
Unpit is

        Copyright (C) 1986 Thomas D. Newton
        This program may be copied and used for noncommercial purposes.
            It may not be sold or offered as inducement to buy a product.
        Parts of this program are derived from code written by various
            authors which itself can be copied and used noncommercially.

Compilation Information:
    This program was compiled using LightSpeed C (tm) on a
    Macintosh.  It uses the "MacTraps" library, and the resources
    can be found in the companion file, 'unpit.proj.rsrc'.

Modification History:
    Version     Date     Who/Comments
    =======    ======    ============
      0.1      Aug 86    Thomas Newton (tdn@spice.cs.cmu.edu)
      			 Created.  Translated Unix 'unpit' to Macintosh;
      			 added SKEL-like user interface shell, Packit-I
      			 packing, delete file, and help commands; hacked
      			 up the structure of the program to gain speed.

      0.2      Aug 86    Thomas Newton (tdn@spice.cs.cmu.edu)
      			 Added code to call Disk Initialization Package
      			 so blank disks don't act "dead" when inserted.

      			 Removed CLOVER-B as an alias for EDIT'CLEAR --
      			 it doesn't seem to work with MockWrite, and it
      			 seems that keyboard events that happen while a
      			 DA window is active are not returned to Unpit,
      			 so Unpit can't "force" the alias to work.
      			 
      			 Fixed a few calls to Err() that didn't include
      			 the second parameter; changed main() to put up
      			 a dialog box rather than beeping if user tries
      			 to Print packed files from the Finder.

      0.3      Sep 86    Thomas Newton (tdn@spice.cs.cmu.edu)
      			 Added the ability to produce compressed packed
      			 files, using Huffman compression (Knuth's "The
      			 Art of Computer Programming", Volume One, Page
      			 402 describes how to build weighted trees with
      			 minimum total weight using Huffman's method).
      			 
      			 Reduced the amount of text in the "About" box,
      			 both to get the size of the executable version
      			 down and because Unpit is now roughly equal to
      			 PackIt-II, rather than to PackIt-1.5 (not that
				 there ever was a Packit-1.5 . . .).

      0.3.1		Dec 86    Reid Ellis (unicus!rae@yetti.uucp)
      			 Added the ability to do "batch" packing by selecting
      			 all the files to be packed from the finder and
      			 holding the option key down whilst booting.
      			 Moved all resources to a '.rsrc' file (I use
      			 ResEdit 1.0 to do resource munging).
-------------------------------------------------------------------------------

Format of a Packit file:

Repeat the following sequence for each file in the Packit file:

	4 byte identifier ("PMag" = not compressed, "Pma4" = compressed)
	variable length compression data (if compressed file)
	92 byte header (see struct pit_header below) *
	2 bytes CRC number *
	data fork (length from header) *
	resource fork (length from header) *
	2 bytes CRC number *

Last file is followed by the 4 byte Ascii string, "Pend", and then the EOF.

* these are in compressed form if compression is on for the file

*/

#include <DialogMgr.h>
#include <EventMgr.h>
#include <FileMgr.h>
#include <MacTypes.h>
#include <MemoryMgr.h>
#include <MenuMgr.h>
#include <pascal.h>
#include <Quickdraw.h>
#include <SegmentLdr.h>
#include <StdFilePkg.h>
#include <WindowMgr.h>

typedef char byte;
typedef int  word;

struct pit_header {	/* Packit file header (92 bytes)
	byte nlen;	/* number of characters in packed file name */
	byte name[63];	/* name of packed file */
	byte type[4];	/* file type */
	byte auth[4];	/* file creator */
	word flags;	/* Finder flags */
	word lock;	/* low-order bit seems to be lock; others are ??? */
	long dlen;	/* number of bytes in data fork */
	long rlen;	/* number of bytes in resource fork */
	long ctim;	/* file creation time */
	long mtim;	/* file modified time */
};

#define HDRBYTES  92

#define BYTEMASK 0xff

#define H_NAMELEN 63

#define H_NLENOFF 0
#define H_NAMEOFF 1
#define H_TYPEOFF 64
#define H_AUTHOFF 68
#define H_FLAGOFF 72
#define H_LOCKOFF 74
#define H_DLENOFF 76
#define H_RLENOFF 80
#define H_CTIMOFF 84
#define H_MTIMOFF 88

#define INITED 0x0100
#define FLOCK  0x01

/* Screen locations of SFGetFile and SFPutFile boxes */
#define GET_FILE_X  82
#define GET_FILE_Y  92
#define PUT_FILE_X 104
#define PUT_FILE_Y  92

/* Screen location of disk initialization dialog */
#define INIT_X     112
#define INIT_Y      80


typedef struct nod {
	int flag, byte, index2;
	long count;
	struct nod *one, *zero;
} node, *nodeptr;

node    nodelist[512];			/* 512 should be big enough */
nodeptr heap[513], freenode;

struct {
	long bits;
	int bcount;
} byte_code[256];

unsigned char hdr[HDRBYTES];

typedef int crctype;

long datalen, rsrclen;
int decode, bit;

Boolean Filter;		/* if TRUE, Unpack... shows only PIT and TEXT files */
Boolean Compress;       /* if TRUE, Pack...   uses Huffman compression      */
Boolean optkeyDown;

/* forward declarations */
nodeptr		read_tree();
long		get4();
crctype		read_hdr();
crctype		write_fork();
crctype		getcrc();
Boolean		pack_files();

/*
 * Error codes that can be used as the second parameter to Err (a function
 * declared below).  They let Err() know roughly what the program was doing
 * at the time that an error occurred so that it can display somewhat more
 * informative error messages.
 */
 
enum {
    errCreateFile,	/* creating output file */
    errOpenDataFk,	/* opening data fork for write */
    errOpenRsrcFk,	/* opening resource fork for write */
    errGetFInfo,	/* getting information for unpacked file */
    errSetFInfo,	/* setting information for unpacked file */
    errWriting,		/* writing output file */
    errReading,		/* reading input file */
    errLock,		/* locking unpacked file */
    errDelete		/* deleting file */
    };
    
/*
Report an error to the user.  This function is used to process the return
codes received from FSOpen and the like.
############################       Err     ##############################
*/
Boolean Err(theErr, activity)
OSErr theErr;
int activity;
{   char *errText, *errWhy;

    if (theErr == noErr)
        return FALSE;
    else {
        switch (activity) {
            case errCreateFile:
            	errWhy = "\Pcreating output file"; break;
            case errOpenDataFk:
            	errWhy = "\Popening data fork"; break;
            case errOpenRsrcFk:
            	errWhy = "\Popening resource fork"; break;
            case errGetFInfo:
            	errWhy = "\Pgetting Finder information"; break;
            case errSetFInfo:
            	errWhy = "\Psetting Finder information"; break;
            case errWriting:
            	errWhy = "\Pwriting to output file"; break;
            case errReading:
                errWhy = "\Preading from Packit file"; break;
            case errLock:
                errWhy = "\Plocking unpacked file"; break;
            case errDelete:
                errWhy = "\Ptrying to delete file"; break;
            default:
                errWhy = "\P<doing random activity>"; break;
            }
            
        switch (theErr) {
	    case bdNamErr:	errText = "\PBad file name"; break;
            case dupFNErr:	errText = "\PDuplicate file name"; break;
	    case dirFulErr:	errText = "\PDirectory full"; break;
	    case extFSErr:	errText = "\PExternal file system"; break;
	    case ioErr:		errText = "\PDisk I/O error"; break;
	    case nsvErr:	errText = "\PNo such volume"; break;
	    case vLckdErr:	errText = "\PSoftware volume lock"; break;
	    case wPrErr:	errText = "\PHardware volume lock"; break;
	    case mFulErr:	errText = "\PMemory full"; break;
	    case tmfoErr:	errText = "\PToo many files open"; break;
	    case dskFulErr:	errText = "\PDisk full"; break;
	    case fLckdErr:	errText = "\PFile locked"; break;
	    case fnOpnErr:	errText = "\PFile not open"; break;
	    case opWrErr:	errText = "\PFile already open for writing"; break;
	    case wrPermErr:	errText = "\PPermission doesn't allow writing"; break;
            default:            errText = "\P<unanticipated error>"; break;
	    }
	    
#define alertboxid 258
	ParamText(errWhy,errText,0L,0L);
	StopAlert(alertboxid, 0L);
        return TRUE;
        }
}

/*
 * Error codes that can be used as parameters to Err2 (below)
 */
 
enum {
    errHeaderCRC,	/* file header CRC mismatch */
    errFileCRC,		/* file data/rsrc CRC mismatch */
    errNotPackit,	/* unrecognized PACKIT format */
    errBadPrint,        /* attempt to Print files from Finder */
    errCompress         /* internal error: out of room for compression */
    }

/*
Report an error to the user.  This function is used for error messages
that aren't directly caused by I/O errors
############################      Err2     ##############################
*/

Err2(theErr)
int theErr;
{
    switch (theErr) {
        case errHeaderCRC:
            ParamText("\PError: file header CRC mismatch",0L,0L,0L);
            break;
        case errFileCRC:
    	    ParamText("\PError: file data/resource CRC mismatch",0L,0L,0L);
    	    break;
    	case errNotPackit:
    	    ParamText("\PThis is not a Packit-I or Packit-II file.",0L,0L,0L);
    	    break;
    	case errBadPrint:
    	    ParamText("\PPrinting packed files is not supported.",0L,0L,0L);
    	    break;
    	case errCompress:
    	    ParamText("\POut of bits for character codes.",0L,0L,0L);
    	    break;
    }
    StopAlert(alertboxid+1,0L);
}

/*
Open a file's resource fork
##############################   Open_Rsrc   ##############################
*/
Open_Rsrc(fName, vRefNum, perm, ref_num)
StringPtr fName;
int       vRefNum, perm;
int       *ref_num;
{   ParamBlockRec ParamB;
    int ret_val;

    ParamB.ioParam.ioCompletion = 0L;
    ParamB.ioParam.ioNamePtr = fName;
    ParamB.ioParam.ioVRefNum = vRefNum;
    ParamB.ioParam.ioVersNum = 0;
    ParamB.ioParam.ioPermssn = perm;
    ParamB.ioParam.ioMisc = 0L;
    ret_val = PBOpenRF(&ParamB,0);
    *ref_num = ParamB.ioParam.ioRefNum;
    return ret_val;
}

/*
Compare two strings that are four bytes long.  This allows us to toss out
the Strings library, since Unpit was pulling it in just for strncmp . . .
##############################   Str_Cmp_4   ##############################
*/
Boolean str_cmp_4(str1, str2)
char *str1, *str2;
{   int i;
    for (i = 0; i < 4; i++)
        if (str1[i] != str2[i]) return FALSE;
    return TRUE;
}

/*
Read a byte from the file denoted by pit_ref_num, using buffered reads.
Note: this routine is bypassed for speed when unpacking Packit-I files.
##############################   Read_Byte   ##############################
*/
#define BSIZE 4096
int pit_ref_num;			/* Mac filesystem reference number */
long pit_bytes_left;			/* # of bytes to be read from disk */
unsigned char pit_buffer[BSIZE];	/* Buffer for bytes read from disk */
int pit_index, pit_max_index;		/* For tracking the buffer's state */

#define read_byte(ARG1) \
	((pit_index < pit_max_index) ? pit_buffer[pit_index++] : do_read(ARG1))

do_read(eflag)
Boolean *eflag;
{   long Count;
    unsigned char Ch;

    if (pit_index < pit_max_index)
        return pit_buffer[pit_index++];
    else
        if (pit_bytes_left == 0L) {
            Err(ioErr,errReading);
            *eflag = TRUE;
            return 0;
            }
        else {
	    Count = (pit_bytes_left < BSIZE) ? pit_bytes_left : BSIZE;
	    pit_index = 0; pit_max_index = (int) Count; pit_bytes_left -= Count;
	    if (Err(FSRead(pit_ref_num, &Count, &pit_buffer), errReading)) {
	        *eflag = TRUE;
	        return 0;
		}
	    else
	        return pit_buffer[pit_index++];
	}
}

/*
Update the value of CRC to include the bytes in a random chunk of memory.
###############################   Upd_Crc   ###############################
*/
crctype upd_crc(crc, theBytes, byteCount)
register crctype crc;
unsigned char   *theBytes;
long             byteCount;
{	register int  i;
	register long n;
	
	for (n = 0; n < byteCount; n++) {
		crc = crc ^ ((int)theBytes[n] << 8);
		for (i = 0; i < 8; i++)
			if (crc & 0x8000)
				crc = (crc << 1) ^ 0x1021;
			else
				crc <<= 1;
	}
	return(crc & 0xffff);
}

/*
Put up a dialog box that allows the user to select a file to unpack.
################################   UnPack   ###############################
*/
unpack()
{   SFReply PitRecord;
    SFTypeList PitTypes;
    Point where;
    ParamBlockRec ParamB;
    
    where.h = GET_FILE_X; where.v = GET_FILE_Y;
    PitTypes[0] = 'PIT '; PitTypes[1] = 'TEXT';
    SFGetFile(where, "", 0L, Filter ? 2 : -1, PitTypes, 0L, &PitRecord);
    if (PitRecord.good) {
        ParamB.fileParam.ioCompletion = 0L;
        ParamB.fileParam.ioNamePtr = PitRecord.fName;
        ParamB.fileParam.ioVRefNum = PitRecord.vRefNum;
        ParamB.fileParam.ioFVersNum = 0;
        ParamB.fileParam.ioFDirIndex = 0;	/* use NamePtr/VRefNum */
        PBGetFInfo(&ParamB,0);
        pit_bytes_left = ParamB.fileParam.ioFlLgLen;
        if (pit_bytes_left < 4L)
            Err2(errNotPackit);   /* more meaningful than "I/O Error..." */
        else {
            pit_index = 0; pit_max_index = -1;
            FSOpen(PitRecord.fName,PitRecord.vRefNum,&pit_ref_num);
            unpit();
            FSClose(pit_ref_num);
        }
    }
}

/*
Put up a dialog box that allows the user to delete a file.
################################   Delete   ###############################
*/
#define deleteconfirm 260
delete()
{   SFReply DelRecord;
    Point where;

    where.h = GET_FILE_X; where.v = GET_FILE_Y;
    SFGetFile(where, "", 0L, -1, 0L, 0L, &DelRecord);
    if (DelRecord.good) {
        ParamText(DelRecord.fName, 0L, 0L, 0L);
        if (CautionAlert(deleteconfirm, 0L) == 1)	/* the OK button */
            Err(FSDelete(DelRecord.fName, DelRecord.vRefNum),errDelete);
    }
}


/*
Unpack a Packit-I or Packit-II files into its component files.
################################   UnPit   #################################

    This routine assumes that the input file has already been opened and
    that the input file can be read one byte at a time using read_byte().
    Errors that occur during the attempted unpacking will (hopefully) be
    reported to the user within UnPit or functions it calls; in any case,
    the caller should close the input file when UnPit returns.

*/
#define statusid 263
unpit()
{   char temp[4];		/* used when searching for Packit identifier */
    SFReply OutRecord;		/* names and volume numbers of output files  */
    Point where;		/* where to locate the SFPutFile dialog box  */
    Boolean saveOutput;		/* to allow extracting pieces of a .PIT file */
    ParamBlockRec ParamB;	/* needed to make low-level filesystem calls */
    int out_ref_num, i;
    crctype data_crc, crc;
    Boolean eflag = FALSE;
    DialogPtr theDialog = 0L;

    while(1) {
        for (i = 0; i < 4; i++) {		/* PACKIT signature */
            temp[i] = read_byte(&eflag);
            if (eflag) return;
            }
	if (str_cmp_4(temp, "PMag") || str_cmp_4(temp, "PMa4")) {
	    if (temp[3] == '4') {
		freenode = nodelist;
		read_tree(&eflag); if (eflag) return;
		decode = 1;
		}
	    else
	        decode = 0;
	    data_crc = read_hdr(&eflag); if (eflag) return;
	    crc = getcrc(&eflag); if (eflag) return;
	    if (crc != data_crc) {
                Err2(errHeaderCRC);
	        return;
	    }
	    
	    /* Get name of output file */
	    where.h = PUT_FILE_X; where.v = PUT_FILE_Y;
	    SFPutFile(where, "\PSave as:", &hdr[H_NLENOFF], 0L, &OutRecord);
	    if (OutRecord.good) {
	        if ((i = Create(OutRecord.fName,OutRecord.vRefNum,'????','????'))
	            == dupFNErr) { /* user said it was OK to replace...delete! */
	            FSDelete(OutRecord.fName, OutRecord.vRefNum);
	            i = Create(OutRecord.fName,OutRecord.vRefNum,'????','????');
	        }
	        if (Err(i,errCreateFile)) return;
	        saveOutput = TRUE;
	        if (Err(FSOpen(OutRecord.fName,OutRecord.vRefNum,&out_ref_num),
			errOpenDataFk)) return;
	        }
	    else {
	        saveOutput = FALSE;
	        out_ref_num = 0;
	    }
	    
	    /* Give visual indication that file is being unpacked */
	    theDialog = GetNewDialog(statusid, 0L, -1L);
	    ParamText(0L,0L,saveOutput ? "\PUnpack":"\PSkipp",OutRecord.fName);
	    DrawDialog(theDialog);

	    /* First, take care of writing the file's data fork */
	    data_crc = write_fork(saveOutput, out_ref_num, datalen,
	    			  (crctype) 0, &eflag);
	    if (saveOutput) FSClose(out_ref_num);
	    if (eflag) goto error;
	    
	    /* Next, take care of writing the file's resource fork. */
	    if (saveOutput && (rsrclen > 0)) {
	        if (Err(Open_Rsrc(OutRecord.fName,OutRecord.vRefNum,fsWrPerm,
	                &out_ref_num), errOpenRsrcFk)) goto error;
	        }
	    else
	        out_ref_num = 0;
	    data_crc = write_fork(saveOutput, out_ref_num, rsrclen,
	    			  data_crc, &eflag);
	    if (saveOutput) FSClose(out_ref_num);
	    if (eflag) goto error;

	    /* Check the CRC to make sure the file was unpacked intact */
	    crc = getcrc(&eflag);
	    if (eflag || (crc != data_crc)) {
		Err2(errFileCRC);
		if (saveOutput) FSDelete(OutRecord.fName, OutRecord.vRefNum);
		goto error;
	    }

	    /* Finally, set the filesystem and Finder info for the file */
	    if (saveOutput) {
		ParamB.fileParam.ioCompletion = 0L;
		ParamB.fileParam.ioNamePtr = OutRecord.fName;
		ParamB.fileParam.ioVRefNum = OutRecord.vRefNum;
		ParamB.fileParam.ioFVersNum = 0;
		ParamB.fileParam.ioFDirIndex = 0;    /* use NamePtr/VRefNum */
		if (Err(PBGetFInfo(&ParamB,0),errGetFInfo)) goto error;

		ParamB.fileParam.ioFlFndrInfo.fdType = get4(&hdr[H_TYPEOFF]);
		ParamB.fileParam.ioFlFndrInfo.fdCreator = get4(&hdr[H_AUTHOFF]);
		ParamB.fileParam.ioFlFndrInfo.fdFlags =
			(hdr[H_FLAGOFF] << 8) | hdr[H_FLAGOFF+1];
		ParamB.fileParam.ioFlCrDat = get4(&hdr[H_CTIMOFF]);
		ParamB.fileParam.ioFlMdDat = get4(&hdr[H_MTIMOFF]);

		/* turn INITed flag off since Finder hasn't seen file yet */
		ParamB.fileParam.ioFlFndrInfo.fdFlags &= (0xFFFF ^ INITED);
		if (Err(PBSetFInfo(&ParamB,0),errSetFInfo)) goto error;

		/* lock file if Packit header says to do so */
		if (hdr[H_LOCKOFF+1] & 1)    /* don't look at other bits */
		    if (Err(SetFLock(OutRecord.fName,OutRecord.vRefNum),errLock))
		        goto error;

		/* finally, flush volume to make sure that data is safe */
		FlushVol(0L,OutRecord.vRefNum);
--- end of part 1 ---

macintosh@felix.UUCP (02/13/87)

[Unpit version 0.3.1 Source - part 2 of 3]

---
	    }
	    DisposDialog(theDialog); theDialog = 0L;
	    decode = 0;
	    bit = 0;	/* flush unused bits */
	    }
	else if (str_cmp_4(temp, "PEnd"))
	    break;
	else {
	    Err2(errNotPackit);
	    return;
	    }
    }
error:				/* should never be reached except by "goto" */
    if (theDialog != 0L)
        DisposDialog(theDialog);
    return;
}

/*
Read compression decoding data.
##############################   Read_Tree   ##############################

    This routine recursively reads the compression decoding data.
    It appears to be Huffman compression.
    
*/

nodeptr read_tree(eflag)
Boolean *eflag;
{	int bit;

	nodeptr np;
	np = freenode++;
	bit = getbit(eflag); if (*eflag) return (0L);
	if (bit == 1) {
		np->flag = 1;
		np->byte = getbyte(eflag); if (*eflag) return (0L);
	}
	else {
		np->flag = 0;
		np->zero = read_tree(eflag); if (*eflag) return (0L);
		np->one  = read_tree(eflag); if (*eflag) return (0L);
	}
	return(np);
}


/*
Read header containing information about the packed file to follow.
###############################   Read_Hdr   ##############################
*/

crctype read_hdr(eflag)
Boolean *eflag;
{
	register int n;

	for (n = 0; n < HDRBYTES; n++) {
		hdr[n] = getbyte(eflag);
		if (*eflag) return;
	}
	datalen = get4(hdr + H_DLENOFF);
	rsrclen = get4(hdr + H_RLENOFF);
	return(upd_crc(0, hdr, (long) HDRBYTES));
}


/*
Write one fork of an unpacked file.
##############################   Write_Fork   #############################

    saveOutput indicates whether or not the output should be saved; to skip
        a file it is still necessary to read it from the .PIT file in order
        to advance to the start of the next file that can be unpacked.

*/

crctype write_fork(saveOutput, out_ref_num, bytes, crc, eflag)
Boolean saveOutput, *eflag;
int out_ref_num;
long bytes;
register crctype crc;
{
	register int b, i;
	long Count;
	static char out_buffer[BSIZE];
	int out_index = 0;
	
	if ((decode == 0) && (bit == 0)) {
	    /* Special-case the unpacking of Packit-I files, as unpacking */
	    /* them using more general-purpose code takes >50% longer (33 */
	    /* vs 19 seconds when unpacking ResEdit on a RAMDisk).  While */
	    /* this code isn't very pretty, it gets the job done. . .     */

	    if ((bytes > 0) && ((Count = pit_max_index-pit_index) > 0L)) {
	        /* we won't be using read_byte(), so empty its buffer */
	        if (bytes < Count) Count = bytes;
	        if (saveOutput && Err(FSWrite(out_ref_num, &Count,
	            &pit_buffer[pit_index]),errWriting)) {
	            *eflag = TRUE; return 0;
	        }
	        crc = upd_crc(crc, &pit_buffer[pit_index], Count);
	        bytes -= Count; pit_index += (int) Count;
	    }

	    while (bytes > 0L) {
	        Count = (bytes >= BSIZE) ? BSIZE : bytes;
	        if (Err(FSRead (pit_ref_num,&Count,out_buffer),errReading) ||
	            (saveOutput && Err( /* this isn't the most elegant code */
		        FSWrite(out_ref_num,&Count,out_buffer),errWriting))) {
	            *eflag = TRUE;
	            return 0;
	        }
	        crc = upd_crc(crc, out_buffer, Count);
	        bytes -= Count; pit_bytes_left -= Count;
	    }
	} else {
	    while (bytes-- > 0) {
		b = getbyte(eflag); if (*eflag) return;
		crc = crc ^ (b << 8);
		for (i = 0; i < 8; i++)
			if (crc & 0x8000)
				crc = (crc << 1) ^ 0x1021;
			else
				crc <<= 1;
		if (saveOutput) {
		    if (out_index == BSIZE) {
			Count = (long) out_index;
			if (Err(FSWrite(out_ref_num, &Count, &out_buffer),
				errWriting)) {
			    *eflag = TRUE;
			    return 0;
			}
			out_index = 0;
    		    }
		    out_buffer[out_index++] = (char) b;
		}
	    }
	    if (saveOutput && (out_index > 0)) {
	        Count = (long) out_index;
	        if (Err(FSWrite(out_ref_num, &Count, &out_buffer),errWriting)) {
	            *eflag = TRUE;
	            return 0;
	        }
	    }
	}
	return(crc & 0xffff);
}

/*
Convert four input characters into a long.
#################################   Get4   #################################
*/
long
get4(bp)
char *bp;
{
	register int i;
	long value = 0;

	for (i = 0; i < 4; i++) {
		value <<= 8;
		value |= (*bp & BYTEMASK);
		bp++;
	}
	return(value);
}

/*
Read and return a two-byte CRC from the input file.
################################   GetCrc   ################################
*/
crctype getcrc(eflag)
Boolean *eflag;
{
	int value1, value2;
	
	value1 = getbyte(eflag) & BYTEMASK; if (*eflag) return 0;
	value2 = getbyte(eflag) & BYTEMASK; if (*eflag) return 0;
	return((value1 << 8) | value2);
}

/*
Copy n characters from p2 to p1.
#################################   Copy   #################################
*/
copy(p1, p2, n)
char *p1, *p2;
int n;
{
	while (n-- > 0)
		*p1++ = *p2++;
}


/*
Return the next bit in the input stream (MSB first).
################################   GetBit   ################################
*/
static char b;
getbit(eflag)
Boolean *eflag;
{
	if (bit == 0) {
		b = read_byte(eflag) & 0xff; if (*eflag) return 0;
		bit = 8;
	}
	bit--;
	return((b >> bit) & 1);
}

/*
Get the next virtual byte from the input file.
###############################   GetByte   ################################

    This routine returns the next 8 bits.  If decoding is on, it finds the
    byte in the decoding tree based on the bits from the input stream.  If
    decoding is not on, it either gets it directly from the input stream or
    puts it together from 8 calls to getbit(), depending upon whether or not
    we are currently on a byte boundary.  (Note: the calls to getbit() have
    been expanded inline in order to gain some speed . . . ((b >> bit) & 1)
    is used where the value of getbit(eflag) was used before, and it's
    preceded by the statements "if (bit == 0 {...}" and "bit--").
    
*/
getbyte(eflag)
Boolean *eflag;
{
	register nodeptr np;
	register int i, byt;
	
	if (decode) {
		np = nodelist;
		while (np->flag == 0) {
			if (bit == 0) {
				b = read_byte(eflag) & 0xff;
				if (*eflag) return 0;
				bit = 8;
			}
			bit--;
			np = ((int) ((b >> bit) & 1)) ? np->one : np->zero;
		}
		byt = np->byte;
	}
	else {
		if (bit == 0) {	/* on byte boundary? */
			byt = read_byte(eflag) & 0xff; if (*eflag) return 0;
			}
		else {		/* no, put a byte together */
			byt = 0;
			for (i = 8; i > 0; i--) {
				if (bit == 0) {
					b = read_byte(eflag) & 0xff;
					if (*eflag) return 0;
					bit = 8;
				}
				bit--;
				byt = (byt << 1) + (int) ((b >> bit) & 1);
			}
		}
	}
	return(byt);
}

/*
Create a Packit-I or -II format file containing files selected by the user.
#################################   Pack   ################################
*/
pack()
	{
	SFReply PitRecord;
    Point   where;
    int     pit_ref_num, i;
    Boolean Success;
    char   *msg;

    /* Get name of output file */
    where.h = PUT_FILE_X; where.v = PUT_FILE_Y;
    msg = Compress ? "\PSave Packit-II file as:" : "\PSave Packit-I file as:";
    SFPutFile(where,msg,"\PPackit.pit",0L,&PitRecord);
    if (! PitRecord.good) return;

    /* Create and open output file */
    if ((i=Create(PitRecord.fName,PitRecord.vRefNum,'UPIT','PIT '))==dupFNErr) {
        FSDelete(PitRecord.fName,PitRecord.vRefNum);
        i = Create(PitRecord.fName, PitRecord.vRefNum, 'UPIT', 'PIT ');
    }
    if (Err(i,errCreateFile)) return;
    if (Err(FSOpen(PitRecord.fName,PitRecord.vRefNum,&pit_ref_num),
            errOpenDataFk)) return;

     /* Call routine that does real work */
     Success = pack_files(pit_ref_num);
     FSClose(pit_ref_num);
     if (! Success) FSDelete(PitRecord.fName, PitRecord.vRefNum);
     FlushVol(0L, PitRecord.vRefNum);
}


/*
Pass the indicated file header, data fork, resource fork, and computed CRCs
through the supplied function "MyWrite".  This function saves some space in
"pack_files", as compressed files need to be scanned twice (once to get the
frequency counts, once to write the Huffman encodings for the bytes).

###########################    Run_Through_File   ##########################
*/
run_through_file(MyWrite,pit_ref_num,fileHeader,InpRecord,data_len,rsrc_len)
int      	(*MyWrite)();
int	        pit_ref_num;
unsigned char  *fileHeader;
long		data_len, rsrc_len;
SFReply        *InpRecord;
{   long	     Count, bytesLeft;
    register crctype crc;
    unsigned char    io_buffer[BSIZE], fileCRC[2];
    int		     inp_ref_num;


    /* Write file header */
    Count = HDRBYTES + 2;
    if (Err((*MyWrite)(pit_ref_num, &Count, fileHeader), errWriting))
        goto error;

    /* Initialize data/resource CRC */
    crc = 0;

    /* Copy file's data fork to Packit file, if it has one */
    if (bytesLeft = data_len) {
        if (Err(FSOpen(InpRecord->fName,InpRecord->vRefNum,&inp_ref_num),
    		          errOpenDataFk)) goto error;
        while (bytesLeft > 0L) {
            Count = (bytesLeft >= BSIZE) ? BSIZE : bytesLeft;
            if (Err(  FSRead  (inp_ref_num,&Count,io_buffer),errReading) ||
	        Err((*MyWrite)(pit_ref_num,&Count,io_buffer),errWriting)) {
	        FSClose(inp_ref_num);
                goto error;
            }
            crc = upd_crc(crc, io_buffer, Count);
            bytesLeft -= Count;
        }
        FSClose(inp_ref_num);
    }

    /* Copy file's resource fork to Packit file, if it has one */
    if (bytesLeft = rsrc_len) {
        if (Err(Open_Rsrc(InpRecord->fName,InpRecord->vRefNum,fsRdPerm,
    		          &inp_ref_num),errOpenRsrcFk)) goto error;
        while (bytesLeft > 0L) {
            Count = (bytesLeft >= BSIZE) ? BSIZE : bytesLeft;
            if (Err(  FSRead  (inp_ref_num,&Count,io_buffer),errReading) ||
	        Err((*MyWrite)(pit_ref_num,&Count,io_buffer),errWriting)) {
	        FSClose(inp_ref_num);
                goto error;
            }
            crc = upd_crc(crc, io_buffer, Count);
            bytesLeft -= Count;
        }
        FSClose(inp_ref_num);
    }

    /* Write file's data/resource CRC */
    fileCRC[0] = (((unsigned int) crc) >> 8) & 0xff;
    fileCRC[1] = (((unsigned int) crc) & 0xff);
    Count = 2;
    if (Err((*MyWrite)(pit_ref_num,&Count,fileCRC),errWriting)) goto error;
    return FALSE;
error:
    return TRUE;
}


/*
Allow FSWrite() to be passed as a parameter to Run_Through_File (above)
###############################   C_FSWrite   ##############################
*/
int C_FSWrite(arg1, arg2, arg3)
int	arg1;
long   *arg2;
char   *arg3;
{
    return FSWrite(arg1, arg2, arg3);
}


/*
Initialize frequency counts to zero.
###############################   InitCount   ##############################
*/
void init_count()
{   int i;

    for (i = 0; i < 256; i++) {
        nodelist[i].flag   = TRUE;
        nodelist[i].byte   = i;
        nodelist[i].index2 = 0;
        nodelist[i].count  = 0L;
        nodelist[i].zero   = 0L;
        nodelist[i].one    = 0L;
        }
}


/*
Build byte frequency counts on a buffer-by-buffer basis.
###############################   FreqCount   ##############################
*/
int freq_count(Dummy, Count, Buffer)
int            Dummy;
long          *Count;
unsigned char *Buffer;
{   long MyCount = *Count;

    while (MyCount--) {
        nodelist[*Buffer].count += 1;
        Buffer++;
    }
    return noErr;
}


/* Macros to simplify using an ordering relationship with a secondary key */
#define GTR(a,b) ((a->count  > b->count) ||\
                 ((a->count == b->count) && (a->index2  > b->index2)))
#define LEQ(a,b) ((a->count  < b->count) ||\
                 ((a->count == b->count) && (a->index2 <= b->index2)))


/*
Insert a new value into the heap in O(log(n)) time.
##############################   HeapInsert   ##############################
*/
void heapinsert(n)	/* standard heap insertion algorithm from a textbook */
int n;			/* inserts heap[n] into heap stored in heap[1...n-1] */
{   int      i, j;
    nodeptr  item;

    j = n;  i = n / 2;  item = heap[n];
    while ((i > 0) && GTR(heap[i], item)) {
        heap[j] = heap[i];
        j = i; i = i / 2;
    }
    heap[j] = item;
}


/*
Turn a tree whose left & right sons are heaps into a heap in O(log(n)) time.
##############################   HeapAdjust   ##############################
*/
void heapadjust(i, n)	/* standard heap adjustment algorithm */
int i, n;
{   int      j;
    nodeptr  item;

    j = 2 * i; item = heap[i];
    while (j <= n) {
        if ((j < n) && GTR(heap[j], heap[j+1])) j++;
        if (LEQ(item, heap[j])) break;
        heap[j / 2] = heap[j];
        j = 2 * j;
    }
    heap[j / 2] = item;
}


/*
Return the heap element with the smallest value and delete it from the heap.
################################   HeapMin   ###############################
*/
nodeptr heapmin(n)
int *n;
{   nodeptr item;

    item = heap[1];
    heap[1] = heap[*n];
    if (*n -= 1) heapadjust(1, *n);
    return item;
}


/*
Build a minimum weighted binary tree using the counts in nodelist[0..255].
###############################   BuildTree   ##############################
*/
nodeptr build_tree()
{   int      i, n, gen;
    nodeptr  lson, rson, nnod, free;
    	 
    n = 0; free = 0L; gen = 0;
    for (i = 256; i < 512; i++) {	/* All nodes that we know don't */
        nodelist[i].zero = free;	/*     contain frequency counts */
        free = &nodelist[i];		/*     go to the free node list */
        }
    for (i = 0; i < 256; i++)
        if (nodelist[i].count) {	/* If a particular byte doesn't */
            heap[++n] = &nodelist[i];	/*     occur at all, it doesn't */
            if (n > 1) heapinsert(n);	/*     get placed into the tree */
    	} else {			/*     since it would just make */
    	    nodelist[i].zero = free;	/*     the header larger . . .  */
    	    free = &nodelist[i];
    	}
    while (n >= 2) {
        lson = heapmin(&n);		/* The standard algorithm which */
        rson = heapmin(&n);		/*     we use to build the tree */
	nnod = free;			/*     is quite elegant...given */
	free = free->zero;		/*     W1, W2, .. Wn one simply */
	nnod->flag   = FALSE;		/*     solves a smaller problem */
	nnod->zero   = lson;            /*     W1 + W2, W3, .. Wn until */
	nnod->one    = rson;		/*     one gets the trivial W1. */
        nnod->count  = lson->count + rson->count;
        nnod->index2 = ++gen;           /* Use a secondary key to place */
        heap[++n]    = nnod;		/*     W1 + W2 subtree so as to */
        if (n > 1) heapinsert(n);	/*     minimize unweighted sum. */
        }
    return heapmin(&n);
}

/*
Write a single bit to the output file.
################################   PutBit   ###############################

    Note that this routine reuses a buffer that was allocated for Unpack.

*/
char OutChar;
int  BitCount;

putbit(bit, file)
int bit, file;
{   long Count;

    OutChar <<= 1;
    if (bit) OutChar |= 1;
    if (++BitCount == 8) {
        pit_buffer[pit_index++] = OutChar;
        BitCount = 0; OutChar = (char) 0;
        if (pit_index == BSIZE) {
            Count = BSIZE;
            pit_index = 0;
            return FSWrite(file, &Count, pit_buffer);
        }
    }
    return noErr;
}


/*
Write a byte to the output file, using eight calls to putbit().
###############################   PutByte   ###############################
*/
putbyte(byt, file)
int byt, file;
{   int retval, i;

    for (i = 7; i >= 0; i--) {
        retval = putbit((byt & (1 << i)) ? 1 : 0, file);
        if (retval != noErr) return retval;
    }
    return noErr;
}

/*
Initialize various status variables before outputting a compressed file.
#############################   Init_Output   #############################
*/
void init_output()
{
    pit_index = 0;
    BitCount  = 0;
    OutChar   = (char) 0;
}

/*
Add needed bit padding and empty buffer after outputting a compressed file.
#############################   Flush_Output   ############################
*/
int flush_output(file)
int file;
{   int  errcode;
    long Count;

    while (BitCount) { if (errcode = putbit(0, file)) return errcode; }
    if  (pit_index)  {
        Count = pit_index;
        return FSWrite(file, &Count, pit_buffer);
    }
    return noErr;
}


/*
Write a copy of the Huffman tree we're using for compression to pit_file.
##############################   Write_Tree   #############################
*/
int write_tree(root, file)
nodeptr   root;
int 	  file;
{   int   errno;
--- end of part 2 ---

macintosh@felix.UUCP (02/13/87)

[Unpit version 0.3.1 Source - part 3 of 3]

---
	if (root->flag) {
		if (errno = putbit    (1,          file))  return errno;
		if (errno = putbyte   (root->byte, file))  return errno;
	} else {
		if (errno = putbit    (0,          file))  return errno;
		if (errno = write_tree(root->zero, file))  return errno;
		if (errno = write_tree(root->one , file))  return errno;
	}
	return noErr;
}

/*
Walk the minimum-total-cost tree to associate bit sequences with each byte.
#############################   Build_Sequences   #########################
*/
Boolean build_sequences(nd, bits, bitcount)
nodeptr nd;
long    bits;
int     bitcount;
{
    if (nd->flag) {
        byte_code[nd->byte].bcount = bitcount;
        byte_code[nd->byte].bits   = bits;
    } else {
        if ((bitcount == 32) || (! build_sequences(nd->zero, bits, bitcount+1))
         ||   (! build_sequences(nd->one , bits | (1 << bitcount), bitcount+1)))
            return FALSE;
    }
    return TRUE;
}


/*
Write the contents of a buffer using precomputed Huffman compression strings.
###############################   PackWrite   ##############################
*/
int pack_write(pit_ref_num, Count, Buffer)
int            pit_ref_num;
long          *Count;
unsigned char *Buffer;
{   long     theBits, MyCount = *Count;
    int      i, e;

    while (MyCount--) {
        theBits = byte_code[*Buffer].bits;
        for (i  = byte_code[*Buffer++].bcount; i; i--) {
            if (e = putbit((int) (theBits & 1), pit_ref_num)) return e;
            theBits = theBits >> 1;
        }
    }
    return noErr;
}


/*
Copy files into the file denoted by pit_ref_num until error or user done.
##############################   Pack_Files   #############################
*/
Boolean pack_files(pit_ref_num)
int pit_ref_num;
{   SFReply          	InpRecord;
    ParamBlockRec    	ParamB;
    Point            	where;
    unsigned char    	fileHeader[HDRBYTES+2];
    long             	Count;
    int					i, j, errno, argCount, msg;
    register crctype	crc;
    DialogPtr			theDialog = 0L;
    nodeptr				root;
    AppFile				argFile;

	if(optkeyDown)
		{
		CountAppFiles(&msg, &argCount);
        for(j=1; j<=argCount; j++)
			{
			GetAppFiles(j, &argFile);
			ParamText(0L, 0L, "\PPack", argFile.fName);
	        theDialog = GetNewDialog(statusid, 0L, -1L);
	        DrawDialog(theDialog);
			ParamB.fileParam.ioCompletion = 0L;
			ParamB.fileParam.ioNamePtr = argFile.fName;
			ParamB.fileParam.ioVRefNum = argFile.vRefNum;
			ParamB.fileParam.ioFVersNum = 0;
			ParamB.fileParam.ioFDirIndex = 0;	/* NamePtr/VRefNum */
			if (Err(PBGetFInfo(&ParamB,0),errGetFInfo))
				goto error;
		
			for (i = 0; i < 64; i++)
				{
				fileHeader[i] = argFile.fName[i];
				InpRecord.fName[i] = argFile.fName[i];
				}
			InpRecord.fType = argFile.fType;
			InpRecord.vRefNum = argFile.vRefNum;
			InpRecord.version = argFile.versNum;
			put4(&fileHeader[H_TYPEOFF], ParamB.fileParam.ioFlFndrInfo.fdType);
			put4(&fileHeader[H_AUTHOFF], ParamB.fileParam.ioFlFndrInfo.fdCreator);
			fileHeader[H_FLAGOFF  ] = (ParamB.fileParam.ioFlFndrInfo.fdFlags >> 8)
						   & 0xff;
			fileHeader[H_FLAGOFF+1] = (ParamB.fileParam.ioFlFndrInfo.fdFlags
						   & 0xff);
			fileHeader[H_LOCKOFF  ] = 0;
			fileHeader[H_LOCKOFF+1] = (ParamB.fileParam.ioFlAttrib & FLOCK) ? 1 : 0;
			put4(&fileHeader[H_DLENOFF], ParamB.fileParam.ioFlLgLen);
			put4(&fileHeader[H_RLENOFF], ParamB.fileParam.ioFlRLgLen);
			put4(&fileHeader[H_CTIMOFF], ParamB.fileParam.ioFlCrDat);
			put4(&fileHeader[H_MTIMOFF], ParamB.fileParam.ioFlMdDat);
		
			crc = upd_crc(0, fileHeader, (long) HDRBYTES);
			fileHeader[HDRBYTES  ] = (crc >> 8) & 0xff;
			fileHeader[HDRBYTES+1] = (crc & 0xff);
			
			if (Compress)
				{
		    	Count = 4L;
			    if (Err(FSWrite(pit_ref_num,&Count,"PMa4"), errWriting)) goto error;
			    init_count();
			    init_output();
			    if (run_through_file(freq_count, pit_ref_num, fileHeader,
			    			 &InpRecord, ParamB.fileParam.ioFlLgLen,
			    			 ParamB.fileParam.ioFlRLgLen))
			    	goto error;
			    root = build_tree();
			    if (Err(write_tree(root, pit_ref_num), errWriting))
			    	goto error;
			    if (! build_sequences(root,0L,0))
			    	{
			    	Err2(errCompress);
			    	goto error;
			    	}
			    if (run_through_file(pack_write, pit_ref_num, fileHeader,
			    			 &InpRecord, ParamB.fileParam.ioFlLgLen,
			    			 ParamB.fileParam.ioFlRLgLen))
			    	goto error;
			    if (Err(flush_output(pit_ref_num), errWriting))
			    	goto error;
				} /* if compress */
			else
				{
		    	Count = 4L;
			    if (Err(FSWrite(pit_ref_num, &Count, "PMag"), errWriting) ||
			        run_through_file(C_FSWrite, pit_ref_num, fileHeader,
			                         &InpRecord, ParamB.fileParam.ioFlLgLen,
			                         ParamB.fileParam.ioFlRLgLen))
					goto error;
				} /* if compress */
			DisposDialog(theDialog);
			theDialog = 0L;
			ClrAppFiles(j);
			} /* for j in argCount */
		Count = 4;
		return (! Err(FSWrite(pit_ref_num, &Count, "PEnd"), errWriting));
		} /* if Args != 0L */
	else
		{
    /* Loop as long as the user is willing to supply files */
		while (TRUE)
			{
	        where.h = GET_FILE_X; where.v = GET_FILE_Y;
	        SFGetFile(where, "", 0L, -1, 0L, 0L, &InpRecord);
	        if (! InpRecord.good)
	        	{
	            Count = 4;
	            return (! Err(FSWrite(pit_ref_num, &Count, "PEnd"), errWriting));
				}
			ParamText(0L, 0L, "\PPack", InpRecord.fName);
	        theDialog = GetNewDialog(statusid, 0L, -1L);
	        DrawDialog(theDialog);
	        
			ParamB.fileParam.ioCompletion = 0L;
			ParamB.fileParam.ioNamePtr = InpRecord.fName;
			ParamB.fileParam.ioVRefNum = InpRecord.vRefNum;
			ParamB.fileParam.ioFVersNum = 0;
			ParamB.fileParam.ioFDirIndex = 0;
			if (Err(PBGetFInfo(&ParamB,0),errGetFInfo)) goto error;
		
			for (i = 0; i < 64; i++) fileHeader[i] = InpRecord.fName[i];
			put4(&fileHeader[H_TYPEOFF], ParamB.fileParam.ioFlFndrInfo.fdType);
			put4(&fileHeader[H_AUTHOFF], ParamB.fileParam.ioFlFndrInfo.fdCreator);
			fileHeader[H_FLAGOFF  ] = (ParamB.fileParam.ioFlFndrInfo.fdFlags >> 8)
						   & 0xff;
			fileHeader[H_FLAGOFF+1] = (ParamB.fileParam.ioFlFndrInfo.fdFlags
						   & 0xff);
			fileHeader[H_LOCKOFF  ] = 0;
			fileHeader[H_LOCKOFF+1] = (ParamB.fileParam.ioFlAttrib & FLOCK) ? 1 : 0;
			put4(&fileHeader[H_DLENOFF], ParamB.fileParam.ioFlLgLen);
			put4(&fileHeader[H_RLENOFF], ParamB.fileParam.ioFlRLgLen);
			put4(&fileHeader[H_CTIMOFF], ParamB.fileParam.ioFlCrDat);
			put4(&fileHeader[H_MTIMOFF], ParamB.fileParam.ioFlMdDat);
		
			crc = upd_crc(0, fileHeader, (long) HDRBYTES);
			fileHeader[HDRBYTES  ] = (crc >> 8) & 0xff;
			fileHeader[HDRBYTES+1] = (crc & 0xff);
			
			if (Compress)
				{
		    	Count = 4L;
			    if (Err(FSWrite(pit_ref_num,&Count,"PMa4"), errWriting))
			    	goto error;
			    init_count();
			    init_output();
			    if (run_through_file(freq_count, pit_ref_num, fileHeader,
			    			 &InpRecord, ParamB.fileParam.ioFlLgLen,
			    			 ParamB.fileParam.ioFlRLgLen))
			    	goto error;
			    root = build_tree();
			    if (Err(write_tree(root, pit_ref_num), errWriting))
			    	goto error;
			    if (! build_sequences(root,0L,0))
			    	{
			    	Err2(errCompress);
			    	goto error;
			    	}
			    if (run_through_file(pack_write, pit_ref_num, fileHeader,
			    			 &InpRecord, ParamB.fileParam.ioFlLgLen,
			    			 ParamB.fileParam.ioFlRLgLen))
			    	goto error;
			    if (Err(flush_output(pit_ref_num), errWriting))
			    	goto error;
				}
			else
				{
		    	    Count = 4L;
			    if (Err(FSWrite(pit_ref_num, &Count, "PMag"), errWriting) ||
			        run_through_file(C_FSWrite, pit_ref_num, fileHeader,
			                         &InpRecord, ParamB.fileParam.ioFlLgLen,
			                         ParamB.fileParam.ioFlRLgLen))
			    	goto error;
				}
			    
			/* Remove status dialog from screen */
			DisposDialog(theDialog); theDialog = 0L;
			} /* while */
		} /* if optkeyDown */
error:				/* should not be reached except by "goto" */
    if (theDialog != 0L)
        DisposDialog(theDialog);
    return FALSE;
	}

/*
Turn a long value into four characters.
#################################   Put4   ################################
*/
put4(str, data)
unsigned char *str;
long  data;
{   int i;

    for (i = 3; i >= 0; i--) {
        str[i] = data & BYTEMASK;
        data >>= 8;
    }
}


/***************************************************************************/
/*       Scaffolding to support the Mac user interface, DAs, etc.          */
/***************************************************************************/

#define charcodemask 255

#define lastmenu 3	/* number of menus */
#define applemenu 1	/* menu ID for desk accessory menu */
#define filemenu 2	/* menu ID for File menu */
#define editmenu 3	/* menu ID for Edit menu */

#define iunpack 1	/* items in the File menu */
#define ifilter 2
 /*-------*/
#define idelete 4
 /*-------*/
#define ipack   6
#define icompress 7
 /*-------*/
#define ihelp   9
 /*-------*/
#define iquit  11

MenuHandle	mymenus[lastmenu+1];
EventRecord	myevent;
WindowPtr	whichwindow;
int		windowcode;
Boolean		userdone;
#define maxStackSize 8192

setup()
{   int i;

    /* Do various magical things to set up memory (this is all from SKEL) */
    typedef long *lomemptr;	/* a pointer to low memory locations */
    lomemptr nilptr;		/* will have value NIL */
    lomemptr stackbaseptr;	/* points to current stack base */
    EventRecord anEvent;

    nilptr = 0L; *nilptr = (long)'Blee';/* for ID=02 bomb on dereferencing 0 */
    stackbaseptr = (lomemptr) 0x908;	/* CurStackBase */
    SetApplLimit ((Ptr) (*stackbaseptr - maxStackSize));
    MaxApplZone();
    MoreMasters(); MoreMasters(); MoreMasters();
    
    InitGraf(&thePort);
    InitFonts();
    FlushEvents(everyEvent, 0);
    InitWindows();
    InitMenus();
    TEInit();
    InitDialogs(0L);
    InitCursor();
    SetEventMask(everyEvent - keyUpMask);

    /* Check to see if the user is holding down the option key for a   */
    /* mass packing						       */

    GetNextEvent(everyEvent, &anEvent);
    if(anEvent.modifiers & optionKey)
    	optkeyDown = TRUE;
    else
    	optkeyDown = FALSE;

    /* I can think of no reason why calling GetMenu() in a loop should */
    /* have different results than unrolling the loop, but if MENU_BUG */
    /* is defined, Unpit will bomb (or drop into Macsbug) when run.  I */
    /* suspect that the bombs are a result of a bug in LightSpeed C... */
    
    /* Update: October 1, 1986.  As suggested by Steve Stein of THINK, */
    /* the problem is caused by SetEventMask in the LSC 1.0.2 MacTraps */
    /* library.  The fix is to search for hexadecimal 225f21df01444ed1 */
    /* using FEdit/equivalent and change the third byte from 21 to 31. */

#ifdef MENU_BUG
    for (i = applemenu; i <= editmenu; i++)
        mymenus[i] = GetMenu(i);
#else
    mymenus[applemenu] = GetMenu(applemenu);
    mymenus[filemenu]  = GetMenu(filemenu);
    mymenus[editmenu]  = GetMenu(editmenu);
#endif

    AddResMenu(mymenus[applemenu],'DRVR');
    Filter = TRUE;
    CheckItem(mymenus[filemenu],ifilter,/* Filter ? */ 255 /* :0 */);
    Compress = TRUE;
    CheckItem(mymenus[filemenu],icompress,/* Compress ? */ 255 /* :0 */);

    for (i = applemenu; i <= editmenu; i++)
        InsertMenu(mymenus[i],0);
    DrawMenuBar();
}

/*
Handle a command given through a menu selection
############################   DoCommand   ##############################

   We carry out the command indicated by mResult.
   If it was Quit, we return true, else false.  Since the menu was
   highlighted by MenuSelect, we must finish by unhighlighting it
   to indicate we're done.
*/
Boolean docommand (mresult)
long    mresult;
{
    int     refnum;
    int     themenu,
            theitem;
    char    name[255];
    GrafPtr saveport;		/* for saving current port in when opening
				   a desk accessory */
    Boolean returns;
	
	
#define aboutboxid 257
#define aboutraeid 258
#define helponeid  261
#define helptwoid  262
#define okButton   1
#define moreButton 2
    DialogPtr theDialog, moreDialog;
    int itemhit;

    returns = FALSE;		/* assume Quit not selected */
    themenu = HiWord (mresult);	/* get the menu selected */
    theitem = LoWord (mresult);	/* ... and the Item of that menu */
    switch (themenu) {
	case 0: 
	    break;		/* user made no selection; do nothing */

	case applemenu: 
	    if (theitem == 1)	 /* tell about the program */
	    	{
	    	for(itemhit=0; itemhit!=okButton;)
	    		{
				theDialog = GetNewDialog(aboutboxid, 0L, -1L);
				ModalDialog(0L, &itemhit);
				DisposDialog(theDialog);
				if(itemhit == moreButton)
					{
					moreDialog = GetNewDialog(aboutraeid, 0L, -1L);
					ModalDialog(0L, &itemhit);
					DisposDialog(moreDialog);
					}
				} /* for */
			} /* if */
	    else		/* run a desk accessory; make sure port is preserved */
	    	{
			GetPort (&saveport);
			GetItem (mymenus[applemenu], theitem, name);  /* get name */
			refnum = OpenDeskAcc (name);/* run the desk accessory */
			SetPort (saveport);
	        }
	    break;

	case filemenu: 
	    switch (theitem) {
		case iunpack:
		    unpack();
		    break;
		case ifilter:
		    Filter = (Filter ? FALSE : TRUE);
		    CheckItem(mymenus[filemenu],ifilter,(Filter) ? 255 : 0);
		    break;
		case idelete:
		    delete();
		    break;
		case ipack:
		    pack();
		    break;
		case icompress:
		    Compress = (Compress ? FALSE : TRUE);
		    CheckItem(mymenus[filemenu],icompress,(Compress) ? 255 : 0);
		    break;
		case ihelp:    /* tell how to use the program */
		    theDialog = GetNewDialog(helponeid, 0L, -1L);
		    ModalDialog(0L, &itemhit);
		    DisposDialog(theDialog);
		    theDialog = GetNewDialog(helptwoid, 0L, -1L);
		    ModalDialog(0L, &itemhit);
		    DisposDialog(theDialog);
		    break;
		case iquit:
		    returns = TRUE;
		    break;
	    }			/* fileMenu case */
	    break;
		
	case editmenu:
	    SystemEdit(theitem-1);
	    break;
    }				/* menu case */

    HiliteMenu (0);		/* turn off hilighting on the menu just used */
    return (returns);
}				/* DoCommand */



maineventloop () {

/* body of MainEventLoop */

    FlushEvents (everyEvent, 0);	/* discard leftover events */

/* get next event, and Handle it appropriately, until user QUITs */

    userdone = FALSE;
    do {
	SystemTask ();		/* Handle desk accessories */
	if (GetNextEvent (everyEvent, &myevent)) {
				/* get event; if for us... */
	    switch (myevent.what) {/* Handle each kind of event */
		case mouseDown: /* find out what window the mouse went
				   down in, and where in it */
		    windowcode = FindWindow (myevent.where, &whichwindow);
		    switch (windowcode) { /* Handle mouse-down for each place */
			case inSysWindow:
			    /* Handle the desk accessories */
			    SystemClick (&myevent, whichwindow);
			    break;/* inSysWindow */
			case inMenuBar: /* Handle the command */
			    userdone = docommand (MenuSelect (myevent.where));
			    break;/* inMenuBar */
		    }
		    break;	/* switch */

		case keyDown: 
		case autoKey: 	/* if command key, pass the char to MenuKey */
		    if ((myevent.modifiers & cmdKey) != 0)
			userdone = docommand (MenuKey ((char) (myevent.message
							      & charcodemask)));
		    break;      /* switch */
		case diskEvt:
		    if (HiWord(myevent.message) != noErr) {
		        Point where;
		        where.h = INIT_X; where.v = INIT_Y;
		        DIBadMount(where, myevent.message);
		    }
		    break;	/* switch */
		    
	    }
	}

    } while (userdone == FALSE);
}

main()
	{
    Handle Args;
    char OurName[64];
    int OurRefNum, ArgCount, ArgType;
    AppFile *ArgFile;
    ParamBlockRec ParamB;
    Boolean even;
    
    setup();
    DILoad();
    GetAppParms(OurName, &OurRefNum, &Args);
    ArgType  = **((int **) Args);
    ArgCount = *(((int *) (*Args)) + 1);
    if (ArgCount == 0)
        {
        maineventloop();
        }
    else
        {
        if (ArgType != appOpen)
            {
            Err2(errBadPrint);
            }
        else
            {
            if(!optkeyDown)
                {
	            HLock(Args);
	            ArgFile = (AppFile *) (*Args + 4);
	            while (ArgCount-- > 0)
	            	{
	                ParamB.fileParam.ioCompletion = 0L;
	                ParamB.fileParam.ioNamePtr = ArgFile->fName;
	                ParamB.fileParam.ioVRefNum = ArgFile->vRefNum;
	                ParamB.fileParam.ioFVersNum = 0;
	                ParamB.fileParam.ioFDirIndex = 0;	/* NamePtr/VRefNum */
	                PBGetFInfo(&ParamB,0);
	                pit_bytes_left = ParamB.fileParam.ioFlLgLen;
	                if (pit_bytes_left < 4L)
	                	{
	                    /* this is more meaningful than "I/O error", */
	                    /* but we should also print the filename ... */
	                    Err2(errNotPackit);
	                    }
	                else
	                	{
	                    pit_index = 0;
	                    pit_max_index = -1;
	                    FSOpen(ArgFile->fName,ArgFile->vRefNum,&pit_ref_num);
	                    unpit();
	                    FSClose(pit_ref_num);
	                	}
	                even = ((ArgFile->fName[0] >> 1) * 2) == ArgFile->fName[0];
	                ArgFile = (AppFile *) (9 + ArgFile->fName[0] + (even ? 1 : 0)
	                		  	 + (char *) ArgFile);
	            	}
	            HUnlock(Args);
	            }
	        else
	        	{
	        	pack();
	        	}
	    	}
        }
    DIUnload();
	}
--- end of part 3 ---