[Pkg] The Trunk: Sound-bf.42.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Dec 8 01:06:23 UTC 2014


Bert Freudenberg uploaded a new version of Sound to project The Trunk:
http://source.squeak.org/trunk/Sound-bf.42.mcz

==================== Summary ====================

Name: Sound-bf.42
Author: bf
Time: 8 December 2014, 2:05:47.367 am
UUID: 01b2784a-0ad7-4a6b-a996-3388ab820acd
Ancestors: Sound-ul.41

Restore timestamps lost in assignment conversion.

=============== Diff against Sound-ul.41 ===============

Item was changed:
  ----- Method: ADPCMCodec>>bytesPerEncodedFrame (in category 'codec stuff') -----
  bytesPerEncodedFrame
  	"Answer the number of bytes required to hold one frame of compressed sound data."
  	"Note: When used as a normal codec, the frame size is always 8 samples which results in (8 * bitsPerSample) / 8 = bitsPerSample bytes."
  
  	| bitCount |
  	frameSizeMask = 0 ifTrue: [^ bitsPerSample].
  	"Following assumes mono:"
  	bitCount := 16 + 6 + ((self samplesPerFrame - 1) * bitsPerSample).
  	^ (bitCount + 7) // 8
  !

Item was changed:
  ----- Method: ADPCMCodec>>compressAndDecompress: (in category 'codec stuff') -----
  compressAndDecompress: aSound
  	"Compress and decompress the given sound. Overridden to use same bits per sample for both compressing and decompressing."
  
  	| compressed decoder |
  	compressed := self compressSound: aSound.
  	decoder := self class new
  		initializeForBitsPerSample: bitsPerSample
  		samplesPerFrame: 0.
  	^ decoder decompressSound: compressed
  
  !

Item was changed:
  ----- Method: ADPCMCodec>>decode:sampleCount:bitsPerSample:frameSize:stereo: (in category 'private') -----
  decode: aByteArray sampleCount: count bitsPerSample: bits frameSize: frameSize stereo: stereoFlag
  
  	self initializeForBitsPerSample: bits samplesPerFrame: frameSize.
  	encodedBytes := aByteArray.
  	byteIndex := 0.
  	bitPosition := 0.
  	currentByte := 0.
  	stereoFlag
  		ifTrue: [
  			self resetForStereo.
  			samples := SoundBuffer newMonoSampleCount: count.
  			rightSamples := SoundBuffer newMonoSampleCount: count.
  			sampleIndex := 0.
  			self privateDecodeStereo: count.
  			^ Array with: samples with: rightSamples]
  		ifFalse: [
  			samples := SoundBuffer newMonoSampleCount: count.
  			sampleIndex := 0.
  			self privateDecodeMono: count.
  			^ samples]
  !

Item was changed:
  ----- Method: ADPCMCodec>>decodeFlash:sampleCount:stereo: (in category 'private') -----
  decodeFlash: aByteArray sampleCount: sampleCount stereo: stereoFlag
  
  	| bits |
  	encodedBytes := aByteArray.
  	byteIndex := 0.
  	bitPosition := 0.
  	currentByte := 0.
  	bits := 2 + (self nextBits: 2).  "bits per sample"
  	self initializeForBitsPerSample: bits samplesPerFrame: 4096.
  	stereoFlag
  		ifTrue: [
  			self resetForStereo.
  			samples := SoundBuffer newMonoSampleCount: sampleCount.
  			rightSamples := SoundBuffer newMonoSampleCount: sampleCount.
  			sampleIndex := 0.
  			self privateDecodeStereo: sampleCount.
  			^ Array with: samples with: rightSamples]
  		ifFalse: [
  			samples := SoundBuffer newMonoSampleCount: sampleCount.
  			sampleIndex := 0.
  			self privateDecodeMono: sampleCount.
  			^ Array with: samples].
  !

Item was changed:
  ----- Method: ADPCMCodec>>decodeFrames:from:at:into:at: (in category 'codec stuff') -----
  decodeFrames: frameCount from: srcByteArray at: srcIndex into: dstSoundBuffer at: dstIndex
  	"Decode the given number of monophonic frames starting at the given index in the given ByteArray of compressed sound data and storing the decoded samples into the given SoundBuffer starting at the given destination index. Answer a pair containing the number of bytes of compressed data consumed and the number of decompressed samples produced."
  	"Note: Assume that the sender has ensured that the given number of frames will not exhaust either the source or destination buffers."
  
  	encodedBytes := srcByteArray.
  	byteIndex := srcIndex - 1.
  	bitPosition := 0.
  	currentByte := 0.
  	samples := dstSoundBuffer.
  	sampleIndex := dstIndex - 1.
  	self privateDecodeMono: (frameCount * self samplesPerFrame).
  	^ Array with: (byteIndex - (srcIndex - 1)) with: (sampleIndex - (dstIndex - 1))
  !

Item was changed:
  ----- Method: ADPCMCodec>>encodeFrames:from:at:into:at: (in category 'codec stuff') -----
  encodeFrames: frameCount from: srcSoundBuffer at: srcIndex into: dstByteArray at: dstIndex
  	"Encode the given number of frames starting at the given index in the given monophonic SoundBuffer and storing the encoded sound data into the given ByteArray starting at the given destination index. Encode only as many complete frames as will fit into the destination. Answer a pair containing the number of samples consumed and the number of bytes of compressed data produced."
  	"Note: Assume that the sender has ensured that the given number of frames will not exhaust either the source or destination buffers."
  
  	samples := srcSoundBuffer.
  	sampleIndex := srcIndex - 1.
  	encodedBytes := dstByteArray.
  	byteIndex := dstIndex - 1.
  	bitPosition := 0.
  	currentByte := 0.
  	self privateEncodeMono: (frameCount * self samplesPerFrame).
  	^ Array with: frameCount with: (byteIndex - (dstIndex - 1))
  !

Item was changed:
  ----- Method: ADPCMCodec>>encodeLeft:right:bitsPerSample:frameSize:forFlash: (in category 'private') -----
  encodeLeft: leftSoundBuffer right: rightSoundBuffer bitsPerSample: bits frameSize: frameSize forFlash: flashFlag
  
  	| stereoFlag sampleCount sampleBitCount bitCount |
  	self initializeForBitsPerSample: bits samplesPerFrame: frameSize.
  	stereoFlag := rightSoundBuffer notNil.
  	sampleCount := leftSoundBuffer monoSampleCount.
  	stereoFlag
  		ifTrue: [sampleBitCount := 2 * (sampleCount * bitsPerSample)]
  		ifFalse: [sampleBitCount := sampleCount * bitsPerSample].
  	bitCount := sampleBitCount +
  		(self headerBitsForSampleCount: sampleCount stereoFlag: stereoFlag).
  
  	encodedBytes := ByteArray new: ((bitCount / 8) ceiling roundUpTo: self bytesPerEncodedFrame).
  	byteIndex := 0.
  	bitPosition := 0.
  	currentByte := 0.
  	flashFlag ifTrue: [self nextBits: 2 put: bits - 2].
  	stereoFlag
  		ifTrue: [
  			samples := Array with: leftSoundBuffer with: rightSoundBuffer.
  			sampleIndex := Array with: 0 with: 0.
  			self privateEncodeStereo: sampleCount]
  		ifFalse: [
  			samples := leftSoundBuffer.
  			sampleIndex := 0.
  			self privateEncodeMono: sampleCount].
  
  	^ encodedBytes
  !

Item was changed:
  ----- Method: ADPCMCodec>>headerBitsForSampleCount:stereoFlag: (in category 'private') -----
  headerBitsForSampleCount: sampleCount stereoFlag: stereoFlag
  	"Answer the number of extra header bits required for the given number of samples. This will be zero if I am not using frame headers."
  
  	| frameCount bitsPerHeader |
  	frameSizeMask = 0 ifTrue: [^ 0].
  	frameCount := (sampleCount / self samplesPerFrame) ceiling.
  	bitsPerHeader := 16 + 6.
  	stereoFlag ifTrue: [bitsPerHeader := 2 * bitsPerHeader].
  	^ frameCount * bitsPerHeader
  !

