[Pkg] The Trunk: MorphicExtras-kfr.255.mcz

commits at source.squeak.org commits at source.squeak.org
Tue May 21 19:28:17 UTC 2019


Karl Ramberg uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-kfr.255.mcz

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

Name: MorphicExtras-kfr.255
Author: kfr
Time: 17 May 2019, 11:21:22.449469 pm
UUID: c061d985-306a-a842-86cc-dfbcfd880fed
Ancestors: MorphicExtras-ms.254

Add input for a selection of chord types possible in KeyboardMorphForInput.

=============== Diff against MorphicExtras-ms.254 ===============

Item was changed:
  PianoKeyboardMorph subclass: #KeyboardMorphForInput
+ 	instanceVariableNames: 'pianoRoll duration durationModifier articulation buildingChord insertMode prevSelection startOfNextNote chordSemitones chordDictionary'
- 	instanceVariableNames: 'pianoRoll duration durationModifier articulation buildingChord insertMode prevSelection startOfNextNote'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'MorphicExtras-SoundInterface'!
  
  !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>>addChordControls (in category 'initialization') -----
+ addChordControls
+ 	| switch chordRow |
+       chordRow := AlignmentMorph newRow.
+       chordRow color: color; borderWidth: 0; layoutInset: 0.
+ 	chordRow 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.
+ 	chordRow addMorphBack: (switch label: 'maj' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(maj)).
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'min' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(min)). 
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'dim' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(dim)). 
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'maj7' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(maj7)). 
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'min7' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(min7)). 
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'dom7' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(dom7)). 
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'sus2' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(sus2)). 
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'sus4' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(sus4)). 
+ 	switch := SimpleSwitchMorph new target: self; borderWidth: 2;
+ 		offColor: color; onColor: (Color r: 1.0 g: 0.6 b: 0.6); setSwitchState: false.
+ 	chordRow addMorphBack: (switch label: 'aug' translated;
+ 				actionSelector: #chords:onOff:; arguments: #(aug)). 
+ 	^chordRow
+ !

Item was added:
+ ----- Method: KeyboardMorphForInput>>addNoteEventAt:rootNote: (in category 'simple keyboard') -----
+ addNoteEventAt: eventTime rootNote: rootNote
+    | noteEvent noteEvents semitones |
+    semitones := chordSemitones.
+    buildingChord ifFalse:[ semitones := #(0)].
+    noteEvents := OrderedCollection new.
+    semitones do:
+    [: semitone | noteEvent := NoteEvent new time: eventTime; duration: self noteDuration;
+ 			key: rootNote + semitone velocity: self velocity channel: 1.
+ 			pianoRoll appendEvent: noteEvent fullDuration: self fullDuration.
+ 			noteEvents add: noteEvent].
+   ^noteEvents!

Item was changed:
  ----- Method: KeyboardMorphForInput>>addRecordingControls (in category 'initialization') -----
  addRecordingControls
+ 	| button switch playRow durRow articRow modRow chordRow |
- 	| 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;
  		borderStyle: (BorderStyle raised width: 2); color: color.
  	playRow addMorphBack: (button label: '          rest          ' translated; actionSelector: #emitRest).
  	button := SimpleButtonMorph new target: self;
  		borderStyle: (BorderStyle raised width: 2); color: color.
  	playRow addMorphBack: (button label: 'del' translated; actionSelector: #deleteNotes).
  	self addMorph: playRow.
  	playRow align: playRow fullBounds topCenter
  			with: self fullBounds bottomCenter.
+       
+       chordRow := self addChordControls.
+       self addMorph: chordRow.
+ 	chordRow align: chordRow fullBounds topCenter
+ 			with: playRow 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: chordRow fullBounds bottomCenter.
- 			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 @ self borderWidth))
  !

Item was changed:
  ----- Method: KeyboardMorphForInput>>buildChord: (in category 'note controls') -----
+ buildChord: onOff
+ 	buildingChord := buildingChord not.!
- buildChord: onOff!

Item was added:
+ ----- Method: KeyboardMorphForInput>>chords:onOff: (in category 'note controls') -----
+ chords: chord onOff: ignored   
+ 	"Select the semi tones of the chord from the chordDictonary."
+ 
+ 	self allMorphsDo:
+ 		[:m | ((m isMemberOf: SimpleSwitchMorph)
+ 				and: [m actionSelector == #chords:onOff:])
+ 				ifTrue: [m setSwitchState: m arguments first = chord]].
+ 	chordSemitones := chordDictionary at: chord.
+ 	!

Item was added:
+ ----- Method: KeyboardMorphForInput>>initChordDictionary (in category 'initialization') -----
+ initChordDictionary
+    
+ chordDictionary :=
+       {'maj' -> #(0 4  7).
+         'min' -> #(0 3 7).
+         'dim' -> #(0 3 6).
+         'maj7' -> #(0 4 7 11).
+         'min7' -> #(0 3 7 10).
+         'dom7' -> #(0 4 7 10).
+         'sus2' -> #(0 2 7).
+         'sus4' -> #(0 5 7).
+         'aug' -> #(0 4 8)} as: Dictionary!

Item was changed:
  ----- 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.
+ 	self initChordDictionary!
- 	insertMode := false!

Item was changed:
  ----- Method: KeyboardMorphForInput>>mouseDownPitch:event:noteMorph: (in category 'simple keyboard') -----
  mouseDownPitch: midiKey event: event noteMorph: keyMorph
  
+ 	| sel noteEvents |
- 	| 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]].
+ 	noteEvents := self addNoteEventAt:startOfNextNote  rootNote: midiKey +23.
- 	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: noteEvents inTrack: sel first) play.
- 	(soundPlaying := self soundForEvent: noteEvent inTrack: sel first) play.
  	prevSelection := pianoRoll selection.
  	startOfNextNote := startOfNextNote + self fullDuration.!

Item was changed:
  ----- Method: KeyboardMorphForInput>>soundForEvent:inTrack: (in category 'events') -----
+ soundForEvent: noteEvents inTrack: trackIndex
- soundForEvent: noteEvent inTrack: trackIndex
  
  	| sound player |
  	player := pianoRoll scorePlayer.
  	sound := MixedSound new.
+ 	noteEvents do:[: noteEvent|
  	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)].
- 						(player volumeForTrack: trackIndex).
  	^ sound
  !

Item was changed:
  ----- 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 soundOfDuration: 0.3) play]!
- 	selMorphs isEmpty ifFalse: [(selMorphs last noteOfDuration: 0.3) play]!



More information about the Packages mailing list