[Seaside] [Component] PIMListEditor

Giovanni Giorgi jj at objectsroot.com
Mon Dec 22 12:41:24 CET 2003


Hi all!
    As promised over two month ago, I have relased a small Seaside 
component.
I post here the first alpha release.
It is a small component for editing a list of key,pair data...
Please give me your feedback!
 From the class comment (yes I wrote class comment...and I am a little 
crazy I know ;)):
=================================
I model a Editor for Key,Pair with nice values.
    You should pass to me a SortedCollection with a good sort block
    if you like to keep your elements sorted.

I can also support closed key list. Give me an array of elements using 
the keyList: message.
The user can edit the key value, for improved flexibility.

*Usage Examples:

    Simple Usage:
        emailList _ PIMListEditor on: contact email.
        emailList fieldSize: 20.

        "Then use
        email render: html
        in a seaside component"

    Advanced Usage:
        phoneList _ PIMListEditor on: contact phone.
        phoneList fieldSize: 14.
        phoneList keyList: #( 'GSM' 'Office Phone' 'Home Phone').

Component Newbie Note:   
    I do not provide a form, so you must  embed me in your form code ;)

Author: jj at objectsroot.com
Please send me hints, bug reports and so on.
Download Url: not yet ready but will be http://cat.sf.net ;)
License: Same as Squeak License.


-- 
  [   [  [ JJ ]  ]   ]  | First, they ignore you. Then they laugh  
                        | at you. Then they fight you. Then you win
http://www.siforge.org  |          Mahatma Ghandi

-------------- next part --------------
'From Squeak3.6 of ''6 October 2003'' [latest update: #5424] on 22 December 2003 at 12:37:28 pm'!
WAComponent subclass: #PIMListEditor
	instanceVariableNames: 'valueList newKey newValue fieldSize keyList '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SIForgePIM-Components'!
!PIMListEditor commentStamp: 'gg 12/21/2003 12:35' prior: 0!
I model a Editor for Key,Pair with nice values.
	You should pass to me a SortedCollection with a good sort block 
	if you like to keep your elements sorted.

I can also support closed key list. Give me an array of elements using the keyList: message.
The user can edit the key value, for improved flexibility.

*Usage Examples:

	Simple Usage:
		emailList _ PIMListEditor on: contact email.
		emailList fieldSize: 20.

		"Then use 
		email render: html 
		in a seaside component"

	Advanced Usage:
		phoneList _ PIMListEditor on: contact phone.
		phoneList fieldSize: 14.
		phoneList keyList: #( 'GSM' 'Office Phone' 'Home Phone').

Component Newbie Note:	
	I do not provide a form, so you must  embed me in your form code ;)

Author: jj at objectsroot.com
Please send me hints, bug reports and so on.
Download Url: not yet ready but will be http://cat.sf.net ;)
License: Same as Squeak License.



!


!PIMListEditor methodsFor: 'initialization' stamp: 'gg 12/21/2003 11:31'!
initialize
	super initialize.	
	newKey _''.
	newValue _''.
	keyList _ nil.
	self fieldSize: 18.
	! !


!PIMListEditor methodsFor: 'rendering' stamp: 'gg 12/21/2003 11:44'!
renderAddEntryBox: html 
	| attribList |
	attribList _ {'size' -> self fieldSize}.
	html
		tableRowWith: [keyList
				ifNil: [html attributes: attribList.
					html
						textInputWithValue: ''
						callback: [:v | newKey _ v]]
				ifNotNil: [html attributes: {'size' -> 1}.
					html
						selectFromList: keyList
						selected: keyList first
						callback: [:v | newKey _ v]]]
		with: [html attributes: attribList;
				
				textInputWithValue: ''
				callback: [:v | newValue _ v].
			html attributes: {'title' -> 'Aggiungi un elemento'. 'id' -> 'vbutton'};
				
				submitButtonWithAction: [newKey ~= ''
						ifTrue: [valueList addLast: newKey -> newValue]]
				text: '+']! !

!PIMListEditor methodsFor: 'rendering' stamp: 'gg 12/21/2003 12:27'!
renderContentOn: html 
	"Non ha bisogno di avere un tasto di 'cancel' per ora"
	| key value attribList |
	attribList _ {'size' -> self fieldSize}.
	valueList reSort.
	
	html
		table: [" 
			html 
			tableRowWith: [html text: 'Denominazione'] 
			with: [html text: 'Valore'].
			"
			valueList
				associationsDo: [:assoc | 
					key _ assoc key.
					value _ assoc value.
					html
						tableRow: [html
								tableData: [html attributes: attribList;
										
										textInputWithValue: key
										callback: [:v | assoc key: v]].
							html
								tableData: [html attributes: attribList.
									html
										textInputWithValue: value
										callback: [:v | assoc value: v].
									html attributes: {'title' -> '!!Rimuovi definitivamente!!'. 'id' -> 'xbutton'};
										
										anchorWithAction: [valueList remove: assoc]
										text: 'X']]].
			self renderAddEntryBox: html.]! !


!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/15/2003 19:19'!
fieldSize
	"Answer the value of fieldSize"

	^ fieldSize! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/15/2003 19:19'!
fieldSize: anObject
	"Set the value of fieldSize"

	fieldSize _ anObject! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/21/2003 11:32'!
keyList: aListOfKey
	keyList _ aListOfKey.
	^aListOfKey.! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/19/2003 19:26'!
list
	"Answer the value of valueList"

	^ valueList! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/19/2003 19:32'!
list: aSortedCollection
	"Set the value of valueList"

	valueList _ (aSortedCollection reSort).! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/14/2003 19:02'!
newKey
	"Answer the value of newKey"

	^ newKey! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/14/2003 19:02'!
newKey: anObject
	"Set the value of newKey"

	newKey _ anObject! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/14/2003 19:02'!
newValue
	"Answer the value of newValue"

	^ newValue! !

!PIMListEditor methodsFor: 'accessing' stamp: 'gg 12/14/2003 19:02'!
newValue: anObject
	"Set the value of newValue"

	newValue _ anObject! !

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

PIMListEditor class
	instanceVariableNames: ''!

!PIMListEditor class methodsFor: 'initialize' stamp: 'gg 12/19/2003 19:26'!
on: aColletion
	|le|
	le _super new.
	le list: (aColletion asSortedCollection).
	^le.! !


More information about the Seaside mailing list