[Pkg] The Trunk: Morphic-ar.445.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jun 18 03:02:55 UTC 2010


Andreas Raab uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-ar.445.mcz

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

Name: Morphic-ar.445
Author: ar
Time: 17 June 2010, 8:01:18.301 pm
UUID: 091eed13-a21e-204e-8c61-81b5bfd4df72
Ancestors: Morphic-ar.444

Several fixes for Morphic:
* Don't shortcut AA lines if aaLevel > 1
* Set warping cellsize properly when doing multi-pass warp
* Do not reset the mouse cursor every single Morphic cycle
* Handle redraws of offscreen Morphic worlds correctly
* Avoid erronous scrolling when accepting large methods in debuggers
* Allow canvas subclasses to know the affected area of redraws


=============== Diff against Morphic-ar.444 ===============

Item was changed:
  ----- Method: WorldState>>doDeferredUpdatingFor: (in category 'update cycle') -----
  doDeferredUpdatingFor: aWorld
          "If this platform supports deferred updates, then make my canvas be the Display (or a rectangular portion of it), set the Display to deferred update mode, and answer true. Otherwise, do nothing and answer false. One can set the class variable DisableDeferredUpdates to true to completely disable the deferred updating feature."
  	| properDisplay |
  	PasteUpMorph disableDeferredUpdates ifTrue: [^ false].
  	(Display deferUpdates: true) ifNil: [^ false].  "deferred updates not supported"
  	remoteServer ifNotNil:[
  		self assuredCanvas.
  		^true].
  	properDisplay := canvas notNil and: [canvas form == Display].
  	aWorld == World ifTrue: [  "this world fills the entire Display"
  		properDisplay ifFalse: [
  			aWorld viewBox: Display boundingBox.    "do first since it may clear canvas"
  			self canvas: (Display getCanvas copyClipRect: Display boundingBox).
  		]
- 	] ifFalse: [  "this world is inside an MVC window"
- 		(properDisplay and: [canvas clipRect = aWorld viewBox]) ifFalse: [
- 			self canvas:
- 				(Display getCanvas copyOffset: 0 at 0 clipRect: aWorld viewBox)
- 		]
  	].
  	^ true
  !

Item was changed:
  ----- Method: FormCanvas>>transformBy:clippingTo:during:smoothing: (in category 'drawing-support') -----
  transformBy: aDisplayTransform clippingTo: aClipRect during: aBlock	 smoothing: cellSize
  
  	"Note: This method has been originally copied from TransformationMorph."
  	| innerRect patchRect sourceQuad warp start subCanvas |
  	(aDisplayTransform isPureTranslation) ifTrue:[
  		^aBlock value: (self copyOffset: aDisplayTransform offset negated truncated
  							clipRect: aClipRect)
  	].
  	"Prepare an appropriate warp from patch to innerRect"
  	innerRect := aClipRect.
  	patchRect := (aDisplayTransform globalBoundsToLocal: innerRect) truncated.
  	sourceQuad := (aDisplayTransform sourceQuadFor: innerRect)
  					collect: [:p | p - patchRect topLeft].
  	warp := self warpFrom: sourceQuad toRect: innerRect.
- 	warp cellSize: cellSize.
  
  	"Render the submorphs visible in the clipping rectangle, as patchForm"
  	start := (self depth = 1 and: [self isShadowDrawing not])
  		"If this is true B&W, then we need a first pass for erasure."
  		ifTrue: [1] ifFalse: [2].
  	start to: 2 do:
  		[:i | "If i=1 we first make a shadow and erase it for opaque whites in B&W"
  		subCanvas := self class extent: patchRect extent depth: self depth.
  		i=1	ifTrue: [subCanvas shadowColor: Color black.
  					warp combinationRule: Form erase]
  			ifFalse: [self isShadowDrawing ifTrue:
  					[subCanvas shadowColor: self shadowColor].
  					warp combinationRule: Form paint].
  		subCanvas translateBy: patchRect topLeft negated
  			during:[:offsetCanvas| aBlock value: offsetCanvas].
+ 		warp sourceForm: subCanvas form; cellSize: cellSize; warpBits.
- 		warp sourceForm: subCanvas form; warpBits.
  		warp sourceForm: nil.  subCanvas := nil "release space for next loop"]
  !

Item was added:
+ ----- Method: HandMorph>>showHardwareCursor: (in category 'drawing') -----
+ showHardwareCursor: aBool
+ 	"Show/hide the current hardware cursor as indicated."
+ 	| cursor |
+ 	cursor :=  hardwareCursor ifNil:[aBool ifTrue:[Cursor normal] ifFalse:[Cursor blank]].
+ 	Sensor currentCursor == cursor ifFalse: [cursor show].
+ !

