ftp.nice.ch/pub/next/developer/languages/smalltalk/squeak-2.0-0.3d109.NIHS.bs.tar.gz#/squeak-2.0/src/sqSoundPrims.c

This is sqSoundPrims.c in view mode; [Download] [Up]

/* Automatically generated from Squeak on (25 May 1998 4:26:36 pm ) */

#include "sq.h"


/* Memory Access Macros */
#define byteAt(i) (*((unsigned char *) (i)))
#define byteAtput(i, val) (*((unsigned char *) (i)) = val)
#define longAt(i) (*((int *) (i)))
#define longAtput(i, val) (*((int *) (i)) = val)

/*** Imported Functions/Variables ***/
extern int stackValue(int);
extern int successFlag;

/*** Variables ***/

/*** Function Prototypes ***/
int primFMSoundmixSampleCountintostartingAtleftVolrightVol(void);
int primPluckedSoundmixSampleCountintostartingAtleftVolrightVol(void);
int primReverbSoundapplyReverbTostartingAtcount(void);
int primSampledSoundmixSampleCountintostartingAtleftVolrightVol(void);

int primFMSoundmixSampleCountintostartingAtleftVolrightVol(void) {
    int rcvr;
    int n;
    short int *aSoundBuffer;
    int startIndex;
    int leftVol;
    int rightVol;
    int sample;
    int s;
    int sliceIndex;
    int offset;
    int lastIndex;
    int i;
    int doingFM;
    int scaledVol;
    int scaledVolIncr;
    int scaledVolLimit;
    int count;
    short int *waveTable;
    int scaledWaveTableSize;
    int scaledIndex;
    int scaledIndexIncr;
    int normalizedModulation;
    int scaledOffsetIndex;
    int scaledOffsetIndexIncr;

	rcvr = stackValue(5);
	n = checkedIntegerValueOf(stackValue(4));
	aSoundBuffer = arrayValueOf(stackValue(3));
	aSoundBuffer -= 1;
	startIndex = checkedIntegerValueOf(stackValue(2));
	leftVol = checkedIntegerValueOf(stackValue(1));
	rightVol = checkedIntegerValueOf(stackValue(0));
	scaledVol = fetchIntegerofObject(3, rcvr);
	scaledVolIncr = fetchIntegerofObject(4, rcvr);
	scaledVolLimit = fetchIntegerofObject(5, rcvr);
	count = fetchIntegerofObject(7, rcvr);
	waveTable = fetchArrayofObject(8, rcvr);
	waveTable -= 1;
	scaledWaveTableSize = fetchIntegerofObject(9, rcvr);
	scaledIndex = fetchIntegerofObject(10, rcvr);
	scaledIndexIncr = fetchIntegerofObject(11, rcvr);
	normalizedModulation = fetchIntegerofObject(14, rcvr);
	scaledOffsetIndex = fetchIntegerofObject(15, rcvr);
	scaledOffsetIndexIncr = fetchIntegerofObject(16, rcvr);
	if (!(successFlag)) {
		return null;
	}
	doingFM = (normalizedModulation != 0) && (scaledOffsetIndexIncr != 0);
	lastIndex = (startIndex + n) - 1;
	for (sliceIndex = startIndex; sliceIndex <= lastIndex; sliceIndex += 1) {
		sample = (scaledVol * (waveTable[(scaledIndex / 32768) + 1])) / 32768;
		if (doingFM) {
			offset = normalizedModulation * (waveTable[(scaledOffsetIndex / 32768) + 1]);
			scaledOffsetIndex = (scaledOffsetIndex + scaledOffsetIndexIncr) % scaledWaveTableSize;
			if (scaledOffsetIndex < 0) {
				scaledOffsetIndex += scaledWaveTableSize;
			}
			scaledIndex = ((scaledIndex + scaledIndexIncr) + offset) % scaledWaveTableSize;
			if (scaledIndex < 0) {
				scaledIndex += scaledWaveTableSize;
			}
		} else {
			scaledIndex = (scaledIndex + scaledIndexIncr) % scaledWaveTableSize;
		}
		if (leftVol > 0) {
			i = (2 * sliceIndex) - 1;
			s = (aSoundBuffer[i]) + ((sample * leftVol) / 32768);
			if (s > 32767) {
				s = 32767;
			}
			if (s < -32767) {
				s = -32767;
			}
			aSoundBuffer[i] = s;
		}
		if (rightVol > 0) {
			i = 2 * sliceIndex;
			s = (aSoundBuffer[i]) + ((sample * rightVol) / 32768);
			if (s > 32767) {
				s = 32767;
			}
			if (s < -32767) {
				s = -32767;
			}
			aSoundBuffer[i] = s;
		}
		if (scaledVolIncr != 0) {
			scaledVol += scaledVolIncr;
			if (((scaledVolIncr > 0) && (scaledVol >= scaledVolLimit)) || ((scaledVolIncr < 0) && (scaledVol <= scaledVolLimit))) {
				scaledVol = scaledVolLimit;
				scaledVolIncr = 0;
			}
		}
	}
	count -= n;
	if (!(successFlag)) {
		return null;
	}
	storeIntegerofObjectwithValue(3, rcvr, scaledVol);
	storeIntegerofObjectwithValue(4, rcvr, scaledVolIncr);
	storeIntegerofObjectwithValue(7, rcvr, count);
	storeIntegerofObjectwithValue(10, rcvr, scaledIndex);
	storeIntegerofObjectwithValue(15, rcvr, scaledOffsetIndex);
	pop(5);
}

