[squeak-dev] The Inbox: Sound-HenrikSperreJohansen.28.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jan 21 19:11:31 UTC 2011


A new version of Sound was added to project The Inbox:
http://source.squeak.org/inbox/Sound-HenrikSperreJohansen.28.mcz

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

Name: Sound-HenrikSperreJohansen.28
Author: HenrikSperreJohansen
Time: 21 January 2011, 8:11:33.349 pm
UUID: 9292e731-70f3-674a-8e71-fc26c493d578
Ancestors: Sound-ul.26

Update to use pragma-based sound preferences

=============== Diff against Sound-ul.26 ===============

Item was changed:
  ----- Method: BaseSoundSystem>>beep (in category 'playing') -----
  beep
  	"There is sound support, so we use the default
  	sampled sound for a beep."
  
+ 	SoundService soundEnabled ifTrue: [
- 	Preferences soundsEnabled ifTrue: [
  		SampledSound beep]!

Item was changed:
  ----- Method: BaseSoundSystem>>playSampledSound:rate: (in category 'playing') -----
  playSampledSound: samples rate: rate
  
+ 	SoundService soundEnabled ifTrue: [
- 	Preferences soundsEnabled ifTrue: [
  		(SampledSound samples: samples samplingRate: rate) play]!

Item was changed:
  ----- Method: BaseSoundSystem>>playSoundNamed: (in category 'playing') -----
  playSoundNamed: soundName
  	"There is sound support, so we play the given sound."
  
+ 	SoundService soundEnabled ifTrue: [
- 	Preferences soundsEnabled ifTrue: [
  		SampledSound playSoundNamed: soundName asString]!

Item was changed:
  ----- Method: BaseSoundSystem>>playSoundNamed:ifAbsentReadFrom: (in category 'playing') -----
  playSoundNamed: soundName ifAbsentReadFrom: aifFileName
  
+ 	SoundService soundEnabled ifTrue: [
- 	Preferences soundsEnabled ifTrue: [
  		(SampledSound soundNames includes: soundName) ifFalse: [
  			(FileDirectory default fileExists: aifFileName) ifTrue: [
  				SampledSound
  					addLibrarySoundNamed: soundName
  					fromAIFFfileNamed: aifFileName]].
  		(SampledSound soundNames includes: soundName) ifTrue: [
  			SampledSound playSoundNamed: soundName]]!

Item was changed:
  ----- Method: BaseSoundSystem>>playSoundNamedOrBeep: (in category 'playing') -----
  playSoundNamedOrBeep: soundName
  	"There is sound support, so we play the given sound
  	instead of beeping."
  
+ 	SoundService soundEnabled ifTrue: [
- 	Preferences soundsEnabled ifTrue: [
  		^self playSoundNamed: soundName]!

Item was changed:
  Object subclass: #SoundPlayer
  	instanceVariableNames: ''
+ 	classVariableNames: 'ActiveSounds Buffer BufferIndex BufferMSecs LastBuffer PlayerProcess PlayerSemaphore ReadyForBuffer ReverbState SamplingRate SoundJustStarted SoundSupported SoundsShouldStartQuick SoundsStopWhenDone Stereo UseReadySemaphore UseReverb'
- 	classVariableNames: 'ActiveSounds Buffer BufferIndex BufferMSecs LastBuffer PlayerProcess PlayerSemaphore ReadyForBuffer ReverbState SamplingRate SoundJustStarted SoundSupported Stereo UseReadySemaphore UseReverb'
  	poolDictionaries: ''
  	category: 'Sound-Synthesis'!

Item was changed:
  ----- Method: SoundPlayer class>>canStartPlayer (in category 'playing') -----
  canStartPlayer
  	"Some platforms do no support simultaneous record and play. If this is one of those platforms, return false if there is a running SoundRecorder."
  
+ 	^SoundRecorder canRecordWhilePlaying 
+ 		or: [	SoundRecorder anyActive not] 
+ 	
- 	Preferences canRecordWhilePlaying ifTrue: [^ true].
- 	SoundRecorder anyActive ifTrue:[^false].
- 	^ true
  !

Item was added:
+ ----- Method: SoundPlayer class>>defaultQuickStartForPlatform (in category 'preferences') -----
+ defaultQuickStartForPlatform
+ 
+ 	^ Smalltalk os platformName = 'Mac OS'.
+ !

Item was added:
+ ----- Method: SoundPlayer class>>defaultStopSoundForPlatform (in category 'preferences') -----
+ defaultStopSoundForPlatform
+ 
+ 	^(Smalltalk os platformName = 'Mac OS') not
+ !

Item was changed:
  ----- Method: SoundPlayer class>>playLoop (in category 'player process') -----
  playLoop
  	"The sound player process loop."
  
  	| bytesPerSlice count willStop mayStop |
+ 	mayStop := self stopSoundWhenDone.
- 	mayStop := Preferences soundStopWhenDone.
  	bytesPerSlice := Stereo ifTrue: [4] ifFalse: [2].
  	[true] whileTrue: [
  		[(count := self primSoundAvailableBytes // bytesPerSlice) > 100]
  			whileFalse: [ReadyForBuffer wait].
  
  		count := count min: Buffer stereoSampleCount.
  		PlayerSemaphore critical: [
  			ActiveSounds := ActiveSounds select: [:snd | snd samplesRemaining > 0].
  			ActiveSounds do: [:snd |
  				snd ~~ SoundJustStarted ifTrue: [
  					snd playSampleCount: count into: Buffer startingAt: 1]].
  			ReverbState == nil ifFalse: [
  				ReverbState applyReverbTo: Buffer startingAt: 1 count: count].
  			self primSoundPlaySamples: count from: Buffer startingAt: 1.
  			willStop := mayStop and:[
  						(ActiveSounds size = 0) and:[
  							self isAllSilence: Buffer size: count]].
  			LastBuffer ifNotNil:[
  				LastBuffer replaceFrom: 1 to: LastBuffer size with: Buffer startingAt: 1.
  			].
  			willStop
  				ifTrue:[self shutDown. PlayerProcess := nil]
  				ifFalse:[Buffer primFill: 0].
  			SoundJustStarted := nil].
  		willStop ifTrue:[^self].
  	].
  !

Item was changed:
  ----- Method: SoundPlayer class>>resumePlaying:quickStart: (in category 'playing') -----
  resumePlaying: aSound quickStart: quickStart
  	"Start playing the given sound without resetting it; it will resume playing from where it last stopped. If quickStart is true, then try to start playing the given sound immediately."
  
  	| doQuickStart |
+ 	SoundService soundEnabled ifFalse: [^ self].
- 	Preferences soundsEnabled ifFalse: [^ self].
  	doQuickStart := quickStart.
+ 	self soundQuickStart ifFalse: [doQuickStart := false].
- 	Preferences soundQuickStart ifFalse: [doQuickStart := false].
  	PlayerProcess == nil ifTrue: [
  		self canStartPlayer ifFalse: [^ self].
  		^self startUpWithSound: aSound].
  
  	PlayerSemaphore critical: [
  		(ActiveSounds includes: aSound)
  			ifTrue: [doQuickStart := false]
  			ifFalse: [
  				doQuickStart ifFalse: [ActiveSounds add: aSound]]].
  
  	"quick-start the given sound, unless the sound player has just started"
  	doQuickStart ifTrue: [self startPlayingImmediately: aSound].
  !

Item was added:
+ ----- Method: SoundPlayer class>>soundQuickStart (in category 'preferences') -----
+ soundQuickStart
+ 		<preference: 'Quickstart Sounds'
+ 		category: 'media'
+ 		description: 'If true, attempt to start playing sounds using option "quick start"'
+ 		type: #Boolean>
+ 	
+ 	^SoundsShouldStartQuick ifNil: [self defaultQuickStartForPlatform]!

Item was added:
+ ----- Method: SoundPlayer class>>soundQuickStart: (in category 'preferences') -----
+ soundQuickStart: aBoolean
+ 
+ 	
+ 	SoundsShouldStartQuick := aBoolean!

Item was added:
+ ----- Method: SoundPlayer class>>stopSoundWhenDone (in category 'preferences') -----
+ stopSoundWhenDone
+ 		<preference: 'Stop sounds when done'
+ 		category: 'media'
+ 		description: 'If true, the sound player is shut down after playing finished'
+ 		type: #Boolean>
+ 	
+ 	^SoundsStopWhenDone ifNil: [self defaultStopSoundForPlatform]!

Item was added:
+ ----- Method: SoundPlayer class>>stopSoundWhenDone: (in category 'preferences') -----
+ stopSoundWhenDone: aBoolean
+ 		
+ 	SoundsStopWhenDone := aBoolean!

Item was changed:
  ----- Method: SoundRecorder class>>canRecordWhilePlaying (in category 'accessing') -----
  canRecordWhilePlaying
  	"Return true if this platform supports simultaneous sound recording and playback."
+ 	<preference: 'Record while playing'
+ 		category: 'media'
+ 		description: 'If true, recording and playing sounds concurrently is permitted (platform dependent)'
+ 		type: #Boolean>
+ 	^CanRecordWhilePlaying ifNil: [false].	
- 
- 	^Preferences canRecordWhilePlaying.		"now in preferences"
  !

Item was added:
+ ----- Method: SoundRecorder class>>canRecordWhilePlaying: (in category 'accessing') -----
+ canRecordWhilePlaying: aBoolean
+ 
+ 	CanRecordWhilePlaying := aBoolean
+ !

Item was changed:
  ----- Method: SoundRecorder class>>initialize (in category 'class initialization') -----
  initialize
  	"SoundRecorder initialize"
  	"Details: Some computers cannot record and playback sound at the same time. If CanRecordWhilePlaying is false, then the SoundRecorder alternates between recording and playing. If it is true, sounds can be playing during recording."
  
+ 	CanRecordWhilePlaying := false.
- 	CanRecordWhilePlaying := #ignoredNowInPreferences.
  !

Item was changed:
  ----- Method: SoundRecorder>>pause (in category 'recording controls') -----
  pause
  	"Go into pause mode. The record level continues to be updated, but no sound is recorded."
  
  	paused := true.
  	((currentBuffer ~~ nil) and: [nextIndex > 1])
  		ifTrue: [self emitPartialBuffer.
  				self allocateBuffer].
  
  	soundPlaying ifNotNil: [
  		soundPlaying pause.
  		soundPlaying := nil].
  	"Note: there can be problems if canRecordWhilePlaying is true. Recorders which only pause will inhibit other recorders from recording. I chose to make #stopPlaying unconditional in a subclass. The same might be appropriate here at the expense of making recorders resumable"
  
+ 	CanRecordWhilePlaying ifFalse: [self stopRecording].
- 	Preferences canRecordWhilePlaying ifFalse: [self stopRecording].
  !

Item was changed:
  ----- Method: SoundRecorder>>resumeRecording (in category 'recording controls') -----
  resumeRecording
  	"Continue recording from the point at which it was last paused."
  
  	self flag: #bob.
  	"Note: If canRecordWhilePlaying is true, then recordings may never get started (at least by this method). One possibility, used in a subclass, is to make the #startPlaying unconditional. Another would be to use #startPlaying instead of #resumePlaying in appropriate cases"
  
+ 	CanRecordWhilePlaying ifFalse: [self startRecording].
- 	Preferences canRecordWhilePlaying ifFalse: [self startRecording].
  	paused := false.
  !

Item was changed:
  ----- Method: SoundRecorder>>startRecording (in category 'recording controls') -----
  startRecording
  	"Turn of the sound input driver and start the recording process. Initially, recording is paused."
  
  	| semaIndex |
  	recordLevel ifNil: [recordLevel := 0.5].  "lazy initialization"
+ 	CanRecordWhilePlaying ifFalse: [SoundPlayer shutDown].
- 	Preferences canRecordWhilePlaying ifFalse: [SoundPlayer shutDown].
  	recordProcess ifNotNil: [self stopRecording].
  	paused := true.
  	meteringBuffer := SoundBuffer newMonoSampleCount: 1024.
  	meterLevel := 0.
  	self allocateBuffer.
  	bufferAvailableSema := Semaphore new.
  	semaIndex := Smalltalk registerExternalObject: bufferAvailableSema.
  	self primStartRecordingDesiredSampleRate: samplingRate asInteger
  		stereo: stereo
  		semaIndex: semaIndex.
  	RecorderActive := true.
  	samplingRate := self primGetActualRecordingSampleRate.
  	self primSetRecordLevel: (1000.0 * recordLevel) asInteger.
  	recordProcess := [self recordLoop] newProcess.
  	recordProcess priority: Processor userInterruptPriority.
  	recordProcess resume.
  !




More information about the Squeak-dev mailing list