A further hack to corner grips in 3.9alpha. [tested in 6716 and 6718]

Robin gmail robin.luiten at gmail.com
Thu Feb 2 12:15:19 UTC 2006


It adds corner grips to all 4 corners.
It exhibits the same behaviour as the original corner gripper in that if
you scale a browser
small enough internal interface elements protrude outside of the
bounding box of the window.

I apologize for the class structure of  CornerGripMorph with subclasses
of CornerGripMorphBottomLeft, CornerGripMorphTopLeft and
CornerGripMorphTopRight. Its a bit ugly but I couldnt see a lot of advantage
in making a proper superand 4 subclassess. [and i am quite lazy if i can
be.]

I have not tried to refactor any of the drawing code as I was more
concerned at trying
to get rid of as many of magic numbers in the original drawing code first.

I also think the current design of having the corner group a square
morph which may overlap with internal window element morphs is not a
good design. It appears to me that in a Workspace window that typing in
the workspace causes the corner groups to redraw for every single
character that renders typed. Which I think might be to do with the
overlap of display areas.

I am still pretty new at squeak and smalltalk so am happy to hear any
constructive feedback.
It seems to me that to make this sort of extension cleaner would require
more structure in the SystemWindow morph structure.

Robin.




-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #6716] on 2 February 2006 at 9:25:51 pm'!
AbstractResizerMorph subclass: #CornerGripMorph
	instanceVariableNames: 'target'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!
CornerGripMorph subclass: #CornerGripMorphBottomLeft
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!
CornerGripMorph subclass: #CornerGripMorphTopLeft
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!
CornerGripMorph subclass: #CornerGripMorphTopRight
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!BorderedMorph methodsFor: 'lookenhancements' stamp: 'rl 2/2/2006 21:22'!
addCornerGrip

	| grip gripBottomLeft gripTopLeft gripTopRight |
	grip _ CornerGripMorph new target: self.
	grip layoutFrame: (grip gripLayoutFrame).
	self addMorphBack: grip.
	
	gripBottomLeft _ CornerGripMorphBottomLeft new target: self.
	gripBottomLeft layoutFrame: (gripBottomLeft gripLayoutFrame).
	self addMorphBack: gripBottomLeft.

	gripTopLeft _ CornerGripMorphTopLeft new target: self.
	gripTopLeft layoutFrame: (gripTopLeft gripLayoutFrame).
	self addMorphBack: gripTopLeft.

	gripTopRight _ CornerGripMorphTopRight new target: self.
	gripTopRight layoutFrame: (gripTopRight gripLayoutFrame).
	self addMorphBack: gripTopRight.
! !


