[Pkg] The Trunk: Morphic-fbs.663.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jul 4 19:16:04 UTC 2013


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

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

Name: Morphic-fbs.663
Author: fbs
Time: 4 July 2013, 8:14:34.141 pm
UUID: 98da4c65-8e7c-7149-ab6a-f260c49c25c7
Ancestors: Morphic-fbs.662

Sound -/-> Morphic.

=============== Diff against Morphic-fbs.662 ===============

Item was changed:
  SystemOrganization addCategory: #'Morphic-Balloon'!
  SystemOrganization addCategory: #'Morphic-Basic'!
  SystemOrganization addCategory: #'Morphic-Basic-NewCurve'!
  SystemOrganization addCategory: #'Morphic-Borders'!
  SystemOrganization addCategory: #'Morphic-Collections-Arrayed'!
  SystemOrganization addCategory: #'Morphic-Demo'!
  SystemOrganization addCategory: #'Morphic-Events'!
  SystemOrganization addCategory: #'Morphic-Explorer'!
  SystemOrganization addCategory: #'Morphic-Kernel'!
  SystemOrganization addCategory: #'Morphic-Layouts'!
  SystemOrganization addCategory: #'Morphic-Menus'!
  SystemOrganization addCategory: #'Morphic-Menus-DockingBar'!
  SystemOrganization addCategory: #'Morphic-Models'!
  SystemOrganization addCategory: #'Morphic-Pluggable Widgets'!
+ SystemOrganization addCategory: #'Morphic-Sound'!
  SystemOrganization addCategory: #'Morphic-Support'!
  SystemOrganization addCategory: #'Morphic-Multilingual'!
  SystemOrganization addCategory: #'Morphic-Text Support'!
  SystemOrganization addCategory: #'Morphic-ToolBuilder'!
  SystemOrganization addCategory: #'Morphic-TrueType'!
  SystemOrganization addCategory: #'Morphic-Widgets'!
  SystemOrganization addCategory: #'Morphic-Windows'!
  SystemOrganization addCategory: #'Morphic-Worlds'!
+ SystemOrganization addCategory: #'Morphic-Sound-Synthesis'!

Item was added:
+ ----- Method: AbstractSound class>>updateScorePlayers (in category '*Morphic-Sounds-sound library-file in/out') -----
+ updateScorePlayers
+ 	| soundsBeingEdited |
+ 	"Force all ScorePlayers to update their instrument list from the sound library. This may done after loading, unloading, or replacing a sound to make all ScorePlayers feel the change."
+ 
+ 	ScorePlayer allSubInstancesDo:
+ 		[:p | p pause].
+ 	SoundPlayer shutDown.
+ 	soundsBeingEdited := EnvelopeEditorMorph allSubInstances collect: [:ed | ed soundBeingEdited].
+ 	ScorePlayerMorph allSubInstancesDo:
+ 		[:p | p updateInstrumentsFromLibraryExcept: soundsBeingEdited].
+ !

Item was added:
+ ----- Method: MIDIFileReader class>>playFileNamed: (in category '*Morphic-Sounds') -----
+ playFileNamed: fileName
+ 
+ 	ScorePlayerMorph
+ 		openOn: (self scoreFromFileNamed: fileName)
+ 		title: (FileDirectory localNameFor: fileName).
+ !

Item was added:
+ ----- Method: MIDIFileReader class>>playStream: (in category '*Morphic-Sounds') -----
+ playStream: binaryStream
+ 
+ 	ScorePlayerMorph
+ 		openOn: (self scoreFromStream: binaryStream)
+ 		title: 'a MIDI stream'
+ !

Item was added:
+ ----- Method: MIDIFileReader class>>playURLNamed: (in category '*Morphic-Sounds') -----
+ playURLNamed: urlString
+ 
+ 	| titleString |
+ 	titleString := urlString
+ 		copyFrom: (urlString findLast: [:c | c=$/]) + 1
+ 		to: urlString size.
+ 	ScorePlayerMorph
+ 		openOn: (self scoreFromURL: urlString)
+ 		title: titleString.
+ !

Item was added:
+ ----- Method: Morph>>addMorphsTo:pianoRoll:eventTime:betweenTime:and: (in category '*Morphic-Sound-piano rolls') -----
+ addMorphsTo: morphList pianoRoll: pianoRoll eventTime: t betweenTime: leftTime and: rightTime
+ 
+ 	"a hack to allow for abitrary morphs to be dropped into piano roll"
+ 	t > rightTime ifTrue: [^ self].  
+ 	t < leftTime ifTrue: [^ self].
+ 	morphList add: (self left: (pianoRoll xForTime: t)).
+ !

Item was added:
+ ----- Method: Morph>>encounteredAtTime:inScorePlayer:atIndex:inEventTrack:secsPerTick: (in category '*Morphic-Sound-piano rolls') -----
+ encounteredAtTime: ticks inScorePlayer: scorePlayer atIndex: index inEventTrack: track secsPerTick: secsPerTick
+ 
+ 	"a hack to allow for abitrary morphs to be dropped into piano roll"
+ 	self triggerActionFromPianoRoll.!

Item was added:
+ ----- Method: Morph>>justDroppedIntoPianoRoll:event: (in category '*Morphic-Sound-piano rolls') -----
+ justDroppedIntoPianoRoll: pianoRoll event: evt
+ 	
+ 	| ambientEvent startTimeInScore |
+ 	startTimeInScore := pianoRoll timeForX: self left.
+ 
+ 	ambientEvent := AmbientEvent new 
+ 		morph: self;
+ 		time: startTimeInScore.
+ 
+ 	pianoRoll score addAmbientEvent: ambientEvent.
+ 
+ 	"self endTime > pianoRoll scorePlayer durationInTicks ifTrue:
+ 		[pianoRoll scorePlayer updateDuration]"
+ !

Item was added:
+ ----- Method: Morph>>pauseFrom: (in category '*Morphic-Sound-piano rolls') -----
+ pauseFrom: scorePlayer
+ 
+ 	"subclasses should take five"!

Item was added:
+ ----- Method: Morph>>resetFrom: (in category '*Morphic-Sound-piano rolls') -----
+ resetFrom: scorePlayer
+ 
+ 	"subclasses should revert to their initial state"!

