[ENH] LoopedSampledSound and sound file enhancements

Jesse Welton jwelton at pacific.mps.ohio-state.edu
Fri Mar 3 16:37:54 UTC 2000


Here is release 1 of some LoopedSampledSound and sound file enhancements
I've been working on.

The first change set is an enhancement to LoopedSampledSound to provide
ping-pong looping functionality, fractional loop endpoints, and one or two
other things needed to more fully support the available selection of sound
file formats.  For best results, a rebuild of the VM is required.

A nearly-original version of LoopedSampledSound has been retained as class
OldLoopedSampledSound, both for performance comparison and as a
place-holder for the old primitive code.  (Advice on how best to phase
this into "old code" someplace would be appreciated.)

The second change set, SoundFiles.1.cs, creates a heirarchy for defining
sampled sound readers which provides support for the creation of
SampledSounds and LoopedSampledSounds from the data read.  The
AIFFFileReader is fitted into this framework (in fact, it forms the basis
of significant parts of it).  The Wave file code from SampledSound class
is used as the basis for a WaveFileReader, so that LoopedSampledSounds can
now be read from Wave files, as well.

Finally, a preliminary GUSFileReader for reading Gravis UltraSound patch
files is defined, per a suggestion by Lex Spoon last April or so.  This is
of pre-alpha quality, as yet unusable, for the simple fact that I have yet
to pin down the precise meaning of many of the fields.  In particular, the
samples' base frequency needs to be scaled in some way for the sounds to
be remotely usable for their intended purpose.  (Does anyone have some
information on this?)  However, the basic framework is in place to allow a
patch file to be read to produce a SampledInstrument.  If nothing else,
perhaps this will provide some additional motivation for the
LoopedSampledSound enhancements.

If anyone has comments, suggestions, or offers to help me polish this
stuff up, just let me know.

-Jesse
-------------- next part --------------
A non-text attachment was scrubbed...
Name: LoopedSampledSoundEnh.1.cs
Type: application/octet-stream
Size: 47745 bytes
Desc: 
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20000303/4b0724d1/LoopedSampledSoundEnh.1.obj
-------------- next part --------------
'From Squeak2.8alpha of 23 February 2000 [latest update: #1852] on 29 February 2000 at 9:32:40 pm'!
"Change Set:		SoundFiles
Date:			29 February 2000
Author:			Jesse Welton

Adds a heirarchy of sound readers to parse sound data from file and stream sources.  SoundStreamReader draws heavily on the most general parts of AIFFFileReader to provide a framework for extracting sound data from binary streams, and SoundFileReader extends this with entry points for reading sound files.  Both are abstract, relying on subclasses to deal with specific sound formats.

AIFFFileReader is redefined as a subclass of SoundFileReader, and a WaveFileReader is also defined, drawing on both AIFFFileReader structure and the Wave file reading methods from SampledSound class.  This begins work towards a unified AIFF and Wave file reading interface for SampledSounds and LoopedSampledSounds.

