[squeak-dev] The Trunk: Sound-pre.65.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Dec 7 15:27:36 UTC 2018


Patrick Rein uploaded a new version of Sound to project The Trunk:
http://source.squeak.org/trunk/Sound-pre.65.mcz

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

Name: Sound-pre.65
Author: pre
Time: 7 December 2018, 4:27:31.425037 pm
UUID: ed53607e-fbea-4ed9-bc9e-9bad91b11372
Ancestors: Sound-pre.64

Categorizes uncategorized messages in the Sound package (1250 methods to go).

=============== Diff against Sound-pre.64 ===============

Item was changed:
+ ----- Method: AmbientEvent>>morph (in category 'accessing') -----
- ----- Method: AmbientEvent>>morph (in category 'as yet unclassified') -----
  morph 
  	^ morph!

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

Item was changed:
+ ----- Method: AmbientEvent>>occurAtTime:inScorePlayer:atIndex:inEventTrack:secsPerTick: (in category 'sound generation') -----
- ----- Method: AmbientEvent>>occurAtTime:inScorePlayer:atIndex:inEventTrack:secsPerTick: (in category 'as yet unclassified') -----
  occurAtTime: ticks inScorePlayer: player atIndex: index inEventTrack: track secsPerTick: secsPerTick
  	(target == nil or: [selector == nil]) ifTrue:
  		[morph ifNil: [^ self].
  		^ morph encounteredAtTime: ticks inScorePlayer: player atIndex: index
  				inEventTrack: track secsPerTick: secsPerTick].
  	target perform: selector withArguments: arguments!

Item was changed:
+ ----- Method: AmbientEvent>>target:selector:arguments: (in category 'accessing') -----
- ----- 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>>compressWith: (in category 'compressing') -----
- ----- Method: CompressedSoundData>>compressWith: (in category 'as yet unclassified') -----
  compressWith: codecClass
  
  	codecName == codecClass name asSymbol ifTrue: [^self].
  	^self asSound compressWith: codecClass!

Item was changed:
+ ----- Method: CompressedSoundData>>compressWith:atRate: (in category 'compressing') -----
- ----- Method: CompressedSoundData>>compressWith:atRate: (in category 'as yet unclassified') -----
  compressWith: codecClass atRate: aSamplingRate
  
  	(codecName == codecClass name asSymbol and: [samplingRate = aSamplingRate]) ifTrue: [^self].
  	^self asSound compressWith: codecClass atRate: aSamplingRate!