Item was added:
+ ----- Method: Morph>>resumeFrom: (in category '*Morphic-Sound-piano rolls') -----
+ resumeFrom: scorePlayer
+ 
+ 	"subclasses should continue from their current position"
+ 	"a hack to allow for abitrary morphs to be dropped into piano roll"!

Item was added:
+ ----- Method: Morph>>triggerActionFromPianoRoll (in category '*Morphic-Sound-piano rolls') -----
+ triggerActionFromPianoRoll
+ 
+ 	| evt |
+ 	"a hack to allow for abitrary morphs to be dropped into piano roll"
+ 	self world ifNil: [^self].
+ 	evt := MouseEvent new setType: nil position: self center buttons: 0 hand: self world activeHand.
+ 	self programmedMouseUp: evt for: self.
+ 
+ !

Item was added:
+ Morph subclass: #PianoRollNoteMorph
+ 	instanceVariableNames: 'trackIndex indexInTrack hitLoc editMode selected notePlaying'
+ 	classVariableNames: 'SoundPlaying'
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Sound'!
+ 
+ !PianoRollNoteMorph commentStamp: '<historical>' prior: 0!
+ A PianoRollNoteMorph is drawn as a simple mroph, but it carries the necessary state to locate its source sound event via its owner (a PianorRollScoreMorph) and the score therein.  Simple editing of pitch and time placement is provided here.!

Item was added:
+ ----- Method: PianoRollNoteMorph>>deselect (in category 'selecting') -----
+ deselect
+ 
+ 	selected ifFalse: [^ self].
+ 	self changed.
+ 	selected := false.
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>drawOn: (in category 'drawing') -----
+ drawOn: aCanvas
+ 
+ 	selected
+ 		ifTrue: [aCanvas frameAndFillRectangle: self fullBounds fillColor: color borderWidth: 1 borderColor: Color black]
+ 		ifFalse: [aCanvas fillRectangle: self bounds color: color].
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>editPitch: (in category 'editing') -----
+ editPitch: evt
+ 
+ 	| mk note |
+ 	mk := owner midiKeyForY: evt cursorPoint y.
+ 	note := (owner score tracks at: trackIndex) at: indexInTrack.
+ 	note midiKey = mk ifTrue: [^ self].
+ 	note midiKey: mk.
+ 	self playSound: (self soundOfDuration: 999.0).
+ 	self position: self position x @ ((owner yForMidiKey: mk) - 1)
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>fullBounds (in category 'layout') -----
+ fullBounds
+ 
+ 	selected
+ 		ifTrue: [^ bounds expandBy: 1]
+ 		ifFalse: [^ bounds]!

Item was added:
+ ----- Method: PianoRollNoteMorph>>gridToNextQuarter (in category 'editing') -----
+ gridToNextQuarter
+ 
+ 	owner score gridTrack: trackIndex toQuarter: 1 at: indexInTrack.
+ 	owner rebuildFromScore!

Item was added:
+ ----- Method: PianoRollNoteMorph>>gridToPrevQuarter (in category 'editing') -----
+ gridToPrevQuarter
+ 
+ 	owner score gridTrack: trackIndex toQuarter: -1 at: indexInTrack.
+ 	owner rebuildFromScore!

Item was added:
+ ----- Method: PianoRollNoteMorph>>handlesMouseDown: (in category 'event handling') -----
+ handlesMouseDown: evt
+ 
+ 	^ owner scorePlayer isPlaying not!

Item was added:
+ ----- Method: PianoRollNoteMorph>>indexInTrack (in category 'accessing') -----
+ indexInTrack
+ 
+ 	^ indexInTrack!

Item was added:
+ ----- Method: PianoRollNoteMorph>>invokeNoteMenu: (in category 'menu') -----
+ invokeNoteMenu: evt
+ 	"Invoke the note's edit menu."
+ 
+ 	| menu |
+ 	menu := MenuMorph new defaultTarget: self.
+ 	menu addList:
+ 		#(('grid to next quarter'		gridToNextQuarter)
+ 		('grid to prev quarter'		gridToPrevQuarter)).
+ 
+ 	menu popUpEvent: evt in: self world.
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>mouseDown: (in category 'event handling') -----
+ mouseDown: evt
+ 
+ 	hitLoc := evt cursorPoint.
+ 	editMode := nil.
+ 	owner submorphsDo:
+ 		[:m | (m isKindOf: PianoRollNoteMorph) ifTrue: [m deselect]].
+ 	selected := true.
+ 	self changed.
+ 	owner selection: (Array with: trackIndex with: indexInTrack with: indexInTrack).
+ 	self playSound!