A partially complete GUSPatchReader is defined, which allows reading Gravis UltraSound patch files.  An extremely basic interface for extracting the patch data to SampledInstruments is provided, but is not yet usable because I have to work out some details of the patch file format.  (In particular, the sampled sounds' sampling rates are orders of magnitude too high; I must find the proper scaling for these.)  The helper class GUSSampleReader illustrates the use of a SoundStreamReader to parse only a part of a more complex file.

Assumes LoopedSampledSounds can handle assorted loop styles (see LoopedSampledSoundEnh.cs).  Includes minor adjustments to AIFFFileReader's interface.  For now, Wave file reading facilities have been left in SampledSound class.
"!

Object subclass: #GUSPatchReader
	instanceVariableNames: 'format manufacturer description instrumentCount voices channelCount waveformCount masterVolume dataSize instrumentID instrumentName instrumentSize layers layerDuplicate layer layerSize layerSampleCount soundSamples '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Sound-Files'!
Object subclass: #SoundStreamReader
	instanceVariableNames: 'channelCount frameCount bitsPerSample samplingRate channelData loopStart loopEnd pitch gain loopStyle skipDataChunk mergeIfStereo '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Sound-Files'!
SoundStreamReader subclass: #GUSSampleReader
	instanceVariableNames: 'waveName fractions signedData tune useSustain useFilterEnvelope clampedRelease scaleFrequency scaleFactor '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Sound-Files'!
SoundStreamReader subclass: #SoundFileReader
	instanceVariableNames: 'in fileType '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Sound-Files'!
SoundFileReader subclass: #AIFFFileReader
	instanceVariableNames: 'markers '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Sound-Files'!
SoundFileReader subclass: #WaveFileReader
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Sound-Files'!

!GUSPatchReader commentStamp: 'JW 2/11/2000 09:15' prior: 0!
This class parses Gravis UltraSound patch files, to create SampledInstruments.!

!GUSPatchReader reorganize!
('reading' readFromFile: readFromFile:skipData: readFromStream:skipData: readPatternSetFrom:)
('accessing' channelCount dataSize description format instrumentCount instrumentID instrumentName instrumentSize layer layerDuplicate layerSampleCount layerSize layers manufacturer masterVolume voices waveformCount)
('other' sampledInstrument)
!


!GUSPatchReader methodsFor: 'reading' stamp: 'JW 2/11/2000 08:21'!
readFromFile: fileName
	"GUSPatchReader new readFromFile: 'Power HD:TiMidity++:patches:eawpats7:acpiano.pat'"

	self readFromFile: fileName skipData: false.
! !

!GUSPatchReader methodsFor: 'reading' stamp: 'JW 2/11/2000 08:20'!
readFromFile: fileName skipData: aBoolean
	"GUSPatchReader new readFromFile: 'acpiano.pat' skipData: true"

	| f |
	f _ (FileStream readOnlyFileNamed: fileName) binary.
	self readFromStream: f skipData: aBoolean.
	f close.
! !

!GUSPatchReader methodsFor: 'reading' stamp: 'JW 2/11/2000 09:28'!
readFromStream: in skipData: aBoolean
	"Read data from a binary stream input."
	"Only supports basic functionality so far, but this includes all patches I personally have.  One instrument/one channel(mono)/one layer.  0 is equivalent to 1 for all these."

	| fmt |
	format := (in next: 12) asString.
	(format copyFrom: 1 to: 8) = 'GF1PATCH'
		ifFalse: [ self error: 'not a GUS patch file' ].
	"Don't know if format 100 is correct, but what docs I can find say 100 and 110 are almost identical."
	(((fmt := format copyFrom: 9 to: 11) = '100' or: [fmt = '110'])
		and: [ (format at: 12) asciiValue = 0 ])
			ifFalse: [ self error: format, 'is not a recognized GUS patch format' ].
	manufacturer := (in next: 10) asString.

	description := (in next: 60) asString.
	instrumentCount := in next.
	instrumentCount = 0 ifTrue: [instrumentCount := 1]. "some use 0 for 1"
	instrumentCount = 1 ifFalse:
		[ self error: 'unsupported instrument count: ', instrumentCount printString ].
	voices := in next. "ignored; usually 14"
	channelCount := in next.
	channelCount = 0 ifTrue: [channelCount := 1].
	channelCount = 1 ifFalse:
		[ self error: 'unsupported channel count: ', channelCount printString ].
	waveformCount := in nextLittleEndianNumber: 2.
	masterVolume := in nextLittleEndianNumber: 2.
	dataSize := in nextLittleEndianNumber: 4.
	in skip: 36. "reserved patch header bytes"

	instrumentID := in nextLittleEndianNumber: 2. "ignored; usually 0"
	instrumentName := (in next: 16) asString.
	instrumentSize := in nextLittleEndianNumber: 4.
	layers := in next.
	layers = 0 ifTrue: [layers := 1].
	layers = 1 ifFalse:
		[ self error: 'unsupported layer count: ', layers printString ].
	in skip: 40. "reserved instrument header bytes"

	layerDuplicate := in next. "ignored; usually 0"
	layer := in next. "ignored; usually 0"
	layerSize := in nextLittleEndianNumber: 4.
	layerSampleCount := in next.
	in skip: 40. "reserved layer header bytes"

	soundSamples := (1 to: layerSampleCount) collect:
		[ :i | GUSSampleReader new
				channelCount: channelCount;
				skipData: aBoolean;
				readFrom: in ].! !

!GUSPatchReader methodsFor: 'reading' stamp: 'JW 2/10/2000 21:21'!
readPatternSetFrom: dirName
	"GUSPatchReader new readPatternSetFrom: 'Power HD:TiMidity++:patches:eawpats7'"

	| all dir fullName pat |
	dir _ FileDirectory default on: dirName.
	all := dir fileNames select: [:each | (each copyLast: 4) = '.pat' ]
			thenCollect: [:n |
		fullName _ dir fullNameFor: n.
		Utilities
			informUser: 'Reading pattern file ', n
			during: [pat _ GUSPatchReader new readFromFile: fullName].
		pat].
	^ all asArray
! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
channelCount
	"Answer the receiver's instance variable channelCount."

	^channelCount! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
dataSize
	"Answer the receiver's instance variable dataSize."

	^dataSize! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
description
	"Answer the receiver's instance variable description."

	^description! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
format
	"Answer the receiver's instance variable format."

	^format! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
instrumentCount
	"Answer the receiver's instance variable instrumentCount."

	^instrumentCount! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
instrumentID
	"Answer the receiver's instance variable instrumentID."

	^instrumentID! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
instrumentName
	"Answer the receiver's instance variable instrumentName."

	^instrumentName! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
instrumentSize
	"Answer the receiver's instance variable instrumentSize."

	^instrumentSize! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
layer
	"Answer the receiver's instance variable layer."

	^layer! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
layerDuplicate
	"Answer the receiver's instance variable layerDuplicate."

	^layerDuplicate! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
layerSampleCount
	"Answer the receiver's instance variable layerSampleCount."

	^layerSampleCount! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:01'!
layerSize
	"Answer the receiver's instance variable layerSize."

	^layerSize! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:02'!
layers
	"Answer the receiver's instance variable layers."

	^layers! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:02'!
manufacturer
	"Answer the receiver's instance variable manufacturer."

	^manufacturer! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:02'!
masterVolume
	"Answer the receiver's instance variable masterVolume."

	^masterVolume! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:02'!
voices
	"Answer the receiver's instance variable voices."

	^voices! !

!GUSPatchReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:02'!
waveformCount
	"Answer the receiver's instance variable waveformCount."

	^waveformCount! !

!GUSPatchReader methodsFor: 'other' stamp: 'JW 2/29/2000 20:58'!
sampledInstrument
	"Return a SampledInstrument with the sounds specified by this GUS patch."

	^ SampledInstrument new allSampleSets: (soundSamples collect: [:each | each sound])! !


!LoopedSampledSound methodsFor: 'initialization' stamp: 'JW 2/29/2000 19:50'!
fromSoundReader: soundReader
	"Initialize this sound from the data in the given sound reader, which is expected to be a kind of SoundStreamReader with its data already loaded."

	soundReader isLooped
		ifTrue: [
			self samples: soundReader leftSamples
				loopEnd: soundReader loopEnd
				loopLength: soundReader loopLength
				pitch: soundReader pitch
				samplingRate: soundReader samplingRate]
		ifFalse: [
			self unloopedSamples: soundReader leftSamples
				pitch: soundReader pitch
				samplingRate: soundReader samplingRate].

	"the following must be done second, since the initialization above sets
	 leftSamples and rightSamples to the same sample data"
	soundReader isStereo
		ifTrue: [rightSamples _ soundReader rightSamples].

	soundReader isLooped ifTrue: [self loopStyle: soundReader loopStyle].

	initialCount _ (leftSamples size * self samplingRate) // originalSamplingRate.
	self loudness: 1.0.

	self addReleaseEnvelope.
! !


!LoopedSampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 19:56'!
fromAIFFFileNamed: fileName
	"Read a SampledSound from the AIFF file of the given name.  Do not merge stereo."

	^ self fromSoundFileReader: AIFFFileReader new
		onFileNamed: fileName
		mergeIfStereo: false
! !

!LoopedSampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 20:00'!
fromAIFFFileNamed: fileName mergeIfStereo: mergeFlag
	"Read a SampledSound from the AIFF file of the given name.  Merge stereo, if mergeFlag is true."

	^ self fromSoundFileReader: AIFFFileReader new
		onFileNamed: fileName
		mergeIfStereo: mergeFlag
! !

!LoopedSampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 20:10'!
fromSoundFileReader: fileReader onFileNamed: fileName mergeIfStereo: mergeFlag
	"Use the given SoundFileReader to read a LoopedSampledSound from the file of the given name, merging stereo to mono if mergeFlag is true."

	fileReader readFromFile: fileName
		mergeIfStereo: mergeFlag
		skipDataChunk: false.
	^ self basicNew fromSoundReader: fileReader

! !

!LoopedSampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 19:58'!
fromWaveFileNamed: fileName
	"Read a SampledSound from the Wave file of the given name.  Do not merge stereo."

	^ self fromSoundFileReader: WaveFileReader new
		onFileNamed: fileName
		mergeIfStereo: false
! !

!LoopedSampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 19:59'!
fromWaveFileNamed: fileName mergeIfStereo: mergeFlag
	"Read a SampledSound from the Wave file of the given name.  Merge stereo, if mergeFlag is true."

	^ self fromSoundFileReader: WaveFileReader new
		onFileNamed: fileName
		mergeIfStereo: mergeFlag
! !


!SampledInstrument methodsFor: 'other' stamp: 'JW 2/29/2000 19:51'!
readSampleSetFrom: dirName
	"Answer a collection of sounds read from AIFF files in the given directory and sorted in ascending pitch order."

	| all dir fullName snd |
	all _ SortedCollection sortBlock: [:s1 :s2 | s1 pitch < s2 pitch].
	dir _ FileDirectory default on: dirName.
	dir fileNames do: [:n |
		fullName _ dir fullNameFor: n.
		Utilities
			informUser: 'Reading AIFF file ', n
			during:
				[snd _ LoopedSampledSound
					fromAIFFFileNamed: fullName
					mergeIfStereo: true].
		all add: snd].
	^ all asArray
! !


!SampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 19:34'!
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]]."

	^ self fromSoundFileReader: AIFFFileReader new onFileNamed: fileName
