PluggableListMorph

Bob Arning arning at charm.net
Sun Jun 18 15:20:30 UTC 2000


On Sat, 17 Jun 2000 23:02:56 -0500 "Eric Arseneau" <eat at huv.com> wrote:
>I am looking for a morph that takes in a list of objects, and has a setting
>for a printBlock.  This way I can have a list of objects and not have to
>deal with indexes or strings.  As this been done ?  If not is there any
>problems to adding support of this to the PluggableListMorph ?  Or is
>totally against the paradigm.

Eric,

Nothing does that at the moment, but I have included a simple example.

Cheers,
Bob

===== code follows ====
'From Squeak2.9alpha of 13 June 2000 [latest update: #2411] on 18 June 2000 at 11:15:30 am'!
"Change Set:		listWithPrinter
Date:			18 June 2000
Author:			Bob Arning

A pluggable list morph that takes a list of arbitrary objects (rather than just strings) and a user-supplied print block to create the visual representation

A whimsical example is included

	PLMTester example

"!

Object subclass: #PLMTester
	instanceVariableNames: 'currentSelection anythingGoes '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Bob-Bob'!
PluggableListMorphByItem subclass: #PluggableListMorphByItemWithPrinter
	instanceVariableNames: 'printer '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!PLMTester methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 10:55'!
getCurrentSelection

	^currentSelection! !

!PLMTester methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 10:51'!
getList

	^anythingGoes
! !

!PLMTester methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 11:14'!
openOn: aCollection with: aPrintBlock

	| window |

	anythingGoes _ aCollection.
	currentSelection _ anythingGoes at: 1 ifAbsent: [nil].
	window _ (SystemWindow labelled: 'Anyting goes') model: self.

	window 
		addMorph: (PluggableListMorphByItemWithPrinter new

			printer: aPrintBlock;

			on: self 
			list: #getList
			selected: #getCurrentSelection 
			changeSelected: #setSelectedItem:
			menu: #nil 
			keystroke: #nil
		)
		frame: (0 at 0 extent: 1 at 1).

	^ window openInWorld! !

!PLMTester methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 10:56'!
setSelectedItem: anItemOrNil

	currentSelection _ anItemOrNil.
	currentSelection ifNotNil: [currentSelection explore].
! !


!PLMTester class methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 11:14'!
example

	self new 
		openOn: {
			'1'. 
			1. 
			#(a b c d). 
			#name->'Bob'. 
			Smalltalk
		}
		with: [ :x | String withAll: (x asString asLowercase asSortedCollection)]! !


!PluggableListMorphByItemWithPrinter methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 11:04'!
getCurrentSelectionIndex
	"Answer the index of the current selection."
	| item |
	getIndexSelector == nil ifTrue: [^ 0].
	item _ model perform: getIndexSelector.
	^ itemList findFirst: [ :x | x == item]
! !

!PluggableListMorphByItemWithPrinter methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 10:20'!
list: arrayOfItems 
	| morphList h loc index |

	printer ifNil: [printer _ [ :x | x asString] ].
	itemList _ arrayOfItems ifNil: [Array new].
	scroller removeAllMorphs.
	list _ itemList collect: [ :each | printer value: each].
	list isEmpty ifTrue: [self setScrollDeltas.  ^ self selectedMorph: nil].
	"NOTE: we will want a quick StringMorph init message, possibly even
		combined with event install and positioning"
	font ifNil: [font _ Preferences standardListFont].
	morphList _ list collect:
		[:item | item isText
			ifTrue: [StringMorph contents: item font: font emphasis: (item emphasisAt: 1)]
			ifFalse: [StringMorph contents: item font: font]].


	"Lay items out vertically and install them in the scroller"
	h _ morphList first height "self listItemHeight".
	loc _ 0 at 0.
	morphList do: [:m | m bounds: (loc extent: 9999 at h).  loc _ loc + (0 at h)].
	scroller addAllMorphs: morphList.
	self installEventHandlerOn: morphList.

	index _ self getCurrentSelectionIndex.
	self selectedMorph: ((index = 0 or: [index > morphList size]) ifTrue: [nil] ifFalse: [morphList at: index]).
	self setScrollDeltas.
	scrollBar setValue: 0.0! !

!PluggableListMorphByItemWithPrinter methodsFor: 'as yet unclassified' stamp: 'RAA 6/18/2000 10:20'!
printer: aBlock

	printer _ aBlock.
! !

PLMTester removeSelector: #openOn:!





More information about the Squeak-dev mailing list