[Pkg] The Trunk: Sound-nice.12.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 27 02:53:06 UTC 2009


Nicolas Cellier uploaded a new version of Sound to project The Trunk:
http://source.squeak.org/trunk/Sound-nice.12.mcz

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

Name: Sound-nice.12
Author: nice
Time: 27 December 2009, 3:52:46 am
UUID: 8e21707d-049d-4d02-8d12-299ef0284291
Ancestors: Sound-nice.11

Cosmetic: move or remove a few temps inside closures

=============== Diff against Sound-nice.11 ===============

Item was changed:
  ----- Method: PianoRollScoreMorph>>addNotes (in category 'drawing') -----
  addNotes
  	"Recompute the set of morphs that should be visible at the current scroll position."
  
+ 	| visibleMorphs rightEdge topEdge rightEdgeTime |
- 	| visibleMorphs rightEdge topEdge trackColor i done n nLeft nTop nRight rightEdgeTime |
  	visibleMorphs := OrderedCollection new: 500.
  	rightEdge := self right - borderWidth.
  	rightEdgeTime := self timeForX: rightEdge.
  	topEdge := self top + borderWidth + 1.
  
  	"Add ambient morphs first (they will be front-most)"
  	score eventMorphsWithTimeDo:
  		[:m :t | m addMorphsTo: visibleMorphs pianoRoll: self eventTime: t
  					betweenTime: leftEdgeTime and: rightEdgeTime].
  
  	"Then add note morphs"
  	score tracks withIndexDo:
