[comp.lang.smalltalk] A small IconEditor for Smalltalk 80, VI2.2

atoenne@laura.UUCP (Andreas Toenne) (12/11/87)

Here is a little IconEditor I wrote.
This goodie works on Smalltalk 80 VI2.2 VM1.1
It comes in two parts.
The first part 'Icon menu.st' adds knowledge about icons to the 
StandardSystemController's blueButtonMenu.
You should file in this one first.
The second part 'Icon Editor.st' is the editor himself.

Some notes about icons:
The icon's textRectangle is clipped with the icon's boundingBox.
To cancel a given textRectangle simply move it outside the outlined box.
The method storeOn: in class OpaqueForm is buggy.
You should add enclosing round brackets to the output. Otherwise
you won't be able to read the saved icon definitions back.

	Have fun

	Andreas Toenne
	atoenne@unido.uucp
	atoenne@unido.bitnet
	...!uunet!unido!atoenne
	atoenne%unido.uucp@uunet.uu.net

~~~~~~~~~~~~~~~~~~ cut here for best results ~~~~~~~~~~~~~~~~~~~~~~~~~~
#! /bin/sh
# This is a shell archive, meaning:
# 1. Remove everything above the #! /bin/sh line.
# 2. Save the resulting text in a file.
# 3. Execute the file with /bin/sh (not csh) to create:
#	Icon Editor.st
#	Icon Menu.st
# This archive created: Thu Dec 10 22:36:04 1987
export PATH; PATH=/bin:/usr/bin:$PATH
if test -f 'Icon Editor.st'
then
	echo shar: "will not over-write existing file 'Icon Editor.st'"
else
cat << \SHAR_EOF > 'Icon Editor.st'
MouseMenuController subclass: #IconDisplayController
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Icon Editor'!


!IconDisplayController methodsFor: 'controller default'!

isControlActive
	^ super isControlActive and: [sensor blueButtonPressed not]! !

!IconDisplayController methodsFor: 'menu messages'!

yellowButtonActivity
	| index menu |
	menu _ view yellowButtonMenu.
	menu == nil
		ifTrue:
			[view flash.
			super controlActivity]
		ifFalse: 
			[index _ menu startUpYellowButton.
			index ~= 0 
				ifTrue:
					[self controlTerminate.
					view perform: (menu selectorAt: index).
					self controlInitialize]]! !

View subclass: #IconDisplayView
	instanceVariableNames: 'icon aspect iconMsg iconMenu '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Icon Editor'!
IconDisplayView comment:
'I am a stupid view used to display the edited icon'!


!IconDisplayView methodsFor: 'displaying'!

displayView
	"display icon centered in my insetBox"

	| r iconRect rec |
	Display white: self insetDisplayBox.
	(icon isKindOf: Icon)
		ifTrue: 
			[r _ self insetDisplayBox.
			icon form displayOn: Display at: r topLeft + r bottomRight - icon form extent // 2.
			iconRect _ icon form computeBoundingBox.
			iconRect _ iconRect translateBy: r topLeft + r bottomRight - iconRect extent // 2.
			(iconRect areasOutside: (iconRect insetBy: 1 @ 1))
				do: [:edge | Display fill: edge mask: Form gray].
			rec _ icon textRect.
			rec = nil
				ifFalse: 
					[rec _ rec translateBy: r topLeft + r bottomRight - icon form computeBoundingBox extent // 2.
					(rec areasOutside: (rec insetBy: 1 @ 1))
						do: [:edge | Display fill: edge mask: Form gray]]]! !

!IconDisplayView methodsFor: 'updating'!

update: anAspect 
	"update the view"

	anAspect == aspect
		ifTrue: 
			[icon _ model perform: iconMsg.
			self displayView]! !

!IconDisplayView methodsFor: 'menu messages'!

allBlack
	"make the selected icon all black"
	| figure shape |
	figure _ icon form figure.
	shape _ icon form shape.
	figure fill: figure computeBoundingBox rule: Form over mask: Form black.
	shape fill: figure computeBoundingBox rule: Form over mask: Form black.
	model changed: #iconView!