Item was changed:
+ ----- Method: CompressedSoundData>>withEToySound:samplingRate: (in category 'initialize-release') -----
- ----- 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: FMBassoonSound>>setPitch:dur:loudness: (in category 'initialization') -----
- ----- 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: MIDIFileReader class>>scoreFromFileNamed: (in category 'reading') -----
- ----- 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 'reading') -----
- ----- 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 'reading') -----
- ----- 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 class>>standardMIDIInstrumentNames (in category 'instruments') -----
- ----- Method: MIDIFileReader class>>standardMIDIInstrumentNames (in category 'as yet unclassified') -----
  standardMIDIInstrumentNames
  	"Answer an array of Standard MIDI instrument names."
  
  	^ #(
  		'Grand Piano'
  		'Bright Piano'
  		'Electric Grand Piano'
  		'Honky-tonk Piano'
  		'Electric Piano 1'
  		'Electric Piano 2'
  		'Harpsichord'
  		'Clavichord'
  		'Celesta'
  		'Glockenspiel'
  		'Music Box'
  		'Vibraphone'
  		'Marimba'
  		'Xylophone'
  		'Tubular Bells'
  		'Duclimer'
  		'Drawbar Organ'
  		'Percussive Organ'
  		'Rock Organ'
  		'Church Organ'
  		'Reed Organ'
  		'Accordion'
  		'Harmonica'
  		'Tango Accordion'
  		'Nylon Guitar'
  		'Steel Guitar'
  		'Electric Guitar 1'
  		'Electric Guitar 2'
  		'Electric Guitar 3'
  		'Overdrive Guitar'
  		'Distorted Guitar'
  		'Guitar Harmonics'
  		'Acoustic Bass'
  		'Electric Bass 1'
  		'Electric Bass 2'
  		'Fretless Bass'
  		'Slap Bass 1'
  		'Slap Bass 2'
  		'Synth Bass 1'
  		'Synth Bass 2'
  		'Violin'
  		'Viola'
  		'Cello'
  		'Contrabass'
  		'Tremolo Strings'
  		'Pizzicato Strings'
  		'Orchestral Harp'
  		'Timpani'
  		'String Ensemble 1'
  		'String Ensemble 2'
  		'Synth Strings 1'
  		'Synth Strings 2'
  		'Choir Ahhs'
  		'Choir Oohs'
  		'Synth Voice'
  		'Orchestra Hit'
  		'Trumpet'
  		'Trombone'
  		'Tuba'
  		'Muted Trumpet'
  		'French Horn'
  		'Brass Section'
  		'Synth Brass 1'
  		'Synth Brass 2'
  		'Soprano Sax'
  		'Alto Sax'
  		'Tenor Sax'
  		'Baritone Sax'
  		'Oboe'
  		'English Horn'
  		'Bassoon'
  		'Clarinet'
  		'Piccolo'
  		'Flute'
  		'Recorder'
  		'Pan Flute'
  		'Blown Bottle'
  		'Shakuhachi'
  		'Whistle'
  		'Ocarina'
  		'Lead 1 (square)'
  		'Lead 2 (sawtooth)'
  		'Lead 3 (calliope)'
  		'Lead 4 (chiff)'
  		'Lead 5 (charang)'
  		'Lead 6 (voice)'
  		'Lead 7 (fifths)'
  		'Lead 8 (bass+lead)'
  		'Pad 1 (new age)'
  		'Pad 2 (warm)'
  		'Pad 3 (polysynth)'
  		'Pad 4 (choir)'
  		'Pad 5 (bowed)'
  		'Pad 6 (metallic)'
  		'Pad 7 (halo)'
  		'Pad 8 (sweep)'
  		'FX 1 (rain)'
  		'FX 2 (soundtrack)'
  		'FX 3 (crystals)'
  		'FX 4 (atmosphere)'
  		'FX 5 (brightness)'
  		'FX 6 (goblins)'
  		'FX 7 (echoes)'
  		'FX 8 (sci-fi)'
  		'Sitar'
  		'Banjo'
  		'Shamisen'
  		'Koto'
  		'Kalimba'
  		'Bagpipe'
  		'Fiddle'
  		'Shanai'
  		'Tinkle Bell'
  		'Agogo'
  		'Steel Drum'
  		'Woodblock'
  		'Taiko Drum'
  		'Melodic Tom'
  		'Synth Drum'
  		'Reverse Cymbal'
  		'Guitar Fret Noise'
  		'Breath Noise'
  		'Seashore'
  		'Bird Tweet'
  		'Telephone Ring'
  		'Helicopter'
  		'Applause'
  		'Gunshot')
  !

Item was changed:
+ ----- Method: MIDISound>>play (in category 'playing') -----
- ----- Method: MIDISound>>play (in category 'as yet unclassified') -----
  play
  	"The base class ScorePlayer has two interfaces: a sound and a sound player. Choose the right interface depending on whether MIDI support is present."
  	
  	SoundService soundEnabled ifFalse: [^ self].
  	
  	SimpleMIDIPort useMIDIDeviceForOutput ifTrue: [
  		[self openMIDIPort]
  			on: Error
  			do: [
  				SimpleMIDIPort askForDefault.
  				[self openMIDIPort]
  					on: Error
  					do: [
  						self inform: 'Use of MIDI device is not working. Using custom synthesis.\Go to preferences to change again.' withCRs.
  						SimpleMIDIPort useMIDIDeviceForOutput: false]]].
  
  	self reset; resumePlaying.!

Item was changed:
+ ----- Method: MIDISynth>>channel: (in category 'channels') -----
- ----- Method: MIDISynth>>channel: (in category 'as yet unclassified') -----
  channel: i
  
  	^ channels at: i
  !

Item was changed:
+ ----- Method: MIDISynth>>closeMIDIPort (in category 'midi port') -----
- ----- Method: MIDISynth>>closeMIDIPort (in category 'as yet unclassified') -----
  closeMIDIPort
  
  	midiParser midiPort ifNil: [^ self].
  	midiParser midiPort close.
  	midiParser midiPort: nil.
  !

Item was changed:
+ ----- Method: MIDISynth>>initialize (in category 'initialize-release') -----
- ----- Method: MIDISynth>>initialize (in category 'as yet unclassified') -----
  initialize
  
  	super initialize.
  	midiParser := MIDIInputParser on: nil.
  	channels := (1 to: 16) collect: [:ch | MIDISynthChannel new initialize].
  !