Item was changed:
  ----- Method: WorldState>>displayWorld:submorphs: (in category 'update cycle') -----
  displayWorld: aWorld submorphs: submorphs
  	"Update this world's display."
  
  	| deferredUpdateMode handsToDraw allDamage |
  
  	submorphs do: [:m | m fullBounds].  "force re-layout if needed"
  	self checkIfUpdateNeeded ifFalse: [^ self].  "display is already up-to-date"
  
  	deferredUpdateMode := self doDeferredUpdatingFor: aWorld.
  	deferredUpdateMode ifFalse: [self assuredCanvas].
  	canvas roundCornersOf: aWorld during:[ | handDamageRects worldDamageRects |
  		worldDamageRects := self drawWorld: aWorld submorphs: submorphs invalidAreasOn: canvas.  "repair world's damage on canvas"
  		"self handsDo:[:h| h noticeDamageRects: worldDamageRects]."
  		handsToDraw := self selectHandsToDrawForDamage: worldDamageRects.
  		handDamageRects := handsToDraw collect: [:h | h savePatchFrom: canvas].
  		allDamage := worldDamageRects, handDamageRects.
  
  		handsToDraw reverseDo: [:h | canvas fullDrawMorph: h].  "draw hands onto world canvas"
  	].
  	"*make this true to flash damaged areas for testing*"
  	Preferences debugShowDamage ifTrue: [aWorld flashRects: allDamage color: Color black].
  
+ 	canvas finish: allDamage.
+ 
- 	canvas finish.
  	"quickly copy altered rects of canvas to Display:"
  	deferredUpdateMode
  		ifTrue: [self forceDamageToScreen: allDamage]
  		ifFalse: [canvas showAt: aWorld viewBox origin invalidRects: allDamage].
  	handsToDraw do: [:h | h restoreSavedPatchOn: canvas].  "restore world canvas under hands"
  	Display deferUpdates: false; forceDisplayUpdate.
  !

Item was added:
+ ----- Method: PasteUpMorph>>canvas: (in category 'project state') -----
+ canvas: aCanvas
+ 	"Set this world's canvas"
+ 
+ 	worldState canvas: aCanvas.
+ !

Item was changed:
  ----- Method: HandMorph>>needsToBeDrawn (in category 'drawing') -----
  needsToBeDrawn
  	"Return true if this hand must be drawn explicitely instead of being drawn via the hardware cursor. This is the case if it (a) it is a remote hand, (b) it is showing a temporary cursor, or (c) it is not empty and there are any visible submorphs. If using the software cursor, ensure that the hardware cursor is hidden."
  	"Details:  Return true if this hand has a saved patch to ensure that is is processed by the world. This saved patch will be deleted after one final display pass when it becomes possible to start using the hardware cursor again. This trick gives us one last display cycle to allow us to remove the software cursor and shadow from the display."
- 	| cursor |
  	(savedPatch notNil
  		or: [ (submorphs anySatisfy: [ :ea | ea visible ])
  			or: [ (temporaryCursor notNil and: [hardwareCursor isNil])
  				or: [ self hasUserInformation ]]])
  		ifTrue: [
  			"using the software cursor; hide the hardware one"
+ 			self showHardwareCursor: false.
- 			Sensor currentCursor == Cursor blank ifFalse: [Cursor blank show].
  			^ true].
- 	"Switch from one hardware cursor to another, if needed."
- 	cursor := hardwareCursor ifNil: [Cursor normal].
- 	Sensor currentCursor == cursor ifFalse: [cursor show].
  	^ false
  !