allGray
	"make the selected icon all transparent"
	| figure shape |
	figure _ icon form figure.
	shape _ icon form shape.
	figure fill: figure computeBoundingBox rule: Form over mask: Form white.
	shape fill: figure computeBoundingBox rule: Form over mask: Form white.
	model changed: #iconView!

allWhite
	"make the selected icon all white"
	| figure shape |
	figure _ icon form figure.
	shape _ icon form shape.
	figure fill: figure computeBoundingBox rule: Form over mask: Form white.
	shape fill: figure computeBoundingBox rule: Form over mask: Form black.
	model changed: #iconView!

editIcon
	"edit the selected icon"

	| figure shape opaqueForm iconExtent bitView viewPoint savedForm |
	(icon = nil and: [model iconSymbol ~= #default])
		ifTrue: 
			[iconExtent _ Rectangle fromUser extent.
			figure _ Form extent: iconExtent.
			shape _ Form extent: iconExtent.
			opaqueForm _ OpaqueForm figure: figure shape: shape.
			model icon: (Icon form: opaqueForm textRect: nil)].
	icon = nil
		ifFalse: 
			[viewPoint _ (BitEditor locateMagnifiedView: icon form scale: 4 @ 4) topLeft.
			bitView _ BitEditor
						bitEdit: icon form
						at: viewPoint
						scale: 4 @ 4
						remoteView: nil.
			savedForm _ Form fromDisplay: (bitView displayBox merge: bitView labelDisplayBox).
			bitView controller startUp.
			savedForm displayOn: Display at: bitView labelDisplayBox topLeft.
			bitView release.
			model changed: #iconView]!

textRect
	"let the user specify a rectangle that will hold the icon's text"

	| rec r|
	rec _ Rectangle fromUser.
	r _ self insetDisplayBox.
	rec _ rec translateBy: 0@0 - (r topLeft + r bottomRight - icon form computeBoundingBox extent //2).
	icon form: icon form textRect: rec.
	model changed: #iconView! !

!IconDisplayView methodsFor: 'controller access'!

defaultControllerClass
	^IconDisplayController! !

!IconDisplayView methodsFor: 'private'!

on: anIcon aspect: m1 icon: m2 menu: m3
	self model: anIcon.
	aspect _ m1.
	iconMsg _ m2.
	iconMenu _ m3! !

!IconDisplayView methodsFor: 'adaptor'!

yellowButtonMenu
	^ self model perform: iconMenu! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

IconDisplayView class
	instanceVariableNames: ''!


!IconDisplayView class methodsFor: 'instance creation'!

on: anIcon aspect: m1 icon: m2 menu: m3
	"create a new view for anIcon with aspect m1"

	^self new
		on: anIcon
		aspect: m1
		icon: m2
		menu: m3! !

Model subclass: #IconEditor
	instanceVariableNames: 'icon iconSymbol iconBuffer '
	classVariableNames: 'IconMenu ListMenu '
	poolDictionaries: ''
	category: 'Icon Editor'!
IconEditor comment:
'I am a bit editor for system icons.

Instance Variables :
	icon 				"The selected icon"
	iconSymbol			"The symbol for the selected icon"

Class Variables:
	ListMenu 			"The action menu for the SelectionInListView over all icons"'!


!IconEditor methodsFor: 'accessing'!

icon
	"return the selected icon"

	^icon!

icon: anIcon 
	"change the selected Icon to anIcon"

	icon _ anIcon.
	Icon constantNamed: iconSymbol put: anIcon.
	self changed: #iconView 	" aspect for the IconDisplayView"!

icon: anIcon named: aSymbol 
	" store anIcon at position aSymbol"

	Icon constantNamed: aSymbol put: anIcon.
	icon _ anIcon.
	iconSymbol _ aSymbol.
	self changed: #iconSymbol.			"aspect for SelectionInListView"
	self changed: #iconView			"aspect for iconDisplayView "!

iconSymbol
	"return the symbol for the selected icon"

	^iconSymbol!

iconSymbol: aSymbol 
	"change the symbol for the selected icon to aSymbol"

	iconSymbol _ aSymbol.
	icon _ Icon constantNamed: aSymbol.
	self changed: #iconView	"aspect for the IconDisplayView"! !

!IconEditor methodsFor: 'removing'!

removeIcon
	" remove the currently selected icon "

	Icon constantDictionary removeKey: iconSymbol ifAbsent: [^nil].
	iconSymbol _ icon _ nil.
	self changed: #iconSymbol.
	self changed: #iconView! !

!IconEditor methodsFor: 'list display'!

iconList
	"return the list of icon symbols"

	| list |
	list _ OrderedCollection new.
	Icon constantDictionary keysDo: [:i | list add: i].
	^list!

initialSymbol
	"get the initial symbol selection"
	"this method is used every time the SelectionInListView receives an update mesage "

	^iconSymbol!

listMenu
	"return the menu for the icon list"

	^ListMenu! !

!IconEditor methodsFor: 'icon display'!

iconMenu
	"return the menu for the iconDisplayController"

	^IconMenu! !

!IconEditor methodsFor: 'menu messages'!

copy
	" save a (deep) copy of the currently selected icon"

	icon = nil ifFalse: [iconBuffer _ icon deepCopy]!

cut
	" remove the currently selected icon from the icon dictionary and   
	save it in iconBuffer"

	(icon ~= nil or: [iconSymbol ~= #default])
		ifTrue: 
			[iconBuffer _ icon.
			self removeIcon]!

loadIcon
	"override the current icon with a definition from a file"

	| aFileName anIcon aStream |
	(icon ~= nil or: [iconSymbol ~= #default])
		ifTrue: 
			[aFileName _ FileDirectory
						requestFileName: 'file : '
						default: iconSymbol asString , '.icn'
						version: #old
						ifFail: [^''].
			aFileName ~= ''
				ifTrue: 
					[aStream _ FileStream oldFileNamed: aFileName.
					anIcon _ Object readFrom: aStream.
					aStream close.
					self icon: anIcon]]!

newIcon
	" create a new clean icon"

	| iconName |
	iconName _ FillInTheBlank request: 'Icon Name ?'.
	iconName = '' ifFalse: [self icon: nil named: iconName asSymbol]!

paste
	" change the currently selected icon to the icon held in iconBuffer"
	" invoke newIcon if none is selected"

	iconSymbol = nil
		ifTrue: 
			["add a new icon"
			self newIcon.
			iconSymbol = nil ifFalse: [self icon: iconBuffer]]
		ifFalse: ["override old icon"
			self icon: iconBuffer]!

renameIcon
	" change the name of an icon"

	| key value newName |
	(icon ~= nil or: [iconSymbol ~= #default])
		ifTrue: 
			[key _ iconSymbol.
			value _ icon.
			newName _ FillInTheBlank request: 'Change icon name' initialAnswer: key.
			newName ~= ''
				ifTrue: 
					[self removeIcon.
					self icon: value named: newName asSymbol]]!

saveIcon
	"store the selected icon to a file"

	| aFileName aStream |
	icon = nil
		ifFalse: 
			[aFileName _ FileDirectory
						requestFileName: 'file : '
						default: iconSymbol asString , '.icn'
						version: #any
						ifFail: [^''].
			aFileName ~= ''
				ifTrue: 
					[aStream _ FileStream newFileNamed: aFileName.
					icon storeOn: aStream.
					aStream close]]! !

!IconEditor methodsFor: 'view creation'!

open
	"open the views"

	| topView |
	topView _ StandardSystemView
				model: self
				label: 'Icon Editor'
				minimumSize: 256 @ 300.
	topView
		addSubView: (SelectionInListView
				on: self
				aspect: #iconSymbol
				change: #iconSymbol:
				list: #iconList
				menu: #listMenu
				initialSelection: #initialSymbol)
		in: (0 @ 0 corner: 1.0 @ 0.3)
		borderWidth: 1.
	topView
		addSubView: (IconDisplayView
				on: self
				aspect: #iconView
				icon: #icon
				menu: #iconMenu)
		in: (0.0 @ 0.3 corner: 1.0 @ 1.0)
		borderWidth: 1.
	topView controller open! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

IconEditor class
	instanceVariableNames: ''!


!IconEditor class methodsFor: 'class initialization'!

initialize
	"Initialize the class IconEditor"
	"IconEditor initialize"

	ListMenu _ ActionMenu labelList: #((copy cut paste ) (newIcon renameIcon ) (saveIcon loadIcon ) ) selectors: #(copy cut paste newIcon renameIcon saveIcon loadIcon ).
	IconMenu _ ActionMenu labelList: #((editIcon textRect ) (allWhite allBlack allGray) ) selectors: #(editIcon textRect allWhite allBlack allGray)! !

!IconEditor class methodsFor: 'instance creation'!

open
	"create on schedule a new Icon Editor"

	self new open! !

IconEditor initialize!
SHAR_EOF
fi
if test -f 'Icon Menu.st'
then
	echo shar: "will not over-write existing file 'Icon Menu.st'"
else
cat << \SHAR_EOF > 'Icon Menu.st'
!MouseMenuController methodsFor: 'menu messages'!

blueButtonActivity
	"Determine which item in the blue button pop-up menu is selected. 
	If one is selected, then send the corresponding message to the object 
	designated as the menu message receiver."
	"Enhanced to use HierarchicalMenus by atoenne@unido.uucp"

	| index |
	blueButtonMenu ~~ nil
		ifTrue: 
			[index _ blueButtonMenu startUpBlueButton.
			index ~= 0 ifTrue: [blueButtonMenu class = HierarchicalMenu
					ifTrue: [self menuMessageReceiver perform: (blueButtonMenu selectorAt: index)]
					ifFalse: [self menuMessageReceiver perform: (blueButtonMessages at: index)]]]
		ifFalse: [super controlActivity]! !

!StandardSystemController class methodsFor: 'class initialization'!

initialize
	"Initialize the class variables."
	"StandardSystemController initialize. 
	StandardSystemController allInstances do: [:sc | sc 
	initializeBlueButtonMenu] "

	ScheduledBlueButtonMenu _ (MenuBuilder parseFrom: (ReadStream on: 'newLabel[newLabel]
(under[under] move[move] frame[frame]) (collapse[collapse]
icon: ((selectIcon[selectIcon] editIcon[editIcon]) (loadIcons[loadIcons] saveIcons[saveIcons])))
(close[close])')) menu.
	MenuWhenCollapsed _ ActionMenu
				labels: 'new label\under\move\expand\close' withCRs
				lines: #(1 4 )
				selectors: #(newLabel under move expand close )! !

!StandardSystemController methodsFor: 'menu messages'!

editIcon
	" call an icon editor "

	IconEditor open!

loadIcons
	"load new constant definitions for icons"

	| aFileName |
	aFileName _ FileDirectory
				requestFileName: 'file:'
				default: '*.icn'
				version: #old
				ifFail: [^''].
	aFileName ~= '' ifTrue: [Icon constantsFromFile: aFileName]!

saveIcons
	"write current icon constants to a file"

	| aFileName |
	aFileName _ FileDirectory
				requestFileName: 'file:'
				default: '*.icn'
				version: #any
				ifFail: [^''].
	aFileName ~= '' ifTrue: [Icon constantsToFile: aFileName]!

selectIcon
	"let the user choose from the current icons"

	| nameList iconList selection selectedIcon |
	nameList _ OrderedCollection new.
	Icon constantDictionary keysDo: [:key | nameList add: key].
	iconList _ Array with: nameList asArray.
	selection _ (PopUpMenu labelList: iconList) startUp.
	selection ~= 0
		ifTrue: 
			[selectedIcon _ (Icon constantNamed: (nameList at: selection) asSymbol) copy.
			self view icon: selectedIcon.				"change the icon"
			self view iconView lock.					"essential. see below"
			self view iconView text: self view label.	"set new icon text"
			self view iconView newIcon]				"compute new icon"
"lock is needed to perform the newIcon computation. Otherwise insetDisplayBox would be garbled. Text setting is merely needed at the first change. (The standard label has no iconText) "! !

!StandardSystemController initialize. 
StandardSystemController allInstances do: [:sc | sc 
initializeBlueButtonMenu]!
SHAR_EOF
fi
exit 0
#	End of shell archive
D