int primPluckedSoundmixSampleCountintostartingAtleftVolrightVol(void) {
    int rcvr;
    int n;
    short int *aSoundBuffer;
    int startIndex;
    int leftVol;
    int rightVol;
    int average;
    int scaledThisIndex;
    int scaledNextIndex;
    int sample;
    int s;
    int sliceIndex;
    int lastIndex;
    int i;
    int scaledVol;
    int scaledVolIncr;
    int scaledVolLimit;
    int count;
    short int *ring;
    int scaledIndex;
    int scaledIndexIncr;
    int scaledIndexLimit;

	rcvr = stackValue(5);
	n = checkedIntegerValueOf(stackValue(4));
	aSoundBuffer = arrayValueOf(stackValue(3));
	aSoundBuffer -= 1;
	startIndex = checkedIntegerValueOf(stackValue(2));
	leftVol = checkedIntegerValueOf(stackValue(1));
	rightVol = checkedIntegerValueOf(stackValue(0));
	scaledVol = fetchIntegerofObject(3, rcvr);
	scaledVolIncr = fetchIntegerofObject(4, rcvr);
	scaledVolLimit = fetchIntegerofObject(5, rcvr);
	count = fetchIntegerofObject(7, rcvr);
	ring = fetchArrayofObject(8, rcvr);
	ring -= 1;
	scaledIndex = fetchIntegerofObject(9, rcvr);
	scaledIndexIncr = fetchIntegerofObject(10, rcvr);
	scaledIndexLimit = fetchIntegerofObject(11, rcvr);
	if (!(successFlag)) {
		return null;
	}
	lastIndex = (startIndex + n) - 1;
	scaledThisIndex = scaledIndex;
	for (sliceIndex = startIndex; sliceIndex <= lastIndex; sliceIndex += 1) {
		scaledNextIndex = scaledThisIndex + scaledIndexIncr;
		if (scaledNextIndex >= scaledIndexLimit) {
			scaledNextIndex = 32768 + (scaledNextIndex - scaledIndexLimit);
		}
		average = ((ring[scaledThisIndex / 32768]) + (ring[scaledNextIndex / 32768])) / 2;
		ring[scaledThisIndex / 32768] = average;
		sample = (average * scaledVol) / 32768;
		scaledThisIndex = scaledNextIndex;
		if (leftVol > 0) {
			i = (2 * sliceIndex) - 1;
			s = (aSoundBuffer[i]) + ((sample * leftVol) / 32768);
			if (s > 32767) {
				s = 32767;
			}
			if (s < -32767) {
				s = -32767;
			}
			aSoundBuffer[i] = s;
		}
		if (rightVol > 0) {
			i = 2 * sliceIndex;
			s = (aSoundBuffer[i]) + ((sample * rightVol) / 32768);
			if (s > 32767) {
				s = 32767;
			}
			if (s < -32767) {
				s = -32767;
			}
			aSoundBuffer[i] = s;
		}
		if (scaledVolIncr != 0) {
			scaledVol += scaledVolIncr;
			if (((scaledVolIncr > 0) && (scaledVol >= scaledVolLimit)) || ((scaledVolIncr < 0) && (scaledVol <= scaledVolLimit))) {
				scaledVol = scaledVolLimit;
				scaledVolIncr = 0;
			}
		}
	}
	scaledIndex = scaledNextIndex;
	count -= n;
	if (!(successFlag)) {
		return null;
	}
	storeIntegerofObjectwithValue(3, rcvr, scaledVol);
	storeIntegerofObjectwithValue(4, rcvr, scaledVolIncr);
	storeIntegerofObjectwithValue(7, rcvr, count);
	storeIntegerofObjectwithValue(9, rcvr, scaledIndex);
	pop(5);
}

