[Seaside] Menu building pattern?

C. David Shaffer cdshaffer at acm.org
Wed Aug 4 19:34:07 CEST 2004


Avi Bryant wrote:

>
> On Aug 4, 2004, at 12:13 AM, C. David Shaffer wrote:
>
>> I have been working on a generic menu component and I'm stumbling on 
>> managing children.  What I'd like to do is after callback processing 
>> is complete (and the component tree is finalized for the next 
>> rendering pass), traverse the tree and ask each visible presenter for 
>> its menu items.  The menu items themselves are components so they 
>> have to appear in the menu's response to #children during the next 
>> render loop iteration.
>
>
> Well, there's a potential infinite recursion here - if you're really 
> starting at the top of the tree, that means you're including the menu 
> when searching for menu items, which means you're including its items, 
> and if any of *those* components has menu items...

I haven't run into any problems with infinite recursion...well, untill I 
started rebuilding the menu inside #children which I can manage easily 
with a flag.  My menu doesn't offer any menu items, it simply holds 
them.  Only components that offer menu items are visited during the tree 
traversal.  So, there's an asymmetry here, maybe not what you expected.

>
> But assuming that's not happening, this shouldn't be a problem, at 
> least not unless you're worried about efficiency.  Just have a 
> #menuItems method that rebuilds the list of components on the fly, and 
> use it from both #children and #renderContentOn:.  Don't worry about 
> the callback processing phase, or which render loop you're in. just 
> make sure that #children and #renderContentOn: are in agreement about 
> what the children are at any given time.

That's where I started but it doesn't seem to work. I think the problem 
has to do with identity of the callback "owner".  Every time I build the 
menu item list I get a fresh list of SCMenuItem instances.  In 
WACallbackStream>>processCallbacksWithOwner: you use #== to test if the 
callback's owner is the component in question.  In my case, two separate 
calls which rebuild my menus will produce two separate sets of menu 
items.  So, upon rendering I create a set of menu items with callbacks 
but upon traveral for callback handling I create a new set of 
instances.  That made me think that I needed to create the menu items 
only once right after callback processing was complete.  I don't want to 
cache the menu items in the subcomponents...that would be horribly 
tedious when developing new components.  Any suggestions.  I have 
attached my code and test cases (sorry for the separate files...how does 
one normally package up parts of class categories/packages for easy 
filein?).

>
> Now, it sounds like maybe you're trying to cache these components 
> between those two calls.  If so, why?  If it's for efficiency, then 
> profile and make sure it's actually worth it first (I'd be 
> surprised).  If it's because new instances of the menu item components 
> are created each time you ask for them, then you don't want components 
> at all - use some other objects that respond to #renderOn:, that 
> aren't expecting to have persistent state the way a component is, and 
> don't need to be included in #children at all.

No, it's not for efficiency...I just want to get it working :-)

>
> Avi
>
> _______________________________________________
> Seaside mailing list
> Seaside at lists.squeakfoundation.org
> http://lists.squeakfoundation.org/listinfo/seaside


-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 4 August 2004 at 1:24:45 pm'!
WAComponent subclass: #SCMenu
	instanceVariableNames: 'categories root rebuilding '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SC-Components'!

!SCMenu methodsFor: 'items' stamp: 'cds 8/3/2004 18:21'!
addItem: aMenuItem toCategory: aSymbol 
	(self itemsInCategory: aSymbol) value
		add: aMenuItem! !

!SCMenu methodsFor: 'items' stamp: 'cds 8/3/2004 14:24'!
categories
	^categories ifNil: [categories _  OrderedCollection new]! !

!SCMenu methodsFor: 'items' stamp: 'cds 8/3/2004 14:26'!
itemsInCategory: aSymbol 
	| result |
	^self categories
		detect: [:each | each key = aSymbol]
		ifNone: [result _ aSymbol -> OrderedCollection new.
			self categories add: result.
			result]! !

!SCMenu methodsFor: 'items' stamp: 'cds 8/4/2004 12:24'!
rebuild
	rebuilding _ true.
	categories _ nil.
	self visitTreeStartingAt: self root.
	rebuilding _ false.! !


