[Pkg] The Trunk: MorphicExtras-fbs.113.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jul 4 19:14:23 UTC 2013


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

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

Name: MorphicExtras-fbs.113
Author: fbs
Time: 4 July 2013, 8:13:40.115 pm
UUID: 46d02786-4625-fc44-9936-54fe4525811d
Ancestors: MorphicExtras-fbs.112

Sound -/-> MorphicExtras.

=============== Diff against MorphicExtras-fbs.112 ===============

Item was changed:
  SystemOrganization addCategory: #'MorphicExtras-AdditionalMorphs'!
  SystemOrganization addCategory: #'MorphicExtras-AdditionalSupport'!
  SystemOrganization addCategory: #'MorphicExtras-AdditionalWidgets'!
  SystemOrganization addCategory: #'MorphicExtras-Books'!
  SystemOrganization addCategory: #'MorphicExtras-Demo'!
  SystemOrganization addCategory: #'MorphicExtras-EToy-Download'!
  SystemOrganization addCategory: #'MorphicExtras-Flaps'!
  SystemOrganization addCategory: #'MorphicExtras-GeeMail'!
  SystemOrganization addCategory: #'MorphicExtras-Leds'!
  SystemOrganization addCategory: #'MorphicExtras-Navigators'!
  SystemOrganization addCategory: #'MorphicExtras-Obsolete'!
  SystemOrganization addCategory: #'MorphicExtras-Palettes'!
  SystemOrganization addCategory: #'MorphicExtras-PartsBin'!
  SystemOrganization addCategory: #'MorphicExtras-Postscript Canvases'!
  SystemOrganization addCategory: #'MorphicExtras-Postscript Filters'!
  SystemOrganization addCategory: #'MorphicExtras-SoundInterface'!
  SystemOrganization addCategory: #'MorphicExtras-SqueakPage'!
  SystemOrganization addCategory: #'MorphicExtras-Support'!
  SystemOrganization addCategory: #'MorphicExtras-Text Support'!
  SystemOrganization addCategory: #'MorphicExtras-Undo'!
  SystemOrganization addCategory: #'MorphicExtras-Widgets'!
+ SystemOrganization addCategory: #'MorphicExtras-Sound'!

Item was added:
+ ----- Method: AIFFFileReader>>edit (in category '*MorphicExtras-Sound') -----
+ edit
+ 
+ 	| ed |
+ 	ed := WaveEditor new.
+ 	ed data: channelData first.
+ 	ed loopEnd: markers last last.
+ 	ed loopLength: (markers last last - markers first last) + 1.
+ 	ed openInWorld.
+ !

Item was added:
+ ----- Method: AbstractMediaEventMorph>>justDroppedIntoPianoRoll:event: (in category 'piano rolls') -----
+ justDroppedIntoPianoRoll: pianoRoll event: evt
+ 	
+ 	| ambientEvent |
+ 	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: AbstractSound>>viewSamples (in category '*MorphicExtras-Sound') -----
+ viewSamples
+ 	"Open a WaveEditor on my samples."
+ 
+ 	WaveEditor openOn: self samples.
+ !

Item was added:
+ ----- Method: BookPageThumbnailMorph>>encounteredAtTime:inScorePlayer:atIndex:inEventTrack:secsPerTick: (in category 'piano rolls') -----
+ encounteredAtTime: ticks inScorePlayer: scorePlayer atIndex: index inEventTrack: track secsPerTick: secsPerTick
+ 	"Flip to this page with no extra sound"
+ 	BookMorph turnOffSoundWhile: [self doPageFlip]!