int primReverbSoundapplyReverbTostartingAtcount(void) {
    int rcvr;
    short int *aSoundBuffer;
    int startIndex;
    int n;
    int j;
    int delayedLeft;
    int delayedRight;
    int sliceIndex;
    int i;
    int out;
    int tapIndex;
    int tapGain;
    int *tapDelays;
    int *tapGains;
    int tapCount;
    int bufferSize;
    int bufferIndex;
    short int *leftBuffer;
    short int *rightBuffer;

	rcvr = stackValue(3);
	aSoundBuffer = arrayValueOf(stackValue(2));
	aSoundBuffer -= 1;
	startIndex = checkedIntegerValueOf(stackValue(1));
	n = checkedIntegerValueOf(stackValue(0));
	tapDelays = fetchArrayofObject(7, rcvr);
	tapDelays -= 1;
	tapGains = fetchArrayofObject(8, rcvr);
	tapGains -= 1;
	tapCount = fetchIntegerofObject(9, rcvr);
	bufferSize = fetchIntegerofObject(10, rcvr);
	bufferIndex = fetchIntegerofObject(11, rcvr);
	leftBuffer = fetchArrayofObject(12, rcvr);
	leftBuffer -= 1;
	rightBuffer = fetchArrayofObject(13, rcvr);
	rightBuffer -= 1;
	if (!(successFlag)) {
		return null;
	}
	for (sliceIndex = startIndex; sliceIndex <= ((startIndex + n) - 1); sliceIndex += 1) {
		delayedLeft = delayedRight = 0;
		for (tapIndex = 1; tapIndex <= tapCount; tapIndex += 1) {
			i = bufferIndex - (tapDelays[tapIndex]);
			if (i < 1) {
				i += bufferSize;
			}
			tapGain = tapGains[tapIndex];
			delayedLeft += tapGain * (leftBuffer[i]);
			delayedRight += tapGain * (rightBuffer[i]);
		}
		j = (2 * sliceIndex) - 1;
		out = (aSoundBuffer[j]) + (delayedLeft / 32768);
		if (out > 32767) {
			out = 32767;
		}
		if (out < -32767) {
			out = -32767;
		}
		aSoundBuffer[j] = out;
		leftBuffer[bufferIndex] = out;
		j += 1;
		out = (aSoundBuffer[j]) + (delayedRight / 32768);
		if (out > 32767) {
			out = 32767;
		}
		if (out < -32767) {
			out = -32767;
		}
		aSoundBuffer[j] = out;
		rightBuffer[bufferIndex] = out;
		bufferIndex = (bufferIndex % bufferSize) + 1;
	}
	if (!(successFlag)) {
		return null;
	}
	storeIntegerofObjectwithValue(11, rcvr, bufferIndex);
	pop(3);
}

int primSampledSoundmixSampleCountintostartingAtleftVolrightVol(void) {
    int rcvr;
    int n;
    short int *aSoundBuffer;
    int startIndex;
    int leftVol;
    int rightVol;
    int sliceIndex;
    int sampleIndex;
    int sample;
    int s;
    int lastIndex;
    int i;
    int scaledVol;
    int scaledVolIncr;
    int scaledVolLimit;
    int count;
    short int *samples;
    int samplesSize;
    int incrementTimes1000;
    int indexTimes1000;

	rcvr = stackValue(5);
	n = checkedIntegerValueOf(stackValue(4));
	aSoundBuffer = arrayValueOf(stackValue(3));
	aSoundBuffer -= 1;
	startIndex = checkedIntegerValueOf(stackValue(2));
	leftVol = checkedIntegerValueOf(stackValue(1));
	rightVol = checkedIntegerValueOf(stackValue(0));
	scaledVol = fetchIntegerofObject(3, rcvr);
	scaledVolIncr = fetchIntegerofObject(4, rcvr);
	scaledVolLimit = fetchIntegerofObject(5, rcvr);
	count = fetchIntegerofObject(7, rcvr);
	samples = fetchArrayofObject(8, rcvr);
	samples -= 1;
	samplesSize = fetchIntegerofObject(10, rcvr);
	incrementTimes1000 = fetchIntegerofObject(11, rcvr);
	indexTimes1000 = fetchIntegerofObject(12, rcvr);
	if (!(successFlag)) {
		return null;
	}
	lastIndex = (startIndex + n) - 1;
	sliceIndex = startIndex;
	sampleIndex = indexTimes1000 / 1000;
	while ((sampleIndex <= samplesSize) && (sliceIndex <= lastIndex)) {
		sample = ((samples[sampleIndex]) * scaledVol) / 32768;
		if (leftVol > 0) {
			i = (2 * sliceIndex) - 1;
			s = (aSoundBuffer[i]) + ((sample * leftVol) / 32768);
			if (s > 32767) {
				s = 32767;
			}
			if (s < -32767) {
				s = -32767;
			}
			aSoundBuffer[i] = s;
		}
		if (rightVol > 0) {
			i = 2 * sliceIndex;
			s = (aSoundBuffer[i]) + ((sample * rightVol) / 32768);
			if (s > 32767) {
				s = 32767;
			}
			if (s < -32767) {
				s = -32767;
			}
			aSoundBuffer[i] = s;
		}
		if (scaledVolIncr != 0) {
			scaledVol += scaledVolIncr;
			if (((scaledVolIncr > 0) && (scaledVol >= scaledVolLimit)) || ((scaledVolIncr < 0) && (scaledVol <= scaledVolLimit))) {
				scaledVol = scaledVolLimit;
				scaledVolIncr = 0;
			}
		}
		indexTimes1000 += incrementTimes1000;
		sampleIndex = indexTimes1000 / 1000;
		sliceIndex += 1;
	}
	count -= n;
	if (!(successFlag)) {
		return null;
	}
	storeIntegerofObjectwithValue(3, rcvr, scaledVol);
	storeIntegerofObjectwithValue(4, rcvr, scaledVolIncr);
	storeIntegerofObjectwithValue(7, rcvr, count);
	storeIntegerofObjectwithValue(12, rcvr, indexTimes1000);
	pop(5);
}

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