Item was changed:
+ ----- Method: MIDISynth>>instrumentForChannel: (in category 'channels') -----
- ----- Method: MIDISynth>>instrumentForChannel: (in category 'as yet unclassified') -----
  instrumentForChannel: channelIndex
  
  	^ (channels at: channelIndex) instrument
  !

Item was changed:
+ ----- Method: MIDISynth>>instrumentForChannel:put: (in category 'channels') -----
- ----- Method: MIDISynth>>instrumentForChannel:put: (in category 'as yet unclassified') -----
  instrumentForChannel: channelIndex put: aSoundProto
  
  	(channels at: channelIndex) instrument: aSoundProto.
  !

Item was changed:
+ ----- Method: MIDISynth>>isOn (in category 'testing') -----
- ----- Method: MIDISynth>>isOn (in category 'as yet unclassified') -----
  isOn
  
  	^ process notNil
  !

Item was changed:
+ ----- Method: MIDISynth>>midiParser (in category 'accessing') -----
- ----- Method: MIDISynth>>midiParser (in category 'as yet unclassified') -----
  midiParser
  
  	^ midiParser
  !

Item was changed:
+ ----- Method: MIDISynth>>midiPort (in category 'midi port') -----
- ----- Method: MIDISynth>>midiPort (in category 'as yet unclassified') -----
  midiPort
  
  	^ midiParser midiPort
  !

Item was changed:
+ ----- Method: MIDISynth>>midiPort: (in category 'midi port') -----
- ----- Method: MIDISynth>>midiPort: (in category 'as yet unclassified') -----
  midiPort: aMIDIPortOrNil
  
  	midiParser midiPort: aMIDIPortOrNil.
  !

Item was changed:
+ ----- Method: MIDISynth>>midiTrackingLoop (in category 'tracking') -----
- ----- Method: MIDISynth>>midiTrackingLoop (in category 'as yet unclassified') -----
  midiTrackingLoop
  
  	midiParser clearBuffers.
  	
  	[self processMIDI ifFalse: [(Delay forMilliseconds: 5) wait]] repeat!

Item was changed:
+ ----- Method: MIDISynth>>mutedForChannel:put: (in category 'channels') -----
- ----- Method: MIDISynth>>mutedForChannel:put: (in category 'as yet unclassified') -----
  mutedForChannel: channelIndex put: aBoolean
  
  	^ (channels at: channelIndex) muted: aBoolean
  !

Item was changed:
+ ----- Method: MIDISynth>>panForChannel: (in category 'channels') -----
- ----- Method: MIDISynth>>panForChannel: (in category 'as yet unclassified') -----
  panForChannel: channelIndex
  
  	^ (channels at: channelIndex) pan
  !

Item was changed:
+ ----- Method: MIDISynth>>panForChannel:put: (in category 'channels') -----
- ----- Method: MIDISynth>>panForChannel:put: (in category 'as yet unclassified') -----
  panForChannel: channelIndex put: newPan
  
  	(channels at: channelIndex) pan: newPan.
  !

Item was changed:
+ ----- Method: MIDISynth>>processMIDI (in category 'private-tracking') -----
- ----- Method: MIDISynth>>processMIDI (in category 'as yet unclassified') -----
  processMIDI
  	"Process some MIDI commands. Answer true if any commands were processed."
  
  	| didSomething |
  	didSomething := false.
  	midiParser midiDo: [:item | | cmdByte byte1 chan cmd byte2 |
  		didSomething := true.
  		cmdByte := item at: 2.
  		byte1 := byte2 := nil.
  		item size > 2 ifTrue: [
  			byte1 := item at: 3.
  			item size > 3 ifTrue: [byte2 := item at: 4]].
  		cmdByte < 240
  			ifTrue: [  "channel message" 
  				cmd := cmdByte bitAnd: 2r11110000.
  				chan := (cmdByte bitAnd: 2r00001111) + 1.
  				(channels at: chan) doChannelCmd: cmd byte1: byte1 byte2: byte2]
  			ifFalse: [  "system message"
  				"process system messages here"
  			]].
  	^ didSomething
  !

Item was changed:
+ ----- Method: MIDISynth>>processMIDIUntilMouseDown (in category 'private-tracking') -----
- ----- Method: MIDISynth>>processMIDIUntilMouseDown (in category 'as yet unclassified') -----
  processMIDIUntilMouseDown
  	"Used for debugging. Do MIDI processing until the mouse is pressed."
  
  	midiParser clearBuffers.
  	[Sensor anyButtonPressed] whileFalse: [self processMIDI].
  !