! !

!SampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 19:33'!
fromSoundFileReader: fileReader onFileNamed: fileName
	"Use the given SoundFileReader to read a SampledSound from the file of the given name, merging stereo to mono if necessary."

	fileReader readFromFile: fileName
		mergeIfStereo: true
		skipDataChunk: false.
	^ self samples: fileReader samples
		samplingRate: fileReader samplingRate
! !

!SampledSound class methodsFor: 'instance creation' stamp: 'JW 2/29/2000 19:35'!
fromWaveFileNamed: fileName
	"(SampledSound fromWaveFileNamed: 'c:\windows\media\chimes.wav') play"
	"| snd fd |
	fd := FileDirectory on:'c:\windows\media\'.
	fd fileNames do: [:n |
		(n asLowercase endsWith: '.wav')
			ifTrue: [
				snd _ SampledSound fromWaveFileNamed: (fd pathName,n).
				snd play.
				SoundPlayer waitUntilDonePlaying: snd]]."

	^ self fromSoundFileReader: WaveFileReader new onFileNamed: fileName
! !


!SoundBuffer methodsFor: 'utilities' stamp: 'JW 2/9/2000 14:57'!
mergeStereo
	"Answer a SoundBuffer half the size of the receiver consisting of the merged left and right channels of the receiver (which is assumed to contain stereo sound data)."

	| n mergedBuf mergedIndex mergedSample |
	n _ self stereoSampleCount.
	mergedBuf _ SoundBuffer newMonoSampleCount: n.
	mergedIndex _ 0.
	1 to: n by: 2 do: [:i |
		mergedSample _ (self at: i) + (self at: i + 1) bitShift: (-1).
		mergedBuf at: (mergedIndex _ mergedIndex + 1) put: mergedSample].
	^ mergedBuf