Item was changed:
  ----- Method: PluggableTextMorph>>accept (in category 'menu commands') -----
  accept 
  	"Inform the model of text to be accepted, and return true if OK."
  
  	| ok saveSelection saveScrollerOffset |
  "sps 8/13/2001 22:41: save selection and scroll info"
  	saveSelection := self selectionInterval copy.
  	saveScrollerOffset := scroller offset copy.
  
  	(self canDiscardEdits and: [(self hasProperty: #alwaysAccept) not])
  		ifTrue: [^ self flash].
  
  	self hasEditingConflicts ifTrue:
  		[(self confirm: 
  'Caution!! This method may have been
  changed elsewhere since you started
  editing it here.  Accept anyway?' translated) ifFalse: [^ self flash]].
  	ok := self acceptTextInModel.
  	ok==true ifTrue:
  		[self setText: self getText.
  		self hasUnacceptedEdits: false.
  		(model dependents detect: [:dep | (dep isKindOf: PluggableTextMorph) and: [dep getTextSelector == #annotation]] ifNone: [nil]) ifNotNil:
  			[:aPane | model changed: #annotation]].
  
  	"sps 8/13/2001 22:41: restore selection and scroll info"
  	["During the step for the browser, updateCodePaneIfNeeded is called, and 
  		invariably resets the contents of the codeholding PluggableTextMorph
  		at that time, resetting the cursor position and scroller in the process.
  		The following line forces that update without waiting for the step, 		then restores the cursor and scrollbar"
  
  	ok ifTrue: "(don't bother if there was an error during compile)"
  		[(model respondsTo: #updateCodePaneIfNeeded) 
  			ifTrue: [model updateCodePaneIfNeeded].
  		WorldState addDeferredUIMessage:
  			[self currentHand newKeyboardFocus: textMorph.
  			scroller offset: saveScrollerOffset.
  			self setScrollDeltas.
+ 			selectionInterval := saveSelection. "restore prior selection"
  			self selectFrom: saveSelection first to: saveSelection last]]]
  
  			on: Error do: []
  !

Item was changed:
  ----- Method: HandMorph>>restoreSavedPatchOn: (in category 'drawing') -----
  restoreSavedPatchOn: aCanvas 
  	"Clear the changed flag and restore the part of the given canvas under this hand from the previously saved patch. If necessary, handle the transition to using the hardware cursor."
- 	| cursor |
  
  	hasChanged := false.
  	savedPatch ifNotNil: 
  			[aCanvas drawImage: savedPatch at: savedPatch offset.
  			self hasUserInformation ifTrue: [^self].	"cannot use hw cursor if so"
  			submorphs notEmpty ifTrue: [^self].
  			(temporaryCursor notNil and: [hardwareCursor isNil]) ifTrue: [^self].
  
  			"Make the transition to using hardware cursor. Clear savedPatch and
  		 report one final damage rectangle to erase the image of the software cursor."
  			super invalidRect: (savedPatch offset 
  						extent: savedPatch extent + self shadowOffset)
  				from: self.
+ 			self showHardwareCursor: true.
- 			cursor := hardwareCursor ifNil: [Cursor normal].
- 			Sensor currentCursor == cursor ifFalse: [cursor show].	"show hardware cursor"
  			savedPatch := nil]!

Item was changed:
  ----- Method: PasteUpMorph>>invalidRect:from: (in category 'change reporting') -----
  invalidRect: damageRect from: aMorph
+ 	"Clip damage reports to my bounds, since drawing is clipped to my bounds."
+ 	self isWorldMorph
+ 		ifTrue: [worldState recordDamagedRect: damageRect].
+ 	^super invalidRect: damageRect from: aMorph!
-         "Clip damage reports to my bounds, since drawing is clipped to my bounds."
- 
-         self == self outermostWorldMorph 
-                 ifTrue: [worldState recordDamagedRect: (damageRect intersect: self bounds)]
-                 ifFalse: [super invalidRect: damageRect from: aMorph]
- !

Item was changed:
  ----- Method: HandMorph>>showTemporaryCursor:hotSpotOffset: (in category 'cursor') -----
  showTemporaryCursor: cursorOrNil hotSpotOffset: hotSpotOffset 
  	"Set the temporary cursor to the given Form.
  	If the argument is nil, revert to the normal hardware cursor."
  
  	self changed.
  	temporaryCursorOffset 
  		ifNotNil: [bounds := bounds translateBy: temporaryCursorOffset negated].
  	cursorOrNil isNil 
  		ifTrue: [temporaryCursor := temporaryCursorOffset := hardwareCursor := nil]
  		ifFalse: 
  			[temporaryCursor := cursorOrNil asCursorForm.
  			temporaryCursorOffset := temporaryCursor offset - hotSpotOffset.
  			(cursorOrNil isKindOf: Cursor) ifTrue: [hardwareCursor := cursorOrNil]].
  	bounds := self cursorBounds.
  	self
  		userInitials: userInitials andPicture: self userPicture;
  		layoutChanged;
+ 		changed;
+ 		showHardwareCursor: (temporaryCursor isNil).!
- 		changed!

Item was changed:
  ----- Method: BalloonCanvas>>line:to:width:color: (in category 'drawing') -----
  line: pt1 to: pt2 width: w color: c
  	"Draw a line from pt1 to: pt2"
+ 
+ 	(aaLevel == 1 and: [self ifNoTransformWithIn:(pt1 rect: pt2)])
- 	(self ifNoTransformWithIn:(pt1 rect: pt2))
  		ifTrue:[^super line: pt1 to: pt2 width: w color: c].
  	^self drawPolygon: (Array with: pt1 with: pt2)
  		color: c
  		borderWidth: w
  		borderColor: c!

Item was added:
+ ----- Method: Canvas>>finish: (in category 'initialization') -----
+ finish: allDamage
+ 	"If there are any pending operations on the receiver complete them. 
+ 	Do not return before all modifications have taken effect."
+ 	^self finish!



More information about the Packages mailing list