[ENH] Grow Buttons for Views

Stephen Travis Pope stp at create.ucsb.edu
Mon Aug 30 17:41:38 UTC 1999


Hello all,

I got to spend some more time this weekend squeaking, and decided to add
grow/shrink buttons to views (because I move between small and very
large screens and can never get the default view sizes right). The
following change set places a small button (with the glyph "^") next to
the collapse button in the upper-right of Morphic views. Pressing this
button grows the view by 50% (or shrinks it if SHIFT is pressed).

Notes:

1) This works only for Morphic views.

2) The minimum size is 120 at 120; the max is the screen size.

3) After you file this in, you'll need to close/reopen all Morphic views
and regenerate the tool flap.

4) There's a minor nit with long labels and small views -- the label can
sometimes overlap the grow button.

5) Comments and further enhancements are invited.

--

stp
  Stephen Travis Pope -- http://www.create.ucsb.edu/~stp
  stp at create.ucsb.edu -- stp9 at cornell.edu


Content-Type: text/plain; charset=us-ascii; x-mac-type="54455854"; x-mac-creator="522A6368";
 name="GrowBox.cs"
Content-Transfer-Encoding: 7bit
Content-Description: Unknown Document
Content-Disposition: inline;
 filename="GrowBox.cs"

'From Squeak 2.5 of August 6, 1999 on 28 August 1999 at 11:36:28 am'!
MorphicModel subclass: #SystemWindow
	instanceVariableNames: 'labelString stripes label closeBox collapseBox growBox activeOnlyOnTop paneMorphs paneRects collapsedFrame fullFrame isCollapsed '
	classVariableNames: 'TopWindow '
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!SystemWindow methodsFor: 'initialization' stamp: 'stp 08/28/1999 10:57'!
initialize
	| aFont |
	super initialize.
	labelString ifNil: [labelString _ 'Untitled Window'].
	isCollapsed _ false.
	activeOnlyOnTop _ true.
	paneMorphs _ Array new.
	paneRects _ Array new.
	borderColor _ #raised.
	borderWidth _ 1.
	color _ Color black.
	aFont _ Preferences fontForScriptorButtons.
	stripes _ Array with: (RectangleMorph newBounds: bounds)  "see extent:"
				with: (RectangleMorph newBounds: bounds).
	self addMorph: (stripes first borderWidth: 1).
	self addMorph: (stripes second borderWidth: 2).
	self addMorph: (label _ StringMorph new contents: labelString;
			font: (TextStyle default fontAt: 2) emphasis: 1).
	self addMorph: (closeBox _ SimpleButtonMorph new borderWidth: 0;
			label: 'X' font: aFont; color: Color transparent;
			actionSelector: #delete; target: self; extent: 16 at 16).
	self addMorph: (collapseBox _ SimpleButtonMorph new borderWidth: 0;
			label: 'O' font: aFont; color: Color transparent;
			actionSelector: #collapseOrExpand; target: self; extent: 16 at 16).
	self addMorph: (growBox _ SimpleButtonMorph new borderWidth: 0;
			label: '^' font: aFont; color: Color transparent;
			actionSelector: #growOrShrink; target: self; extent: 16 at 16).
	Preferences noviceMode ifTrue:
		[closeBox setBalloonText: 'close window'.
		collapseBox 	setBalloonText: 'collapse/expand window'].
	self on: #mouseEnter send: #spawnReframeHandle: to: self.
	self on: #mouseLeave send: #spawnReframeHandle: to: self.
	label on: #mouseDown send: #relabelEvent: to: self.
	self extent: 300 at 200! !

!SystemWindow methodsFor: 'geometry' stamp: 'stp 08/28/1999 11:35'!
extent: newExtent
	| inner labelRect |
	isCollapsed
		ifTrue: [super extent: newExtent x @ (self labelHeight + 2)]
		ifFalse: [super extent: newExtent].
	inner _ self innerBounds.
	labelRect _ self labelRect.

	stripes first bounds: (labelRect insetBy: 1).
	stripes second bounds: (labelRect insetBy: 3).
	self setStripeColorsFrom: self paneColor.
	closeBox align: closeBox topLeft with: inner topLeft + (4 at 0).
	collapseBox align: collapseBox topRight with: inner topRight - (4 at 0).
	growBox align: growBox topRight with: collapseBox topLeft.
	label fitContents; setWidth: (label width min: bounds width - 50).
	label align: label bounds topCenter with: inner topCenter.
	self setBoundsOfPaneMorphs.
	isCollapsed
		ifTrue: [collapsedFrame _ self bounds]
		ifFalse: [fullFrame _ self bounds].
! !

!SystemWindow methodsFor: 'resize/collapse' stamp: 'stp 08/28/1999 11:34'!
growOrShrink
	"Expand (or shrink if shiftDown) the view by 50%, clipping to the screen size and centering it.
	The minimum size is 120 at 120."

	| oldSize newSize |
	oldSize := self bounds.
	newSize := Sensor leftShiftDown
		ifTrue: [(oldSize scaleBy: 0.66 at 0.66) truncated]
		ifFalse: [(oldSize scaleBy: 1.5 at 1.5) truncated].
	newSize extent < (120 at 120)
		ifTrue: [^self].
	newSize := newSize translateBy: (newSize center - oldSize center) negated.
	newSize := newSize intersect: Display boundingBox.
	super bounds: newSize.
	paneMorphs reverseDo: [:m | self addMorph: m]
! !





More information about the Squeak-dev mailing list