!CornerGripMorph methodsFor: 'as yet unclassified' stamp: 'rl 2/2/2006 21:24'!
drawOn: aCanvas

	| dotBounds alphaCanvas windowBorderWidth dotBounds2 |
	"super drawOn: aCanvas." "intentionally not calling super for now since bottomRight corner is the super class"
	SystemWindow resizeOnAllSides ifTrue: [^self].

	windowBorderWidth _ SystemWindow borderWidth.
	bounds _ self bounds.
	alphaCanvas _ aCanvas asAlphaBlendingCanvas: 0.7.	
	"alphaCanvas
		frameRectangle: bounds color: Color blue."

	dotBounds _ (bounds insetBy: 1).
	dotBounds2 _ dotBounds left: (dotBounds right - windowBorderWidth).
	dotBounds2 _ dotBounds2 top: (dotBounds2 bottom - windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.
	
	dotBounds2 _ dotBounds right: (dotBounds right - windowBorderWidth).
	dotBounds2 _ dotBounds2 top: (dotBounds2 bottom - windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 left: (dotBounds2 left + 7).
	dotBounds2 _ dotBounds2 right: (dotBounds2 right - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.

	dotBounds2 _ dotBounds left: (dotBounds right - windowBorderWidth).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 bottom - windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 top: (dotBounds2 top + 7).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 bottom - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.
! !

!CornerGripMorph methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 19:26'!
gripLayoutFrame
	"the layout frame suitable for positioning this grip in parent"
	^LayoutFrame
		fractions: (1 at 1 corner: 1 at 1) 
		offsets: (-22 at -22 corner: 0 at 0).
! !


!CornerGripMorphBottomLeft methodsFor: 'as yet unclassified' stamp: 'rl 2/2/2006 21:25'!
drawOn: aCanvas

	| dotBounds alphaCanvas windowBorderWidth dotBounds2 |
	"super drawOn: aCanvas." "intentionally not calling super for now since bottomRight corner is the super class"
	SystemWindow resizeOnAllSides ifTrue: [^self].

	windowBorderWidth _ SystemWindow borderWidth.
	bounds _ self bounds.
	alphaCanvas _ aCanvas asAlphaBlendingCanvas: 0.7.	
	"alphaCanvas
		frameRectangle: bounds color: Color blue."

	dotBounds _ (bounds insetBy: 1).
	dotBounds2 _ dotBounds right: (dotBounds left + windowBorderWidth).
	dotBounds2 _ dotBounds2 top: (dotBounds2 bottom - windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.
	
	dotBounds2 _ dotBounds left: (dotBounds left + windowBorderWidth).
	dotBounds2 _ dotBounds2 top: (dotBounds2 bottom - windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 left: (dotBounds2 left + 7).
	dotBounds2 _ dotBounds2 right: (dotBounds2 right - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.

	dotBounds2 _ dotBounds right: (dotBounds left + windowBorderWidth).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 bottom - windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 top: (dotBounds2 top + 7).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 bottom - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.



! !

!CornerGripMorphBottomLeft methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 19:25'!
gripLayoutFrame
	^LayoutFrame
		fractions: (0 at 1 corner: 0 at 1) 
		offsets: (0 at 0 corner: 22 at -22).! !

!CornerGripMorphBottomLeft methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 20:34'!
mouseMove: anEvent

	| delta oldBounds |
	target ifNil: [^ self].
	
	delta _ anEvent cursorPoint - lastMouse.
	lastMouse _ anEvent cursorPoint.
	
	oldBounds _ target bounds.
	"target bounds: (oldBounds origin corner: (oldBounds corner + delta))."
	target bounds:
		(((oldBounds left + delta x) @ oldBounds top) corner: (oldBounds right @ (oldBounds bottom + delta y))).
	
	self bounds: (self bounds origin + delta extent: self bounds extent)! !

!CornerGripMorphBottomLeft methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 19:24'!
resizeCursor

	^ Cursor resizeForEdge: #bottomLeft! !


!CornerGripMorphTopLeft methodsFor: 'as yet unclassified' stamp: 'rl 2/2/2006 21:25'!
drawOn: aCanvas

	| dotBounds alphaCanvas windowBorderWidth dotBounds2 |
	"super drawOn: aCanvas." "intentionally not calling super for now since bottomRight corner is the super class"
	SystemWindow resizeOnAllSides ifTrue: [^self].

	windowBorderWidth _ SystemWindow borderWidth.
	bounds _ self bounds.
	alphaCanvas _ aCanvas asAlphaBlendingCanvas: 0.7.	
	"alphaCanvas
		frameRectangle: bounds color: Color blue."

	dotBounds _ (bounds insetBy: 1).
	dotBounds2 _ dotBounds right: (dotBounds left + windowBorderWidth).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 top + windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.
	
	dotBounds2 _ dotBounds left: (dotBounds left + windowBorderWidth).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 top + windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 left: (dotBounds2 left + 7).
	dotBounds2 _ dotBounds2 right: (dotBounds2 right - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.

	dotBounds2 _ dotBounds right: (dotBounds left + windowBorderWidth).
	dotBounds2 _ dotBounds2 top: (dotBounds2 top + windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 top: (dotBounds2 top + 7).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 bottom - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.



! !

!CornerGripMorphTopLeft methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 22:41'!
gripLayoutFrame
	^LayoutFrame
		fractions: (0 at 0 corner: 0 at 0) 
		offsets: (0 at 0 corner: 22@(22-49)).   " GRRR magic numbers. ? twice labelHeight i think maybe ? "! !

!CornerGripMorphTopLeft methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 22:53'!
mouseMove: anEvent

	| delta oldBounds |
	target ifNil: [^ self].
	
	delta _ anEvent cursorPoint - lastMouse.
	lastMouse _ anEvent cursorPoint.
	
	oldBounds _ target bounds.
	"target bounds: (oldBounds origin corner: (oldBounds corner + delta))."
	target bounds:
		(((oldBounds left + delta x) @ (oldBounds top + delta y)) corner: (oldBounds right @ oldBounds bottom)).
	
	self bounds: (self bounds origin + delta extent: self bounds extent)! !

!CornerGripMorphTopLeft methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 22:30'!
resizeCursor

	^ Cursor resizeForEdge: #topLeft! !


!CornerGripMorphTopRight methodsFor: 'as yet unclassified' stamp: 'rl 2/2/2006 21:25'!
drawOn: aCanvas

	| dotBounds alphaCanvas windowBorderWidth dotBounds2 |
	"super drawOn: aCanvas." "intentionally not calling super for now since bottomRight corner is the super class"
	SystemWindow resizeOnAllSides ifTrue: [^self].

	windowBorderWidth _ SystemWindow borderWidth.
	bounds _ self bounds.
	alphaCanvas _ aCanvas asAlphaBlendingCanvas: 0.7.	
	"alphaCanvas
		frameRectangle: bounds color: Color blue."

	dotBounds _ (bounds insetBy: 1).
	dotBounds2 _ dotBounds left: (dotBounds right - windowBorderWidth).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 top + windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.
	
	dotBounds2 _ dotBounds right: (dotBounds right - windowBorderWidth).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 top + windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 left: (dotBounds2 left + 7).
	dotBounds2 _ dotBounds2 right: (dotBounds2 right - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.

	dotBounds2 _ dotBounds left: (dotBounds right - windowBorderWidth).
	dotBounds2 _ dotBounds2 top: (dotBounds2 top + windowBorderWidth).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self handleColor.

	dotBounds2 _ dotBounds2 top: (dotBounds2 top + 7).
	dotBounds2 _ dotBounds2 bottom: (dotBounds2 bottom - 7).
	alphaCanvas
		fillRectangle: dotBounds2
		color: self dotColor.



! !

!CornerGripMorphTopRight methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 22:59'!
gripLayoutFrame
	^LayoutFrame
		fractions: (1 at 0 corner: 1 at 0) 
		offsets: (0 at -49 corner: -22 at 22).   " GRRR magic numbers. ? twice labelHeight i think maybe ? "! !

!CornerGripMorphTopRight methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 23:01'!
mouseMove: anEvent

	| delta oldBounds |
	target ifNil: [^ self].
	
	delta _ anEvent cursorPoint - lastMouse.
	lastMouse _ anEvent cursorPoint.
	
	oldBounds _ target bounds.
	"target bounds: (oldBounds origin corner: (oldBounds corner + delta))."
	target bounds:
		((oldBounds left @ (oldBounds top + delta y)) corner: ((oldBounds right + delta x) @ oldBounds bottom)).
	
	self bounds: (self bounds origin + delta extent: self bounds extent)! !

!CornerGripMorphTopRight methodsFor: 'as yet unclassified' stamp: 'rl 1/31/2006 22:54'!
resizeCursor

	^ Cursor resizeForEdge: #topRight! !




More information about the Squeak-dev mailing list