! !

!SoundBuffer methodsFor: 'utilities' stamp: 'JW 2/9/2000 14:54'!
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 stereoSampleCount.
	leftBuf _ SoundBuffer newMonoSampleCount: n.
	rightBuf _ SoundBuffer newMonoSampleCount: n.
	leftIndex _ rightIndex _ 0.
	1 to: n*2 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
! !

Smalltalk renameClassNamed: #SoundFileReader as: #SoundStreamReader!

!SoundStreamReader commentStamp: 'JW 2/11/2000 09:02' prior: 0!
This is an abstract base class for assorted audio readers.  It provides the high-level interface for extracting sound data used in the initialization of various species of sampled sounds.

Sound files should be read with concrete subclasses of the abstract SoundFileReader subclass.!

!SoundStreamReader reorganize!
('reading' readFrom:)
('accessing' bitsPerSample channelCount channelData frameCount gain isLooped isPingpongLooped isStereo leftSamples loopEnd loopLength loopStart loopStyle pitch rightSamples samples samplingRate)
('other' edit pitchForMIDIKey: pitchForMIDIKey:detune: sound soundAsLoopedSampledSound soundAsSampledOrMixedSound)
('utilities' convert8bitSignedFrom:to16Bit: convert8bitSignedTo16Bit: convert8bitUnsignedTo16Bit: convertBytesTo16BitSamples:mostSignificantByteFirst: convertBytesToUnsigned16BitSamples:mostSignificantByteFirst: uLawDecode: uLawDecodeTable uLawEncode: uLawEncodeSample:)
!


!SoundStreamReader methodsFor: 'reading' stamp: 'JW 2/5/2000 21:56'!
readFrom: aBinaryStream
	^self subclassResponsibility! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
bitsPerSample

	^ bitsPerSample
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
channelCount

	^ channelCount
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
channelData

	^ channelData
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
frameCount

	^ frameCount
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
gain

	^ gain
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
isLooped

	^ (loopStyle = #unlooped) not
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/28/2000 20:46'!
isPingpongLooped

	^ loopStyle = #pingpong
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
isStereo

	^ channelData size = 2
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
leftSamples

	^ channelData at: 1
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/7/2000 20:52'!
loopEnd

	^ loopEnd
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/7/2000 20:52'!
loopLength

	^ loopEnd - loopStart
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/7/2000 20:52'!
loopStart

	^ loopStart
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/28/2000 20:45'!
loopStyle

	^ loopStyle
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
pitch

	^ pitch
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
rightSamples

	^ channelData at: 2
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 08:58'!
samples

	^ self leftSamples
! !

!SoundStreamReader methodsFor: 'accessing' stamp: 'JW 2/5/2000 21:49'!
samplingRate

	^ samplingRate
! !

!SoundStreamReader methodsFor: 'other' stamp: 'JW 2/11/2000 18:30'!
edit

	| ed |
	ed _ WaveEditor new.
	ed data: channelData first.
	ed loopEnd: self loopEnd.
	ed loopLength: self loopLength.
	ed openInWorld.
! !

!SoundStreamReader methodsFor: 'other' stamp: 'JW 2/7/2000 20:35'!
pitchForMIDIKey: 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)
! !

