ftp.nice.ch/pub/next/developer/languages/smalltalk/squeak-2.0-0.3d109.s.tar.gz#/squeak-2.0/src/sq.h

This is sq.h in view mode; [Download] [Up]

#include <math.h>
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <time.h>

#include "sqConfig.h"

#define true 1
#define false 0
#define null 0  /* using 'null' because nil is predefined in Think C */

/*
	PJB:
	
	All these following sections, down to 'interp' included, should actually 
	be put in header files. They may be #included here, if you really want to. 
	But I would insert the #includes where #include "sq.h" stands.
	
	Only the last section 'sq' belong to this header file. It declares the
	interface of the primitive routines that must be ported to each specific
	platforms.
	
	The actual implementation of these routine is found in:
		- sqXWindow.c         for the UNIX systems with X-Window GUI.
		- ../nextstep/sq.m    for NeXTSTEP 3.3 system & GUI.
*/


/* ----sqImageFile---------------------------------------------------------- */
/* image save/restore macros */
/* Note: The image file save and restore code uses these macros; they
   can be redefined in sqPlatformSpecific.h if desired. These default
   versions are defined in terms of the ANSI Standard C libraries.
*/
#define sqImageFile FILE *
#define sqImageFileClose(f)                  fclose(f)
#define sqImageFileOpen(fileName,mode)      fopen(fileName,mode)
#define sqImageFilePosition(f)               ftell(f)
#define sqImageFileRead(ptr,sz,count,f)   fread(ptr,sz,count,f)
#define sqImageFileSeek(f,pos)              fseek(f,pos,SEEK_SET)
#define sqImageFileWrite(ptr,sz,count,f)  fwrite(ptr,sz,count,f)
#define sqAllocateMemory(minHeapSize,desiredHeapSize)   \
			malloc(desiredHeapSize)


/* ----sqFloatFormat-------------------------------------------------------- */
/* platform-dependent float conversion macros */
/* Note: Second argument must be a variable name,not an expression! */
/* Note: Floats in image are always in PowerPC word order; change
   these macros to swap words if necessary. This costs no extra and
   obviates sometimes having to word-swap floats when reading an image.
*/
#if defined(DOUBLE_WORD_ALIGNMENT) || defined(DOUBLE_WORD_ORDER)
# ifdef DOUBLE_WORD_ORDER
/* word-based copy with swapping for non-PowerPC order */
#   define storeFloatAtfrom(i,floatVarName) \
	*((int *) (i) + 0) = *((int *) &(floatVarName) + 1); \
	*((int *) (i) + 1) = *((int *) &(floatVarName) + 0);
#   define fetchFloatAtinto(i,floatVarName) \
	*((int *) &(floatVarName) + 0) = *((int *) (i) + 1); \
	*((int *) &(floatVarName) + 1) = *((int *) (i) + 0);
# else /*!DOUBLE_WORD_ORDER*/
/* word-based copy for machines with alignment restrictions */
#   define storeFloatAtfrom(i,floatVarName) \
	*((int *) (i) + 0) = *((int *) &(floatVarName) + 0); \
	*((int *) (i) + 1) = *((int *) &(floatVarName) + 1);
#   define fetchFloatAtinto(i,floatVarName) \
	*((int *) &(floatVarName) + 0) = *((int *) (i) + 0); \
	*((int *) &(floatVarName) + 1) = *((int *) (i) + 1);
# endif /*!DOUBLE_WORD_ORDER*/
#else /*!(DOUBLE_WORD_ORDER||DOUBLE_WORD_ALIGNMENT)*/
/* for machines that allow doubles to be on any word boundary */
# define storeFloatAtfrom(i,floatVarName) \
	*((double *) (i)) = (floatVarName);
# define fetchFloatAtinto(i,floatVarName) \
	(floatVarName) = *((double *) (i));
#endif


/* ----sqPlatformSpecific--------------------------------------------------- */
/* this include file may redefine earlier definitions and macros: */
#include "sqPlatformSpecific.h"