+ 		[:track :trackIndex | | done n i nRight nTop nLeft trackColor |
- 		[:track :trackIndex |
  		trackColor := colorForTrack at: trackIndex.
  		i := indexInTrack at: trackIndex.
  		done := scorePlayer mutedForTrack: trackIndex.
  		[done | (i > track size)] whileFalse: [
  			n := track at: i.
  			(n isNoteEvent and: [n midiKey >= lowestNote]) ifTrue: [
  				n time > rightEdgeTime
  					ifTrue: [done := true]
  					ifFalse: [
  						nLeft := self xForTime: n time.
  						nTop := (self yForMidiKey: n midiKey) - 1.
  						nTop > topEdge ifTrue: [
  							nRight := nLeft + (n duration * timeScale) truncated - 1.
  							visibleMorphs add:
  								((PianoRollNoteMorph
  									newBounds: (nLeft at nTop corner: nRight@(nTop + 3))
  									color: trackColor)
  									trackIndex: trackIndex indexInTrack: i)]]].
  			i := i + 1].
  			(selection notNil
  				and: [trackIndex = selection first
  				and: [i >= selection second and: [(indexInTrack at: trackIndex) <= selection third]]])
  				ifTrue: [visibleMorphs do:
  						[:vm | (vm isKindOf: PianoRollNoteMorph) ifTrue: [vm selectFrom: selection]]]].
  
  	"Add the cursor morph in front of all notes; height and position are set later."
  	cursor ifNil: [cursor := Morph newBounds: (self topLeft extent: 1 at 1) color: Color red].
  	visibleMorphs addFirst: cursor.
  
  	self changed.
  	self removeAllMorphs.
  	self addAllMorphs: visibleMorphs.
  !

Item was changed:
  ----- Method: StreamingMonoSound>>storeSunAudioOn:compressionType: (in category 'converting') -----
  storeSunAudioOn: aBinaryStream compressionType: compressionName
  	"Store myself on the given stream as a monophonic sound compressed with the given type of compression. The sampling rate is reduced to 22050 samples/second if it is higher."
  
+ 	| fmt inBufSize samplesPerFrame outCodec compressed outSamplingRate audioWriter |
- 	| fmt inBufSize samplesPerFrame outCodec compressed outSamplingRate audioWriter samplesRemaining inBuf outBuf counts byteCount |
  	self pause; reset.  "stop playing and return to beginning"
  
  	fmt := SunAudioFileWriter formatCodeForCompressionType: compressionName.
  	inBufSize := 64000.
  	samplesPerFrame := 1.
  	outCodec := SunAudioFileWriter codecForFormatCode: fmt.
  	outCodec ifNotNil: [
  		samplesPerFrame := outCodec samplesPerFrame.
  		inBufSize := inBufSize roundUpTo: (2 * samplesPerFrame).
  		compressed := ByteArray new:
  			(inBufSize // samplesPerFrame) * outCodec bytesPerEncodedFrame].
  	outSamplingRate := streamSamplingRate.
  	streamSamplingRate > 22050 ifTrue: [
  		streamSamplingRate = 44100 ifFalse: [self error: 'unexpected MP3 sampling rate'].
  		outSamplingRate := 22050].
  
  	"write audio header"
  	audioWriter := SunAudioFileWriter onStream: aBinaryStream.
  	audioWriter writeHeaderSamplingRate: outSamplingRate format: fmt.
  
  	"convert and write sound data"
  	'Storing audio...' displayProgressAt: Sensor cursorPoint
+ 		from: 0 to: totalSamples during: [:bar | | outBuf counts inBuf samplesRemaining byteCount |
- 		from: 0 to: totalSamples during: [:bar |
  			samplesRemaining := totalSamples.
  			[samplesRemaining > 0] whileTrue: [
  				bar value: totalSamples - samplesRemaining.
  				self loadBuffersForSampleCount: (inBufSize min: samplesRemaining).
  				inBuf := mixer sounds first samples.
  				outSamplingRate < streamSamplingRate
  					ifTrue: [outBuf := inBuf downSampledLowPassFiltering: true]
  					ifFalse: [outBuf := inBuf].
  				outCodec
  					ifNil: [audioWriter appendSamples: outBuf]
  					ifNotNil: [
  						counts := outCodec
  							encodeFrames: (outBuf size // samplesPerFrame)
  							from: outBuf at: 1
  							into: compressed at: 1.
  						byteCount := counts last.
  						byteCount = compressed size
  							ifTrue: [audioWriter appendBytes: compressed]
  							ifFalse: [audioWriter appendBytes: (compressed copyFrom: 1 to: byteCount)]].
  				samplesRemaining := samplesRemaining - inBuf monoSampleCount]].
  
  	"update audio header"
  	audioWriter updateHeaderDataSize.
  !

Item was changed:
  ----- Method: FFT>>plot:in: (in category 'testing') -----
  plot: samples in: rect
  	"Throw-away code just to check out a couple of examples"
+ 	| dx pen min max x |
- 	| min max x dx pen y |
  	Display fillWhite: rect; border: (rect expandBy: 2) width: 2.
  	min := 1.0e30.  max := -1.0e30.
  	samples do:
  		[:v |
  		min := min min: v.
  		max := max max: v].
  	pen := Pen new.  pen up.
  	x := rect left.
  	dx := rect width asFloat / samples size.
  	samples do:
+ 		[:v | | y |
- 		[:v |
  		y := (max-v) / (max-min) * rect height asFloat.
  		pen goto: x asInteger @ (rect top + y asInteger).
  		pen down.
  		x := x + dx].
  	max printString displayOn: Display at: (x+2) @ (rect top-9).
  	min printString displayOn: Display at: (x+2) @ (rect bottom - 9)!

Item was changed:
  ----- Method: SampledInstrument>>readSampleSetFrom: (in category 'other') -----
  readSampleSetFrom: dirName
  	"Answer a collection of sounds read from AIFF files in the given directory and sorted in ascending pitch order."
  
+ 	| all dir |
- 	| all dir fullName snd |
  	all := SortedCollection sortBlock: [:s1 :s2 | s1 pitch < s2 pitch].
  	dir := FileDirectory default on: dirName.
+ 	dir fileNames do: [:n | | fullName snd |
- 	dir fileNames do: [:n |
  		fullName := dir fullNameFor: n.
  		Utilities
  			informUser: 'Reading AIFF file ', n
  			during:
  				[snd := LoopedSampledSound new
  					fromAIFFFileNamed: fullName
  					mergeIfStereo: true].
  		all add: snd].
  	^ all asArray
  !

Item was changed:
  ----- Method: PianoRollScoreMorph>>mouseDown: (in category 'event handling') -----
  mouseDown: evt
  
+ 	| noteMorphs chordRect |
- 	| noteMorphs chordRect sound |
  	(self notesInRect: ((evt cursorPoint extent: 1 at 0) expandBy: 2 at 30)) isEmpty
  		ifTrue: ["If not near a note, then put up score edit menu"
  				^ self invokeScoreMenu: evt].
  
  	"Clicked near (but not on) a note, so play all notes at the cursor time"
  	noteMorphs := self notesInRect: ((evt cursorPoint extent: 1 at 0) expandBy: 0 at self height).
  	chordRect := (self innerBounds withLeft: evt cursorPoint x) withWidth: 1.
  	soundsPlayingMorph := Morph newBounds: chordRect color: Color green.
  	self addMorphBack: soundsPlayingMorph.
  	
  	soundsPlaying := IdentityDictionary new.
  	noteMorphs do:
+ 		[:m | | sound | sound := m soundOfDuration: 999.0.
- 		[:m | sound := m soundOfDuration: 999.0.
  		soundsPlaying at: m put: sound.
  		SoundPlayer resumePlaying: sound quickStart: false].
  
  !

Item was changed:
  ----- Method: SoundRecorder>>segmentsAbove:normalizedVolume: (in category 'trimming') -----
  segmentsAbove: threshold normalizedVolume: percentOfMaxVolume
  	"Break the current recording up into a sequence of sound segments separated by silences."
  
+ 	| dcOffset firstPlace endPlace resultBuf nFactor lastPlace segments gapSize minDur minLull soundSize restSize max min sum totalSamples |
- 	| max min sum totalSamples bufSize s dcOffset firstPlace endPlace resultBuf nFactor lastPlace segments gapSize minDur minLull soundSize restSize |
  	stereo ifTrue: [self error: 'stereo trimming is not yet supported'].
  	paused ifFalse: [self error: 'must stop recording before trimming'].
  	(recordedSound == nil or: [recordedSound sounds isEmpty]) ifTrue:[^ self].
  	"Reconstruct buffers so old trimming code will work"
  	recordedBuffers := recordedSound sounds collect: [:snd | snd samples].
  	soundSize := restSize := 0.
  
  	max := min := sum := totalSamples := 0.
+ 	recordedBuffers do: [:buf | | bufSize s |
- 	recordedBuffers do: [:buf |
  		bufSize := buf size.
  		totalSamples := totalSamples + buf size.
  		1 to: bufSize do: [:i |
  			s := buf at: i.
  			s > max ifTrue: [max := s].
  			s < min ifTrue: [min := s].
  			sum := sum + s]].
  	dcOffset := sum // totalSamples.
  
  	minDur := (samplingRate/20.0) asInteger.  " 1/20 second "
  	minLull := (samplingRate/4.0) asInteger.  " 1/2 second "
  	segments := SequentialSound new.
  	endPlace := self endPlace.
  	lastPlace := #(1 1).
  	[firstPlace := self scanForStartThreshold: threshold
  						dcOffset: dcOffset
  						minDur: minDur
  						startingAt: lastPlace.
  	firstPlace = endPlace]
  		whileFalse:
  		[firstPlace = lastPlace ifFalse:
  			["Add a silence equal to the gap size"
  			"Wasteful but simple way to get gap size..."
  			gapSize := (self copyFrom: lastPlace to: firstPlace
  						normalize: 1000 dcOffset: dcOffset) size - 2.
  			"... -2 makes up for overlap of one sample on either end"
  			segments add: (RestSound dur: gapSize asFloat / samplingRate).
  			restSize := restSize + gapSize.
  "Transcript cr; print: firstPlace; space; print: lastPlace; space; print: gapSize; space; show: 'gap'."
  			].
  		lastPlace := self scanForEndThreshold: threshold
  						dcOffset: dcOffset
  						minLull: minLull + minDur
  						startingAt: firstPlace.
  		"Allow room for lead time of next sound"
  		lastPlace := self place: lastPlace plus: minDur negated.
  		nFactor := self normalizeFactorFor: percentOfMaxVolume
  						min: min max: max dcOffset: dcOffset.
  		resultBuf := self copyFrom: firstPlace to: lastPlace
  						normalize: nFactor dcOffset: dcOffset.
  		soundSize := soundSize + resultBuf size.
  "Transcript cr; print: firstPlace; space; print: lastPlace; space; print: resultBuf size; space; show: 'sound'."
  		segments add: (codec == nil
  			ifTrue: [SampledSound new setSamples: resultBuf samplingRate: samplingRate]
  			ifFalse: [codec compressSound: (SampledSound new setSamples: resultBuf samplingRate: samplingRate)])].
  
  	"Final gap for consistency"
  	gapSize := (self copyFrom: lastPlace to: self endPlace
  				normalize: 1000 dcOffset: dcOffset) size - 1.
  	segments add: (RestSound dur: gapSize asFloat / samplingRate).
  	restSize := restSize + gapSize.
  	self inform: ((soundSize+restSize/samplingRate) roundTo: 0.1) printString , ' secs reduced to ' , ((soundSize/samplingRate) roundTo: 0.1) printString.
  	recordedBuffers := nil.
  	^ segments!

Item was changed:
  ----- Method: SampledInstrument>>readSampleSetInfoFrom: (in category 'other') -----
  readSampleSetInfoFrom: dirName
  	"MessageTally spyOn: [SampledInstrument new readSampleSetFrom: 'Tosh:Desktop Folder:AAA Squeak2.0 Beta:Organ Samples:Flute8'] timeToRun"
  
+ 	| all dir |
- 	| all dir fullName info |
  	all := OrderedCollection new.
  	dir := FileDirectory default on: dirName.
+ 	dir fileNames do: [:n | | info fullName |
- 	dir fileNames do: [:n |
  		fullName := dir fullNameFor: n.
  		info := AIFFFileReader new readFromFile: fullName
  			mergeIfStereo: false
  			skipDataChunk: true.
  		all add: n -> info].
  	^ all
  !

Item was changed:
  ----- Method: ScorePlayer>>turnOffActiveMIDINotesAt: (in category 'midi output') -----
  turnOffActiveMIDINotesAt: scoreTick
  	"Turn off any active MIDI notes that should be turned off at the given score tick."
  
+ 	| someNoteEnded |
- 	| evt someNoteEnded |
  	midiPort ifNil: [^ self].
  	someNoteEnded := false. 
+ 	activeMIDINotes do: [:pair | | evt |
- 	activeMIDINotes do: [:pair |
  		evt := pair first.
  		evt endTime <= scoreTick ifTrue: [
  			evt endNoteOnMidiPort: midiPort.
  			someNoteEnded := true]].
  
  	someNoteEnded ifTrue: [
  		activeMIDINotes := activeMIDINotes select: [:p | p first endTime > scoreTick]].
  !

Item was changed:
  ----- Method: SampledSound>>sonogramMorph:from:to:nPoints: (in category 'sound tracks') -----
  sonogramMorph: height from: start to: stop nPoints: nPoints
  	"FYI:  It is very cool that we can do this, but for sound tracks on a movie,
  	simple volume is easier to read, easier to scale, and way faster to compute.
  	Code preserved here just in case it makes a useful example."
  	"In an inspector of a samplesSound...
  		self currentWorld addMorph: (self sonogramMorph: 32 from: 1 to: 50000 nPoints: 256)
  	"
+ 	| fft sonogramMorph width |
- 	| fft sonogramMorph data width |
  	fft := FFT new: nPoints.
  	width := stop-start//nPoints.
  	sonogramMorph := Sonogram new
  			extent: width at height
  			minVal: 0.0
  			maxVal: 1.0
  			scrollDelta: width.
  	start to: stop-nPoints by: nPoints do:
+ 		[:i | | data |
- 		[:i |
  		data := fft transformDataFrom: samples startingAt: i.
  		data := data collect: [:v | v sqrt].  "square root compresses dynamic range"
  		data /= 200.0.
  		sonogramMorph plotColumn: data].
  	^ sonogramMorph
  	
  !

Item was changed:
  ----- Method: MIDISynthChannel>>adjustPitch: (in category 'other') -----
  adjustPitch: bend
  	"Handle a pitch-bend change."
  
+ 	| pitchAdj |
- 	| snd pitchAdj centerPitch |
  	pitchBend := bend.
  	pitchAdj := 2.0 raisedTo: (bend asFloat / 8192.0) / 6.0.
+ 	activeSounds copy do: [:entry | | snd centerPitch |
- 	activeSounds copy do: [:entry |
  		snd := entry at: 2.
  		centerPitch := entry at: 3.
  		snd pitch: pitchAdj * centerPitch.
  		snd internalizeModulationAndRatio].
  !

Item was changed:
  ----- Method: MIDISynthChannel>>newVolume: (in category 'other') -----
  newVolume: valueByte
  	"Set the channel volume to the level given by the given number in the range 0..127."
  
+ 	| newVolume |
- 	| snd newVolume |
  	channelVolume := valueByte asFloat / 127.0.
  	newVolume := masterVolume * channelVolume.
+ 	activeSounds do: [:entry | | snd |
- 	activeSounds do: [:entry |
  		snd := entry at: 2.
  		snd adjustVolumeTo: newVolume overMSecs: 10].
  !

Item was changed:
  ----- Method: AbstractSound class>>noteSequenceOn:from: (in category 'instance creation') -----
  noteSequenceOn: aSound from: anArray
  	"Build a note sequence (i.e., a SequentialSound) from the given array using the given sound as the instrument. Elements are either (pitch, duration, loudness) triples or (#rest duration) pairs.  Pitches can be given as names or as numbers."
+ 	| score |
- 	| score pitch |
  	score := SequentialSound new.
+ 	anArray do: [:el | | pitch |
- 	anArray do: [:el |
  		el size = 3
  			ifTrue: [
  				pitch := el at: 1.
  				pitch isNumber ifFalse: [pitch := self pitchForName: pitch].
  				score add: (
  					aSound
  						soundForPitch: pitch
  						dur: (el at: 2)
  						loudness: (el at: 3) / 1000.0)]
  			ifFalse: [
  				score add: (RestSound dur: (el at: 2))]].
  	^ score
  !

Item was changed:
  ----- Method: MIDIScore>>jitterStartAndEndTimesBy: (in category 'editing') -----
  jitterStartAndEndTimesBy: mSecs
  
+ 	| r range halfRange |
- 	| r range halfRange oldEnd newEnd newStart |
  	r := Random new.
  	range := 2.0 * mSecs.
  	halfRange := mSecs.
  	tracks do: [:t |
+ 		t do: [:e | | newEnd newStart oldEnd |
- 		t do: [:e |
  			e isNoteEvent ifTrue: [
  				oldEnd := e time + e duration.
  				newEnd := oldEnd + ((r next * range) asInteger - halfRange).
  				newStart := e time + ((r next * range) asInteger - halfRange).
  				e time: newStart.
  				e duration: (newEnd - newStart)]]].
  
  				!

Item was changed:
  ----- Method: AbstractSound class>>majorChordOn:from: (in category 'examples') -----
  majorChordOn: aSound from: aPitch
  	"FMSound majorChord play"
  
+ 	| score majorScale leadingRest pan |
- 	| score majorScale leadingRest pan note |
  	majorScale := self majorPitchesFrom: aPitch.
  	score := MixedSound new.
  	leadingRest := pan := 0.
+ 	#(1 3 5 8) do: [:noteIndex | | note |
- 	#(1 3 5 8) do: [:noteIndex |
  		note := aSound
  			soundForPitch: (majorScale at: noteIndex)
  			dur: 2.0 - leadingRest
  			loudness: 0.3.
  		score add: (RestSound dur: leadingRest), note pan: pan.
  		leadingRest := leadingRest + 0.2.
  		pan := pan + 0.3].
  	^ score
  !

Item was changed:
  ----- Method: AbstractSound class>>dial: (in category 'utilities') -----
  dial: aString
+ 	| s |
- 	| index lo hi m s |
  	"AbstractSound dial: '867-5309'" "ask for Jenny"
  
  	s := SequentialSound new.
+ 	aString do: [ :c | | lo m index hi |
- 	aString do: [ :c |
  		c = $,
  			ifTrue: [ s add: (FMSound new setPitch: 1 dur: 1 loudness: 0) ]
  			ifFalse: [
  				(index := ('123A456B789C*0#D' indexOf: c)) > 0
  					ifTrue: [
  						lo := #(697 770 852 941) at: (index - 1 // 4 + 1).
  						hi := #(1209 1336 1477 1633) at: (index - 1 \\ 4 + 1).
  						m := MixedSound new.
  						m add: (FMSound new setPitch: lo dur: 0.15 loudness: 0.5).
  						m add: (FMSound new setPitch: hi dur: 0.15 loudness: 0.5).
  						s add: m.
  						s add: (FMSound new setPitch: 1 dur: 0.05 loudness: 0)]]].
  	^ s play.
  
  !

Item was changed:
  ----- Method: MIDISynthChannel>>keyUp:vel: (in category 'midi dispatching') -----
  keyUp: key vel: vel
  	"Handle a key up event."
  
+ 	
+ 	activeSounds copy do: [:entry | | snd |
- 	| snd |
- 	activeSounds copy do: [:entry |
  		(entry at: 1) = key ifTrue: [
  			snd := entry at: 2.
  			snd stopGracefully.
  			activeSounds remove: entry]].
  !

Item was changed:
  ----- Method: MIDIFileReader>>startNote:vel:chan:at: (in category 'track reading') -----
  startNote: midiKey vel: vel chan: chan at: startTicks
  	"Record the beginning of a note."
  	"Details: Some MIDI scores have missing note-off events, causing a note-on to be received for a (key, channel) that is already sounding. If the previous note is suspiciously long, truncate it."
  
+ 	| noteOnEvent newActiveEvents |
- 	| newActiveEvents dur noteOnEvent |
  	newActiveEvents := nil.
+ 	activeEvents do: [:e | | dur |
- 	activeEvents do: [:e |
  		((e midiKey = midiKey) and: [e channel = chan]) ifTrue: [
  			"turn off key already sounding"
  			dur := startTicks - e time.
  			dur > maxNoteTicks ifTrue: [dur := ticksPerQuarter].  "truncate"
  			e duration: dur.
  			newActiveEvents ifNil: [newActiveEvents := activeEvents copy].
  			newActiveEvents remove: e ifAbsent: []]].
  	newActiveEvents ifNotNil: [activeEvents := newActiveEvents].
  
  	noteOnEvent := NoteEvent new key: midiKey velocity: vel channel: chan.
  	noteOnEvent time: startTicks.
  	track add: noteOnEvent.
  	activeEvents add: noteOnEvent.
  !

Item was changed:
  ----- Method: SoundPlayer class>>startPlayingImmediately: (in category 'private') -----
  startPlayingImmediately: aSound
  	"Private!! Start playing the given sound as soon as possible by mixing it into the sound output buffers of the underlying sound driver."
  
+ 	| totalSamples buf |
- 	| totalSamples buf n leftover src rest |
  	"first, fill a double-size buffer with samples"
  	"Note: The code below assumes that totalSamples contains two
  	 buffers worth of samples, and the insertSamples primitive is
  	 expected to consume at least one buffer's worth of these
  	 samples. The remaining samples are guaranteed to fit into
  	 a single buffer."
  	totalSamples := Buffer stereoSampleCount * 2.  "two buffer's worth"
  	buf := SoundBuffer newStereoSampleCount: totalSamples.
  	aSound playSampleCount: totalSamples into: buf startingAt: 1.
  	ReverbState == nil ifFalse: [
  		ReverbState applyReverbTo: buf startingAt: 1 count: totalSamples].
  
+ 	PlayerSemaphore critical: [ | n src leftover rest |
- 	PlayerSemaphore critical: [
  		"insert as many samples as possible into the sound driver's buffers"
  		n := self primSoundInsertSamples: totalSamples
  			from: buf
  			samplesOfLeadTime: 1024.
  		n > 0 ifTrue:[
  			leftover := totalSamples - n.
  
  			"copy the remainder of buf into Buffer"
  			"Note: the following loop iterates over 16-bit words, not two-word stereo slices"
  			"assert: 0 < leftover <= Buffer stereoSampleCount"
  			src := 2 * n.
  			1 to: 2 * leftover do:
  				[:dst | Buffer at: dst put: (buf at: (src := src + 1))].
  
  			"generate enough additional samples to finish filling Buffer"
  			rest := Buffer stereoSampleCount - leftover.
  			aSound playSampleCount: rest into: Buffer startingAt: leftover + 1.
  			ReverbState == nil ifFalse: [
  				ReverbState applyReverbTo: Buffer startingAt: leftover + 1 count: rest].
  
  			"record the fact that this sound has already been played into Buffer so that we don't process it again this time around"
  			SoundJustStarted := aSound.
  		] ifFalse:[
  			"quick start failed; reset the sound so we start over"
  			aSound reset.
  		].
  		ActiveSounds add: aSound].
  !

Item was changed:
  ----- Method: SampledSound>>volumeForm:from:to:nSamplesPerPixel: (in category 'sound tracks') -----
  volumeForm: height from: start to: stop nSamplesPerPixel: nPerPixel
  	"Note: nPerPixel can be Integer or Float for pixel-perfect alignment."
  	"In an inspector of a samplesSound...
  		self currentWorld addMorph: (ImageMorph new image:
  			(self volumeForm: 32 from: 1 to: samples size nSamplesPerPixel: 225))
  	"
+ 	| volPlot width max |
- 	| volPlot width sample min max vol |
  	width := stop-start//nPerPixel.
  	volPlot := Form extent: width at height.
  	(start max: 1) to: (stop min: samples size)-nPerPixel by: nPerPixel do:
+ 		[:i | | sample min vol | min:= max:= 0.
- 		[:i | min:= max:= 0.
  		i asInteger to: (i+nPerPixel-1) asInteger by: 4 do:  "by: 4 makes it faster yet looks the same"
  			[:j | sample := samples at: j.
  			sample < min ifTrue: [min := sample].
  			sample > max ifTrue: [max := sample]].
  		vol := (max - min) * height // 65536.
  		volPlot fillBlack: ((i-start//nPerPixel) @ (height-vol//2) extent: 1@(vol+1))].
  	^ volPlot
  	
  !

Item was changed:
  ----- Method: PianoRollScoreMorph>>mouseMove: (in category 'event handling') -----
  mouseMove: evt
  
+ 	| noteMorphs chordRect |
- 	| noteMorphs chordRect sound |
  	soundsPlaying ifNil: [^ self].
  	self autoScrollForX: evt cursorPoint x.
  
  	"Play all notes at the cursor time"
  	noteMorphs := self notesInRect: ((evt cursorPoint extent: 1 at 0) expandBy: 0 at self height).
  	chordRect := (self innerBounds withLeft: evt cursorPoint x) withWidth: 1.
  	soundsPlayingMorph delete.
  	soundsPlayingMorph := Morph newBounds: chordRect color: Color green.
  	self addMorphBack: soundsPlayingMorph.
  	
  	noteMorphs do:
+ 		[:m | | sound |  "Add any new sounds"
- 		[:m |  "Add any new sounds"
  		(soundsPlaying includesKey: m)
  			ifFalse: [sound := m soundOfDuration: 999.0.
  					soundsPlaying at: m put: sound.
  					SoundPlayer resumePlaying: sound quickStart: false]].
  	soundsPlaying keys do:
  		[:m |  "Remove any sounds no longer in selection."
  		(noteMorphs includes: m)
  			ifFalse: [(soundsPlaying at: m) stopGracefully.
  					soundsPlaying removeKey: m]].
  
  !

Item was changed:
  ----- Method: PianoRollScoreMorph>>updateLowestNote (in category 'initialization') -----
  updateLowestNote
  	"find the actual lowest note in the score"
  
+ 	
- 	| n |
  	lowestNote := 128 - (self innerBounds height // 3).
+ 	score tracks do: [:track | | n |
- 	score tracks do: [:track |
  		1 to: track size do: [:i |
  			n := track at: i.
  			(n isNoteEvent and: [n midiKey < lowestNote])
  				ifTrue: [lowestNote := n midiKey - 4]]].
  !

Item was changed:
  ----- Method: SoundRecorder>>trim:normalizedVolume: (in category 'trimming') -----
  trim: threshold normalizedVolume: percentOfMaxVolume
  	"Remove the leading and trailing parts of this recording that are below the given threshold. Remove any DC offset and scale the recording so that its peaks are the given percent of the maximum volume."
  
+ 	| dcOffset startPlace endPlace resultBuf nFactor max min sum totalSamples |
- 	| max min sum totalSamples bufSize s dcOffset startPlace endPlace resultBuf nFactor |
  	stereo ifTrue: [self error: 'stereo trimming is not yet supported'].
  	paused ifFalse: [self error: 'must stop recording before trimming'].
  	recordedBuffers := recordedSound sounds collect: [:snd | snd samples].
  	recordedBuffers isEmpty ifTrue: [^ self].
  
  	max := min := sum := totalSamples := 0.
+ 	recordedBuffers do: [:buf | | bufSize s |
- 	recordedBuffers do: [:buf |
  		bufSize := buf size.
  		totalSamples := totalSamples + buf size.
  		1 to: bufSize do: [:i |
  			s := buf at: i.
  			s > max ifTrue: [max := s].
  			s < min ifTrue: [min := s].
  			sum := sum + s]].
  	dcOffset := sum // totalSamples.
  
  	"a place is an array of <buffer index><index of sample in buffer>"
  	startPlace := self scanForStartThreshold: threshold
  					dcOffset: dcOffset
  					minDur: (samplingRate/60.0) asInteger "at least 1/60th of a second"
  					startingAt: #(1 1).
  	startPlace = self endPlace ifTrue:
  		["no samples above threshold"
  		recordedBuffers := nil.  ^ self].
  
  	endPlace := self scanForEndThreshold: threshold
  					dcOffset: dcOffset
  					minLull: (samplingRate/5) asInteger
  					startingAt: startPlace.
  	nFactor := self normalizeFactorFor: percentOfMaxVolume min: min max: max dcOffset: dcOffset.
  	resultBuf := self copyFrom: startPlace to: endPlace normalize: nFactor dcOffset: dcOffset.
  	recordedSound := SampledSound new setSamples: resultBuf samplingRate: samplingRate.
  	recordedBuffers := nil
  !

Item was changed:
  ----- Method: MIDIFileReader>>endAllNotesAt: (in category 'track reading') -----
  endAllNotesAt: endTicks
  	"End of score; end any notes still sounding."
  	"Details: Some MIDI files have missing note-off events, resulting in very long notes. Truncate any such notes encountered."
  
+ 	
+ 	activeEvents do: [:e | | dur |
- 	| dur |
- 	activeEvents do: [:e |
  		dur := endTicks - e time.
  		dur > maxNoteTicks ifTrue: [dur := ticksPerQuarter].  "truncate long note"
  		e duration: dur].
  	activeEvents := activeEvents species new.
  !

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 |
- 	| bufSize stereoBuffer reverseBytes remaining out |
  	self reset.
  	bufSize := (2 * self samplingRate rounded) min: samplesToStore.  "two second buffer"
  	stereoBuffer := SoundBuffer newStereoSampleCount: bufSize.
  	reverseBytes := bigEndianFlag ~= (SmalltalkImage current isBigEndian).
  
  	'Storing audio...' displayProgressAt: Sensor cursorPoint
+ 		from: 0 to: samplesToStore during: [:bar | | remaining out |
- 		from: 0 to: samplesToStore during: [:bar |
  			remaining := samplesToStore.
  			[remaining > 0] whileTrue: [
  				bar value: samplesToStore - remaining.
  				stereoBuffer primFill: 0.  "clear the buffer"
  				self playSampleCount: (bufSize min: remaining) into: stereoBuffer startingAt: 1.
  				self isStereo
  					ifTrue: [out := stereoBuffer]
  					ifFalse: [out := 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: MIDISynth>>processMIDI (in category 'as yet unclassified') -----
  processMIDI
  	"Process some MIDI commands. Answer true if any commands were processed."
  
+ 	| didSomething |
- 	| didSomething cmdByte byte1 byte2 cmd chan |
  	didSomething := false.
+ 	midiParser midiDo: [:item | | cmdByte byte1 chan cmd byte2 |
- 	midiParser midiDo: [:item |
  		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
  !



More information about the Packages mailing list