[Seaside] Mewa & latest seaside

Vadim Kolontsov vk at tvcom.ru
Wed May 12 19:11:44 CEST 2004


Adrian Lienhard wrote:

> You can get Mewa for Seaside 2.5 here: 
> http://kilana.unibe.ch:8888/Mewa/Mewa.Seaside2.5.al.13.mcz. Though, one 
> thing is not working properly yet: The editor for multiple 
> relationships. (I just haven't had time to figure out how I can easily 
> implement the newly added requirement to return the collection of child 
> components). 

It seems that it's easy to implement - see included changeset. Now 
example works just fine (including multiple relationships editor).

Best regards and thanks again,
Vadim.
-------------- next part --------------
'From Squeak3.7beta of ''1 April 2004'' [latest update: #5905] on 12 May 2004 at 9:05:19 pm'!
"Change Set:		Mewa
Date:			12 May 2004
Author:			Vadim Kolontsov

This changes allows Mewa to run on latest Seaside (2.5+) by adding children tracking." !

WAComponent subclass: #MWExample
	instanceVariableNames: 'batcher children'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Mewa-Example'!
WAComponent subclass: #MWVisitor
	instanceVariableNames: 'metaobject children'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Mewa-Visitors'!
MWVisitor subclass: #MWEditorVisitor
	instanceVariableNames: 'renderer validationErrors subForm'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Mewa-Visitors'!

!MWExample methodsFor: 'initialization' stamp: 'vk 5/12/2004 20:55'!
initialize
	| views |
	super initialize.
	views _ self session domainmodel persons asOrderedCollection collect: [ :each |
		MWListItemViewer metaobject: (
			each metaobject
				hideAttributeOf: #interests;
				hideAttributeOf: #phoneNumbers;
				yourself) ].

	batcher _ WABatchedList new
		items: views;
		batchSize: 5;
		yourself.
	
	children := OrderedCollection new.
	views do: [ :v | children add: v ].
        children add: batcher.
! !

!MWExample methodsFor: 'accessing' stamp: 'vk 5/12/2004 20:51'!
children

	^children.! !


!MWVisitor methodsFor: 'initialization' stamp: 'vk 5/12/2004 20:47'!
initializeWith: aMetaobject
	metaobject _ aMetaobject.
	children _ OrderedCollection new.! !

!MWVisitor methodsFor: 'accessing' stamp: 'vk 5/12/2004 20:48'!
addChild: anObject

	children add: anObject.! !

!MWVisitor methodsFor: 'accessing' stamp: 'vk 5/12/2004 20:46'!
children

	^ children asArray.! !


!MWEditorVisitor methodsFor: 'visiting' stamp: 'vk 5/12/2004 20:48'!
visitMultipleAttribute: aMultipleAttribute 
	| form editForm |
	aMultipleAttribute isReadOnly ifFalse: [
		self renderLabel: aMultipleAttribute label control: [
			aMultipleAttribute cache do: [ :each | 
				aMultipleAttribute itemSelectedToEdit = each 
					ifFalse: [
						| child |
						child := MWViewerVisitor model: each.
						self addChild: child.
						renderer render: child.
						renderer anchorWithAction: [ aMultipleAttribute itemSelectedToEdit: each ]
						text: 'edit'; space;
						anchorWithAction: [ aMultipleAttribute removeFromCache: each ] text: 'delete'.
						renderer break ]
					ifTrue: [
						editForm _ (self class model: each) subForm: true.
						self addChild: editForm.
						editForm onAnswer: [ :value | aMultipleAttribute itemSelectedToEdit: nil ].
						renderer render: editForm ] ] fixTemps.
					renderer break.
					aMultipleAttribute itemSelectedToEdit isNil ifTrue: [
						form _ (self class model: aMultipleAttribute baseClass new) subForm: true.
						self addChild: form.
						form onAnswer: [ :value |
							value ifNotNilDo: [ :newBaseObject | aMultipleAttribute addToCache: newBaseObject ] ].
							renderer render: form ] ] ]! !

!MWEditorVisitor methodsFor: 'initialization' stamp: 'vk 5/12/2004 20:47'!
initializeWith: aMetaobject
	super initializeWith: aMetaobject.
	self metaobject refreshCache.
	self subForm: false.! !

MWEditorVisitor removeSelector: #children!
MWVisitor removeSelector: #addEditor:!
MWVisitor removeSelector: #addViewer:!


More information about the Seaside mailing list