/* ----sqFilePrims---------------------------------------------------------- */
/* squeak file record; see sqFilePrims.c for details */
/*** increment this version number when the image file format changes ***/
#define CURRENT_VERSION 6502

typedef struct {
	FILE	*file;
	int sessionID;
	int writable;
	int fileSize;
	int lastOp;  /* 0 = uncommitted,1 = read,2 = write */
} SQFile;

/* file i/o */
	extern int sqFileAtEnd(SQFile *f);
	extern int sqFileClose(SQFile *f);
	extern int sqFileDeleteNameSize(int sqFileNameIndex,int sqFileNameSize);
	extern int sqFileGetPosition(SQFile *f);
	extern int sqFileInit(void);
	extern int sqFileOpen(SQFile *f,int sqFileNameIndex,
			int sqFileNameSize,int writeFlag);
	extern int sqFileReadIntoAt(SQFile *f,int count,
			int byteArrayIndex,int startIndex);
	extern int sqFileRenameOldSizeNewSize(int oldNameIndex,
			int oldNameSize,int newNameIndex,int newNameSize);
	extern int sqFileSetPosition(SQFile *f,int position);
	extern int sqFileSize(SQFile *f);
	extern int sqFileValid(SQFile *f);
	extern int sqFileWriteFromAt(SQFile *f,int count,
			int byteArrayIndex,int startIndex);

/* ----sqUnixDirectory------------------------------------------------------ */
/* directories */
	extern int dir_Create(char *pathString,int pathStringLength);
	extern int dir_Delimitor(void);
	extern int dir_Lookup(char *pathString,int pathStringLength,int index,
		/* outputs: */
		char *name,int *nameLength,int *creationDate,int *modificationDate,
		int *isDirectory,int *sizeIfFile);
	extern int dir_PathToWorkingDir(char *pathName,int pathNameMax);
	extern int dir_SetMacFileTypeAndCreator(char *filename,
			int filenameSize,char *fType,char *fCreator);

	extern int convertToSqueakTime(int unixTime);


/* ----sqUnixSound---------------------------------------------------------- */
/* sound output */
	extern int snd_AvailableSpace(void);
	extern int snd_InsertSamplesFromLeadTime(int frameCount,int srcBufPtr,
			int samplesOfLeadTime);
	extern int snd_PlaySamplesFromAtLength(int frameCount,int arrayIndex,
			int startIndex);
	extern int snd_PlaySilence(void);
	extern int snd_Start(int frameCount,int samplesPerSec,int stereo,
			int semaIndex);
	extern int snd_Stop(void);

/* sound input */
	extern int snd_SetRecordLevel(int level);
	extern int snd_StartRecording(int desiredSamplesPerSec,int stereo,
			int semaIndex);
	extern int snd_StopRecording(void);
	extern double snd_GetRecordingSampleRate(void);
	extern int snd_RecordSamplesIntoAtLength(int buf,int startSliceIndex,
			int bufferSizeInBytes);

/* ----sqUnixJoystick------------------------------------------------------- */
/* joystick support */
	extern int joystickInit(void);
	extern int joystickRead(int stickIndex);


/* ----sqOldSoundPrims------------------------------------------------------ */
/* sound generation primitives (old,for backward compatibility) */
	extern int primWaveTableSoundmixSampleCountintostartingAtpan(void);
	extern int primFMSoundmixSampleCountintostartingAtpan(void);
	extern int primPluckedSoundmixSampleCountintostartingAtpan(void);
	extern int primSampledSoundmixSampleCountintostartingAtpan(void);


/* ----sqSoundPrims--------------------------------------------------------- */
/* sound generation primitives */
	extern int primFMSoundmixSampleCountintostartingAtleftVolrightVol(void);
	extern int 
		primPluckedSoundmixSampleCountintostartingAtleftVolrightVol(void);
	extern int primReverbSoundapplyReverbTostartingAtcount(void);
	extern int 
		primSampledSoundmixSampleCountintostartingAtleftVolrightVol(void);

