[squeak-dev] The Trunk: Sound-fbs.36.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jul 25 07:51:16 UTC 2013


Frank Shearar uploaded a new version of Sound to project The Trunk:
http://source.squeak.org/trunk/Sound-fbs.36.mcz

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

Name: Sound-fbs.36
Author: fbs
Time: 25 July 2013, 8:50:56.412 am
UUID: 762fd943-db8f-4042-a39e-503409126b52
Ancestors: Sound-fbs.35

SmalltalkImage current -> Smalltalk.

=============== Diff against Sound-fbs.35 ===============

Item was changed:
  ----- Method: AbstractSound>>storeSampleCount:bigEndian:on: (in category 'file i/o') -----
  storeSampleCount: samplesToStore bigEndian: bigEndianFlag on: aBinaryStream
  	"Store my samples on the given stream at the current SoundPlayer sampling rate. If bigFlag is true, then each 16-bit sample is stored most-significant byte first (AIFF files), otherwise it is stored least-significant byte first (WAV files). If self isStereo is true, both channels are stored, creating a stereo file. Otherwise, only the left channel is stored, creating a mono file."
  
  	| bufSize stereoBuffer reverseBytes |
  	self reset.
  	bufSize := (2 * self samplingRate rounded) min: samplesToStore.  "two second buffer"
  	stereoBuffer := SoundBuffer newStereoSampleCount: bufSize.