!SoundStreamReader methodsFor: 'other' stamp: 'JW 2/7/2000 20:35'!
pitchForMIDIKey: midiKey detune: detune
	"Answer the pitch for the given MIDI key, detuned by detune semitones."

	^ (self pitchForMIDIKey: midiKey) * (1.059463094359295 "(2 raisedTo: 1/12)" raisedTo: detune)

! !

!SoundStreamReader methodsFor: 'other' stamp: 'JW 2/29/2000 20:38'!
sound
	"Answer the sound represented by this SoundFileReader. This method should be called only after readFrom: has been done."

	self isLooped ifTrue: [^ self soundAsLoopedSampledSound].
	^ self soundAsSampledOrMixedSound.! !

!SoundStreamReader methodsFor: 'other' stamp: 'JW 2/29/2000 20:38'!
soundAsLoopedSampledSound
	"Answer the sound represented by this SoundFileReader, as a LoopedSmapledSound."

	^ LoopedSampledSound new fromSoundReader: self
! !

!SoundStreamReader methodsFor: 'other' stamp: 'JW 2/5/2000 21:53'!
soundAsSampledOrMixedSound
	"Answer the sound represented by this SoundFileReader, as a SampledSound or (if stereo) a MixedSound."

	| 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
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:50'!
convert8bitSignedFrom: aByteArray to16Bit: aSoundBuffer
	"Copy the contents of the given array of signed 8-bit samples into the given array of 16-bit signed samples."

	| n s |
	<primitive: 236>
	self var: #aByteArray declareC: 'unsigned char *aByteArray'.
	self var: #aSoundBuffer declareC: 'unsigned short *aSoundBuffer'.
	n _ aByteArray size.
	1 to: n do: [:i |
		s _ aByteArray at: i.
		s > 127
			ifTrue: [aSoundBuffer at: i put: ((s - 256) bitShift: 8)]
			ifFalse: [aSoundBuffer at: i put: (s bitShift: 8)]].
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:51'!
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
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:51'!
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
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:51'!
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
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 18:11'!
convertBytesToUnsigned16BitSamples: 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 - 32768]
			ifFalse: [w _ (b2 bitShift: 8) + b1 - 32768].
		data at: i put: w.
		src _ src + 2].
	^ data
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:51'!
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
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:51'!
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)
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:51'!
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
! !

!SoundStreamReader methodsFor: 'utilities' stamp: 'JW 2/11/2000 08:51'!
uLawEncodeSample: s
	"Encode the given 16-bit signed sample using the uLaw 8-bit encoding."

	s < 496 ifTrue: [
		s < 112 ifTrue: [
			s < 48 ifTrue: [
				s < 16
					ifTrue: [^ 16r70 bitOr: (15 - s)]
					ifFalse: [^ 16r60 bitOr: (15 - ((s - 16) bitShift: -1))]].
			^ 16r50 bitOr: (15 - ((s - 48) bitShift: -2))].
		s < 240
			ifTrue: [^ 16r40 bitOr: (15 - ((s - 112) bitShift: -3))]
			ifFalse: [^ 16r30 bitOr: (15 - ((s - 240) bitShift: -4))]].

	s < 2032 ifTrue: [
		s < 1008
			ifTrue: [^ 16r20 bitOr: (15 - ((s - 496) bitShift: -5))]
			ifFalse: [^ 16r10 bitOr: (15 - ((s - 1008) bitShift: -6))]].

	s < 4080
		ifTrue: [^ 15 - ((s - 2032) bitShift: -7)]
		ifFalse: [^ 0].
! !


!GUSSampleReader commentStamp: 'JW 2/11/2000 09:16' prior: 0!
This class assists the GUSPatchReader by reading individual sample records from the GUS patch data stream.!