/* ----sqUnixNetwork-------------------------------------------------------- */
/* squeak socket record; see sqMacNetwork.c for details */
typedef struct {
	int sessionID;
	int socketType;  /* 0 = TCP,1 = UDP */
	void	*privateSocketPtr;
}  SQSocket,*SocketPtr;

/* networking primitives */
	extern int sqNetworkInit(int resolverSemaIndex);
	extern void	sqNetworkShutdown(void);
	extern void	sqResolverAbort(void);
	extern void	sqResolverAddrLookupResult(char *nameForAddress,int nameSize);
	extern int sqResolverAddrLookupResultSize(void);
	extern int sqResolverError(void);
	extern int sqResolverLocalAddress(void);
	extern int sqResolverNameLookupResult(void);
	extern void	sqResolverStartAddrLookup(int address);
	extern void	sqResolverStartNameLookup(char *hostName,int nameSize);
	extern int sqResolverStatus(void);
	extern void	sqSocketAbortConnection(SocketPtr s);
	extern void	sqSocketCloseConnection(SocketPtr s);
	extern int sqSocketConnectionStatus(SocketPtr s);
	extern void	sqSocketConnectToPort(SocketPtr s,int addr,int port);
	extern void	sqSocketCreateNetTypeSocketTypeRecvBytesSendBytesSemaID(
			SocketPtr s,int netType,int socketType,
			int recvBufSize,int sendBufSize,int semaIndex);
	extern void	sqSocketDestroy(SocketPtr s);
	extern int sqSocketError(SocketPtr s);
	extern void	sqSocketListenOnPort(SocketPtr s,int port);
	extern int sqSocketLocalAddress(SocketPtr s);
	extern int sqSocketLocalPort(SocketPtr s);
	extern int sqSocketReceiveDataAvailable(SocketPtr s);
	extern int sqSocketReceiveDataBufCount(SocketPtr s,int buf,int bufSize);
	extern int sqSocketRemoteAddress(SocketPtr s);
	extern int sqSocketRemotePort(SocketPtr s);
	extern int sqSocketSendDataBufCount(SocketPtr s,int buf,int bufSize);
	extern int sqSocketSendDone(SocketPtr s);


/* ----sqMiscPrims---------------------------------------------------------- */
/* miscellaneous primitives */
	extern int primBitmapcompresstoByteArray(void);
	extern int primBitmapdecompressfromByteArrayat(void);
	extern int primStringcomparewithcollated(void);
	extern int primSampledSoundconvert8bitSignedFromto16Bit(void);


/* ----sqUnixSerialAndMIDIPort---------------------------------------------- */
/* serial port primitives */
	extern int serialPortClose(int portNum);
	extern int serialPortOpen(
		int portNum,int baudRate,int stopBitsType,int parityType,int dataBits,
		int inFlowCtrl,int outFlowCtrl,int xOnChar,int xOffChar);
	extern int serialPortReadInto(int portNum,int count,int bufferPtr);
	extern int serialPortWriteFrom(int portNum,int count,int bufferPtr);

/* MIDI primitives */
	extern int sqMIDIGetClock(void);
	extern int sqMIDIGetPortCount(void);
	extern int sqMIDIGetPortDirectionality(int portNum);
	extern int sqMIDIGetPortName(int portNum,int namePtr,int length);
	extern int sqMIDIClosePort(int portNum);
	extern int sqMIDIOpenPort(int portNum,int readSemaIndex,
			int interfaceClockRate);
	extern int sqMIDIParameter(int whichParameter,int modify,int newValue);
	extern int sqMIDIPortReadInto(int portNum,int count,int bufferPtr);
	extern int sqMIDIPortWriteFromAt(int portNum,int count,int bufferPtr,
			int time);


/* ------------------------------------------------------------------------- */
/* There's no implementation of these...
/* netscape plug-in support */
	extern int plugInInit(char *imageName);
	extern int plugInShutdown(void);
	extern int plugInInterpretCycles(int cycleCount);