+ 	reverseBytes := bigEndianFlag ~= (Smalltalk isBigEndian).
- 	reverseBytes := bigEndianFlag ~= (SmalltalkImage current isBigEndian).
  
  	'Storing audio...'
  		displayProgressFrom: 0 to: samplesToStore during: [:bar | | remaining out |
  			remaining := samplesToStore.
  			[remaining > 0] whileTrue: [
  				bar value: samplesToStore - remaining.
  				stereoBuffer primFill: 0.  "clear the buffer"
  				self playSampleCount: (bufSize min: remaining) into: stereoBuffer startingAt: 1.
  				out := self isStereo
  						ifTrue: [stereoBuffer]
  						ifFalse: [stereoBuffer extractLeftChannel].
  				reverseBytes ifTrue: [out reverseEndianness].
  				(aBinaryStream isKindOf: StandardFileStream)
  					ifTrue: [  "optimization for files: write sound buffer directly to file"
  						aBinaryStream next: (out size // 2) putAll: out startingAt: 1]  "size in words"
  					ifFalse: [  "for non-file streams:"
  						1 to: out monoSampleCount do: [:i | aBinaryStream int16: (out at: i)]].
  				remaining := remaining - bufSize]].
  !

Item was changed:
  ----- Method: LoopedSampledSound>>storeSampleCount:bigEndian:on: (in category 'file i/o') -----
  storeSampleCount: samplesToStore bigEndian: bigEndianFlag on: aBinaryStream
  	"Store my samples on the given stream at the current SoundPlayer sampling rate. If bigFlag is true, then each 16-bit sample is stored most-significant byte first (AIFF files), otherwise it is stored least-significant byte first (WAV files)."
  
  	| reverseBytes |
  	(self isStereo or: [self samplingRate ~= originalSamplingRate]) ifTrue: [
  		^ super storeSampleCount: samplesToStore bigEndian: bigEndianFlag on: aBinaryStream].
  
  	"optimization: if I'm not stereo and sampling rates match, just store my buffer"
+ 	reverseBytes := bigEndianFlag ~= Smalltalk  isBigEndian.
- 	reverseBytes := bigEndianFlag ~= SmalltalkImage current  isBigEndian.
  	reverseBytes ifTrue: [leftSamples reverseEndianness].
  	(aBinaryStream isKindOf: StandardFileStream)
  		ifTrue: [  "optimization for files: write sound buffer directly to file"
  			aBinaryStream next: (leftSamples size // 2) putAll: leftSamples startingAt: 1]  "size in words"
  		ifFalse: [  "for non-file streams:"
  			1 to: leftSamples monoSampleCount do: [:i | aBinaryStream int16: (leftSamples at: i)]].
  	reverseBytes ifTrue: [leftSamples reverseEndianness].  "restore to original endianness"
  !

Item was changed:
  ----- Method: SampledSound>>storeSampleCount:bigEndian:on: (in category 'file i/o') -----
  storeSampleCount: samplesToStore bigEndian: bigEndianFlag on: aBinaryStream
  	"Store my samples on the given stream at the current SoundPlayer sampling rate. If bigFlag is true, then each 16-bit sample is stored most-significant byte first (AIFF files), otherwise it is stored least-significant byte first (WAV files)."
  
  	| reverseBytes |
  	self samplingRate ~= originalSamplingRate ifTrue: [
  		^ super storeSampleCount: samplesToStore bigEndian: bigEndianFlag on: aBinaryStream].
  
  	"optimization: if sampling rates match, just store my buffer"
+ 	reverseBytes := bigEndianFlag ~= Smalltalk isBigEndian.
- 	reverseBytes := bigEndianFlag ~= SmalltalkImage current  isBigEndian.
  	reverseBytes ifTrue: [samples reverseEndianness].
  	(aBinaryStream isKindOf: StandardFileStream)
  		ifTrue: [  "optimization for files: write sound buffer directly to file"
  			aBinaryStream next: (samples size // 2) putAll: samples startingAt: 1]  "size in words"
  		ifFalse: [  "for non-file streams:"
  			1 to: samples monoSampleCount do: [:i | aBinaryStream int16: (samples at: i)]].
  	reverseBytes ifTrue: [samples reverseEndianness].  "restore to original endianness"
  !

Item was changed:
  ----- Method: SoundBuffer class>>startUpFrom: (in category 'objects from disk') -----
  startUpFrom: anImageSegment 
  	"In this case, do we need to swap word halves when reading this segment?"
  
+ 	^Smalltalk endianness ~~ anImageSegment endianness 
- 	^SmalltalkImage current endianness ~~ anImageSegment endianness 
  		ifTrue: [Message selector: #swapHalves	"will be run on each instance"]
  		ifFalse: [nil]!

Item was changed:
  ----- Method: SoundBuffer>>restoreEndianness (in category 'objects from disk') -----
  restoreEndianness
  	"This word object was just read in from a stream.  It was stored in Big Endian (Mac) format.  Swap each pair of bytes (16-bit word), if the current machine is Little Endian.
  	Why is this the right thing to do?  We are using memory as a byteStream.  High and low bytes are reversed in each 16-bit word, but the stream of words ascends through memory.  Different from a Bitmap."
  
  	| hack blt |
+ 	Smalltalk isLittleEndian ifTrue: [
- 	SmalltalkImage current  isLittleEndian ifTrue: [
  		"The implementation is a hack, but fast for large ranges"
  		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>>saveAsAIFFFileSamplingRate:on: (in category 'utilities') -----
  saveAsAIFFFileSamplingRate: rate on: aBinaryStream
  	"Store this mono sound buffer in AIFF file format with the given sampling rate on the given stream."
  
  	| sampleCount s swapBytes |
  	sampleCount := self monoSampleCount.
  	aBinaryStream nextPutAll: 'FORM' asByteArray.
  	aBinaryStream nextInt32Put: (2 * sampleCount) + ((7 * 4) + 18).
  	aBinaryStream nextPutAll: 'AIFF' asByteArray.
  	aBinaryStream nextPutAll: 'COMM' asByteArray.
  	aBinaryStream nextInt32Put: 18.
  	aBinaryStream nextNumber: 2 put: 1.  "channels"
  	aBinaryStream nextInt32Put: sampleCount.
  	aBinaryStream nextNumber: 2 put: 16.  "bits/sample"
  	self storeExtendedFloat: rate on: aBinaryStream.
  	aBinaryStream nextPutAll: 'SSND' asByteArray.
  	aBinaryStream nextInt32Put: (2 * sampleCount) + 8.
  	aBinaryStream nextInt32Put: 0.
  	aBinaryStream nextInt32Put: 0.
  
  	(aBinaryStream isKindOf: StandardFileStream) ifTrue: [
  		"optimization: write sound buffer directly to file"
+ 		swapBytes := Smalltalk isLittleEndian.
- 		swapBytes := SmalltalkImage current  isLittleEndian.
  		swapBytes ifTrue: [self reverseEndianness].  "make big endian"
  		aBinaryStream next: (self size // 2) putAll: self startingAt: 1.  "size in words"
  		swapBytes ifTrue: [self reverseEndianness].  "revert to little endian"
  		^ self].
  
  	1 to: sampleCount do: [:i |
  		s := self at: i.
  		aBinaryStream nextPut: ((s bitShift: -8) bitAnd: 16rFF).
  		aBinaryStream nextPut: (s bitAnd: 16rFF)].
  !

Item was changed:
  ----- Method: SunAudioFileWriter>>appendSamples: (in category 'other') -----
  appendSamples: aSoundBuffer
  	"Append the given SoundBuffer to my stream."
  
  	| swapBytes s |
  	(stream isKindOf: StandardFileStream) ifTrue: [
  		"optimization: write sound buffer directly to file"
+ 		swapBytes := Smalltalk isLittleEndian.
- 		swapBytes := SmalltalkImage current  isLittleEndian.
  		swapBytes ifTrue: [aSoundBuffer reverseEndianness].  "make big endian"
  		stream next: (aSoundBuffer size // 2) putAll: aSoundBuffer startingAt: 1.  "size in words"
  		swapBytes ifTrue: [aSoundBuffer reverseEndianness].  "revert to little endian"
  		^ self].
  
  	"for non-file streams:"
  	s := WriteStream on: (ByteArray new: 2 * aSoundBuffer monoSampleCount).
  	1 to: aSoundBuffer monoSampleCount do: [:i | s int16: (aSoundBuffer at: i)].
  	self appendBytes: s contents.
  !



More information about the Squeak-dev mailing list