!GUSSampleReader methodsFor: 'reading' stamp: 'JW 2/24/2000 09:38'!
readFrom: in

	| dataSize loopStartInBytes loopEndInBytes sampleModes data |
	waveName := (in next: 7) asString.
	fractions := in next.
	dataSize := in nextLittleEndianNumber: 4.
	loopStartInBytes := (in nextLittleEndianNumber: 4).
	loopEndInBytes := (in nextLittleEndianNumber: 4).

	samplingRate := in nextLittleEndianNumber: 2.
	in skip: 8. "low and high frequencies - come back to this"
	pitch := in nextLittleEndianNumber: 4.

	tune := in nextLittleEndianNumber: 2.
	"tune = 1 ifFalse: [ self error: 'tune field must be 1' ]."

	in skip: 19. "panning, envelopes, etc - come back to this"

	sampleModes := in next.
	(sampleModes allMask: 1)
		ifTrue: [ bitsPerSample := 16.
			loopStart := loopStartInBytes / (2 * channelCount).
			loopEnd := loopEndInBytes / (2 * channelCount). ]
		ifFalse: [ bitsPerSample := 8.
			loopStart := loopStartInBytes / channelCount.
			loopEnd := loopEndInBytes / channelCount. ].
	loopStart := loopStart + ((fractions bitAnd: 15)/16).
	loopEnd := loopEnd + ((fractions bitShift: -4)/16).
	signedData := (sampleModes allMask: 2) not.
	loopStyle := #unlooped.
	(sampleModes allMask: 4) ifTrue: [ loopStyle := #looped ].
	(sampleModes allMask: 8) ifTrue: [ loopStyle := #pingpong ].
	(sampleModes allMask: 16) ifTrue: [ loopStyle := #reverse ].
	useSustain := (sampleModes allMask: 32). "not sure how this works"
	useFilterEnvelope := (sampleModes allMask: 64). "not sure how this works"
	clampedRelease := (sampleModes allMask: 128). "not sure how this works"

	scaleFrequency := in nextLittleEndianNumber: 2. "not sure how this works"
	scaleFactor := in nextLittleEndianNumber: 2. "not sure how this works"

"	Transcript show: 'tune: ', tune printString;
		show: '	scaleFreq: ', scaleFrequency printString;
		show: '	scaleFact: ', scaleFactor printString;
		cr."

	in skip: 36. "sample header reserved bytes"

	skipDataChunk ifTrue: [ in skip: dataSize. ^ self ].

	data := in next: dataSize.
	bitsPerSample = 8
		ifTrue: [signedData
					ifTrue: [data _ self convert8bitSignedTo16Bit: data]
					ifFalse: [data _ self convert8bitUnsignedTo16Bit: data]]
		ifFalse: [signedData
					ifTrue: [data _ self convertBytesTo16BitSamples: data mostSignificantByteFirst: false]
					ifFalse: [data _ self convertBytesToUnsigned16BitSamples: data mostSignificantByteFirst: false]].

	channelCount = 1 ifTrue: [ channelData _ Array with: data ].
	channelCount = 2 ifTrue: [ channelData _ data splitStereo ].
! !

!GUSSampleReader methodsFor: 'other' stamp: 'JW 2/29/2000 20:48'!
sound
	"Provide LoopedSampledSounds for use in SampledInstruments, even if the sounds are unlooped."

	^ self soundAsLoopedSampledSound! !

!GUSSampleReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 09:25'!
channelCount: anInteger
	channelCount := anInteger! !

!GUSSampleReader methodsFor: 'accessing' stamp: 'JW 2/11/2000 09:26'!
skipData: aBoolean
	skipDataChunk := aBoolean! !


!SoundFileReader commentStamp: 'JW 2/11/2000 09:17' prior: 0!
This is the abstract base class for various concrete sound file readers which understand how to parse entire sound files.!

!SoundFileReader methodsFor: 'reading' stamp: 'JW 2/11/2000 08:53'!
readFromFile: fileName
	"Read the sound file of the given name."
	"(AIFFFileReader new readFromFile: 'Power HD:Sound and Music:Sound Samples:Roland Samples:Choir Samples:choirTenor.aiff') sound duration: 3; play"

	self readFromFile: fileName
		mergeIfStereo: false
		skipDataChunk: false.
! !

!SoundFileReader methodsFor: 'reading' stamp: 'JW 2/11/2000 08:53'!
readFromFile: fileName mergeIfStereo: mergeFlag skipDataChunk: skipDataFlag
	"Read the sound file of the given name. If mergeFlag is true and the file contains stereo data, then the left and right channels will be mixed together as the samples are read in. If skipDataFlag is true, then the data chunk to be skipped; this allows the other chunks of a file to be processed in order to extract format information quickly without reading the data."
	"AIFFFileReader new readFromFile: 'test.aiff' mergeIfStereo: false skipDataChunk: true"

	| f |
	mergeIfStereo _ mergeFlag.
	skipDataChunk _ skipDataFlag.
	f _ (FileStream readOnlyFileNamed: fileName) binary.
	loopStyle _ #unlooped.
	gain _ 1.0.
	self readFrom: f.
	f close.
! !


!AIFFFileReader methodsFor: 'private' stamp: 'JW 2/22/2000 08:15'!
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.
	loopStyle _ #(unlooped looped pingpong) at: sustainMode + 1.
	(loopStart isNil or: [loopEnd isNil]) ifTrue: [
		loopStart := sustainStartID.
		loopEnd := sustainEndID. ].
	(self isLooped and: [loopStart notNil]) ifTrue: [
		((loopStart > frameCount) or: [loopEnd > frameCount]) ifTrue: [
			"bad loop data; some sample CD files claim to be looped but aren't"
			loopStyle _ #unlooped]].
	pitch _ self pitchForMIDIKey: midiKey detune: detune/128.
! !

!AIFFFileReader methodsFor: 'private' stamp: 'JW 2/7/2000 20:57'!
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)].

	loopStart := markers first last.
	loopEnd := markers last last.
! !

!AIFFFileReader methodsFor: 'accessing' stamp: 'JW 2/7/2000 20:54'!
markers
	"Do we really need to keep marker data?  I'm saving it just in case."
	^ markers
! !


!WaveFileReader commentStamp: 'JW 2/11/2000 09:10' prior: 0!
This class represents a parser for Wave-format audio files.  It is capable of reading uncompressed  8- and 16-bit Wave files with one or two channels, and understands looping data contained in the 'smpl' sampler chunk.!

!WaveFileReader methodsFor: 'private' stamp: 'JW 2/7/2000 19:45'!
readChunk: chunkType size: chunkSize
	"Read a RIFF chunk of the given type. Skip unrecognized chunks. Leave the input stream positioned chunkSize bytes past its position when this method is called."
	"Cue ('cue ') and PlayList ('plst') chunks not currently supported."

	chunkType = 'fmt ' ifTrue: [^ self readFormatChunk: chunkSize].
	chunkType = 'data' ifTrue: [^ self readDataChunk: chunkSize].
	chunkType = 'smpl' ifTrue: [^ self readSamplerChunk: chunkSize].
	in skip: chunkSize.  "skip unknown chunks"

	Transcript show: 'Wave file chunk "', chunkType, '", length ', chunkSize printString, ', skipped'; cr. 	"just to see what we're missing"
! !

!WaveFileReader methodsFor: 'private' stamp: 'JW 2/24/2000 09:46'!
readDataChunk: chunkSize
	| data |
	skipDataChunk ifTrue: [in skip: chunkSize. ^ self].

	data := in next: chunkSize.

	bitsPerSample = 8
		ifTrue: [data _ self convert8bitUnsignedTo16Bit: data]
		ifFalse: [data _ self convertBytesTo16BitSamples: data mostSignificantByteFirst: false].

	channelCount = 1 ifTrue: [ channelData _ Array with: data ].
	channelCount = 2 ifTrue: [ mergeIfStereo
									ifTrue: [ channelData _ data mergeStereo ]
									ifFalse: [ channelData _ data splitStereo ] ].
! !

!WaveFileReader methodsFor: 'private' stamp: 'JW 2/7/2000 16:39'!
readFormatChunk: chunkSize
	| type blockAlign |

	type _ in nextLittleEndianNumber: 2.
	type = 1 ifFalse: [^ self error:'Unexpected wave format'].
	channelCount _ in nextLittleEndianNumber: 2.
	(channelCount < 1 or: [channelCount > 2])
		ifTrue: [^ self error: 'Unexpected number of wave channels'].
	samplingRate _ in nextLittleEndianNumber: 4.
	in skip: 4.	"skip average bytes per second"
	blockAlign _ in nextLittleEndianNumber: 2.
	bitsPerSample _ in nextLittleEndianNumber: 2.
	(bitsPerSample = 8 or: [bitsPerSample = 16])
		ifFalse: [	"recompute bits per sample"
			bitsPerSample _ (blockAlign // channelCount) * 8].


! !

!WaveFileReader methodsFor: 'private' stamp: 'JW 2/5/2000 22:48'!
readFrom: aBinaryStream
	"Read Wave data from the given binary stream."

	| sz end chunkType chunkSize p |
	in _ aBinaryStream.

	"read RIFF chunk"
	(in next: 4) asString = 'RIFF' ifFalse: [^ self error: 'not a Wave file'].
	sz _ in nextLittleEndianNumber: 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 nextLittleEndianNumber: 4.
		p _ in position.
		self readChunk: chunkType size: chunkSize.
		(in position = (p + chunkSize))
			ifFalse: [self error: 'chunk size mismatch; bad Wave file?'].
		chunkSize odd ifTrue: [in skip: 1]].  "skip padding byte"
! !

!WaveFileReader methodsFor: 'private' stamp: 'JW 2/24/2000 09:38'!
readSamplerChunk: chunkSize
	| chunkStart samplePeriod MIDINote detune loopCount loopType loopStartBytes loopEndBytes loopFineTuning |

	chunkStart := in position.

	in skip: 8.	"skip manuafacturer code and product number"
	samplePeriod := in nextLittleEndianNumber: 4.	"nanoseconds per sample"
	(samplingRate isNil or: [samplingRate < samplePeriod]) ifTrue:
		[ samplingRate := 1000000000/samplePeriod ].	"us this when it gives better precision"
	MIDINote := in nextLittleEndianNumber: 4.	"nominal pitch"
	detune := in nextLittleEndianNumber: 4.	"pitch adjustment - not sure if this is signed"
		"16r80000000 = 50 cents = 1/2 semitone"
	pitch := self pitchForMIDIKey: MIDINote detune: detune/16r100000000.
	in skip: 8.	"skip SMPTEFormat and SMPTEOffset"
	loopCount := in nextLittleEndianNumber: 4.	"number of loop records"
	in skip: 4.	"skip count of bytes of additional sampler data - implicit in chunk size"
	loopCount > 0 ifTrue: [
		loopCount > 1
			ifTrue: [ Transcript show: 'Wave file has multiple loop records; using first defined' ].
		in skip: 4.	"skip loop ID"
		loopType := in nextLittleEndianNumber: 4.
		loopStyle := #(looped pingpong backward) at: loopType + 1.
		loopStyle = #backward ifTrue: [
			Transcript show: 'backward loops are unsupported; using forward loop'; cr.
			loopStyle := #looped. ].
		loopStartBytes := in nextLittleEndianNumber: 4.	"byte offset"
		loopEndBytes := in nextLittleEndianNumber: 4.	"byte offset"
		loopFineTuning := in nextLittleEndianNumber: 4.	"16r80000000 = 1/2 sample length"
		loopStart := loopStartBytes // (bitsPerSample//8 * channelCount).
		loopEnd := loopEndBytes // (bitsPerSample//8 * channelCount).
		loopFineTuning = 0
			ifFalse: [ Transcript show: 'Ignoring loopFineTuning: ', loopFineTuning; cr. ].
		in skip: 4.	"skip loop play (repetition) count"
		].

	in skip: (chunkSize - (in position - chunkStart)).
! !


GUSPatchReader removeSelector: #readFrom:!
GUSPatchReader removeSelector: #reserved1!
GUSPatchReader removeSelector: #readFromStream:!
GUSPatchReader removeSelector: #reserved2!
GUSPatchReader removeSelector: #reserved3!
LoopedSampledSound removeSelector: #fromAIFFFileNamed:mergeIfStereo:!
LoopedSampledSound class removeSelector: #fromAIFFfileNamed:!
SoundStreamReader removeSelector: #readMergedStereoChannelDataFrom:!
SoundStreamReader removeSelector: #readInstrumentChunk:!
SoundStreamReader removeSelector: #skipData:!
SoundStreamReader removeSelector: #readCommonChunk:!
SoundStreamReader removeSelector: #readMarkerChunk:!
SoundStreamReader removeSelector: #readMultiChannelDataFrom:!
SoundStreamReader removeSelector: #readExtendedFloat!
SoundStreamReader removeSelector: #readStereoChannelDataFrom:!
SoundStreamReader removeSelector: #markers!
SoundStreamReader removeSelector: #readMonoChannelDataFrom:!
SoundStreamReader removeSelector: #readChunk:size:!
SoundStreamReader removeSelector: #pitchForKey:!
SoundStreamReader removeSelector: #readSamplesChunk:!
SoundStreamReader removeSelector: #soundAsLoopedSampledSound:!
SoundStreamReader removeSelector: #isPingPongLooped!
SoundStreamReader removeSelector: #readFromFile:!
SoundStreamReader removeSelector: #readFromFile:mergeIfStereo:skipDataChunk:!
AIFFFileReader removeSelector: #rightSamples!
AIFFFileReader removeSelector: #soundAsSampledOrMixedSound!
AIFFFileReader removeSelector: #isStereo!
AIFFFileReader removeSelector: #sound!
AIFFFileReader removeSelector: #bitsPerSample!
AIFFFileReader removeSelector: #pitch!
AIFFFileReader removeSelector: #samplingRate!
AIFFFileReader removeSelector: #frameCount!
AIFFFileReader removeSelector: #channelData!
AIFFFileReader removeSelector: #leftSamples!
AIFFFileReader removeSelector: #isLooped!
AIFFFileReader removeSelector: #pitchForKey:!
AIFFFileReader removeSelector: #soundAsLoopedSampledSound:!
AIFFFileReader removeSelector: #gain!
AIFFFileReader removeSelector: #isPingPongLooped!
AIFFFileReader removeSelector: #loopLength!
AIFFFileReader removeSelector: #channelCount!
AIFFFileReader removeSelector: #edit!
AIFFFileReader removeSelector: #readFromFile:!
AIFFFileReader removeSelector: #loopEnd!
AIFFFileReader removeSelector: #readFromFile:mergeIfStereo:skipDataChunk:!
WaveFileReader removeSelector: #convertBytesTo16BitSamples:mostSignificantByteFirst:!
WaveFileReader removeSelector: #readStereoChannelDataFrom:!
WaveFileReader removeSelector: #readMonoChannelDataFrom:!
WaveFileReader removeSelector: #readMergedStereoChannelDataFrom:!
WaveFileReader removeSelector: #uLawDecode:!
WaveFileReader removeSelector: #convert8bitSignedFrom:to16Bit:!
WaveFileReader removeSelector: #convert8bitSignedTo16Bit:!
WaveFileReader removeSelector: #uLawEncodeSample:!
WaveFileReader removeSelector: #readMultiChannelDataFrom:!
WaveFileReader removeSelector: #uLawDecodeTable!
WaveFileReader removeSelector: #uLawEncode:!
WaveFileReader removeSelector: #convert8bitUnsignedTo16Bit:!
WaveFileReader removeSelector: #readSamplesChunk:!


More information about the Squeak-dev mailing list