/* ----interp--------------------------------------------------------------- */
/* interpreter entry points */
	extern void error(char *s);
	extern int checkedByteAt(int byteAddress);
	extern int checkedByteAtput(int byteAddress,int byte);
	extern int checkedLongAt(int byteAddress);
	extern int checkedLongAtput(int byteAddress,int a32BitInteger);
	extern int fullDisplayUpdate(void);
	extern int initializeInterpreter(int bytesToShift);
	extern int interpret(void);
	extern int primitiveFail(void);
	extern int signalSemaphoreWithIndex(int index);
	extern int success(int);

/* interpreter entry points needed by compiled primitives */
	extern void * arrayValueOf(int arrayOop);
	extern int checkedIntegerValueOf(int intOop);
	extern void * fetchArrayofObject(int fieldIndex,int objectPointer);
	extern double fetchFloatofObject(int fieldIndex,int objectPointer);
	extern int fetchIntegerofObject(int fieldIndex,int objectPointer);
	extern double floatValueOf(int floatOop);
	extern int pop(int nItems);
	extern int pushInteger(int integerValue);
	extern int sizeOfSTArrayFromCPrimitive(void *cPtr);
	extern int storeIntegerofObjectwithValue(int fieldIndex,int objectPointer,
			int integerValue);

/* save/restore */
	extern int readImageFromFileHeapSize(sqImageFile f,int desiredHeapSize);


/*** Variables -- Imported from Virtual Machine ***/
	extern unsigned char *memory;
	extern int interruptKeycode;
	extern int interruptPending;
	extern int interruptCheckCounter;
	extern int contextCacheEntries; // May be defined, may be not.
	extern int stackCacheEntries;   // May be defined, may be not.




/* ----sq------------------------------------------------------------------- */
/* This is the only part that is actually exported by this sq module.        */

/* display,mouse,keyboard,time i/o */
	extern int ioBeep(void);
	extern int ioExit(void);
	extern int ioForceDisplayUpdate(void);
	extern int ioFormPrint(
		int bitsAddr,int width,int height,int depth,
		double hScale,double vScale,int landscapeFlag);
	extern int ioSetFullScreen(int fullScreen);
	extern int ioGetButtonState(void);
	extern int ioGetKeystroke(void);
	extern int ioMicroMSecs(void);
	extern int ioMSecs(void);
	extern int ioMousePoint(void);
	extern int ioPeekKeystroke(void);
	extern int ioProcessEvents(void);
	extern int ioRelinquishProcessorForMicroseconds(int microSeconds);
	extern int ioScreenSize(void);
	extern int ioSeconds(void);
	extern int ioSetCursorWithMask(int cursorBitsIndex,int cursorMaskIndex,
		int offsetX,int offsetY);
	extern int ioSetCursor(int cursorBitsIndex,int offsetX,int offsetY);
	extern int ioShowDisplay(
		int dispBitsIndex,int width,int height,int depth,
		int affectedL,int affectedR,int affectedT,int affectedB);

/* optional millisecond clock macro */
#ifdef USE_CLOCK_MSECS
# define ioMSecs() ((1000 * clock()) / CLOCKS_PER_SEC)
#endif

/* image file and VM path names */
	extern char imageName[]; // = Dirty trick for writeImageFile.
	extern int imageNameGetLength(int sqImageNameIndex,int length);
	extern int imageNamePutLength(int sqImageNameIndex,int length);
	extern int imageNameSize(void);
	extern int vmPathSize(void);
	extern int vmPathGetLength(int sqVMPathIndex,int length);


/* clipboard (cut/copy/paste) */
	extern int clipboardSize(void);
	extern int clipboardReadIntoAt(int count,int byteArrayIndex,
			int startIndex);
	extern int clipboardWriteFromAt(int count,int byteArrayIndex,
			int startIndex);

/* profiling */
	extern int clearProfile(void);
	extern int dumpProfile(void);
	extern int startProfiling(void);
	extern int stopProfiling(void);

/* system attributes */
	extern int attributeSize(int ident);
	extern int getAttributeIntoLength(int ident,int byteArrayIndex,int length);

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

These are the contents of the former NiCE NeXT User Group NeXTSTEP/OpenStep software archive, currently hosted by Netfuture.ch.