[squeak-dev] The Inbox: MorphicExtras-kfr.254.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Feb 28 14:27:28 UTC 2019


A new version of MorphicExtras was added to project The Inbox:
http://source.squeak.org/inbox/MorphicExtras-kfr.254.mcz

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

Name: MorphicExtras-kfr.254
Author: kfr
Time: 28 February 2019, 3:27:07.129575 pm
UUID: 9e0ac524-c2e1-44e1-a258-b2b5a7755fc8
Ancestors: MorphicExtras-kfr.253

Update extent form halo handle. Only grow allow extent to grow.

Unlimited undo of SketchMorphEditor. Just add current form to a collection. 
Redo with holding shift down while undo.
This is a memory hog of a change. Must be reviewed

=============== Diff against MorphicExtras-kfr.253 ===============

Item was changed:
  Morph subclass: #SketchEditorMorph
+ 	instanceVariableNames: 'hostView palette ticksToDwell rotationCenter registrationPoint newPicBlock emptyPicBlock paintingForm dimForm formCanvas rotationButton scaleButton cumRot cumMag undoBuffer enclosingPasteUpMorph forEachHand firstUndoFlag undoBufferIndex'
- 	instanceVariableNames: 'hostView palette ticksToDwell rotationCenter registrationPoint newPicBlock emptyPicBlock paintingForm dimForm formCanvas rotationButton scaleButton cumRot cumMag undoBuffer enclosingPasteUpMorph forEachHand'
  	classVariableNames: 'SketchTimes'
  	poolDictionaries: ''
  	category: 'MorphicExtras-Support'!
  
  !SketchEditorMorph commentStamp: '<historical>' prior: 0!
  Inst vars (converting to morphic events)
  hostView -- SketchMorph we are working on.
  stampForm -- Stamp is stored here.
  canvasRectangle -- later use bounds
  palette -- the PaintBox interface Morph
  dirty -- not used
  currentColor 
  ticksToDwell rotationCenter registrationPoint 
  newPicBlock -- do this after painting
  action -- selector of painting action
  paintingForm -- our copy
  composite -- now paintArea origin.  world relative.  stop using it.
  dimForm -- SketchMorph of the dimmed background.  Opaque.  
  		installed behind the editor morph.
  buff 
  brush -- 1-bit Form of the brush, 
  paintingFormPen 
  formCanvas -- Aim it at paintingForm to allow it to draw ovals, rectangles, lines, etc.
  picToComp dimToComp compToDisplay -- used to composite -- obsolete
  picToBuff brushToBuff buffToBuff buffToPic 
  rotationButton scaleButton -- submorphs, handles to do these actions.
  strokeOrigin -- During Pickup, origin of rect. 
  cumRot cumMag -- cumulative for multiple operations from same original
  undoBuffer 
  lastEvent 
  currentNib -- 1 bit deep form.
  
  
  For now, we do not carry the SketchMorph's registration point, rotation center, or ticksToDwell.
  
  New -- using transform morphs to rotate the finished player.  How get it rotated back and the rotationDegrees to be right?  We cancel out rotationDegrees, so how remember it?
  
  Registration point convention:  
  In a GraphicFrame, reg point is relative to this image's origin.
  During painting, it is relative to canvasRectangle origin, and thus us absolute within the canvas.  To convert back, subract newBox origin.
  
  Be sure to convert back and forth correctly.  In deliverPainting. initializeFromFrame:inView: !