!SCMenu methodsFor: 'tree' stamp: 'cds 8/4/2004 12:25'!
children
	| res |
	rebuilding
		ifTrue: [^ #()].
	self rebuild.
	res _ OrderedCollection new.
	self categories
		do: [:each | res addAll: each value].
	^ res! !

!SCMenu methodsFor: 'tree' stamp: 'cds 8/3/2004 18:25'!
visitComponent: aComponent 
	aComponent hasSCMenuItems
		ifTrue: [aComponent addMenuItemsTo: self]! !

!SCMenu methodsFor: 'tree' stamp: 'cds 8/3/2004 18:15'!
visitTreeStartingAt: aComponent 
	aComponent
		visiblePresentersDo: [:p | self visitComponent: p]! !


!SCMenu methodsFor: 'rendering' stamp: 'cds 8/4/2004 01:49'!
renderCategory: category on: html 
	category value isEmpty
		ifTrue: [^ nil].
	html heading: category key level: 4.
	category value
		do: [:item | html render: item] separatedBy: [html br]! !

!SCMenu methodsFor: 'rendering' stamp: 'cds 8/4/2004 12:02'!
renderContentOn: html 
	self rebuild.
	self categories
		do: [:category | self renderCategory: category on: html]
		separatedBy: [html hr].
! !


!SCMenu methodsFor: 'accessing' stamp: 'cds 8/3/2004 18:11'!
root
	^root! !

!SCMenu methodsFor: 'accessing' stamp: 'cds 8/3/2004 18:11'!
root: anObject
	root := anObject! !


!SCMenu methodsFor: 'initialization' stamp: 'cds 8/4/2004 12:24'!
initialize
	rebuilding _ false! !
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 4 August 2004 at 1:24:48 pm'!
WAComponent subclass: #SCMenuItem
	instanceVariableNames: 'text action id '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SC-Components'!

!SCMenuItem methodsFor: 'accessing' stamp: 'cds 8/3/2004 14:27'!
action
	^action! !

!SCMenuItem methodsFor: 'accessing' stamp: 'cds 8/3/2004 14:27'!
action: anObject
	action := anObject! !

!SCMenuItem methodsFor: 'accessing' stamp: 'cds 8/3/2004 15:33'!
id
	^id! !

!SCMenuItem methodsFor: 'accessing' stamp: 'cds 8/3/2004 15:33'!
id: anObject
	id := anObject! !

!SCMenuItem methodsFor: 'accessing' stamp: 'cds 8/3/2004 14:27'!
text
	^text! !

!SCMenuItem methodsFor: 'accessing' stamp: 'cds 8/3/2004 14:27'!
text: anObject
	text := anObject! !


!SCMenuItem methodsFor: 'rendering' stamp: 'cds 8/3/2004 18:00'!
renderContentOn: html 
	html cssId: id.
	html anchorWithAction: self action text: self text! !


!SCMenuItem methodsFor: 'comparing' stamp: 'cds 8/4/2004 13:05'!
= other
	^(other isKindOf: self class) and: [other id = self id and: [other text = self text]]! !

!SCMenuItem methodsFor: 'comparing' stamp: 'cds 8/4/2004 13:06'!
hash
	^self id hash bitXor: self text hash! !
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 4 August 2004 at 1:24:54 pm'!
SCComponentTestCase subclass: #SCMenuTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SC-Tests'!

!SCMenuTest methodsFor: 'tests' stamp: 'cds 8/4/2004 02:26'!
testNested
	self newApplicationWithRootClass: SCMenuTestClient.
	self establishSession.
	self
		followAnchor: (self lastResponse anchorWithId: 'child1').
	self assert: self component firstChild doingIt.
	self
		submitForm: self lastResponse forms first
		pressingButton: (self lastResponse forms first buttonWithValue: 'Ok').
	self deny: self component firstChild doingIt! !

!SCMenuTest methodsFor: 'tests' stamp: 'cds 8/4/2004 02:26'!
testNested2
	self newApplicationWithRootClass: SCMenuTestClient.
	self establishSession.
	self
		followAnchor: (self lastResponse anchorWithId: 'child2').
	self assert: self component secondChild doingIt.
	self
		submitForm: self lastResponse forms first
		pressingButton: (self lastResponse forms first buttonWithValue: 'Ok').
	self deny: self component secondChild doingIt! !

!SCMenuTest methodsFor: 'tests' stamp: 'cds 8/3/2004 18:24'!
testSimple
	self newApplicationWithRootClass: SCMenuTestClient.
	self establishSession.
	self
		followAnchor: (self lastResponse anchorWithId: 'parent').
	self assert: self component sayingHello.
	self
		submitForm: self lastResponse forms first
		pressingButton: (self lastResponse forms first buttonWithValue: 'Ok').
	self deny: self component sayingHello.! !

!SCMenuTest methodsFor: 'tests' stamp: 'cds 8/4/2004 03:02'!
testStructure
	| menu |
	self newApplicationWithRootClass: SCMenuTestClient.
	self establishSession.
	menu _ self component menu.
	self assert: menu categories size = 1.
	self assert: menu categories first key = #generic.
	self assert: menu categories first value size = 3.! !
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 4 August 2004 at 1:24:58 pm'!
WAComponent subclass: #SCMenuTestClientChild
	instanceVariableNames: 'number doingIt '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SC-Tests'!

!SCMenuTestClientChild methodsFor: 'menu items' stamp: 'cds 8/4/2004 00:05'!
addMenuItemsTo: aMenu 
	| i |
	i _ SCMenuItem new text: 'do nothing';
				
				action: [self doIt];
				 id: 'child' , self number printString;
				 yourself.
	aMenu addItem: i toCategory: #generic! !

!SCMenuTestClientChild methodsFor: 'menu items' stamp: 'cds 8/4/2004 00:06'!
doIt
	doingIt _ true.
	self inform: 'doing it'.
	doingIt _ false! !

!SCMenuTestClientChild methodsFor: 'menu items' stamp: 'cds 8/3/2004 18:01'!
hasSCMenuItems
	^ true! !


!SCMenuTestClientChild methodsFor: 'accessing' stamp: 'cds 8/4/2004 00:05'!
doingIt
	^doingIt! !

!SCMenuTestClientChild methodsFor: 'accessing' stamp: 'cds 8/3/2004 18:06'!
number
	^number! !

!SCMenuTestClientChild methodsFor: 'accessing' stamp: 'cds 8/3/2004 18:06'!
number: anObject
	number := anObject! !


!SCMenuTestClientChild methodsFor: 'rendering' stamp: 'cds 8/4/2004 00:09'!
renderContentOn: html
	html text: 'child'! !
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 4 August 2004 at 1:25:19 pm'!


!WAPresenter methodsFor: '*SC-Components' stamp: 'cds 8/4/2004 01:11'!
hasSCMenuItems
	^ false! !
-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 4 August 2004 at 1:30 pm'!
WAComponent subclass: #SCMenuTestClient
	instanceVariableNames: 'menu children sayingHello '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SC-Tests'!

!SCMenuTestClient methodsFor: 'initialization' stamp: 'cds 8/4/2004 11:53'!
initialize
	menu _ SCMenu new.
	menu root: self.
	children _ OrderedCollection new.
	children
		add: (SCMenuTestClientChild new number: 1).
	children
		add: (SCMenuTestClientChild new number: 2)! !


!SCMenuTestClient methodsFor: 'menu items' stamp: 'cds 8/3/2004 18:15'!
addMenuItemsTo: aMenu 
	| i |
	i _ SCMenuItem new text: 'say hello';
				
				action: [self sayHello];
				 id: 'parent';
				 yourself.
	aMenu addItem: i toCategory: #generic.! !

!SCMenuTestClient methodsFor: 'menu items' stamp: 'cds 8/3/2004 15:06'!
hasSCMenuItems
	^true! !

!SCMenuTestClient methodsFor: 'menu items' stamp: 'cds 8/3/2004 18:24'!
sayHello
	sayingHello _ true.
	self inform: 'Hello'.
	sayingHello _ false.! !


!SCMenuTestClient methodsFor: 'tree' stamp: 'cds 8/4/2004 11:54'!
children
	^ children copy add: menu; yourself! !

!SCMenuTestClient methodsFor: 'tree' stamp: 'cds 8/4/2004 02:25'!
firstChild
	^self children first! !

!SCMenuTestClient methodsFor: 'tree' stamp: 'cds 8/4/2004 02:26'!
secondChild
	^ self children second! !


!SCMenuTestClient methodsFor: 'rendering' stamp: 'cds 8/4/2004 13:29'!
renderContentOn: html 
	self children
		do: [:c | html render: c]! !


!SCMenuTestClient methodsFor: 'accessing' stamp: 'cds 8/4/2004 02:26'!
menu
	^menu! !

!SCMenuTestClient methodsFor: 'accessing' stamp: 'cds 8/3/2004 18:23'!
sayingHello
	^sayingHello! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

SCMenuTestClient class
	instanceVariableNames: ''!

!SCMenuTestClient class methodsFor: 'seaside' stamp: 'cds 8/4/2004 13:28'!
canBeRoot
	^true! !


More information about the Seaside mailing list