Item was changed:
+ ----- Method: MIDISynth>>setAllChannelMasterVolumes: (in category 'channels') -----
- ----- 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 'tracking') -----
- ----- 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 'tracking') -----
- ----- Method: MIDISynth>>stopMIDITracking (in category 'as yet unclassified') -----
  stopMIDITracking
  
  	process ifNotNil: [
  		process terminate.
  		process := nil].
  	SoundPlayer shutDown: true; initialize.  "revert to normal buffer size"
  !

Item was changed:
+ ----- Method: MIDISynth>>volumeForChannel: (in category 'channels') -----
- ----- Method: MIDISynth>>volumeForChannel: (in category 'as yet unclassified') -----
  volumeForChannel: channelIndex
  
  	^  (channels at: channelIndex) masterVolume
  !

Item was changed:
+ ----- Method: MIDISynth>>volumeForChannel:put: (in category 'channels') -----
- ----- Method: MIDISynth>>volumeForChannel:put: (in category 'as yet unclassified') -----
  volumeForChannel: channelIndex put: newVolume
  
  	(channels at: channelIndex) masterVolume: newVolume.
  !

Item was changed:
+ ----- Method: PitchEnvelope>>centerPitch (in category 'accessing') -----
- ----- Method: PitchEnvelope>>centerPitch (in category 'as yet unclassified') -----
  centerPitch
  
  	^ centerPitch
  !

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

Item was changed:
+ ----- Method: PitchEnvelope>>updateSelector (in category 'accessing') -----
- ----- Method: PitchEnvelope>>updateSelector (in category 'as yet unclassified') -----
  updateSelector
  	"Needed by the envelope editor."
  
  	^ #pitch:
  !

Item was changed:
+ ----- Method: PitchEnvelope>>updateTargetAt: (in category 'applying') -----
- ----- 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: 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: SoundBuffer>>writeOnGZIPByteStream: (in category 'objects from disk') -----
- ----- Method: SoundBuffer>>writeOnGZIPByteStream: (in category 'as yet unclassified') -----
  writeOnGZIPByteStream: aStream 
  	
  	aStream nextPutAllWordArray: self!

Item was changed:
+ ----- Method: SoundPlayer>>startUp (in category 'system startup') -----
- ----- Method: SoundPlayer>>startUp (in category 'as yet unclassified') -----
  startUp
  	Preferences automaticPlatformSettings ifFalse: [^ self].
  
  	SoundPlayer soundQuickStart: SoundPlayer defaultQuickStartForPlatform.
  	SoundPlayer stopSoundWhenDone: SoundPlayer defaultStopSoundForPlatform.!

Item was changed:
+ ----- Method: TempoEvent>>isTempoEvent (in category 'classification') -----
- ----- Method: TempoEvent>>isTempoEvent (in category 'as yet unclassified') -----
  isTempoEvent
  
  	^ true
  !

Item was changed:
+ ----- Method: TempoEvent>>printOn: (in category 'printing') -----
- ----- Method: TempoEvent>>printOn: (in category 'as yet unclassified') -----
  printOn: aStream
  
  	aStream nextPut: $(.
  	time printOn: aStream.
  	aStream nextPutAll: ': tempo '.
  	aStream nextPutAll:  (120.0 * (500000.0 / tempo) printShowingMaxDecimalPlaces: 2).
  	aStream nextPut: $).
  !

Item was changed:
+ ----- Method: TempoEvent>>tempo (in category 'accessing') -----
- ----- Method: TempoEvent>>tempo (in category 'as yet unclassified') -----
  tempo
  
  	^ tempo
  !

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

Item was changed:
+ ----- Method: UnloadedSound class>>default (in category 'instruments') -----
- ----- 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 'private') -----
- ----- 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 'applying') -----
- ----- 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>>updateSelector (in category 'accessing') -----
- ----- Method: VolumeEnvelope>>updateSelector (in category 'as yet unclassified') -----
  updateSelector
  	"Needed by the envelope editor."
  
  	^ #volume:
  !

Item was changed:
+ ----- Method: VolumeEnvelope>>updateTargetAt: (in category 'applying') -----
- ----- 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 'accessing') -----
- ----- Method: VolumeEnvelope>>volume: (in category 'as yet unclassified') -----
  volume: aNumber
  	"Set the maximum volume of a volume-controlling envelope."
  
  	scale := aNumber asFloat.
  !



More information about the Squeak-dev mailing list