Item was changed:
+ ----- Method: SketchEditorMorph>>extent: (in category 'morphic') -----
+ extent: aPoint 
+ 	| form |
+ 	paintingForm ifNil: [^super extent: aPoint].
+ 	super extent: aPoint.
- ----- Method: SketchEditorMorph>>extent: (in category 'actions & preps') -----
- extent: aPoint
-  | form |
- super extent: aPoint.
-    paintingForm ifNotNil:[ 
  	form := Form extent: self extent depth: paintingForm depth.
  	paintingForm displayOn: form.
  	paintingForm := form.
+ 	forEachHand do: [:i | i at: #changed put: true].
+ 	rotationButton position: bounds topCenter - (6 at 0).		
+ 	scaleButton position: bounds rightCenter - ((scaleButton width)@6).
+ 	
+ 	!
-       forEachHand do:[ :i| i at:#changed put: true]
-     ]!

Item was changed:
  ----- Method: SketchEditorMorph>>initializeFor:inBounds:pasteUpMorph:paintBoxPosition: (in category 'initialization') -----
  initializeFor: aSketchMorph inBounds: boundsToUse pasteUpMorph: aPasteUpMorph paintBoxPosition: aPosition
  	"NB: if aPosition is nil, then it's assumed that the paintbox is obtained from a flap or some such, so do nothing special regarding a palette in this case.  The palette needs already to be in the world for this to work."
  	| w  |
  	(w := aPasteUpMorph world) addMorphInLayer: self.	"in back of palette"
  	enclosingPasteUpMorph := aPasteUpMorph.
  	hostView := aSketchMorph.  "may be ownerless"
  	self bounds: boundsToUse.
  	palette := w paintBox focusMorph: self.
  	palette beStatic.		"give Nebraska whatever help we can"
  	palette addWeakDependent: self.
  	aPosition ifNotNil:
  		[w addMorphFront: palette.  "bring to front"
  		palette position: aPosition].
  	paintingForm := Form extent: bounds extent depth: w assuredCanvas depth.
  	self dimTheWindow.
  	self addRotationScaleHandles.
  	aSketchMorph ifNotNil:
  		[
  		aSketchMorph form
  			displayOn: paintingForm
  			at: (hostView boundsInWorld origin - bounds origin - hostView form offset)
  			clippingBox: (0 at 0 extent: paintingForm extent)
  			rule: Form over
  			fillColor: nil.  "assume they are the same depth".
+ 			undoBuffer := OrderedCollection new.
+ 			undoBuffer add: paintingForm deepCopy.
- 			undoBuffer := paintingForm deepCopy.
  		rotationCenter := aSketchMorph rotationCenter]!

Item was changed:
  ----- Method: SketchEditorMorph>>mouseDown: (in category 'morphic') -----
  mouseDown: evt
  	"Start a new stroke.  Check if any palette setting have changed.  6/11/97 20:30 tk"
  	| cur pfPen myAction |
  	"verify that we are in a good state"
  	self verifyState: evt.		"includes prepareToPaint and #scalingOrRotate"
  	pfPen := self get: #paintingFormPen for: evt.
+ 	undoBuffer add: paintingForm deepCopy.
+ 	firstUndoFlag := true.
- 	paintingForm extent = undoBuffer extent ifTrue: [
- 		paintingForm displayOn: undoBuffer at: 0 at 0 rule: Form over.
- 	] ifFalse: [
- 		undoBuffer := paintingForm deepCopy.	"know we will draw something"
- 	].
  	pfPen place: (evt cursorPoint - bounds origin).
  	myAction := self getActionFor: evt.
  	palette colorable ifTrue:[
  		palette recentColor: (self getColorFor: evt)].
  	self set: #strokeOrigin for: evt to: evt cursorPoint.
  		"origin point for pickup: rect: ellispe: polygon: line: star:.  Always take it."
  	myAction == #pickup: ifTrue: [
  		cur := Cursor corner shallowCopy.
  		cur offset: 0 at 0  "cur offset abs".
  		evt hand showTemporaryCursor: cur].
  	myAction == #polygon: ifTrue: [self polyNew: evt].	"a mode lets you drag vertices"
  	self mouseMove: evt.!

Item was changed:
  ----- Method: SketchEditorMorph>>restoreRect: (in category 'actions & preps') -----
  restoreRect: oldRect
  	"Restore the given rectangular area of the painting Form from the undo buffer."
  
+ 	formCanvas drawImage: undoBuffer last
- 	formCanvas drawImage: undoBuffer
  		at: oldRect origin
  		sourceRect: (oldRect translateBy: self topLeft negated).
  	self invalidRect: oldRect.
  !

Item was changed:
  ----- Method: SketchEditorMorph>>rotateBy: (in category 'actions & preps') -----
  rotateBy: evt 
  	"Left-right is rotation. 3/26/97 tk Slider at top of window. 4/3/97 tk"
  	| pt temp amt smooth myBuff |
+       undoBuffer add: paintingForm deepCopy.
+       firstUndoFlag := true.
- 
  	myBuff := self get: #buff for: evt.
  	evt cursorPoint x - self left < 20
  		ifTrue: [^ self flipHoriz: evt].
  	"at left end flip horizontal"
  	evt cursorPoint x - self right > -20
  		ifTrue: [^ self flipVert: evt].
  	"at right end flip vertical"
  	pt := evt cursorPoint - bounds center.
  	smooth := 2.
  	"paintingForm depth > 8 ifTrue: [2] ifFalse: [1]."
  	"Could go back to 1 for speed"
  	amt := pt x abs < 12
  				ifTrue: ["detent"
  					0]
  				ifFalse: [pt x - (12 * pt x abs // pt x)].
  	amt := amt * 1.8.
  	temp := myBuff
  				rotateBy: amt
  				magnify: cumMag
  				smoothing: smooth.
  	temp displayOn: paintingForm at: paintingForm center - temp center + myBuff offset.
  	rotationButton position: evt cursorPoint x - 6 @ rotationButton position y.
  	self render: bounds.
  	cumRot := amt!

Item was changed:
  ----- Method: SketchEditorMorph>>scaleBy: (in category 'actions & preps') -----
  scaleBy: evt 
  	"up-down is scale. 3/26/97 tk Now a slider on the right."
  	| pt temp cy oldRect amt myBuff |
+       undoBuffer add: paintingForm deepCopy.
+       firstUndoFlag := true.
- 
  	myBuff := self get: #buff for: evt.
  	pt := evt cursorPoint - bounds center.
  	cy := bounds height * 0.5.
  	oldRect := myBuff boundingBox expandBy: myBuff extent * cumMag / 2.
  	amt := pt y abs < 12
  				ifTrue: ["detent"
  					1.0]
  				ifFalse: [pt y - (12 * pt y abs // pt x)].
  	amt := amt asFloat / cy + 1.0.
  	temp := myBuff
  				rotateBy: cumRot
  				magnify: amt
  				smoothing: 2.
  	cumMag > amt
  		ifTrue: ["shrinking"
  			oldRect := oldRect translateBy: paintingForm center - oldRect center + myBuff offset.
  			paintingForm
  				fill: (oldRect expandBy: 1 @ 1)
  				rule: Form over
  				fillColor: Color transparent].
  	temp displayOn: paintingForm at: paintingForm center - temp center + myBuff offset.
  	scaleButton position: scaleButton position x @ (evt cursorPoint y - 6).
  	self render: bounds.
  	cumMag := amt!

Item was added:
+ ----- Method: SketchEditorMorph>>setExtentFromHalo: (in category 'morphic') -----
+ setExtentFromHalo: anExtent
+ 	"The user has dragged the grow box such that the receiver's extent would be anExtent.  Do what's needed"
+ 	
+ 	super setExtentFromHalo: ((anExtent x max: paintingForm width) @ (anExtent y max: paintingForm height)).
+ !

Item was changed:
  ----- Method: SketchEditorMorph>>undo: (in category 'start & finish') -----
  undo: evt 
  	"revert to a previous state.  "
  
+ 	| poly pen |
- 	| temp poly pen |
  	self flag: #bob.	"what is undo in multihand environment?"
  	undoBuffer ifNil: [^Beeper beep].	"nothing to go back to"
  	(poly := self valueOfProperty: #polygon) ifNotNil: 
  			[poly delete.
  			self setProperty: #polygon toValue: nil.
  			self polyEditing: false.
  			^self].
+ 	firstUndoFlag ifTrue:[
+ 	undoBuffer add: paintingForm deepCopy.
+ 	firstUndoFlag := false.
+ 	undoBufferIndex := undoBuffer size].
+       evt shiftPressed 
+                ifTrue:[undoBufferIndex := undoBufferIndex + 1.
+ 	paintingForm := undoBuffer at: undoBufferIndex  ifAbsent:[^self inform:'Nothing to redo']]
+                ifFalse:[undoBufferIndex := undoBufferIndex - 1.
+ 	paintingForm := undoBuffer at: undoBufferIndex  ifAbsent:[^self inform:'Nothing to undo']].
- 	temp := paintingForm.
- 	paintingForm := undoBuffer.
- 	undoBuffer := temp.	"can get back to what you had by undoing again"
  	pen := self get: #paintingFormPen for: evt.
  	pen ifNil: [^Beeper  beep].
  	pen setDestForm: paintingForm.
  	formCanvas := paintingForm getCanvas.	"used for lines, ovals, etc."
  	formCanvas := formCanvas copyOrigin: self topLeft negated
  				clipRect: (0 @ 0 extent: bounds extent).
  	self render: bounds!



More information about the Squeak-dev mailing list