[squeak-dev] Collapsed windows not quite so collapsed

Bob Arning arning315 at comcast.net
Wed May 9 00:05:14 UTC 2018


Inspired by a comment earlier today:

Change Set:        minimorphs
Date:            8 May 2018
Author:            Bob Arning

You can have tons of SystemWindows open or collapsed. Sometimes it can 
be difficult to find what you really want. This is a compromise: partial 
thumbnails for collapsed windows. Auto-tiling for neatness. Squeak 5.1

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20180508/15ad8eee/attachment.html>
-------------- next part --------------
'From Squeak5.1 of 23 August 2016 [latest update: #16548] on 8 May 2018 at 8:03:10 pm'!
"Change Set:		minimorphs
Date:			8 May 2018
Author:			Bob Arning

You can have tons of SystemWindows open or collapsed. Sometimes it can be difficult to find what you really want. This is a compromise: partial thumbnails for collapsed windows. Auto-tiling for neatness. Squeak 5.1"!

ImageMorph subclass: #MiniMeMorph
	instanceVariableNames: 'window '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!MiniMeMorph commentStamp: 'raa 5/8/2018 19:52' prior: 0!
other modes

	mode = 1 ifTrue: [
		f _ f scaledToSize: 200 at 200.
	].
	mode = 2 ifTrue: [
		f _ f copy: (0 at 0 extent: (200 min: f width)@(200 min: f height)).
	].
!
]style[(13 1 4 1 1 1 1 1 7 5 1 1 1 1 1 1 13 1 3 1 3 7 4 1 1 1 1 1 7 5 1 1 1 1 1 1 5 1 1 1 1 1 1 7 1 1 3 1 4 1 1 1 5 1 1 1 3 1 4 1 1 1 6 1 1 6),cblack;,c106106106,cblack;,c000000126,cblack;,c126000000,cblack;,c000000126,cblack;,c106106106,cblack;,b,cblack;,c106106106,cblack;,c000000126,cblack;,c126000000,c000000126,c126000000,cblack;,c106106106,cblack;,c000000126,cblack;,c126000000,cblack;,c000000126,cblack;,c106106106,cblack;,b,cblack;,c106106106,cblack;,c000000126,cblack;,c000126000,c126000000,c000000126,c126000000,cblack;,c000000126,cblack;,c126000126,c126000000,cblack;,c000000126,cblack;,c106106106,cblack;,c000000126,c126000126,c000000126,c126000126,c126000000,cblack;,c000000126,cblack;,c106106106,cblack;,c000000126,c126000126,c000126000,cblack;!


!MiniMeMorph methodsFor: 'as yet unclassified' stamp: 'raa 5/8/2018 19:53'!
miniMe: aWindow
"
(World submorphs select: [ :e | e isSystemWindow and: [e visible]]) do: [ :m | MiniMeMorph new miniMe: m]
"
	| others maxX nextX nextY f n |
	
	window _ aWindow.
	window passivate; hasDropShadow: false.
	f _ aWindow imageForm.
	f _ f copy: (0 at 0 extent: (350 min: f width)@(350 min: f height)).
	f _ f magnify: f boundingBox by: 0.5 smoothing: 3.
	n _ 4.
	(f width > n and: [f height > n]) ifTrue: [
		f _ f copy: ((n at n//2) extent: f  extent - (n at n))
	].
	self image: f.
	others _ World submorphs select: [ :e | e hasProperty: #MiniMePosition].
	others _ others,{self}.
	nextX _ nextY _ maxX _ 0.
	others withIndexDo: [ :m :index |
		m setProperty: #MiniMePosition toValue: index.
		m position: nextX @ nextY.
		m bottom > World bottom ifTrue: [
			nextY _ 0.
			nextX _ maxX + 2.
			m position: nextX @ nextY.
		].
		nextY _ m bottom + 2.
		maxX _ maxX max: m right.
	].
	World addMorphBack: self.
	self on: #mouseDown send: #value to: [
		self delete.
		window show; beKeyWindow
	].
	self setBalloonText: window label.
	window hide.
	SystemWindow noteTopWindowIn: World.! !


!SystemWindow methodsFor: 'resize/collapse' stamp: 'raa 5/8/2018 19:50'!
collapseOrExpand
	"Collapse or expand the window, depending on existing state"
	| cf |
	
	isCollapsed ifFalse: [
		^MiniMeMorph new miniMe: self
	].
	isCollapsed
		ifTrue: 
			["Expand -- restore panes to morphics structure"
			isCollapsed := false.
			self beKeyWindow.  "Bring to frint first"
			Preferences collapseWindowsInPlace
				ifTrue: 
					[fullFrame := fullFrame align: fullFrame topLeft with: self getBoundsWithFlex topLeft]
				ifFalse:
					[collapsedFrame := self getBoundsWithFlex].
			collapseBox ifNotNil: [collapseBox setBalloonText: 'collapse this window' translated].
			self setBoundsWithFlex: fullFrame.
			paneMorphs reverseDo: 
					[:m |  self addMorph: m unlock.
					self world startSteppingSubmorphsOf: m].
			self addPaneSplitters.
			(self hasProperty: #applyTheme) ifTrue: [
				self removeProperty: #applyTheme.
				self userInterfaceTheme applyTo: self allMorphs]]
		ifFalse: 
			["Collapse -- remove panes from morphics structure"
			isCollapsed := true.
			fullFrame := self getBoundsWithFlex.
			"First save latest fullFrame"
			paneMorphs do: [:m | m delete; releaseCachedState].
			self removePaneSplitters.
			self removeCornerGrips.
			model modelSleep.
			cf := self getCollapsedFrame.
			(collapsedFrame isNil and: [Preferences collapseWindowsInPlace not]) ifTrue:
				[collapsedFrame := cf].
			self setBoundsWithFlex: cf.
			collapseBox ifNotNil: [collapseBox setBalloonText: 'expand this window' translated ].
			expandBox ifNotNil: [expandBox setBalloonText: 'expand this window' translated ].
			self sendToBack].
	self layoutChanged! !


!SystemWindow class methodsFor: 'top window' stamp: 'raa 5/8/2018 17:06'!
noteTopWindowIn: aWorld
	"Look for a new top window in the given world. We have to reset the former top window because this is global state shared between all worlds."

	| newTopWindow |
	TopWindow := nil.
	newTopWindow := nil.

	aWorld ifNil: [^ self].

	aWorld submorphsDo: [:m |
		(m isSystemWindow and: [m visible] and: [newTopWindow isNil])
			ifTrue: [newTopWindow := m].
		
		self flag: #refactor. "This really belongs in a special ProjWindow class"
		(m model isKindOf: Project)
			ifTrue: [m label ~= m model name ifTrue: [m setLabel: m model name]]].

	newTopWindow ifNotNil: [newTopWindow beKeyWindow].! !



More information about the Squeak-dev mailing list