Item was added:
+ ----- Method: EventRecorderMorph>>addMorphsTo:pianoRoll:eventTime:betweenTime:and: (in category 'sound-piano rolls') -----
+ addMorphsTo: morphList pianoRoll: pianoRoll eventTime: t betweenTime: leftTime and: rightTime
+ 
+ 	| startX myDurationInTicks endX |
+ 
+ 	startX := pianoRoll xForTime: t.
+ 	myDurationInTicks := pianoRoll scorePlayer ticksForMSecs: self myDurationInMS.
+ 	t > rightTime ifTrue: [^ self].  
+ 	(t + myDurationInTicks) < leftTime ifTrue: [^ self].
+ 	endX := pianoRoll xForTime: t + myDurationInTicks.
+ 
+ 	morphList add: 
+ 		(self hResizing: #spaceFill; left: startX; width: endX - startX).
+ 
+ !

Item was added:
+ ----- Method: EventRecorderMorph>>addVoiceControls (in category 'sound') -----
+ addVoiceControls 
+ 
+ 	| levelSlider r meterBox |
+ 	voiceRecorder := SoundRecorder new
+ 		desiredSampleRate: 11025.0;		"<==try real hard to get the low rate"
+ 		codec: (GSMCodec new).		"<--this should compress better than ADPCM.. is it too slow?"
+ 		"codec: (ADPCMCodec new initializeForBitsPerSample: 4 samplesPerFrame: 0)."
+ 
+ 	levelSlider := SimpleSliderMorph new
+ 		color: color;
+ 		extent: 100 at 2;
+ 		target: voiceRecorder;
+ 		actionSelector: #recordLevel:;
+ 		adjustToValue: voiceRecorder recordLevel.
+ 	r := AlignmentMorph newRow
+ 		color: color;
+ 		layoutInset: 0;
+ 		wrapCentering: #center; cellPositioning: #leftCenter;
+ 		hResizing: #shrinkWrap;
+ 		vResizing: #rigid;
+ 		height: 24.
+ 	r addMorphBack: (StringMorph contents: '0 ').
+ 	r addMorphBack: levelSlider.
+ 	r addMorphBack: (StringMorph contents: ' 10').
+ 	self addMorphBack: r.
+ 
+ 	meterBox := Morph new extent: 102 at 18; color: Color gray.
+ 	recordMeter := Morph new extent: 1 at 16; color: Color yellow.
+ 	recordMeter position: meterBox topLeft + (1 at 1).
+ 	meterBox addMorph: recordMeter.
+ 
+ 	r := AlignmentMorph newRow vResizing: #shrinkWrap.
+ 	r addMorphBack: meterBox.
+ 	self addMorphBack: r.
+ !

Item was added:
+ ----- Method: EventRecorderMorph>>encounteredAtTime:inScorePlayer:atIndex:inEventTrack:secsPerTick: (in category 'sound-piano rolls') -----
+ encounteredAtTime: ticks inScorePlayer: scorePlayer atIndex: index inEventTrack: track secsPerTick: secsPerTick
+ 
+ 	self play.!

Item was added:
+ ----- Method: EventRecorderMorph>>justDroppedIntoPianoRoll:event: (in category 'sound-piano rolls') -----
+ justDroppedIntoPianoRoll: newOwner event: evt
+ 	
+ 	| startX lengthInTicks endX startTimeInScore endTimeInScore |
+ 
+ 	super justDroppedIntoPianoRoll: newOwner event: evt.
+ 
+ 	startTimeInScore := newOwner timeForX: self left.
+ 	lengthInTicks := newOwner scorePlayer ticksForMSecs: self myDurationInMS.
+ 	endTimeInScore := startTimeInScore + lengthInTicks.
+ 
+ 	endTimeInScore > newOwner scorePlayer durationInTicks ifTrue:
+ 		[newOwner scorePlayer updateDuration].
+ 
+ 	startX := newOwner xForTime: startTimeInScore.
+ 	endX := newOwner xForTime: endTimeInScore.
+ 	self width: endX - startX.
+ !

Item was added:
+ ----- Method: EventRecorderMorph>>myDurationInMS (in category 'sound-piano rolls') -----
+ myDurationInMS
+ 
+ 	^tape isEmptyOrNil ifTrue: [
+ 		10
+ 	] ifFalse: [
+ 		tape last timeStamp - tape first timeStamp
+ 	]
+ !

Item was added:
+ ----- Method: GraphMorph>>addCustomMenuItems:hand: (in category 'sound') -----
+ addCustomMenuItems: aCustomMenu hand: aHandMorph
+ 
+ 	super addCustomMenuItems: aCustomMenu hand: aHandMorph.
+ 	aCustomMenu add: 'open wave editor' translated action: #openWaveEditor.
+ 	aCustomMenu add: 'read file' translated action: #readDataFromFile.
+ !

Item was added:
+ ----- Method: GraphMorph>>openWaveEditor (in category 'sound') -----
+ openWaveEditor
+ 
+ 	| scaleFactor scaledData editor |
+ 	self data: data.  "make sure maxVal and minVal are current"
+ 	scaleFactor := 32767 // ((minVal abs max: maxVal abs) max: 1).
+ 	scaledData := SoundBuffer newMonoSampleCount: data size.
+ 	1 to: data size do: [:i | scaledData at: i put: (scaleFactor * (data at: i)) truncated].
+ 	editor := WaveEditor new
+ 		data: scaledData;
+ 		samplingRate: 11025;
+ 		perceivedFrequency: 220.0.
+ 	editor openInWorld.
+ !

Item was added:
+ ----- Method: GraphMorph>>readDataFromFile (in category 'sound') -----
+ readDataFromFile
+ 
+ 	| fileName |
+ 	fileName := UIManager default
+ 		request: 'File name?' translated
+ 		initialAnswer: ''.
+ 	fileName isEmpty ifTrue: [^ self].
+ 	(StandardFileStream isAFileNamed: fileName) ifFalse: [
+ 		^ self inform: 'Sorry, I cannot find that file' translated].
+ 	self data: (SampledSound fromAIFFfileNamed: fileName) samples.
+ 
+ !

Item was added:
+ PianoKeyboardMorph subclass: #KeyboardMorphForInput
+ 	instanceVariableNames: 'pianoRoll duration durationModifier articulation buildingChord insertMode prevSelection startOfNextNote'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Sound'!
+ 
+ !KeyboardMorphForInput commentStamp: 'nice 3/24/2010 07:37' prior: 0!
+ This class adds state and controls to the basic PianoKeyboardMorph so that notes of reliable duration can be keyed into a score without the need for a real keyboard.
+ 
+ To try this out, execute...
+ 
+ 	| n score | n := 3.
+ 	score := (MIDIScore new tracks: ((1 to: n) collect: [:i | Array new]);
+ 		trackInfo: ((1 to: n) collect: [:i | 'Instrument' , i printString]);
+ 		tempoMap: nil; ticksPerQuarterNote: 96).
+ 	ScorePlayerMorph openOn: score title: 'empty score'
+ 
+ Then open a pianoRoll and, from that, open a keyboard.  The rule is that the keyboard will append after the current selection.  If the current selection is muted or nil, then input will go to the end of the first non-muted track.!

Item was added:
+ ----- Method: KeyboardMorphForInput>>addRecordingControls (in category 'initialization') -----
+ addRecordingControls
+ 	| button switch playRow durRow articRow modRow |
+ 
+ 	"Add chord, rest and delete buttons"
+ 	playRow := AlignmentMorph newRow.
+ 	playRow color: color; borderWidth: 0; layoutInset: 0.
+ 	playRow hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	playRow addMorphBack: (switch label: 'chord' translated; actionSelector: #buildChord:).
+ 	button := SimpleButtonMorph new target: self;
+ 		borderColor: #raised; borderWidth: 2; color: color.
+ 	playRow addMorphBack: (button label: '          rest          ' translated; actionSelector: #emitRest).
+ 	button := SimpleButtonMorph new target: self;
+ 		borderColor: #raised; borderWidth: 2; color: color.
+ 	playRow addMorphBack: (button label: 'del' translated; actionSelector: #deleteNotes).
+ 	self addMorph: playRow.
+ 	playRow align: playRow fullBounds topCenter
+ 			with: self fullBounds bottomCenter.
+ 
+ 	"Add note duration buttons"
+ 	durRow := AlignmentMorph newRow.
+ 	durRow color: color; borderWidth: 0; layoutInset: 0.
+ 	durRow hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	durRow addMorphBack: (switch label: 'whole' translated;
+ 				actionSelector: #duration:onOff:; arguments: #(1)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	durRow addMorphBack: (switch label: 'half' translated;
+ 				actionSelector: #duration:onOff:; arguments: #(2)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	durRow addMorphBack: (switch label: 'quarter' translated;
+ 				actionSelector: #duration:onOff:; arguments: #(4)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	durRow addMorphBack: (switch label: 'eighth' translated;
+ 				actionSelector: #duration:onOff:; arguments: #(8)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	durRow addMorphBack: (switch label: 'sixteenth' translated;
+ 				actionSelector: #duration:onOff:; arguments: #(16)).
+ 	self addMorph: durRow.
+ 	durRow align: durRow fullBounds topCenter
+ 			with: playRow fullBounds bottomCenter.
+ 
+ 	"Add note duration modifier buttons"
+ 	modRow := AlignmentMorph newRow.
+ 	modRow color: color; borderWidth: 0; layoutInset: 0.
+ 	modRow hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	modRow addMorphBack: (switch label: 'dotted' translated;
+ 				actionSelector: #durMod:onOff:; arguments: #(dotted)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	modRow addMorphBack: (switch label: 'normal' translated;
+ 				actionSelector: #durMod:onOff:; arguments: #(normal)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	modRow addMorphBack: (switch label: 'triplets' translated;
+ 				actionSelector: #durMod:onOff:; arguments: #(triplets)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	modRow addMorphBack: (switch label: 'quints' translated;
+ 				actionSelector: #durMod:onOff:; arguments: #(quints)).
+ 	self addMorph: modRow.
+ 	modRow align: modRow fullBounds topCenter
+ 			with: durRow fullBounds bottomCenter.
+ 
+ 	"Add articulation buttons"
+ 	articRow := AlignmentMorph newRow.
+ 	articRow color: color; borderWidth: 0; layoutInset: 0.
+ 	articRow hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	articRow addMorphBack: (switch label: 'legato' translated;
+ 				actionSelector: #articulation:onOff:; arguments: #(legato)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	articRow addMorphBack: (switch label: 'normal' translated;
+ 				actionSelector: #articulation:onOff:; arguments: #(normal)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	articRow addMorphBack: (switch label: 'staccato' translated;
+ 				actionSelector: #articulation:onOff:; arguments: #(staccato)).
+ 	self addMorph: articRow.
+ 	articRow align: articRow fullBounds topCenter
+ 			with: modRow fullBounds bottomCenter.
+ 
+ 	self bounds: (self fullBounds expandBy: (0 at 0 extent: 0 at borderWidth))
+ !

Item was added:
+ ----- Method: KeyboardMorphForInput>>articulation:onOff: (in category 'note controls') -----
+ articulation: artic onOff: ignored    "artic = eg, #legato, #normal, #staccato."
+ 	"Set the articulation of notes to be emitted when a key is pressed."
+ 
+ 	self allMorphsDo:
+ 		[:m | ((m isMemberOf: SimpleSwitchMorph)
+ 				and: [m actionSelector == #articulation:onOff:])
+ 				ifTrue: [m setSwitchState: m arguments first == artic]].
+ 	articulation := artic!

Item was added:
+ ----- Method: KeyboardMorphForInput>>backspaceNote (in category 'note controls') -----
+ backspaceNote
+ 
+ 	self deleteNotes!

Item was added:
+ ----- Method: KeyboardMorphForInput>>buildChord: (in category 'note controls') -----
+ buildChord: onOff!

Item was added:
+ ----- Method: KeyboardMorphForInput>>deleteNotes (in category 'note controls') -----
+ deleteNotes
+ 
+ 	pianoRoll deleteSelection!

Item was added:
+ ----- Method: KeyboardMorphForInput>>durMod:onOff: (in category 'note controls') -----
+ durMod: durMod onOff: ignored    "durMod = eg, #dotted, #normal, #triplets, #quints"
+ 	"Set the duration of notes to be emitted when a key is pressed."
+ 
+ 	self allMorphsDo:
+ 		[:m | ((m isMemberOf: SimpleSwitchMorph)
+ 				and: [m actionSelector == #durMod:onOff:])
+ 				ifTrue: [m setSwitchState: m arguments first = durMod]].
+ 	durationModifier := durMod!

Item was added:
+ ----- Method: KeyboardMorphForInput>>duration:onOff: (in category 'note controls') -----
+ duration: denom onOff: ignored    "denom = eg, 1, 2, 4, 8, 16"
+ 	"Set the duration of notes to be emitted when a key is pressed."
+ 
+ 	self allMorphsDo:
+ 		[:m | ((m isMemberOf: SimpleSwitchMorph)
+ 				and: [m actionSelector == #duration:onOff:])
+ 				ifTrue: [m setSwitchState: m arguments first = denom]].
+ 	duration := denom.
+ 	self durMod: #normal onOff: true!

Item was added:
+ ----- Method: KeyboardMorphForInput>>emitRest (in category 'note controls') -----
+ emitRest
+ 
+ 	| sel noteEvent |
+ 
+ 	"All this selection logic should be shared with mouseDown..."
+ 	(sel := pianoRoll selection) ifNil: [^ self].
+ 	insertMode ifTrue:
+ 		[sel := pianoRoll selectionForInsertion.
+ 		insertMode := false].
+ 	sel = prevSelection ifFalse:
+ 		["This is a new selection -- need to determine start time"
+ 		sel third = 0
+ 			ifTrue: [startOfNextNote := 0]
+ 			ifFalse: [startOfNextNote := ((pianoRoll score tracks at: sel first)
+ 										at: sel third) endTime.
+ 					startOfNextNote := startOfNextNote + self fullDuration - 1
+ 										truncateTo: self fullDuration]].
+ 	noteEvent := NoteEvent new time: startOfNextNote; duration: self noteDuration;
+ 			key: -1 "my flag for rest" velocity: self velocity channel: 1.
+ 	pianoRoll appendEvent: noteEvent fullDuration: self fullDuration.
+ 	soundPlaying ifNotNil: [soundPlaying stopGracefully].
+ 	prevSelection := pianoRoll selection.
+ 	startOfNextNote := startOfNextNote + self fullDuration.!

Item was added:
+ ----- Method: KeyboardMorphForInput>>fullDuration (in category 'note controls') -----
+ fullDuration
+ 
+ 	| num denom |
+ 	num := denom := 1.
+ 	durationModifier == #dotted ifTrue: [num := 3.  denom := 2].
+ 	durationModifier == #triplets ifTrue: [num := 2.  denom := 3].
+ 	durationModifier == #quints ifTrue: [num := 2.  denom := 5].
+ 	^ pianoRoll score ticksPerQuarterNote * 4 * num // duration // denom!

Item was added:
+ ----- Method: KeyboardMorphForInput>>initialize (in category 'initialization') -----
+ initialize
+ "initialize the state of the receiver"
+ 	super initialize.
+ ""
+ 	buildingChord := false.
+ 	self addRecordingControls.
+ 	self duration: 4 onOff: true.
+ 	self durMod: #normal onOff: true.
+ 	self articulation: #normal onOff: true.
+ 	insertMode := false!

Item was added:
+ ----- Method: KeyboardMorphForInput>>mouseDownPitch:event:noteMorph: (in category 'simple keyboard') -----
+ mouseDownPitch: midiKey event: event noteMorph: keyMorph
+ 
+ 	| sel noteEvent |
+ 	event hand hasSubmorphs ifTrue: [^ self  "no response if drag something over me"].
+ 	keyMorph color: playingKeyColor.
+ 	(sel := pianoRoll selection) ifNil: [^ self].
+ 	insertMode ifTrue:
+ 		[sel := pianoRoll selectionForInsertion.
+ 		insertMode := false].
+ 	sel = prevSelection ifFalse:
+ 		["This is a new selection -- need to determine start time"
+ 		sel third = 0
+ 			ifTrue: [startOfNextNote := 0]
+ 			ifFalse: [startOfNextNote := ((pianoRoll score tracks at: sel first)
+ 										at: sel third) endTime.
+ 					startOfNextNote := startOfNextNote + self fullDuration - 1
+ 										truncateTo: self fullDuration]].
+ 	noteEvent := NoteEvent new time: startOfNextNote; duration: self noteDuration;
+ 			key: midiKey + 23 velocity: self velocity channel: 1.
+ 	pianoRoll appendEvent: noteEvent fullDuration: self fullDuration.
+ 	soundPlaying ifNotNil: [soundPlaying stopGracefully].
+ 	(soundPlaying := self soundForEvent: noteEvent inTrack: sel first) play.
+ 	prevSelection := pianoRoll selection.
+ 	startOfNextNote := startOfNextNote + self fullDuration.!

Item was added:
+ ----- Method: KeyboardMorphForInput>>mouseUpPitch:event:noteMorph: (in category 'simple keyboard') -----
+ mouseUpPitch: pitch event: event noteMorph: noteMorph
+ 	noteMorph color: ((#(0 1 3 5 6 8 10) includes: pitch\\12)
+ 					ifTrue: [whiteKeyColor]
+ 					ifFalse: [blackKeyColor]).
+ !

Item was added:
+ ----- Method: KeyboardMorphForInput>>noteDuration (in category 'note controls') -----
+ noteDuration
+ 
+ 	articulation == #staccato ifTrue: [^ (self fullDuration * 0.65) asInteger].
+ 	articulation == #normal ifTrue: [^ (self fullDuration * 0.8) asInteger].
+ 	articulation == #legato ifTrue: [^ (self fullDuration * 0.95) asInteger].
+ !

Item was added:
+ ----- Method: KeyboardMorphForInput>>pianoRoll: (in category 'initialization') -----
+ pianoRoll: prMorph
+ 
+ 	pianoRoll := prMorph!

Item was added:
+ ----- Method: KeyboardMorphForInput>>soundForEvent:inTrack: (in category 'events') -----
+ soundForEvent: noteEvent inTrack: trackIndex
+ 
+ 	| sound player |
+ 	player := pianoRoll scorePlayer.
+ 	sound := MixedSound new.
+ 	sound add: ((player instrumentForTrack: trackIndex)
+ 					soundForMidiKey: noteEvent midiKey
+ 					dur: noteEvent duration / (pianoRoll scorePlayer ticksForMSecs: 1000)
+ 					loudness: (noteEvent velocity asFloat / 127.0))
+ 			pan: (player panForTrack: trackIndex)
+ 			volume: player overallVolume *
+ 						(player volumeForTrack: trackIndex).
+ 	^ sound
+ !

Item was added:
+ ----- Method: KeyboardMorphForInput>>velocity (in category 'note controls') -----
+ velocity
+ 
+ 	^ 80  "Later put a slider on the keyboard control"!

Item was added:
+ ----- Method: LoopedSampledSound>>edit (in category '*MorphicExtras-Sound') -----
+ edit
+ 	"Open a WaveEditor on this sound."
+ 
+ 	| loopLen ed |
+ 	loopLen := scaledLoopLength asFloat / LoopIndexScaleFactor.
+ 	ed := WaveEditor new
+ 		data: leftSamples;
+ 		samplingRate: originalSamplingRate;
+ 		loopEnd: loopEnd;
+ 		loopLength: loopLen;
+ 		loopCycles: (loopLen / (originalSamplingRate asFloat / perceivedPitch)) rounded.
+ 	ed openInWorld.
+ !

Item was added:
+ RectangleMorph subclass: #PianoRollScoreMorph
+ 	instanceVariableNames: 'scorePlayer score colorForTrack lowestNote leftEdgeTime timeScale indexInTrack lastUpdateTick lastMutedState cursor selection timeSignature beatsPerMeasure notePerBeat showMeasureLines showBeatLines soundsPlaying soundsPlayingMorph movieClipPlayer'
+ 	classVariableNames: 'NotePasteBuffer'
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-Sound'!
+ 
+ !PianoRollScoreMorph commentStamp: '<historical>' prior: 0!
+ A PianoRollScoreMorph displays a score such as a MIDIScore, and will scroll through it tracking the progress of a ScorePlayerMorph (from which it is usually spawned).
+ 
+ timeScale is in pixels per score tick.
+ 
+ Currently the ambient track (for synchronizing thumbnails, eg) is treated specially here and in the score.  This should be cleaned up by adding a trackType or something like it in the score.!

Item was added:
+ ----- Method: PianoRollScoreMorph>>acceptDroppingMorph:event: (in category 'layout') -----
+ acceptDroppingMorph: aMorph event: evt
+ 	"In addition to placing this morph in the pianoRoll, add a corresponding
+ 	event to the score so that it will always appear when played, in addition
+ 	to possibly triggering other actions"
+ 
+ 	aMorph justDroppedIntoPianoRoll: self event: evt.
+ 	super acceptDroppingMorph: aMorph event: evt.
+ 
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>addCustomMenuItems:hand: (in category 'menu') -----
+ addCustomMenuItems: aMenu hand: aHandMorph
+ 
+ 	super addCustomMenuItems: aMenu hand: aHandMorph.
+ 	aMenu add: 'expand time' translated action: #expandTime.
+ 	aMenu add: 'contract time' translated action: #contractTime.
+ 	aMenu addLine.
+ 	aMenu add: 'add movie clip player' translated action: #addMovieClipPlayer.
+ 	(self valueOfProperty: #dragNDropEnabled) == true
+ 		ifTrue: [aMenu add: 'close drag and drop' translated action: #disableDragNDrop]
+ 		ifFalse: [aMenu add: 'open drag and drop' translated action: #enableDragNDrop].
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>addKeyboard (in category 'menu') -----
+ addKeyboard
+ 
+ 	(KeyboardMorphForInput new pianoRoll: self) openInWorld!

Item was added:
+ ----- 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 := 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 |
+ 		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 added:
+ ----- Method: PianoRollScoreMorph>>appendEvent:fullDuration: (in category 'editing') -----
+ appendEvent: noteEvent fullDuration: fullDuration 
+ 
+ 	| sel x |
+ 	score appendEvent: noteEvent fullDuration: fullDuration at: (sel := self selection).
+ 	noteEvent midiKey = -1 ifFalse:  "Unless it is a rest..."
+ 		["Advance the selection to the note just entered"
+ 		selection := Array with: sel first with: sel third + 1 with: sel third + 1].
+ 
+ 	"This is all horribly inefficient..."
+ 	scorePlayer updateDuration.
+ 	(x := self xForTime: noteEvent endTime) > (self right - 30) ifTrue:
+ 		[self autoScrollForX: x + (30 + self width // 4)].
+ 	self updateLowestNote.
+ 	self rebuildFromScore!

Item was added:
+ ----- Method: PianoRollScoreMorph>>autoScrollForX: (in category 'scrolling') -----
+ autoScrollForX: x
+ 	"Scroll by the amount x lies outside of my innerBounds.  Return true if this happens."
+ 
+ 	| d ticks |
+ 	((d := x - self innerBounds right) > 0
+ 		or: [(d := x - self innerBounds left) < 0])
+ 		ifTrue: [ticks := (self timeForX: self bounds center x + d+1)
+ 						min: score durationInTicks max: 0.
+ 				self moveCursorToTime: ticks.
+ 				scorePlayer ticksSinceStart: ticks.
+ 				^ true].
+ 	^ false
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>beatLinesOnOff (in category 'menu') -----
+ beatLinesOnOff
+ 
+ 	showBeatLines := showBeatLines not.
+ 	self changed!

Item was added:
+ ----- Method: PianoRollScoreMorph>>beatsPerMeasure: (in category 'accessing') -----
+ beatsPerMeasure: n
+ 
+ 	^ self timeSignature: n over: notePerBeat!

Item was added:
+ ----- Method: PianoRollScoreMorph>>contractTime (in category 'geometry') -----
+ contractTime
+ 
+ 	timeScale := timeScale / 1.5.
+ 	self rebuildFromScore.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>copySelection (in category 'editing') -----
+ copySelection
+ 	selection isNil ifTrue: [^self].
+ 	NotePasteBuffer := (score tracks at: selection first) 
+ 				copyFrom: selection second
+ 				to: selection third!

Item was added:
+ ----- Method: PianoRollScoreMorph>>cutSelection (in category 'editing') -----
+ cutSelection
+ 	selection isNil ifTrue: [^self].
+ 	self copySelection.
+ 	self deleteSelection!

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

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

Item was added:
+ ----- Method: PianoRollScoreMorph>>deleteSelection (in category 'editing') -----
+ deleteSelection
+ 	| selMorphs priorEvent x |
+ 	(selection isNil or: [selection second = 0]) ifTrue: [^self].
+ 	score cutSelection: selection.
+ 	selection second > 1 
+ 		ifTrue: 
+ 			[selection at: 2 put: selection second - 1.
+ 			selection at: 3 put: selection second.
+ 			priorEvent := (score tracks at: selection first) at: selection second.
+ 			(x := self xForTime: priorEvent time) < (self left + 30) 
+ 				ifTrue: [self autoScrollForX: x - ((30 + self width) // 4)]]
+ 		ifFalse: [selection := nil].
+ 	scorePlayer updateDuration.
+ 	self rebuildFromScore.
+ 	selMorphs := self 
+ 				submorphsSatisfying: [:m | (m isKindOf: PianoRollNoteMorph) and: [m selected]].
+ 	selMorphs isEmpty ifFalse: [(selMorphs last noteOfDuration: 0.3) play]!

Item was added:
+ ----- Method: PianoRollScoreMorph>>drawMeasureLinesOn: (in category 'drawing') -----
+ drawMeasureLinesOn: aCanvas
+ 
+ 	| ticksPerMeas x measureLineColor inner |
+ 	showBeatLines ifNil: [showBeatLines := false].
+ 	showMeasureLines ifNil: [showMeasureLines := true].
+ 	notePerBeat ifNil: [self timeSignature: 4 over: 4].
+ 	showBeatLines ifTrue:
+ 		[measureLineColor := Color gray: 0.8.
+ 		ticksPerMeas := score ticksPerQuarterNote.
+ 		inner := self innerBounds.
+ 		(leftEdgeTime + ticksPerMeas truncateTo: ticksPerMeas)
+ 			to: ((self timeForX: self right - borderWidth) truncateTo: ticksPerMeas)
+ 			by: ticksPerMeas
+ 			do: [:tickTime | x := self xForTime: tickTime.
+ 				aCanvas fillRectangle: (x @ inner top extent: 1 @ inner height)
+ 					color: measureLineColor]].
+ 
+ 	showMeasureLines ifTrue:
+ 		[measureLineColor := Color gray: 0.7.
+ 		ticksPerMeas := beatsPerMeasure*score ticksPerQuarterNote*4//notePerBeat.
+ 		inner := self innerBounds.
+ 		(leftEdgeTime + ticksPerMeas truncateTo: ticksPerMeas)
+ 			to: ((self timeForX: self right - borderWidth) truncateTo: ticksPerMeas)
+ 			by: ticksPerMeas
+ 			do: [:tickTime | x := self xForTime: tickTime.
+ 				aCanvas fillRectangle: (x @ inner top extent: 1 @ inner height)
+ 						color: (tickTime = 0 ifTrue: [Color black] ifFalse: [measureLineColor])]].
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>drawOn: (in category 'drawing') -----
+ drawOn: aCanvas
+ 
+ 	super drawOn: aCanvas.
+ 	self drawStaffOn: aCanvas.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>drawStaffOn: (in category 'drawing') -----
+ drawStaffOn: aCanvas
+ 
+ 	| blackKeyColor l r topEdge y |
+ 	self drawMeasureLinesOn: aCanvas.
+ 
+ 	blackKeyColor := Color gray: 0.5.
+ 	l := self left + borderWidth.
+ 	r := self right - borderWidth.
+ 	topEdge := self top + borderWidth + 3.
+ 	lowestNote to: 127 do: [:k |
+ 		y := self yForMidiKey: k.
+ 		y <= topEdge ifTrue: [^ self].  "over the top!!"
+ 		(self isBlackKey: k) ifTrue: [
+ 			aCanvas
+ 				fillRectangle: (l at y corner: r@(y + 1))
+ 				color: blackKeyColor]].
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>expandTime (in category 'geometry') -----
+ expandTime
+ 
+ 	timeScale := timeScale * 1.5.
+ 	self rebuildFromScore.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>extent: (in category 'geometry') -----
+ extent: aPoint
+ 	"Force rebuild when re-sized."
+ 
+ 	super extent: aPoint. 
+ 	score ifNotNil: [self updateLowestNote].
+ 	self rebuildFromScore.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>fullBounds (in category 'layout') -----
+ fullBounds
+ 	"Overridden to clip submorph hit detection to my bounds."
+ 
+ 	fullBounds ifNil: [fullBounds := bounds].
+ 	^ bounds
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>goToTime: (in category 'scrolling') -----
+ goToTime: scoreTime
+ 
+ 	| track trackSize index newLeftEdgeTime |
+ 	newLeftEdgeTime := scoreTime asInteger.
+ 	newLeftEdgeTime < leftEdgeTime
+ 		ifTrue: [indexInTrack := Array new: score tracks size+1 withAll: 1].
+ 	leftEdgeTime := newLeftEdgeTime.
+ 	1 to: score tracks size do: [:trackIndex |
+ 		track := score tracks at: trackIndex.
+ 		index := indexInTrack at: trackIndex.
+ 		trackSize := track size.
+ 		[(index < trackSize) and:
+ 		 [(track at: index) endTime < leftEdgeTime]]
+ 			whileTrue: [index := index + 1].
+ 		indexInTrack at: trackIndex put: index].
+ 	self addNotes.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>handlesMouseDown: (in category 'event handling') -----
+ handlesMouseDown: evt
+ 
+ 	^ true!

Item was added:
+ ----- Method: PianoRollScoreMorph>>initialize (in category 'initialization') -----
+ initialize
+ 	"initialize the state of the receiver"
+ 	super initialize.
+ 	""
+ 	
+ 	self extent: 400 @ 300.
+ 	showMeasureLines := true.
+ 	showBeatLines := false.
+ 	self timeSignature: 4 over: 4.
+ 	self clipSubmorphs: true!

Item was added:
+ ----- Method: PianoRollScoreMorph>>insertSelection (in category 'editing') -----
+ insertSelection
+ 	self selection isNil ifTrue: [^self].
+ 	score insertEvents: NotePasteBuffer at: self selection.
+ 	scorePlayer updateDuration.
+ 	self rebuildFromScore!

Item was added:
+ ----- Method: PianoRollScoreMorph>>insertTransposed (in category 'editing') -----
+ insertTransposed
+ 	| delta transposedNotes |
+ 	(delta := UIManager default 
+ 		chooseFrom: ((12 to: -12 by: -1) collect: [:i | i printString])
+ 		values: ((12 to: -12 by: -1) collect: [:i | i printString])
+ 		title: 'offset...') ifNil: [^self].
+ 	transposedNotes := NotePasteBuffer 
+ 				collect: [:note | note copy midiKey: note midiKey + delta].
+ 	selection isNil ifTrue: [^self].
+ 	score insertEvents: transposedNotes at: self selection.
+ 	scorePlayer updateDuration.
+ 	self rebuildFromScore!

Item was added:
+ ----- Method: PianoRollScoreMorph>>invokeScoreMenu: (in category 'menu') -----
+ invokeScoreMenu: evt
+ 	"Invoke the score's edit menu."
+ 
+ 	| menu subMenu |
+ 	menu := MenuMorph new defaultTarget: self.
+ 	menu addList:
+ 		{{'cut' translated.		#cutSelection}.
+ 		{'copy' translated.		#copySelection}.
+ 		{'paste' translated.		#insertSelection}.
+ 		{'paste...' translated.		#insertTransposed}}.
+ 	menu addLine.
+ 	menu addList:
+ 		{{'legato' translated.		#selectionBeLegato}.
+ 		{'staccato' translated.	#selectionBeStaccato}.
+ 		{'normal' translated.		#selectionBeNormal}}.
+ 	menu addLine.
+ 	menu addList:
+ 		{{'expand time' translated.		#expandTime}.
+ 		{'contract time' translated.		#contractTime}}.
+ 	menu addLine.
+ 	subMenu := MenuMorph new defaultTarget: self.
+ 		(2 to: 12) do: [:i | subMenu add: i printString selector: #beatsPerMeasure: argument: i].
+ 		menu add: 'time   ' translated, beatsPerMeasure printString subMenu: subMenu.
+ 	subMenu := MenuMorph new defaultTarget: self.
+ 		#(2 4 8) do: [:i | subMenu add: i printString selector: #notePerBeat: argument: i].
+ 		menu add: 'sig     ' translated, notePerBeat printString subMenu: subMenu.
+ 	menu addLine.
+ 	showMeasureLines
+ 		ifTrue: [menu add: 'hide measure lines' translated action: #measureLinesOnOff]
+ 		ifFalse: [menu add: 'show measure lines' translated action: #measureLinesOnOff].
+ 	showBeatLines
+ 		ifTrue: [menu add: 'hide beat lines' translated action: #beatLinesOnOff]
+ 		ifFalse: [menu add: 'show beat lines' translated action: #beatLinesOnOff].
+ 
+ 	menu addLine.
+ 	menu add: 'add keyboard' translated action: #addKeyboard.
+ 
+ 	menu popUpEvent: evt in: self world.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>isBlackKey: (in category 'drawing') -----
+ isBlackKey: midiKey
+ 	"Answer true if the given MIDI key corresponds to a black key on the piano keyboard."
+ 
+ 	| note |
+ 	note := midiKey \\ 12.
+ 	note = 1 ifTrue: [^ true].
+ 	note = 3 ifTrue: [^ true].
+ 	note = 6 ifTrue: [^ true].
+ 	note = 8 ifTrue: [^ true].
+ 	note = 10 ifTrue: [^ true].
+ 	^ false
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>layoutChanged (in category 'layout') -----
+ layoutChanged
+ 	"Override this to avoid propagating 'layoutChanged' when just adding/removing note objects."
+ 
+ 	fullBounds = bounds ifTrue: [^ self].
+ 	super layoutChanged.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>measureLinesOnOff (in category 'menu') -----
+ measureLinesOnOff
+ 
+ 	showMeasureLines := showMeasureLines not.
+ 	self changed!

Item was added:
+ ----- Method: PianoRollScoreMorph>>midiKeyForY: (in category 'geometry') -----
+ midiKeyForY: y
+ 
+ 	^ lowestNote - ((y - (bounds bottom - borderWidth - 4)) // 3)
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>mouseDown: (in category 'event handling') -----
+ mouseDown: evt
+ 
+ 	| noteMorphs chordRect |
+ 	(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.
+ 		soundsPlaying at: m put: sound.
+ 		SoundPlayer resumePlaying: sound quickStart: false].
+ 
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>mouseMove: (in category 'event handling') -----
+ mouseMove: evt
+ 
+ 	| noteMorphs chordRect |
+ 	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"
+ 		(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 added:
+ ----- Method: PianoRollScoreMorph>>mouseUp: (in category 'event handling') -----
+ mouseUp: evt
+ 
+ 	soundsPlayingMorph ifNotNil: [soundsPlayingMorph delete].
+ 	soundsPlaying ifNotNil: [soundsPlaying do: [:s | s stopGracefully]].
+ 	soundsPlayingMorph := soundsPlaying := nil
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>moveCursorToTime: (in category 'scrolling') -----
+ moveCursorToTime: scoreTime
+ 
+ 	| cursorOffset desiredCursorHeight |
+ 	scorePlayer isPlaying
+ 		ifTrue:
+ 			[cursorOffset := ((scoreTime - leftEdgeTime) asFloat * timeScale) asInteger.
+ 			(cursorOffset < 0
+ 				or: [cursorOffset > (self width-20)])
+ 				ifTrue:
+ 				[self goToTime: scoreTime - (20/timeScale).
+ 				cursorOffset := ((scoreTime - leftEdgeTime) asFloat * timeScale) asInteger]]
+ 		ifFalse:
+ 			[self goToTime: (scoreTime - (self width//2 / timeScale)
+ 							max: (self width//10 / timeScale) negated).
+ 			cursorOffset := ((scoreTime - leftEdgeTime) asFloat * timeScale) asInteger].
+ 
+ 	cursor position: (self left + borderWidth + cursorOffset)@(self top + borderWidth).
+ 	desiredCursorHeight := self height.
+ 	cursor height ~= desiredCursorHeight ifTrue: [cursor extent: 1 at desiredCursorHeight].
+ !

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

Item was added:
+ ----- Method: PianoRollScoreMorph>>movieClipPlayer: (in category 'accessing') -----
+ movieClipPlayer: moviePlayer
+ 
+ 	movieClipPlayer := moviePlayer
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>notePerBeat: (in category 'accessing') -----
+ notePerBeat: n
+ 
+ 	^ self timeSignature: beatsPerMeasure over: n!

Item was added:
+ ----- Method: PianoRollScoreMorph>>notesInRect: (in category 'scrolling') -----
+ notesInRect: timeSlice
+ 
+ 	^ self submorphsSatisfying:
+ 		[:m | (timeSlice intersects: m bounds)
+ 				and: [m isKindOf: PianoRollNoteMorph]]!

Item was added:
+ ----- Method: PianoRollScoreMorph>>on: (in category 'initialization') -----
+ on: aScorePlayer
+ 
+ 	scorePlayer := aScorePlayer.
+ 	score := aScorePlayer score.
+ 	colorForTrack := Color wheel: score tracks size.
+ 	leftEdgeTime := 0.
+ 	timeScale := 0.1.
+ 	indexInTrack := Array new: score tracks size withAll: 1.
+ 	lastUpdateTick := -1.
+ 
+ 	self updateLowestNote
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>rebuildFromScore (in category 'drawing') -----
+ rebuildFromScore
+ 	"Rebuild my submorphs from the score. This method should be invoked after changing the time scale, the color or visibility of a track, the extent of this morph, etc."
+ 
+ 	score ifNil: [^ self].
+ 	self addNotes.
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>removedMorph: (in category 'private') -----
+ removedMorph: aMorph
+ 	| trackSize |
+ 	trackSize := score ambientTrack size.
+ 	score removeAmbientEventWithMorph: aMorph.
+ 	trackSize = score ambientTrack size ifFalse:
+ 		["Update duration if we removed an event"
+ 		scorePlayer updateDuration].
+ 	^super removedMorph: aMorph!

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

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

Item was added:
+ ----- Method: PianoRollScoreMorph>>selection (in category 'accessing') -----
+ selection
+ 	"Returns an array of 3 elements:
+ 		trackIndex
+ 		indexInTrack of first note
+ 		indexInTrack of last note"
+ 
+ 	| trackIndex track |
+ 	selection ifNil:  "If no selection, return last event of 1st non-muted track (or nil)"
+ 		[trackIndex := (1 to: score tracks size)
+ 			detect: [:i | (scorePlayer mutedForTrack: i) not] ifNone: [^ nil].
+ 		track := score tracks at: trackIndex.
+ 		^ Array with: trackIndex with: track size with: track size].
+ 	(scorePlayer mutedForTrack: selection first)
+ 		ifTrue: [selection := nil.  ^ self selection].
+ 	^ selection!

Item was added:
+ ----- Method: PianoRollScoreMorph>>selection: (in category 'accessing') -----
+ selection: anArray
+ 
+ 	selection := anArray!

Item was added:
+ ----- Method: PianoRollScoreMorph>>step (in category 'stepping and presenter') -----
+ step
+ 
+ 	| t |
+ 	score ifNil: [^ self].
+ 
+ 	lastMutedState ~= scorePlayer mutedState ifTrue: [
+ 		self rebuildFromScore.
+ 		lastMutedState := scorePlayer mutedState copy].
+ 
+ 	t := scorePlayer ticksSinceStart.
+ 	t = lastUpdateTick ifFalse: [
+ 		self moveCursorToTime: t.
+ 		lastUpdateTick := t].
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>stepTime (in category 'testing') -----
+ stepTime
+ 
+ 	^ 0
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>tickTimeAtCursor (in category 'geometry') -----
+ tickTimeAtCursor
+ 	cursor ifNil: [^ 0].
+ 	^ self timeForX: cursor left!

Item was added:
+ ----- Method: PianoRollScoreMorph>>timeForX: (in category 'geometry') -----
+ timeForX: aNumber
+ 
+ 	^ ((aNumber - bounds left - borderWidth) asFloat / timeScale + leftEdgeTime) asInteger!

Item was added:
+ ----- Method: PianoRollScoreMorph>>timeScale (in category 'accessing') -----
+ timeScale
+ 
+ 	^ timeScale  "in pixels per tick"!

Item was added:
+ ----- Method: PianoRollScoreMorph>>timeSignature:over: (in category 'accessing') -----
+ timeSignature: num over: denom
+ 
+ 	beatsPerMeasure := num.
+ 	notePerBeat := denom.  "a number like 2, 4, 8"
+ 	self changed!

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

Item was added:
+ ----- Method: PianoRollScoreMorph>>xForTime: (in category 'geometry') -----
+ xForTime: aNumber
+ 
+ 	^ ((aNumber - leftEdgeTime) asFloat * timeScale) asInteger + bounds left + borderWidth
+ !

Item was added:
+ ----- Method: PianoRollScoreMorph>>yForMidiKey: (in category 'geometry') -----
+ yForMidiKey: midiKey
+ 
+ 	^ (bounds bottom - borderWidth - 4) - (3 * (midiKey - lowestNote))
+ !

Item was added:
+ ----- Method: ProjectNavigationMorph>>buttonSound (in category '*MorphicExtras-Sound') -----
+ buttonSound
+ 
+ 	| myButton m |
+ 
+ 	myButton := RectangleMorph new 
+ 		borderWidth: 1;
+ 		cornerStyle: #rounded;
+ 		borderColor: #raised;
+ 		color: self colorForButtons;
+ 		setBalloonText: 'Change sound volume' translated;
+ 		on: #mouseDown send: #soundDownEvt:morph: to: self;
+ 		on: #mouseStillDown send: #soundStillDownEvt:morph: to: self;
+ 		on: #mouseUp send: #soundUpEvt:morph: to: self;
+ 		yourself.
+ 
+ 	myButton addMorph: (m := self speakerIcon lock).
+ 	myButton extent: m extent + (myButton borderWidth + 6).
+ 	m position: myButton center - (m extent // 2).
+ 	^myButton
+ !

Item was added:
+ ----- Method: ProjectNavigationMorph>>getSoundVolume (in category '*MorphicExtras-Sound') -----
+ getSoundVolume
+ 
+ 	^SoundPlayer soundVolume average!

Item was added:
+ ----- Method: ProjectNavigationMorph>>setSoundVolume: (in category '*MorphicExtras-Sound') -----
+ setSoundVolume: x
+ 
+ 	SoundPlayer setVolumeLeft: x volumeRight: x.
+ !

Item was added:
+ ----- Method: ProjectNavigationMorph>>soundDownEvt:morph: (in category '*MorphicExtras-Sound') -----
+ soundDownEvt: a morph: b
+ 
+ 	soundSlider ifNotNil: [soundSlider delete].
+ 	(soundSlider := RectangleMorph new)
+ 		setProperty: #morphicLayerNumber toValue: 1;
+ 		extent: b width @ (b width * 3);
+ 		color: self colorForButtons;
+ 		borderColor: #raised;
+ 		bottomLeft: b boundsInWorld origin.
+ 	soundSlider addMorph: (
+ 		RectangleMorph new
+ 			color: self colorForButtons;
+ 			borderColor: #raised;
+ 			extent: b width @ 8;
+ 			center: soundSlider center x @ 
+ 				(soundSlider bottom - (soundSlider height * self getSoundVolume) asInteger)
+ 	).
+ 	soundSlider openInWorld.!

Item was added:
+ ----- Method: ProjectNavigationMorph>>soundStillDownEvt:morph: (in category '*MorphicExtras-Sound') -----
+ soundStillDownEvt: evt morph: b
+ 
+ 	| y pct |
+ 
+ 	soundSlider ifNil: [^self].
+ 	y := evt hand position y.
+ 	(y between: soundSlider top and: soundSlider bottom) ifTrue: [
+ 		pct := (soundSlider bottom - y) asFloat / soundSlider height.
+ 		self setSoundVolume: pct.
+ 		soundSlider firstSubmorph top: y - 5.
+ 	]. 
+ !

Item was added:
+ ----- Method: ProjectNavigationMorph>>soundUpEvt:morph: (in category '*MorphicExtras-Sound') -----
+ soundUpEvt: a morph: b
+ 
+ 	soundSlider ifNotNil: [soundSlider delete].
+ 	soundSlider := nil.
+ 	Beeper beep !

Item was added:
+ ----- Method: ProjectNavigationMorph>>speakerIcon (in category '*MorphicExtras-Sound') -----
+ speakerIcon
+ 
+ 
+ 	^ImageMorph new
+ 			image: (
+ (Form
+ 	extent: 19 at 18
+ 	depth: 8
+ 	fromArray: #( 0 0 1493172224 0 0 0 0 1493172224 0 0 0 138 1493172224 0 0 0 35509 2315255808 0 0 0 9090522 2315255808 0 0 0 2327173887 2315255819 0 0 138 3051028442 2315255819 0 0 1505080590 4294957786 2315255808 184549376 0 3053453311 4292532917 1493172224 184549376 0 1505080714 3048584629 1493172224 184549376 0 9079434 3048584629 1493172224 184549376 0 138 2327164341 1493172235 0 0 0 2324346293 1493172235 0 0 0 9079477 1493172224 0 0 0 35466 1493172224 0 0 0 138 0 0 0 0 0 0 0 0 0 0 0 0 0)
+ 	offset: 0 at 0)
+ 			);
+ 			setBalloonText: 'Quiet';
+ 			on: #mouseUp send: #yourself to: 1
+ 	!

Item was added:
+ ----- Method: ZASMCameraMarkMorph>>addMorphsTo:pianoRoll:eventTime:betweenTime:and: (in category 'piano rolls') -----
+ addMorphsTo: morphList pianoRoll: pianoRoll eventTime: t betweenTime: leftTime and: rightTime
+ 
+ 	| startX pseudoEndTime |
+ 
+ 	startX := pianoRoll xForTime: startTimeInScore.
+ 	pseudoEndTime := pianoRoll timeForX: startX + self width.
+ 	startTimeInScore > rightTime ifTrue: [^ self].  
+ 	pseudoEndTime < leftTime ifTrue: [^ self].
+ 
+ 	morphList add: 
+ 		(self align: self bottomLeft
+ 			with: startX @ self bottom).
+ 
+ !

Item was added:
+ ----- Method: ZASMCameraMarkMorph>>encounteredAtTime:inScorePlayer:atIndex:inEventTrack:secsPerTick: (in category 'piano rolls') -----
+ encounteredAtTime: ticks inScorePlayer: scorePlayer atIndex: index inEventTrack: track secsPerTick: secsPerTick
+ 
+ 	| nextAmbient m nextDurationInMs program now finalMark thisPage nextPage |
+ 
+ 	self gotoMark.
+ 	nextAmbient := nil.
+ 	index to: track size do: [ :i |
+ 		(nextAmbient isNil and: [((m := track at: i) morph) isKindOf: self class]) ifTrue: [
+ 			nextAmbient := m.
+ 		].
+ 	].
+ 	nextAmbient ifNil: [^self].
+ 	nextDurationInMs := (nextAmbient time - ticks * secsPerTick * 1000) rounded.
+ 	finalMark := nextAmbient morph.
+ 	thisPage := self valueOfProperty: #bookPage.
+ 	nextPage := finalMark valueOfProperty: #bookPage.
+ 	(thisPage = nextPage or: [thisPage isNil | nextPage isNil]) ifFalse: [^finalMark gotoMark].
+ 	now := Time millisecondClockValue.
+ 	program := Dictionary new.
+ 	program
+ 		at: #startTime put: now;
+ 		at: #endTime put: now + nextDurationInMs;
+ 		at: #startPoint put: (self valueOfProperty: #cameraPoint);
+ 		at: #endPoint put: (finalMark valueOfProperty: #cameraPoint);
+ 		at: #startZoom put: (self valueOfProperty: #cameraScale);
+ 		at: #endZoom put: (finalMark valueOfProperty: #cameraScale).
+ 
+ 	self cameraController setProgrammedMoves: {program}.
+ 
+ !

Item was added:
+ ----- Method: ZASMCameraMarkMorph>>pauseFrom: (in category 'piano rolls') -----
+ pauseFrom: scorePlayer
+ 
+ 	self cameraController pauseProgrammedMoves.!

Item was added:
+ ----- Method: ZASMCameraMarkMorph>>resumeFrom: (in category 'piano rolls') -----
+ resumeFrom: scorePlayer
+ 
+ 	self cameraController resumeProgrammedMoves!



More information about the Packages mailing list