Item was added:
+ ----- Method: PianoRollNoteMorph>>mouseMove: (in category 'event handling') -----
+ mouseMove: evt 
+ 	| delta offsetEvt |
+ 	editMode isNil 
+ 		ifTrue: 
+ 			["First movement determines edit mode"
+ 
+ 			((delta := evt cursorPoint - hitLoc) dist: 0 @ 0) <= 2 
+ 				ifTrue: [^self	"No significant movement yet."].
+ 			delta x abs > delta y abs 
+ 				ifTrue: 
+ 					[delta x > 0 
+ 						ifTrue: 
+ 							["Horizontal drag"
+ 
+ 							editMode := #selectNotes]
+ 						ifFalse: 
+ 							[self playSound: nil.
+ 							offsetEvt := evt copy setCursorPoint: evt cursorPoint + (20 @ 0).
+ 							self invokeNoteMenu: offsetEvt]]
+ 				ifFalse: [editMode := #editPitch	"Vertical drag"]].
+ 	editMode == #editPitch ifTrue: [self editPitch: evt].
+ 	editMode == #selectNotes ifTrue: [self selectNotes: evt]!

Item was added:
+ ----- Method: PianoRollNoteMorph>>mouseUp: (in category 'event handling') -----
+ mouseUp: evt
+ 
+ 	self playSound: nil!

Item was added:
+ ----- Method: PianoRollNoteMorph>>noteInScore (in category 'note playing') -----
+ noteInScore
+ 
+ 	^ (owner score tracks at: trackIndex) at: indexInTrack
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>noteOfDuration: (in category 'note playing') -----
+ noteOfDuration: duration
+ 
+ 	| note |
+ 	note := self noteInScore.
+ 	^ (owner scorePlayer instrumentForTrack: trackIndex)
+ 			soundForMidiKey: note midiKey
+ 			dur: duration
+ 			loudness: (note velocity asFloat / 127.0)
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>playSound (in category 'note playing') -----
+ playSound
+ 	"This STARTS a single long sound.  It must be stopped by playing another or nil."
+ 
+ 	^ self playSound: (self soundOfDuration: 999.0)!

Item was added:
+ ----- Method: PianoRollNoteMorph>>playSound: (in category 'note playing') -----
+ playSound: aSoundOrNil
+ 
+ 	SoundPlaying ifNotNil: [SoundPlaying stopGracefully].
+ 	SoundPlaying := aSoundOrNil.
+ 	SoundPlaying ifNotNil: [SoundPlaying play].!

Item was added:
+ ----- Method: PianoRollNoteMorph>>select (in category 'selecting') -----
+ select
+ 
+ 	selected ifTrue: [^ self].
+ 	selected := true.
+ 	self changed!

Item was added:
+ ----- Method: PianoRollNoteMorph>>selectFrom: (in category 'selecting') -----
+ selectFrom: selection 
+ 	(trackIndex = selection first and: 
+ 			[indexInTrack >= (selection second) and: [indexInTrack <= (selection third)]]) 
+ 		ifTrue: [selected ifFalse: [self select]]
+ 		ifFalse: [selected ifTrue: [self deselect]]!

Item was added:
+ ----- Method: PianoRollNoteMorph>>selectNotes: (in category 'selecting') -----
+ selectNotes: evt
+ 
+ 	| lastMorph oldEnd saveOwner |
+ 	saveOwner := owner.
+ 	(owner autoScrollForX: evt cursorPoint x) ifTrue:
+ 		["If scroll talkes place I will be deleted and my x-pos will become invalid."
+ 		owner := saveOwner.
+ 		bounds := bounds withLeft: (owner xForTime: self noteInScore time)].
+ 	oldEnd := owner selection last.
+ 	(owner notesInRect: (evt cursorPoint x @ owner top corner: owner bottomRight))
+ 		do: [:m | m trackIndex = trackIndex ifTrue: [m deselect]].
+ 	self select.  lastMorph := self.
+ 	(owner notesInRect: (self left @ owner top corner: evt cursorPoint x @ owner bottom))
+ 		do: [:m | m trackIndex = trackIndex ifTrue: [m select.  lastMorph := m]].
+ 	owner selection: (Array with: trackIndex with: indexInTrack with: lastMorph indexInTrack).
+ 	lastMorph indexInTrack ~= oldEnd ifTrue:
+ 		["Play last note as selection grows or shrinks"
+ 		owner ifNotNil: [lastMorph playSound]]
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>selected (in category 'selecting') -----
+ selected
+ 
+ 	^ selected!

Item was added:
+ ----- Method: PianoRollNoteMorph>>soundOfDuration: (in category 'note playing') -----
+ soundOfDuration: duration
+ 
+ 	| sound |
+ 	sound := MixedSound new.
+ 	sound add: (self noteOfDuration: duration)
+ 		pan: (owner scorePlayer panForTrack: trackIndex)
+ 		volume: owner scorePlayer overallVolume *
+ 				(owner scorePlayer volumeForTrack: trackIndex).
+ 	^ sound reset
+ !

Item was added:
+ ----- Method: PianoRollNoteMorph>>trackIndex (in category 'accessing') -----
+ trackIndex
+ 
+ 	^ trackIndex!

Item was added:
+ ----- Method: PianoRollNoteMorph>>trackIndex:indexInTrack: (in category 'initialization') -----
+ trackIndex: ti indexInTrack: i
+ 
+ 	trackIndex := ti.
+ 	indexInTrack := i.
+ 	selected := false!

Item was added:
+ ----- Method: ProjectViewMorph>>triggerActionFromPianoRoll (in category '*Morphic-Sound-piano rolls') -----
+ triggerActionFromPianoRoll
+ 
+ 	WorldState addDeferredUIMessage: [
+ 		project world setProperty: #letTheMusicPlay toValue: true.
+ 		self enter.
+ 	]!

Item was added:
+ ----- Method: SampledSound>>sonogramMorph:from:to:nPoints: (in category '*Morphic-Sounds-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 := 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 |
+ 		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 added:
+ AlignmentMorph subclass: #ScorePlayerMorph
+ 	instanceVariableNames: 'scorePlayer trackInstNames instrumentSelector scrollSlider'
+ 	classVariableNames: 'LastMIDIPort'
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Sound'!
+ 
+ !ScorePlayerMorph commentStamp: '<historical>' prior: 0!
+ A ScorePlayerMorph mediates between a score such as a MIDIScore, a PianoRollScoreMorph, and the actual SoundPlayer synthesizer.
+ 
+ It provides control over volume, tempo, instrumentation, and location in the score.!

Item was added:
+ ----- Method: ScorePlayerMorph class>>descriptionForPartsBin (in category 'parts bin') -----
+ descriptionForPartsBin
+ 	^ self partName: 	'ScorePlayer'
+ 		categories:		#('Multimedia')
+ 		documentation:	' Mediates between a score such as a MIDIScore, a PianoRollScoreMorph, and the actual SoundPlayer synthesizer'!

Item was added:
+ ----- Method: ScorePlayerMorph class>>fileReaderServicesForFile:suffix: (in category 'fileIn/Out') -----
+ fileReaderServicesForFile: fullName suffix: suffix
+ 
+ 	^(suffix = 'mid') | (suffix = '*') 
+ 		ifTrue: [ self services]
+ 		ifFalse: [#()]
+ !

Item was added:
+ ----- Method: ScorePlayerMorph class>>initialize (in category 'class initialization') -----
+ initialize
+ 
+ 	FileServices registerFileReader: self!

Item was added:
+ ----- Method: ScorePlayerMorph class>>onMIDIFileNamed: (in category 'system hookup') -----
+ onMIDIFileNamed: fileName
+ 	"Return a ScorePlayerMorph on the score from the MIDI file of the given name."
+ 
+ 	| score player |
+ 	score := MIDIFileReader scoreFromFileNamed: fileName	.
+ 	player := ScorePlayer onScore: score.
+ 	^ self new onScorePlayer: player title: fileName
+ !

Item was added:
+ ----- Method: ScorePlayerMorph class>>openOn:title: (in category 'system hookup') -----
+ openOn: aScore title: aString
+ 
+ 	| player |
+ 	player := ScorePlayer onScore: aScore.
+ 	(self new onScorePlayer: player title: aString) openInWorld.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph class>>playMidiFile: (in category 'class initialization') -----
+ playMidiFile: fullName
+ 	"Play a MIDI file."
+  
+ 	Smalltalk at: #MIDIFileReader ifPresent: [:midiReader |
+ 			| f score |
+ 			f := (FileStream oldFileNamed: fullName) binary.
+ 			score := (midiReader new readMIDIFrom: f) asScore.
+ 			f close.
+ 			self openOn: score title: (FileDirectory localNameFor: fullName)]
+ !

Item was added:
+ ----- Method: ScorePlayerMorph class>>servicePlayMidiFile (in category 'class initialization') -----
+ servicePlayMidiFile
+ 	"Answer a service for opening player on a midi file"
+ 
+ 	^ SimpleServiceEntry 
+ 		provider: self 
+ 		label: 'open in midi player'
+ 		selector: #playMidiFile:
+ 		description: 'open the midi-player tool on this file'
+ 		buttonLabel: 'open'!

Item was added:
+ ----- Method: ScorePlayerMorph class>>services (in category 'fileIn/Out') -----
+ services
+ 
+ 	^ Array with: self servicePlayMidiFile
+ 
+ 	!

Item was added:
+ ----- Method: ScorePlayerMorph class>>unload (in category 'initialize-release') -----
+ unload
+ 
+ 	FileServices unregisterFileReader: self !

Item was added:
+ ----- Method: ScorePlayerMorph>>atTrack:from:selectInstrument: (in category 'controls') -----
+ atTrack: trackIndex from: aPopUpChoice selectInstrument: selection 
+ 	| oldSnd name snd |
+ 	oldSnd := scorePlayer instrumentForTrack: trackIndex.
+ 	(selection beginsWith: 'edit ') 
+ 		ifTrue: 
+ 			[name := selection copyFrom: 6 to: selection size.
+ 			aPopUpChoice contentsClipped: name.
+ 			(oldSnd isKindOf: FMSound) | (oldSnd isKindOf: LoopedSampledSound) 
+ 				ifTrue: [EnvelopeEditorMorph openOn: oldSnd title: name].
+ 			(oldSnd isKindOf: SampledInstrument) 
+ 				ifTrue: [EnvelopeEditorMorph openOn: oldSnd allNotes first title: name].
+ 			^self].
+ 	snd := nil.
+ 	1 to: instrumentSelector size
+ 		do: 
+ 			[:i | 
+ 			(trackIndex ~= i and: [selection = (instrumentSelector at: i) contents]) 
+ 				ifTrue: [snd := scorePlayer instrumentForTrack: i]].	"use existing instrument prototype"
+ 	snd ifNil: 
+ 			[snd := (selection = 'clink' 
+ 				ifTrue: 
+ 					[(SampledSound samples: SampledSound coffeeCupClink
+ 								samplingRate: 11025) ]
+ 				ifFalse: [(AbstractSound soundNamed: selection)]) copy].
+ 	scorePlayer instrumentForTrack: trackIndex put: snd.
+ 	(instrumentSelector at: trackIndex) contentsClipped: selection!

Item was added:
+ ----- Method: ScorePlayerMorph>>closeMIDIPort (in category 'initialization') -----
+ closeMIDIPort
+ 
+ 	scorePlayer closeMIDIPort.
+ 	LastMIDIPort := nil.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>defaultBorderWidth (in category 'initialization') -----
+ defaultBorderWidth
+ 	"answer the default border width for the receiver"
+ 	^ 2!

Item was added:
+ ----- Method: ScorePlayerMorph>>defaultColor (in category 'initialization') -----
+ defaultColor
+ 	"answer the default color/fill style for the receiver"
+ 	^ Color veryLightGray!

Item was added:
+ ----- Method: ScorePlayerMorph>>initialize (in category 'initialization') -----
+ initialize
+ 	"initialize the state of the receiver"
+ 	super initialize.
+ 	""
+ 	self listDirection: #topToBottom;
+ 		 wrapCentering: #center;
+ 		 cellPositioning: #topCenter;
+ 		 hResizing: #shrinkWrap;
+ 		 vResizing: #shrinkWrap;
+ 		 layoutInset: 3;
+ 		 onScorePlayer: ScorePlayer new initialize title: ' ';
+ 		 extent: 20 @ 20 !

Item was added:
+ ----- Method: ScorePlayerMorph>>instrumentChoicesForTrack: (in category 'menu') -----
+ instrumentChoicesForTrack: trackIndex
+ 	| names |
+ 	names := AbstractSound soundNames asOrderedCollection.
+ 	names := names collect: [:n |
+ 		| inst |
+ 		inst := AbstractSound soundNamed: n.
+ 		(inst isKindOf: UnloadedSound)
+ 			ifTrue: [n, '(out)']
+ 			ifFalse: [n]].
+ 	names add: 'clink'.
+ 	names add: 'edit ', (instrumentSelector at: trackIndex) contents.
+ 	^ names asArray
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>invokeMenu (in category 'menu') -----
+ invokeMenu
+ 	"Invoke a menu of additonal functions for this ScorePlayer."
+ 
+ 	| aMenu |
+ 	aMenu := MenuMorph new defaultTarget: self.
+ 	aMenu add: 'open a MIDI file' translated action: #openMIDIFile.
+ 	aMenu addList: {
+ 		#-.
+ 		{'save as AIFF file' translated.	#saveAsAIFF}.
+ 		{'save as WAV file' translated.		#saveAsWAV}.
+ 		{'save as Sun AU file' translated.	#saveAsSunAudio}.
+ 		#-}.
+ 	aMenu add: 'reload instruments' translated target: AbstractSound selector: #updateScorePlayers.
+ 	aMenu addLine.
+ 	scorePlayer midiPort
+ 		ifNil: [
+ 			aMenu add: 'play via MIDI' translated action: #openMIDIPort]
+ 		ifNotNil: [
+ 			aMenu add: 'play via built in synth' translated action: #closeMIDIPort.
+ 			aMenu add: 'new MIDI controller' translated action: #makeMIDIController:].
+ 	aMenu addLine.
+ 	aMenu add: 'make a pause marker' translated action: #makeAPauseEvent:.
+ 
+ 	aMenu popUpInWorld: self world.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>makeAPauseEvent: (in category 'menu') -----
+ makeAPauseEvent: evt
+ 
+ 	| newWidget |
+ 
+ 	newWidget := AlignmentMorph newRow.
+ 	newWidget 
+ 		color: Color orange; 
+ 		borderWidth: 0; 
+ 		layoutInset: 0;
+ 		hResizing: #shrinkWrap; 
+ 		vResizing: #shrinkWrap; 
+ 		extent: 5 at 5;
+ 		addMorph: (StringMorph contents: '[pause]' translated) lock;
+ 		addMouseUpActionWith: (
+ 			MessageSend receiver: self selector: #showResumeButtonInTheWorld
+ 		).
+ 
+ 	evt hand attachMorph: newWidget.!

Item was added:
+ ----- Method: ScorePlayerMorph>>makeControls (in category 'layout') -----
+ makeControls
+ 
+ 	| bb r reverbSwitch repeatSwitch |
+ 	r := AlignmentMorph newRow.
+ 	r color: color; borderWidth: 0; layoutInset: 0.
+ 	r hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
+ 	bb := SimpleButtonMorph new target: self; borderColor: #raised;
+ 			borderWidth: 2; color: color.
+ 	r addMorphBack: (bb label: '<>'; actWhen: #buttonDown;
+ 												actionSelector: #invokeMenu).
+ 	bb := SimpleButtonMorph new target: self; borderColor: #raised;
+ 			borderWidth: 2; color: color.
+ 	r addMorphBack: (bb label: 'Piano Roll' translated;		actionSelector: #makePianoRoll).
+ 	bb := SimpleButtonMorph new target: self; borderColor: #raised;
+ 			borderWidth: 2; color: color.
+ 	r addMorphBack: (bb label: 'Rewind' translated;		actionSelector: #rewind).
+ 	bb := SimpleButtonMorph new target: scorePlayer; borderColor: #raised;
+ 			borderWidth: 2; color: color.
+ 	r addMorphBack: (bb label: 'Play' translated;			actionSelector: #resumePlaying).
+ 	bb := SimpleButtonMorph new target: scorePlayer; borderColor: #raised;
+ 			borderWidth: 2; color: color.
+ 	r addMorphBack: (bb label: 'Pause' translated;			actionSelector: #pause).
+ 	reverbSwitch := SimpleSwitchMorph new
+ 		offColor: color;
+ 		onColor: (Color r: 1.0 g: 0.6 b: 0.6);
+ 		borderWidth: 2;
+ 		label: 'Reverb Disable' translated;
+ 		actionSelector: #disableReverb:;
+ 		target: scorePlayer;
+ 		setSwitchState: SoundPlayer isReverbOn not.
+ 	r addMorphBack: reverbSwitch.
+ 	scorePlayer ifNotNil:
+ 		[repeatSwitch := SimpleSwitchMorph new
+ 			offColor: color;
+ 			onColor: (Color r: 1.0 g: 0.6 b: 0.6);
+ 			borderWidth: 2;
+ 			label: 'Repeat' translated;
+ 			actionSelector: #repeat:;
+ 			target: scorePlayer;
+ 			setSwitchState: scorePlayer repeat.
+ 		r addMorphBack: repeatSwitch].
+ 	^ r
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>makeMIDIController: (in category 'layout') -----
+ makeMIDIController: evt
+ 
+ 	self world activeHand attachMorph:
+ 		(MIDIControllerMorph new midiPort: scorePlayer midiPort).
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>makePianoRoll (in category 'layout') -----
+ makePianoRoll
+ 	"Create a piano roll viewer for this score player."
+ 
+ 	| pianoRoll hand |
+ 	pianoRoll := PianoRollScoreMorph new on: scorePlayer.
+ 	hand := self world activeHand.
+ 	hand ifNil: [self world addMorph: pianoRoll]
+ 		ifNotNil: [hand attachMorph: pianoRoll.
+ 				hand lastEvent shiftPressed ifTrue:
+ 					["Special case for NOBM demo"
+ 					pianoRoll contractTime; contractTime; enableDragNDrop]].
+ 	pianoRoll startStepping.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>makeRow (in category 'layout') -----
+ makeRow
+ 
+ 	^ AlignmentMorph newRow
+ 		color: color;
+ 		layoutInset: 0;
+ 		wrapCentering: #center; cellPositioning: #leftCenter;
+ 		hResizing: #spaceFill;
+ 		vResizing: #shrinkWrap
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>onScorePlayer:title: (in category 'initialization') -----
+ onScorePlayer: aScorePlayer title: scoreName
+ 	| divider col r |
+ 	scorePlayer := aScorePlayer.
+ 	scorePlayer ifNotNil:
+ 		[scorePlayer  reset.
+ 		instrumentSelector := Array new: scorePlayer score tracks size].
+ 
+ 	self removeAllMorphs.
+ 	self addMorphBack: self makeControls.
+ 	scorePlayer ifNil: [^ self].
+ 
+ 	r := self makeRow
+ 		hResizing: #shrinkWrap;
+ 		vResizing: #shrinkWrap.
+ 	r addMorphBack: self rateControl;
+ 		addMorphBack: (Morph newBounds: (0 at 0 extent: 20 at 0) color: Color transparent);
+ 		addMorphBack: self volumeControl.
+ 	self addMorphBack: r.
+ 	self addMorphBack: self scrollControl.
+ 
+ 	col := AlignmentMorph newColumn color: color; layoutInset: 0.
+ 	self addMorphBack: col.
+ 	1 to: scorePlayer trackCount do: [:trackIndex |
+ 		divider := AlignmentMorph new
+ 			extent: 10 at 1;
+ 			borderWidth: 1;
+ 			layoutInset: 0;
+ 			borderColor: #raised;
+ 			color: color;
+ 			hResizing: #spaceFill;
+ 			vResizing: #rigid.
+ 		col addMorphBack: divider.
+ 		col addMorphBack: (self trackControlsFor: trackIndex)].
+ 
+ 	LastMIDIPort ifNotNil: [
+ 		"use the most recently set MIDI port"
+ 		scorePlayer openMIDIPort: LastMIDIPort].
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>openMIDIFile (in category 'initialization') -----
+ openMIDIFile
+ 	"Open a MIDI score and re-init controls..."
+ 	| score fileName f player |
+ 	fileName := Utilities chooseFileWithSuffixFromList: #('.mid' '.midi')
+ 					withCaption: 'Choose a MIDI file to open' translated.
+ 	(fileName isNil or: [ fileName == #none ])
+ 		ifTrue: [^ self inform: 'No .mid/.midi files found in the Squeak directory' translated].
+ 	f := FileStream readOnlyFileNamed: fileName.
+ 	score := (MIDIFileReader new readMIDIFrom: f binary) asScore.
+ 	f close.
+ 	player := ScorePlayer onScore: score.
+ 	self onScorePlayer: player title: fileName!

Item was added:
+ ----- Method: ScorePlayerMorph>>openMIDIPort (in category 'initialization') -----
+ openMIDIPort
+ 
+ 	| portNum |
+ 	portNum := SimpleMIDIPort outputPortNumFromUser.
+ 	portNum ifNil: [^ self].
+ 	scorePlayer openMIDIPort: portNum.
+ 	LastMIDIPort := portNum.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>panAndVolControlsFor: (in category 'layout') -----
+ panAndVolControlsFor: trackIndex
+ 
+ 	| volSlider panSlider c r middleLine pianoRollColor |
+ 	pianoRollColor := (Color wheel: scorePlayer score tracks size) at: trackIndex.
+ 	volSlider := SimpleSliderMorph new
+ 		color: color;
+ 		sliderColor: pianoRollColor;
+ 		extent: 101 at 2;
+ 		target: scorePlayer;
+ 		arguments: (Array with: trackIndex);
+ 		actionSelector: #volumeForTrack:put:;
+ 		minVal: 0.0;
+ 		maxVal: 1.0;
+ 		adjustToValue: (scorePlayer volumeForTrack: trackIndex).
+ 	panSlider := SimpleSliderMorph new
+ 		color: color;
+ 		sliderColor: pianoRollColor;
+ 		extent: 101 at 2;
+ 		target: scorePlayer;
+ 		arguments: (Array with: trackIndex);
+ 		actionSelector: #panForTrack:put:;
+ 		minVal: 0.0;
+ 		maxVal: 1.0;		
+ 		adjustToValue: (scorePlayer panForTrack: trackIndex).
+ 	c := AlignmentMorph newColumn
+ 		color: color;
+ 		layoutInset: 0;
+ 		wrapCentering: #center; cellPositioning: #topCenter;
+ 		hResizing: #spaceFill;
+ 		vResizing: #shrinkWrap.
+ 	middleLine := Morph new  "center indicator for pan slider"
+ 		color: (Color r: 0.4 g: 0.4 b: 0.4);
+ 		extent: 1@(panSlider height - 4);
+ 		position: panSlider center x@(panSlider top + 2).
+ 	panSlider addMorphBack: middleLine.
+ 	r := self makeRow.
+ 	r addMorphBack: (StringMorph contents: '0').
+ 	r addMorphBack: volSlider.
+ 	r addMorphBack: (StringMorph contents: '10').
+ 	c addMorphBack: r.
+ 	r := self makeRow.
+ 	r addMorphBack: (StringMorph contents: 'L' translated).
+ 	r addMorphBack: panSlider.
+ 	r addMorphBack: (StringMorph contents: 'R' translated).
+ 	c addMorphBack: r.
+ 	^ c
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>rateControl (in category 'layout') -----
+ rateControl
+ 
+ 	| rateSlider middleLine r |
+ 	rateSlider := SimpleSliderMorph new
+ 		color: color;
+ 		sliderColor: Color gray;
+ 		extent: 180 at 2;
+ 		target: self;
+ 		actionSelector: #setLogRate:;
+ 		minVal: -1.0;
+ 		maxVal: 1.0;
+ 		adjustToValue: 0.0.
+ 	middleLine := Morph new  "center indicator for pan slider"
+ 		color: (Color r: 0.4 g: 0.4 b: 0.4);
+ 		extent: 1@(rateSlider height - 4);
+ 		position: rateSlider center x@(rateSlider top + 2).
+ 	rateSlider addMorphBack: middleLine.
+ 	r := self makeRow
+ 		hResizing: #shrinkWrap;
+ 		vResizing: #rigid;
+ 		height: 24.
+ 	r addMorphBack: (StringMorph contents: 'slow ' translated).
+ 	r addMorphBack: rateSlider.
+ 	r addMorphBack: (StringMorph contents: ' fast' translated).
+ 	^ r
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>rewind (in category 'controls') -----
+ rewind
+ 
+ 	scorePlayer pause; reset.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>saveAsAIFF (in category 'menu') -----
+ saveAsAIFF
+ 	"Create a stereo AIFF audio file with the result of performing my score."
+ 
+ 	| fileName |
+ 	fileName := UIManager default request: 'New file name?' translated.
+ 	fileName isEmpty ifTrue: [^ self].
+ 	(fileName asLowercase endsWith: '.aif') ifFalse: [
+ 		fileName := fileName, '.aif'].
+ 
+ 	scorePlayer storeAIFFOnFileNamed: fileName.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>saveAsSunAudio (in category 'menu') -----
+ saveAsSunAudio
+ 	"Create a stereo Sun audio file with the result of performing my score."
+ 
+ 	| fileName |
+ 	fileName := UIManager default request: 'New file name?' translated.
+ 	fileName isEmpty ifTrue: [^ self].
+ 	(fileName asLowercase endsWith: '.au') ifFalse: [
+ 		fileName := fileName, '.au'].
+ 
+ 	scorePlayer storeSunAudioOnFileNamed: fileName.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>saveAsWAV (in category 'menu') -----
+ saveAsWAV
+ 	"Create a stereo WAV audio file with the result of performing my score."
+ 
+ 	| fileName |
+ 	fileName := UIManager default request: 'New file name?' translated.
+ 	fileName isEmpty ifTrue: [^ self].
+ 	(fileName asLowercase endsWith: '.wav') ifFalse: [
+ 		fileName := fileName, '.wav'].
+ 
+ 	scorePlayer storeWAVOnFileNamed: fileName.
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>scorePlayer (in category 'accessing') -----
+ scorePlayer
+ 
+ 	^ scorePlayer
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>scrollControl (in category 'layout') -----
+ scrollControl
+ 
+ 	| r |
+ 	scrollSlider := SimpleSliderMorph new
+ 		color: color;
+ 		sliderColor: Color gray;
+ 		extent: 360 at 2;
+ 		target: scorePlayer;
+ 		actionSelector: #positionInScore:;
+ 		adjustToValue: scorePlayer positionInScore.
+ 	r := self makeRow
+ 		hResizing: #shrinkWrap;
+ 		vResizing: #rigid;
+ 		height: 24.
+ 	r addMorphBack: (StringMorph contents: 'start ' translated).
+ 	r addMorphBack: scrollSlider.
+ 	r addMorphBack: (StringMorph contents: ' end' translated).
+ 	^ r
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>setLogRate: (in category 'controls') -----
+ setLogRate: logOfRate
+ 
+ 	scorePlayer rate: (3.5 raisedTo: logOfRate).
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>showResumeButtonInTheWorld (in category 'layout') -----
+ showResumeButtonInTheWorld
+ 	WorldState addDeferredUIMessage: [
+ 		| w |
+ 		w := self world.
+ 		w ifNotNil: [
+ 			w addMorphFront:
+ 				(self standaloneResumeButton position: (w right - 100) @ (w top + 10)).
+ 			scorePlayer pause.
+ 			].
+ 	]
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>standaloneResumeButton (in category 'layout') -----
+ standaloneResumeButton
+ 
+ 	| r |
+ 
+ 	r := AlignmentMorph newRow.
+ 	r color: Color red; borderWidth: 0; layoutInset: 6; useRoundedCorners.
+ 	r hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
+ 	r addMorphBack: (
+ 		SimpleButtonMorph new
+ 			target: [
+ 				scorePlayer resumePlaying.
+ 				r delete
+ 			];
+ 			borderColor: #raised;
+ 			borderWidth: 2;
+ 			color: Color green;
+ 			label: 'Continue' translated;
+ 			actionSelector: #value
+ 	).
+ 	r setBalloonText: 'Continue playing a paused presentation' translated.
+ 	^r
+ 
+ 
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>step (in category 'stepping and presenter') -----
+ step
+ 
+ 	scrollSlider adjustToValue: scorePlayer positionInScore.
+ 
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>trackControlsFor: (in category 'layout') -----
+ trackControlsFor: trackIndex
+ 
+ 	| r |
+ 	r := self makeRow
+ 		hResizing: #shrinkWrap;
+ 		vResizing: #shrinkWrap.
+ 	r addMorphBack: (self trackNumAndMuteButtonFor: trackIndex).
+ 	r addMorphBack: (Morph new extent: 10 at 5; color: color).  "spacer"
+ 	r addMorphBack: (self panAndVolControlsFor: trackIndex).
+ 	^ r
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>trackNumAndMuteButtonFor: (in category 'layout') -----
+ trackNumAndMuteButtonFor: trackIndex
+ 
+ 	| muteButton instSelector pianoRollColor r |
+ 	muteButton := SimpleSwitchMorph new
+ 		onColor: (Color r: 1.0 g: 0.6 b: 0.6);
+ 		offColor: color;
+ 		color: color;
+ 		label: 'Mute' translated;
+ 		target: scorePlayer;
+ 		actionSelector: #mutedForTrack:put:;
+ 		arguments: (Array with: trackIndex).
+ 	instSelector := PopUpChoiceMorph new
+ 		extent: 95 at 14;
+ 		contentsClipped: 'oboe1';
+ 		target: self;
+ 		actionSelector: #atTrack:from:selectInstrument:;
+ 		getItemsSelector: #instrumentChoicesForTrack:;
+ 		getItemsArgs: (Array with: trackIndex).
+ 	instSelector arguments:
+ 		(Array with: trackIndex with: instSelector).
+ 	instrumentSelector at: trackIndex put: instSelector.
+ 
+ 	"select track color using same color list as PianoRollScoreMorph"
+ 	pianoRollColor := (Color wheel: scorePlayer score tracks size) at: trackIndex.
+ 
+ 	r := self makeRow
+ 		hResizing: #rigid;
+ 		vResizing: #spaceFill;
+ 		extent: 70 at 10.
+ 	r addMorphBack:
+ 		((StringMorph
+ 			contents: trackIndex printString
+ 			font: (TextStyle default fontOfSize: 24)) color: pianoRollColor).
+ 	trackIndex < 10
+ 		ifTrue: [r addMorphBack: (Morph new color: color; extent: 19 at 8)]  "spacer"
+ 		ifFalse: [r addMorphBack: (Morph new color: color; extent: 8 at 8)].  "spacer"
+ 	r addMorphBack:
+ 		(StringMorph new
+ 			extent: 140 at 14;
+ 			contentsClipped: (scorePlayer infoForTrack: trackIndex)).
+ 	r addMorphBack: (Morph new color: color; extent: 8 at 8).  "spacer"
+ 	r addMorphBack: instSelector.
+ 	r addMorphBack: (AlignmentMorph newRow color: color).  "spacer"
+ 	r addMorphBack: muteButton.
+ 	^ r
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>updateInstrumentsFromLibraryExcept: (in category 'menu') -----
+ updateInstrumentsFromLibraryExcept: soundsBeingEdited
+ 	"The instrument library has been modified. Update my instruments with the new versions from the library. Use a single instrument prototype for all parts with the same name; this allows the envelope editor to edit all the parts by changing a single sound prototype."
+ 
+ 	"soundsBeingEdited is a collection of sounds being edited (by an EnvelopeEditor).  If any of my instruments share one of these, then they will be left alone so as not to disturb that dynamic linkage."
+ 
+ 	| unloadPostfix myInstruments name displaysAsUnloaded isUnloaded |
+ 	unloadPostfix := '(out)'.
+ 	myInstruments := Dictionary new.
+ 	1 to: instrumentSelector size do: [:i |
+ 		name := (instrumentSelector at: i) contents.
+ 		displaysAsUnloaded := name endsWith: unloadPostfix.
+ 		displaysAsUnloaded ifTrue: [
+ 			name := name copyFrom: 1 to: name size - unloadPostfix size].
+ 		(myInstruments includesKey: name) ifFalse: [
+ 			myInstruments at: name put:
+ 				(name = 'clink'
+ 					ifTrue: [
+ 						(SampledSound
+ 							samples: SampledSound coffeeCupClink
+ 							samplingRate: 11025) copy]
+ 					ifFalse: [
+ 						(AbstractSound
+ 							soundNamed: name
+ 							ifAbsent: [
+ 								(instrumentSelector at: i) contentsClipped: 'default'.
+ 								FMSound default]) copy])].
+ 		(soundsBeingEdited includes: (scorePlayer instrumentForTrack: i)) ifFalse:
+ 			["Do not update any instrument that is currently being edited"
+ 			scorePlayer instrumentForTrack: i put: (myInstruments at: name)].
+ 
+ 		"update loaded/unloaded status in instrumentSelector if necessary"
+ 		isUnloaded := (myInstruments at: name) isKindOf: UnloadedSound.
+ 		(displaysAsUnloaded and: [isUnloaded not])
+ 			ifTrue: [(instrumentSelector at: i) contentsClipped: name].
+ 		(displaysAsUnloaded not and: [isUnloaded])
+ 			ifTrue: [(instrumentSelector at: i) contentsClipped: name, unloadPostfix]].
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>volumeControl (in category 'layout') -----
+ volumeControl
+ 
+ 	| volumeSlider r |
+ 	volumeSlider := SimpleSliderMorph new
+ 		color: color;
+ 		sliderColor: Color gray;
+ 		extent: 80 at 2;
+ 		target: scorePlayer;
+ 		actionSelector: #overallVolume:;
+ 		adjustToValue: scorePlayer overallVolume.
+ 	r := self makeRow
+ 		hResizing: #shrinkWrap;
+ 		vResizing: #rigid;
+ 		height: 24.
+ 	r addMorphBack: (StringMorph contents: 'soft  ' translated).
+ 	r addMorphBack: volumeSlider.
+ 	r addMorphBack: (StringMorph contents: ' loud' translated).
+ 	^ r
+ !

Item was added:
+ ----- Method: ScorePlayerMorph>>wantsRoundedCorners (in category 'rounding') -----
+ wantsRoundedCorners
+ 	^ Preferences roundedWindowCorners or: [super wantsRoundedCorners]!

Item was added:
+ ImageMorph subclass: #Sonogram
+ 	instanceVariableNames: 'lastX scrollDelta columnForm minVal maxVal pixValMap'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Sound-Synthesis'!
+ 
+ !Sonogram commentStamp: '<historical>' prior: 0!
+ Sonograms are imageMorphs that will repeatedly plot arrays of values as black on white columns moving to the right in time and scrolling left as necessary.!

Item was added:
+ ----- Method: Sonogram>>extent: (in category 'geometry') -----
+ extent: newExtent
+ 	super image: (Form extent: newExtent depth: Display depth).
+ 	lastX := -1.
+ 	columnForm := Form extent: (32//image depth)@(image height) depth: image depth.
+ 	pixValMap := ((1 to: 256) collect:
+ 			[:i | columnForm pixelValueFor: (Color gray: (256-i)/255.0)])
+ 		as: Bitmap.
+ !

Item was added:
+ ----- Method: Sonogram>>extent:minVal:maxVal:scrollDelta: (in category 'all') -----
+ extent: extent minVal: min maxVal: max scrollDelta: d
+ 	minVal := min.
+ 	maxVal := max.
+ 	scrollDelta := d.
+ 	self extent: extent.
+ 
+ " try following with scrolldelta = 1, 20, 200
+ 	| s data |
+ 	s := Sonogram new extent: 200 at 50
+ 				minVal: 0.0 maxVal: 1.0 scrollDelta: 20.
+ 	World addMorph: s.
+ 	data := (1 to: 133) collect: [:i | 0.0].
+ 	1 to: 300 do:
+ 		[:i | data at: (i\\133)+1 put: 1.0.
+ 		s plotColumn: data.
+ 		data at: (i\\133)+1 put: 0.0.
+ 		World doOneCycleNow].
+ 	s delete	
+ "!

Item was added:
+ ----- Method: Sonogram>>plotColumn: (in category 'all') -----
+ plotColumn: dataArray 
+ 	| chm1 i normVal r |
+ 	columnForm unhibernate.
+ 	chm1 := columnForm height - 1.
+ 	0 to: chm1
+ 		do: 
+ 			[:y | 
+ 			i := y * (dataArray size - 1) // chm1 + 1.
+ 			normVal := ((dataArray at: i) - minVal) / (maxVal - minVal).
+ 			normVal := normVal max: 0.0.
+ 			normVal := normVal min: 1.0.
+ 			columnForm bits at: chm1 - y + 1
+ 				put: (pixValMap at: (normVal * 255.0) truncated + 1)].
+ 	(lastX := lastX + 1) > (image width - 1) ifTrue: [self scroll].
+ 	image 
+ 		copy: (r := lastX @ 0 extent: 1 @ image height)
+ 		from: (32 // image depth - 1) @ 0
+ 		in: columnForm
+ 		rule: Form over.
+ 	"self changed."
+ 	self invalidRect: (r translateBy: self position)!

Item was added:
+ ----- Method: Sonogram>>scroll (in category 'all') -----
+ scroll
+ 	image copy: (scrollDelta at 0 extent: (image width-scrollDelta)@image height)
+ 			from: image to: 0 at 0 rule: Form over.
+ 	lastX := lastX - scrollDelta.
+ 	self changed!



More information about the Packages mailing list