Item was changed:
  ----- Method: ADPCMCodec>>initializeForBitsPerSample:samplesPerFrame: (in category 'private') -----
  initializeForBitsPerSample: sampleBits samplesPerFrame: frameSize
  
  	self resetForMono.
  	stepSizeTable := #(7 8 9 10 11 12 13 14 16 17 19 21 23 25 28 31 34 37 41 45 50 55 60 66 73 80 88 97 107 118 130 143 157 173 190 209 230 253 279 307 337 371 408 449 494 544 598 658 724 796 876 963 1060 1166 1282 1411 1552 1707 1878 2066 2272 2499 2749 3024 3327 3660 4026 4428 4871 5358 5894 6484 7132 7845 8630 9493 10442 11487 12635 13899 15289 16818 18500 20350 22385 24623 27086 29794 32767).
  
  	indexTable := nil.
  	sampleBits = 2 ifTrue: [
  		indexTable := #(-1 2)].
  	sampleBits = 3 ifTrue: [
  		indexTable := #(-1 -1 2 4)].
  	sampleBits = 4 ifTrue: [
  		indexTable := #(-1 -1 -1 -1 2 4 6 8)].
  	sampleBits = 5 ifTrue: [
  		indexTable := #(-1 -1 -1 -1 -1 -1 -1 -1 1 2 4 6 8 10 13 16)].
  	indexTable ifNil: [self error: 'unimplemented bits/sample'].
  
  	bitsPerSample := sampleBits.
  	deltaSignMask := 1 bitShift: bitsPerSample - 1.
  	deltaValueMask := deltaSignMask - 1.
  	deltaValueHighBit := deltaSignMask / 2.
  
  	frameSize <= 1
  		ifTrue: [frameSizeMask := 0]
  		ifFalse: [
  			(frameSize = (1 bitShift: frameSize highBit - 1))
  				ifFalse: [self error: 'frameSize must be a power of two'].
  			frameSizeMask := frameSize - 1].
  
  	"keep as SoundBuffer to allow fast access from primitive"
  	indexTable := SoundBuffer fromArray: indexTable.
  	stepSizeTable := SoundBuffer fromArray: stepSizeTable.
  !

Item was changed:
  ----- Method: ADPCMCodec>>resetForMono (in category 'codec stuff') -----
  resetForMono
  	"Reset my encoding and decoding state for mono."
  
  	predicted := 0.
  	index := 0.
  !

Item was changed:
  ----- Method: ADPCMCodec>>resetForStereo (in category 'codec stuff') -----
  resetForStereo
  	"Reset my encoding and decoding state for stereo."
  
  	"keep state as SoundBuffers to allow fast access from primitive"
  	predicted := SoundBuffer new: 2.
  	index := SoundBuffer new: 2.
  !

Item was changed:
  ----- Method: AIFFFileReader>>pitchForKey: (in category 'other') -----
  pitchForKey: midiKey
  	"Convert my MIDI key number to a pitch and return it."
  
  	| indexInOctave octave p |
  	indexInOctave := (midiKey \\ 12) + 1.
  	octave := (midiKey // 12) + 1.
  	"Table generator: (0 to: 11) collect: [:i | 16.3516 * (2.0 raisedTo: i asFloat / 12.0)]"
  	p := #(16.3516 17.32391 18.35405 19.44544 20.60173 21.82677
  		  23.12466 24.49972 25.95655 27.50000 29.13524 30.86771) at: indexInOctave.
  	^ p * (#(0.5 1.0 2.0 4.0 8.0 16.0 32.0 64.0 128.0 256.0 512.0) at: octave)
  !

Item was changed:
  ----- Method: AIFFFileReader>>readCommonChunk: (in category 'private') -----
  readCommonChunk: chunkSize
  	"Read a COMM chunk. All AIFF files have exactly one chunk of this type."
  
  	| compressionType |
  	channelCount := in nextNumber: 2.
  	frameCount := in nextNumber: 4.
  	bitsPerSample := in nextNumber: 2.
  	samplingRate := self readExtendedFloat.
  	chunkSize > 18 ifTrue: [
  		fileType = 'AIFF'
  			ifTrue: [self error: 'unexpectedly long COMM chunk size for AIFF file'].
  		compressionType := (in next: 4) asString.
  		compressionType = 'NONE' ifFalse: [self error: 'cannot read compressed AIFF files'].
  		in skip: (chunkSize - 22)].  "skip the reminder of AIFF-C style chunk"
  !

Item was changed:
  ----- Method: AIFFFileReader>>readExtendedFloat (in category 'private') -----
  readExtendedFloat
  	"Read and answer an Apple extended-precision 80-bit floating point number from the input stream."
  	"Details: I could not find the specification for this format, so constants were determined empirically based on assumption of 1-bit sign, 15-bit exponent, 64-bit mantissa. This format does not seem to have an implicit one before the mantissa as some float formats do."
  
  	| signAndExp mantissa sign exp |
  	signAndExp := in nextNumber: 2.
  	mantissa := in nextNumber: 8.  "scaled by (2 raisedTo: -64) below"
  	(signAndExp bitAnd: 16r8000) = 0
  		ifTrue: [sign := 1.0]
  		ifFalse: [sign := -1.0].
  	exp := (signAndExp bitAnd: 16r7FFF) - 16r4000 + 2.  "not sure why +2 is needed..."
  	^ (sign * mantissa asFloat * (2.0 raisedTo: exp - 64)) roundTo: 0.00000001
  !

Item was changed:
  ----- Method: AIFFFileReader>>readFrom: (in category 'private') -----
  readFrom: aBinaryStream
  	"Read AIFF data from the given binary stream."
  	"Details: An AIFF file consists of a header (FORM chunk) followed by a sequence of tagged data chunks. Each chunk starts with a header consisting of a four-byte tag (a string) and a four byte size. These eight bytes of chunk header are not included in the chunk size. For each chunk, the readChunk:size: method consumes chunkSize bytes of the input stream, parsing recognized chunks or skipping unrecognized ones. If chunkSize is odd, it will be followed by a padding byte. Chunks may occur in any order."
  
  	| sz end chunkType chunkSize p |
  	in := aBinaryStream.
  
  	"read FORM chunk"
  	(in next: 4) asString = 'FORM' ifFalse: [^ self error: 'not an AIFF file'].
  	sz := in nextNumber: 4.
  	end := in position + sz.
  	fileType := (in next: 4) asString.
  
  	[in atEnd not and: [in position < end]] whileTrue: [
  		chunkType := (in next: 4) asString.
  		chunkSize := in nextNumber: 4.
  		p := in position.
  		self readChunk: chunkType size: chunkSize.
  		(in position = (p + chunkSize))
  			ifFalse: [self error: 'chunk size mismatch; bad AIFF file?'].
  		chunkSize odd ifTrue: [in skip: 1]].  "skip padding byte"
  !

Item was changed:
  ----- Method: AIFFFileReader>>readFromFile:mergeIfStereo:skipDataChunk: (in category 'reading') -----
  readFromFile: fileName mergeIfStereo: mergeFlag skipDataChunk: skipDataFlag
  	"Read the AIFF file of the given name. See comment in readFromStream:mergeIfStereo:skipDataChunk:."
  	"AIFFFileReader new readFromFile: 'test.aiff' mergeIfStereo: false skipDataChunk: true"
  
  	| f |
  	f := (FileStream readOnlyFileNamed: fileName) binary.
  	self readFromStream: f mergeIfStereo: mergeFlag skipDataChunk: skipDataFlag.
  	f close.
  !

Item was changed:
  ----- Method: AIFFFileReader>>readInstrumentChunk: (in category 'private') -----
  readInstrumentChunk: chunkSize
  
  	| midiKey detune lowNote highNote lowVelocity highVelocity
  	  sustainMode sustainStartID sustainEndID
  	  releaseMode releaseStartID releaseEndID |
  
  	midiKey := in next.
  	detune := in next.
  	lowNote := in next.
  	highNote := in next.
  	lowVelocity := in next.
  	highVelocity := in next.
  	gain := in nextNumber: 2.
  	sustainMode := in nextNumber: 2.
  	sustainStartID := in nextNumber: 2.
  	sustainEndID := in nextNumber: 2.
  	releaseMode := in nextNumber: 2.
  	releaseStartID := in nextNumber: 2.
  	releaseEndID := in nextNumber: 2.
  	isLooped := sustainMode = 1.
  	(isLooped and: [markers notNil]) ifTrue: [
  		((markers first last > frameCount) or:
  		 [markers last last > frameCount]) ifTrue: [
  			"bad loop data; some sample CD files claim to be looped but aren't"
  			isLooped := false]].
  	pitch := self pitchForKey: midiKey.
  !

Item was changed:
  ----- Method: AIFFFileReader>>readMarkerChunk: (in category 'private') -----
  readMarkerChunk: chunkSize
  
  	| markerCount id position labelBytes label |
  	markerCount := in nextNumber: 2.
  	markers := Array new: markerCount.
  	1 to: markerCount do: [:i |
  		id := in nextNumber: 2.
  		position := in nextNumber: 4.
  		labelBytes := in next.
  		label := (in next: labelBytes) asString.
  		labelBytes even ifTrue: [in skip: 1].
  		markers at: i put: (Array with: id with: label with: position)].
  
  !

Item was changed:
  ----- Method: AIFFFileReader>>readMergedStereoChannelDataFrom: (in category 'private') -----
  readMergedStereoChannelDataFrom: s
  	"Read stereophonic channel data from the given stream, mixing the two channels to create a single monophonic channel. Each frame contains two samples."
  
  	| buf w1 w2 |
  	buf := channelData at: 1.
  	bitsPerSample = 8
  		ifTrue: [
  			1 to: frameCount do: [:i |
  				w1 := s next.
  				w1 > 127 ifTrue: [w1 := w1 - 256].
  				w2 := s next.
  				w2 > 127 ifTrue: [w2 := w2 - 256].
  				buf at: i put: ((w1 + w2) bitShift: 7)]]
  		ifFalse: [
  			1 to: frameCount do: [:i |
  				w1 := (s next bitShift: 8) + s next.
  				w1 > 32767 ifTrue: [w1 := w1 - 65536].
  				w2 := (s next bitShift: 8) + s next.
  				w2 > 32767 ifTrue: [w2 := w2 - 65536].
  				buf at: i put: ((w1 + w2) bitShift: -1)]].
  !

Item was changed:
  ----- Method: AIFFFileReader>>readMonoChannelDataFrom: (in category 'private') -----
  readMonoChannelDataFrom: s
  	"Read monophonic channel data from the given stream. Each frame contains a single sample."
  
  	| buf w |
  	buf := channelData at: 1.  "the only buffer"
  	bitsPerSample = 8
  		ifTrue: [
  			1 to: frameCount do: [:i |
  				w := s next.
  				w > 127 ifTrue: [w := w - 256].
  				buf at: i put: (w bitShift: 8)]]
  		ifFalse: [
  			1 to: frameCount do: [:i |
  				w := (s next bitShift: 8) + s next.
  				w > 32767 ifTrue: [w := w - 65536].
  				buf at: i put: w]].
  !

Item was changed:
  ----- Method: AIFFFileReader>>readMultiChannelDataFrom: (in category 'private') -----
  readMultiChannelDataFrom: s
  	"Read multi-channel data from the given stream. Each frame contains channelCount samples."
  
  	| w |
  	bitsPerSample = 8
  		ifTrue: [
  			1 to: frameCount do: [:i |
  				1 to: channelCount do: [:ch |
  					w := s next.
  					w > 127 ifTrue: [w := w - 256].
  					(channelData at: ch) at: i put: (w bitShift: 8)]]]
  		ifFalse: [
  			1 to: frameCount do: [:i |
  				1 to: channelCount do: [:ch |
  					w := (s next bitShift: 8) + s next.
  					w > 32767 ifTrue: [w := w - 65536].
  					(channelData at: ch) at: i put: w]]].
  !

Item was changed:
  ----- Method: AIFFFileReader>>readSamplesChunk: (in category 'private') -----
  readSamplesChunk: chunkSize
  	"Read a SSND chunk. All AIFF files with a non-zero frameCount contain exactly one chunk of this type."
  
  	| offset blockSize bytesOfSamples s |
  	offset := in nextNumber: 4.
  	blockSize := in nextNumber: 4.
  	((offset ~= 0) or: [blockSize ~= 0])
  		ifTrue: [^ self error: 'this AIFF reader cannot handle blocked sample chunks'].
  	bytesOfSamples := chunkSize - 8.
  	bytesOfSamples = (channelCount * frameCount * (bitsPerSample // 8))
  		ifFalse: [self error: 'actual sample count does not match COMM chunk'].
  
  	channelDataOffset := in position.  "record stream position for start of data"
  	skipDataChunk ifTrue: [in skip: (chunkSize - 8). ^ self].  "if skipDataChunk, skip sample data"
  
  	(mergeIfStereo and: [channelCount = 2])
  		ifTrue: [
  			channelData := Array with: (SoundBuffer newMonoSampleCount: frameCount)]
  		ifFalse: [
  			channelData :=
  				(1 to: channelCount) collect: [:i | SoundBuffer newMonoSampleCount: frameCount]].
  
  	(bytesOfSamples < (Smalltalk garbageCollectMost - 300000))
  		ifTrue: [s := ReadStream on: (in next: bytesOfSamples)]  "bulk-read, then process"
  		ifFalse: [s := in].  "not enough space to buffer; read directly from file"
  
  	"mono and stereo are special-cased for better performance"
  	channelCount = 1 ifTrue: [^ self readMonoChannelDataFrom: s].
  	channelCount = 2 ifTrue: [
  		mergeIfStereo
  			ifTrue: [channelCount := 1. ^ self readMergedStereoChannelDataFrom: s]
  			ifFalse: [^ self readStereoChannelDataFrom: s]].
  	self readMultiChannelDataFrom: s.
  !

Item was changed:
  ----- Method: AIFFFileReader>>readStereoChannelDataFrom: (in category 'private') -----
  readStereoChannelDataFrom: s
  	"Read stereophonic channel data from the given stream. Each frame contains two samples."
  
  	| left right w |
  	left := channelData at: 1.
  	right := channelData at: 2.
  	bitsPerSample = 8
  		ifTrue: [
  			1 to: frameCount do: [:i |
  				w := s next.
  				w > 127 ifTrue: [w := w - 256].
  				left at: i put: (w bitShift: 8).
  				w := s next.
  				w > 127 ifTrue: [w := w - 256].
  				right at: i put: (w bitShift: 8)]]
  		ifFalse: [
  			1 to: frameCount do: [:i |
  				w := (s next bitShift: 8) + s next.
  				w > 32767 ifTrue: [w := w - 65536].
  				left at: i put: w.
  				w := (s next bitShift: 8) + s next.
  				w > 32767 ifTrue: [w := w - 65536].
  				right at: i put: w]].
  !

Item was changed:
  ----- Method: AIFFFileReader>>sound (in category 'other') -----
  sound
  	"Answer the sound represented by this AIFFFileReader. This method should be called only after readFrom: has been done."
  
  	| snd rightSnd |
  	snd := SampledSound
  		samples: (channelData at: 1)
  		samplingRate: samplingRate.
  	self isStereo ifTrue: [
  		rightSnd := SampledSound
  			samples: (channelData at: 2)
  			samplingRate: samplingRate.
  		snd := MixedSound new
  			add: snd pan: 0;
  			add: rightSnd pan: 1.0].
  	^ snd
  !

Item was changed:
  ----- Method: AbstractScoreEvent>>adjustTimeBy: (in category 'accessing') -----
  adjustTimeBy: delta
  
  	time := time + delta
  !

Item was changed:
  ----- Method: AbstractScoreEvent>>time: (in category 'accessing') -----
  time: aNumber
  
  	time := aNumber.
  !

Item was changed:
  ----- Method: AbstractSound class>>busySignal: (in category 'utilities') -----
  busySignal: count
  	"AbstractSound busySignal: 3"
  	| m s |
  	s := SequentialSound new.
  	m := MixedSound new.
  	m	add: (FMSound new setPitch: 480 dur: 0.5 loudness: 0.5);
  		add: (FMSound new setPitch: 620 dur: 0.5 loudness: 0.5).
  	s add: m.
  	s add: (FMSound new setPitch: 1 dur: 0.5 loudness: 0).
  	^ (RepeatingSound repeat: s count: count) play.
  
  !

Item was changed:
  ----- Method: AbstractSound class>>chromaticPitchesFrom: (in category 'examples') -----
  chromaticPitchesFrom: aPitch
  
  	| halfStep pitch |
  	halfStep := 2.0 raisedTo: (1.0 / 12.0).
  	pitch := aPitch isNumber
  			ifTrue: [aPitch]
  			ifFalse: [self pitchForName: aPitch].
  	pitch := pitch / halfStep.
  	^ (0 to: 14) collect: [:i | pitch := pitch * halfStep]
  !

Item was changed:
  ----- Method: AbstractSound class>>chromaticRunFrom:to:on: (in category 'examples') -----
  chromaticRunFrom: startPitch to: endPitch on: aSound
  	"Answer a composite sound consisting of a rapid chromatic run between the given pitches on the given sound."
  	"(AbstractSound chromaticRunFrom: 'c3' to: 'c#5' on: FMSound oboe1) play"
  
  	| scale halfStep pEnd p |
  	scale := SequentialSound new.
  	halfStep := 2.0 raisedTo: (1.0 / 12.0).
  	endPitch isNumber
  		ifTrue: [pEnd := endPitch asFloat]
  		ifFalse: [pEnd := AbstractSound pitchForName: endPitch].
  	startPitch isNumber
  		ifTrue: [p := startPitch asFloat]
  		ifFalse: [p := AbstractSound pitchForName: startPitch].
  	[p <= pEnd] whileTrue: [
  		scale add: (aSound soundForPitch: p dur: 0.2 loudness: 0.5).
  		p := p * halfStep].
  	^ scale
  !

Item was changed:
  ----- Method: AbstractSound class>>dialTone: (in category 'utilities') -----
  dialTone: duration
  	"AbstractSound dialTone: 2"
  	| m |
  	m := MixedSound new.
  	m add: (FMSound new setPitch: 350 dur: duration loudness: 0.5).
  	m add: (FMSound new setPitch: 440 dur: duration loudness: 0.5).
  	m play.
  	^ m!

Item was changed:
  ----- Method: AbstractSound class>>fileInSoundLibraryNamed: (in category 'sound library-file in/out') -----
  fileInSoundLibraryNamed: fileName
  	"File in the sound library with the given file name, and add its contents to the current sound library."
  
  	| s newSounds |
  	s := FileStream oldFileNamed: fileName.
  	newSounds := s fileInObjectAndCode.
  	s close.
  	newSounds associationsDo:
  		[:assoc | self storeFiledInSound: assoc value named: assoc key].
  	AbstractSound updateScorePlayers.
  	Smalltalk garbageCollect.  "Large objects may have been released"
  !

Item was changed:
  ----- Method: AbstractSound class>>hangUpWarning: (in category 'utilities') -----
  hangUpWarning: count
  	"AbstractSound hangUpWarning: 20"
  	| m s |
  	s := SequentialSound new.
  	m := MixedSound new.
  	m	add: (FMSound new setPitch: 1400 dur: 0.1 loudness: 0.5);
  		add: (FMSound new setPitch: 2060 dur: 0.1 loudness: 0.5).
  	s add: m; add: (FMSound new setPitch: 1 dur: 0.1 loudness: 0).
  	^ (RepeatingSound repeat: s count: count) play
  
  !

Item was changed:
  ----- Method: AbstractSound class>>initSounds (in category 'sound library') -----
  initSounds
  	"AbstractSound initSounds"
  
  	Sounds := Dictionary new.
  	(FMSound class organization listAtCategoryNamed: #instruments)
  		do: [:sel | Sounds at: sel asString put: (FMSound perform: sel)].
  !

Item was changed:
  ----- Method: AbstractSound class>>initialize (in category 'class initialization') -----
  initialize
  	"AbstractSound initialize"
   
  	| bottomC |
  	ScaleFactor := 2 raisedTo: 15.
  	FloatScaleFactor := ScaleFactor asFloat.
  	MaxScaledValue := ((2 raisedTo: 31) // ScaleFactor) - 1.  "magnitude of largest scaled value in 32-bits"
  
  	"generate pitches for c-1 through c0"
  	bottomC := (440.0 / 32) * (2.0 raisedTo: -9.0 / 12.0).
  	PitchesForBottomOctave := (0 to: 12) collect: [:i | bottomC * (2.0 raisedTo: i asFloat / 12.0)].
  	TopOfBottomOctave := PitchesForBottomOctave last.
  !

Item was changed:
  ----- Method: AbstractSound class>>majorPitchesFrom: (in category 'examples') -----
  majorPitchesFrom: aPitch
  	| chromatic |
  	chromatic := self chromaticPitchesFrom: aPitch.
  	^ #(1 3 5 6 8 10 12 13 15 13 12 10 8 6 5 3 1) collect: [:i | chromatic at: i].
  !

Item was changed:
  ----- Method: AbstractSound class>>majorScaleOn:from:octaves: (in category 'examples') -----
  majorScaleOn: aSound from: aPitch octaves: octaveCount
  	"(AbstractSound majorScaleOn: FMSound oboe1 from: #c2 octaves: 5) play"
  
  	| startingPitch pitches chromatic |
  	startingPitch := aPitch isNumber
  		ifTrue: [aPitch]
  		ifFalse: [self pitchForName: aPitch].
  	pitches := OrderedCollection new.
  	0 to: octaveCount - 1 do: [:i |
  		chromatic := self chromaticPitchesFrom: startingPitch * (2 raisedTo: i).
  		#(1 3 5 6 8 10 12) do: [:j | pitches addLast: (chromatic at: j)]].
  	pitches addLast: startingPitch * (2 raisedTo: octaveCount).
  	^ self noteSequenceOn: aSound
  		from: (pitches collect: [:pitch | Array with: pitch with: 0.5 with: 300])
  !

Item was changed:
  ----- Method: AbstractSound class>>midiKeyForPitch: (in category 'utilities') -----
  midiKeyForPitch: pitchNameOrNumber
  	"Answer the midiKey closest to the given pitch. Pitch may be a numeric pitch or a pitch name string such as 'c4'."
  	"AbstractSound midiKeyForPitch: 440.0"
  
  	| p octave i midiKey |
  	pitchNameOrNumber isNumber
  		ifTrue: [p := pitchNameOrNumber asFloat]
  		ifFalse: [p := AbstractSound pitchForName: pitchNameOrNumber].
  	octave := -1.
  	[p >= TopOfBottomOctave] whileTrue: [
  		octave := octave + 1.
  		p := p / 2.0].
  
  	i := self indexOfBottomOctavePitch: p.
  	(i > 1) ifTrue: [
  		(p - (PitchesForBottomOctave at: i - 1)) < ((PitchesForBottomOctave at: i) - p)
  			ifTrue: [i := i - 1]].
  
  	midiKey := ((octave * 12) + 11 + i).
  	midiKey > 127 ifTrue: [midiKey := 127].
  	^ midiKey
  !

Item was changed:
  ----- Method: AbstractSound class>>pitchForMIDIKey: (in category 'utilities') -----
  pitchForMIDIKey: midiKey
  	"Answer the pitch for the given MIDI key."
  	"(1 to: 127) collect: [:i | AbstractSound pitchForMIDIKey: i]"
  
  	| indexInOctave octave |
  	indexInOctave := (midiKey \\ 12) + 1.
  	octave := (midiKey // 12) + 1.
  	^ (PitchesForBottomOctave at: indexInOctave) *
  		(#(1.0 2.0 4.0 8.0 16.0 32.0 64.0 128.0 256.0 512.0 1024.0) at: octave)
  !

Item was changed:
  ----- Method: AbstractSound class>>pitchTable (in category 'utilities') -----
  pitchTable
  	"AbstractSound pitchTable"
  
  	| out note i |
  	out := WriteStream on: (String new: 1000).
  	i := 12.
  	0 to: 8 do: [:octave |
  		#(c 'c#' d eb e f fs g 'g#' a bf b) do: [:noteName |
  			note := noteName, octave printString.
  			out nextPutAll: note; tab.
  			out nextPutAll: i printString; tab.
  			out nextPutAll: (AbstractSound pitchForName: note) printString; cr.
  			i := i + 1]].
  	^ out contents
  !

Item was changed:
  ----- Method: AbstractSound class>>testFMInteractively (in category 'examples') -----
  testFMInteractively
  	"Experiment with different settings of the FM modulation and multiplier settings interactively by moving the mouse. The top-left corner of the screen is 0 for both parameters. Stop when the mouse is pressed."
  	"AbstractSound testFMInteractively"
  
  	| s mousePt lastVal status mod ratio |
  	SoundPlayer startPlayerProcessBufferSize: 1100 rate: 11025 stereo: false.
  	s := FMSound pitch: 440.0 dur: 200.0 loudness: 0.2.
  
  	SoundPlayer playSound: s.
  	lastVal := nil.
  	[Sensor anyButtonPressed] whileFalse: [
  		mousePt := Sensor cursorPoint.
  		mousePt ~= lastVal ifTrue: [
  			mod := mousePt x asFloat / 20.0.
  			ratio := mousePt y asFloat / 20.0.
  			s modulation: mod ratio: ratio.
  			lastVal := mousePt.
  			status :=
  'mod: ', mod printString, '
  ratio: ', ratio printString.
  			status displayOn: Display at: 10 at 10]].
  
  	SoundPlayer shutDown.
  !

Item was changed:
  ----- Method: AbstractSound class>>unloadedSound (in category 'sound library-file in/out') -----
  unloadedSound
  	"Answer a sound to be used as the place-holder for sounds that have been unloaded."
  
  	UnloadedSnd ifNil: [UnloadedSnd := UnloadedSound default copy].
  	^ UnloadedSnd
  !

Item was changed:
  ----- Method: AbstractSound>>addEnvelope: (in category 'envelopes') -----
  addEnvelope: anEnvelope
  	"Add the given envelope to my envelopes list."
  
  	anEnvelope target: self.
  	envelopes := envelopes copyWith: anEnvelope.
  !

Item was changed:
  ----- Method: AbstractSound>>adjustVolumeTo:overMSecs: (in category 'volume') -----
  adjustVolumeTo: vol overMSecs: mSecs
  	"Adjust the volume of this sound to the given volume, a number in the range [0.0..1.0], over the given number of milliseconds. The volume will be changed a little bit on each sample until the desired volume is reached."
  
  	| newScaledVol |
  
  	self flag: #bob.		"I removed the upper limit to allow making sounds louder. hmm..."
  
  	newScaledVol := (32768.0 * vol) truncated.
  	newScaledVol = scaledVol ifTrue: [^ self].
  	scaledVolLimit := newScaledVol.
  	"scaledVolLimit > ScaleFactor ifTrue: [scaledVolLimit := ScaleFactor]."
  	scaledVolLimit < 0 ifTrue: [scaledVolLimit := 0].
  	mSecs = 0
  		ifTrue: [  "change immediately"
  			scaledVol := scaledVolLimit.
  			scaledVolIncr := 0]
  		ifFalse: [
  			scaledVolIncr :=
  				((scaledVolLimit - scaledVol) * 1000) // (self samplingRate * mSecs)].
  !

Item was changed:
  ----- Method: AbstractSound>>computeSamplesForSeconds: (in category 'playing') -----
  computeSamplesForSeconds: seconds
  	"Compute the samples of this sound without outputting them, and return the resulting buffer of samples."
  
  	| buf |
  	self reset.
  	buf := SoundBuffer newStereoSampleCount: (self samplingRate * seconds) asInteger.
  	self playSampleCount: buf stereoSampleCount into: buf startingAt: 1.
  	^ buf
  !

Item was changed:
  ----- Method: AbstractSound>>copyEnvelopes (in category 'copying') -----
  copyEnvelopes
  	"Private!! Support for copying. Copy my envelopes."
  
  	envelopes := envelopes collect: [:e | e copy target: self].
  !

Item was changed:
  ----- Method: AbstractSound>>doControl (in category 'sound generation') -----
  doControl
  	"Update the control parameters of this sound using its envelopes, if any."
  	"Note: This is only called at a small fraction of the sampling rate."
  
  	| pitchModOrRatioChange |
  	envelopes size > 0 ifTrue: [
  		pitchModOrRatioChange := false.
  		1 to: envelopes size do: [:i |
  			((envelopes at: i) updateTargetAt: mSecsSinceStart)
  				ifTrue: [pitchModOrRatioChange := true]].
  		pitchModOrRatioChange ifTrue: [self internalizeModulationAndRatio]].
  	mSecsSinceStart := mSecsSinceStart + (1000 // self controlRate).
  !

Item was changed:
  ----- Method: AbstractSound>>initialVolume: (in category 'volume') -----
  initialVolume: vol
  	"Set the initial volume of this sound to the given volume, a number in the range [0.0..1.0]."
  
  	scaledVol := (((vol asFloat min: 1.0) max: 0.0) * ScaleFactor) rounded.
  	scaledVolLimit := scaledVol.
  	scaledVolIncr := 0.
  !

Item was changed:
  ----- Method: AbstractSound>>loudness: (in category 'initialization') -----
  loudness: aNumber
  	"Initialize my volume envelopes and initial volume. Subclasses overriding this method should include a resend to super."
  
  	| vol |
  	vol := (aNumber asFloat max: 0.0) min: 1.0.
  	envelopes do: [:e |
  		(e isKindOf: VolumeEnvelope) ifTrue: [e scale: vol]].
  	self initialVolume: vol.
  !

Item was changed:
  ----- Method: AbstractSound>>playSampleCount:into:startingAt: (in category 'playing') -----
  playSampleCount: n into: aSoundBuffer startingAt: startIndex
  	"Mix the next n samples of this sound into the given buffer starting at the given index. Update the receiver's control parameters periodically."
  
  	| fullVol samplesBetweenControlUpdates pastEnd i remainingSamples count |
  	fullVol := AbstractSound scaleFactor.
  	samplesBetweenControlUpdates := self samplingRate // self controlRate.
  	pastEnd := startIndex + n.  "index just after the last sample"
  	i := startIndex.
  	[i < pastEnd] whileTrue: [
  		remainingSamples := self samplesRemaining.
  		remainingSamples <= 0 ifTrue: [^ self].
  		count := pastEnd - i.
  		samplesUntilNextControl < count ifTrue: [count := samplesUntilNextControl].
  		remainingSamples < count ifTrue: [count := remainingSamples].
  		self mixSampleCount: count into: aSoundBuffer startingAt: i leftVol: fullVol rightVol: fullVol.
  		samplesUntilNextControl := samplesUntilNextControl - count.
  		samplesUntilNextControl <= 0 ifTrue: [
  			self doControl.
  			samplesUntilNextControl := samplesBetweenControlUpdates].
  		i := i + count].
  !

Item was changed:
  ----- Method: AbstractSound>>playSilently (in category 'playing') -----
  playSilently
  	"Compute the samples of this sound without outputting them. Used for performance analysis."
  
  	| bufSize buf |
  	self reset.
  	bufSize := self samplingRate // 10.
  	buf := SoundBuffer newStereoSampleCount: bufSize.
  	[self samplesRemaining > 0] whileTrue: [
  		buf primFill: 0.
  		self playSampleCount: bufSize into: buf startingAt: 1].
  !

Item was changed:
  ----- Method: AbstractSound>>playSilentlyUntil: (in category 'playing') -----
  playSilentlyUntil: startTime
  	"Compute the samples of this sound without outputting them. Used to fast foward to a particular starting time. The start time is given in seconds."
  
  	| buf startSample nextSample samplesRemaining n |
  	self reset.
  	buf := SoundBuffer newStereoSampleCount: (self samplingRate // 10).
  	startSample := (startTime * self samplingRate) asInteger.
  	nextSample := 1.
  	[self samplesRemaining > 0] whileTrue: [
  		nextSample >= startSample ifTrue: [^ self].
  		samplesRemaining := startSample - nextSample.
  		samplesRemaining > buf stereoSampleCount
  			ifTrue: [n := buf stereoSampleCount]
  			ifFalse: [n := samplesRemaining].
  		self playSampleCount: n into: buf startingAt: 1.
  		nextSample := nextSample + n].
  !

Item was changed:
  ----- Method: AbstractSound>>removeAllEnvelopes (in category 'envelopes') -----
  removeAllEnvelopes
  	"Remove all envelopes from my envelopes list."
  
  	envelopes := #().
  !

Item was changed:
  ----- Method: AbstractSound>>removeEnvelope: (in category 'envelopes') -----
  removeEnvelope: anEnvelope
  	"Remove the given envelope from my envelopes list."
  
  	envelopes := envelopes copyWithout: anEnvelope.
  !

Item was changed:
  ----- Method: AbstractSound>>reset (in category 'sound generation') -----
  reset
  	"Reset my internal state for a replay. Methods that override this method should do super reset."
  
  	mSecsSinceStart := 0.
  	samplesUntilNextControl := 0.
  	envelopes size > 0 ifTrue: [
  		1 to: envelopes size do: [:i | (envelopes at: i) reset]].
  !

Item was changed:
  ----- Method: AbstractSound>>setPitch:dur:loudness: (in category 'initialization') -----
  setPitch: pitchNameOrNumber dur: d loudness: l
  	"Initialize my envelopes for the given parameters. Subclasses overriding this method should include a resend to super."
  
  	| p |
  	p := self nameOrNumberToPitch: pitchNameOrNumber.
  	envelopes do: [:e |
  		e volume: l.
  		e centerPitch: p].
  	self initialVolume: l.
  	self duration: d.
  !

Item was changed:
  ----- Method: AbstractSound>>stopGracefully (in category 'sound generation') -----
  stopGracefully
  	"End this note with a graceful decay. If the note has envelopes, determine the decay time from its envelopes."
  
  	| decayInMs env |
  	envelopes isEmpty
  		ifTrue: [
  			self adjustVolumeTo: 0 overMSecs: 10.
  			decayInMs := 10]
  		ifFalse: [
  			env := envelopes first.
  			decayInMs := env attackTime + env decayTime].
  	self duration: (mSecsSinceStart + decayInMs) / 1000.0.
  	self stopAfterMSecs: decayInMs.
  !

Item was changed:
  ----- Method: AbstractSound>>storeAIFFOnFileNamed: (in category 'file i/o') -----
  storeAIFFOnFileNamed: fileName
  	"Store this sound as a AIFF file of the given name."
  
  	| f |
  	f := (FileStream fileNamed: fileName) binary.
  	self storeAIFFSamplesOn: f.
  	f close.
  !

Item was changed:
  ----- Method: AbstractSound>>storeAIFFSamplesOn: (in category 'file i/o') -----
  storeAIFFSamplesOn: aBinaryStream
  	"Store this sound as a 16-bit AIFF file at the current SoundPlayer sampling rate. Store both channels if self isStereo is true; otherwise, store the left channel only as a mono sound."
  
  	| samplesToStore channelCount dataByteCount |
  	samplesToStore := (self duration * self samplingRate) ceiling.
  	channelCount := self isStereo ifTrue: [2] ifFalse: [1].
  	dataByteCount := samplesToStore * channelCount * 2.
  
  	"write AIFF file header:"
  	aBinaryStream nextPutAll: 'FORM' asByteArray.
  	aBinaryStream nextInt32Put: ((7 * 4) + 18) + dataByteCount.
  	aBinaryStream nextPutAll: 'AIFF' asByteArray.
  	aBinaryStream nextPutAll: 'COMM' asByteArray.
  	aBinaryStream nextInt32Put: 18.
  	aBinaryStream nextNumber: 2 put: channelCount.
  	aBinaryStream nextInt32Put: samplesToStore.
  	aBinaryStream nextNumber: 2 put: 16.  "bits/sample"
  	self storeExtendedFloat: self samplingRate on: aBinaryStream.
  	aBinaryStream nextPutAll: 'SSND' asByteArray.
  	aBinaryStream nextInt32Put: dataByteCount + 8.
  	aBinaryStream nextInt32Put: 0.
  	aBinaryStream nextInt32Put: 0.
  
  	"write data:"
  	self storeSampleCount: samplesToStore bigEndian: true on: aBinaryStream.
  !

Item was changed:
  ----- Method: AbstractSound>>storeExtendedFloat:on: (in category 'file i/o') -----
  storeExtendedFloat: aNumber on: aBinaryStream
  	"Store an Apple extended-precision 80-bit floating point number on the given stream."
  	"Details: I could not find the specification for this format, so constants were determined empirically based on assumption of 1-bit sign, 15-bit exponent, 64-bit mantissa. This format does not seem to have an implicit one before the mantissa as some float formats do."
  
  	| n isNeg exp mantissa |
  	n := aNumber asFloat.
  	isNeg := false.
  	n < 0.0 ifTrue: [
  		n := 0.0 - n.
  		isNeg := true].
  	exp := (n log: 2.0) ceiling.
  	mantissa := (n * (2 raisedTo: 64 - exp)) truncated.
  	exp := exp + 16r4000 - 2.  "not sure why the -2 is needed..."
  	isNeg ifTrue: [exp := exp bitOr: 16r8000].  "set sign bit"
  	aBinaryStream nextPut: ((exp bitShift: -8) bitAnd: 16rFF).
  	aBinaryStream nextPut: (exp bitAnd: 16rFF).
  	8 to: 1 by: -1 do: [:i | aBinaryStream nextPut: (mantissa digitAt: i)].
  !

Item was changed:
  ----- Method: AbstractSound>>storeSample:in:at:leftVol:rightVol: (in category 'sound generation') -----
  storeSample: sample in: aSoundBuffer at: sliceIndex leftVol: leftVol rightVol: rightVol
  	"This method is provided for documentation. To gain 10% more speed when running sound generation in Smalltalk, this method is hand-inlined into all sound generation methods that use it."
  
  	| i s |
  		leftVol > 0 ifTrue: [
  			i := (2 * sliceIndex) - 1.
  			s := (aSoundBuffer at: i) + ((sample * leftVol) // ScaleFactor).
  			s >  32767 ifTrue: [s :=  32767].  "clipping!!"
  			s < -32767 ifTrue: [s := -32767].  "clipping!!"
  			aSoundBuffer at: i put: s].
  		rightVol > 0 ifTrue: [
  			i := 2 * sliceIndex.
  			s := (aSoundBuffer at: i) + ((sample * rightVol) // ScaleFactor).
  			s >  32767 ifTrue: [s :=  32767].  "clipping!!"
  			s < -32767 ifTrue: [s := -32767].  "clipping!!"
  			aSoundBuffer at: i put: s].
  !

Item was changed:
  ----- Method: AbstractSound>>storeSunAudioOnFileNamed: (in category 'file i/o') -----
  storeSunAudioOnFileNamed: fileName
  	"Store this sound as an uncompressed Sun audio file of the given name."
  
  	| f |
  	f := (FileStream fileNamed: fileName) binary.
  	self storeSunAudioSamplesOn: f.
  	f close.
  !

Item was changed:
  ----- Method: AbstractSound>>storeSunAudioSamplesOn: (in category 'file i/o') -----
  storeSunAudioSamplesOn: aBinaryStream
  	"Store this sound as a 16-bit Sun audio file at the current SoundPlayer sampling rate. Store both channels if self isStereo is true; otherwise, store the left channel only as a mono sound."
  
  
  	| samplesToStore channelCount dataByteCount |
  	samplesToStore := (self duration * self samplingRate) ceiling.
  	channelCount := self isStereo ifTrue: [2] ifFalse: [1].
  	dataByteCount := samplesToStore * channelCount * 2.
  
  	"write Sun audio file header"
  	channelCount := self isStereo ifTrue: [2] ifFalse: [1].
  	aBinaryStream nextPutAll: '.snd' asByteArray.
  	aBinaryStream uint32: 24.	"header size in bytes"
  	aBinaryStream uint32: dataByteCount.
  	aBinaryStream uint32: 3.	"format: 16-bit linear"
  	aBinaryStream uint32: self samplingRate truncated.
  	aBinaryStream uint32: channelCount.
  
  	"write data:"
  	self storeSampleCount: samplesToStore bigEndian: true on: aBinaryStream.
  !

Item was changed:
  ----- Method: AbstractSound>>storeWAVOnFileNamed: (in category 'file i/o') -----
  storeWAVOnFileNamed: fileName
  	"Store this sound as a 16-bit Windows WAV file of the given name."
  
  	| f |
  	f := (FileStream fileNamed: fileName) binary.
  	self storeWAVSamplesOn: f.
  	f close.
  !

Item was changed:
  ----- Method: AbstractSound>>storeWAVSamplesOn: (in category 'file i/o') -----
  storeWAVSamplesOn: aBinaryStream
  	"Store this sound as a 16-bit Windows WAV file at the current SoundPlayer sampling rate. Store both channels if self isStereo is true; otherwise, store the left channel only as a mono sound."
  
  	| samplesToStore channelCount dataByteCount samplesPerSec bytesPerSec |
  	samplesToStore := (self duration * self samplingRate) ceiling.
  	channelCount := self isStereo ifTrue: [2] ifFalse: [1].
  	dataByteCount := samplesToStore * channelCount * 2.
  	samplesPerSec := self samplingRate rounded.
  	bytesPerSec := samplesPerSec * channelCount * 2.
  
  	"file header"
  	aBinaryStream
  		nextPutAll: 'RIFF' asByteArray;
  		nextLittleEndianNumber: 4 put: dataByteCount + 36;	"total length of all chunks"
  		nextPutAll: 'WAVE' asByteArray.
  
  	"format chunk"
  	aBinaryStream
  		nextPutAll: 'fmt ' asByteArray;
  		nextLittleEndianNumber: 4 put: 16;	"length of this chunk"
  		nextLittleEndianNumber: 2 put: 1;	"format tag"
  		nextLittleEndianNumber: 2 put: channelCount;
  		nextLittleEndianNumber: 4 put: samplesPerSec;
  		nextLittleEndianNumber: 4 put: bytesPerSec;
  		nextLittleEndianNumber: 2 put: 4;	"alignment"
  		nextLittleEndianNumber: 2 put: 16.	"bits per sample"
  
  	"data chunk"
  	aBinaryStream
  		nextPutAll: 'data' asByteArray;
  		nextLittleEndianNumber: 4 put: dataByteCount.  "length of this chunk"
  
  	self storeSampleCount: samplesToStore bigEndian: false on: aBinaryStream.
  !

Item was changed:
  ----- Method: AbstractSound>>updateVolume (in category 'sound generation') -----
  updateVolume
  	"Increment the volume envelope of this sound. To avoid clicks, the volume envelope must be interpolated at the sampling rate, rather than just at the control rate like other envelopes. At the control rate, the volume envelope computes the slope and next target volume volume for the current segment of the envelope (i.e., it sets the rate of change for the volume parameter). When that target volume is reached, incrementing is stopped until a new increment is set."
  	"This method is provided for documentation. To gain 10% more speed when running sound generation in Smalltalk, it is hand-inlined into all sound generation methods that use it."
  
  		scaledVolIncr ~= 0 ifTrue: [
  			scaledVol := scaledVol + scaledVolIncr.
  			((scaledVolIncr > 0 and: [scaledVol >= scaledVolLimit]) or:
  			 [scaledVolIncr < 0 and: [scaledVol <= scaledVolLimit]])
  				ifTrue: [  "reached the limit; stop incrementing"
  					scaledVol := scaledVolLimit.
  					scaledVolIncr := 0]].
  !

Item was changed:
  ----- Method: AmbientEvent>>morph: (in category 'as yet unclassified') -----
  morph: m
  	morph := m!

Item was changed:
  ----- Method: AmbientEvent>>target:selector:arguments: (in category 'as yet unclassified') -----
  target: t selector: s arguments: a
  	target := t.
  	selector := s.
  	arguments := a.
  !

Item was changed:
  ----- Method: CompressedSoundData>>asSound (in category 'asSound') -----
  asSound
  	"Answer the result of decompressing the receiver."
  
  	| codecClass |
  	codecClass := Smalltalk at: codecName
  		ifAbsent: [^ self error: 'The codec for decompressing this sound is not available'].
  	^ (codecClass new decompressSound: self) reset
  !

Item was changed:
  ----- Method: CompressedSoundData>>channels: (in category 'accessing') -----
  channels: anArray
  
  	channels := anArray.
  !

Item was changed:
  ----- Method: CompressedSoundData>>codecName: (in category 'accessing') -----
  codecName: aStringOrSymbol
  
  	codecName := aStringOrSymbol asSymbol.
  !

Item was changed:
  ----- Method: CompressedSoundData>>firstSample: (in category 'accessing') -----
  firstSample: anInteger
  
  	firstSample := anInteger.
  !

Item was changed:
  ----- Method: CompressedSoundData>>gain: (in category 'accessing') -----
  gain: aNumber
  
  	gain := aNumber.
  !

Item was changed:
  ----- Method: CompressedSoundData>>loopEnd: (in category 'accessing') -----
  loopEnd: anInteger
  
  	loopEnd := anInteger.
  !

Item was changed:
  ----- Method: CompressedSoundData>>loopLength: (in category 'accessing') -----
  loopLength: anInteger
  
  	loopLength := anInteger.
  !

Item was changed:
  ----- Method: CompressedSoundData>>perceivedPitch: (in category 'accessing') -----
  perceivedPitch: aNumber
  
  	perceivedPitch := aNumber.
  !

Item was changed:
  ----- Method: CompressedSoundData>>reset (in category 'asSound') -----
  reset
  	"This message is the cue to start behaving like a real sound in order to be played.
  	We do this by caching a decompressed version of this sound.
  	See also samplesRemaining."
  
  	cachedSound == nil ifTrue: [cachedSound := self asSound].
  	cachedSound reset
  !

Item was changed:
  ----- Method: CompressedSoundData>>samplesRemaining (in category 'asSound') -----
  samplesRemaining
  	"This message is the cue that the cached sound may no longer be needed.
  	We know it is done playing when samplesRemaining=0."
  
  	| samplesRemaining |
  	samplesRemaining := cachedSound samplesRemaining.
  	samplesRemaining <= 0 ifTrue: [cachedSound := nil].
  	^ samplesRemaining!

Item was changed:
  ----- Method: CompressedSoundData>>samplingRate: (in category 'accessing') -----
  samplingRate: aNumber
  
  	samplingRate := aNumber.
  !

Item was changed:
  ----- Method: CompressedSoundData>>soundClassName: (in category 'accessing') -----
  soundClassName: aStringOrSymbol
  
  	soundClassName := aStringOrSymbol asSymbol.
  !

Item was changed:
  ----- Method: CompressedSoundData>>withEToySound:samplingRate: (in category 'as yet unclassified') -----
  withEToySound: aByteArray samplingRate: anInteger
  
  	soundClassName := #SampledSound.
  	channels := {aByteArray}.
  	codecName := #GSMCodec.
  	loopEnd := nil.	"???"
  	loopLength :=  nil.
  	perceivedPitch := 100.0.
  	samplingRate  := anInteger.
  	gain  := 1.0.	"???"
  	firstSample := 1.
  	cachedSound  := nil.	"???"!

Item was changed:
  ----- Method: ControlChangeEvent>>channel: (in category 'accessing') -----
  channel: midiChannel
  
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: ControlChangeEvent>>control: (in category 'accessing') -----
  control: midiControl
  
  	control := midiControl.
  !

Item was changed:
  ----- Method: ControlChangeEvent>>control:value:channel: (in category 'accessing') -----
  control: midiControl value: midiControlValue channel: midiChannel
  
  	control := midiControl.
  	value := midiControlValue.
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: ControlChangeEvent>>value: (in category 'accessing') -----
  value: midiControlValue
  
  	value := midiControlValue.
  !

Item was changed:
  ----- Method: Envelope class>>example (in category 'instance creation') -----
  example
  	"Envelope example"
  
  	| p |
  	p := Array with: 0 at 0 with: 100 at 1.0 with: 250 at 0.7 with: 400 at 1.0 with: 500 at 0.
  	^ (self points: p loopStart: 2 loopEnd: 4) sustainEnd: 1200.
  !

Item was changed:
  ----- Method: Envelope class>>exponentialDecay: (in category 'instance creation') -----
  exponentialDecay: multiplier
  	"(Envelope exponentialDecay: 0.95) "
  
  	| mSecsPerStep pList t v last |
  	mSecsPerStep := 10.
  	((multiplier > 0.0) and: [multiplier < 1.0])
  		ifFalse: [self error: 'multiplier must be greater than 0.0 and less than 1.0'].
  	pList := OrderedCollection new.
  	pList add: 0 at 0.0.
  	last := 0.0.
  	v := 1.0.
  	t := 10.
  	[v > 0.01] whileTrue: [
  		(v - last) abs > 0.02 ifTrue: [
  			"only record substatial changes"
  			pList add: t at v.
  			last := v].
  		t := t + mSecsPerStep.
  		v := v * multiplier].
  	pList add: (t + mSecsPerStep)@0.0.
  
  	^ self points: pList asArray
  		loopStart: pList size 
  		loopEnd: pList size
  !

Item was changed:
  ----- Method: Envelope>>checkParameters (in category 'private') -----
  checkParameters
  	"Verify that the point array, loopStartIndex, and loopStopIndex obey the rules."
  
  	| lastT t |
  	points size > 1
  		ifFalse: [^ self error: 'the point list must contain at least two points'].
  	points first x = 0
  		ifFalse: [^ self error: 'the time of the first point must be zero'].
  	lastT := points first x.
  	2 to: points size do: [:i |
  		t := (points at: i) x.
  		t >= lastT
  			ifFalse: [^ self error: 'the points must be in ascending time order']].
  
  	(loopStartIndex isInteger and:
  	 [(loopStartIndex > 0) and: [loopStartIndex <= points size]])
  		ifFalse: [^ self error: 'loopStartIndex is not a valid point index'].
  	(loopEndIndex isInteger and:
  	 [(loopEndIndex > 0) and: [loopEndIndex <= points size]])
  		ifFalse: [^ self error: 'loopEndIndex is not a valid point index'].
  	 loopStartIndex <= loopEndIndex
  		ifFalse: [^ self error: 'loopEndIndex must not precede loopStartIndex'].
  !

Item was changed:
  ----- Method: Envelope>>computeIncrementAt:between:and:scale: (in category 'private') -----
  computeIncrementAt: mSecs between: p1 and: p2 scale: combinedScale
  	"Compute the current and increment values for the given time between the given inflection points."
  	"Assume: p1 x <= mSecs <= p2 x"
  
  	| valueRange timeRange |
  	valueRange := (p2 y - p1 y) asFloat.
  	timeRange := (p2 x - p1 x) asFloat.
  	currValue := (p1 y + (((mSecs - p1 x) asFloat / timeRange) * valueRange)) * combinedScale.
  	valueIncr := (((p2 y * combinedScale) - currValue) / (p2 x - mSecs)) * 10.0.
  	^ currValue
  !

Item was changed:
  ----- Method: Envelope>>computeValueAtMSecs: (in category 'applying') -----
  computeValueAtMSecs: mSecs
  	"Return the value of this envelope at the given number of milliseconds from its onset. Return zero for times outside the time range of this envelope."
  	"Note: Unlike the private method incrementalComputeValueAtMSecs:, this method does is not increment. Thus it is slower, but it doesn't depend on being called sequentially at fixed time intervals."
  
  	| t i |
  	mSecs < 0 ifTrue: [^ 0.0].
  
  	((loopEndMSecs ~~ nil) and: [mSecs >= loopEndMSecs]) ifTrue: [  "decay phase"
  		t := (points at: loopEndIndex) x + (mSecs - loopEndMSecs).
  		i := self indexOfPointAfterMSecs: t startingAt: loopEndIndex.
  		i == nil ifTrue: [^ 0.0].  "past end"
  		^ (self interpolate: t between: (points at: i - 1) and: (points at: i)) * decayScale].
  
  	mSecs < loopStartMSecs ifTrue: [  "attack phase"
  		i := self indexOfPointAfterMSecs: mSecs startingAt: 1.
  		i = 1 ifTrue: [^ (points at: 1) y * scale].
  		^ self interpolate: mSecs between: (points at: i - 1) and: (points at: i)].
  
  	"sustain phase"
  	loopMSecs = 0 ifTrue: [^ (points at: loopEndIndex) y * scale].  "looping on a single point"
  	t := loopStartMSecs + ((mSecs - loopStartMSecs) \\ loopMSecs).
  	i := self indexOfPointAfterMSecs: t startingAt: loopStartIndex.
  
  	^ self interpolate: t between: (points at: i - 1) and: (points at: i)
  !

Item was changed:
  ----- Method: Envelope>>duration: (in category 'accessing') -----
  duration: seconds
  	"Set the note duration to the given number of seconds."
  	"Details: The duration is reduced by 19 mSec to ensure proper cutoffs even when the sound starts playing between doControl epochs."
  	"Note: This is a hack. With a little additional work on the envelope logic, it should be possible to reduce or eliminate this fudge factor. In particular, an envelope should use the time remaining, rather than time-since-start to determine when to enter its decay phase. In addition, an envelope must be able to cut off in minimum time (~5-10 msec) if there isn't enough time to do their normal decay. All of this is to allow instruments with leisurely decays to play very short notes if necessary (say, when fast-forwarding through a score)." 
  
  	| attack decay endTime |
  	endMSecs := (seconds * 1000.0) asInteger - 19.
  	attack := self attackTime.
  	decay := self decayTime.
  	endMSecs > (attack + decay)
  		ifTrue: [endTime := endMSecs - decay]
  		ifFalse: [
  			endMSecs >= attack
  				ifTrue: [endTime := attack]
  				ifFalse: [endTime := endMSecs]].
  
  	self sustainEnd: (endTime max: 0).
  !

Item was changed:
  ----- Method: Envelope>>incrementalComputeValueAtMSecs: (in category 'private') -----
  incrementalComputeValueAtMSecs: mSecs
  	"Compute the current value, per-step increment, and the time of the next inflection point."
  	"Note: This method is part of faster, but less general, way of computing envelope values. It depends on a known, fixed control updating rate."
  
  	| t i |
  	((loopEndMSecs ~~ nil) and: [mSecs >= loopEndMSecs]) ifTrue: [  "decay phase"
  		t := (points at: loopEndIndex) x + (mSecs - loopEndMSecs).
  		i := self indexOfPointAfterMSecs: t startingAt: loopEndIndex.
  		i == nil ifTrue: [  "past end"
  			currValue := points last y * scale * decayScale.
  			valueIncr := 0.0.
  			nextRecomputeTime := mSecs + 1000000.
  			^ currValue].
  		nextRecomputeTime := mSecs + ((points at: i) x - t).
  		^ self computeIncrementAt: t
  			between: (points at: i - 1)
  			and: (points at: i)
  			scale: scale * decayScale].
  
  	mSecs < loopStartMSecs
  		ifTrue: [  "attack phase"
  			t := mSecs.
  			i := self indexOfPointAfterMSecs: t startingAt: 1.
  			nextRecomputeTime := mSecs + ((points at: i) x - t)]
  		ifFalse: [  "sustain (looping) phase"
  			noChangesDuringLoop ifTrue: [
  				currValue := (points at: loopEndIndex) y * scale.
  				valueIncr := 0.0.
  				loopEndMSecs == nil
  					ifTrue: [nextRecomputeTime := mSecs + 10]  "unknown end time"
  					ifFalse: [nextRecomputeTime := loopEndMSecs].
  				^ currValue].
  			t := loopStartMSecs + ((mSecs - loopStartMSecs) \\ loopMSecs).
  			i := self indexOfPointAfterMSecs: t startingAt: loopStartIndex.
  			nextRecomputeTime := (mSecs + ((points at: i) x - t)) min: loopEndMSecs].
  
  	^ self computeIncrementAt: t
  		between: (points at: i - 1)
  		and: (points at: i)
  		scale: scale.
  !

Item was changed:
  ----- Method: Envelope>>interpolate:between:and: (in category 'private') -----
  interpolate: mSecs between: p1 and: p2
  	"Return the scaled, interpolated value for the given time between the given time points."
  	"Assume: p1 x <= mSecs <= p2 x"
  
  	| valueRange timeRange |
  	valueRange := (p2 y - p1 y) asFloat.
  	valueRange = 0.0 ifTrue: [^ p1 y * scale].
  	timeRange := (p2 x - p1 x) asFloat.
  	^ (p1 y + (((mSecs - p1 x) asFloat / timeRange) * valueRange)) * scale.
  !

Item was changed:
  ----- Method: Envelope>>reset (in category 'applying') -----
  reset
  	"Reset the state for this envelope."
  
  	lastValue := -100000.0.  "impossible value"
  	nextRecomputeTime := 0.
  	self updateTargetAt: 0.
  !

Item was changed:
  ----- Method: Envelope>>scale: (in category 'accessing') -----
  scale: aNumber
  
  	scale := aNumber asFloat.
  !

Item was changed:
  ----- Method: Envelope>>setPoints:loopStart:loopEnd: (in category 'private') -----
  setPoints: pointList loopStart: startIndex loopEnd: endIndex
  
  	| lastVal |
  	points := pointList asArray collect: [:p | p x asInteger @ p y asFloat].
  	loopStartIndex := startIndex.
  	loopEndIndex := endIndex.
  	self checkParameters.
  	loopStartMSecs := (points at: loopStartIndex) x.
  	loopMSecs := (points at: loopEndIndex) x - (points at: loopStartIndex) x.
  	loopEndMSecs := nil.  "unknown end time; sustain until end time is known"
  	scale ifNil: [scale := 1.0].
  	decayScale ifNil: [decayScale := 1.0].
  
  	"note if there are no changes during the loop phase"
  	noChangesDuringLoop := true.
  	lastVal := (points at: loopStartIndex) y.
  	loopStartIndex to: loopEndIndex do: [:i | 
  		(points at: i) y ~= lastVal ifTrue: [
  			noChangesDuringLoop := false.
  			^ self]].
  !

Item was changed:
  ----- Method: Envelope>>sustainEnd: (in category 'applying') -----
  sustainEnd: mSecs
  	"Set the ending time of the sustain phase of this envelope; the decay phase will start this point. Typically derived from a note's duration."
  	"Details: to avoid a sharp transient, the decay phase is scaled so that the beginning of the decay matches the envelope's instantaneous value when the decay phase starts."
  
  	| vIfSustaining firstVOfDecay |
  	loopEndMSecs := nil. "pretend to be sustaining"
  	decayScale := 1.0.
  	nextRecomputeTime := 0.
  	vIfSustaining := self computeValueAtMSecs: mSecs.  "get value at end of sustain phase"
  	loopEndMSecs := mSecs.
  	firstVOfDecay := (points at: loopEndIndex) y * scale.
  	firstVOfDecay = 0.0
  		ifTrue: [decayScale := 1.0]
  		ifFalse: [decayScale := vIfSustaining / firstVOfDecay].
  !

Item was changed:
  ----- Method: Envelope>>target: (in category 'accessing') -----
  target: anObject
  
  	target := anObject.
  !

Item was changed:
  ----- Method: Envelope>>updateSelector: (in category 'accessing') -----
  updateSelector: aSymbol
  
  	updateSelector := aSymbol.
  !

Item was changed:
  ----- Method: Envelope>>updateTargetAt: (in category 'applying') -----
  updateTargetAt: mSecs
  	"Send my updateSelector to the given target object with the value of this envelope at the given number of milliseconds from its onset. Answer true if the value changed."
  
  	| newValue |
  	newValue := self valueAtMSecs: mSecs.
  	newValue = lastValue ifTrue: [^ false].
  	target
  		perform: updateSelector
  		with: newValue.
  	lastValue := newValue.
  	^ true
  !

Item was changed:
  ----- Method: Envelope>>valueAtMSecs: (in category 'applying') -----
  valueAtMSecs: mSecs
  	"Return the value of this envelope at the given number of milliseconds from its onset. Return zero for times outside the time range of this envelope."
  
  	mSecs < 0 ifTrue: [^ 0.0].
  	mSecs < nextRecomputeTime
  		ifTrue: [currValue := currValue + valueIncr]
  		ifFalse: [currValue := self incrementalComputeValueAtMSecs: mSecs].
  	^ currValue
  !

Item was changed:
  ----- Method: FFT>>initializeHammingWindow: (in category 'bulk processing') -----
  initializeHammingWindow: alpha
  	"Initialize the windowing function to the generalized Hamming window. See F. Richard Moore, Elements of Computer Music, p. 100. An alpha of 0.54 gives the Hamming window, 0.5 gives the hanning window."
  
  	| v midPoint |
  	window := FloatArray new: n.
  	midPoint := (n + 1) / 2.0.
  	1 to: n do: [:i |
  		v := alpha + ((1.0 - alpha) * (2.0 * Float pi * ((i - midPoint) / n)) cos).
  		window at: i put: v].
  
  !

Item was changed:
  ----- Method: FFT>>initializeTriangularWindow (in category 'bulk processing') -----
  initializeTriangularWindow
  	"Initialize the windowing function to the triangular, or Parzen, window. See F. Richard Moore, Elements of Computer Music, p. 100."
  
  	| v |
  	window := FloatArray new: n.
  	0 to: (n // 2) - 1 do: [:i |
  		v := i / ((n // 2) - 1).
  		window at: (i + 1) put: v.
  		window at: (n - i) put: v].
  !

Item was changed:
  ----- Method: FFT>>nu: (in category 'initialization') -----
  nu: order
  	"Initialize variables and tables for transforming 2^nu points"
  	|  j perms k |
  	nu := order.
  	n := 2 bitShift: nu-1.
  
  	"Initialize permutation table (bit-reversed indices)"
  	j:=0.
  	perms := WriteStream on: (Array new: n).
  	0 to: n-2 do:
  		[:i |
  		i < j ifTrue: [perms nextPut: i+1; nextPut: j+1].
  		k := n // 2.
  		[k <= j] whileTrue: [j := j-k.  k := k//2].
  		j := j + k].
  	permTable := perms contents.
  
  	"Initialize sin table 0..pi/2 in n/4 steps."
  	sinTable := (0 to: n/4) collect: [:i | (i asFloat / (n//4) * Float pi / 2.0) sin]!

Item was changed:
  ----- Method: FFT>>permuteData (in category 'transforming') -----
  permuteData
  	| i end a b |
  	i := 1.
  	end := permTable size.
  	[i <= end] whileTrue:
  		[a := permTable at: i.
  		b := permTable at: i+1.
  		realData swap: a with: b.
  		imagData swap: a with: b.
  		i := i + 2]!

Item was changed:
  ----- Method: FFT>>pluginPrepareData (in category 'plugin-testing') -----
  pluginPrepareData
  	"The FFT plugin requires data to be represented in WordArrays or FloatArrays"
  	sinTable := sinTable asFloatArray.
  	permTable := permTable asWordArray.
  	realData := realData asFloatArray.
  	imagData := imagData asFloatArray.!

Item was changed:
  ----- Method: FFT>>realData: (in category 'initialization') -----
  realData: real
  	realData := real.
  	imagData := real collect: [:i | 0.0]  "imaginary component all zero"!

Item was changed:
  ----- Method: FFT>>realData:imagData: (in category 'initialization') -----
  realData: real imagData: imag
  	realData := real.
  	imagData := imag!

Item was changed:
  ----- Method: FFT>>samplesPerCycleForIndex: (in category 'testing') -----
  samplesPerCycleForIndex: i
  	"Answer the number of samples per cycle corresponding to a power peak at the given index. Answer zero if i = 1, since an index of 1 corresponds to the D.C. component."
  
  	| windowSize |
  	windowSize := 2 raisedTo: nu.
  	(i < 1 or: [i > (windowSize // 2)]) ifTrue: [^ self error: 'index is out of range'].
  	i = 1 ifTrue: [^ 0].  "the D.C. component"
  	^ windowSize asFloat / (i - 1)
  !

Item was changed:
  ----- Method: FFT>>scaleData (in category 'transforming') -----
  scaleData
  	"Scale all elements by 1/n when doing inverse"
  	| realN |
  	realN := n asFloat.
  	1 to: n do:
  		[:i |
  		realData at: i put: (realData at: i) / realN.
  		imagData at: i put: (imagData at: i) / realN]!

Item was changed:
  ----- Method: FFT>>setSize: (in category 'bulk processing') -----
  setSize: anIntegerPowerOfTwo
  	"Initialize variables and tables for performing an FFT on the given number of samples. The number of samples must be an integral power of two (e.g. 1024). Prepare data for use with the fast primitive."
  
  	self nu: (anIntegerPowerOfTwo log: 2) asInteger.
  	n = anIntegerPowerOfTwo ifFalse: [self error: 'size must be a power of two'].
  	sinTable := sinTable asFloatArray.
  	permTable := permTable asWordArray.
  	realData := FloatArray new: n.
  	imagData := FloatArray new: n.
  	self initializeHammingWindow: 0.54.  "0.54 for Hamming, 0.5 for hanning"
  !

Item was changed:
  ----- Method: FMBassoonSound>>setPitch:dur:loudness: (in category 'as yet unclassified') -----
  setPitch: pitchNameOrNumber dur: d loudness: l
  	"Select a modulation ratio and modulation envelope scale based on my pitch."
  
  	| p modScale |
  	p := self nameOrNumberToPitch: pitchNameOrNumber.
  	modScale := 9.4.
  	p > 100.0 ifTrue: [modScale := 8.3].
  	p > 150.0 ifTrue: [modScale := 6.4].
  	p > 200.0 ifTrue: [modScale := 5.2].
  	p > 300.0 ifTrue: [modScale := 3.9].
  	p > 400.0 ifTrue: [modScale := 2.8].
  	p > 600.0 ifTrue: [modScale := 1.7].
  
  	envelopes size > 0 ifTrue: [
  		envelopes do: [:e |
  			(e updateSelector = #modulation:)
  				ifTrue: [e scale: modScale]]].
  
  	super setPitch: p dur: d loudness: l.
  !

Item was changed:
  ----- Method: FMClarinetSound>>setPitch:dur:loudness: (in category 'initialization') -----
  setPitch: pitchNameOrNumber dur: d loudness: l
  	"Select a modulation ratio and modulation envelope scale based on my pitch."
  
  	| p modScale |
  	p := self nameOrNumberToPitch: pitchNameOrNumber.
  	p < 262.0
  		ifTrue: [modScale := 25.0. self ratio: 4]
  		ifFalse: [modScale := 20.0. self ratio: 2].
  	p > 524.0 ifTrue: [modScale := 8.0].
  
  	envelopes size > 0 ifTrue: [
  		envelopes do: [:e |
  			(e updateSelector = #modulation:)
  				ifTrue: [e scale: modScale]]].
  
  	super setPitch: p dur: d loudness: l.
  !

Item was changed:
  ----- Method: FMSound class>>bass1 (in category 'instruments') -----
  bass1
  	"FMSound bass1 play"
  	"(FMSound lowMajorScaleOn: FMSound bass1) play"
  
  	| snd |
  	snd := FMSound new modulation: 0 ratio: 0.
  	snd addEnvelope: (VolumeEnvelope exponentialDecay: 0.95).
  	^ snd setPitch: 220 dur: 1.0 loudness: 0.3
  !

Item was changed:
  ----- Method: FMSound class>>bassoon1 (in category 'instruments') -----
  bassoon1
  	"FMSound bassoon1 play"
  	"(FMSound lowMajorScaleOn: FMSound bassoon1) play"
  
  	| snd p env |
  	snd := FMBassoonSound new ratio: 1.
  
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 40 at 0.45; add: 90 at 1.0; add: 180 at 0.9; add: 270 at 1.0; add: 320 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 3 loopEnd: 5).
  
  	p := OrderedCollection new.
  	p add: 0 at 0.2; add: 40 at 0.9; add: 90 at 0.6; add: 270 at 0.6; add: 320 at 0.5.
  	env := Envelope points: p loopStart: 3 loopEnd: 4.
  	env updateSelector: #modulation:; scale: 5.05.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>brass1 (in category 'instruments') -----
  brass1
  	"FMSound brass1 play"
  	"(FMSound lowMajorScaleOn: FMSound brass1) play"
  
  	| snd p env |
  	snd := FMSound new modulation: 0 ratio: 1.
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 30 at 0.8; add: 90 at 1.0; add: 120 at 0.9; add: 220 at 0.7; add: 320 at 0.9; add: 360 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 4 loopEnd: 6).
  
  	p := OrderedCollection new.
  	p add: 0 at 0.5; add: 60 at 1.0; add: 120 at 0.8; add: 220 at 0.65; add: 320 at 0.8; add: 360 at 0.0.
  	env := Envelope points: p loopStart: 3 loopEnd: 5.
  	env target: snd; updateSelector: #modulation:; scale: 5.0.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>brass2 (in category 'instruments') -----
  brass2
  	"FMSound brass2 play"
  	"(FMSound lowMajorScaleOn: FMSound brass2) play"
  
  	| snd p env |
  	snd := FMSound new modulation: 1 ratio: 1.
  
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 20 at 1.0; add: 40 at 0.9; add: 100 at 0.7; add: 160 at 0.9; add: 200 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 3 loopEnd: 5).
  
  	p := OrderedCollection new.
  	p add: 0 at 0.5; add: 30 at 1.0; add: 40 at 0.8; add: 100 at 0.7; add: 160 at 0.8; add: 200 at 0.0.
  	env := Envelope points: p loopStart: 3 loopEnd: 5.
  	env updateSelector: #modulation:; scale: 5.0.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>clarinet (in category 'instruments') -----
  clarinet
  	"FMSound clarinet play"
  	"(FMSound lowMajorScaleOn: FMSound clarinet) play"
  
  	| snd p env |
  	snd := FMSound new modulation: 0 ratio: 2.
  
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 60 at 1.0; add: 310 at 1.0; add: 350 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 3).
  
  	p := OrderedCollection new.
  	p add: 0 at 0.0167; add: 60 at 0.106; add: 310 at 0.106; add: 350 at 0.0.
  	env := Envelope points: p loopStart: 2 loopEnd: 3.
  	env updateSelector: #modulation:; scale: 10.0.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>clarinet2 (in category 'instruments') -----
  clarinet2
  	"FMSound clarinet2 play"
  	"(FMSound lowMajorScaleOn: FMSound clarinet2) play"
  
  	| snd p env |
  	snd := FMClarinetSound new modulation: 0 ratio: 2.
  
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 60 at 1.0; add: 310 at 1.0; add: 350 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 3).
  
  	p := OrderedCollection new.
  	p add: 0 at 0.0167; add: 60 at 0.106; add: 310 at 0.106; add: 350 at 0.0.
  	env := Envelope points: p loopStart: 2 loopEnd: 3.
  	env updateSelector: #modulation:; scale: 10.0.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  
  !

Item was changed:
  ----- Method: FMSound class>>flute1 (in category 'instruments') -----
  flute1
  	"FMSound flute1 play"
  	"(FMSound majorScaleOn: FMSound flute1) play"
  
  	| snd p |
  	snd := FMSound new.
  	p := OrderedCollection new.
  	p add: 0 at 0; add: 20 at 1.0; add: 100 at 1.0; add: 120 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 3).
  	^ snd setPitch: 440.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>flute2 (in category 'instruments') -----
  flute2
  	"FMSound flute2 play"
  	"(FMSound majorScaleOn: FMSound flute2) play"
  
  	| snd p |
  	snd := FMSound new.
  	p := OrderedCollection new.
  	p add: 0 at 0; add: 20 at 1.0; add: 100 at 1.0; add: 120 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 3).
  	snd addEnvelope: (RandomEnvelope for: #pitch:).
  	^ snd setPitch: 440.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>initialize (in category 'class initialization') -----
  initialize
  	"Build a sine wave table."
  	"FMSound initialize"
  
  	| tableSize radiansPerStep peak |
  	tableSize := 4000.
  	SineTable := SoundBuffer newMonoSampleCount: tableSize.
  	radiansPerStep := (2.0 * Float pi) / tableSize asFloat.
  	peak := ((1 bitShift: 15) - 1) asFloat.  "range is +/- (2^15 - 1)"
  	1 to: tableSize do: [:i |
  		SineTable at: i put: (peak * (radiansPerStep * (i - 1)) sin) rounded].
  !

Item was changed:
  ----- Method: FMSound class>>marimba (in category 'instruments') -----
  marimba
  	"FMSound marimba play"
  	"(FMSound majorScaleOn: FMSound marimba) play"
  
  	| snd p env |
  	snd := FMSound new modulation: 1 ratio: 0.98.
  
  	p := OrderedCollection new.
  	p add: 0 at 1.0; add: 10 at 0.3; add: 40 at 0.1; add: 80 at 0.02; add: 120 at 0.1; add: 160 at 0.02; add: 220 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 4 loopEnd: 6).
  
  	p := OrderedCollection new.
  	p add: 0 at 1.2; add: 80 at 0.85; add: 120 at 1.0; add: 160 at 0.85; add: 220 at 0.0.
  	env := Envelope points: p loopStart: 2 loopEnd: 4.
  	env updateSelector: #modulation:.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>mellowBrass (in category 'instruments') -----
  mellowBrass
  	"FMSound mellowBrass play"
  	"(FMSound lowMajorScaleOn: FMSound mellowBrass) play"
  
  	| snd p env |
  	snd := FMSound new modulation: 0 ratio: 1.
  
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 70 at 0.325; add: 120 at 0.194; add: 200 at 0.194; add: 320 at 0.194; add: 380 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 3 loopEnd: 5).
  
  	p := OrderedCollection new.
  	p add: 0 at 0.1; add: 70 at 0.68; add: 120 at 0.528; add: 200 at 0.519; add: 320 at 0.528; add: 380 at 0.0.
  	env := Envelope points: p loopStart: 3 loopEnd: 5.
  	env updateSelector: #modulation:; scale: 5.0.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>oboe1 (in category 'instruments') -----
  oboe1
  	"FMSound oboe1 play"
  	"(FMSound majorScaleOn: FMSound oboe1) play"
  
  	| snd p |
  	snd := FMSound new modulation: 1 ratio: 1.
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 10 at 1.0; add: 100 at 1.0; add: 120 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 3).
  	^ snd setPitch: 440.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>oboe2 (in category 'instruments') -----
  oboe2
  	"FMSound oboe2 play"
  	"(FMSound majorScaleOn: FMSound oboe2) play"
  
  	| snd p |
  	snd := FMSound new modulation: 1 ratio: 1.
  	p := OrderedCollection new.
  	p add: 0 at 0; add: 20 at 1.0; add: 100 at 1.0; add: 120 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 3).
  	snd addEnvelope: (RandomEnvelope for: #pitch:).
  	^ snd setPitch: 440.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>organ1 (in category 'instruments') -----
  organ1
  	"FMSound organ1 play"
  	"(FMSound majorScaleOn: FMSound organ1) play"
  
  	| snd p |
  	snd := FMSound new.
  	p := OrderedCollection new.
  	p add: 0 at 0; add: 60 at 1.0; add: 110 at 0.8; add: 200 at 1.0; add: 250 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 4).
  	^ snd setPitch: 440.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>pluckedElecBass (in category 'instruments') -----
  pluckedElecBass
  	"FMSound pluckedElecBass play"
  	"(FMSound lowMajorScaleOn: FMSound pluckedElecBass) play"
  
  	| snd p env |
  	snd := FMSound new modulation: 1 ratio: 3.0.
  
  	p := OrderedCollection new.
  	p add: 0 at 0.4; add: 20 at 1.0; add: 30 at 0.6; add: 100 at 0.6; add: 130 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 3 loopEnd: 4).
  
  	p := OrderedCollection new.
  	p add: 0 at 1.0; add: 20 at 2.0; add: 30 at 4.5; add: 100 at 4.5; add: 130 at 0.0.
  	env := Envelope points: p loopStart: 3 loopEnd: 4.
  	env updateSelector: #modulation:.
  	snd addEnvelope: env.
  
  	p := OrderedCollection new.
  	p add: 0 at 6.0; add: 20 at 4.0; add: 30 at 3.0; add: 100 at 3.0; add: 130 at 3.0.
  	env := Envelope points: p loopStart: 3 loopEnd: 4.
  	env updateSelector: #ratio:.
  	snd addEnvelope: env.
  
  	^ snd setPitch: 220.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>randomWeird1 (in category 'instruments') -----
  randomWeird1
  	"FMSound randomWeird1 play"
  
  	| snd p |
  	snd := FMSound new.
  	snd addEnvelope: (VolumeEnvelope exponentialDecay: 0.96).
  	p := Array with: 0 at 0 with: 100 at 1.0 with: 250 at 0.7 with: 400 at 1.0 with: 500 at 0.
  	snd addEnvelope: (PitchEnvelope points: p loopStart: 2 loopEnd: 4).
  	^ snd setPitch: (150 + 2000 atRandom) dur: 2.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound class>>randomWeird2 (in category 'instruments') -----
  randomWeird2
  	"FMSound randomWeird2 play"
  
  	| snd |
  	snd := FMSound new.
  	snd addEnvelope: (VolumeEnvelope exponentialDecay: 0.96).
  	snd addEnvelope: (PitchEnvelope exponentialDecay: 0.98).
  	^ snd setPitch: (150 + 2000 atRandom) dur: 2.0 loudness: 0.5
  !

Item was changed:
  ----- Method: FMSound>>duration: (in category 'accessing') -----
  duration: seconds
  
  	super duration: seconds.
  	count := initialCount := (seconds * self samplingRate) rounded.
  !

Item was changed:
  ----- Method: FMSound>>initialize (in category 'initialization') -----
  initialize
  
  	super initialize.
  	waveTable := SineTable.
  	scaledWaveTableSize := waveTable size * ScaleFactor.
  	self setPitch: 440.0 dur: 1.0 loudness: 0.2.
  !

Item was changed:
  ----- Method: FMSound>>internalizeModulationAndRatio (in category 'accessing') -----
  internalizeModulationAndRatio
  	"Recompute the internal state for the modulation index and frequency ratio relative to the current pitch."
  
  	modulation < 0.0 ifTrue: [modulation := modulation negated].
  	multiplier < 0.0 ifTrue: [multiplier := multiplier negated].
  	normalizedModulation :=
  		((modulation * scaledIndexIncr)  / ScaleFactor) asInteger.
  	scaledOffsetIndexIncr := (multiplier * scaledIndexIncr) asInteger.
  
  	"clip to maximum values if necessary"
  	normalizedModulation > MaxScaledValue ifTrue: [
  		normalizedModulation := MaxScaledValue.
  		modulation := (normalizedModulation * ScaleFactor) asFloat / scaledIndexIncr].
  	scaledOffsetIndexIncr > (scaledWaveTableSize // 2) ifTrue: [
  		scaledOffsetIndexIncr := scaledWaveTableSize // 2.
  		multiplier := scaledOffsetIndexIncr asFloat / scaledIndexIncr].
  !

Item was changed:
  ----- Method: FMSound>>modulation: (in category 'accessing') -----
  modulation: mod
  	"Set the FM modulation index. Typical values range from 0 (no modulation) to 5, although values up to about 10 are sometimes useful."
  	"Warning: This method is intended primarily for use by envelopes. For efficiency during envelope processing, this change will not take effect until internalizeModulationAndRatio is called."
  
  	modulation := mod asFloat.
  !

Item was changed:
  ----- Method: FMSound>>modulation:ratio: (in category 'accessing') -----
  modulation: mod ratio: freqRatio
  	"Set the modulation index and carrier to modulation frequency ratio for this sound, and compute the internal state that depends on these parameters."
  
  	modulation := mod asFloat.
  	multiplier := freqRatio asFloat.
  	self internalizeModulationAndRatio.
  !

Item was changed:
  ----- Method: FMSound>>pitch: (in category 'accessing') -----
  pitch: p
  	"Warning: Since the modulation and ratio are relative to the current pitch, some internal state must be recomputed when the pitch is changed. However, for efficiency during envelope processing, this compuation will not be done until internalizeModulationAndRatio is called."
  
  	scaledIndexIncr :=
  		((p asFloat * waveTable size asFloat * ScaleFactor asFloat) / self samplingRate asFloat) asInteger
  			min: (waveTable size // 2) * ScaleFactor.
  !

Item was changed:
  ----- Method: FMSound>>ratio: (in category 'accessing') -----
  ratio: freqRatio
  	"Set the FM modulation to carrier frequency ratio."
  	"Warning: This method is intended primarily for use by envelopes. For efficiency during envelope processing, this change will not take effect until internalizeModulationAndRatio is called."
  
  	multiplier := freqRatio asFloat.
  !

Item was changed:
  ----- Method: FMSound>>reset (in category 'sound generation') -----
  reset
  
  	self internalizeModulationAndRatio.
  	super reset.
  	count := initialCount.
  	scaledIndex := 0.
  	scaledOffsetIndex := 0.
  !

Item was changed:
  ----- Method: FMSound>>setPitch:dur:loudness: (in category 'initialization') -----
  setPitch: pitchNameOrNumber dur: d loudness: vol
  	"(FMSound pitch: 'a4' dur: 2.5 loudness: 0.4) play"
  
  	super setPitch: pitchNameOrNumber dur: d loudness: vol.
  	modulation ifNil: [modulation := 0.0].
  	multiplier ifNil: [multiplier := 0.0].
  	self pitch: (self nameOrNumberToPitch: pitchNameOrNumber).
  	self reset.
  !

Item was changed:
  ----- Method: FMSound>>setWavetable: (in category 'initialization') -----
  setWavetable: anArray
  	"(AbstractSound lowMajorScaleOn: (FMSound new setWavetable: AA)) play"
  
  	| samples p dur vol |
  	"copy the array into a SoundBuffer if necessary"
  	anArray class isPointers
  		ifTrue: [samples := SoundBuffer fromArray: anArray]
  		ifFalse: [samples := anArray].
  
  	p := self pitch.
  	dur := self duration.
  	vol := self loudness.
  	waveTable := samples.
  	scaledWaveTableSize := waveTable size * ScaleFactor.
  	self setPitch: p dur: dur loudness: vol.
  !

Item was changed:
  ----- Method: FMSound>>stopAfterMSecs: (in category 'sound generation') -----
  stopAfterMSecs: mSecs
  	"Terminate this sound this note after the given number of milliseconds."
  
  	count := (mSecs * self samplingRate) // 1000.
  !

Item was changed:
  ----- Method: FMSound>>storeOn: (in category 'storing') -----
  storeOn: strm
  	| env |
  	strm nextPutAll: '(((FMSound';
  		nextPutAll: ' pitch: '; print: self pitch;
  		nextPutAll: ' dur: '; print: self duration;
  		nextPutAll: ' loudness: '; print: self loudness; nextPutAll: ')';
  		nextPutAll: ' modulation: '; print: self modulation;
  		nextPutAll: ' ratio: '; print: self ratio; nextPutAll: ')'.
  	1 to: envelopes size do:
  		[:i | env := envelopes at: i.
  		strm cr; nextPutAll: '    addEnvelope: '. env storeOn: strm.
  		i < envelopes size ifTrue: [strm nextPutAll: ';']].
  	strm  nextPutAll: ')'.
  !

Item was changed:
  ----- Method: FWT>>coeffs (in category 'access') -----
  coeffs
  	"Return all coefficients needed to reconstruct the original samples"
  	| header csize strm |
  	header := Array with: nSamples with: nLevels with: alpha with: beta.
  	csize := header size.
  	1 to: nLevels do: [:i | csize := csize + (transform at: i*2) size].
  	csize := csize + (transform at: nLevels*2-1) size.
  	coeffs := Array new: csize.
  	strm := WriteStream on: coeffs.
  	strm nextPutAll: header.
  	1 to: nLevels do: [:i | strm nextPutAll: (transform at: i*2)].
  	strm nextPutAll: (transform at: nLevels*2-1).
  	^ coeffs!

Item was changed:
  ----- Method: FWT>>coeffs: (in category 'access') -----
  coeffs: coeffArray
  	"Initialize this instance from the given coeff array (including header)."
  	| header strm |
  	strm := ReadStream on: coeffArray.
  	header := strm next: 4.
  	self nSamples: header first nLevels: header second.
  	self setAlpha: header third beta: header fourth.
  	1 to: nLevels do: [:i | transform at: i*2 put: (strm next: (transform at: i*2) size)].
  	transform at: nLevels*2-1 put: (strm next: (transform at: nLevels*2-1) size).
  	strm atEnd ifFalse: [self error: 'Data size error'].
  !

Item was changed:
  ----- Method: FWT>>convolveAndDec:dataLen:filter:out: (in category 'computation') -----
  convolveAndDec: inData dataLen: inLen filter: filter out: outData
  	"convolve the input sequence with the filter and decimate by two"
  	| filtLen offset outi dotp |
  	filtLen := filter size.
  	outi := 1.
  	1 to: inLen+9 by: 2 do:
  		[:i | 
  		i < filtLen
  		ifTrue:
  			[dotp := self dotpData: inData endIndex: i filter: filter
  						start: 1 stop: i inc: 1]
  		ifFalse:
  			[i > (inLen+5)
  			ifTrue:
  				[offset := i - (inLen+5).
  				dotp := self dotpData: inData endIndex: inLen+5 filter: filter
  						start: 1+offset stop: filtLen inc: 1]
  			ifFalse:
  				[dotp := self dotpData: inData endIndex: i filter: filter
  						start: 1 stop: filtLen inc: 1]].
  		outData at: outi put: dotp.
  		outi := outi + 1]!

Item was changed:
  ----- Method: FWT>>convolveAndInt:dataLen:filter:sumOutput:into: (in category 'computation') -----
  convolveAndInt: inData dataLen: inLen filter: filter sumOutput:
  sumOutput into: outData
  	"insert zeros between each element of the input sequence and
  	   convolve with the filter to interpolate the data"
  	| outi filtLen oddTerm evenTerm j |
  	outi := 1.
  	filtLen := filter size.
  
  	"every other dot product interpolates the data"
  	filtLen // 2 to: inLen + filtLen - 2 do:
  		[:i |
  		oddTerm := self dotpData: inData endIndex: i filter: filter
  									start: 2 stop: filter size inc: 2.
  		evenTerm := self dotpData: inData endIndex: i+1 filter: filter
  									start: 1 stop: filter size inc: 2.
  		sumOutput
  			ifTrue:
  				["summation with previous convolution if true"
  				outData at: outi put: (outData at: outi) + oddTerm.
  				outData at: outi+1 put: (outData at: outi+1) + evenTerm]
  			ifFalse:
  				["first convolution of pair if false"
  				outData at: outi put: oddTerm.
  				outData at: outi+1 put: evenTerm].
  		outi := outi + 2].
  
  	"Ought to be able to fit this last term into the above loop."
  	j := inLen + filtLen - 1.
  	oddTerm := self dotpData: inData endIndex: j filter: filter
  									start: 2 stop: filter size inc: 2.
  	sumOutput
  		ifTrue: [outData at: outi put: (outData at: outi) + oddTerm]
  		ifFalse: [outData at: outi put: oddTerm].
  !

Item was changed:
  ----- Method: FWT>>doWaveDemo (in category 'testing') -----
  doWaveDemo  "FWT new doWaveDemo"
  	"Printing the above should yield a small number -- I get 1.1e-32"
  	| originalData |
  	self nSamples: 312 nLevels: 3.
  	self setAlpha: 0.0 beta: 0.0.
  
  	"Install a sine wave as sample data"
  	self samples: ((1 to: nSamples) collect: [:i | ((i-1) * 0.02 * Float pi) sin]).
  	originalData := samples copy.
  	FFT new plot: (samples copyFrom: 1 to: nSamples) in: (0 at 0 extent: nSamples at 100).
  
  	"Transform forward and plot the decomposition"
  	self transformForward: true.
  	transform withIndexDo:
  		[:w :i |
  		FFT new plot: (w copyFrom: 1 to: w size-5)
  			in: (i-1\\2*320@(i+1//2*130) extent: (w size-5)@100)].
  
  	"Test copy out and read in the transform coefficients"
  	self coeffs: self coeffs.
  
  	"Ttransform back, plot the reconstruction, and return the error figure"
  	self transformForward: false.
  	FFT new plot: (samples copyFrom: 1 to: nSamples) in: (320 at 0 extent: nSamples at 100).
  	^ self meanSquareError: originalData!

Item was changed:
  ----- Method: FWT>>dotpData:endIndex:filter:start:stop:inc: (in category 'computation') -----
  dotpData: data endIndex: endIndex filter: filter start: start stop: stop inc: inc
  	| sum i j |
  	sum := 0.0.
  	j := endIndex.
  	i := start.
  	[i <= stop] whileTrue:
  		[sum := sum + ((data at: j) * (filter at: i)).
  		i := i + inc.
  		j := j - 1].
  	^ sum!

Item was changed:
  ----- Method: FWT>>meanSquareError: (in category 'testing') -----
  meanSquareError: otherData
  	"Return the mean-square error between the current sample array and
  	some other data, presumably to evaluate a compression scheme."
  	| topSum bottomSum pointDiff |
  	topSum := bottomSum := 0.0.
  	1 to: nSamples do:
  		[:i |  pointDiff := (samples at: i) - (otherData at: i).
  		topSum := topSum + (pointDiff * pointDiff).
  		bottomSum := bottomSum + ((otherData at: i) * (otherData at: i))].
  	^ topSum / bottomSum!

Item was changed:
  ----- Method: FWT>>nSamples:nLevels: (in category 'initialization') -----
  nSamples: n nLevels: nLevs
  	"Initialize a wavelet transform."
  	"Note the sample array size must be N + 5, where N is a multiple of 2^nLevels"
  	| dyadSize |
  	(n // (1 bitShift: nLevs)) > 0 ifFalse: [self error: 'Data size error'].
  	(n \\ (1 bitShift: nLevs)) = 0 ifFalse: [self error: 'Data size error'].
  	nSamples := n.
  	samples := Array new: n + 5.
  	nLevels := nLevs.
  	transform := Array new: nLevels*2.  "Transformed data is stored as a tree of coeffs"
  	dyadSize := nSamples.
  	1 to: nLevels do:
  		[:i |  dyadSize := dyadSize // 2.
  		transform at: 2*i-1 put: (Array new: dyadSize + 5).
  		transform at: 2*i put: (Array new: dyadSize + 5)]!

Item was changed:
  ----- Method: FWT>>setAlpha:beta: (in category 'initialization') -----
  setAlpha: alph beta: bet
  	"Set alpha and beta, compute wavelet coeefs, and derive hFilter and lFilter"
  	| tcosa tcosb tsina tsinb |
  	alpha := alph.
  	beta := bet.
  
  	"WaveletCoeffs..."
  	"precalculate cosine of alpha and sine of beta"
  	tcosa := alpha cos.
  	tcosb := beta cos.
  	tsina := alpha sin.
  	tsinb := beta sin.
  	coeffs := Array new: 6.
  	
  	"calculate first two wavelet coefficients a := a(-2) and b := a(-1)"
  	coeffs at: 1 put: ((1.0 + tcosa + tsina) * (1.0 - tcosb - tsinb)
  					+ (2.0 * tsinb * tcosa)) / 4.0.
  	coeffs at: 2 put: ((1.0 - tcosa + tsina) * (1.0 + tcosb - tsinb)
  					- (2.0 * tsinb * tcosa)) / 4.0.
  
  	"precalculate cosine and sine of alpha minus beta"
  	tcosa := (alpha - beta) cos.
  	tsina := (alpha - beta) sin.
  
  	"calculate last four wavelet coefficients c := a(0), d := a(1), e := a(2), and f := a(3)"
  	coeffs at: 3 put: (1.0 + tcosa + tsina) / 2.0.
  	coeffs at: 4 put: (1.0 + tcosa - tsina) / 2.0.
  	coeffs at: 5 put: 1.0 - (coeffs at: 1) - (coeffs at: 3).
  	coeffs at: 6 put: 1.0 - (coeffs at: 2) - (coeffs at: 4).
  
  	"MakeFiltersFromCoeffs..."
  	"Select the non-zero wavelet coefficients"
  	coeffs := coeffs copyFrom: (coeffs findFirst: [:c | c abs > 1.0e-14])
  						to: (coeffs findLast: [:c | c abs > 1.0e-14]).
  
  	"Form the low pass and high pass filters for decomposition"
  	hTilde := coeffs reversed collect: [:c | c / 2.0].
  	gTilde := coeffs collect: [:c | c / 2.0].
  	1 to: gTilde size by: 2 do:
  		[:i | gTilde at: i put: (gTilde at: i) negated].
  
  	"Form the low pass and high pass filters for reconstruction"
  	h := coeffs copy.
  	g := coeffs reversed.
  	2 to: g size by: 2 do:
  		[:i | g at: i put: (g at: i) negated]
  !

Item was changed:
  ----- Method: FWT>>transformForward: (in category 'computation') -----
  transformForward: forward
  	| inData inLen outData |
  	forward
  	ifTrue:
  		["first InData is input signal, following are intermediate approx coefficients"
  		inData := samples.  inLen := nSamples.
  		1 to: nLevels do:
  			[:i |
  			self convolveAndDec: inData dataLen: inLen
  					filter: hTilde out: (transform at: 2*i-1).
  			self convolveAndDec: inData dataLen: inLen
  					filter: gTilde out: (transform at: 2*i).
  			inData := transform at: 2*i-1.  inLen := inLen // 2]]
  	ifFalse:
  		[inLen := nSamples >> nLevels.
  		"all but last outData are next higher intermediate approximations,
  		last is final reconstruction of samples"
  		nLevels to: 1 by: -1 do:
  			[:i |
  			outData := i = 1 ifTrue: [samples]
  						ifFalse: [transform at: 2*(i-1)-1].
  			self convolveAndInt: (transform at: 2*i-1) dataLen: inLen
  					filter: h sumOutput: false into: outData.
  			self convolveAndInt: (transform at: 2*i) dataLen: inLen
  					filter: g sumOutput: true into: outData.
  			inLen := inLen * 2]]
  !

Item was changed:
  ----- Method: GSMCodec>>decodeFrames:from:at:into:at: (in category 'subclass responsibilities') -----
  decodeFrames: frameCount from: srcByteArray at: srcIndex into: dstSoundBuffer at: dstIndex
  
  	| p |
  	p := self	primDecode: decodeState frames: frameCount
  			from: srcByteArray at: srcIndex
  			into: dstSoundBuffer at: dstIndex.
  	^ Array with: p x with: p y
  !

Item was changed:
  ----- Method: GSMCodec>>encodeFrames:from:at:into:at: (in category 'subclass responsibilities') -----
  encodeFrames: frameCount from: srcSoundBuffer at: srcIndex into: dstByteArray at: dstIndex
  
  	| p |
  	p := self	primEncode: encodeState frames: frameCount
  			from: srcSoundBuffer at: srcIndex
  			into: dstByteArray at: dstIndex.
  	^ Array with: p x with: p y
  !

Item was changed:
  ----- Method: GSMCodec>>reset (in category 'subclass responsibilities') -----
  reset
  	"Reset my encoding/decoding state to prepare to encode or decode a new sound stream."
  
  	encodeState := self primNewState.
  	decodeState := self primNewState.
  !

Item was changed:
  ----- Method: LoopedSampledSound class>>initialize (in category 'class initialization') -----
  initialize
  	"LoopedSampledSound initialize"
  
  	LoopIndexScaleFactor := 512.
  	FloatLoopIndexScaleFactor := LoopIndexScaleFactor asFloat.
  	LoopIndexFractionMask := LoopIndexScaleFactor - 1.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>addReleaseEnvelope (in category 'initialization') -----
  addReleaseEnvelope
  	"Add a simple release envelope to this sound."
  
  	| p env |
  	p := OrderedCollection new.
  	p add: 0 at 1.0; add: 10 at 1.0; add: 100 at 1.0; add: 120 at 0.0.
  	env := (VolumeEnvelope points: p loopStart: 2 loopEnd: 3) target: self.
  	envelopes size > 0 ifTrue: [  "remove any existing volume envelopes"
  		envelopes copy do: [:e |
  			(e isKindOf: VolumeEnvelope) ifTrue: [self removeEnvelope: e]]].
  	self addEnvelope: env.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>beUnlooped (in category 'accessing') -----
  beUnlooped
  
  	scaledLoopLength := 0.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>comeFullyUpOnReload: (in category 'disk i/o') -----
  comeFullyUpOnReload: smartRefStream
  	"Convert my sample buffers from ByteArrays into SampleBuffers after raw loading from a DataStream. Answer myself."
  
  	leftSamples == rightSamples
  		ifTrue: [
  			leftSamples := SoundBuffer fromByteArray: self leftSamples.
  			rightSamples := leftSamples]
  		ifFalse: [
  			leftSamples := SoundBuffer fromByteArray: self leftSamples.
  			rightSamples := SoundBuffer fromByteArray: self rightSamples].
  
  !

Item was changed:
  ----- Method: LoopedSampledSound>>computeSampleCountForRelease (in category 'initialization') -----
  computeSampleCountForRelease
  	"Calculate the number of samples before the end of the note after which looping back will be be disabled. The units of this value, sampleCountForRelease, are samples at the original sampling rate. When playing a specific note, this value is converted to releaseCount, which is number of samples to be computed at the current pitch and sampling rate."
  	"Details: For short loops, set the sampleCountForRelease to the loop length plus the number of samples between loopEnd and lastSample. Otherwise, set it to 1/10th of a second worth of samples plus the number of samples between loopEnd and lastSample. In this case, the trailing samples will be played only if the last loop-back occurs within 1/10th of a second of the total note duration, and the note may be shortened by up to 1/10th second. For long loops, this is the best we can do."
  
  	(scaledLoopLength > 0 and: [lastSample > loopEnd])
  		ifTrue: [
  			sampleCountForRelease := (lastSample - loopEnd) +
  				(self loopLength min: (originalSamplingRate / 10.0)) asInteger]
  		ifFalse: [sampleCountForRelease := 0].
  
  	releaseCount := sampleCountForRelease.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>downSampleLowPassFiltering: (in category 'private') -----
  downSampleLowPassFiltering: doFiltering
  	"Cut my sampling rate in half. Use low-pass filtering (slower) if doFiltering is true."
  	"Note: This operation loses information, and modifies the receiver in place."
  
  	| stereo newLoopLength |
  	stereo := self isStereo.
  	leftSamples := leftSamples downSampledLowPassFiltering: doFiltering.
  	stereo
  		ifTrue: [rightSamples := rightSamples downSampledLowPassFiltering: doFiltering]
  		ifFalse: [rightSamples := leftSamples].
  	originalSamplingRate := originalSamplingRate / 2.0.
  	loopEnd odd
  		ifTrue: [newLoopLength := (self loopLength / 2.0) + 0.5]
  		ifFalse: [newLoopLength := self loopLength / 2.0].
  	firstSample := (firstSample + 1) // 2.
  	lastSample := (lastSample + 1) // 2.
  	loopEnd := (loopEnd + 1) // 2.
  	scaledLoopLength := (newLoopLength * LoopIndexScaleFactor) asInteger.
  	scaledIndexIncr := scaledIndexIncr // 2.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>duration: (in category 'accessing') -----
  duration: seconds
  
  	super duration: seconds.
  	count := initialCount := (seconds * self samplingRate) rounded.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>fftAt: (in category 'other') -----
  fftAt: startIndex
  	"Answer the Fast Fourier Transform (FFT) of my samples (only the left channel, if stereo) starting at the given index."
  
  	| availableSamples fftWinSize |
  	availableSamples := (leftSamples size - startIndex) + 1.
  	fftWinSize := 2 raisedTo: (((availableSamples - 1) log: 2) truncated + 1).
  	fftWinSize := fftWinSize min: 4096.
  	fftWinSize > availableSamples ifTrue: [fftWinSize := fftWinSize / 2].
  	^ self fftWindowSize: fftWinSize startingAt: startIndex
  !

Item was changed:
  ----- Method: LoopedSampledSound>>fftWindowSize:startingAt: (in category 'private') -----
  fftWindowSize: windowSize startingAt: startIndex
  	"Answer a Fast Fourier Transform (FFT) of the given number of samples starting at the given index (the left channel only, if stereo). The window size will be rounded up to the nearest power of two greater than the requested size. There must be enough samples past the given starting index to accomodate this window size."
  
  	| nu n fft |
  	nu := ((windowSize - 1) log: 2) truncated + 1.
  	n := 2 raisedTo: nu.
  	fft := FFT new nu: nu.
  	fft realData: ((startIndex to: startIndex + n - 1) collect: [:i | leftSamples at: i]).
  	^ fft transformForward: true.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>findStartPointAfter: (in category 'other') -----
  findStartPointAfter: index
  	"Answer the index of the last zero crossing sample before the given index."
  
  	| i |
  	i := index min: lastSample.
  
  	"scan backwards to the last zero-crossing"
  	(leftSamples at: i) > 0
  		ifTrue: [
  			[i > 1 and: [(leftSamples at: i) > 0]] whileTrue: [i := i - 1]]
  		ifFalse: [
  			[i > 1 and: [(leftSamples at: i) < 0]] whileTrue: [i := i - 1]].
  	^ i
  !

Item was changed:
  ----- Method: LoopedSampledSound>>findStartPointForThreshold: (in category 'other') -----
  findStartPointForThreshold: threshold
  	"Answer the index of the last zero crossing sample before the first sample whose absolute value (in either the right or left channel) exceeds the given threshold."
  
  	| i |
  	i := self indexOfFirstPointOverThreshold: threshold.
  	i >= lastSample ifTrue: [^ self error: 'no sample exceeds the given threshold'].
  
  	"scan backwards to the last zero-crossing"
  	(leftSamples at: i) > 0
  		ifTrue: [
  			[i > 1 and: [(leftSamples at: i) > 0]] whileTrue: [i := i - 1]]
  		ifFalse: [
  			[i > 1 and: [(leftSamples at: i) < 0]] whileTrue: [i := i - 1]].
  	^ i
  !

Item was changed:
  ----- Method: LoopedSampledSound>>firstSample: (in category 'accessing') -----
  firstSample: aNumber
  
  	firstSample := (aNumber asInteger max: 1) min: lastSample.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>fromAIFFFileNamed:mergeIfStereo: (in category 'initialization') -----
  fromAIFFFileNamed: fileName mergeIfStereo: mergeFlag
  	"Initialize this sound from the data in the given AIFF file. If mergeFlag is true and the file is stereo, its left and right channels are mixed together to produce a mono sampled sound."
  
  	| aiffFileReader |
  	aiffFileReader := AIFFFileReader new.
  	aiffFileReader readFromFile: fileName
  		mergeIfStereo: mergeFlag
  		skipDataChunk: false.
  	aiffFileReader isLooped
  		ifTrue: [
  			self samples: aiffFileReader leftSamples
  				loopEnd: aiffFileReader loopEnd
  				loopLength: aiffFileReader loopLength
  				pitch: aiffFileReader pitch
  				samplingRate: aiffFileReader samplingRate]
  		ifFalse: [
  			self unloopedSamples: aiffFileReader leftSamples
  				pitch: aiffFileReader pitch
  				samplingRate: aiffFileReader samplingRate].
  
  	"the following must be done second, since the initialization above sets
  	 leftSamples and rightSamples to the same sample data"
  	aiffFileReader isStereo
  		ifTrue: [rightSamples := aiffFileReader rightSamples].
  
  	initialCount := (leftSamples size * self samplingRate) // originalSamplingRate.
  	self loudness: 1.0.
  
  	self addReleaseEnvelope.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>gain: (in category 'accessing') -----
  gain: aNumber
  
  	gain := aNumber asFloat.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>highestSignificantFrequencyAt: (in category 'other') -----
  highestSignificantFrequencyAt: startIndex
  	"Answer the highest significant frequency in the sample window starting at the given index. The a frequency is considered significant if it's power is at least 1/50th that of the maximum frequency component in the frequency spectrum."
  
  	| fft powerArray threshold indices |
  	fft := self fftAt: startIndex.
  	powerArray := self normalizedResultsFromFFT: fft.
  	threshold := powerArray max / 50.0.
  	indices := (1 to: powerArray size) select: [:i | (powerArray at: i) > threshold].
  	^ originalSamplingRate / (fft samplesPerCycleForIndex: indices last)
  !

Item was changed:
  ----- Method: LoopedSampledSound>>indexOfFirstPointOverThreshold: (in category 'other') -----
  indexOfFirstPointOverThreshold: threshold
  	"Answer the index of the first sample whose absolute value exceeds the given threshold."
  
  	| s |
  	leftSamples == rightSamples
  		ifTrue: [
  			1 to: lastSample do: [:i |
  				s := leftSamples at: i.
  				s < 0 ifTrue: [s := 0 - s].
  				s > threshold ifTrue: [^ i]]]
  		ifFalse: [
  			1 to: lastSample do: [:i |
  				s := leftSamples at: i.
  				s < 0 ifTrue: [s := 0 - s].
  				s > threshold ifTrue: [^ i].
  				s := rightSamples at: i.
  				s < 0 ifTrue: [s := 0 - s].
  				s > threshold ifTrue: [^ i]]].
  	^ lastSample + 1
  !

Item was changed:
  ----- Method: LoopedSampledSound>>initialize (in category 'initialization') -----
  initialize
  	"This default initialization creates a loop consisting of a single cycle of a sine wave."
  	"(LoopedSampledSound pitch: 440.0 dur: 1.0 loudness: 0.4) play"
  
  	| samples |
  	super initialize.
  	samples := FMSound sineTable.
  	self samples: samples
  		loopEnd: samples size
  		loopLength: samples size
  		pitch: 1.0
  		samplingRate: samples size.
  	self addReleaseEnvelope.
  	self setPitch: 440.0 dur: 1.0 loudness: 0.5.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>leftSamples: (in category 'accessing') -----
  leftSamples: aSampleBuffer
  
  	leftSamples := aSampleBuffer.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>normalizedResultsFromFFT: (in category 'private') -----
  normalizedResultsFromFFT: fft
  	"Answer an array whose size is half of the FFT window size containing power in each frequency band, normalized to the average power over the entire FFT. A value of 10.0 in this array thus means that the power at the corresponding frequences is ten times the average power across the entire FFT."
  
  	| r avg |
  	r := (1 to: fft realData size // 2) collect:
  		[:i | ((fft realData at: i) squared + (fft imagData at: i) squared) sqrt].
  	avg := r sum / r size.
  	^ r collect: [:v | v / avg].
  !

Item was changed:
  ----- Method: LoopedSampledSound>>pitch: (in category 'accessing') -----
  pitch: p
  
  	scaledIndexIncr :=
  		((p asFloat * originalSamplingRate * FloatLoopIndexScaleFactor) /
  		 (perceivedPitch * self samplingRate asFloat)) asInteger.
  
  	sampleCountForRelease > 0
  		ifTrue: [releaseCount := (sampleCountForRelease * LoopIndexScaleFactor) // scaledIndexIncr]
  		ifFalse: [releaseCount := 0].
  !

Item was changed:
  ----- Method: LoopedSampledSound>>reset (in category 'sound generation') -----
  reset
  
  	super reset.
  	count := initialCount.
  	scaledIndex := firstSample * LoopIndexScaleFactor.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>rightSamples: (in category 'accessing') -----
  rightSamples: aSampleBuffer
  
  	rightSamples := aSampleBuffer.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>samples:loopEnd:loopLength:pitch:samplingRate: (in category 'initialization') -----
  samples: aSoundBuffer loopEnd: loopEndIndex loopLength: loopSampleCount pitch: perceivedPitchInHz samplingRate: samplingRateInHz
  	"Make this sound use the given samples array with a loop of the given length starting at the given index. The loop length may have a fractional part; this is necessary to achieve pitch accuracy for short loops."
  
  	| loopStartIndex |
  	super initialize.
  	loopStartIndex := (loopEndIndex - loopSampleCount) truncated + 1.
  	((1 <= loopStartIndex) and:
  	 [loopStartIndex < loopEndIndex and:
  	 [loopEndIndex <= aSoundBuffer size]])
  		ifFalse: [self error: 'bad loop parameters'].
  
  	leftSamples := rightSamples := aSoundBuffer.
  	originalSamplingRate := samplingRateInHz asFloat.
  	perceivedPitch := perceivedPitchInHz asFloat.
  	gain := 1.0.
  	firstSample := 1.
  	lastSample := leftSamples size.
  	lastSample >= (SmallInteger maxVal // LoopIndexScaleFactor) ifTrue: [
  		self error: 'cannot handle more than ',
  			(SmallInteger maxVal // LoopIndexScaleFactor) printString, ' samples'].
  	loopEnd := loopEndIndex.
  	scaledLoopLength := (loopSampleCount * LoopIndexScaleFactor) asInteger.
  	scaledIndexIncr := (samplingRateInHz * LoopIndexScaleFactor) // self samplingRate.
  	self computeSampleCountForRelease.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>stopAfterMSecs: (in category 'sound generation') -----
  stopAfterMSecs: mSecs
  	"Terminate this sound this note after the given number of milliseconds."
  
  	count := (mSecs * self samplingRate) // 1000.
  !

Item was changed:
  ----- Method: LoopedSampledSound>>unloopedSamples:pitch:samplingRate: (in category 'initialization') -----
  unloopedSamples: aSoundBuffer pitch: perceivedPitchInHz samplingRate: samplingRateInHz
  	"Make this sound play the given samples unlooped. The samples have the given perceived pitch when played at the given sampling rate. By convention, unpitched sounds such as percussion sounds should specify a pitch of nil or 100 Hz."
  
  	super initialize.
  	leftSamples := rightSamples := aSoundBuffer.
  	originalSamplingRate := samplingRateInHz asFloat.
  	perceivedPitchInHz
  		ifNil: [perceivedPitch := 100.0]
  		ifNotNil: [perceivedPitch := perceivedPitchInHz asFloat].
  	gain := 1.0.
  	firstSample := 1.
  	lastSample := leftSamples size.
  	lastSample >= (SmallInteger maxVal // LoopIndexScaleFactor) ifTrue: [
  		self error: 'cannot handle more than ',
  			(SmallInteger maxVal // LoopIndexScaleFactor) printString, ' samples'].
  	loopEnd := leftSamples size.
  	scaledLoopLength := 0.  "zero length means unlooped"
  	scaledIndexIncr := (samplingRateInHz * LoopIndexScaleFactor) // self samplingRate.
  	self computeSampleCountForRelease.
  !

Item was changed:
  ----- Method: MIDIFileReader class>>scoreFromFileNamed: (in category 'as yet unclassified') -----
  scoreFromFileNamed: fileName
  
  	| f score |
  	f := (FileStream readOnlyFileNamed: fileName) binary.
  	score := (self new readMIDIFrom: f) asScore.
  	f close.
  	^ score
  !

Item was changed:
  ----- Method: MIDIFileReader class>>scoreFromStream: (in category 'as yet unclassified') -----
  scoreFromStream: binaryStream
  
  	|  score |
  	score := (self new readMIDIFrom: binaryStream) asScore.
  	^ score
  !

Item was changed:
  ----- Method: MIDIFileReader class>>scoreFromURL: (in category 'as yet unclassified') -----
  scoreFromURL: urlString
  
  	| data |
  	data := HTTPSocket httpGet: urlString accept: 'audio/midi'.
  	data binary.
  	^ (self new readMIDIFrom: data) asScore.
  !

Item was changed:
  ----- Method: MIDIFileReader>>endNote:chan:at: (in category 'track reading') -----
  endNote: midiKey chan: channel at: endTicks
  
  	| evt |
  	evt := activeEvents
  		detect: [:e | (e midiKey = midiKey) and: [e channel = channel]]
  		ifNone: [^ self].
  	evt duration: (endTicks - evt time).
  	activeEvents remove: evt ifAbsent: [].
  !

Item was changed:
  ----- Method: MIDIFileReader>>guessMissingInstrumentNames (in category 'private') -----
  guessMissingInstrumentNames
  	"Attempt to guess missing instrument names from the first program change in that track."
  
  	| progChange instrIndex instrName |
  	1 to: tracks size do: [:i |
  		(trackInfo at: i) isEmpty ifTrue: [
  			progChange := (tracks at: i) detect: [:e | e isProgramChange] ifNone: [nil].
  			progChange ifNotNil: [
  				instrIndex := progChange program + 1.
  				instrName := self class standardMIDIInstrumentNames at: instrIndex.
  				trackInfo at: i put: instrName]]].
  !

Item was changed:
  ----- Method: MIDIFileReader>>metaEventAt: (in category 'track reading') -----
  metaEventAt: ticks
  	"Read a meta event. Event types appear roughly in order of expected frequency."
  
  	| type length tempo |
  	type := trackStream next.
  	length := self readVarLengthIntFrom: trackStream.
  
  	type = 16r51 ifTrue: [  "tempo"
  		tempo := 0.
  		length timesRepeat: [tempo := (tempo bitShift: 8) + trackStream next].
  		track add: (TempoEvent new tempo: tempo; time: ticks).
  		^ self].
  
  	type = 16r2F ifTrue: [  "end of track"
  		length = 0 ifFalse: [self error: 'length of end-of-track chunk should be zero'].
  		self endAllNotesAt: ticks.
  		trackStream skip: length.
  		^ self].
  
  	type = 16r58 ifTrue: [  "time signature"
  		length = 4 ifFalse: [self error: 'length of time signature chunk should be four'].
  		trackStream skip: length.
  		^ self].
  
  	type = 16r59 ifTrue: [  "key signature"
  		length = 2 ifFalse: [self error: 'length of key signature chunk should be two'].
  		trackStream skip: length.
  		^ self].
  
  	((type >= 1) and: [type <= 7]) ifTrue: [  "string"
  		strings add: (trackStream next: length) asString.
  		^ self].
  
  	(  type = 16r21 or:   "mystery; found in MIDI files but not in MIDI File 1.0 Spec"
  	 [(type = 16r7F) or:  "sequencer specific meta event"
  	 [(type = 16r00) or:  "sequence number"
  	 [(type = 16r20)]]])  "MIDI channel prefix"
  		ifTrue: [
  			trackStream skip: length.
  			^ self].
  
  	type = 16r54 ifTrue: [
  		"SMPTE offset"
  		self report: 'Ignoring SMPTE offset'.
  		trackStream skip: length.
  		^ self].
  
  	"skip unrecognized meta event"
  	self report:
  		'skipping unrecognized meta event: ', (type printStringBase: 16),
  		' (', length printString, ' bytes)'.
  	trackStream skip: length.
  !

Item was changed:
  ----- Method: MIDIFileReader>>next16BitWord (in category 'private') -----
  next16BitWord
  	"Read a 16-bit positive integer from the input stream, most significant byte first."
  	"Assume: Stream has at least two bytes left."
  
  	| n |
  	n := stream next.
  	^ (n bitShift: 8) + stream next
  !

Item was changed:
  ----- Method: MIDIFileReader>>next32BitWord: (in category 'private') -----
  next32BitWord: msbFirst
  	"Read a 32-bit positive integer from the input stream."
  	"Assume: Stream has at least four bytes left."
  
  	| n |
  	n := stream next: 4.
  	^msbFirst
  		ifTrue:[((n at: 1) bitShift: 24) + ((n at: 2) bitShift: 16) + ((n at: 3) bitShift: 8) + (n at: 4)]
  		ifFalse:[((n at: 4) bitShift: 24) + ((n at: 3) bitShift: 16) + ((n at: 2) bitShift: 8) + (n at: 1)]
  !

Item was changed:
  ----- Method: MIDIFileReader>>readChunkSize (in category 'private') -----
  readChunkSize
  	"Read a 32-bit positive integer from the next 4 bytes, most significant byte first."
  	"Assume: Stream has at least four bytes left."
  
  	| n |
  	n := 0.
  	1 to: 4 do: [:ignore | n := (n bitShift: 8) + stream next].
  	^ n
  !

Item was changed:
  ----- Method: MIDIFileReader>>readChunkType (in category 'private') -----
  readChunkType
  	"Read a chunk ID string from the next 4 bytes."
  	"Assume: Stream has at least four bytes left."
  
  	| s |
  	s := String new: 4.
  	1 to: 4 do: [:i | s at: i put: (stream next) asCharacter].
  	^ s
  !

Item was changed:
  ----- Method: MIDIFileReader>>readHeaderChunk (in category 'chunk reading') -----
  readHeaderChunk
  
  	| chunkType chunkSize division |
  	chunkType := self readChunkType.
  	chunkType = 'RIFF' ifTrue:[chunkType := self riffSkipToMidiChunk].
  	chunkType = 'MThd' ifFalse: [self scanForMIDIHeader].
  	chunkSize := self readChunkSize.
  	fileType := self next16BitWord.
  	trackCount := self next16BitWord.
  	division := self next16BitWord.
  	(division anyMask: 16r8000)
  		ifTrue: [self error: 'SMPTE time formats are not yet supported']
  		ifFalse: [ticksPerQuarter := division].
  	maxNoteTicks := 12 * 4 * ticksPerQuarter.
  		"longest acceptable note; used to detect stuck notes"
  
  	"sanity checks"
  	((chunkSize < 6) or: [chunkSize > 100])
  		ifTrue: [self error: 'unexpected MIDI header size ', chunkSize printString].
  	(#(0 1 2) includes: fileType)
  		ifFalse: [self error: 'unknown MIDI file type ', fileType printString].
  
  	Transcript
  		show: 'Reading Type ', fileType printString, ' MIDI File (';
  		show: trackCount printString, ' tracks, ';
  		show: ticksPerQuarter printString, ' ticks per quarter note)';
  		cr.
  !

Item was changed:
  ----- Method: MIDIFileReader>>readMIDIFrom: (in category 'chunk reading') -----
  readMIDIFrom: aBinaryStream
  	"Read one or more MIDI tracks from the given binary stream."
  
  	stream := aBinaryStream.
  	tracks := OrderedCollection new.
  	trackInfo := OrderedCollection new.
  	self readHeaderChunk.
  	trackCount timesRepeat: [self readTrackChunk].
  	stream atEnd ifFalse: [self report: 'data beyond final track'].
  	fileType = 0 ifTrue: [self splitIntoTracks].
  	self guessMissingInstrumentNames.
  !

Item was changed:
  ----- Method: MIDIFileReader>>readTrackChunk (in category 'chunk reading') -----
  readTrackChunk
  
  	| chunkType chunkSize |
  	chunkType := self readChunkType.
  	[chunkType = 'MTrk'] whileFalse: [
  		self report: 'skipping unexpected chunk type "', chunkType, '"'.
  		stream skip: (self readChunkSize).  "skip it"
  		chunkType := (stream next: 4) asString].
  	chunkSize := self readChunkSize.
  	chunkSize < 10000000 ifFalse: [
  		self error: 'suspiciously large track chunk; this may not be MIDI file'].
  
  	self readTrackContents: chunkSize.
  !

Item was changed:
  ----- Method: MIDIFileReader>>readTrackContents: (in category 'track reading') -----
  readTrackContents: byteCount
  
  	| info |
  	strings := OrderedCollection new.
  	track := OrderedCollection new.
  	trackStream := ReadStream on: (stream next: byteCount).
  	activeEvents := OrderedCollection new.
  	self readTrackEvents.
  	(tracks isEmpty and: [self isTempoTrack: track])
  		ifTrue: [tempoMap := track asArray]
  		ifFalse: [
  			"Note: Tracks without note events are currently not saved to
  			 eliminate clutter in the score player. In control applications,
  			 this can be easily changed by modifying the following test."
  			(self trackContainsNotes: track) ifTrue: [
  				tracks add: track asArray.
  				info := WriteStream on: (String new: 100).
  				strings do: [:s | info nextPutAll: s; cr].
  				trackInfo add: info contents]].
  	strings := track := trackStream := activeEvents := nil.
  !

Item was changed:
  ----- Method: MIDIFileReader>>readTrackEvents (in category 'track reading') -----
  readTrackEvents
  	"Read the events of the current track."
  
  	| cmd chan key vel ticks byte length evt |
  	cmd := #unknown.
  	chan := key := vel := 0.
  	ticks := 0.
  	[trackStream atEnd] whileFalse: [
  		ticks := ticks + (self readVarLengthIntFrom: trackStream).
  		byte := trackStream next.
  		byte >= 16rF0
  			ifTrue: [  "meta or system exclusive event"
  				byte = 16rFF ifTrue: [self metaEventAt: ticks].
  				((byte = 16rF0) or: [byte = 16rF7]) ifTrue: [  "system exclusive data"
  					length := self readVarLengthIntFrom: trackStream.
  					trackStream skip: length].
  				cmd := #unknown]
  			ifFalse: [  "channel message event"
  				byte >= 16r80
  					ifTrue: [  "new command"
  						cmd := byte bitAnd: 16rF0.
  						chan := byte bitAnd: 16r0F.
  						key := trackStream next]
  					ifFalse: [  "use running status"
  						cmd == #unknown
  							ifTrue: [self error: 'undefined running status; bad MIDI file?'].
  						key := byte].
  
  				((cmd = 16rC0) or: [cmd = 16rD0]) ifFalse: [
  					"all but program change and channel pressure have two data bytes"
  					vel := trackStream next].
  
  				cmd = 16r80 ifTrue: [  "note off"
  					self endNote: key chan: chan at: ticks].
  
  				cmd = 16r90 ifTrue: [  "note on"
  					vel = 0
  						ifTrue: [self endNote: key chan: chan at: ticks]
  						ifFalse: [self startNote: key vel: vel chan: chan at: ticks]].
  
  				"cmd = 16A0 -- polyphonic key pressure; skip"
  
  				cmd = 16rB0 ifTrue: [
  					evt := ControlChangeEvent new control: key value: vel channel: chan.
  					evt time: ticks.
  					track add: evt].
  
  				cmd = 16rC0 ifTrue: [
  					evt := ProgramChangeEvent new program: key channel: chan.
  					evt time: ticks.
  					track add: evt].
  
  				"cmd = 16D0 -- channel aftertouch pressure; skip"
  
  				cmd = 16rE0 ifTrue: [
  					evt := PitchBendEvent new bend: key + (vel bitShift: 7) channel: chan.
  					evt time: ticks.
  					track add: evt]
  	]].
  !

Item was changed:
  ----- Method: MIDIFileReader>>readVarLengthIntFrom: (in category 'private') -----
  readVarLengthIntFrom: aBinaryStream
  	"Read a one to four byte positive integer from the given stream, most significant byte first. Use only the lowest seven bits of each byte. The highest bit of a byte is set for all bytes except the last."
  
  	| n byte |
  	n := 0.
  	1 to: 4 do: [:ignore |
  		byte := aBinaryStream next.
  		byte < 128 ifTrue: [
  			n = 0
  				ifTrue: [^ byte]  "optimization for one-byte lengths"
  				ifFalse: [^ (n bitShift: 7) + byte]].
  		n := (n bitShift: 7) + (byte bitAnd: 16r7F)].
  
  	self error: 'variable length quantity must not exceed four bytes'.
  !

Item was changed:
  ----- Method: MIDIFileReader>>scanForMIDIHeader (in category 'private') -----
  scanForMIDIHeader
  	"Scan the first part of this file in search of the MIDI header string 'MThd'. Report an error if it is not found. Otherwise, leave the input stream positioned to the first byte after this string."
  
  	| asciiM p lastSearchPosition byte restOfHeader |
  	asciiM := $M asciiValue.
  	stream skip: -3.
  	p := stream position.
  	lastSearchPosition := p + 10000.  "search only the first 10000 bytes of the file"
  	[p < lastSearchPosition and: [stream atEnd not]] whileTrue: [
  		[(byte := stream next) ~= asciiM and: [byte ~~ nil]] whileTrue.  "find the next 'M' or file end"
  		restOfHeader := (stream next: 3) asString.
  		restOfHeader = 'Thd'
  			ifTrue: [^ self]
  			ifFalse: [restOfHeader size = 3 ifTrue: [stream skip: -3]].
  		p := stream position].
  
  	self error: 'MIDI header chunk not found'.
  !

Item was changed:
  ----- Method: MIDIFileReader>>splitIntoTracks (in category 'private') -----
  splitIntoTracks
  	"Split a type zero MIDI file into separate tracks by channel number."
  
  	| newTempoMap newTracks |
  	tracks size = 1 ifFalse: [self error: 'expected exactly one track in type 0 file'].
  	tempoMap ifNotNil: [self error: 'did not expect a tempo map in type 0 file'].
  	newTempoMap := OrderedCollection new.
  	newTracks := (1 to: 16) collect: [:i | OrderedCollection new].
  	tracks first do: [:e |
  		e isTempoEvent
  			ifTrue: [newTempoMap addLast: e]
  			ifFalse: [(newTracks at: e channel + 1) addLast: e]].
  	newTempoMap size > 0 ifTrue: [tempoMap := newTempoMap asArray].
  	newTracks := newTracks select: [:t | self trackContainsNotes: t].
  	tracks := newTracks collect: [:t | t asArray].
  	trackInfo := trackInfo, ((2 to: tracks size) collect: [:i | '']).
  !

Item was changed:
  ----- Method: MIDIInputParser class>>initialize (in category 'class initialization') -----
  initialize
  	"Build the default MIDI command-byte action table. This table maps MIDI command bytes to the action to be performed when that is received. Note that MIDI data bytes (bytes whose value is < 128) are never used to index into this table."
  	"MIDIInputParser initialize"
  
  	DefaultMidiTable := Array new: 255 withAll: #undefined:.
  	128 to: 143 do: [:i | DefaultMidiTable at: i put: #recordTwo:].		"key off"
  	144 to: 159 do: [:i | DefaultMidiTable at: i put: #recordTwo:].		"key on"
  	160 to: 175 do: [:i | DefaultMidiTable at: i put: #recordTwo:].		"polyphonic after-touch"
  	176 to: 191 do: [:i | DefaultMidiTable at: i put: #recordTwo:].		"control change"
  	192 to: 207 do: [:i | DefaultMidiTable at: i put: #recordOne:].		"program change"
  	208 to: 223 do: [:i | DefaultMidiTable at: i put: #recordOne:].		"channel after-touch"
  	224 to: 239 do: [:i | DefaultMidiTable at: i put: #recordTwo:].		"pitch bend"
  
  	DefaultMidiTable at: 240 put: #startSysExclusive:.		"start a system exclusive block"
  	DefaultMidiTable at: 241 put: #recordOne:.			"MIDI time code quarter frame"
  	DefaultMidiTable at: 242 put: #recordTwo:.			"song position select"
  	DefaultMidiTable at: 243 put: #recordOne:.			"song select"
  	DefaultMidiTable at: 244 put: #undefined:.
  	DefaultMidiTable at: 245 put: #undefined:.
  	DefaultMidiTable at: 246 put: #recordZero:.			"tune request"
  	DefaultMidiTable at: 247 put: #endSysExclusive:.		"end a system exclusive block"
  	DefaultMidiTable at: 248 put: #recordZero:.			"timing clock"
  	DefaultMidiTable at: 249 put: #undefined:.
  	DefaultMidiTable at: 250 put: #recordZero:.			"start"
  	DefaultMidiTable at: 251 put: #recordZero:.			"continue"
  	DefaultMidiTable at: 252 put: #recordZero:.			"stop/Clock"
  	DefaultMidiTable at: 253 put: #undefined:.
  	DefaultMidiTable at: 254 put: #recordZero:.			"active sensing"
  	DefaultMidiTable at: 255 put: #recordZero:.			"system reset"
  !

Item was changed:
  ----- Method: MIDIInputParser>>clearBuffers (in category 'recording') -----
  clearBuffers
  	"Clear the MIDI record buffers. This should be called at the start of recording or real-time MIDI processing."	
  
  	received := received species new: 5000.
  	rawDataBuffer := ByteArray new: 1000.
  	sysExBuffer := WriteStream on: (ByteArray new: 100).
  	midiPort ifNotNil: [midiPort ensureOpen; flushInput].
  	startTime := Time millisecondClockValue.
  	state := #idle.
  !

Item was changed:
  ----- Method: MIDIInputParser>>ignoreCommand: (in category 'midi filtering') -----
  ignoreCommand: midiCmd
  	"Don't record the given MIDI command on any channel."
  
  	| cmd sel | 
  	((midiCmd isInteger not) | (midiCmd < 128) | (midiCmd > 255))
  		ifTrue: [^ self error: 'bad MIDI command'].
  
  	midiCmd < 240 ifTrue: [  "channel commands; ignore on all channels"
  		cmd := midiCmd bitAnd: 2r11110000.
  		sel := (#(128 144 160 176 224) includes: cmd)
  			ifTrue: [#ignoreTwo:]
  			ifFalse: [#ignoreOne:].
  		 1 to: 16 do: [:ch | cmdActionTable at: (cmd bitOr: ch - 1) put: sel].
  		^ self].
  
  	(#(240 241 244 245 247 249 253) includes: midiCmd) ifTrue: [
  		^ self error: 'You can''t ignore the undefined MIDI command: ', midiCmd printString].
  
  	midiCmd = 242 ifTrue: [  "two-arg command"
  		cmdActionTable at: midiCmd put: #ignoreTwo:.
  		 ^ self].
  
  	midiCmd = 243 ifTrue: [  "one-arg command"
  		cmdActionTable at: midiCmd put: #ignoreOne:.
  		^ self].
  
  	(#(246 248 250 251 252 254 255) includes: midiCmd) ifTrue:	[  "zero-arg command"
  		cmdActionTable at: midiCmd put: #ignore.
  		 ^ self].
  
  	"we should not get here"
  	self error: 'implementation error'.
  !

Item was changed:
  ----- Method: MIDIInputParser>>ignoreOne: (in category 'private-state machine') -----
  ignoreOne: cmdByte
  	"Ignore a one argument command."	
  
  	lastCmdByte := cmdByte.
  	lastSelector := #ignoreOne:.
  	state := #ignore1.
  !

Item was changed:
  ----- Method: MIDIInputParser>>ignoreSysEx: (in category 'midi filtering') -----
  ignoreSysEx: aBoolean
  	"If the argument is true, then ignore incoming system exclusive message."
  
  	ignoreSysEx := aBoolean.
  !

Item was changed:
  ----- Method: MIDIInputParser>>ignoreTwo: (in category 'private-state machine') -----
  ignoreTwo: cmdByte
  	"Ignore a two argument command."	
  
  	lastCmdByte := cmdByte.
  	lastSelector := #ignoreTwo:.
  	state := #ignore2.
  !

Item was changed:
  ----- Method: MIDIInputParser>>midiDoUntilMouseDown: (in category 'real-time processing') -----
  midiDoUntilMouseDown: midiActionBlock
  	"Process the incoming MIDI stream in real time by calling midiActionBlock for each MIDI event. This block takes three arguments: the MIDI command byte and two argument bytes. One or both argument bytes may be nil, depending on the MIDI command. If not nil, evaluatue idleBlock regularly whether MIDI data is available or not. Pressing any mouse button terminates the interaction."
  
  	| time cmd arg1 arg2 |
  	self clearBuffers.
  	[Sensor anyButtonPressed] whileFalse: [
  		self midiDo: [:item |
  			time := item at: 1.
  			cmd := item at: 2.
  			arg1 := arg2 := nil.
  			item size > 2 ifTrue: [
  				arg1 := item at: 3.
  				item size > 3 ifTrue: [arg2 := item at: 4]].
  				midiActionBlock value: cmd value: arg1 value: arg2]].
  !

Item was changed:
  ----- Method: MIDIInputParser>>midiPort: (in category 'accessing') -----
  midiPort: aMIDIPort
  	"Use the given MIDI port."
  
  	midiPort := aMIDIPort.
  	self clearBuffers.
  !

Item was changed:
  ----- Method: MIDIInputParser>>noFiltering (in category 'midi filtering') -----
  noFiltering
  	"Revert to accepting all MIDI commands on all channels. This undoes any earlier request to filter the incoming MIDI stream."
  
  	cmdActionTable := DefaultMidiTable deepCopy.
  	ignoreSysEx := false.
  !

Item was changed:
  ----- Method: MIDIInputParser>>printCmd:with:with: (in category 'midi monitor') -----
  printCmd: cmdByte with: arg1 with: arg2
  	"Print the given MIDI command."
  
  	| cmd ch bend |
  	cmdByte < 240
  		ifTrue: [  "channel message" 
  			cmd := cmdByte bitAnd: 2r11110000.
  			ch := (cmdByte bitAnd: 2r00001111) + 1]
  		ifFalse: [cmd := cmdByte].  "system message"
  
  	cmd = 128 ifTrue: [
  		^ Transcript show: ('key up ', arg1 printString, ' vel: ', arg2 printString, ' chan: ', ch printString); cr].
  	cmd = 144 ifTrue: [
  		^ Transcript show: ('key down: ', arg1 printString, ' vel: ', arg2 printString, ' chan: ', ch printString); cr].
  	cmd = 160 ifTrue: [
  		^ Transcript show: ('key pressure: ', arg1 printString, ' val: ', arg2 printString, ' chan: ', ch printString); cr].
  	cmd = 176 ifTrue: [
  		^ Transcript show: ('CC', arg1 printString, ': val: ', arg2 printString, ' chan: ', ch printString); cr].
  	cmd = 192 ifTrue: [
  		^ Transcript show: ('prog: ', (arg1 + 1) printString, ' chan: ', ch printString); cr].
  	cmd = 208 ifTrue: [
  		^ Transcript show: ('channel pressure ', arg1 printString, ' chan: ', ch printString); cr].
  	cmd = 224 ifTrue: [
  		bend := ((arg2 bitShift: 7) + arg1) - 8192.
  		^ Transcript show: ('bend: ', bend printString, ' chan: ', ch printString); cr].
  
  	cmd = 240 ifTrue: [
  		^ Transcript show: ('system exclusive: ', (arg1 at: 1) printString, ' (', arg1 size printString, ' bytes)'); cr].
  
  	Transcript show: 'cmd: ', cmd printString, ' arg1: ', arg1 printString, ' arg2: ', arg2 printString; cr.
  !

Item was changed:
  ----- Method: MIDIInputParser>>processByte: (in category 'private-state machine') -----
  processByte: aByte
  	"Process the given incoming MIDI byte and record completed commands."
  	"Details: Because this must be fast, it has been hand-tuned. Be careful!!"
  
  	aByte > 247 ifTrue: [  "real-time message; can arrive at any time"
  		^ self perform: (cmdActionTable at: aByte) with: aByte].
  
  	#idle = state ifTrue: [
  		aByte >= 128
  			ifTrue: [  "command byte in idle state: start new command"
  				^ self perform: (cmdActionTable at: aByte) with: aByte]
  			ifFalse: [  "data byte in idle state: use running status if possible"
  				lastCmdByte ifNil: [^ self].  "running status unknown; skip byte"
  				"process this data as if it had the last command byte in front of it"
  				 self perform: lastSelector with: lastCmdByte.
  
  				"the previous line put us into a new state; we now 'fall through'
  				 to process the data byte given this new state."]].
  
  	#ignore1 = state ifTrue: [^ state := #idle].
  	#ignore2 = state ifTrue: [^ state := #ignore1].
  
  	#want1of2 = state ifTrue: [
  		argByte1 := aByte.
  		^ state := #want2of2].
  
  	#want2of2 = state ifTrue: [
  		argByte2 := aByte.
  		received addLast: (Array with: timeNow with: lastCmdByte with: argByte1 with: argByte2).
  		^ state := #idle].
  
  	#want1only = state ifTrue: [
  		argByte1 := aByte.
  		received addLast: (Array with: timeNow with: lastCmdByte with: argByte1).
  		^ state := #idle].
  
  	#sysExclusive = state ifTrue: [
  		aByte < 128 ifTrue: [
  			"record a system exclusive data byte"
  			ignoreSysEx ifFalse: [sysExBuffer nextPut: aByte].
  			^ self]
  		ifFalse: [
  			aByte < 248 ifTrue: [
  				"a system exclusive message is terminated by any non-real-time command byte"
  				ignoreSysEx ifFalse: [
  					received addLast: (Array with: timeNow with: lastCmdByte with: sysExBuffer contents)].
  				state := #idle.
  				aByte = 247
  					ifTrue: [^ self]							"endSysExclusive command, nothing left to do"
  					ifFalse: [^ self processByte: aByte]]]].  	"no endSysExclusive; just start the next command"
  !

Item was changed:
  ----- Method: MIDIInputParser>>processMIDIData (in category 'recording') -----
  processMIDIData
  	"Process all MIDI data that has arrived since the last time this method was executed. This method should be called frequently to process, filter, and timestamp MIDI data as it arrives."
  
  	| bytesRead |
  	[(bytesRead := midiPort readInto: rawDataBuffer) > 0] whileTrue: [
  		timeNow := (midiPort bufferTimeStampFrom: rawDataBuffer) - startTime.
  		5 to: bytesRead do: [:i | self processByte: (rawDataBuffer at: i)]].
  !

Item was changed:
  ----- Method: MIDIInputParser>>recordOne: (in category 'private-state machine') -----
  recordOne: cmdByte
  	"Record a one argument command at the current time."	
  
  	lastCmdByte := cmdByte.
  	lastSelector := #recordOne:.
  	state := #want1only.
  !

Item was changed:
  ----- Method: MIDIInputParser>>recordTwo: (in category 'private-state machine') -----
  recordTwo: cmdByte
  	"Record a two argument command at the current time."	
  
  	lastCmdByte := cmdByte.
  	lastSelector := #recordTwo:.
  	state := #want1of2.
  !

Item was changed:
  ----- Method: MIDIInputParser>>setMIDIPort: (in category 'private-other') -----
  setMIDIPort: aMIDIPort
  	"Initialize this instance for recording from the given MIDI port. Tune and real-time commands are filtered out by default; the client can send noFiltering to receive these messages."
  
  	midiPort := aMIDIPort.
  	received := OrderedCollection new.
  	self noFiltering.  "initializes cmdActionTable"
  	self ignoreTuneAndRealTimeCommands.
  !

Item was changed:
  ----- Method: MIDIInputParser>>startSysExclusive: (in category 'private-state machine') -----
  startSysExclusive: cmdByte
  	"The beginning of a variable length 'system exclusive' command."
  
  	sysExBuffer resetContents.
  	lastCmdByte := nil.  "system exclusive commands clear running status"
  	lastSelector := nil.
  	state := #sysExclusive.
  !

Item was changed:
  ----- Method: MIDIScore>>addAmbientEvent: (in category 'ambient track') -----
  addAmbientEvent: evt
  	| i |
  	i := ambientTrack findFirst: [:e | e time >= evt time].
  	i = 0 ifTrue: [^ ambientTrack := ambientTrack , (Array with: evt)].
  	ambientTrack := ambientTrack copyReplaceFrom: i to: i-1 with: (Array with: evt)!

Item was changed:
  ----- Method: MIDIScore>>ambientEventAfter:ticks: (in category 'ambient track') -----
  ambientEventAfter: eventIndex ticks: scoreTicks
  	| evt |
  	(ambientTrack == nil or: [eventIndex > ambientTrack size]) ifTrue: [^ nil].
  	evt := ambientTrack at: eventIndex.
  	evt time <= scoreTicks ifTrue: [^ evt].
  	^ nil!

Item was changed:
  ----- Method: MIDIScore>>ambientTrack (in category 'ambient track') -----
  ambientTrack
  	^ ambientTrack ifNil: [ambientTrack := Array new]!

Item was changed:
  ----- Method: MIDIScore>>appendEvent:fullDuration:at: (in category 'editing') -----
  appendEvent: noteEvent fullDuration: fullDuration at: selection
  	"It is assumed that the noteEvent already has the proper time"
  
  	| track noteLoc |
  	track := tracks at: selection first.
  	noteLoc := selection third + 1.
  	noteEvent midiKey = -1
  		ifTrue: [noteLoc := noteLoc - 1]
  		ifFalse: ["If not a rest..."
  				track := track copyReplaceFrom: noteLoc to: noteLoc - 1
  								with: (Array with: noteEvent)].
  	track size >= (noteLoc + 1) ifTrue:
  		["Adjust times of following events"
  		noteLoc + 1 to: track size do:
  			[:i | (track at: i) adjustTimeBy: fullDuration]].
  	tracks at: selection first put: track!

Item was changed:
  ----- Method: MIDIScore>>cutSelection: (in category 'editing') -----
  cutSelection: selection
  
  	| track selStartTime delta |
  	track := tracks at: selection first.
  	selStartTime := (track at: selection second) time.
  	track := track copyReplaceFrom: selection second to: selection third with: Array new.
  	track size >=  selection second ifTrue:
  		["Adjust times of following events"
  		delta := selStartTime - (track at: selection second) time.
  		selection second to: track size do:
  			[:i | (track at: i) adjustTimeBy: delta]].
  	tracks at: selection first put: track!

Item was changed:
  ----- Method: MIDIScore>>durationInTicks (in category 'accessing') -----
  durationInTicks
  	
  	| t |
  	t := 0.
  	tracks, {self ambientTrack} do:
  		[:track |
  		track do:
  			[:n | (n isNoteEvent)
  				ifTrue: [t := t max: n endTime]
  				ifFalse: [t := t max: n time]]].
  	^ t
  !

Item was changed:
  ----- Method: MIDIScore>>eventForTrack:after:ticks: (in category 'editing') -----
  eventForTrack: trackIndex after: eventIndex ticks: scoreTick
  
  	| track evt |
  	track := tracks at: trackIndex.
  	eventIndex > track size ifTrue: [^ nil].
  	evt := track at: eventIndex.
  	evt time > scoreTick ifTrue: [^ nil].
  	^ evt
  !

Item was changed:
  ----- Method: MIDIScore>>gridTrack:toQuarter:at: (in category 'editing') -----
  gridTrack: trackIndex toQuarter: quarterDelta at: indexInTrack
  
  	| track selStartTime delta |
  	track := tracks at: trackIndex.
  	selStartTime := (track at: indexInTrack) time.
  	delta := (self gridToQuarterNote: selStartTime + (quarterDelta*ticksPerQuarterNote))
  				- selStartTime.
  	indexInTrack to: track size do:
  		[:i | (track at: i) adjustTimeBy: delta].
  !

Item was changed:
  ----- Method: MIDIScore>>insertEvents:at: (in category 'editing') -----
  insertEvents: events at: selection
  
  	| track selStartTime delta |
  	track := tracks at: selection first.
  	selection second = 0
  		ifTrue: [selStartTime := 0.
  				selection at: 2 put: 1]
  		ifFalse: [selStartTime := (track at: selection second) time].
  	track := track copyReplaceFrom: selection second to: selection second - 1
  				with: (events collect: [:e | e copy]).
  	track size >=  (selection second + events size) ifTrue:
  		["Adjust times of following events"
  		delta := selStartTime - (track at: selection second) time.
  		selection second to: selection second + events size - 1 do:
  			[:i | (track at: i) adjustTimeBy: delta].
  		delta := (self gridToNextQuarterNote: (track at: selection second + events size - 1) endTime)
  					- (track at: selection second + events size) time.
  		selection second + events size to: track size do:
  			[:i | (track at: i) adjustTimeBy: delta].
  		].
  	tracks at: selection first put: track!

Item was changed:
  ----- Method: MIDIScore>>removeAmbientEventWithMorph: (in category 'ambient track') -----
  removeAmbientEventWithMorph: aMorph
  	| i |
  	i := ambientTrack findFirst: [:e | e morph == aMorph].
  	i = 0 ifTrue: [^ self].
  	ambientTrack := ambientTrack copyReplaceFrom: i to: i with: Array new!

Item was changed:
  ----- Method: MIDIScore>>tempoMap: (in category 'accessing') -----
  tempoMap: tempoEventList
  
  	tempoEventList ifNil: [
  		tempoMap := #().
  		^ self].
  	tempoMap := tempoEventList asArray.
  !

Item was changed:
  ----- Method: MIDIScore>>ticksPerQuarterNote: (in category 'accessing') -----
  ticksPerQuarterNote: anInteger
  
  	ticksPerQuarterNote := anInteger.
  !

Item was changed:
  ----- Method: MIDIScore>>trackInfo: (in category 'accessing') -----
  trackInfo: trackInfoList
  
  	trackInfo := trackInfoList asArray.
  !

Item was changed:
  ----- Method: MIDIScore>>tracks: (in category 'accessing') -----
  tracks: trackList
  
  	tracks := trackList asArray collect: [:trackEvents | trackEvents asArray].
  	self ambientTrack.  "Assure it's not nil"!

Item was changed:
  ----- Method: MIDISynth class>>example (in category 'examples') -----
  example
  	"Here's one way to run the MIDI synth. It will get a nice Morphic UI later. Click the mouse to stop running it. (Mac users note: be sure you have MIDI interface adaptor plugged in, or Squeak will hang waiting for the external clock signal.)."
  	"MIDISynth example"
  
  	| portNum synth |
  	portNum := SimpleMIDIPort inputPortNumFromUser.
  	portNum ifNil: [^ self].
  	SoundPlayer useShortBuffer.
  	synth := MIDISynth new
  		midiPort: (SimpleMIDIPort openOnPortNumber: portNum).
  	synth midiParser ignoreCommand: 224.  "filter out pitch bends"
  	1 to: 16 do: [:i |
  		(synth channel: i) instrument:
   			 (AbstractSound soundNamed: 'oboe1')].
  	1 to: 16 do: [:ch | synth volumeForChannel: ch put: 0.2].
  
  	synth processMIDIUntilMouseDown.
  	SoundPlayer shutDown; initialize.  "revert to normal buffer size"
  !

Item was changed:
  ----- Method: MIDISynth>>setAllChannelMasterVolumes: (in category 'as yet unclassified') -----
  setAllChannelMasterVolumes: aNumber
  
  	| vol |
  	vol := (aNumber asFloat min: 1.0) max: 0.0.
  	channels do: [:ch | ch masterVolume: vol].
  !

Item was changed:
  ----- Method: MIDISynth>>startMIDITracking (in category 'as yet unclassified') -----
  startMIDITracking
  
  	midiParser ifNil: [^ self].
  	midiParser midiPort ifNil: [^ self].
  	midiParser midiPort ensureOpen.
  	self stopMIDITracking.
  	SoundPlayer useShortBuffer.
  	process := [self midiTrackingLoop] newProcess.
  	process priority: Processor userInterruptPriority.
  	process resume.
  !

Item was changed:
  ----- Method: MIDISynth>>stopMIDITracking (in category 'as yet unclassified') -----
  stopMIDITracking
  
  	process ifNotNil: [
  		process terminate.
  		process := nil].
  	SoundPlayer shutDown; initialize.  "revert to normal buffer size"
  !

Item was changed:
  ----- Method: MIDISynthChannel>>convertVelocity: (in category 'other') -----
  convertVelocity: valueByte
  	"Map a value in the range 0..127 to a volume in the range 0.0..1.0."
  	"Details: A quadratic function seems to give a good keyboard feel."
  
  	| r |
  	r := (valueByte * valueByte) / 12000.0.
  	r > 1.0 ifTrue: [^ 1.0].
  	r < 0.08 ifTrue: [^ 0.08].
  	^ r
  !

Item was changed:
  ----- Method: MIDISynthChannel>>instrument: (in category 'accessing') -----
  instrument: aSound
  
  	instrument := aSound.
  !

Item was changed:
  ----- Method: MIDISynthChannel>>keyDown:vel: (in category 'midi dispatching') -----
  keyDown: key vel: vel
  	"Handle a key down event with non-zero velocity."
  
  	| pitch snd |
  	muted ifTrue: [^ self].
  	pitch := AbstractSound pitchForMIDIKey: key.
  	snd := instrument
  		soundForPitch: pitch
  		dur: 10000.0  "sustain a long time, or until turned off"
  		loudness: masterVolume * channelVolume * (self convertVelocity: vel).
  	snd := (MixedSound new add: snd pan: pan) reset.
  	SoundPlayer resumePlaying: snd quickStart: false.
  	activeSounds add: (Array with: key with: snd with: pitch).
  !

Item was changed:
  ----- Method: MIDISynthChannel>>masterVolume: (in category 'accessing') -----
  masterVolume: aNumber
  	"Set the master volume the the given value (0.0 to 1.0)."
  
  	masterVolume := aNumber asFloat.
  !

Item was changed:
  ----- Method: MIDISynthChannel>>muted: (in category 'accessing') -----
  muted: aBoolean
  
  	muted := aBoolean.
  !

Item was changed:
  ----- Method: MIDISynthChannel>>pan: (in category 'accessing') -----
  pan: aNumber
  	"Set the left-right pan to the given value (0.0 to 1.0)."
  
  	pan := aNumber asFloat.
  !

Item was changed:
  ----- Method: MixedSound>>add:pan:volume: (in category 'composition') -----
  add: aSound pan: leftRightPan volume: volume
  	"Add the given sound with the given left-right pan, where 0.0 is full left, 1.0 is full right, and 0.5 is centered. The loudness of the sound will be scaled by volume, which ranges from 0 to 1.0."
  
  	| pan vol |
  	pan := ((leftRightPan * ScaleFactor) asInteger max: 0) min: ScaleFactor.
  	vol := ((volume * ScaleFactor) asInteger max: 0) min: ScaleFactor.
  	sounds := sounds copyWith: aSound.
  	leftVols := leftVols copyWith: ((ScaleFactor - pan) * vol) // ScaleFactor.
  	rightVols := rightVols copyWith: (pan * vol) // ScaleFactor.
  !

Item was changed:
  ----- Method: MixedSound>>copySounds (in category 'copying') -----
  copySounds
  	"Private!! Support for copying. Copy my component sounds and settings array."
  
  	sounds := sounds collect: [:s | s copy].
  	leftVols := leftVols copy.
  	rightVols := rightVols copy.
  !

Item was changed:
  ----- Method: MixedSound>>duration (in category 'accessing') -----
  duration
  	"Answer the duration of this sound in seconds."
  
  	| dur |
  	dur := 0.
  	sounds do: [:snd | dur := dur max: snd duration].
  	^ dur
  !

Item was changed:
  ----- Method: MixedSound>>initialize (in category 'initialization') -----
  initialize
  
  	super initialize.
  	sounds := Array new.
  	leftVols := Array new.
  	rightVols := Array new.
  !

Item was changed:
  ----- Method: MixedSound>>mixSampleCount:into:startingAt:leftVol:rightVol: (in category 'sound generation') -----
  mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol
  	"Play a number of sounds concurrently. The level of each sound can be set independently for the left and right channels."
  
  	| snd left right |
  	1 to: sounds size do: [:i |
  		(soundDone at: i) ifFalse: [
  			snd := sounds at: i.
  			left := (leftVol * (leftVols at: i)) // ScaleFactor.
  			right := (rightVol * (rightVols at: i)) // ScaleFactor.
  			snd samplesRemaining > 0
  				ifTrue: [
  					snd mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: left rightVol: right]
  				ifFalse: [soundDone at: i put: true]]].
  !

Item was changed:
  ----- Method: MixedSound>>reset (in category 'sound generation') -----
  reset
  
  	super reset.
  	sounds do: [:snd | snd reset].
  	soundDone := (Array new: sounds size) atAllPut: false.
  !

Item was changed:
  ----- Method: MixedSound>>samplesRemaining (in category 'sound generation') -----
  samplesRemaining
  
  	| remaining r |
  	remaining := 0.
  	1 to: sounds size do: [:i |
  		r := (sounds at: i) samplesRemaining.
  		r > remaining ifTrue: [remaining := r]].
  
  	^ remaining
  !

Item was changed:
  ----- Method: MuLawCodec class>>initialize (in category 'class initialization') -----
  initialize
  	"Build the 256 entry table to be used to decode 8-bit uLaw-encoded samples."
  	"MuLawCodec initialize"
  
  	| encoded codec lastEncodedPos lastEncodedNeg |
  	DecodingTable := Array new: 256.
  	codec := self new.
  	lastEncodedPos := nil.
  	lastEncodedNeg := nil.
  	4095 to: 0 by: -1 do: [:s |
  		encoded := codec uLawEncode12Bits: s.
  		lastEncodedPos = encoded
  			ifFalse: [
  				DecodingTable at: (encoded + 1) put: (s bitShift: 3).
  				lastEncodedPos := encoded].
  		encoded := encoded bitOr: 16r80.
  		lastEncodedNeg = encoded
  			ifFalse: [
  				DecodingTable at: (encoded + 1) put: (s bitShift: 3) negated.
  				lastEncodedNeg := encoded]].
  !

Item was changed:
  ----- Method: MuLawCodec>>decodeFrames:from:at:into:at: (in category 'subclass responsibility') -----
  decodeFrames: frameCount from: srcByteArray at: srcIndex into: dstSoundBuffer at: dstIndex
  	"Decode the given number of monophonic frames starting at the given index in the given ByteArray of compressed sound data and storing the decoded samples into the given SoundBuffer starting at the given destination index. Answer a pair containing the number of bytes of compressed data consumed and the number of decompressed samples produced."
  	"Note: Assume that the sender has ensured that the given number of frames will not exhaust either the source or destination buffers."
  
  	| dst |
  	dst := dstIndex.
  	srcIndex to: srcIndex + frameCount - 1 do: [:src |
  		dstSoundBuffer at: dst put: (DecodingTable at: (srcByteArray at: src) + 1).
  		dst := dst + 1].
  	^ Array with: frameCount with: frameCount
  !

Item was changed:
  ----- Method: MuLawCodec>>uLawEncodeSample: (in category 'external access') -----
  uLawEncodeSample: sample
  	"Encode a 16-bit signed sample into 8 bits using uLaw encoding"
  
  	| s |
  	s := sample // 8.  "drop 3 least significant bits"
  	s < 0 ifTrue: [^ (self uLawEncode12Bits: 0-s) + 16r80]
  		ifFalse: [^ (self uLawEncode12Bits: s)].
  !

Item was changed:
  ----- Method: NoteEvent>>channel: (in category 'accessing') -----
  channel: midiChannel
  
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: NoteEvent>>duration: (in category 'accessing') -----
  duration: aNumber
  
  	duration := aNumber.
  !

Item was changed:
  ----- Method: NoteEvent>>key:velocity:channel: (in category 'accessing') -----
  key: midiKeyNum velocity: midiVelocity channel: midiChannel
  
  	midiKey := midiKeyNum.
  	velocity := midiVelocity.
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: NoteEvent>>keyName (in category 'printing') -----
  keyName
  	"Return a note name for my pitch."
  
  	| pitchName octave |
  	pitchName := #(c cs d ef e f fs g af a bf b) at: (midiKey \\ 12) + 1.
  	octave := (#(-1 0 1 2 3 4 5 6 7 8 9) at: (midiKey // 12) + 1) printString.
  	^ pitchName, octave
  !

Item was changed:
  ----- Method: NoteEvent>>midiKey: (in category 'accessing') -----
  midiKey: midiKeyNum
  
  	midiKey := midiKeyNum.
  !

Item was changed:
  ----- Method: NoteEvent>>velocity: (in category 'accessing') -----
  velocity: midiVelocity
  
  	velocity := midiVelocity.
  !

Item was changed:
  ----- Method: PitchBendEvent>>bend: (in category 'accessing') -----
  bend: midiPitchBend
  
  	bend := midiPitchBend.
  !

Item was changed:
  ----- Method: PitchBendEvent>>bend:channel: (in category 'accessing') -----
  bend: midiPitchBend channel: midiChannel
  
  	bend := midiPitchBend.
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: PitchBendEvent>>channel: (in category 'accessing') -----
  channel: midiChannel
  
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: PitchEnvelope>>centerPitch: (in category 'as yet unclassified') -----
  centerPitch: aNumber
  
  	centerPitch := aNumber.
  !

Item was changed:
  ----- Method: PitchEnvelope>>updateTargetAt: (in category 'as yet unclassified') -----
  updateTargetAt: mSecs
  	"Update the pitch for my target. Answer true if the value changed."
  	"Details: Assume envelope range is 0.0..2.0, with 1 being the center pitch. Subtracting one yields the range -1.0..1.0. Raising two to this power yields pitches between half and double the center pitch; i.e. from an octave below to an octave about the center pitch."
  
  	| newValue |
  	newValue := self valueAtMSecs: mSecs.
  	newValue ~= lastValue ifTrue: [
  		target pitch: (2.0 raisedTo: newValue - (scale / 2.0)) * centerPitch.
  		lastValue := newValue.
  		^ true].
  
  	^ false
  !

Item was changed:
  ----- Method: PluckedSound class>>default (in category 'instruments') -----
  default
  	"PluckedSound default play"
  	"(AbstractSound majorScaleOn: PluckedSound default) play"
  
  	| snd p env |
  	snd := PluckedSound new.
  	p := OrderedCollection new.
  	p add: 0 at 1.0; add: 10 at 1.0; add: 20 at 0.0.
  	env := VolumeEnvelope points: p loopStart: 2 loopEnd: 2.
  	env target: snd; scale: 0.3.
  	^ snd
  		addEnvelope: env;
  		setPitch: 220 dur: 3.0 loudness: 0.3
  !

Item was changed:
  ----- Method: PluckedSound>>copyRing (in category 'copying') -----
  copyRing
  	"Private!! Support for copying"
  
  	ring := ring copy.
  !

Item was changed:
  ----- Method: PluckedSound>>duration: (in category 'accessing') -----
  duration: seconds
  
  	super duration: seconds.
  	count := initialCount := (seconds * self samplingRate) rounded.
  !

Item was changed:
  ----- Method: PluckedSound>>reset (in category 'sound generation') -----
  reset
  	"Fill the ring with random noise."
  
  	| seed n |
  	super reset.
  	seed := 17.
  	n := ring monoSampleCount.
  	1 to: n do: [:i |
  		seed := ((seed * 1309) + 13849) bitAnd: 65535.
  		ring at: i put: seed - 32768].
  	count := initialCount.
  	scaledIndex := ScaleFactor.
  !

Item was changed:
  ----- Method: PluckedSound>>setPitch:dur:loudness: (in category 'initialization') -----
  setPitch: pitchNameOrNumber dur: d loudness: vol
  
  	| p sz |
  	super setPitch: pitchNameOrNumber dur: d loudness: vol.
  	p := self nameOrNumberToPitch: pitchNameOrNumber.
  	initialCount := (d * self samplingRate asFloat) asInteger.
  	ring := SoundBuffer newMonoSampleCount:
  		(((2.0 * self samplingRate) / p) asInteger max: 2).
  	sz := ring monoSampleCount.
  	scaledIndexLimit := (sz + 1) * ScaleFactor.
  	scaledIndexIncr := (p * sz * ScaleFactor) // (2.0 * self samplingRate).
  	self reset.
  !

Item was changed:
  ----- Method: PluckedSound>>stopAfterMSecs: (in category 'sound generation') -----
  stopAfterMSecs: mSecs
  	"Terminate this sound this note after the given number of milliseconds."
  
  	count := (mSecs * self samplingRate) // 1000.
  !

Item was changed:
  ----- Method: ProgramChangeEvent>>channel: (in category 'accessing') -----
  channel: midiChannel
  
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: ProgramChangeEvent>>program: (in category 'accessing') -----
  program: midiProgramChange
  
  	program := midiProgramChange.
  !

Item was changed:
  ----- Method: ProgramChangeEvent>>program:channel: (in category 'accessing') -----
  program: midiProgramChange channel: midiChannel
  
  	program := midiProgramChange.
  	channel := midiChannel.
  !

Item was changed:
  ----- Method: QueueSound>>currentSound: (in category 'accessing') -----
  currentSound: aSound
  	currentSound := aSound!

Item was changed:
  ----- Method: QueueSound>>done: (in category 'accessing') -----
  done: aBoolean
  	done := aBoolean!

Item was changed:
  ----- Method: QueueSound>>initialize (in category 'initialization') -----
  initialize
  	super initialize.
  	sounds := SharedQueue new.
  	done := false.
  	startTime := Time millisecondClockValue!

Item was changed:
  ----- Method: QueueSound>>nextSound (in category 'sound generation') -----
  nextSound
  	| answer |
  	sounds isEmpty ifTrue: [^ nil].
  	answer := sounds next.
  	answer reset.
  	^ answer!

Item was changed:
  ----- Method: QueueSound>>startTime: (in category 'accessing') -----
  startTime: anInteger
  	startTime := anInteger!

Item was changed:
  ----- Method: RandomEnvelope>>delta: (in category 'accessing') -----
  delta: aNumber
  
  	delta := aNumber.
  !

Item was changed:
  ----- Method: RandomEnvelope>>highLimit: (in category 'accessing') -----
  highLimit: aNumber
  
  	highLimit := aNumber.
  !

Item was changed:
  ----- Method: RandomEnvelope>>lowLimit: (in category 'accessing') -----
  lowLimit: aNumber
  
  	lowLimit := aNumber.
  !

Item was changed:
  ----- Method: RandomEnvelope>>updateTargetAt: (in category 'applying') -----
  updateTargetAt: mSecs
  	"Send my updateSelector to the given target object with the value of this envelope at the given number of milliseconds from its onset. Answer true if the value changed."
  
  	| r |
  	r := rand next.
  	r > 0.5
  		ifTrue: [
  			currValue := currValue + delta.
  			currValue > highLimit ifTrue: [currValue := highLimit]]
  		ifFalse: [
  			currValue := currValue - delta.
  			currValue < lowLimit ifTrue: [currValue := lowLimit]].
  	currValue = lastValue ifTrue: [^ false].
  	((target == nil) or: [updateSelector == nil]) ifTrue: [^ false].
  	target
  		perform: updateSelector
  		with: scale * currValue.
  	lastValue := currValue.
  	^ true
  !

Item was changed:
  ----- Method: RepeatingSound class>>initializeCarMotor (in category 'car motor example') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: RepeatingSound>>copySound (in category 'copying') -----
  copySound
  	"Private!! Support for copying. Copy my component sound."
  
  	sound := sound copy.
  !

Item was changed:
  ----- Method: RepeatingSound>>iterationCount: (in category 'accessing') -----
  iterationCount: aNumber
  
  	iterationCount := aNumber.
  !

Item was changed:
  ----- Method: RepeatingSound>>mixSampleCount:into:startingAt:leftVol:rightVol: (in category 'sound generation') -----
  mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol
  	"Play a collection of sounds in sequence."
  	"(RepeatingSound new
  		setSound: FMSound majorScale
  		iterations: 2) play"
  
  	| i count samplesNeeded |
  	iteration <= 0 ifTrue: [^ self].
  	i := startIndex.
  	samplesNeeded := n.
  	[samplesNeeded > 0] whileTrue: [
  		count := sound samplesRemaining min: samplesNeeded.
  		count = 0 ifTrue: [
  			iterationCount == #forever
  				ifFalse: [
  					iteration := iteration - 1.
  					iteration <= 0 ifTrue: [^ self]].  "done"
  			sound reset.
  			count := sound samplesRemaining min: samplesNeeded.
  			count = 0 ifTrue: [^ self]].  "zero length sound"
  		sound mixSampleCount: count
  			into: aSoundBuffer
  			startingAt: i
  			leftVol: leftVol
  			rightVol: rightVol.
  		i := i + count.
  		samplesNeeded := samplesNeeded - count].
  !

Item was changed:
  ----- Method: RepeatingSound>>reset (in category 'sound generation') -----
  reset
  
  	super reset.
  	sound reset.
  	samplesPerIteration := sound samplesRemaining.
  	iterationCount == #forever
  		ifTrue: [iteration := 1]
  		ifFalse: [iteration := iterationCount].
  !

Item was changed:
  ----- Method: RepeatingSound>>setSound:iterations: (in category 'initialization') -----
  setSound: aSound iterations: anIntegerOrSymbol
  	"Initialize the receiver to play the given sound the given number of times. If iteration count is the symbol #forever, then repeat indefinitely."
  	"(RepeatingSound repeat: AbstractSound scaleTest count: 2) play"
  	"(RepeatingSound repeatForever: PluckedSound lowMajorScale) play"
  
  	super initialize.
  	sound := aSound.
  	iterationCount := anIntegerOrSymbol.
  	self reset.
  !

Item was changed:
  ----- Method: RepeatingSound>>sound: (in category 'accessing') -----
  sound: aSound
  
  	sound := aSound.
  !

Item was changed:
  ----- Method: RestSound>>duration: (in category 'accessing') -----
  duration: seconds
  
  	super duration: seconds.
  	count := initialCount := (seconds * self samplingRate) rounded.
  !

Item was changed:
  ----- Method: RestSound>>mixSampleCount:into:startingAt:leftVol:rightVol: (in category 'sound generation') -----
  mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol
  	"Play silence for a given duration."
  	"(RestSound dur: 1.0) play"
  
  	count := count - n.
  !

Item was changed:
  ----- Method: RestSound>>setDur: (in category 'initialization') -----
  setDur: d
  	"Set rest duration in seconds."
  
  	initialCount := (d * self samplingRate asFloat) rounded.
  	count := initialCount.
  	self reset.
  !

Item was changed:
  ----- Method: ReverbSound>>copySound (in category 'copying') -----
  copySound
  	"Private!! Support for copying. Copy my component sound."
  
  	sound := sound copy.
  	leftBuffer := leftBuffer clone.
  	rightBuffer := rightBuffer clone.
  !

Item was changed:
  ----- Method: ReverbSound>>sound: (in category 'accessing') -----
  sound: aSound
  
  	sound := aSound.
  !

Item was changed:
  ----- Method: ReverbSound>>tapDelays:gains: (in category 'accessing') -----
  tapDelays: delayList gains: gainList
  	"ReverbSound new tapDelays: #(537 691 1191) gains: #(0.07 0.07 0.07)"
  
  	| maxDelay gain d |
  	delayList size = gainList size
  		ifFalse: [self error: 'tap delay and gains lists must be the same size'].
  	tapCount := delayList size.
  	tapDelays := Bitmap new: tapCount.
  	tapGains := Bitmap new: tapCount.
  
  	maxDelay := 0.
  	1 to: tapGains size do: [:i |
  		tapDelays at: i put: (delayList at: i) asInteger.
  		gain := gainList at: i.
  		gain >= 1.0 ifTrue: [self error: 'reverb tap gains must be under 1.0'].
  		tapGains at: i put: (gain * ScaleFactor) asInteger.
  		d := tapDelays at: i.
  		d > maxDelay ifTrue: [maxDelay := d]].
  	bufferSize := maxDelay.
  	leftBuffer := SoundBuffer newMonoSampleCount: maxDelay.
  	rightBuffer := SoundBuffer newMonoSampleCount: maxDelay.
  	bufferIndex := 1.
  !

Item was changed:
  ----- Method: SampledInstrument class>>buildSmallOrchestra (in category 'instance creation') -----
  buildSmallOrchestra
  	"Example of how to build a skeleton orchestra that uses less memory (about 14 MBytes)."
  	"SampledInstrument buildSmallOrchestra"
  
  	| dir |
  	AbstractSound unloadSampledTimbres.
  	dir := 'Tosh:Not Backed Up:Sample Library:Orchestra'.
  	#(clarinet oboe bassoon trombone tympani) do: [:instName |
  		SampledInstrument
  			readSimpleInstrument: instName
  			fromDirectory: dir.
  		(AbstractSound soundNamed: instName, '-f') pruneToNotesPerOctave: 1].
  	#(flute bass) do: [:instName |
  		SampledInstrument
  			readSimpleInstrument: instName
  			fromDirectory: dir.
  		(AbstractSound soundNamed: instName, '-f') pruneToNotesPerOctave: 2].
  
  	(AbstractSound soundNamed: 'bass-f') allNotes do: [:n |
  		n firstSample: (n findStartPointForThreshold: 2500)].
  
  	(AbstractSound soundNamed: 'bassoon-f') allNotes do: [:n |
  		n beUnlooped.
  		n firstSample: (n findStartPointForThreshold: 0)].
  
  	(AbstractSound soundNamed: 'trombone-f') allNotes do: [:n |
  		n firstSample: (n findStartPointForThreshold: 1800)].
  
  	AbstractSound soundNamed: 'trumpet-f' put: (AbstractSound soundNamed: 'trombone-f').
  	AbstractSound soundNamed: 'horn-f' put: (AbstractSound soundNamed: 'trombone-f').
  	AbstractSound soundNamed: 'violin-f' put: (AbstractSound soundNamed: 'bass-f').
  	AbstractSound soundNamed: 'viola-f' put: (AbstractSound soundNamed: 'bass-f').
  	AbstractSound soundNamed: 'cello-f' put: (AbstractSound soundNamed: 'bass-f').
  
  	(AbstractSound soundNamed: 'bassoon-f') allNotes do: [:n | n beUnlooped].
  
  !

Item was changed:
  ----- Method: SampledInstrument class>>readLoudAndStaccatoInstrument:fromDirectory: (in category 'instance creation') -----
  readLoudAndStaccatoInstrument: instName fromDirectory: orchestraDir
  	"SampledInstrument
  		readLoudAndStaccatoInstrument: 'oboe'
  		fromDirectory: 'Tosh:Sample Library:Orchestra'"
  
  	| sampleSetDir memBefore memAfter loud short snd |
  	sampleSetDir := orchestraDir, ':', instName.
  	memBefore := Smalltalk garbageCollect.
  	loud := SampledInstrument new readSampleSetFrom: sampleSetDir, ' f'.
  	short := SampledInstrument new readSampleSetFrom: sampleSetDir, ' stacc'.
  	memAfter := Smalltalk garbageCollect.
  	Transcript show:
  		instName, ': ', (memBefore - memAfter) printString,
  		' bytes; ', memAfter printString, ' bytes left'; cr.
  	AbstractSound soundNamed: instName, '-f&stacc' put:
  		(snd := SampledInstrument new
  			allSampleSets: loud;
  			staccatoLoudAndSoftSampleSet: short).
  	"fix slow attacks"
  	snd allNotes do: [:n | n firstSample: (n findStartPointForThreshold: 500)].
  
  	AbstractSound soundNamed: instName, '-f' put:
  		(snd := SampledInstrument new
  			allSampleSets: loud).
  	"fix slow attacks"
  	snd allNotes do: [:n | n firstSample: (n findStartPointForThreshold: 1000)].
  !

Item was changed:
  ----- Method: SampledInstrument class>>readPizzInstrument:fromDirectory: (in category 'instance creation') -----
  readPizzInstrument: instName fromDirectory: orchestraDir
  	"SampledInstrument
  		readPizzInstrument: 'violin'
  		fromDirectory: 'Tosh:Sample Library:Orchestra'"
  
  	| sampleSetDir memBefore memAfter sampleSet snd |
  	sampleSetDir := orchestraDir, ':', instName, ' pizz'.
  	memBefore := Smalltalk garbageCollect.
  	sampleSet := SampledInstrument new readSampleSetFrom: sampleSetDir.
  	memAfter := Smalltalk garbageCollect.
  	Transcript show:
  		instName, ': ', (memBefore - memAfter) printString,
  		' bytes; ', memAfter printString, ' bytes left'; cr.
  	AbstractSound soundNamed: instName, '-pizz' put:
  		(snd := SampledInstrument new allSampleSets: sampleSet).
  
  	"fix slow attacks"
  	snd allNotes do: [:n |
  		n firstSample: (n findStartPointForThreshold: 1000)].
  
  	^ snd
  !

Item was changed:
  ----- Method: SampledInstrument class>>readSimpleInstrument:fromDirectory: (in category 'instance creation') -----
  readSimpleInstrument: instName fromDirectory: orchestraDir
  	"SampledInstrument
  		readSimpleInstrument: 'oboe'
  		fromDirectory: 'Tosh:Sample Library:Orchestra'"
  
  	| sampleSetDir memBefore memAfter sampleSet snd |
  	sampleSetDir := orchestraDir, ':', instName, ' f'.
  	memBefore := Smalltalk garbageCollect.
  	sampleSet := SampledInstrument new readSampleSetFrom: sampleSetDir.
  	memAfter := Smalltalk garbageCollect.
  	Transcript show:
  		instName, ': ', (memBefore - memAfter) printString,
  		' bytes; ', memAfter printString, ' bytes left'; cr.
  	AbstractSound soundNamed: instName, '-f' put:
  		(snd := SampledInstrument new allSampleSets: sampleSet).
  
  	"fix slow attacks"
  	snd allNotes do: [:n |
  		n firstSample: (n findStartPointForThreshold: 1000)].
  
  	^ snd
  !

Item was changed:
  ----- Method: SampledInstrument>>allSampleSets: (in category 'accessing') -----
  allSampleSets: sortedNotes
  
  	| keyMap |
  	keyMap := self midiKeyMapFor: sortedNotes.
  	sustainedSoft := keyMap.
  	sustainedLoud := keyMap.
  	staccatoSoft := keyMap.
  	staccatoLoud := keyMap.
  !

Item was changed:
  ----- Method: SampledInstrument>>chooseSamplesForPitch:from: (in category 'other') -----
  chooseSamplesForPitch: pitchInHz from: sortedNotes
  	"From the given collection of LoopedSampledSounds, choose the best one to be pitch-shifted to produce the given pitch."
  	"Assume: the given collection is sorted in ascending pitch order."
  
  	| i lower higher |
  	i := 1.
  	[(i < sortedNotes size) and: [(sortedNotes at: i) pitch < pitchInHz]]
  		whileTrue: [i := i + 1].
  	i = 1 ifTrue: [^ sortedNotes at: 1].
  	lower := sortedNotes at: i - 1.
  	higher := sortedNotes at: i.
  	"note: give slight preference for down-shifting a higher-pitched sample set"
  	(pitchInHz / lower pitch) < ((0.95 * higher pitch) / pitchInHz)
  		ifTrue: [^ lower]
  		ifFalse: [^ higher].
  !

Item was changed:
  ----- Method: SampledInstrument>>loudThreshold: (in category 'accessing') -----
  loudThreshold: aNumber
  
  	loudThreshold := aNumber asFloat.
  !

Item was changed:
  ----- Method: SampledInstrument>>memorySpace (in category 'other') -----
  memorySpace
  	"Answer the number of bytes required to store the samples for this instrument."
  
  	| total |
  	total := 0.
  	self allNotes do: [:n |
  		total := total + (n leftSamples monoSampleCount * 2).
  		n isStereo ifTrue: [total := total + (n leftSamples monoSampleCount * 2)]].
  	^ total
  !

Item was changed:
  ----- Method: SampledInstrument>>pruneNoteList:notesPerOctave: (in category 'other') -----
  pruneNoteList: aNoteList notesPerOctave: notesPerOctave
  	"Return a pruned version of the given note list with only the given number of notes per octave. Assume the given notelist is in sorted order."
  
  	| r interval lastPitch |
  	r := OrderedCollection new: aNoteList size.
  	interval := (2.0 raisedTo: (1.0 / notesPerOctave)) * 0.995.
  	lastPitch := 0.0.
  	aNoteList do: [:n |
  		n pitch > (lastPitch * interval) ifTrue: [
  			r addLast: n.
  			lastPitch := n pitch]].
  	^ r
  !

Item was changed:
  ----- Method: SampledInstrument>>pruneToNotesPerOctave: (in category 'other') -----
  pruneToNotesPerOctave: notesPerOctave
  	"Prune all my keymaps to the given number of notes per octave."
  
  	sustainedLoud := self midiKeyMapFor:
  		(self pruneNoteList: sustainedLoud notesPerOctave: notesPerOctave).
  	sustainedSoft := self midiKeyMapFor:
  		(self pruneNoteList: sustainedSoft notesPerOctave: notesPerOctave).
  	staccatoLoud := self midiKeyMapFor:
  		(self pruneNoteList: staccatoLoud notesPerOctave: notesPerOctave).
  	staccatoSoft := self midiKeyMapFor:
  		(self pruneNoteList: staccatoSoft notesPerOctave: notesPerOctave).
  !

Item was changed:
  ----- Method: SampledInstrument>>pruneToSingleNote: (in category 'other') -----
  pruneToSingleNote: aNote
  	"Fill all my keymaps with the given note."
  
  	| oneNoteMap |
  	oneNoteMap := Array new: 128 withAll: aNote.
  	sustainedLoud := oneNoteMap.
  	sustainedSoft := oneNoteMap.
  	staccatoLoud := oneNoteMap.
  	staccatoSoft := oneNoteMap.
  !

Item was changed:
  ----- Method: SampledInstrument>>soundForMidiKey:dur:loudness: (in category 'playing') -----
  soundForMidiKey: midiKey dur: d loudness: l
  	"Answer an initialized sound object that generates a note for the given MIDI key (in the range 0..127), duration (in seconds), and loudness (in the range 0.0 to 1.0)."
  
  	| keymap note |
  	l >= loudThreshold
  		ifTrue: [
  			d >= sustainedThreshold
  				ifTrue: [keymap := sustainedLoud]
  				ifFalse: [keymap := staccatoLoud]]
  		ifFalse: [
  			d >= sustainedThreshold
  				ifTrue: [keymap := sustainedSoft]
  				ifFalse: [keymap := staccatoSoft]].
  	keymap ifNil: [keymap := sustainedLoud].
  	note := (keymap at: midiKey) copy.
  	^ note
  		setPitch: (AbstractSound pitchForMIDIKey: midiKey)
  		dur: d
  		loudness: (l * note gain)
  !

Item was changed:
  ----- Method: SampledInstrument>>staccatoLoudAndSoftSampleSet: (in category 'accessing') -----
  staccatoLoudAndSoftSampleSet: sortedNotes
  
  	staccatoLoud := self midiKeyMapFor: sortedNotes.
  	staccatoSoft := staccatoLoud.
  !

Item was changed:
  ----- Method: SampledInstrument>>staccatoLoudSampleSet: (in category 'accessing') -----
  staccatoLoudSampleSet: sortedNotes
  
  	staccatoLoud := self midiKeyMapFor: sortedNotes.
  !

Item was changed:
  ----- Method: SampledInstrument>>staccatoSoftSampleSet: (in category 'accessing') -----
  staccatoSoftSampleSet: sortedNotes
  
  	staccatoSoft := self midiKeyMapFor: sortedNotes.
  !

Item was changed:
  ----- Method: SampledInstrument>>sustainedLoudSampleSet: (in category 'accessing') -----
  sustainedLoudSampleSet: sortedNotes
  
  	sustainedLoud := self midiKeyMapFor: sortedNotes.
  !

Item was changed:
  ----- Method: SampledInstrument>>sustainedSoftSampleSet: (in category 'accessing') -----
  sustainedSoftSampleSet: sortedNotes
  
  	sustainedSoft := self midiKeyMapFor: sortedNotes.
  !

Item was changed:
  ----- Method: SampledInstrument>>sustainedThreshold: (in category 'accessing') -----
  sustainedThreshold: aNumber
  
  	sustainedThreshold := aNumber asFloat.
  !

Item was changed:
  ----- Method: SampledInstrument>>testAtPitch: (in category 'other') -----
  testAtPitch: aPitch
  	"SampledInstrument testAtPitch: 'c4'"
  
  	| pattern |
  	pattern := (#(
  		(c4 0.64 100) 
  		(c4 0.64 200) 
  		(c4 0.64 400) 
  		(c4 0.64 600) 
  		(c4 0.64 800) 
  		(c4 1.28 1000) 
  		(c4 1.28 400) 
  		(c4 0.32 500) 
  		(c4 0.32 500) 
  		(c4 0.32 500) 
  		(c4 0.32 500) 
  		(c4 0.16 500) 
  		(c4 0.16 500) 
  		(c4 0.16 500) 
  		(c4 0.16 500) 
  		(c4 0.16 500) 
  		(c4 0.08 500) 
  		(c4 0.08 500) 
  		(c4 0.16 500) 
  		(c4 0.08 500) 
  		(c4 0.08 500) 
  		(c4 0.64 500))
  			collect: [:triple | triple copy at: 1 put: aPitch; yourself]).
  	(AbstractSound noteSequenceOn: self from: pattern) play.
  !

Item was changed:
  ----- Method: SampledSound class>>addLibrarySoundNamed:fromAIFFfileNamed: (in category 'sound library') -----
  addLibrarySoundNamed: aString fromAIFFfileNamed: fileName
  	"Add a sound from the given AIFF file to the library."
  	"SampledSound
  		addLibrarySoundNamed: 'shutterClick'
  		fromAIFFfileNamed: '7.aif'"
  	"Add all .aif files in the current directory to the sound library:
  	| fileNames |
  	fileNames := FileDirectory default fileNamesMatching: '*.aif'.
  	fileNames do: [:fName |
  		SampledSound
  			addLibrarySoundNamed: (fName copyUpTo: $.)
  			fromAIFFfileNamed: fName]"
  
  	| snd |
  	snd := self fromAIFFfileNamed: fileName.
  	self addLibrarySoundNamed: aString
  		samples: snd samples
  		samplingRate: snd originalSamplingRate.
  !

Item was changed:
  ----- Method: SampledSound class>>convert8bitSignedTo16Bit: (in category 'utilities') -----
  convert8bitSignedTo16Bit: aByteArray
  	"Convert the given array of samples--assumed to be 8-bit signed, linear data--into 16-bit signed samples. Return an array containing the resulting samples. Typically used to read uncompressed AIFF sound data."
  
  	| result |
  	result := SoundBuffer newMonoSampleCount: aByteArray size.
  	self convert8bitSignedFrom: aByteArray to16Bit: result.
  	^ result
  !

Item was changed:
  ----- Method: SampledSound class>>convert8bitUnsignedTo16Bit: (in category 'utilities') -----
  convert8bitUnsignedTo16Bit: anArray
  	"Convert the given array of samples--assumed to be 8-bit unsigned, linear data--into 16-bit signed samples. Return an array containing the resulting samples. Typically used to read uncompressed WAVE sound data."
  
  	| n samples s |
  	n := anArray size.
  	samples := SoundBuffer newMonoSampleCount: n.
  	1 to: n do: [:i |
  		s := anArray at: i.
  		samples at: i put: (s - 128 * 256)].
  	^ samples
  !

Item was changed:
  ----- Method: SampledSound class>>convertBytesTo16BitSamples:mostSignificantByteFirst: (in category 'utilities') -----
  convertBytesTo16BitSamples: aByteArray mostSignificantByteFirst: msbFirst
  	"Convert the given ByteArray (with the given byte ordering) into 16-bit sample buffer."
  
  	| n data src b1 b2 w |
  	n := aByteArray size // 2.
  	data := SoundBuffer newMonoSampleCount: n.
  	src := 1.
  	1 to: n do: [:i |
  		b1 := aByteArray at: src.
  		b2 := aByteArray at: src + 1.
  		msbFirst
  			ifTrue: [w := (b1 bitShift: 8) + b2]
  			ifFalse: [w := (b2 bitShift: 8) + b1].
  		w > 32767 ifTrue: [w := w - 65536].
  		data at: i put: w.
  		src := src + 2].
  	^ data
  !

Item was changed:
  ----- Method: SampledSound class>>defaultSampleTable: (in category 'default sound') -----
  defaultSampleTable: anArray
  	"Set the sample table to be used as the default waveform for playing a score such as the Bach fugue. Array is assumed to contain monaural signed 16-bit sample values."
  
  	DefaultSampleTable := SoundBuffer fromArray: anArray.
  !

Item was changed:
  ----- Method: SampledSound class>>defaultSamples:repeated: (in category 'default sound') -----
  defaultSamples: anArray repeated: n
  
  	| data |
  	data := WriteStream on: (SoundBuffer newMonoSampleCount: anArray size * n).
  	n timesRepeat: [
  		anArray do: [:sample | data nextPut: sample truncated]].
  	DefaultSampleTable := data contents.
  !

Item was changed:
  ----- Method: SampledSound class>>fromAIFFfileNamed: (in category 'instance creation') -----
  fromAIFFfileNamed: fileName
  	"Read a SampledSound from the AIFF file of the given name, merging stereo to mono if necessary."
  	"(SampledSound fromAIFFfileNamed: '1.aif') play"
  	"| snd |
  	 FileDirectory default fileNames do: [:n |
  		(n endsWith: '.aif')
  			ifTrue: [
  				snd := SampledSound fromAIFFfileNamed: n.
  				snd play.
  				SoundPlayer waitUntilDonePlaying: snd]]."
  
  	| aiffFileReader |
  	aiffFileReader := AIFFFileReader new.
  	aiffFileReader readFromFile: fileName
  		mergeIfStereo: true
  		skipDataChunk: false.
  	^ self
  		samples: (aiffFileReader channelData at: 1)
  		samplingRate: aiffFileReader samplingRate
  !

Item was changed:
  ----- Method: SampledSound class>>initialize (in category 'class initialization') -----
  initialize
  	"SampledSound initialize"
  
  	IncrementFractionBits := 16.
  	IncrementScaleFactor := 2 raisedTo: IncrementFractionBits.
  	ScaledIndexOverflow := 2 raisedTo: 29.  "handle overflow before needing LargePositiveIntegers"
  	self useCoffeeCupClink.
  	SoundLibrary ifNil: [SoundLibrary := Dictionary new].
  	Beeper setDefault: (self new
  						setSamples: self coffeeCupClink
  						samplingRate: 12000).
  !

Item was changed:
  ----- Method: SampledSound class>>initializeCoffeeCupClink (in category 'coffee cup clink') -----
  initializeCoffeeCupClink
  	"Initialize the samples array for the sound of a spoon being tapped against a coffee cup."
  	"SampledSound initializeCoffeeCupClink"
  
  	| samples |
  	samples := #(768 1024 -256 2304 -13312 26624 32512 19200 6400 -256 5888 32512 28928 32512 -32768 32512 -32768 18688 26368 -26112 32512 32512 2304 32512 5632 2816 10240 -4608 -1792 32512 32512 -5376 10752 32512 32512 32512 8192 15872 32512 -3584 -32768 -23296 -24832 -32768 -32768 -32768 -2304 32512 32512 -32768 32512 -15360 6400 8448 -18176 -32768 -256 -32768 -29440 9472 20992 17920 32512 32512 -256 32512 -32768 -32768 -23040 -32768 -25088 -32768 -27648 -1536 24320 -32768 32512 20480 27904 22016 16384 -32768 32512 -27648 -32768 -7168 28160 -6400 5376 32512 -256 32512 -7168 -11776 -19456 -27392 -24576 -32768 -24064 -19456 12800 32512 27136 2048 25344 15616 8192 -4608 -28672 -32768 -30464 -2560 17664 256 -8192 8448 32512 27648 -6144 -512 -7424 -18688 7936 -256 -22272 -14080 2048 27648 15616 -12288 -768 5376 3328 5632 3072 -6656 -20480 10240 27136 -10752 -11008 -768 -2048 6144 -7168 -3584 -1024 -7680 19712 26112 1024 -11008 3072 16384 -8960 -14848 -4864 -23808 -11264 12288 8192 7168 4864 23040 32512 512 -11776 -5632 -16896 -21504 -12800 -6144 -16896 -4352 32512 32512 23296 21760 5632 2816 -9472 -20992 -11264 -29440 -32768 -3584 7680 8448 15360 32512 32512 15616 15104 -2048 -27904 -27904 -25600 -12288 -12032 -13568 17152 22272 15360 30208 28160 7680 -5632 -8192 -16384 -31744 -25856 -10752 -3840 6656 13056 24320 26368 12800 20736 12288 -19200 -20992 -16640 -21504 -17920 -6912 8448 11264 14080 23040 18176 8192 -1024 0 256 -20992 -19712 -4608 -11264 -2048 14080 12032 8192 6912 13056 9216 -5632 -5376 -3840 -6656 -9984 -5632 4864 -3584 -1280 17408 7680 -1280 4096 2816 -1024 -4864 3328 8448 -768 -5888 -2048 5120 0 3072 11008 -7680 -15360 2560 6656 -3840 0 11776 7680 2816 1536 -1280 -3840 -8704 -1536 3584 -9728 -9728 11776 18688 7680 6656 6400 -4864 -3840 -256 -6912 -13312 -11264 2304 9728 1792 3328 18944 18432 6912 6144 -1536 -17664 -14336 -2304 -10496 -15616 -4096 9728 17152 14848 13312 11520 2304 -1024 2560 -8704 -26624 -18688 -256 -256 2816 14080 13824 12544 14080 9728 -512 -12032 -8960 -3328 -9984 -15872 -5120 8192 3584 10496 20224 7936 4608 6144 1280 -8704 -12800 -7424 -8448 -8960 -3840 7424 13056 8704 13312 13056 -2304 -4864 -768 -7168 -10496 -4608 -1536 -3072 -1280 6144 13312 11008 4864 4864 1536 -8960 -7680 1792 -4864 -7680 2816 5632 3328 2560 5376 7936 3584 -512 512 -4608 -9728 0 9216 768 -4096 7680 7168 256 4608 -768 -8704 -6400 2048 6144 -3072 -3328 6400 9472 3840 -768 1792 -3840 -5120 6144 768 -9984 -4352 5120 9472 6912 2816 1792 1280 768 512 -2816 -9728 -6912 6912 6912 -3328 -768 8448 11776 10752 3328 -6912 -10752 -8704 -1536 0 -6912 -3328 9984 13568 7424 6144 6656 256 0 256 -12032 -17920 -8192 3584 8960 4096 5632 12032 8704 6912 5632 -3584 -10496 -7936 -2048 -9216 -11776 2304 9472 15104 14848 5888 512 -2816 1024 2560 -9984 -13312 -5120 768 1792 768 8448 12032 11264 12800 -256 -11264 -9728 -2304 3072 -4352 -6912 256 2304 5376 9984 8192 2816 1280 3584 -2048 -11008 -8448 -2048 3072 4864 2304 3072 3072 3072 7168 3328 -5376 -4864 512 512 -1792 -1792 1792 5376 5888 5888 512 -5888 -3584 4096 3584 -6400 -4864 4608 3072 3840 5376 1024 768 2816 5888 -768 -12288 -7936 2304 5888 3328 2048 6144 3072 3072 6400 -3328 -7168 256 4096 -512 -9472 -6656 3328 6912 9216 8704 3840 -2560 -256 6656 -2560 -11264 -4608 -768 -1280 1536 3072 4096 5120 9984 11264 1024 -8192 -6144 -1024 -3840 -5632 -512 1024 2304 9728 9728 1280 512 4096 2816 -3584 -9984 -6912 -2304 512 5632 7680 3584 1024 5632 5888 -1280 -3584 -2304 -2560 -1536 -1024 -1792 -512 1536 7680 9984 2048 -2048 2048 3328 -1280 -4096 -3328 -4608 -1280 4352 3328 1280 1792 5120 6912 1024 -2560 0 -768 -1024 1280 -256 -4608 -1280 6400 5120 768 1792 2560 2048 0 -1536 -1280 -2304 1024 5376 2560 -2560 -512 4096 2048 512 768 -1280 -256 2560 2560 -256 -1024 768 3584 1280 -3328 -1536 1792 2816 3328 2304 -256 256 2816 2304 -1280 -3328 -1536 2304 2304 -256 -256 1024 1536 3840 5120 1024 -2048 0 1536 -768 -2560 -1792 256 2304 2048 1536 256 768 5888 6656 256 -3840 -2304 -1280 -1536 256 0 -512 2304 4352 3840 768 0 2304 3072 256 -3072 -2560 -2560 256 4608 2560 256 1536 3072 3072 1792 256 256 512 -256 -768 -1280 -1536 768 4352 2816 -512 768 2560 2560 2304 -256 -1792 -768 768 1792 256 -2304 -256 3328 3840 2304 2304 1536 256 2048 1024 -1536 -1792 -1024 512 256 -512 0 2304 4864 5120 4352 1024 -1280 0 -768 -2816 -2304 -512 1024 2048 2304 2048 3072 3840 2816 2048 -512 -3072 -1792 -1536 -1280 768 1280 1536 2304 2816 2048 1536 2048 1536 1536 -768 -3840 -2048 0 1280 2816 1792 1536 2560 3584 2816 1024 256 -768 -768 -1280 -2816 -768 1792 3328 5120 3072 1280 1536 1792 768 -1024 -1280 -1536 -768 512 256 1536 2560 2560 3328 1280 0 768 1536 768 -256 -512 -1536 -1280 768 1280 2304 2560 2560 2560 1024 -256 -512 0 1280 1536 768 -1280 -512 2048 1536 2048 1280 -256 256 512 768 768 1280 2304 1792 512 -1280 -1024 768 1536 1536 256 -768 1536 3584 3072 1792 -256 -1536 -512 256 -512 -512 768 2048 2048 1792 1280 1280 3072 2816 768 -1024 -2304 -1024 256 256 1280 1792 2304 2816 2304 1280 512 1024 768 -768 -1280 -1280 -512 1536 2560 2816 2048 512 1024 1792 1280 768 0 -768 -768 0 256 256 1280 2560 2304 2304 1536 512 512 1024 1280 0 -1792 -1536 -512 1280 3072 2816 1792 512 1024 1536 256 -256 768 768 256 256 -256 512 1280 1280 1536 768 1024 1792 1536 1024 0 256 -512 -256 1024 512 256 768 1792 2304 1280 256 768 1024 1280 1792 768 -768 -768 768 512 256 1024 1792 1536 1280 1536 1792 1280 768 512 -512 -1792 -512 512 768 2304 2816 1792 768 1536 2304 1536 0 -256 -256 -768 -768 256 1536 1536 2304 2048 256 768 2048 2304 1280 0 -256 -1024 -1024 0 1024 1792 2304 2304 1280 512 1280 2048 1280 256 -512 -1792 -1536 256 1536 1792 2048 2048 2048 1536 512 512 768 256 -256 0 -512 -1024 768 2048 2304 2304 1280 1280 1024 1024 1024 0 -512 256 768 0 -256 1536 2304 1792 2304 1280 -512 -256 768 1536 1024 256 512 512 1024 1792 1792 1536 1024 1280 0 -1280 256 2048 2560 2048 1024 -256 -256 1024 1280 1536 1024 0 0 256 768 1792 2304 2048 1280 1024 0 -512 -256 256 1024 1024 512 768 768 1280 2048 1792 1024 768 768 -256 -1024 0 256 1024 1536 1024 1280 1536 1792 1792 1024 512 512 0 -512 -256 512 768 1280 1280 1024 1280 1792 1792 1280 512 -256 -256 256 512 1280 1024 1280 1280 1024 1024 768 1024 1024 1024 1280 256 256 768 768 1024 512 256 768 1280 2560 2560 1280 512 -256 -512 -256 1024 1536 768 1024 1280 768 1024 1536 1536 1024 256 0 0 0 768 768 512 1280 1536 1280 1280 1280 1280 768 768 256 -256 768 768 256 768 1280 1792 1536 1536 1536 256 512 1024 0 -768 -256 768 512 1024 2048 1536 1024 1536 1536 768 0 0 -256).
  
  	CoffeeCupClink := SoundBuffer fromArray: samples.
  !

Item was changed:
  ----- Method: SampledSound class>>next16BitWord:from: (in category 'WAV reading') -----
  next16BitWord: msbFirst from: stream
  	"Read a 16-bit positive integer from the input stream."
  	"Assume: Stream has at least two bytes left."
  
  	| n |
  	n := stream next: 2.
  	^msbFirst
  		ifTrue:[(n at: 1) * 256 + (n at: 2)]
  		ifFalse:[(n at: 2) * 256 + (n at: 1)]
  !

Item was changed:
  ----- Method: SampledSound class>>next32BitWord:from: (in category 'WAV reading') -----
  next32BitWord: msbFirst from: stream
  	"Read a 32-bit positive integer from the input stream."
  	"Assume: Stream has at least four bytes left."
  
  	| n |
  	n := stream next: 4.
  	^msbFirst
  		ifTrue:[(n at: 1) * 256 + (n at: 2) * 256 + (n at: 3) * 256 + (n at: 4)]
  		ifFalse:[(n at: 4) * 256 + (n at: 3) * 256 + (n at: 2) * 256 + (n at: 1)]
  !

Item was changed:
  ----- Method: SampledSound class>>playSoundNamed: (in category 'sound library') -----
  playSoundNamed: aString
  	"Play the sound with given name. Do nothing if there is no sound of that name in the library."
  	"SampledSound playSoundNamed: 'croak'"
  
  	| snd |
  	snd := self soundNamed: aString.
  	snd ifNotNil: [snd play].
  	^ snd
  !

Item was changed:
  ----- Method: SampledSound class>>readWaveChunk:inRIFF: (in category 'WAV reading') -----
  readWaveChunk: chunkType inRIFF: stream
  	"Search the stream for a format chunk of the given type and return its contents."
  
  	| id count |
  	stream reset; binary.
  	stream skip: 8.  "skip 'RIFF' and total length"
  	id := (stream next: 4) asString.  "contents type"
  	id = 'WAVE' ifFalse: [^ ''].     "content type must be WAVE"
  
  	"search for a chunk of the given type"
  	[id := (stream next: 4) asString.
  	 count := self next32BitWord: false from: stream.
  	 id = chunkType] whileFalse: [
  		"skip this chunk, rounding length up to a word boundary"
  		stream skip: (count + 1 bitAnd: 16rFFFFFFFE).
  		stream atEnd ifTrue: [^ '']].
  
  	^ stream next: count  "return raw chunk data"
  !

Item was changed:
  ----- Method: SampledSound class>>soundNamed:ifAbsent: (in category 'sound library') -----
  soundNamed: aString ifAbsent: aBlock
  	"Answer the sound of the given name, or if there is no sound of that name, answer the result of evaluating aBlock"
  	"(SampledSound soundNamed: 'shutterClick') play"
  
  	| entry samples |
  	entry := SoundLibrary
  		at: aString
  		ifAbsent:
  			[^ aBlock value].
  	entry ifNil: [^ aBlock value].
  	samples := entry at: 1.
  	samples class isBytes ifTrue: [samples := self convert8bitSignedTo16Bit: samples].
  	^ self samples: samples samplingRate: (entry at: 2)
  !

Item was changed:
  ----- Method: SampledSound class>>soundNames (in category 'sound library') -----
  soundNames
  	"Answer a list of sound names for the sounds stored in the sound library."
  	"| s |
  	 SampledSound soundNames asSortedCollection do: [:n |
  		n asParagraph display.
  		s := SampledSound soundNamed: n.
  		s ifNotNil: [s playAndWaitUntilDone]]"
  
  	^ SoundLibrary keys asArray
  !

Item was changed:
  ----- Method: SampledSound class>>uLawDecode: (in category 'utilities') -----
  uLawDecode: aByteArray
  	"Convert the given array of uLaw-encoded 8-bit samples into a SoundBuffer of 16-bit signed samples."
  
  	| n out decodingTable |
  	n := aByteArray size.
  	out := SoundBuffer newMonoSampleCount: n.
  	decodingTable := self uLawDecodeTable.
  	1 to: n do: [:i | out at: i put: (decodingTable at: (aByteArray at: i) + 1)].
  	^ out
  !

Item was changed:
  ----- Method: SampledSound class>>uLawDecodeTable (in category 'utilities') -----
  uLawDecodeTable
  	"Return a 256 entry table to be used to decode 8-bit uLaw-encoded samples."
  	"Details: This table was computed as follows:
  		| d encoded lastEncodedPos lastEncodedNeg |
  		d := Array new: 256.
  		lastEncodedPos := nil.
  		lastEncodedNeg := nil.
  		4095 to: 0 by: -1 do: [:s |
  			encoded := SampledSound uLawEncodeSample: s.
  			lastEncodedPos = encoded
  				ifFalse: [
  					d at: (encoded + 1) put: (s bitShift: 3).
  					lastEncodedPos := encoded].
  			encoded := encoded bitOr: 16r80.
  			lastEncodedNeg = encoded
  				ifFalse: [
  					d at: (encoded + 1) put: (s bitShift: 3) negated.
  					lastEncodedNeg := encoded]].
  		d "
  
  	^ #(32760 31608 30584 29560 28536 27512 26488 25464 24440 23416 22392 21368 20344 19320 18296 17272 16248 15736 15224 14712 14200 13688 13176 12664 12152 11640 11128 10616 10104 9592 9080 8568 8056 7800 7544 7288 7032 6776 6520 6264 6008 5752 5496 5240 4984 4728 4472 4216 3960 3832 3704 3576 3448 3320 3192 3064 2936 2808 2680 2552 2424 2296 2168 2040 1912 1848 1784 1720 1656 1592 1528 1464 1400 1336 1272 1208 1144 1080 1016 952 888 856 824 792 760 728 696 664 632 600 568 536 504 472 440 408 376 360 344 328 312 296 280 264 248 232 216 200 184 168 152 136 120 112 104 96 88 80 72 64 56 48 40 32 24 16 8 0 -32760 -31608 -30584 -29560 -28536 -27512 -26488 -25464 -24440 -23416 -22392 -21368 -20344 -19320 -18296 -17272 -16248 -15736 -15224 -14712 -14200 -13688 -13176 -12664 -12152 -11640 -11128 -10616 -10104 -9592 -9080 -8568 -8056 -7800 -7544 -7288 -7032 -6776 -6520 -6264 -6008 -5752 -5496 -5240 -4984 -4728 -4472 -4216 -3960 -3832 -3704 -3576 -3448 -3320 -3192 -3064 -2936 -2808 -2680 -2552 -2424 -2296 -2168 -2040 -1912 -1848 -1784 -1720 -1656 -1592 -1528 -1464 -1400 -1336 -1272 -1208 -1144 -1080 -1016 -952 -888 -856 -824 -792 -760 -728 -696 -664 -632 -600 -568 -536 -504 -472 -440 -408 -376 -360 -344 -328 -312 -296 -280 -264 -248 -232 -216 -200 -184 -168 -152 -136 -120 -112 -104 -96 -88 -80 -72 -64 -56 -48 -40 -32 -24 -16 -8 0)
  !

Item was changed:
  ----- Method: SampledSound class>>uLawEncode: (in category 'utilities') -----
  uLawEncode: anArray
  	"Convert the given array of 16-bit signed samples into a ByteArray of uLaw-encoded 8-bit samples."
  
  	| n out s |
  	n := anArray size.
  	out := ByteArray new: n.
  	1 to: n do: [:i |
  		s := anArray at: i.
  		s := s bitShift: -3.  "drop 4 least significant bits"
  		s < 0
  			ifTrue: [s := (self uLawEncodeSample: s negated) bitOr: 16r80]
  			ifFalse: [s := (self uLawEncodeSample: s)].
  		out at: i put: s].
  	^ out
  !

Item was changed:
  ----- Method: SampledSound class>>unusedSoundNameLike: (in category 'sound library') -----
  unusedSoundNameLike: desiredName
  	"Pick an unused sound name based on the given string. If necessary, append digits to avoid name conflicts with existing sounds."
  	"SampledSound unusedSoundNameLike: 'chirp'"
  
  	| newName i |
  	newName := desiredName.
  	i := 2.
  	[SoundLibrary includesKey: newName] whileTrue: [
  		newName := desiredName, i printString.
  		i := i + 1].
  	^ newName
  !

Item was changed:
  ----- Method: SampledSound class>>useCoffeeCupClink (in category 'default sound') -----
  useCoffeeCupClink
  	"Set the sample table to be used as the default waveform to the sound of a coffee cup being tapped with a spoon."
  	"SampledSound useCoffeeCupClink bachFugue play"
  
  	DefaultSampleTable := self coffeeCupClink.
  	NominalSamplePitch := 400.
  !

Item was changed:
  ----- Method: SampledSound>>duration: (in category 'accessing') -----
  duration: seconds
  
  	super duration: seconds.
  	count := initialCount := (seconds * self samplingRate) rounded.
  !

Item was changed:
  ----- Method: SampledSound>>endGracefully (in category 'playing') -----
  endGracefully
  	"See stopGracefully, which affects initialCOunt, and I don't think it should (di)."
  
  	| decayInMs env |
  	envelopes isEmpty
  		ifTrue: [
  			self adjustVolumeTo: 0 overMSecs: 10.
  			decayInMs := 10]
  		ifFalse: [
  			env := envelopes first.
  			decayInMs := env attackTime + env decayTime].
  	count := decayInMs * self samplingRate // 1000.
  !

Item was changed:
  ----- Method: SampledSound>>pitch: (in category 'initialization') -----
  pitch: pitchNameOrNumber
  
  	| p |
  	p := self nameOrNumberToPitch: pitchNameOrNumber.
  	originalSamplingRate :=
  		((self samplingRate asFloat * p asFloat) / NominalSamplePitch asFloat) asInteger.
  	self reset.
  !

Item was changed:
  ----- Method: SampledSound>>playSilentlyUntil: (in category 'playing') -----
  playSilentlyUntil: startTime
  	"Used to fast foward to a particular starting time.
  	Overridden to be instant for sampled sounds."
  
  "true ifTrue: [^ super playSilentlyUntil: startTime]."
  	indexHighBits := (startTime * originalSamplingRate) asInteger.
  	scaledIndex := IncrementScaleFactor.
  	count := initialCount - (startTime * self samplingRate).
  	mSecsSinceStart := (startTime * 1000) asInteger.
  
  !

Item was changed:
  ----- Method: SampledSound>>reset (in category 'playing') -----
  reset
  	"Details: The sample index and increment are scaled to allow fractional increments without having to do floating point arithmetic in the inner loop."
  
  	super reset.
  	scaledIncrement :=
  		((originalSamplingRate asFloat / self samplingRate) * IncrementScaleFactor) rounded.
  	count := initialCount.
  	scaledIndex := IncrementScaleFactor.  "index of the first sample, scaled"
  	indexHighBits := 0.
  !

Item was changed:
  ----- Method: SampledSound>>setPitch:dur:loudness: (in category 'initialization') -----
  setPitch: pitchNameOrNumber dur: d loudness: vol
  	"Used to play scores using the default sample table."
  	"(SampledSound pitch: 880.0 dur: 1.5 loudness: 0.6) play"
  
  	| p |
  	super setPitch: pitchNameOrNumber dur: d loudness: vol.
  	p := self nameOrNumberToPitch: pitchNameOrNumber.
  	samples := DefaultSampleTable.
  	samplesSize := samples size.
  	initialCount := (d * self samplingRate asFloat) rounded.
  	originalSamplingRate :=
  		((self samplingRate asFloat * p asFloat) / NominalSamplePitch asFloat) asInteger.
  	self loudness: vol.
  	self reset.
  !

Item was changed:
  ----- Method: SampledSound>>setSamples:samplingRate: (in category 'initialization') -----
  setSamples: anArray samplingRate: rate
  	"Set my samples array to the given array with the given nominal sampling rate. Altering the rate parameter allows the sampled sound to be played back at different pitches."
  	"Note: There are two ways to use sampled sound: (a) you can play them through once (supported by this method) or (b) you can make them the default waveform with which to play a musical score (supported by the class method defaultSampleTable:)."
  	"Assume: anArray is either a SoundBuffer or a collection of signed 16-bit sample values."
  	"(SampledSound
  		samples: SampledSound coffeeCupClink
  		samplingRate: 5000) play"
  
  	"copy the array into a SoundBuffer if necessary"
  	anArray class isWords
  		ifTrue: [samples := anArray]
  		ifFalse: [samples := SoundBuffer fromArray: anArray].
  
  	samplesSize := samples size.
  	samplesSize >= SmallInteger maxVal ifTrue: [  "this is unlikely..."
  		self error: 'sample count must be under ',  SmallInteger maxVal printString].
  	originalSamplingRate := rate.
  	initialCount := (samplesSize * self samplingRate) // originalSamplingRate.
  	self loudness: 1.0.
  	self reset.
  !

Item was changed:
  ----- Method: SampledSound>>setScaledIncrement: (in category 'playing') -----
  setScaledIncrement: aNumber
  
  	scaledIncrement := (aNumber * IncrementScaleFactor) rounded.
  
  !

Item was changed:
  ----- Method: SampledSound>>stopAfterMSecs: (in category 'playing') -----
  stopAfterMSecs: mSecs
  	"Terminate this sound this note after the given number of milliseconds."
  
  	count := (mSecs * self samplingRate) // 1000.
  !

Item was changed:
  ----- Method: ScorePlayer>>closeMIDIPort (in category 'midi output') -----
  closeMIDIPort
  	"Stop using MIDI for output. Music will be played using the built-in sound synthesis."
  
  	self pause.
  	midiPort := nil.
  !

Item was changed:
  ----- Method: ScorePlayer>>copySounds (in category 'copying') -----
  copySounds
  	"Private!! Support for copying."
  
  	instruments := instruments copy.
  	leftVols := leftVols copy.
  	rightVols := rightVols copy.
  	muted := muted copy.
  	self reset.
  !

Item was changed:
  ----- Method: ScorePlayer>>doControl (in category 'sound generation') -----
  doControl
  
  	super doControl.
  	1 to: activeSounds size do: [:i | (activeSounds at: i) first doControl].
  	ticksSinceStart := ticksSinceStart + ticksClockIncr.
  	self processAllAtTick: ticksSinceStart asInteger.
  !

Item was changed:
  ----- Method: ScorePlayer>>duration (in category 'accessing') -----
  duration
  	"Answer the duration in seconds of my MIDI score when played at the current rate. Take tempo changes into account."
  
  	| totalSecs currentTempo lastTempoChangeTick |
  	totalSecs := 0.0.
  	currentTempo := 120.0.  "quarter notes per minute"
  	lastTempoChangeTick := 0.
  	score tempoMap ifNotNil: [
  		score tempoMap do: [:tempoEvt |
  			"accumulate time up to this tempo change event"
  			secsPerTick := 60.0 / (currentTempo * rate * score ticksPerQuarterNote).
  			totalSecs := totalSecs + (secsPerTick * (tempoEvt time - lastTempoChangeTick)).
  
  			"set the new tempo"
  			currentTempo := (120.0 * (500000.0 / tempoEvt tempo)) roundTo: 0.01.
  			lastTempoChangeTick := tempoEvt time]].
  
  	"add remaining time through end of score"
  	secsPerTick := 60.0 / (currentTempo * rate * score ticksPerQuarterNote).
  	totalSecs := totalSecs + (secsPerTick * (score durationInTicks - lastTempoChangeTick)).
  	^ totalSecs
  !

Item was changed:
  ----- Method: ScorePlayer>>initialize (in category 'initialization') -----
  initialize
  
  	super initialize.
  	score := MIDIScore new initialize.
  	instruments := Array new.
  	overallVolume := 0.5.
  	leftVols := Array new.
  	rightVols := Array new.
  	muted := Array new.
  	rate := 1.0.
  	repeat := false.
  	durationInTicks := 100.!

Item was changed:
  ----- Method: ScorePlayer>>isDone (in category 'sound generation') -----
  isDone
  
  	| track |
  	activeSounds size > 0 ifTrue: [^ false].
  	activeMIDINotes size > 0 ifTrue: [^ false].
  	1 to: score tracks size do: [:i |
  		track := score tracks at: i.
  		(trackEventIndex at: i) <= track size ifTrue: [^ false]].
  	(trackEventIndex last) <= score ambientTrack size ifTrue: [^ false].
  	^ true
  !

Item was changed:
  ----- Method: ScorePlayer>>jumpToTick: (in category 'sound generation') -----
  jumpToTick: startTick
  
  
  	self reset.
  	self processTempoMapAtTick: startTick.
  	self skipNoteEventsThruTick: startTick.
  	self skipAmbientEventsThruTick: startTick.
  	ticksSinceStart := startTick.
  !

Item was changed:
  ----- Method: ScorePlayer>>midiPlayLoop (in category 'midi output') -----
  midiPlayLoop
  
  	| mSecsPerStep tStart mSecs |
  	mSecsPerStep := 5.
  	[done] whileFalse: [
  		tStart := Time millisecondClockValue.
  		self processAllAtTick: ticksSinceStart asInteger.
  		(Delay forMilliseconds: mSecsPerStep) wait.
  		mSecs := Time millisecondClockValue - tStart.
  		mSecs < 0 ifTrue: [mSecs := mSecsPerStep].  "clock wrap"
  		ticksSinceStart := ticksSinceStart + (mSecs asFloat / (1000.0 * secsPerTick))].
  !

Item was changed:
  ----- Method: ScorePlayer>>mixSampleCount:into:startingAt:leftVol:rightVol: (in category 'sound generation') -----
  mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol
  	"Play a number of sounds concurrently. The level of each sound can be set independently for the left and right channels."
  
  	| myLeftVol myRightVol someSoundIsDone pair snd trk left right |
  	myLeftVol := (leftVol * overallVolume) asInteger.
  	myRightVol := (rightVol * overallVolume) asInteger.
  	someSoundIsDone := false.
  	1 to: activeSounds size do: [:i |
  		pair := activeSounds at: i.
  		snd := pair at: 1.
  		trk := pair at: 2.
  		left := (myLeftVol * (leftVols at: trk)) // ScaleFactor.
  		right := (myRightVol * (rightVols at: trk)) // ScaleFactor.
  		snd samplesRemaining > 0
  			ifTrue: [
  				snd mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: left rightVol: right]
  			ifFalse: [someSoundIsDone := true]].
  
  	someSoundIsDone ifTrue: [
  		activeSounds := activeSounds select: [:p | p first samplesRemaining > 0]].
  !

Item was changed:
  ----- Method: ScorePlayer>>onScore: (in category 'initialization') -----
  onScore: aMIDIScore
  
  	| trackCount totalVol incr curr pan |
  	score := aMIDIScore.
  	trackCount := score tracks size.
  	durationInTicks := score durationInTicks.
  	instruments := (1 to: trackCount) collect: [:i | FMSound oboe1].
  	leftVols := Array new: trackCount.
  	rightVols := Array new: trackCount.
  	muted  := Array new: trackCount withAll: false.
  	rate := 1.0.
  	repeat := false.
  	tempo := 120.0.
  
  	trackCount = 0 ifTrue: [^ self].
  	1 to: trackCount do: [:i |
  		leftVols at: i put: ScaleFactor // 4.
  		rightVols at: i put: ScaleFactor // 4].
  
  	"distribute inital panning of tracks left-to-right"
  	totalVol := 1.0.
  	incr := totalVol / (((trackCount // 2) + 1) * 2).
  	curr := 0.
  	1 to: trackCount do: [:t |
  		t even
  			ifTrue: [pan := curr]
  			ifFalse: [
  				curr := curr + incr.
  				pan := totalVol - curr].
  		self panForTrack: t put: pan].
  
  !

Item was changed:
  ----- Method: ScorePlayer>>openMIDIPort: (in category 'midi output') -----
  openMIDIPort: portNum
  	"Open the given MIDI port. Music will be played as MIDI commands to the given MIDI port."
  
  	midiPort := SimpleMIDIPort openOnPortNumber: portNum.
  !

Item was changed:
  ----- Method: ScorePlayer>>overallVolume: (in category 'accessing') -----
  overallVolume: aNumber
  	"Set the overally playback volume to a value between 0.0 (off) and 1.0 (full blast)."
  
  	overallVolume := (aNumber asFloat min: 1.0) max: 0.0.
  
  !

Item was changed:
  ----- Method: ScorePlayer>>panForTrack: (in category 'accessing') -----
  panForTrack: i
  
  	| left right fullVol pan |
  	left := leftVols at: i.
  	right := rightVols at: i.
  	left = right ifTrue: [^ 0.5].  "centered"
  	fullVol := left max: right.
  	left < fullVol
  		ifTrue: [pan := left asFloat / (2.0 * fullVol)]
  		ifFalse: [pan := 1.0 - (right asFloat / (2.0 * fullVol))].
  	^ pan roundTo: 0.001
  
  !

Item was changed:
  ----- Method: ScorePlayer>>panForTrack:put: (in category 'accessing') -----
  panForTrack: trackIndex put: aNumber
  	"Set the left-right pan for this track to a value in the range [0.0..1.0], where 0.0 means full-left."
  
  	| fullVol pan left right |
  	trackIndex > leftVols size ifTrue: [^ self].
  	fullVol := (leftVols at: trackIndex) max: (rightVols at: trackIndex).
  	pan := (aNumber asFloat min: 1.0) max: 0.0.
  	pan <= 0.5
  		ifTrue: [  "attenuate right channel"
  			left := fullVol.
  			right := 2.0 * pan * fullVol]
  		ifFalse: [  "attenuate left channel"
  			left := 2.0 * (1.0 - pan) * fullVol.
  			right := fullVol].
  	rightVols at: trackIndex put: right asInteger.
  	leftVols at: trackIndex put: left asInteger.
  !

Item was changed:
  ----- Method: ScorePlayer>>pause (in category 'operating') -----
  pause
  	"Pause this sound. It can be resumed from this point, or reset and resumed to start from the beginning."
  
  	score pauseFrom: self.
  	super pause.
  	activeSounds := activeSounds species new.
  	midiPort ifNotNil: [self stopMIDIPlaying].
  !

Item was changed:
  ----- Method: ScorePlayer>>positionInScore: (in category 'accessing') -----
  positionInScore: pos
  
  	self isPlaying ifTrue: [^ self "ignore rude intrusion"].
  	ticksSinceStart := pos * durationInTicks.
  	done := false.
  
  !

Item was changed:
  ----- Method: ScorePlayer>>processAllAtTick: (in category 'sound generation') -----
  processAllAtTick: scoreTick
  
  	self processTempoMapAtTick: scoreTick.
  	midiPort
  		ifNil: [self processNoteEventsAtTick: scoreTick]
  		ifNotNil: [self processMIDIEventsAtTick: scoreTick].
  	self processAmbientEventsAtTick: scoreTick.
  	self isDone ifTrue: [
  		repeat
  			ifTrue: [self reset]
  			ifFalse: [done := true]].
  !

Item was changed:
  ----- Method: ScorePlayer>>processAmbientEventsAtTick: (in category 'sound generation') -----
  processAmbientEventsAtTick: scoreTick
  	"Process ambient events through the given tick."
  
  	| i evt |
  	i := trackEventIndex at: trackEventIndex size.
  	[evt := score ambientEventAfter: i ticks: scoreTick.
  	 evt ~~ nil] whileTrue: [
  		i := i + 1.
  		evt occurAtTime: scoreTick inScorePlayer: self atIndex: i inEventTrack: score ambientTrack secsPerTick: secsPerTick].
  	trackEventIndex at: trackEventIndex size put: i.
  !

Item was changed:
  ----- Method: ScorePlayer>>processMIDIEventsAtTick: (in category 'midi output') -----
  processMIDIEventsAtTick: scoreTick
  	"Process note events through the given score tick using MIDI."
  
  	| j evt |
  	1 to: score tracks size do: [:i |
  		j := trackEventIndex at: i.
  		[evt := score eventForTrack: i after: j ticks: scoreTick.
  		 evt ~~ nil] whileTrue: [
  			evt isNoteEvent
  				ifTrue: [
  					(muted at: i) ifFalse: [
  						evt startNoteOnMidiPort: midiPort.
  						activeMIDINotes add: (Array with: evt with: i)]]
  				ifFalse: [evt outputOnMidiPort: midiPort].
  			j := j + 1.
  			trackEventIndex at: i put: j]].
  	self turnOffActiveMIDINotesAt: scoreTick.
  !

Item was changed:
  ----- Method: ScorePlayer>>processNoteEventsAtTick: (in category 'sound generation') -----
  processNoteEventsAtTick: scoreTick
  	"Process note events through the given score tick using internal Squeak sound synthesis."
  
  	| instr j evt snd |
  	1 to: score tracks size do: [:i |
  		instr := instruments at: i.
  		j := trackEventIndex at: i.
  		[evt := score eventForTrack: i after: j ticks: scoreTick.
  		 evt ~~ nil] whileTrue: [
  			(evt isNoteEvent and: [(muted at: i) not]) ifTrue: [
  				snd := instr
  					soundForMidiKey: evt midiKey
  					dur: secsPerTick * evt duration
  					loudness: evt velocity asFloat / 127.0.
  				activeSounds add: (Array with: snd with: i)].
  			j := j + 1.
  			trackEventIndex at: i put: j]].
  !

Item was changed:
  ----- Method: ScorePlayer>>processTempoMapAtTick: (in category 'sound generation') -----
  processTempoMapAtTick: scoreTick
  	"Process tempo changes through the given score tick."
  
  	| map tempoChanged |
  	map := score tempoMap.
  	map ifNil: [^ self].
  	tempoChanged := false.
  	[(tempoMapIndex <= map size) and:
  	 [(map at: tempoMapIndex) time <= scoreTick]] whileTrue: [
  		tempoChanged := true.
  		tempoMapIndex := tempoMapIndex + 1].
  
  	tempoChanged ifTrue: [
  		tempo := (120.0 * (500000.0 / (map at: tempoMapIndex - 1) tempo)) roundTo: 0.01.
  		self tempoOrRateChanged].
  
  !

Item was changed:
  ----- Method: ScorePlayer>>rate: (in category 'accessing') -----
  rate: aNumber
  	"Set the playback rate. For example, a rate of 2.0 will playback at twice normal speed."
  
  	rate := aNumber asFloat.
  	self tempoOrRateChanged.
  !

Item was changed:
  ----- Method: ScorePlayer>>repeat: (in category 'accessing') -----
  repeat: aBoolean
  	"Turn repeat mode on or off."
  
  	repeat := aBoolean.
  !

Item was changed:
  ----- Method: ScorePlayer>>reset (in category 'sound generation') -----
  reset
  
  	super reset.
  	tempo := 120.0.
  	self tempoOrRateChanged.
  	done := false.
  	ticksSinceStart := 0.
  	"one index for each sound track, plus one for the ambient track..."
  	trackEventIndex := Array new: score tracks size+1 withAll: 1.
  	tempoMapIndex := 1.
  	activeSounds := OrderedCollection new.
  	activeMIDINotes := OrderedCollection new.
  	score resetFrom: self.
  	overallVolume ifNil: [overallVolume := 0.5].
  !

Item was changed:
  ----- Method: ScorePlayer>>settingsString (in category 'accessing') -----
  settingsString
  
  	| s |
  	s := WriteStream on: (String new: 1000).
  	s nextPutAll: 'player'; cr.
  	s tab; nextPutAll: 'rate: ', self rate printString, ';'; cr.
  	s tab; nextPutAll: 'overallVolume: ', self overallVolume printString, ';'; cr.
  	1 to: self trackCount do: [:t |
  		s tab; nextPutAll: 'instrumentForTrack: ', t printString,
  			' put: (AbstractSound soundNamed: #default);'; cr.
  		s tab; nextPutAll: 'mutedForTrack: ', t printString,
  			' put: ', (self mutedForTrack: t) printString, ';'; cr.
  		s tab; nextPutAll: 'volumeForTrack: ', t printString,
  			' put: ', (self volumeForTrack: t) printString, ';'; cr.
  		s tab; nextPutAll: 'panForTrack: ', t printString,
  			' put: ', (self panForTrack: t) printString, ';'; cr].
  	s tab; nextPutAll: 'repeat: ', self repeat printString, '.'; cr.
  	^ s contents
  !

Item was changed:
  ----- Method: ScorePlayer>>skipNoteEventsThruTick: (in category 'sound generation') -----
  skipNoteEventsThruTick: startTick
  	"Skip note events through the given score tick using internal Squeak sound synthesis."
  
  	| j evt |
  	1 to: score tracks size do: [:i |
  		j := trackEventIndex at: i.
  		[evt := score eventForTrack: i after: j ticks: startTick.
  		 evt == nil] whileFalse: [
  			evt isNoteEvent
  				ifTrue: [
  					(((evt time + evt duration) > startTick) and: [(muted at: i) not]) ifTrue: [
  						self startNote: evt forStartTick: startTick trackIndex: i]]
  				ifFalse: [
  					midiPort == nil ifFalse: [evt outputOnMidiPort: midiPort]].
  			j := j + 1].
  		trackEventIndex at: i put: j].
  !

Item was changed:
  ----- Method: ScorePlayer>>startMIDIPlaying (in category 'midi output') -----
  startMIDIPlaying
  	"Start up a process to play this score via MIDI."
  
  	midiPort ensureOpen.
  	midiPlayerProcess ifNotNil: [midiPlayerProcess terminate].
  	midiPlayerProcess := [self midiPlayLoop] newProcess.
  	midiPlayerProcess
  		priority: Processor userInterruptPriority;
  		resume.
  !

Item was changed:
  ----- Method: ScorePlayer>>startNote:forStartTick:trackIndex: (in category 'sound generation') -----
  startNote: noteEvent forStartTick: startTick trackIndex: trackIndex
  	"Prepare a note to begin playing at the given tick. Used to start playing at an arbitrary point in the score. Handle both MIDI and built-in synthesis cases."
  
  	| snd |
  	midiPort
  		ifNil: [
  			snd := (instruments at: trackIndex)
  				soundForMidiKey: noteEvent midiKey
  				dur: secsPerTick * (noteEvent endTime - startTick)
  				loudness: noteEvent velocity asFloat / 127.0.
  			activeSounds add: (Array with: snd with: trackIndex)]
  		ifNotNil: [
  			noteEvent startNoteOnMidiPort: midiPort.
  			activeMIDINotes add: (Array with: noteEvent with: trackIndex)].
  !

Item was changed:
  ----- Method: ScorePlayer>>stopMIDIPlaying (in category 'midi output') -----
  stopMIDIPlaying
  	"Terminate the MIDI player process and turn off any active notes."
  
  	midiPlayerProcess ifNotNil: [midiPlayerProcess terminate].
  	midiPlayerProcess := nil.
  	activeMIDINotes do: [:pair | pair first endNoteOnMidiPort: midiPort].
  	activeMIDINotes := activeMIDINotes species new.
  !

Item was changed:
  ----- Method: ScorePlayer>>tempoOrRateChanged (in category 'operating') -----
  tempoOrRateChanged
  	"This method should be called after changing the tempo or rate."
  
  	secsPerTick := 60.0 / (tempo * rate * score ticksPerQuarterNote).
  	ticksClockIncr := (1.0 / self controlRate) / secsPerTick.
  !

Item was changed:
  ----- Method: ScorePlayer>>ticksSinceStart: (in category 'accessing') -----
  ticksSinceStart: newTicks
  	"Adjust ticks to folow, eg, piano roll autoscrolling"
  
  	self isPlaying ifFalse: [ticksSinceStart := newTicks]
  !

Item was changed:
  ----- Method: ScorePlayer>>updateDuration (in category 'initialization') -----
  updateDuration
  
  	durationInTicks := score durationInTicks.
  !

Item was changed:
  ----- Method: ScorePlayer>>volumeForTrack: (in category 'accessing') -----
  volumeForTrack: i
  
  	| vol |
  	vol := (leftVols at: i) max: (rightVols at: i).
  	^ (vol asFloat / ScaleFactor) roundTo: 0.0001
  !

Item was changed:
  ----- Method: ScorePlayer>>volumeForTrack:put: (in category 'accessing') -----
  volumeForTrack: trackIndex put: aNumber
  
  	| newVol oldLeft oldRight oldFullVol left right |
  	trackIndex > leftVols size ifTrue: [^ self].
  	newVol := ((aNumber asFloat max: 0.0) min: 1.0) * ScaleFactor.
  	oldLeft := leftVols at: trackIndex.
  	oldRight := rightVols at: trackIndex.
  	oldFullVol := oldLeft max: oldRight.
  	oldFullVol = 0 ifTrue: [oldFullVol := 1.0].
  	oldLeft < oldFullVol
  		ifTrue: [
  			left := newVol * oldLeft / oldFullVol.
  			right := newVol]
  		ifFalse: [
  			left := newVol.
  			right := newVol * oldRight / oldFullVol].
  	leftVols at: trackIndex put: left asInteger.
  	rightVols at: trackIndex put: right asInteger.
  !

Item was changed:
  ----- Method: SequentialSound>>copySounds (in category 'copying') -----
  copySounds
  	"Private!! Support for copying. Copy my component sounds."
  
  	sounds := sounds collect: [:s | s copy].
  !

Item was changed:
  ----- Method: SequentialSound>>initialize (in category 'initialization') -----
  initialize
  
  	super initialize.
  	sounds := Array new.
  	currentIndex := 0.
  !

Item was changed:
  ----- Method: SequentialSound>>mixSampleCount:into:startingAt:leftVol:rightVol: (in category 'sound generation') -----
  mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol
  	"Play a collection of sounds in sequence."
  	"PluckedSound chromaticScale play"
  
  	| finalIndex i snd remaining count |
  	currentIndex = 0 ifTrue: [^ self].  "already done"
  	finalIndex := (startIndex + n) - 1.
  	i := startIndex.
  	[i <= finalIndex] whileTrue: [
  		snd := (sounds at: currentIndex).
  		[(remaining := snd samplesRemaining) <= 0] whileTrue: [
  			"find next undone sound"
  			currentIndex < sounds size
  				ifTrue: [
  					currentIndex := currentIndex + 1.
  					snd := (sounds at: currentIndex)]
  				ifFalse: [
  					currentIndex := 0.
  					^ self]].  "no more sounds"
  		count := (finalIndex - i) + 1.
  		remaining < count ifTrue: [count := remaining].
  		snd mixSampleCount: count into: aSoundBuffer startingAt: i leftVol: leftVol rightVol: rightVol.
  		i := i + count].
  !

Item was changed:
  ----- Method: SequentialSound>>pruneFinishedSounds (in category 'composition') -----
  pruneFinishedSounds
  	"Remove any sounds that have been completely played."
  
  	| newSnds |
  	(currentIndex > 1 and: [currentIndex < sounds size]) ifFalse: [^ self].
  	newSnds := sounds copyFrom: currentIndex to: sounds size.
  	currentIndex := 1.
  	sounds := newSnds.
  !

Item was changed:
  ----- Method: SequentialSound>>removeFirstCompleteSoundOrNil (in category 'composition') -----
  removeFirstCompleteSoundOrNil
  	"Remove the first sound if it has been completely recorded."
  
  	| firstSound |
  
  	sounds size > 0 ifFalse: [^ nil].
  	firstSound := sounds first.
  	sounds := sounds copyFrom: 2 to: sounds size.
  	^firstSound
  !

Item was changed:
  ----- Method: SequentialSound>>reset (in category 'sound generation') -----
  reset
  
  	super reset.
  	sounds do: [:snd | snd reset].
  	sounds size > 0 ifTrue: [currentIndex := 1].
  !

Item was changed:
  ----- Method: SimpleMIDIPort class>>closeAllPorts (in category 'utilities') -----
  closeAllPorts
  	"Close all MIDI ports."
  	"SimpleMIDIPort closeAllPorts"
  
  	| lastPortNum |
  	lastPortNum := self primPortCount - 1.
  	0 to: lastPortNum do: [:portNum | self basicNew primMIDIClosePort: portNum].
  !

Item was changed:
  ----- Method: SimpleMIDIPort class>>initialize (in category 'class initialization') -----
  initialize
  	"SimpleMIDIPort initialize"
  
  	InterfaceClockRate := 1000000.
  	DefaultPortNumber := 0.
  !

Item was changed:
  ----- Method: SimpleMIDIPort>>close (in category 'open/close') -----
  close
  	"Close this MIDI port."
  
  	portNumber ifNotNil: [self primMIDIClosePort: portNumber].
  	accessSema := nil.
  	lastCommandByteOut := nil.
  !

Item was changed:
  ----- Method: SimpleMIDIPort>>ensureOpen (in category 'open/close') -----
  ensureOpen
  	"Make sure this MIDI port is open. It is good to call this before starting to use a port in case an intervening image save/restore has caused the underlying hardware port to get closed."
  
  	portNumber ifNil: [^ self error: 'Use "openOn:" to open a MIDI port initially'].
  	self primMIDIClosePort: portNumber.
  	self primMIDIOpenPort: portNumber readSemaIndex: 0 interfaceClockRate: InterfaceClockRate.
  	accessSema := Semaphore forMutualExclusion.
  	lastCommandByteOut := Array new: 16 withAll: 0.  "clear running status"
  !

Item was changed:
  ----- Method: SimpleMIDIPort>>flushInput (in category 'input') -----
  flushInput
  	"Read any lingering MIDI data from this port's input buffer."
  
  	| buf |
  	buf := ByteArray new: 1000.
  	[(self readInto: buf) > 0] whileTrue.
  !

Item was changed:
  ----- Method: SimpleMIDIPort>>openOnPortNumber: (in category 'open/close') -----
  openOnPortNumber: portNum
  	"Open this MIDI port on the given port number."
  
  	self close.
  	portNumber := portNum.
  	accessSema := Semaphore forMutualExclusion.
  	self ensureOpen.
  !

Item was changed:
  ----- Method: SoundBuffer class>>fromArray: (in category 'instance creation') -----
  fromArray: anArray
  	"Return a new SoundBuffer whose contents are copied from the given Array or ByteArray."
  
  	| new |
  	new := SoundBuffer newMonoSampleCount: anArray size.
  	1 to: anArray size do: [:i | new at: i put: (anArray at: i)].
  	^ new
  !

Item was changed:
  ----- Method: SoundBuffer class>>fromByteArray: (in category 'instance creation') -----
  fromByteArray: aByteArray
  	"Convert the given ByteArray (stored with the most significant byte first) into 16-bit sample buffer."
  
  	| n buf src w |
  	n := aByteArray size // 2.
  	buf := SoundBuffer newMonoSampleCount: n.
  	src := 1.
  	1 to: n do: [:i |
  		w := ((aByteArray at: src) bitShift: 8) + (aByteArray at: src + 1).
  		w > 32767 ifTrue: [w := w - 65536].
  		buf at: i put: w.
  		src := src + 2].
  	^ buf
  !

Item was changed:
  ----- Method: SoundBuffer class>>initialize (in category 'class initialization') -----
  initialize
  	"Build a sine wave table."
  	"SoundBuffer initialize"
  
  	| tableSize radiansPerStep peak |
  	tableSize := 4000.
  	SineTable := self newMonoSampleCount: tableSize.
  	radiansPerStep := (2.0 * Float pi) / tableSize asFloat.
  	peak := ((1 bitShift: 15) - 1) asFloat.  "range is +/- (2^15 - 1)"
  	1 to: tableSize do: [:i |
  		SineTable at: i put: (peak * (radiansPerStep * (i - 1)) sin) rounded].
  !

Item was changed:
  ----- Method: SoundBuffer class>>startUp (in category 'objects from disk') -----
  startUp
  	"Check if the word order has changed from the last save."
  
  	| la |
  	la := ShortIntegerArray classPool at: #LastSaveOrder.
  	((la at: 2) = 42 and: [(la at: 1) = 13]) 
  		ifTrue: [^self swapHalves]. "Reverse the two 16-bit halves."
  				"Another reversal happened automatically which reversed the bytes."
  !

Item was changed:
  ----- Method: SoundBuffer>>asByteArray (in category 'utilities') -----
  asByteArray
  	"Answer a ByteArray containing my sample data serialized in most-significant byte first order."
  
  	| sampleCount bytes dst s |
  	sampleCount := self monoSampleCount.
  	bytes := ByteArray new: 2 * sampleCount.
  	dst := 0.
  	1 to: sampleCount do: [:src |
  		s := self at: src.
  		bytes at: (dst := dst + 1) put: ((s bitShift: -8) bitAnd: 255).
  		bytes at: (dst := dst + 1) put: (s bitAnd: 255)].
  	^ bytes
  
  	!

Item was changed:
  ----- Method: SoundBuffer>>averageEvery:from:upTo: (in category 'utilities') -----
  averageEvery: nSamples from: anotherBuffer upTo: inCount
  
  	| fromIndex sum |
  
  	fromIndex := 1.
  	1 to: inCount // nSamples do: [ :i |
  		sum := 0.
  		nSamples timesRepeat: [
  			sum := sum + (anotherBuffer at: fromIndex).
  			fromIndex := fromIndex + 1.
  		].
  		self at: i put: sum // nSamples.
  	].
  !

Item was changed:
  ----- Method: SoundBuffer>>downSampledLowPassFiltering: (in category 'utilities') -----
  downSampledLowPassFiltering: doFiltering
  	"Answer a new SoundBuffer half the size of the receiver consisting of every other sample. If doFiltering is true, a simple low-pass filter is applied to avoid aliasing of high frequencies. Assume that receiver is monophonic."
  	"Details: The simple low-pass filter in the current implementation could be improved, at some additional cost."
  
  	| n resultBuf j |
  	n := self monoSampleCount.
  	resultBuf := SoundBuffer newMonoSampleCount: n // 2.
  	j := 0.
  	doFiltering
  		ifTrue: [
  			1 to: n by: 2 do: [:i |
  				resultBuf at: (j := j + 1) put:
  					(((self at: i) + (self at: i + 1)) bitShift: -1)]]
  		ifFalse: [
  			1 to: n by: 2 do: [:i |
  				resultBuf at: (j := j + 1) put: (self at: i)]].
  
  	^ resultBuf!

Item was changed:
  ----- Method: SoundBuffer>>extractLeftChannel (in category 'utilities') -----
  extractLeftChannel
  	"Answer a new SoundBuffer half the size of the receiver consisting of only the left channel of the receiver, which is assumed to contain stereo sound data."
  
  	| n resultBuf j |
  	n := self monoSampleCount.
  	resultBuf := SoundBuffer newMonoSampleCount: n // 2.
  	j := 0.
  	1 to: n by: 2 do: [:i | resultBuf at: (j := j + 1) put: (self at: i)].
  	^ resultBuf!

Item was changed:
  ----- Method: SoundBuffer>>extractRightChannel (in category 'utilities') -----
  extractRightChannel
  	"Answer a new SoundBuffer half the size of the receiver consisting of only the right channel of the receiver, which is assumed to contain stereo sound data."
  
  	| n resultBuf j |
  	n := self monoSampleCount.
  	resultBuf := SoundBuffer newMonoSampleCount: n // 2.
  	j := 0.
  	2 to: n by: 2 do: [:i | resultBuf at: (j := j + 1) put: (self at: i)].
  	^ resultBuf!

Item was changed:
  ----- Method: SoundBuffer>>lowPassFiltered (in category 'utilities') -----
  lowPassFiltered
  	"Answer a simple low-pass filtered copy of this buffer. Assume it is monophonic."
  
  	| sz out last this |
  	sz := self monoSampleCount.
  	out := self clone.
  	last := self at: 1.
  	2 to: sz do: [:i |
  		this := self at: i.
  		out at: i put: (this + last) // 2.
  		last := this].
  	^ out
  !

Item was changed:
  ----- Method: SoundBuffer>>mergeStereo (in category 'utilities') -----
  mergeStereo
  	"Answer a new SoundBuffer half the size of the receiver that mixes the left and right stereo channels of the receiver, which is assumed to contain stereo sound data."
  
  	| n resultBuf j |
  	n := self monoSampleCount.
  	resultBuf := SoundBuffer newMonoSampleCount: n // 2.
  	j := 0.
  	1 to: n by: 2 do: [:i | resultBuf at: (j := j + 1) put: (((self at: i) + (self at: i + 1)) // 2)].
  	^ resultBuf
  !

Item was changed:
  ----- Method: SoundBuffer>>normalized: (in category 'utilities') -----
  normalized: percentOfFullVolume
  	"Increase my amplitudes so that the highest peak is the given percent of full volume. For example 's normalized: 50' would normalize to half of full volume."
  
  	| peak s mult |
  	peak := 0.
  	1 to: self size do: [:i |
  		s := (self at: i) abs.
  		s > peak ifTrue: [peak := s]].
  	mult := (32767.0 * percentOfFullVolume) / (100.0 * peak).
  	1 to: self size do: [:i | self at: i put: (mult * (self at: i)) asInteger].
  !

Item was changed:
  ----- Method: SoundBuffer>>reverseEndianness (in category 'objects from disk') -----
  reverseEndianness
  	"Swap the bytes of each 16-bit word, using a fast BitBlt hack."
  
  	| hack blt |
  	hack := Form new hackBits: self.
  	blt := (BitBlt toForm: hack) sourceForm: hack.
  	blt combinationRule: Form reverse.  "XOR"
  	blt sourceY: 0; destY: 0; height: self size; width: 1.
  	blt sourceX: 0; destX: 1; copyBits.  "Exchange bytes 0 and 1"
  	blt sourceX: 1; destX: 0; copyBits.
  	blt sourceX: 0; destX: 1; copyBits.
  	blt sourceX: 2; destX: 3; copyBits.  "Exchange bytes 2 and 3"
  	blt sourceX: 3; destX: 2; copyBits.
  	blt sourceX: 2; destX: 3; copyBits.
  !

Item was changed:
  ----- Method: SoundBuffer>>splitStereo (in category 'utilities') -----
  splitStereo
  	"Answer an array of two SoundBuffers half the size of the receiver consisting of the left and right channels of the receiver (which is assumed to contain stereo sound data)."
  
  	| n leftBuf rightBuf leftIndex rightIndex |
  	n := self monoSampleCount.
  	leftBuf := SoundBuffer newMonoSampleCount: n // 2.
  	rightBuf := SoundBuffer newMonoSampleCount: n // 2.
  	leftIndex := rightIndex := 0.
  	1 to: n by: 2 do: [:i |
  		leftBuf at: (leftIndex := leftIndex + 1) put: (self at: i).
  		rightBuf at: (rightIndex := rightIndex + 1) put: (self at: i + 1)].
  	^ Array with: leftBuf with: rightBuf
  !

Item was changed:
  ----- Method: SoundBuffer>>storeExtendedFloat:on: (in category 'utilities') -----
  storeExtendedFloat: aNumber on: aBinaryStream
  	"Store an Apple extended-precision 80-bit floating point number on the given stream."
  	"Details: I could not find the specification for this format, so constants were determined empirically based on assumption of 1-bit sign, 15-bit exponent, 64-bit mantissa. This format does not seem to have an implicit one before the mantissa as some float formats do."
  
  	| n isNeg exp mantissa |
  	n := aNumber asFloat.
  	isNeg := false.
  	n < 0.0 ifTrue: [
  		n := 0.0 - n.
  		isNeg := true].
  	exp := (n log: 2.0) ceiling.
  	mantissa := (n * (2 raisedTo: 64 - exp)) truncated.
  	exp := exp + 16r4000 - 2.  "not sure why the -2 is needed..."
  	isNeg ifTrue: [exp := exp bitOr: 16r8000].  "set sign bit"
  	aBinaryStream nextPut: ((exp bitShift: -8) bitAnd: 16rFF).
  	aBinaryStream nextPut: (exp bitAnd: 16rFF).
  	8 to: 1 by: -1 do: [:i | aBinaryStream nextPut: (mantissa digitAt: i)].!

Item was changed:
  ----- Method: SoundBuffer>>trimmedThreshold: (in category 'utilities') -----
  trimmedThreshold: threshold
  
  	| start end |
  	start := self indexOfFirstSampleOver: threshold.
  	end :=  self indexOfLastSampleOver: threshold.
  	start > end ifTrue: [^ SoundBuffer new].
  	start := (start - 200) max: 1.
  	end := (end + 200) min: self size.
  	^ self copyFrom: start to: end
  !

Item was changed:
  ----- Method: SoundCodec>>compressSound: (in category 'compress/decompress') -----
  compressSound: aSound
  	"Compress the entirety of the given sound with this codec. Answer a CompressedSoundData."
  
  	| compressed channels |
  	compressed := CompressedSoundData new
  		codecName: self class name;
  		soundClassName: aSound class name.
  	(aSound isKindOf: SampledSound) ifTrue: [
  		channels := Array new: 1.
  		channels at: 1 put: (self encodeSoundBuffer: aSound samples).
  		compressed
  			channels: channels;
  			samplingRate: aSound originalSamplingRate;
  			firstSample: 1;
  			loopEnd: aSound samples size;
  			loopLength: 0.0;
  			perceivedPitch: 100.0;
  			gain: aSound loudness.
  		^ compressed].
  	(aSound isKindOf: LoopedSampledSound) ifTrue: [
  		aSound isStereo
  			ifTrue: [
  				channels := Array new: 2.
  				channels at: 1 put: (self encodeSoundBuffer: aSound leftSamples).
  				channels at: 2 put: (self encodeSoundBuffer: aSound rightSamples)]
  			ifFalse: [
  				channels := Array new: 1.
  				channels at: 1 put: (self encodeSoundBuffer: aSound leftSamples)].
  		compressed
  			channels: channels;
  			samplingRate: aSound originalSamplingRate;
  			firstSample: aSound firstSample;
  			loopEnd: aSound loopEnd;
  			loopLength: aSound loopLength;
  			perceivedPitch: aSound perceivedPitch;
  			gain: aSound gain.
  		^ compressed].
  	self error: 'you can only compress sampled sounds'.
  !

Item was changed:
  ----- Method: SoundCodec>>compressSound:atRate: (in category 'compress/decompress') -----
  compressSound: aSound atRate: desiredSampleRate
  	"Compress the entirety of the given sound with this codec. Answer a CompressedSoundData."
  
  	| compressed channels samples newRate ratio buffer |
  
  	compressed := CompressedSoundData new
  		codecName: self class name;
  		soundClassName: aSound class name.
  	(aSound isKindOf: SampledSound) ifTrue: [
  		(desiredSampleRate isNil or: 
  				[(ratio := aSound originalSamplingRate // desiredSampleRate) <= 1]) ifTrue: [
  			samples := aSound samples.
  			newRate := aSound originalSamplingRate.
  		] ifFalse: [
  			buffer := aSound samples.
  			samples := SoundBuffer 
  				averageEvery: ratio 
  				from: buffer 
  				upTo: buffer monoSampleCount.
  			newRate := aSound originalSamplingRate / ratio.
  		].
  
  		channels := Array new: 1.
  		channels at: 1 put: (self encodeSoundBuffer: samples).
  		compressed
  			channels: channels;
  			samplingRate: newRate;
  			firstSample: 1;
  			loopEnd: samples size;
  			loopLength: 0.0;
  			perceivedPitch: 100.0;
  			gain: aSound loudness.
  		^ compressed].
  	(aSound isKindOf: LoopedSampledSound) ifTrue: [
  		aSound isStereo
  			ifTrue: [
  				channels := Array new: 2.
  				channels at: 1 put: (self encodeSoundBuffer: aSound leftSamples).
  				channels at: 2 put: (self encodeSoundBuffer: aSound rightSamples)]
  			ifFalse: [
  				channels := Array new: 1.
  				channels at: 1 put: (self encodeSoundBuffer: aSound leftSamples)].
  		compressed
  			channels: channels;
  			samplingRate: aSound originalSamplingRate;
  			firstSample: aSound firstSample;
  			loopEnd: aSound loopEnd;
  			loopLength: aSound loopLength;
  			perceivedPitch: aSound perceivedPitch;
  			gain: aSound gain.
  		^ compressed].
  	self error: 'you can only compress sampled sounds'.
  !

Item was changed:
  ----- Method: SoundCodec>>decodeCompressedData: (in category 'private') -----
  decodeCompressedData: aByteArray
  	"Decode the entirety of the given encoded data buffer with this codec. Answer a monophonic SoundBuffer containing the uncompressed samples."
  
  	| frameCount result increments |
  	frameCount := self frameCount: aByteArray.
  	result := SoundBuffer newMonoSampleCount: frameCount * self samplesPerFrame.
  	self reset.
  	increments := self decodeFrames: frameCount from: aByteArray at: 1 into: result at: 1.
  	((increments first = aByteArray size) and: [increments last = result size]) ifFalse: [
  		self error: 'implementation problem; increment sizes should match buffer sizes'].
  	^ result
  !

Item was changed:
  ----- Method: SoundCodec>>decompressSound: (in category 'compress/decompress') -----
  decompressSound: aCompressedSound
  	"Decompress the entirety of the given compressed sound with this codec and answer the resulting sound."
  
  	| channels sound |
  	channels := aCompressedSound channels
  		collect: [:compressed | self decodeCompressedData: compressed].
  	'SampledSound' = aCompressedSound soundClassName ifTrue: [
  		sound := SampledSound
  			samples: channels first
  			samplingRate: (aCompressedSound samplingRate).
  		sound loudness: aCompressedSound gain.
  		^ sound].
  	'LoopedSampledSound' = aCompressedSound soundClassName ifTrue: [
  		aCompressedSound loopLength = 0
  			ifTrue: [
  				sound := LoopedSampledSound
  					unloopedSamples: channels first
  					pitch: aCompressedSound perceivedPitch
  					samplingRate: aCompressedSound samplingRate]
  			ifFalse: [
  				sound := LoopedSampledSound
  					samples: channels first
  					loopEnd: aCompressedSound loopEnd
  					loopLength: aCompressedSound loopLength
  					pitch: aCompressedSound perceivedPitch
  					samplingRate: aCompressedSound samplingRate].
  		channels size > 1 ifTrue: [sound rightSamples: channels last].
  		sound
  			firstSample: aCompressedSound firstSample;
  			gain: aCompressedSound gain.
  		sound
  			setPitch: 100.0
  			dur: (channels first size / aCompressedSound samplingRate)
  			loudness: 1.0.
  		^ sound].
  	self error: 'unknown sound class'.
  !

Item was changed:
  ----- Method: SoundCodec>>encodeSoundBuffer: (in category 'private') -----
  encodeSoundBuffer: aSoundBuffer
  	"Encode the entirety of the given monophonic SoundBuffer with this codec. Answer a ByteArray containing the compressed sound data."
  
  	| codeFrameSize frameSize fullFrameCount lastFrameSamples result increments finalFrame i lastIncs |
  	frameSize := self samplesPerFrame.
  	fullFrameCount := aSoundBuffer monoSampleCount // frameSize.
  	lastFrameSamples := aSoundBuffer monoSampleCount - (fullFrameCount * frameSize).
  	codeFrameSize := self bytesPerEncodedFrame.
  	codeFrameSize = 0 ifTrue:
  		["Allow room for 1 byte per sample for variable-length compression"
  		codeFrameSize := frameSize].
  	lastFrameSamples > 0
  		ifTrue: [result := ByteArray new: (fullFrameCount + 1) * codeFrameSize]
  		ifFalse: [result := ByteArray new: fullFrameCount * codeFrameSize].
  	self reset.
  	increments := self encodeFrames: fullFrameCount from: aSoundBuffer at: 1 into: result at: 1.
  	lastFrameSamples > 0 ifTrue: [
  		finalFrame := SoundBuffer newMonoSampleCount: frameSize.
  		i := fullFrameCount * frameSize.
  		1 to: lastFrameSamples do: [:j |
  			finalFrame at: j put: (aSoundBuffer at: (i := i + 1))].
  		lastIncs := self encodeFrames: 1 from: finalFrame at: 1 into: result at: 1 + increments second.
  		increments := Array with: increments first + lastIncs first
  							with: increments second + lastIncs second].
  	increments second < result size
  		ifTrue: [^ result copyFrom: 1 to: increments second]
  		ifFalse: [^ result]
  !

Item was changed:
  ----- Method: SoundCodec>>frameCount: (in category 'private') -----
  frameCount: aByteArray
  	"Compute the frame count for this byteArray.  This default computation will have to be overridden by codecs with variable frame sizes."
  
  	| codeFrameSize |
  	codeFrameSize := self bytesPerEncodedFrame.
  	(aByteArray size \\ codeFrameSize) = 0 ifFalse:
  		[self error: 'encoded buffer is not an even multiple of the encoded frame size'].
  	^ aByteArray size // codeFrameSize!

Item was changed:
  ----- Method: SoundInputStream>>allocateBuffer (in category 'private') -----
  allocateBuffer
  	"Allocate a new buffer and reset nextIndex. This message is sent by the sound input process."
  
  	currentBuffer := SoundBuffer newMonoSampleCount: bufferSize.
  	nextIndex := 1.
  !

Item was changed:
  ----- Method: SoundInputStream>>bufferSize: (in category 'accessing') -----
  bufferSize: aNumber
  	"Set the sound buffer size. Buffers of this size will be queued for the client to process."
  
  	bufferSize := aNumber truncated.
  !

Item was changed:
  ----- Method: SoundInputStream>>initialize (in category 'initialization') -----
  initialize
  
  	super initialize.
  	bufferSize := 1024.
  	mutex := nil.
  !

Item was changed:
  ----- Method: SoundInputStream>>startRecording (in category 'recording controls') -----
  startRecording
  	"Start the sound input process."
  
  	recordProcess ifNotNil: [self stopRecording].
  	recordedBuffers := OrderedCollection new: 100.
  	mutex := Semaphore forMutualExclusion.
  	super startRecording.
  	paused := false.
  !

Item was changed:
  ----- Method: SoundInputStream>>stopRecording (in category 'recording controls') -----
  stopRecording
  	"Turn off the sound input process and close the driver."
  
  	super stopRecording.
  	recordedBuffers := nil.
  	mutex := nil.
  !

Item was changed:
  ----- Method: SoundPlayer class>>boinkPitch:dur:loudness:waveTable:pan: (in category 'primitive test') -----
  boinkPitch: p dur: d loudness: l waveTable: waveTable pan: pan
  	"Play a decaying note on the given stream using the given wave table. Used for testing only."
  
  	| decay tableSize amplitude increment cycles i |
  	decay := 0.96.
  	tableSize := waveTable size.
  	amplitude := l asInteger min: 1000.
  	increment := ((p asFloat * tableSize asFloat) / SamplingRate asFloat) asInteger.
  	increment := (increment max: 1) min: (tableSize // 2).
  	cycles := (d * SamplingRate asFloat) asInteger.
  
  	i := 1.
  	1 to: cycles do: [:cycle |
  		(cycle \\ 100) = 0
  			ifTrue: [amplitude := (decay * amplitude asFloat) asInteger].
  		i := (((i - 1) + increment) \\ tableSize) + 1.
  		self playTestSample: (amplitude * (waveTable at: i)) // 1000 pan: pan].
  !

Item was changed:
  ----- Method: SoundPlayer class>>boinkScale (in category 'primitive test') -----
  boinkScale
  	"Tests the sound output primitives by playing a scale."
  	"SoundPlayer boinkScale"
  
  	| sineTable pan |
  	self shutDown.
  	SamplingRate := 11025.
  	Stereo := true.
  	sineTable := self sineTable: 1000.
  	Buffer := SoundBuffer newStereoSampleCount: 1000.
  	BufferIndex := 1.
  	self primSoundStartBufferSize: Buffer stereoSampleCount
  		rate: SamplingRate
  		stereo: Stereo.
  	pan := 0.
  	#(261.626 293.665 329.628 349.229 391.996 440.001 493.884 523.252) do: [:p |
  		self boinkPitch: p dur: 0.3 loudness: 300 waveTable: sineTable pan: pan.
  		pan := pan + 125].
  
  	self boinkPitch: 261.626 dur: 1.0 loudness: 300 waveTable: sineTable pan: 500.
  	self primSoundStop.
  	self shutDown.
  	SoundPlayer initialize.  "reset sampling rate, buffer size, and stereo flag"
  !

Item was changed:
  ----- Method: SoundPlayer class>>initialize (in category 'initialization') -----
  initialize
  	"SoundPlayer initialize; shutDown; startUp"
  	"Details: BufferMSecs represents a tradeoff between latency and quality. If BufferMSecs is too low, the sound will not play smoothly, especially during long-running primitives such as large BitBlts. If BufferMSecs is too high, there will be a long time lag between when a sound buffer is submitted to be played and when that sound is actually heard. BufferMSecs is typically in the range 50-200."
  
  	SamplingRate := 22050.
  	BufferMSecs := 120.
  	Stereo := true.
  	UseReverb ifNil: [UseReverb := true].
  !

Item was changed:
  ----- Method: SoundPlayer class>>isAllSilence:size: (in category 'private') -----
  isAllSilence: buffer size: count
  	"return true if the buffer is all silence after reverb has ended"
  	| value |
  	value := buffer at: 1.
  	2 to: count do:[:i| (buffer at: i) = value ifFalse:[^false]].
  	^true!

Item was changed:
  ----- Method: SoundPlayer class>>playTestSample:pan: (in category 'primitive test') -----
  playTestSample: s pan: pan
  	"Append the given sample in the range [-32767..32767] to the output buffer, playing the output buffer when it is full. Used for testing only."
  
  	| sample leftSample |
  	BufferIndex >= Buffer size
  		ifTrue: [
  			"current buffer is full; play it"
  			[self primSoundAvailableBytes > 0]
  				whileFalse. "wait for space to be available"
  			self primSoundPlaySamples: Buffer stereoSampleCount from: Buffer startingAt: 1.
  			Buffer primFill: 0.
  			BufferIndex := 1].
  
  	sample := s.
  	sample >  32767 ifTrue: [ sample :=  32767 ]. 
  	sample < -32767 ifTrue: [ sample := -32767 ].
  
  	Stereo
  		ifTrue: [
  			leftSample := (sample * pan) // 1000.
  			Buffer at: BufferIndex		put: sample - leftSample.
  			Buffer at: BufferIndex + 1	put: leftSample]
  		ifFalse: [
  			Buffer at: BufferIndex + 1 put: sample].
  	BufferIndex := BufferIndex + 2.
  !

Item was changed:
  ----- Method: SoundPlayer class>>primSoundStartBufferSize:rate:stereo: (in category 'private') -----
  primSoundStartBufferSize: bufferSize rate: samplesPerSecond stereo: stereoFlag
  	"Start double-buffered sound output with the given buffer size and sampling rate. This version has been superceded by primitive 171 (primSoundStartBufferSize:rate:stereo:semaIndex:)."
  	"ar 12/5/1998 Turn off the sound if not supported"
  	<primitive: 'primitiveSoundStart' module: 'SoundPlugin'>
  	SoundSupported := false.!

Item was changed:
  ----- Method: SoundPlayer class>>primSoundStartBufferSize:rate:stereo:semaIndex: (in category 'private') -----
  primSoundStartBufferSize: bufferSize rate: samplesPerSecond stereo: stereoFlag semaIndex: anInteger
  	"Start double-buffered sound output with the given buffer size and sampling rate. If the given semaphore index is > 0, it is taken to be the index of a Semaphore in the external objects array to be signalled when the sound driver is ready to accept another buffer of samples."
  	"Details: If this primitive fails, this method tries to use the older version instead."
  
  	<primitive: 'primitiveSoundStartWithSemaphore' module: 'SoundPlugin'>
  	UseReadySemaphore := false.
  	self primSoundStartBufferSize: bufferSize rate: samplesPerSecond stereo: stereoFlag.
  !

Item was changed:
  ----- Method: SoundPlayer class>>shutDown (in category 'snapshotting') -----
  shutDown
  	"Stop player process, for example before snapshotting."
  
  	self stopPlayerProcess.
  	ReverbState := nil.
  !

Item was changed:
  ----- Method: SoundPlayer class>>sineTable: (in category 'primitive test') -----
  sineTable: size
  	"Compute a sine table of the given size. Used for testing only."
  
  	| radiansPerStep table |
  	table := Array new: size.
  	radiansPerStep := (2.0 * Float pi) / table size asFloat.
  	1 to: table size do: [:i |
  		table at: i put:
  			(32767.0 * (radiansPerStep * i) sin) asInteger].
  
  	^ table
  !

Item was changed:
  ----- Method: SoundPlayer class>>startReverb (in category 'player process') -----
  startReverb
  	"Start a delay-line style reverb with the given tap delays and gains. Tap delays are given in samples and should be prime integers; the following comment gives an expression that generates primes."
  	"Integer primesUpTo: 22050"
  
  	UseReverb := true.
  	ReverbState := ReverbSound new
  		tapDelays: #(1601 7919) gains: #(0.12 0.07).
  !

Item was changed:
  ----- Method: SoundPlayer class>>stopPlayerProcess (in category 'player process') -----
  stopPlayerProcess
  	"Stop the sound player process."
  	"SoundPlayer stopPlayerProcess"
  
  	(PlayerProcess == nil or:[PlayerProcess == Processor activeProcess]) 
  		ifFalse:[PlayerProcess terminate].
  	PlayerProcess := nil.
  	self primSoundStop.
  	ActiveSounds := OrderedCollection new.
  	Buffer := nil.
  	PlayerSemaphore := Semaphore forMutualExclusion.
  	ReadyForBuffer ifNotNil:
  		[Smalltalk unregisterExternalObject: ReadyForBuffer].
  	ReadyForBuffer := nil.
  !

Item was changed:
  ----- Method: SoundPlayer class>>stopPlayingAll (in category 'playing') -----
  stopPlayingAll
  	"Stop playing all sounds."
  
  	PlayerSemaphore critical: [
  		ActiveSounds := ActiveSounds species new].
  !

Item was changed:
  ----- Method: SoundPlayer class>>stopReverb (in category 'player process') -----
  stopReverb
  
  	UseReverb := false.
  	ReverbState := nil.
  !

Item was changed:
  ----- Method: SoundPlayer class>>useLastBuffer: (in category 'initialization') -----
  useLastBuffer: aBool
  	Buffer ifNil:[^self].
  	aBool 
  		ifTrue:[LastBuffer := SoundBuffer basicNew: Buffer basicSize]
  		ifFalse:[LastBuffer := nil]	!

Item was changed:
  ----- Method: SoundPlayer class>>useShortBuffer (in category 'initialization') -----
  useShortBuffer
  	"Experimental support for real-time MIDI input. This only works on platforms whose hardware allows very short buffer sizes. It has been tested on a Macintosh Powerbook G3."
  	"SoundPlayer useShortBuffer"
  
  	self shutDown.
  	BufferMSecs := 15.
  	SoundPlayer
  		startPlayerProcessBufferSize: (BufferMSecs * SamplingRate) // 1000
  		rate: SamplingRate
  		stereo: Stereo.
  !

Item was changed:
  ----- Method: SoundRecorder>>allocateBuffer (in category 'private') -----
  allocateBuffer
  	"Allocate a new buffer and reset nextIndex."
  
  	| bufferTime |
  	bufferTime := stereo  "Buffer time = 1/2 second"
  		ifTrue: [self samplingRate asInteger]
  		ifFalse: [self samplingRate asInteger // 2].
  	currentBuffer := SoundBuffer newMonoSampleCount:
  		"Multiple of samplesPerFrame that is approx. bufferTime long"
  		(bufferTime truncateTo: self samplesPerFrame).
  	nextIndex := 1.
  !

Item was changed:
  ----- Method: SoundRecorder>>clearRecordedSound (in category 'recording controls') -----
  clearRecordedSound
  	"Clear the sound recorded thus far. Go into pause mode if currently recording."
  
  	paused := true.
  	recordedSound := SequentialSound new.
  	self allocateBuffer.
  !

Item was changed:
  ----- Method: SoundRecorder>>codec: (in category 'accessing') -----
  codec: aSoundCodec
  
  	codec := aSoundCodec!

Item was changed:
  ----- Method: SoundRecorder>>condensedSamples (in category 'results') -----
  condensedSamples
  	"Return a single SoundBuffer that is the contatenation of all my recorded buffers."
  
  	| sz newBuf i |
  	recordedBuffers := recordedSound sounds collect: [:snd | snd samples].
  	recordedBuffers isEmpty ifTrue: [^ SoundBuffer new: 0].
  	recordedBuffers size = 1 ifTrue: [^ recordedBuffers first copy].
  	sz := recordedBuffers inject: 0 into: [:tot :buff | tot + buff size].
  	newBuf := SoundBuffer newMonoSampleCount: sz.
  	i := 1.
  	recordedBuffers do: [:b |
  		1 to: b size do: [:j |
  			newBuf at: i put: (b at: j).
  			i := i + 1]].
  	recordedBuffers := nil.
  	^ newBuf
  !

Item was changed:
  ----- Method: SoundRecorder>>condensedStereoSound (in category 'results') -----
  condensedStereoSound
  	"Decompose my buffers into left and right channels and return a mixed sound consisting of the those two channels. This may be take a while, since the data must be copied into new buffers."
  
  	| sz leftBuf rightBuf leftI rightI left |
  	sz := recordedBuffers inject: 0 into: [:tot :buff | tot + buff size].
  	leftBuf := SoundBuffer newMonoSampleCount: (sz + 1) // 2.
  	rightBuf := SoundBuffer newMonoSampleCount: (sz + 1) // 2.
  	leftI := rightI := 1.
  	left := true.
  	recordedBuffers do: [:b |
  		1 to: b size do: [:j |
  			left
  				ifTrue: [leftBuf at: leftI put: (b at: j). leftI := leftI + 1. left := false]
  				ifFalse: [rightBuf at: rightI put: (b at: j). rightI := rightI + 1. left := true]]].
  	^ MixedSound new
  		add: (SampledSound new setSamples: leftBuf samplingRate: samplingRate) pan: 0.0;
  		add: (SampledSound new setSamples: rightBuf samplingRate: samplingRate) pan: 1.0
  !

Item was changed:
  ----- Method: SoundRecorder>>copyFrom:to:normalize:dcOffset: (in category 'trimming') -----
  copyFrom: startPlace to: endPlace normalize: nFactor dcOffset: dcOffset
  	"Return a new SoundBuffer containing the samples in the given range."
  
  	| startBufIndex startSampleIndex endBufIndex endSampleIndex
  	 count resultBuf j buf firstInBuf n |
  	startBufIndex := startPlace at: 1.
  	startSampleIndex := startPlace at: 2.
  	endBufIndex := endPlace at: 1.
  	endSampleIndex := endPlace at: 2.
  
  	startBufIndex = endBufIndex
  		ifTrue: [count := endSampleIndex + 1 - startSampleIndex]
  		ifFalse: [
  			count := ((recordedBuffers at: startBufIndex) size + 1 - startSampleIndex).  "first buffer"
  			count := count + endSampleIndex.  "last buffer"
  			startBufIndex + 1 to: endBufIndex - 1 do:
  				[:i | count := count + (recordedBuffers at: i) size]].  "middle buffers"
  	resultBuf := SoundBuffer newMonoSampleCount: count.
  
  	j := 1.  "next destination index in resultBuf"
  	startBufIndex to: endBufIndex do: [:i |
  		buf := recordedBuffers at: i.
  		firstInBuf := 1.
  	 	n := buf size.
  		i = startBufIndex ifTrue: [
  			n := (recordedBuffers at: startBufIndex) size + 1 - startSampleIndex.
  			firstInBuf := startSampleIndex].
  		i = endBufIndex ifTrue: [
  			i = startBufIndex
  				ifTrue: [n := endSampleIndex + 1 - startSampleIndex]
  				ifFalse: [n := endSampleIndex]].
  		self copyTo: resultBuf from: j to: (j + n - 1)
  			from: buf startingAt: firstInBuf
  			normalize: nFactor dcOffset: dcOffset.
  		j := j + n].
  	^ resultBuf
  !

Item was changed:
  ----- Method: SoundRecorder>>copyTo:from:to:from:startingAt:normalize:dcOffset: (in category 'trimming') -----
  copyTo: resultBuf from: startIndex to: endIndex from: buf startingAt: firstInBuf normalize: nFactor dcOffset: dcOffset
  	"Copy samples from buf to resultBuf removing the DC offset and normalizing their volume in the process."
  
  	| indexOffset |
  	indexOffset := firstInBuf - startIndex.
  	startIndex to: endIndex do: [:i |
  		resultBuf at: i put: (((buf at: (i + indexOffset)) - dcOffset) * nFactor) // 1000].
  !

Item was changed:
  ----- Method: SoundRecorder>>desiredSampleRate: (in category 'accessing') -----
  desiredSampleRate: newRate
  
  	"use of this method indicates a strong desire for the specified rate, even if
  	the OS/hardware are not cooperative"
  
  	desiredSampleRate := samplingRate := newRate  "Best are 44100 22050 11025"
  !

Item was changed:
  ----- Method: SoundRecorder>>emitBuffer: (in category 'private') -----
  emitBuffer: buffer
  
  	| sound ratio resultBuf |
  
  	"since some sound recording devices cannot (or will not) record below a certain sample rate,
  	trim the samples down if the user really wanted fewer samples"
  
  	(desiredSampleRate isNil or: [(ratio := samplingRate // desiredSampleRate) <= 1]) ifTrue: [
  		sound := SampledSound new setSamples: buffer samplingRate: samplingRate.
  	] ifFalse: [
  		resultBuf := SoundBuffer 
  			averageEvery: ratio 
  			from: buffer 
  			upTo: buffer monoSampleCount.
  		sound := SampledSound new setSamples: resultBuf samplingRate: samplingRate / ratio.
  	].
  
  	recordedSound add: (codec ifNil: [sound] ifNotNil: [codec compressSound: sound])!

Item was changed:
  ----- Method: SoundRecorder>>emitPartialBuffer (in category 'private') -----
  emitPartialBuffer
  	| s |
  	s := self samplesPerFrame.
  	self emitBuffer: (currentBuffer copyFrom: 1 to: ((nextIndex-1) +( s-1) truncateTo: s))!

Item was changed:
  ----- Method: SoundRecorder>>firstSampleOverThreshold:dcOffset:startingAt: (in category 'trimming') -----
  firstSampleOverThreshold: threshold dcOffset: dcOffset startingAt: startPlace
  	"Beginning at startPlace, this routine will return the first place at which a sample exceeds the given threshold."
  
  	| buf s iStart jStart nThreshold |
  	nThreshold := threshold negated.
  	iStart := startPlace first.
  	jStart := startPlace second.
  	iStart to: recordedBuffers size do:
  		[:i | buf := recordedBuffers at: i.
  		jStart to: buf size do:
  			[:j | s := (buf at: j) - dcOffset.
  			(s < nThreshold or: [s > threshold]) ifTrue:
  				["found a sample over threshold"
  				^ Array with: i with: j]].
  		jStart := 1].
  	^ self endPlace!

Item was changed:
  ----- Method: SoundRecorder>>initializeRecordingState (in category 'initialization') -----
  initializeRecordingState
  
  	recordProcess := nil.
  	bufferAvailableSema := nil.
  	paused := true.
  	meteringBuffer := nil.
  	meterLevel := 0.
  	soundPlaying := nil.
  	currentBuffer := nil.
  	nextIndex := 1.
  !

Item was changed:
  ----- Method: SoundRecorder>>meterFrom:count:in: (in category 'private') -----
  meterFrom: start count: count in: buffer
  	"Update the meter level with the maximum signal level in the given range of the given buffer."
  
  	| last max sample |
  	count = 0 ifTrue: [^ self].  "no new samples"
  	last := start + count - 1.
  	max := 0.
  	start to: last do: [:i |
  		sample := buffer at: i.
  		sample < 0 ifTrue: [sample := sample negated].
  		sample > max ifTrue: [max := sample]].
  	meterLevel := max.
  !

Item was changed:
  ----- Method: SoundRecorder>>normalizeFactorFor:min:max:dcOffset: (in category 'trimming') -----
  normalizeFactorFor: percentOfMaxVolume min: min max: max dcOffset: dcOffset
  	"Return a normalization factor for the range of sample values and DC offset. A normalization factor is a fixed-point number that will be divided by 1000 after multiplication with each sample value."
  
  	| peak factor |
  	peak := (max - dcOffset) max: (min - dcOffset) negated.
  	peak = 0 ifTrue: [^ 1000].
  	factor := (32767.0 * percentOfMaxVolume) / (100.0 * peak).
  	^ (factor * 1000.0) asInteger
  !

Item was changed:
  ----- Method: SoundRecorder>>place:plus: (in category 'trimming') -----
  place: startPlace plus: nSamples
  	"Return the place that is nSamples (may be negative) beyond thisPlace."
  
  	| i j remaining buf |
  	i := startPlace first.
  	j := startPlace second.
  	nSamples >= 0
  	ifTrue: [remaining := nSamples.
  			[buf := recordedBuffers at: i.
  			(j + remaining) <= buf size ifTrue: [^ Array with: i with: j + remaining].
  			i < recordedBuffers size]
  				whileTrue: [remaining := remaining - (buf size - j + 1).
  							i := i+1.  j := 1].
  			^ self endPlace]
  	ifFalse: [remaining := nSamples negated.
  			[buf := recordedBuffers at: i.
  			(j - remaining) >= 1 ifTrue: [^ Array with: i with: j - remaining].
  			i > 1]
  				whileTrue: [remaining := remaining - j.
  							i := i-1.  j := (recordedBuffers at: i) size].
  			^ #(1 1)]!

Item was changed:
  ----- Method: SoundRecorder>>playback (in category 'recording controls') -----
  playback
  	"Playback the sound that has been recorded."
  
  	self pause.
  	soundPlaying := self recordedSound.
  	soundPlaying play.
  !

Item was changed:
  ----- Method: SoundRecorder>>recordLevel: (in category 'accessing') -----
  recordLevel: level
  	"Set the desired recording level to the given value in the range 0.0 to 1.0, where 0.0 is the lowest recording level and 1.0 is the maximum. Do nothing if the sound input hardware does not support changing the recording level."
  	"Details: On the Macintosh, the lowest possible record level attenuates the input signal, but does not silence it entirely." 
  
  	recordLevel := (level asFloat min: 1.0) max: 0.0.
  	recordProcess ifNotNil: [
  		self primSetRecordLevel: (1000.0 * recordLevel) asInteger].
  !

Item was changed:
  ----- Method: SoundRecorder>>samplingRate: (in category 'accessing') -----
  samplingRate: newRate
  
  	samplingRate := newRate  "Best are 44100 22050 11025"
  !

Item was changed:
  ----- Method: SoundRecorder>>scanForEndThreshold:dcOffset:minLull:startingAt: (in category 'trimming') -----
  scanForEndThreshold: threshold dcOffset: dcOffset minLull: lull startingAt: startPlace
  	"Beginning at startPlace, this routine will find the last sound that exceeds threshold, such that if you look lull samples later you will not find another sound over threshold within the following block of lull samples.
  	Return the place that is lull samples beyond to that last sound.
  	If no end of sound is found, return endPlace."
  
  	| buf s iStart jStart nThreshold n |
  	nThreshold := threshold negated.
  	iStart := startPlace first.
  	jStart := startPlace second.
  	n := 0.
  	iStart to: recordedBuffers size do:
  		[:i | buf := recordedBuffers at: i.
  		jStart to: buf size do:
  			[:j | s := (buf at: j) - dcOffset.
  			(s < nThreshold or: [s > threshold])
  				ifTrue: ["found a sample over threshold"
  						n := 0]
  				ifFalse: ["still not over threshold"
  						n := n + 1.
  						n >= lull ifTrue: [^ Array with: i with: j]]].
  		jStart := 1].
  	^ self endPlace!

Item was changed:
  ----- Method: SoundRecorder>>scanForStartThreshold:dcOffset:minDur:startingAt: (in category 'trimming') -----
  scanForStartThreshold: threshold dcOffset: dcOffset minDur: duration startingAt: startPlace
  	"Beginning at startPlace, this routine will find the first sound that exceeds threshold, such that if you look duration samples later you will find another sound over threshold within the following block of duration samples.
  	Return the place that is duration samples prior to that first sound.
  	If no sound is found, return endPlace."
  
  	| soundPlace lookPlace nextSoundPlace thirdPlace |
  	soundPlace := self firstSampleOverThreshold: threshold dcOffset: dcOffset
  					startingAt: startPlace.
  	[soundPlace = self endPlace ifTrue: [^ soundPlace].
  	"Found a sound -- look duration later"
  	lookPlace := self place: soundPlace plus: duration.
  	nextSoundPlace := self firstSampleOverThreshold: threshold dcOffset: dcOffset
  					startingAt: lookPlace.
  	thirdPlace := self place: lookPlace plus: duration.
  	nextSoundPlace first < thirdPlace first
  		or: [nextSoundPlace first = thirdPlace first
  			and: [nextSoundPlace second < thirdPlace second]]]
  		whileFalse: [soundPlace := nextSoundPlace].
  
  	"Yes, there is sound in the next interval as well"
  	^ self place: soundPlace plus: 0-duration
  !

Item was changed:
  ----- Method: SoundRecorder>>stopRecording (in category 'recording controls') -----
  stopRecording
  	"Stop the recording process and turn of the sound input driver."
  
  	recordProcess ifNotNil: [recordProcess terminate].
  	recordProcess := nil.
  	self primStopRecording.
  	RecorderActive := false.
  	Smalltalk unregisterExternalObject: bufferAvailableSema.
  	((currentBuffer ~~ nil) and: [nextIndex > 1])
  		ifTrue: [self emitPartialBuffer].
  	self initializeRecordingState.
  !

Item was changed:
  ----- Method: SoundRecorder>>suppressSilence (in category 'trimming') -----
  suppressSilence
  
  	recordedSound := self soundSegments!

Item was changed:
  ----- Method: StreamingMonoSound class>>onFileNamed: (in category 'instance creation') -----
  onFileNamed: fileName
  	"Answer an instance of me for playing the file with the given name."
  
  	| f |
  	f := FileDirectory default readOnlyFileNamed: fileName.
  	f ifNil: [^ self error: 'could not open ', fileName].
  	^ self new initStream: f headerStart: 0
  !

Item was changed:
  ----- Method: StreamingMonoSound class>>onFileNamed:headerStart: (in category 'instance creation') -----
  onFileNamed: fileName headerStart: anInteger
  	"Answer an instance of me for playing audio data starting at the given position in the file with the given name."
  
  	| f |
  	f := FileDirectory default readOnlyFileNamed: fileName.
  	f ifNil: [^ self error: 'could not open ', fileName].
  	^ self new initStream: f headerStart: anInteger
  !

Item was changed:
  ----- Method: StreamingMonoSound>>closeFile (in category 'other') -----
  closeFile
  	"Close my stream, if it responds to close."
  
  	stream ifNotNil: [
  		(stream respondsTo: #close) ifTrue: [stream close]].
  	mixer := nil.
  	codec := nil.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>createMixer (in category 'private') -----
  createMixer
  	"Create a mixed sound consisting of sampled sounds with one sound buffer's worth of samples."
  
  	| snd |
  	mixer := MixedSound new.
  	snd := SampledSound
  		samples: (SoundBuffer newMonoSampleCount: 2)  "buffer size will be adjusted dynamically"
  		samplingRate: streamSamplingRate.
  	mixer add: snd pan: 0.5 volume: volume.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>currentSampleIndex (in category 'private') -----
  currentSampleIndex
  	"Answer the index of the current sample."
  
  	| bytePosition frameIndex |
  	bytePosition := stream position - audioDataStart.
  	codec
  		ifNil: [^ bytePosition // 2]
  		ifNotNil: [
  			frameIndex := bytePosition // codec bytesPerEncodedFrame.
  			^ (frameIndex * codec samplesPerFrame) - leftoverSamples monoSampleCount].
  !

Item was changed:
  ----- Method: StreamingMonoSound>>extractFrom:to: (in category 'other') -----
  extractFrom: startSecs to: endSecs
  	"Extract a portion of this sound between the given start and end times. The current implementation only works if the sound is uncompressed."
  
  	| emptySound first last sampleCount byteStream sndBuf |
  	codec ifNotNil: [^ self error: 'only works on uncompressed sounds'].
  	emptySound := SampledSound samples: SoundBuffer new samplingRate: streamSamplingRate.
  	first := (startSecs * streamSamplingRate) truncated max: 0.
  	last := ((endSecs * streamSamplingRate) truncated min: totalSamples) - 1.
  	first >= last ifTrue: [^ emptySound].
  	codec ifNotNil: [self error: 'extracting from compressed sounds is not supported'].
  	sampleCount := last + 1 - first.
  	stream position: audioDataStart + (2 * first).
  	byteStream := ReadStream on: (stream next: 2 * sampleCount).
  	sndBuf := SoundBuffer newMonoSampleCount: sampleCount.
  	1 to: sampleCount do: [:i | sndBuf at: i put: byteStream int16].
  	^ SampledSound samples: sndBuf samplingRate: streamSamplingRate
  !

Item was changed:
  ----- Method: StreamingMonoSound>>initStream:headerStart: (in category 'initialization') -----
  initStream: aStream headerStart: anInteger
  	"Initialize for streaming from the given stream. The audio file header starts at the given stream position."
  
  	stream := aStream.
  	volume := 1.0.
  	repeat := false.
  	headerStart := anInteger.
  	self reset.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>loadBuffer:compressedSampleCount: (in category 'private') -----
  loadBuffer: aSoundBuffer compressedSampleCount: sampleCount
  	"Load the given sound buffer from the compressed sample stream."
  	"Details: Most codecs decode in multi-sample units called 'frames'. Since the requested sampleCount is typically not an even multiple of the frame size, we need to deal with partial frames. The unused samples from a partial frame are retained until the next call to this method."
  
  	| n samplesNeeded frameCount encodedBytes r decodedCount buf j |
  	"first, use any leftover samples"
  	n := self loadFromLeftovers: aSoundBuffer sampleCount: sampleCount.
  	samplesNeeded := sampleCount - n.
  	samplesNeeded <= 0 ifTrue: [^ self].
  
  	"decode an integral number of full compression frames"
  	frameCount := samplesNeeded // codec samplesPerFrame.
  	encodedBytes := stream next: (frameCount * codec bytesPerEncodedFrame).
  	r := codec decodeFrames: frameCount from: encodedBytes at: 1 into: aSoundBuffer at: n + 1.
  	decodedCount := r last.
  	decodedCount >= samplesNeeded ifTrue: [^ self].
  
  	"decode one last compression frame to finish filling the buffer"
  	buf := SoundBuffer newMonoSampleCount: codec samplesPerFrame.
  	encodedBytes := stream next: codec bytesPerEncodedFrame.
  	codec decodeFrames: 1 from: encodedBytes at: 1 into: buf at: 1.
  	j := 0.
  	(n + decodedCount + 1) to: sampleCount do: [:i |
  		aSoundBuffer at: i put: (buf at: (j := j + 1))].
  
  	"save the leftover samples"
  	leftoverSamples := buf copyFrom: (j + 1) to: buf monoSampleCount.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>loadBuffersForSampleCount: (in category 'private') -----
  loadBuffersForSampleCount: count
  	"Load the sound buffers from the stream."
  
  	| snd buf sampleCount |
  	snd := mixer sounds first.
  	buf := snd samples.
  	buf monoSampleCount = count ifFalse: [
  		buf := SoundBuffer newMonoSampleCount: count.
  		snd setSamples: buf samplingRate: streamSamplingRate].
  	sampleCount := count min: (totalSamples - self currentSampleIndex).
  	sampleCount < count ifTrue: [buf primFill: 0].
  
  	codec
  		ifNil: [self loadBuffer: buf uncompressedSampleCount: sampleCount]
  		ifNotNil: [self loadBuffer: buf compressedSampleCount: sampleCount].
  
  	mixer reset.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>loadFromLeftovers:sampleCount: (in category 'private') -----
  loadFromLeftovers: aSoundBuffer sampleCount: sampleCount
  	"Load the given sound buffer from the samples leftover from the last frame. Answer the number of samples loaded, which typically is less than sampleCount."
  
  	| leftoverCount n |
  	leftoverCount := leftoverSamples monoSampleCount.
  	leftoverCount = 0 ifTrue: [^ 0].
  
  	n := leftoverCount min: sampleCount.
  	1 to: n do: [:i | aSoundBuffer at: i put: (leftoverSamples at: i)].
  	n < sampleCount
  		ifTrue: [leftoverSamples := SoundBuffer new]
  		ifFalse: [leftoverSamples := leftoverSamples copyFrom: n + 1 to: leftoverSamples size].
  	^ n
  !

Item was changed:
  ----- Method: StreamingMonoSound>>millisecondsSinceStart (in category 'playing') -----
  millisecondsSinceStart
  	"Answer the number of milliseconds of this sound started playing."
  
  	| mSecs |
  	(stream isNil or: [stream closed]) ifTrue: [^ 0].
  	mSecs := self currentSampleIndex * 1000 // streamSamplingRate.
  	(self isPlaying and: [lastBufferMSecs > 0]) ifTrue: [
  		"adjust mSecs by the milliseconds since the last buffer"
  		mutex critical: [
  			mSecs := self currentSampleIndex * 1000 // streamSamplingRate.
  			mSecs := mSecs + ((Time millisecondClockValue - lastBufferMSecs) max: 0)]].
  	^ mSecs + 350 - (2 * SoundPlayer bufferMSecs)
  !

Item was changed:
  ----- Method: StreamingMonoSound>>playSampleCount:into:startingAt: (in category 'playing') -----
  playSampleCount: n into: aSoundBuffer startingAt: startIndex
  	"Mix the next n samples of this sound into the given buffer starting at the given index"
  
  	self repeat ifTrue: [  "loop if necessary"
  		(totalSamples - self currentSampleIndex) < n ifTrue: [self startOver]].
  
  	mutex critical: [
  		lastBufferMSecs := Time millisecondClockValue.
  		self loadBuffersForSampleCount: (n * streamSamplingRate) // SoundPlayer samplingRate.
  		mixer playSampleCount: n into: aSoundBuffer startingAt: startIndex].
  !

Item was changed:
  ----- Method: StreamingMonoSound>>positionCodecTo: (in category 'private') -----
  positionCodecTo: desiredSampleIndex
  	"Position to the closest frame before the given sample index when using a codec. If using the ADPCM codec, try to ensure that it is in sync with the compressed sample stream."
  
  	| desiredFrameIndex desiredPosition tmpStream tmpCodec byteBuf bufFrames sampleBuf frameCount n startOffset |
  	(codec isKindOf: ADPCMCodec) ifFalse: [
  		"stateless codecs (or relatively stateless ones, like GSM: just jump to frame boundary"
  		desiredFrameIndex := desiredSampleIndex // codec samplesPerFrame.
  		stream position: audioDataStart + (desiredFrameIndex * codec bytesPerEncodedFrame).
  		codec reset.
  		^ self].
  
  	"compute the desired stream position"
  	desiredFrameIndex := desiredSampleIndex // codec samplesPerFrame.
  	desiredPosition := audioDataStart + (desiredFrameIndex * codec bytesPerEncodedFrame).
  
  	"copy stream and codec"
  	(stream isKindOf: FileStream)
  		ifTrue: [tmpStream := (FileStream readOnlyFileNamed: stream name) binary]
  		ifFalse: [tmpStream := stream deepCopy].
  	tmpCodec := codec copy reset.
  
  	"reset the codec and start back about 30 seconds to try to get codec in sync"
  	startOffset := ((desiredFrameIndex - 80000) max: 0) * codec bytesPerEncodedFrame.
  	tmpStream position: audioDataStart + startOffset.
  
  	"decode forward to the desired position"
  	byteBuf := ByteArray new: (32000 roundTo: codec bytesPerEncodedFrame).
  	bufFrames := byteBuf size // codec bytesPerEncodedFrame.
  	sampleBuf := SoundBuffer newMonoSampleCount: bufFrames * codec samplesPerFrame.
  	frameCount := (desiredPosition - tmpStream position) // codec bytesPerEncodedFrame.
  	[frameCount > 0] whileTrue: [
  		n := bufFrames min: frameCount.
  		tmpStream next: n * codec bytesPerEncodedFrame into: byteBuf startingAt: 1.
  		tmpCodec decodeFrames: n from: byteBuf at: 1 into: sampleBuf at: 1.
  		frameCount := frameCount - n].
  
  	codec := tmpCodec.
  	stream position: tmpStream position.
  	(tmpStream isKindOf: FileStream) ifTrue: [tmpStream close].!

Item was changed:
  ----- Method: StreamingMonoSound>>readAIFFHeader (in category 'private') -----
  readAIFFHeader
  	"Read an AIFF file header from stream."
  
  	| aiffReader |
  	aiffReader := AIFFFileReader new.
  	aiffReader readFromStream: stream mergeIfStereo: false skipDataChunk: true.
  	aiffReader channelCount = 1 ifFalse: [self error: 'not monophonic'].
  	aiffReader bitsPerSample = 16 ifFalse: [self error: 'not 16-bit'].
  
  	audioDataStart := headerStart + aiffReader channelDataOffset.
  	streamSamplingRate := aiffReader samplingRate.
  	totalSamples := aiffReader frameCount min: (stream size - audioDataStart) // 2.
  	codec := nil.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>readHeader (in category 'private') -----
  readHeader
  	"Read the sound file header from my stream."
  
  	| id |
  	stream position: headerStart.
  	id := (stream next: 4) asString.
  	stream position: headerStart.
  	id = '.snd' ifTrue: [^ self readSunAudioHeader].
  	id = 'FORM' ifTrue: [^ self readAIFFHeader].
  	self error: 'unrecognized sound file format'.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>readSunAudioHeader (in category 'private') -----
  readSunAudioHeader
  	"Read a Sun audio file header from my stream."
  
  	| id headerBytes dataBytes format channelCount |
  	id := (stream next: 4) asString.
  	headerBytes := stream uint32.  "header bytes"
  	dataBytes := stream uint32.
  	format := stream uint32.
  	streamSamplingRate := stream uint32.
  	channelCount := stream uint32.
  
  	id = '.snd' ifFalse: [self error: 'not Sun audio format'].
  	dataBytes := dataBytes min: (stream size - headerBytes).
  	channelCount = 1 ifFalse: [self error: 'not monophonic'].
  	audioDataStart := headerStart + headerBytes.
  	codec := nil.
  	format = 1 ifTrue: [  "8-bit u-LAW"
  		codec := MuLawCodec new.
  		totalSamples := dataBytes.
  		^ self].
  	format = 3 ifTrue: [  "16-bit linear"
  		totalSamples := dataBytes // 2.
  		^ self].
  	format = 23 ifTrue: [  "ADPCM-4 bit (CCITT G.721)"
  		codec := ADPCMCodec new
  			initializeForBitsPerSample: 4 samplesPerFrame: 0.
  		totalSamples := (dataBytes // 4) * 8.
  		^ self].
  	format = 25 ifTrue: [  "ADPCM-3 bit (CCITT G.723)"
  		codec := ADPCMCodec new
  			initializeForBitsPerSample: 3 samplesPerFrame: 0.
  		totalSamples := (dataBytes // 3) * 8.
  		^ self].
  	format = 26 ifTrue: [  "ADPCM-5 bit (CCITT G.723)"
  		codec := ADPCMCodec new
  			initializeForBitsPerSample: 5 samplesPerFrame: 0.
  		totalSamples := (dataBytes // 5) * 8.
  		^ self].
  	format = 610 ifTrue: [  "GSM 06.10 (this format was added by Squeak)"
  		codec := GSMCodec new.
  		totalSamples := (dataBytes // 33) * 160.
  		^ self].
  	self error: 'unsupported Sun audio format ', format printString
  !

Item was changed:
  ----- Method: StreamingMonoSound>>repeat: (in category 'accessing') -----
  repeat: aBoolean
  	"Set the repeat flag. If true, this sound will loop back to the beginning when it gets to the end."
  
  	repeat := aBoolean.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>samplesRemaining (in category 'playing') -----
  samplesRemaining
  	"Answer the number of samples remaining to be played."
  
  	| result |
  	(stream isNil or: [stream closed]) ifTrue: [^ 0].
  	self repeat ifTrue: [^ 1000000].
  	result := (totalSamples - self currentSampleIndex) max: 0.
  	result <= 0 ifTrue: [self closeFile].
  	^ result
  !

Item was changed:
  ----- Method: StreamingMonoSound>>saveAsFileNamed:compressionType: (in category 'converting') -----
  saveAsFileNamed: newFileName compressionType: compressionTypeString
  	"Store this sound in a new file with the given name using the given compression type. Useful for converting between compression formats."
  
  	| outFile |
  	outFile := (FileStream newFileNamed: newFileName) binary.
  	self storeSunAudioOn: outFile compressionType: compressionTypeString.
  	outFile close.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>soundPosition: (in category 'accessing') -----
  soundPosition: fraction
  	"Jump to the position the given fraction through the sound file. The argument is a number between 0.0 and 1.0."
  
  	| desiredSampleIndex |
  	(stream isNil or: [stream closed]) ifTrue: [^ self].
  	desiredSampleIndex := ((totalSamples * fraction) truncated max: 0) min: totalSamples.
  	codec
  		ifNil: [stream position: audioDataStart + (desiredSampleIndex * 2)]
  		ifNotNil: [self positionCodecTo: desiredSampleIndex].
  	leftoverSamples := SoundBuffer new.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>startOver (in category 'private') -----
  startOver
  	"Jump back to the first sample."
  
  	stream reopen; binary.
  	self readHeader.
  	stream position: audioDataStart.
  	leftoverSamples := SoundBuffer new.
  	lastBufferMSecs := 0.
  	mutex := Semaphore forMutualExclusion.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>volume: (in category 'accessing') -----
  volume: aNumber
  	"Set my volume to the given number between 0.0 and 1.0."
  
  	volume := aNumber.
  	self createMixer.
  !

Item was changed:
  ----- Method: SunAudioFileWriter class>>formatCodeForCompressionType: (in category 'sound storing') -----
  formatCodeForCompressionType: aString
  	"Answer the Sun audio file format number for the given compression type name."
  
  	| lowercase |
  	lowercase := aString asLowercase.
  	'mulaw' = lowercase ifTrue: [^ 1].
  	'none' = lowercase ifTrue: [^ 3].
  	'adpcm3' = lowercase ifTrue: [^ 25].
  	'adpcm4' = lowercase ifTrue: [^ 23].
  	'adpcm5' = lowercase ifTrue: [^ 26].
  	'gsm' = lowercase ifTrue: [^ 610].
  	self error: 'unknown compression style'
  !

Item was changed:
  ----- Method: SunAudioFileWriter class>>onFileNamed: (in category 'instance creation') -----
  onFileNamed: fileName
  	"Answer an instance of me on a newly created file with the given name."
  
  	| file |
  	file := (FileStream newFileNamed: fileName) binary.
  	^ self new setStream: file
  !

Item was changed:
  ----- Method: SunAudioFileWriter class>>storeSampledSound:onFileNamed:compressionType: (in category 'sound storing') -----
  storeSampledSound: aSampledSound onFileNamed: fileName compressionType: aString
  	"Store the samples of the given sampled sound on a file with the given name using the given type of compression. See formatCodeForCompressionType: for the list of compression types."
  
  	| fmt codec f compressed |
  	fmt := self formatCodeForCompressionType: aString.
  	codec := self codecForFormatCode: fmt.
  	f := self onFileNamed: fileName.
  	f writeHeaderSamplingRate: aSampledSound originalSamplingRate format: fmt.
  	codec
  		ifNil: [f appendSamples: aSampledSound samples]
  		ifNotNil: [
  			compressed := codec encodeSoundBuffer: aSampledSound samples.
  			f appendBytes: compressed].
  	f closeFile.
  !

Item was changed:
  ----- Method: SunAudioFileWriter>>setStream: (in category 'initialization') -----
  setStream: aBinaryStream
  	"Initialize myself for writing on the given stream."
  
  	stream := aBinaryStream.
  	headerStart := aBinaryStream position.
  !

Item was changed:
  ----- Method: SunAudioFileWriter>>updateHeaderDataSize (in category 'other') -----
  updateHeaderDataSize
  	"Update the Sun audio file header to reflect the final size of the sound data."
  
  	| byteCount |
  	byteCount := stream position - (headerStart + 24).
  	stream position: headerStart + 8.
  	stream uint32: byteCount.
  !

Item was changed:
  ----- Method: TempoEvent>>tempo: (in category 'as yet unclassified') -----
  tempo: anInteger
  
  	tempo := anInteger.
  !

Item was changed:
  ----- Method: UnloadedSound class>>default (in category 'as yet unclassified') -----
  default
  	"UnloadedSound default play"
  
  	| snd p |
  	snd := super new modulation: 1 ratio: 1.
  	p := OrderedCollection new.
  	p add: 0 at 0.0; add: 10 at 1.0; add: 100 at 1.0; add: 120 at 0.0.
  	snd addEnvelope: (VolumeEnvelope points: p loopStart: 2 loopEnd: 3).
  	^ snd setPitch: 440.0 dur: 1.0 loudness: 0.5
  !

Item was changed:
  ----- Method: VolumeEnvelope>>computeSlopeAtMSecs: (in category 'as yet unclassified') -----
  computeSlopeAtMSecs: mSecs
  	"Private!! Find the next inflection point of this envelope and compute its target volume and the number of milliseconds until the inflection point is reached."
  
  	| t i |
  	((loopEndMSecs ~~ nil) and: [mSecs >= loopEndMSecs]) ifTrue: [  "decay phase"
  		t := (points at: loopEndIndex) x + (mSecs - loopEndMSecs).
  		i := self indexOfPointAfterMSecs: t startingAt: loopEndIndex.
  		i == nil ifTrue: [  "past end"
  			targetVol := points last y * decayScale.
  			mSecsForChange := 0.
  			nextRecomputeTime := mSecs + 1000000.
  			^ self].
  		targetVol := (points at: i) y * decayScale.
  		mSecsForChange := (((points at: i) x - t) min: (endMSecs - mSecs)) max: 4.
  		nextRecomputeTime := mSecs + mSecsForChange.
  		^ self].
  
  	mSecs < loopStartMSecs ifTrue: [  "attack phase"
  		i := self indexOfPointAfterMSecs: mSecs startingAt: 1.
  		targetVol := (points at: i) y.
  		mSecsForChange := ((points at: i) x - mSecs) max: 4.
  		nextRecomputeTime := mSecs + mSecsForChange.
  		((loopEndMSecs ~~ nil) and: [nextRecomputeTime > loopEndMSecs])
  			ifTrue: [nextRecomputeTime := loopEndMSecs].
  		^ self].
  
  	"sustain and loop phase"
  	noChangesDuringLoop ifTrue: [
  		targetVol := (points at: loopEndIndex) y.
  		mSecsForChange := 10.
  		loopEndMSecs == nil
  			ifTrue: [nextRecomputeTime := mSecs + 10]  "unknown end time"
  			ifFalse: [nextRecomputeTime := loopEndMSecs].
  		^ self].
  
  	loopMSecs = 0 ifTrue: [^ (points at: loopEndIndex) y].  "looping on a single point"
  	t := loopStartMSecs + ((mSecs - loopStartMSecs) \\ loopMSecs).
  	i := self indexOfPointAfterMSecs: t startingAt: loopStartIndex.
  	targetVol := (points at: i) y.
  	mSecsForChange := ((points at: i) x - t) max: 4.
  	nextRecomputeTime := (mSecs + mSecsForChange) min: loopEndMSecs.
  !

Item was changed:
  ----- Method: VolumeEnvelope>>reset (in category 'as yet unclassified') -----
  reset
  	"Reset the state for this envelope."
  
  	super reset.
  	target initialVolume: points first y * scale.
  	nextRecomputeTime := 0.
  !

Item was changed:
  ----- Method: VolumeEnvelope>>updateTargetAt: (in category 'as yet unclassified') -----
  updateTargetAt: mSecs
  	"Update the volume envelope slope and limit for my target. Answer false."
  
  	mSecs < nextRecomputeTime ifTrue: [^ false].
  	self computeSlopeAtMSecs: mSecs.
  	mSecsForChange < 5 ifTrue: [mSecsForChange := 5].  "don't change instantly to avoid clicks"
  	target adjustVolumeTo: targetVol * scale overMSecs: mSecsForChange.
  	^ false
  !

Item was changed:
  ----- Method: VolumeEnvelope>>volume: (in category 'as yet unclassified') -----
  volume: aNumber
  	"Set the maximum volume of a volume-controlling envelope."
  
  	scale := aNumber asFloat.
  !

Item was changed:
  ----- Method: WaveletCodec>>decodeFrames:from:at:into:at: (in category 'subclass responsibilities') -----
  decodeFrames: frameCount from: srcByteArray at: srcIndex into: dstSoundBuffer at: dstIndex
  	"Decode the given number of monophonic frames starting at the given index in the given ByteArray of compressed sound data and storing the decoded samples into the given SoundBuffer starting at the given destination index. Answer a pair containing the number of bytes of compressed data consumed and the number of decompressed samples produced."
  	"Note: Assume that the sender has ensured that the given number of frames will not exhaust either the source or destination buffers."
  
  	| frameBase coeffArray scale i c nullCount samples sourceFrameEnd frameSize inStream val |
  	inStream := ReadStream on: srcByteArray from: srcIndex to: srcByteArray size.
  	"frameCount := " inStream nextNumber: 4.
  	samplesPerFrame := inStream nextNumber: 4.
  	nLevels := inStream nextNumber: 4.
  	alpha := Float fromIEEE32Bit: (inStream nextNumber: 4).
  	beta := Float fromIEEE32Bit: (inStream nextNumber: 4).
  	fwt ifNil:
  		["NOTE: This should read parameters from the encoded data"
  		fwt := FWT new.
  		fwt nSamples: samplesPerFrame nLevels: nLevels.
  		fwt setAlpha: alpha beta: beta].
  	frameBase := dstIndex.
  	coeffArray := fwt coeffs.  "A copy that we can modify"
  
  	1 to: frameCount do:
  		[:frame | 
  
  		"Decode the scale for this frame"
  		frameSize := inStream nextNumber: 2.
  		sourceFrameEnd := frameSize + inStream position.
  		scale := Float fromIEEE32Bit: (inStream nextNumber: 4).
  
  		"Expand run-coded samples to scaled float values."
  		i := 5.
  		[i <= coeffArray size]
  			whileTrue:
  			[c := inStream next.
  			c < 128
  				ifTrue: [nullCount := c < 112
  							ifTrue: [c + 1]
  							ifFalse: [(c-112)*256 + inStream next + 1].
  						i to: i + nullCount - 1 do: [:j | coeffArray at: j put: 0.0].
  						i := i + nullCount]
  				ifFalse: [val := (c*256 + inStream next) - 32768 - 16384.
  						coeffArray at: i put: val * scale.
  						i := i + 1]].
  
  		"Copy float values into the wavelet sample array"		
  			fwt coeffs: coeffArray.
  
  		"Compute the transform"
  		fwt transformForward: false.
  
  		"Determine the scale for this frame"
  		samples := fwt samples.
  		samples size = samplesPerFrame ifFalse: [self error: 'frame size error'].
  		1 to: samples size do:
  			[:j | dstSoundBuffer at: frameBase + j - 1 put: (samples at: j) asInteger].
  
  		inStream position = sourceFrameEnd ifFalse: [self error: 'frame size error'].
  		frameBase := frameBase + samplesPerFrame].
  
  	^ Array with: inStream position + 1 - srcIndex
  			with: frameBase - dstIndex!



More information about the Packages mailing list